Report Typos and Errors    
Semi-Lagrangian Library
Modular library for kinetic and gyrokinetic simulations of plasmas in fusion energy devices.
sll_m_particle_mesh_coupling_spline_2d_feec.F90
Go to the documentation of this file.
1 
5 
7 
8 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
9 #include "sll_assert.h"
10 #include "sll_memory.h"
11 #include "sll_working_precision.h"
12 
13  use sll_m_low_level_bsplines, only: &
14  sll_s_uniform_bsplines_eval_basis
15 
18 
19  use sll_m_splines_pp, only : &
29 
30  use sll_m_particle_group_base, only: &
32 
33 
34  implicit none
35 
36  public :: &
38 
39  private
40 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
41 
44  ! Information about the 3d mesh
45  sll_real64 :: delta_x(2)
46  sll_real64 :: domain(2,2)
47  sll_real64 :: rdelta_x(2)
48 
49  ! Information about the particles
50  sll_int32 :: no_particles
51 
52  !
53  sll_int32 :: spline_degree
54  sll_int32 :: n_span
55  sll_int32 :: n_quad_points
56 
57  sll_real64, allocatable :: spline_val(:,:)
58  sll_real64, allocatable :: spline_0(:,:)
59  sll_real64, allocatable :: spline_1(:,:)
60  sll_real64, allocatable :: spline_val_more(:,:)
61  sll_real64, allocatable :: spline_2d(:,:)
62  sll_real64, allocatable :: j1d(:)
63  sll_real64, allocatable :: quad_xw(:,:)
64 
65 
66  sll_int32 :: dim
67  sll_int32 :: n_dofs
68  sll_int32 :: n_grid(2)
69 
70  type(sll_t_spline_pp_1d) :: spline_pp1d_0
71  type(sll_t_spline_pp_1d) :: spline_pp1d_1
72 
73  contains
74 
75  procedure :: add_charge => add_charge_single_spline_2d_feec
76  ! procedure :: add_charge_pp => add_charge_single_spline_pp_3d_feec !> Add charge of one particle
77  procedure :: add_current => add_current_spline_2d_feec
78  procedure :: add_current_update_v_component1 => add_current_update_v_primitive_component1_spline_2d_feec
79  procedure :: add_current_update_v_component2 => add_current_update_v_primitive_component2_spline_2d_feec
80  !procedure :: add_current_update_v_component3 => add_current_update_v_primitive_component3_spline_3d_feec !> Add current of one particle
81  procedure :: evaluate => evaluate_field_single_spline_2d_feec
82  procedure :: evaluate_pp => evaluate_field_single_spline_pp_2d_feec
83  procedure :: evaluate_multiple => evaluate_multiple_spline_2d_feec
84  !procedure :: update_jv !> helper function to compute the integral of j using Gauss quadrature
85  procedure :: add_particle_mass => add_particle_mass_spline_2d_feec
86  procedure :: init => init_spline_2d_feec
87  procedure :: free => free_spline_2d_feec
89 
90 
91 contains
92 
93 
94  !---------------------------------------------------------------------------!
96  subroutine add_charge_single_spline_2d_feec(self, position, marker_charge, degree, rho_dofs)
97  class( sll_t_particle_mesh_coupling_spline_2d_feec ), intent(inout) :: self
98  sll_real64, intent( in ) :: position(self%dim)
99  sll_real64, intent( in ) :: marker_charge
100  sll_int32, intent( in ) :: degree(2)
101  sll_real64, intent( inout ) :: rho_dofs(self%n_dofs)
102 
103  sll_int32 :: box(2)
104  sll_real64 :: xi(2)
105  sll_int32 :: index2d(2)
106  sll_int32 :: index1d
107  sll_int32 :: i,j
108 
109 
110  call convert_x_to_xbox( self, position, xi, box )
111 
112  self%spline_0 = 0.0_f64
113  do j=1,2
114  call sll_s_uniform_bsplines_eval_basis( degree(j), xi(j), self%spline_0(:,j) )
115  end do
116 
117  ! Build scaling with marker_charge into spline along first dimension
118  self%spline_0(:,1) = self%spline_0(:,1)*marker_charge
119 
120  box = box-degree
121  do j=1,degree(2)+1
122  index2d(2) = modulo(box(2)+j-2,self%n_grid(2))+1
123  do i=1,degree(1)+1
124  index2d(1) = modulo(box(1)+i-2,self%n_grid(1))+1
125  index1d = convert_index_2d_to_1d( index2d, self%n_grid )
126  rho_dofs(index1d) = rho_dofs(index1d) + &
127  (self%spline_0(i,1) * self%spline_0(j,2))
128  end do
129  end do
130 
131 
132  end subroutine add_charge_single_spline_2d_feec
133  !---------------------------------------------------------------------------!
135  subroutine add_particle_mass_spline_2d_feec(self, position, marker_charge, degree, particle_mass )
136  class( sll_t_particle_mesh_coupling_spline_2d_feec ), intent(inout) :: self
137  sll_real64, intent( in ) :: position(self%dim)
138  sll_real64, intent( in ) :: marker_charge
139  sll_int32, intent( in ) :: degree(2)
140  sll_real64, intent( inout ) :: particle_mass(:,:)
141 
142  sll_int32 :: box(2)
143  sll_real64 :: xi(2)
144  sll_int32 :: index2d(2)
145  sll_int32 :: index1d
146  sll_int32 :: i,j, col1, col2, ind
147  sll_real64 :: splineijk
148 
149 
150  call convert_x_to_xbox( self, position, xi, box )
151 
152 
153  ! Old version based on arbitrary degree splines
154  self%spline_0 = 0.0_f64
155  do j=1,2
156  call sll_s_uniform_bsplines_eval_basis( degree(j), xi(j), self%spline_0(:,j) )
157  end do
158 
159  ! 2d array combining first and second dimension
160  do j=1,degree(2)+1
161  do i=1,degree(1)+1
162  self%spline_2d(i,j) = self%spline_0(i,1)*self%spline_0(j,2)
163  end do
164  end do
165  ! TODO: Check if also 3d array would make sense
166 
167 
168  box = box-degree
169  do j=1,degree(2)+1
170  index2d(2) = modulo(box(2)+j-2,self%n_grid(2))+1
171  do i=1,degree(1)+1
172  index2d(1) = modulo(box(1)+i-2,self%n_grid(1))+1
173  index1d = convert_index_2d_to_1d( index2d, self%n_grid )
174  ind = 1+(degree(1)+1-i)+(degree(2)+1-j)*(2*degree(1)+1)
175  splineijk = marker_charge * self%spline_2d(i,j)
176  do col2 = 1,degree(2)+1
177  do col1 = 1,degree(1)+1
178  particle_mass(ind, index1d) = &
179  particle_mass( ind, index1d) + &
180  splineijk * &
181  self%spline_2d(col1,col2)
182  ind = ind+1
183  end do
184  ind = ind+degree(1)
185  end do
186  ind = ind+( degree(2) ) * (2*degree(1)+1)
187  end do
188  end do
189 
190 
191 
192 
193  end subroutine add_particle_mass_spline_2d_feec
194 
195 
196 !!$ !---------------------------------------------------------------------------!
197 !!$ !> Add charge of one particle
198 !!$ subroutine add_charge_single_spline_pp_3d_feec(self, position, marker_charge, degree, rho_dofs)
199 !!$ class( sll_t_particle_mesh_coupling_spline_2d_feec ), intent(inout) :: self !< kernel smoother object
200 !!$ sll_real64, intent( in ) :: position(self%dim) !< Position of the particle
201 !!$ sll_real64, intent( in ) :: marker_charge !< Particle weights time charge
202 !!$ sll_int32, intent( in ) :: degree(3) !< Spline degree along each dimension
203 !!$ sll_real64, intent( inout ) :: rho_dofs(self%n_dofs) !< Coefficient vector of the charge distribution
204 !!$
205 !!$ sll_int32 :: box(3)
206 !!$ sll_real64 :: xi(3)
207 !!$ sll_int32 :: index3d(3)
208 !!$ sll_int32 :: index1d
209 !!$ sll_int32 :: i,j,k
210 !!$
211 !!$
212 !!$ call convert_x_to_xbox( self, position, xi, box )
213 !!$
214 !!$ self%spline_0 = 0.0_f64
215 !!$ call sll_s_spline_pp_horner_m_3d (self%spline_pp_0, self%spline_0, degree, xi)
216 !!$ ! USE THIS IF DEGREE IS NOT ALLWAYS SELF%SPLINE_DEGREE
217 !!$ !do j=1,2
218 !!$ ! if (degree(j) == self%spline_degree) then
219 !!$ ! call sll_s_spline_pp_horner_m_1d(self%spline_pp1d_0, self%spline_0(:,j), self%spline_degree, xi(j))
220 !!$ ! else
221 !!$ ! call sll_s_spline_pp_horner_m_1d(self%spline_pp1d_1, self%spline_0(:,j), self%spline_degree-1, xi(j))
222 !!$ ! end if
223 !!$ !end do
224 !!$
225 !!$
226 !!$ ! Build scaling with marker_charge into spline along first dimension
227 !!$ self%spline_0(:,1) = self%spline_0(:,1)*marker_charge
228 !!$ ! 2d array combining first and second dimension
229 !!$ do j=1,degree(2)+1
230 !!$ do i=1,degree(1)+1
231 !!$ self%spline_2d(i,j) = self%spline_0(i,1)*self%spline_0(j,2)
232 !!$ end do
233 !!$ end do
234 !!$
235 !!$
236 !!$ box = box-degree
237 !!$ do k=1,degree(3)+1
238 !!$ index3d(3) = modulo(box(3)+k-2,self%n_grid(3))+1
239 !!$ do j=1,degree(2)+1
240 !!$ index3d(2) = modulo(box(2)+j-2,self%n_grid(2))+1
241 !!$ do i=1,degree(1)+1
242 !!$ index3d(1) = modulo(box(1)+i-2,self%n_grid(1))+1
243 !!$ index1d = convert_index_3d_to_1d( index3d, self%n_grid )
244 !!$ rho_dofs(index1d) = rho_dofs(index1d) + &
245 !!$ (self%spline_2d(i,j) * &
246 !!$ self%spline_0(k,3) )
247 !!$ end do
248 !!$ end do
249 !!$ end do
250 !!$
251 !!$
252 !!$ end subroutine add_charge_single_spline_pp_3d_feec
253 
254 
255  pure function convert_index_2d_to_1d( index2d, n_grid ) result( index1d )
256  sll_int32, intent( in ) :: index2d(2)
257  sll_int32, intent( in ) :: n_grid(2)
258  sll_int32 :: index1d
259 
260  index1d = index2d(1) + (index2d(2)-1)*n_grid(1)
261 
262 
263  end function convert_index_2d_to_1d
264 
265  subroutine convert_x_to_xbox( self, position, xi, box )
266  class( sll_t_particle_mesh_coupling_spline_2d_feec ), intent(inout) :: self
267  sll_real64, intent( in ) :: position(self%dim)
268  sll_real64, intent( out ) :: xi(self%dim)
269  sll_int32, intent( out ) :: box(self%dim)
270 
271  xi = (position - self%domain(:,1)) * self%rdelta_x
272  box = ceiling( xi )
273  xi = xi - real(box-1, f64)
274 
275  end subroutine convert_x_to_xbox
276 
277 
278 
280  subroutine add_current_spline_2d_feec (self, position_old, position_new, marker_charge, qoverm, bfield_dofs, vi, j_dofs)
281  class(sll_t_particle_mesh_coupling_spline_2d_feec), intent(inout) :: self
282  sll_real64, intent(in) :: position_old(self%dim)
283  sll_real64, intent(in) :: position_new(self%dim)
284  sll_real64, intent(in) :: marker_charge
285  sll_real64, intent(in) :: qoverm
286  sll_real64, intent(in) :: bfield_dofs(self%n_dofs*3)
287  sll_real64, intent(inout) :: vi(:)
288  sll_real64, intent(inout) :: j_dofs(self%n_dofs)
289 
290 
291  sll_int32 :: box(2), boxnew(2), boxold(2), local_size(2)
292  sll_int32 :: degree
293  sll_int32 :: index2d(2)
294  sll_int32 :: index1d
295  sll_int32 :: i,j
296  sll_real64 :: xnew(2), xold(2)
297  sll_int32 :: component
298 
299  degree = self%spline_degree
300  component = 1
301 
302  call convert_x_to_xbox( self, position_old, xold, boxold )
303  call convert_x_to_xbox( self, position_new, xnew, boxnew )
304 
305  local_size = abs(boxnew-boxold)+degree
306  local_size(2) = degree+1
307 
308  do i=1, degree
309  self%spline_1(i,1) = sll_f_spline_pp_horner_1d(degree, self%spline_pp1d_1%poly_coeffs_fpa, xold(1), i) &
310  * self%delta_x(1)
311  self%spline_1(i,2) = sll_f_spline_pp_horner_1d(degree, self%spline_pp1d_1%poly_coeffs_fpa, xnew(1), i) &
312  * self%delta_x(1)
313  end do
314 
315  if (position_old(1) < position_new(1) ) then
316  self%j1d(local_size(component)-degree+1:local_size(component)) = self%spline_1(:,2)
317  self%j1d(1:local_size(component)-degree) = self%delta_x(1)
318  self%j1d(1:degree) = self%j1d(1:degree) - self%spline_1(:,1)
319  else
320  self%j1d(1:local_size(component)-degree) = -self%delta_x(1)
321  self%j1d(local_size(component)-degree+1:local_size(component)) = -self%spline_1(:,1)
322  self%j1d(1:degree) = self%j1d(1:degree) + self%spline_1(:,2)
323  end if
324 
325  self%spline_0 = 0.0_f64
326  do j=1,2
327  if (j .ne. component ) then
328  call sll_s_uniform_bsplines_eval_basis( self%spline_degree, xold(j), self%spline_0(:,j) )
329  end if
330  end do
331 
332  box = boxold-degree
333  box(component) = min(boxnew(component), boxold(component))-degree+1
334  do j=1,local_size(2)
335  index2d(2) = modulo(box(2)+j-2,self%n_grid(2))+1
336  do i=1,local_size(1)
337  index2d(1) = modulo(box(1)+i-2,self%n_grid(1))+1
338  index1d = convert_index_2d_to_1d( index2d, self%n_grid )
339  j_dofs(index1d) = j_dofs(index1d) + &
340  marker_charge * self%j1d( i ) * &
341  self%spline_0(j,2)
342  end do
343  end do
344 
345 
346 
347  end subroutine add_current_spline_2d_feec
348 
349 
350 
352  subroutine add_current_update_v_primitive_component1_spline_2d_feec (self, position_old, position_new, marker_charge, qoverm, bfield_dofs, vi, j_dofs)
353  class(sll_t_particle_mesh_coupling_spline_2d_feec), intent(inout) :: self
354  sll_real64, intent(in) :: position_old(self%dim)
355  sll_real64, intent(in) :: position_new
356  sll_real64, intent(in) :: marker_charge
357  sll_real64, intent(in) :: qoverm
358  sll_real64, intent(in) :: bfield_dofs(self%n_dofs*3)
359  sll_real64, intent(inout) :: vi(:)
360  sll_real64, intent(inout) :: j_dofs(self%n_dofs)
361 
362 
363  sll_int32 :: box(2), boxnew, boxold
364  sll_real64 :: xi(2)
365  sll_int32 :: index2d(2)
366  sll_int32 :: index1d
367  sll_int32 :: i,j
368  sll_real64 :: xnew
369  sll_real64 :: vt(2), vtt2, vtt3
370  sll_int32 :: start1, start2
371  sll_int32 :: component
372  sll_int32 :: stride
373  sll_int32 :: local_size
374  sll_int32 :: degree
375 
376  component = 1
377  start1 = 2*self%n_dofs
378  start2 = self%n_dofs
379  stride = 1
380  degree = self%spline_degree
381 
382  call convert_x_to_xbox( self, position_old, xi, box )
383 
384  ! Convert position_new to xbox
385  xnew = (position_new-self%domain(component,1)) * self%rdelta_x(component)
386  boxnew = ceiling(xnew)
387  xnew = xnew-real(boxnew-1, f64)
388  boxold = box(component)
389 
390  !-- For current along x1
391  local_size = abs(boxnew-boxold)+degree
392 
393  ! For j=component, we need the primitive
394  do i=1, degree
395  self%spline_1(i,1) = sll_f_spline_pp_horner_1d(degree, &
396  self%spline_pp1d_1%poly_coeffs_fpa, xi(component), i) &
397  * self%delta_x(component)
398  self%spline_1(i,2) = sll_f_spline_pp_horner_1d(degree, &
399  self%spline_pp1d_1%poly_coeffs_fpa, xnew, i) &
400  * self%delta_x(component)
401  end do
402 
403  !print*, boxold, boxnew
404  !print*, position_old, position_new
405  !print*, local_size, degree
406 
407  if (position_old(component) .le. position_new ) then
408  self%j1d(local_size-degree+1:local_size) = self%spline_1(:,2)
409  self%j1d(1:local_size-degree) = self%delta_x(component)
410  self%j1d(1:degree) = self%j1d(1:degree) - self%spline_1(:,1)
411  else
412  self%j1d(1:local_size-degree) = -self%delta_x(component)
413  self%j1d(local_size-degree+1:local_size) = -self%spline_1(:,1)
414  self%j1d(1:degree) = self%j1d(1:degree) + self%spline_1(:,2)
415  end if
416  !----
417 
418 
419  ! Achtung wir brauchen nun splines von beidem Grad
420  self%spline_0 = 0.0_f64
421  self%spline_1 = 0.0_f64
422  do j=1,2
423  if (j .ne. component ) then
424  call sll_s_spline_pp_horner_m_1d(self%spline_pp1d_0, self%spline_0(:,j), self%spline_degree, xi(j))
425  call sll_s_spline_pp_horner_m_1d(self%spline_pp1d_1, self%spline_1(:,j), self%spline_degree-1, xi(j))
426  end if
427  end do
428 
429  box(component) = box(component)-self%spline_degree+1
430  box(2) = box(2) - self%spline_degree
431 
432  ! Define the range of the first component
433  if (boxold<boxnew) then
434  box(component) = boxold-self%spline_degree+1
435  else
436  box(component) = boxnew-self%spline_degree+1
437  end if
438 
439 
440  vtt2 = 0.0_f64
441  vtt3 = 0.0_f64
442  do j=1,self%spline_degree+1
443  index2d(2) = modulo(box(2)+j-2,self%n_grid(2))+1
444 
445  vt = 0.0_f64
446 
447  do i=1,local_size
448  index2d(1) = modulo(box(1)+i-2,self%n_grid(1))+1
449  index1d = convert_index_2d_to_1d( index2d, self%n_grid )
450  j_dofs(index1d) = j_dofs(index1d) + self%j1d(i) * &
451  self%spline_0(j,2)*marker_charge
452 
453  vt(1) = vt(1) + bfield_dofs(start1+index1d)*self%j1d(i)
454  vt(2) = vt(2) + bfield_dofs(start2+index1d)*self%j1d(i)
455 
456  end do
457 
458  if (j>1) then
459  vtt2 = vtt2 + vt(1)*self%spline_1(j-1, 2)
460  end if
461  vtt3 = vtt3 - vt(2)*self%spline_0(j, 2)
462 
463  end do
464  vi(2) = vi(2) - qoverm*vtt2
465  vi(3) = vi(3) - qoverm*vtt3
466 
468 
469  subroutine add_current_update_v_primitive_component2_spline_2d_feec (self, position_old, position_new, marker_charge, qoverm, bfield_dofs, vi, j_dofs)
470  class(sll_t_particle_mesh_coupling_spline_2d_feec), intent(inout) :: self
471  sll_real64, intent(in) :: position_old(self%dim)
472  sll_real64, intent(in) :: position_new
473  sll_real64, intent(in) :: marker_charge
474  sll_real64, intent(in) :: qoverm
475  sll_real64, intent(in) :: bfield_dofs(self%n_dofs*3)
476  sll_real64, intent(inout) :: vi(:)
477  sll_real64, intent(inout) :: j_dofs(self%n_dofs)
478 
479 
480 
481  sll_int32 :: box(2), boxnew, boxold
482  sll_real64 :: xi(2)
483  sll_int32 :: index2d(2)
484  sll_int32 :: index1d
485  sll_int32 :: i,j
486  sll_real64 :: xnew
487  sll_real64 :: vt(2), vtt2, vtt3
488  sll_int32 :: start1, start2
489  sll_int32 :: component, local_size
490  sll_int32 :: stride
491  sll_int32 :: degree
492 
493  component = 2
494  start1 = 2*self%n_dofs !
495  start2 = 0!
496  stride = self%n_grid(1)
497  degree = self%spline_degree
498 
499  call convert_x_to_xbox( self, position_old, xi, box )
500 
501  ! TODO: Umstellen von 1d function of ceiling statt floor
502  ! Convert position_new to xbox
503  xnew = (position_new-self%domain(component,1)) * self%rdelta_x(component)
504  boxnew = ceiling(xnew)
505  xnew = xnew-real(boxnew-1, f64)
506  boxold = box(component)
507 
508  !-- For current along x2
509  local_size = abs(boxnew-boxold)+degree
510 
511  ! For j=component, we need the primitive
512  do i=1, degree
513  self%spline_1(i,1) = sll_f_spline_pp_horner_1d(degree, &
514  self%spline_pp1d_1%poly_coeffs_fpa, xi(component), i) &
515  * self%delta_x(component)
516  self%spline_1(i,2) = sll_f_spline_pp_horner_1d(degree, &
517  self%spline_pp1d_1%poly_coeffs_fpa, xnew, i) &
518  * self%delta_x(component)
519  end do
520 
521  if (position_old(component) .le. position_new ) then
522  self%j1d(local_size-degree+1:local_size) = self%spline_1(:,2)
523  self%j1d(1:local_size-degree) = self%delta_x(component)
524  self%j1d(1:degree) = self%j1d(1:degree) - self%spline_1(:,1)
525  else
526  self%j1d(1:local_size-degree) = -self%delta_x(component)
527  self%j1d(local_size-degree+1:local_size) = -self%spline_1(:,1)
528  self%j1d(1:degree) = self%j1d(1:degree) + self%spline_1(:,2)
529  end if
530  !----
531 
532 
533  ! Achtung wir brauchen nun splines von beidem Grad
534  self%spline_0 = 0.0_f64
535  self%spline_1 = 0.0_f64
536  do j=1,2
537  if (j .ne. component ) then
538  call sll_s_spline_pp_horner_m_1d(self%spline_pp1d_0, self%spline_0(:,j), self%spline_degree, xi(j))
539  call sll_s_spline_pp_horner_m_1d(self%spline_pp1d_1, self%spline_1(:,j), self%spline_degree-1, xi(j))
540  end if
541  end do
542 
543  box(1) = box(1) - self%spline_degree
544 
545  ! Define the range of the first component
546  if (boxold<boxnew) then
547  box(component) = boxold-self%spline_degree+1
548  else
549  box(component) = boxnew-self%spline_degree+1
550  end if
551 
552  vtt2 = 0.0_f64
553  vtt3 = 0.0_f64
554  do j=1,self%spline_degree+1
555  index2d(1) = modulo(box(1)+j-2,self%n_grid(1))+1
556  vt = 0.0_f64
557  do i=1,local_size
558  index2d(2) = modulo(box(2)+i-2,self%n_grid(2))+1
559  index1d = convert_index_2d_to_1d( index2d, self%n_grid )
560  j_dofs(index1d) = j_dofs(index1d) + self%j1d(i) * &
561  self%spline_0(j,1) * marker_charge
562 
563  vt(1) = vt(1) + bfield_dofs(start1+index1d)*self%j1d(i)
564  vt(2) = vt(2) + bfield_dofs(start2+index1d)*self%j1d(i)
565  end do
566 
567  if (j>1) then
568  vtt2 = vtt2 + vt(1)*self%spline_1(j-1, 1)
569  end if
570  vtt3 = vtt3 + vt(2)*self%spline_0(j, 1)
571 
572  end do
573  vi(1) = vi(1) + qoverm*vtt2
574  vi(3) = vi(3) - qoverm*vtt3
575 
577 
578 
579  !---------------------------------------------------------------------------!
581  subroutine evaluate_field_single_spline_2d_feec(self, position, degree, field_dofs, field_value)
582  class(sll_t_particle_mesh_coupling_spline_2d_feec), intent( inout ) :: self
583  sll_real64, intent( in ) :: position(self%dim)
584  sll_int32 , intent( in ) :: degree(self%dim)
585  sll_real64, intent( in ) :: field_dofs(self%n_dofs)
586  sll_real64, intent( out ) :: field_value
587 
588  sll_int32 :: i,j
589  sll_int32 :: box(2)
590  sll_int32 :: index2d(2)
591  sll_int32 :: index1d
592  sll_real64 :: xi(2)
593 
594  ! TODO: Optimize by sum factorization
595 
596  call convert_x_to_xbox( self, position, xi, box )
597 
598  do j=1,2
599  call sll_s_uniform_bsplines_eval_basis( degree(j), xi(j), self%spline_val(1:degree(j)+1,j) )
600  end do
601 
602  field_value = 0.0_f64
603  box = box-degree
604  do j=1,degree(2)+1
605  index2d(2) = modulo(box(2)+j-2,self%n_grid(2))+1
606  do i=1,degree(1)+1
607  index2d(1) = modulo(box(1)+i-2,self%n_grid(1))+1
608  index1d = convert_index_2d_to_1d( index2d, self%n_grid )
609  field_value = field_value + &
610  field_dofs(index1d) * &
611  self%spline_val(i,1) * self%spline_val(j,2)
612  end do
613  end do
614 
616 
617  !---------------------------------------------------------------------------!
619  subroutine evaluate_field_single_spline_pp_2d_feec(self, position, degree, field_dofs_pp, field_value)
620  class(sll_t_particle_mesh_coupling_spline_2d_feec), intent( inout ) :: self
621  sll_real64, intent( in ) :: position(self%dim)
622  sll_int32 , intent( in ) :: degree(self%dim)
623  sll_real64, intent( in ) :: field_dofs_pp(:,:)
624  sll_real64, intent( out ) :: field_value
625 
626  sll_int32 :: box(3)
627  sll_real64 :: xi(3)
628 
629  call convert_x_to_xbox( self, position, xi, box )
630 
631  field_value = sll_f_spline_pp_horner_2d(degree, field_dofs_pp, xi, box,self%n_grid)
632 
634 
635 
636 
637  !---------------------------------------------------------------------------!
639  subroutine evaluate_multiple_spline_2d_feec(self, position, components, field_dofs, field_value)
640  class(sll_t_particle_mesh_coupling_spline_2d_feec), intent( inout ) :: self
641  sll_real64, intent( in ) :: position(self%dim)
642  sll_int32, intent(in) :: components(:)
643  sll_real64, intent( in ) :: field_dofs(:,:)
644  sll_real64, intent(out) :: field_value(:)
645 
646 
647 
648  end subroutine evaluate_multiple_spline_2d_feec
649 
651  subroutine init_spline_2d_feec ( self, n_grid, domain, no_particles, spline_degree )
652  class(sll_t_particle_mesh_coupling_spline_2d_feec), intent( out ) :: self
653  sll_int32, intent(in) :: n_grid(2)
654  sll_real64, intent(in) :: domain(2,2)
655  sll_int32, intent(in) :: no_particles
656  sll_int32, intent(in) :: spline_degree
657 
658  self%dim = 2
659 
660  ! Store grid information
661  self%domain = domain
662  self%n_grid = n_grid
663  self%n_dofs = product(n_grid)
664  self%delta_x = (self%domain(:,2)-self%domain(:,1))/real(n_grid, f64)
665  self%rdelta_x = 1.0_f64/self%delta_x
666 
667  ! Store basis function information
668  self%no_particles = no_particles
669 
670  ! Initialize information on the spline
671  self%spline_degree = spline_degree
672  self%n_span = spline_degree + 1
673 
674 
675  self%n_quad_points = (self%spline_degree+2)/2
676  allocate( self%quad_xw(2,self%n_quad_points) )
677  ! normalized Gauss Legendre points and weights
678  self%quad_xw = sll_f_gauss_legendre_points_and_weights(self%n_quad_points)
679 
680 
681  allocate( self%spline_val(self%n_span,2) )
682  allocate( self%spline_val_more(self%n_span,2) )
683  allocate( self%spline_0(self%n_span,2) )
684  allocate( self%spline_1(self%n_span-1,2) )
685  allocate( self%j1d( maxval(self%n_grid) ))
686  allocate( self%spline_2d(self%n_span, self%n_span) )
687 
688 
689 !!$ call sll_s_spline_pp_init_3d(self%spline_pp_0, [spline_degree,spline_degree,spline_degree], n_grid)
690 !!$ call sll_s_spline_pp_init_3d(self%spline_pp_11, [spline_degree-1,spline_degree,spline_degree], n_grid)
691 !!$ call sll_s_spline_pp_init_3d(self%spline_pp_12, [spline_degree,spline_degree-1,spline_degree], n_grid)
692 !!$ call sll_s_spline_pp_init_3d(self%spline_pp_13, [spline_degree,spline_degree,spline_degree-1], n_grid)
693 !!$ call sll_s_spline_pp_init_3d(self%spline_pp_21, [spline_degree,spline_degree-1,spline_degree-1], n_grid)
694 !!$ call sll_s_spline_pp_init_3d(self%spline_pp_22, [spline_degree-1,spline_degree,spline_degree-1], n_grid)
695 !!$ call sll_s_spline_pp_init_3d(self%spline_pp_23, [spline_degree-1,spline_degree-1,spline_degree], n_grid)
696 
697  call sll_s_spline_pp_init_1d( self%spline_pp1d_0, spline_degree, n_grid(1) )
698  call sll_s_spline_pp_init_1d( self%spline_pp1d_1, spline_degree-1, n_grid(1) )
699 
700  end subroutine init_spline_2d_feec
701 
702 
704  subroutine free_spline_2d_feec(self)
705  class(sll_t_particle_mesh_coupling_spline_2d_feec), intent( inout ) :: self
706 
707  deallocate( self%quad_xw)
708  deallocate( self%spline_val)
709  deallocate( self%spline_val_more)
710  deallocate( self%spline_0)
711  deallocate( self%spline_1)
712  deallocate( self%j1d)
713 
714  !call sll_s_spline_pp_free_3d(self%spline_pp_0)
715 
716  end subroutine free_spline_2d_feec
717 
718 
real(kind=f64) function, dimension(2, 1:npoints), public sll_f_gauss_legendre_points_and_weights(npoints, a, b)
Returns a 2d array of size (2,npoints) containing gauss-legendre points and weights in the interval [...
Low level arbitrary degree splines.
Particle mesh coupling for 3d with splines of arbitrary degree placed on a uniform tensor product mes...
subroutine add_charge_single_spline_2d_feec(self, position, marker_charge, degree, rho_dofs)
Destructor.
subroutine evaluate_field_single_spline_pp_2d_feec(self, position, degree, field_dofs_pp, field_value)
Evaluate field at at position position.
subroutine add_current_spline_2d_feec(self, position_old, position_new, marker_charge, qoverm, bfield_dofs, vi, j_dofs)
Add current for one particle.
subroutine add_current_update_v_primitive_component2_spline_2d_feec(self, position_old, position_new, marker_charge, qoverm, bfield_dofs, vi, j_dofs)
subroutine add_current_update_v_primitive_component1_spline_2d_feec(self, position_old, position_new, marker_charge, qoverm, bfield_dofs, vi, j_dofs)
Add current for one particle and update v (according to H_p1 part in Hamiltonian splitting)
subroutine evaluate_multiple_spline_2d_feec(self, position, components, field_dofs, field_value)
Evaluate several fields at position position.
pure integer(kind=i32) function convert_index_2d_to_1d(index2d, n_grid)
subroutine init_spline_2d_feec(self, n_grid, domain, no_particles, spline_degree)
Constructor.
subroutine add_particle_mass_spline_2d_feec(self, position, marker_charge, degree, particle_mass)
Add charge of one particle.
subroutine evaluate_field_single_spline_2d_feec(self, position, degree, field_dofs, field_value)
Evaluate field at at position position.
Splines in pp form.
subroutine, public sll_s_spline_pp_init_3d(self, degree, n_cells, boundary)
Initialize sll_t_spline_pp_3d object.
real(kind=f64) function, public sll_f_spline_pp_horner_2d(degree, pp_coeffs, x, indices, n_cells)
Perform a 2d hornerschema on the pp_coeffs at the indices.
subroutine, public sll_s_spline_pp_horner_m_3d(self, val, degree, x)
Perform three times a 1d hornerschema on the poly_coeffs.
subroutine, public sll_s_spline_pp_free_3d(self)
Destructor 3d.
subroutine, public sll_s_spline_pp_init_1d(self, degree, n_cells, boundary)
Initialize sll_t_spline_pp_1d object (Set poly_coeffs depending on degree)
subroutine, public sll_s_spline_pp_horner_m_1d(self, val, degree, x)
Perform a 1d hornerschema on the poly_coeffs.
real(kind=f64) function, public sll_f_spline_pp_horner_1d(degree, pp_coeffs, x, index)
Perform a 1d hornerschema on the pp_coeffs at index.
Particle mesh coupling in 3d based on (arbitrary degree) spline on a tensor product uniform mesh.
    Report Typos and Errors