Report Typos and Errors    
Semi-Lagrangian Library
Modular library for kinetic and gyrokinetic simulations of plasmas in fusion energy devices.
sll_m_maxwell_3d_pstd.F90
Go to the documentation of this file.
1 !**************************************************************
2 ! Copyright INRIA
3 !
4 ! This code SeLaLib (for Semi-Lagrangian-Library)
5 ! is a parallel library for simulating the plasma turbulence
6 ! in a tokamak.
7 !
8 ! This software is governed by the CeCILL-B license
9 ! under French law and abiding by the rules of distribution
10 ! of free software. You can use, modify and redistribute
11 ! the software under the terms of the CeCILL-B license as
12 ! circulated by CEA, CNRS and INRIA at the following URL
13 ! "http://www.cecill.info".
14 !**************************************************************
15 
16 #include "sll_fftw.h"
17 
18 #define D_DX(field) \
19 self%d_dx = field; \
20 call sll_s_fft_exec_r2c_1d(self%fwx, self%d_dx, self%tmp_x); \
21 self%tmp_x(2:nc_x/2 + 1) = -cmplx(0.0_f64, self%kx(2:nc_x/2 + 1), kind=f64)*self%tmp_x(2:nc_x/2 + 1); \
22 call sll_s_fft_exec_c2r_1d(self%bwx, self%tmp_x, self%d_dx); \
23 self%d_dx = self%d_dx/nc_x
24 
25 #define D_DY(field) \
26 self%d_dy = field; \
27 call sll_s_fft_exec_r2c_1d(self%fwy, self%d_dy, self%tmp_y); \
28 self%tmp_y(2:nc_y/2 + 1) = -cmplx(0.0_f64, self%ky(2:nc_y/2 + 1), kind=f64)*self%tmp_y(2:nc_y/2 + 1); \
29 call sll_s_fft_exec_c2r_1d(self%bwy, self%tmp_y, self%d_dy); \
30 self%d_dy = self%d_dy/nc_y
31 
32 #define D_DZ(field) \
33 self%d_dz = field; \
34 call sll_s_fft_exec_r2c_1d(self%fwz, self%d_dz, self%tmp_z); \
35 self%tmp_z(2:nc_z/2 + 1) = -cmplx(0.0_f64, self%kz(2:nc_z/2 + 1), kind=f64)*self%tmp_z(2:nc_z/2 + 1); \
36 call sll_s_fft_exec_c2r_1d(self%bwz, self%tmp_z, self%d_dz); \
37 self%d_dz = self%d_dz/nc_z
38 
66 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
67 #include "sll_memory.h"
68 #include "sll_working_precision.h"
69 #include "sll_maxwell_solvers_macros.h"
70 
71  use sll_m_constants, only: sll_p_pi
72 
73  use sll_m_fft
74 
75  implicit none
76 
78  type, public :: sll_t_maxwell_3d_pstd
79  private
80  sll_int32 :: nc_x
81  sll_int32 :: nc_y
82  sll_int32 :: nc_z
83  sll_real64, dimension(:), pointer :: d_dx
84  sll_real64, dimension(:), pointer :: d_dy
85  sll_real64, dimension(:), pointer :: d_dz
86  sll_real64, dimension(:), pointer :: kx
87  sll_real64, dimension(:), pointer :: ky
88  sll_real64, dimension(:), pointer :: kz
89  type(sll_t_fft) :: fwx
90  type(sll_t_fft) :: fwy
91  type(sll_t_fft) :: fwz
92  type(sll_t_fft) :: bwx
93  type(sll_t_fft) :: bwy
94  type(sll_t_fft) :: bwz
95  sll_comp64, pointer :: tmp_x(:)
96  sll_comp64, pointer :: tmp_y(:)
97  sll_comp64, pointer :: tmp_z(:)
98  sll_int32 :: polarization
99  sll_real64 :: e_0
100  sll_real64 :: mu_0
101  end type sll_t_maxwell_3d_pstd
102 
103 contains
104 
106  subroutine sll_s_maxwell_3d_pstd_init(self, xmin, xmax, nc_x, &
107  ymin, ymax, nc_y, &
108  zmin, zmax, nc_z)
109 
110  type(sll_t_maxwell_3d_pstd) :: self
111  sll_real64, intent(in) :: xmin
112  sll_real64, intent(in) :: xmax
113  sll_real64, intent(in) :: ymin
114  sll_real64, intent(in) :: ymax
115  sll_real64, intent(in) :: zmin
116  sll_real64, intent(in) :: zmax
117  sll_int32, intent(in) :: nc_x
118  sll_int32, intent(in) :: nc_y
119  sll_int32, intent(in) :: nc_z
120 
121  sll_int32 :: error
122  sll_real64 :: dx
123  sll_real64 :: dy
124  sll_real64 :: dz
125  sll_real64 :: kx0
126  sll_real64 :: ky0
127  sll_real64 :: kz0
128 
129  sll_int32 :: i, j, k
130 
131  self%nc_x = nc_x
132  self%nc_y = nc_y
133  self%nc_z = nc_z
134 
135  self%e_0 = 1.0_f64
136  self%mu_0 = 1.0_f64
137 
138  sll_allocate(self%tmp_x(1:nc_x/2 + 1), error); self%tmp_x = (0.0_f64, 0.0_f64)
139  sll_allocate(self%tmp_y(1:nc_y/2 + 1), error); self%tmp_y = (0.0_f64, 0.0_f64)
140  sll_allocate(self%tmp_z(1:nc_z/2 + 1), error); self%tmp_z = (0.0_f64, 0.0_f64)
141 
142  sll_clear_allocate(self%d_dx(1:nc_x), error)
143  sll_clear_allocate(self%d_dy(1:nc_y), error)
144  sll_clear_allocate(self%d_dz(1:nc_z), error)
145 
146  call sll_s_fft_init_r2c_1d(self%fwx, nc_x, self%d_dx, self%tmp_x)
147  call sll_s_fft_init_c2r_1d(self%bwx, nc_x, self%tmp_x, self%d_dx)
148  call sll_s_fft_init_r2c_1d(self%fwy, nc_y, self%d_dy, self%tmp_y)
149  call sll_s_fft_init_c2r_1d(self%bwy, nc_y, self%tmp_y, self%d_dy)
150  call sll_s_fft_init_r2c_1d(self%fwz, nc_z, self%d_dz, self%tmp_z)
151  call sll_s_fft_init_c2r_1d(self%bwz, nc_z, self%tmp_z, self%d_dz)
152 
153  sll_allocate(self%kx(nc_x/2 + 1), error)
154  sll_allocate(self%ky(nc_y/2 + 1), error)
155  sll_allocate(self%kz(nc_z/2 + 1), error)
156 
157  dx = (xmax - xmin)/real(nc_x,f64)
158  dy = (ymax - ymin)/real(nc_y,f64)
159  dz = (zmax - zmin)/real(nc_z,f64)
160 
161  kx0 = 2._f64*sll_p_pi/(real(nc_x,f64)*dx)
162  ky0 = 2._f64*sll_p_pi/(real(nc_y,f64)*dy)
163  kz0 = 2._f64*sll_p_pi/(real(nc_z,f64)*dz)
164 
165  self%kx(1) = 1.0_f64
166  do i = 2, nc_x/2 + 1
167  self%kx(i) = real(i - 1, f64)*kx0
168  end do
169  self%ky(1) = 1.0_f64
170  do j = 2, nc_y/2 + 1
171  self%ky(j) = real(j - 1, f64)*ky0
172  end do
173  self%kz(1) = 1.0_f64
174  do k = 2, nc_z/2 + 1
175  self%kz(k) = real(k - 1, f64)*kz0
176  end do
177 
178  end subroutine sll_s_maxwell_3d_pstd_init
179 
181  subroutine sll_s_maxwell_3d_pstd_faraday(self, ex, ey, ez, hx, hy, hz, dt)
182 
183  type(sll_t_maxwell_3d_pstd), intent(inout) :: self
184  sll_real64, dimension(:, :, :), intent(inout) :: ex
185  sll_real64, dimension(:, :, :), intent(inout) :: ey
186  sll_real64, dimension(:, :, :), intent(inout) :: ez
187  sll_real64, dimension(:, :, :), intent(inout) :: hx
188  sll_real64, dimension(:, :, :), intent(inout) :: hy
189  sll_real64, dimension(:, :, :), intent(inout) :: hz
190  sll_int32 :: nc_x
191  sll_int32 :: nc_y
192  sll_int32 :: nc_z
193  sll_real64, intent(in) :: dt
194 
195  sll_real64 :: dt_mu
196  sll_int32 :: i, j, k
197 
198  nc_x = self%nc_x
199  nc_y = self%nc_y
200  nc_z = self%nc_z
201 
202  dt_mu = dt/self%mu_0
203 
204  do k = 1, nc_z + 1
205  do i = 1, nc_x + 1
206  d_dy(ez(i, 1:nc_y, k))
207  hx(i, 1:nc_y, k) = hx(i, 1:nc_y, k) - dt_mu*self%d_dy
208  d_dy(ex(i, 1:nc_y, k))
209  hz(i, 1:nc_y, k) = hz(i, 1:nc_y, k) + dt_mu*self%d_dy
210  end do
211  end do
212 
213  hx(:, nc_y + 1, :) = hx(:, 1, :)
214  hz(:, nc_y + 1, :) = hz(:, 1, :)
215 
216  do j = 1, nc_y + 1
217  do i = 1, nc_x + 1
218  d_dz(ey(i, j, 1:nc_z))
219  hx(i, j, 1:nc_z) = hx(i, j, 1:nc_z) + dt_mu*self%d_dz
220  d_dz(ex(i, j, 1:nc_z))
221  hy(i, j, 1:nc_z) = hy(i, j, 1:nc_z) - dt_mu*self%d_dz
222  end do
223  end do
224 
225  hx(:, :, nc_z + 1) = hx(:, :, 1)
226  hy(:, :, nc_z + 1) = hy(:, :, 1)
227 
228  do k = 1, nc_z + 1
229  do j = 1, nc_y + 1
230  d_dx(ez(1:nc_x, j, k))
231  hy(1:nc_x, j, k) = hy(1:nc_x, j, k) + dt_mu*self%d_dx
232  d_dx(ey(1:nc_x, j, k))
233  hz(1:nc_x, j, k) = hz(1:nc_x, j, k) - dt_mu*self%d_dx
234  end do
235  end do
236 
237  hy(nc_x + 1, :, :) = hy(1, :, :)
238  hz(nc_x + 1, :, :) = hz(1, :, :)
239 
240  end subroutine sll_s_maxwell_3d_pstd_faraday
241 
243  subroutine sll_s_maxwell_3d_pstd_ampere(self, hx, hy, hz, ex, ey, ez, dt, jx, jy, jz)
244 
245  type(sll_t_maxwell_3d_pstd), intent(inout) :: self
246  sll_real64, dimension(:, :, :) :: hx
247  sll_real64, dimension(:, :, :) :: hy
248  sll_real64, dimension(:, :, :) :: hz
249  sll_real64, dimension(:, :, :) :: ex
250  sll_real64, dimension(:, :, :) :: ey
251  sll_real64, dimension(:, :, :) :: ez
252  sll_real64 :: dt
253  sll_real64, dimension(:, :, :), optional :: jx
254  sll_real64, dimension(:, :, :), optional :: jy
255  sll_real64, dimension(:, :, :), optional :: jz
256 
257  sll_int32 :: nc_x
258  sll_int32 :: nc_y
259  sll_int32 :: nc_z
260 
261  sll_real64 :: dt_e
262  sll_int32 :: i, j, k
263 
264  nc_x = self%nc_x
265  nc_y = self%nc_y
266  nc_z = self%nc_z
267 
268  dt_e = dt/self%e_0
269 
270  do k = 1, nc_z + 1
271  do i = 1, nc_x + 1
272  d_dy(hz(i, 1:nc_y, k))
273  ex(i, 1:nc_y, k) = ex(i, 1:nc_y, k) + dt_e*self%d_dy
274  d_dy(hx(i, 1:nc_y, k))
275  ez(i, 1:nc_y, k) = ez(i, 1:nc_y, k) - dt_e*self%d_dy
276  end do
277  end do
278 
279  ex(:, nc_y + 1, :) = ex(:, 1, :)
280  ez(:, nc_y + 1, :) = ez(:, 1, :)
281 
282  do j = 1, nc_y + 1
283  do i = 1, nc_x + 1
284  d_dz(hy(i, j, 1:nc_z))
285  ex(i, j, 1:nc_z) = ex(i, j, 1:nc_z) - dt_e*self%d_dz
286  d_dz(hx(i, j, 1:nc_z))
287  ey(i, j, 1:nc_z) = ey(i, j, 1:nc_z) + dt_e*self%d_dz
288  end do
289  end do
290 
291  ex(:, :, nc_z + 1) = ex(:, :, 1)
292  ey(:, :, nc_z + 1) = ey(:, :, 1)
293 
294  do k = 1, nc_z + 1
295  do j = 1, nc_y + 1
296  d_dx(hz(1:nc_x, j, k))
297  ey(1:nc_x, j, k) = ey(1:nc_x, j, k) - dt_e*self%d_dx
298  d_dx(hy(1:nc_x, j, k))
299  ez(1:nc_x, j, k) = ez(1:nc_x, j, k) + dt_e*self%d_dx
300  end do
301  end do
302 
303  ey(nc_x + 1, :, :) = ey(1, :, :)
304  ez(nc_x + 1, :, :) = ez(1, :, :)
305 
306  if (present(jx) .and. present(jy) .and. present(jz)) then
307  ex = ex - dt_e*jx
308  ey = ey - dt_e*jy
309  ez = ez - dt_e*jz
310  end if
311 
312  end subroutine sll_s_maxwell_3d_pstd_ampere
313 
315  subroutine sll_s_maxwell_3d_pstd_free(self)
316 
317  type(sll_t_maxwell_3d_pstd) :: self
318 
319  call sll_s_fft_free(self%fwx)
320  call sll_s_fft_free(self%fwy)
321  call sll_s_fft_free(self%fwz)
322  call sll_s_fft_free(self%bwx)
323  call sll_s_fft_free(self%bwy)
324  call sll_s_fft_free(self%bwz)
325 
326  end subroutine sll_s_maxwell_3d_pstd_free
327 
328 end module sll_m_maxwell_3d_pstd
Fortran module where set some physical and mathematical constants.
real(kind=f64), parameter, public sll_p_pi
FFT interface for FFTW.
subroutine, public sll_s_fft_free(plan)
Delete a plan.
subroutine, public sll_s_fft_init_r2c_1d(plan, nx, array_in, array_out, normalized, aligned, optimization)
Create new 1d real to complex plan for forward FFT.
subroutine, public sll_s_fft_init_c2r_1d(plan, nx, array_in, array_out, normalized, aligned, optimization)
Create new 1d complex to real plan for backward FFT.
Implements the Maxwell solver in 3D with periodic boundary conditions with PSTD method.
subroutine sll_s_maxwell_3d_pstd_faraday(self, ex, ey, ez, hx, hy, hz, dt)
Solve faraday equation (hx,hy,ez)
subroutine sll_s_maxwell_3d_pstd_init(self, xmin, xmax, nc_x, ymin, ymax, nc_y, zmin, zmax, nc_z)
Initialize 3d maxwell solver on cartesian mesh with PSTD scheme.
subroutine sll_s_maxwell_3d_pstd_ampere(self, hx, hy, hz, ex, ey, ez, dt, jx, jy, jz)
Solve ampere maxwell equation (hx,hy,ez)
subroutine sll_s_maxwell_3d_pstd_free(self)
delete maxwell solver object
Type for FFT plan in SeLaLib.
    Report Typos and Errors