Report Typos and Errors    
Semi-Lagrangian Library
Modular library for kinetic and gyrokinetic simulations of plasmas in fusion energy devices.
sll_m_maxwell_2d_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 !
17 !**************************************************************
18 
19 #include "sll_fftw.h"
20 
21 #define D_DX(FIELD)\
22 self%d_dx = field; \
23 call sll_s_fft_exec_r2c_1d(self%fwx, self%d_dx, self%tmp_x); \
24 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); \
25 call sll_s_fft_exec_c2r_1d(self%bwx, self%tmp_x, self%d_dx); \
26 self%d_dx = self%d_dx/nc_x
27 
28 #define D_DY(FIELD) \
29 self%d_dy = field; \
30 call sll_s_fft_exec_r2c_1d(self%fwy, self%d_dy, self%tmp_y); \
31 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); \
32 call sll_s_fft_exec_c2r_1d(self%bwy, self%tmp_y, self%d_dy); \
33 self%d_dy = self%d_dy/nc_y
34 
59 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
60 #include "sll_memory.h"
61 #include "sll_working_precision.h"
62 #include "sll_maxwell_solvers_macros.h"
63 
64  use sll_m_constants, only: sll_p_pi
65  use sll_m_fft, only: sll_t_fft, &
71 
72  implicit none
73 
74  public :: sll_t_maxwell_2d_pstd, &
80 
81  private
82 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
83 
90 
91  private
92  sll_int32 :: nc_eta1
93  sll_int32 :: nc_eta2
94  sll_int32 :: polarization
95  sll_real64 :: e_0
96  sll_real64 :: mu_0
97  sll_real64 :: c
98  sll_real64 :: eta1_min
99  sll_real64 :: eta1_max
100  sll_real64 :: delta_eta1
101  sll_real64 :: eta2_min
102  sll_real64 :: eta2_max
103  sll_real64 :: delta_eta2
104  sll_real64, pointer :: d_dx(:)
105  sll_real64, pointer :: d_dy(:)
106  sll_real64, pointer :: kx(:)
107  sll_real64, pointer :: ky(:)
108  type(sll_t_fft) :: fwx
109  type(sll_t_fft) :: fwy
110  type(sll_t_fft) :: bwx
111  type(sll_t_fft) :: bwy
112  sll_comp64, pointer :: tmp_x(:)
113  sll_comp64, pointer :: tmp_y(:)
114 
115  end type sll_t_maxwell_2d_pstd
116 
118 
120 
122 
124 
125 contains
126 
128  subroutine sll_s_maxwell_2d_pstd_init(self, xmin, xmax, nc_x, ymin, ymax, nc_y, polarization)
129 
130  type(sll_t_maxwell_2d_pstd) :: self
131  sll_real64, intent(in) :: xmin
132  sll_real64, intent(in) :: xmax
133  sll_real64, intent(in) :: ymin
134  sll_real64, intent(in) :: ymax
135  sll_int32, intent(in) :: nc_x
136  sll_int32, intent(in) :: nc_y
137  sll_int32, intent(in) :: polarization
138 
139  sll_int32 :: error
140  sll_real64 :: dx
141  sll_real64 :: dy
142  sll_real64 :: kx0
143  sll_real64 :: ky0
144  sll_int32 :: i, j
145 
146  self%nc_eta1 = nc_x
147  self%nc_eta2 = nc_y
148  self%polarization = polarization
149 
150  self%e_0 = 1._f64
151  self%mu_0 = 1._f64
152 
153  sll_allocate(self%d_dx(nc_x), error)
154  sll_allocate(self%d_dy(nc_y), error)
155 
156  sll_allocate(self%tmp_x(nc_x/2 + 1), error)
157  sll_allocate(self%tmp_y(nc_y/2 + 1), error)
158 
159  call sll_s_fft_init_r2c_1d(self%fwx, nc_x, self%d_dx, self%tmp_x)
160  call sll_s_fft_init_c2r_1d(self%bwx, nc_x, self%tmp_x, self%d_dx)
161  call sll_s_fft_init_r2c_1d(self%fwy, nc_y, self%d_dy, self%tmp_y)
162  call sll_s_fft_init_c2r_1d(self%bwy, nc_y, self%tmp_y, self%d_dy)
163 
164  sll_allocate(self%kx(nc_x/2 + 1), error)
165  sll_allocate(self%ky(nc_y/2 + 1), error)
166 
167  dx = (xmax - xmin)/nc_x
168  dy = (ymax - ymin)/nc_y
169 
170  kx0 = 2._f64*sll_p_pi/(nc_x*dx)
171  ky0 = 2._f64*sll_p_pi/(nc_y*dy)
172 
173  do i = 2, nc_x/2 + 1
174  self%kx(i) = (i - 1)*kx0
175  end do
176  self%kx(1) = 1.0_f64
177  do j = 2, nc_y/2 + 1
178  self%ky(j) = (j - 1)*ky0
179  end do
180  self%ky(1) = 1.0_f64
181 
182  end subroutine sll_s_maxwell_2d_pstd_init
183 
186  subroutine sll_s_solve_maxwell_2d_pstd(self, fx, fy, fz, dt)
187 
188  type(sll_t_maxwell_2d_pstd), intent(inout) :: self
189  sll_real64, intent(inout), dimension(:, :) :: fx
190  sll_real64, intent(inout), dimension(:, :) :: fy
191  sll_real64, intent(inout), dimension(:, :) :: fz
192  sll_real64, intent(in) :: dt
193 
194  IF (self%polarization == tm_polarization) then
195  call faraday_tm_2d_pstd(self, fx, fy, fz, 0.5*dt)
196  call ampere_tm_2d_pstd(self, fx, fy, fz, dt)
197  call faraday_tm_2d_pstd(self, fx, fy, fz, 0.5*dt)
198  end if
199 
200  IF (self%polarization == te_polarization) then
201  call faraday_te_2d_pstd(self, fx, fy, fz, 0.5*dt)
202  call ampere_te_2d_pstd(self, fx, fy, fz, dt)
203  call faraday_te_2d_pstd(self, fx, fy, fz, 0.5*dt)
204  end if
205 
206  end subroutine sll_s_solve_maxwell_2d_pstd
207 
209  subroutine sll_s_solve_faraday_2d_pstd(self, fx, fy, fz, dt)
210  type(sll_t_maxwell_2d_pstd), intent(inout) :: self
211  sll_real64, dimension(:, :), intent(inout) :: fx
212  sll_real64, dimension(:, :), intent(inout) :: fy
213  sll_real64, dimension(:, :), intent(inout) :: fz
214  sll_real64, intent(in) :: dt
215 
216  if (self%polarization == tm_polarization) then
217  call faraday_tm_2d_pstd(self, fx, fy, fz, dt)
218  end if
219 
220  if (self%polarization == te_polarization) then
221  call faraday_te_2d_pstd(self, fx, fy, fz, dt)
222  end if
223 
224  end subroutine sll_s_solve_faraday_2d_pstd
225 
226  subroutine sll_s_solve_ampere_2d_pstd(self, fx, fy, fz, dt, sx, sy)
227  type(sll_t_maxwell_2d_pstd), intent(inout) :: self
228  sll_real64, dimension(:, :), intent(inout) :: fx
229  sll_real64, dimension(:, :), intent(inout) :: fy
230  sll_real64, dimension(:, :), intent(inout) :: fz
231  sll_real64, intent(in) :: dt
232  sll_real64, dimension(:, :), optional :: sx
233  sll_real64, dimension(:, :), optional :: sy
234 
235  if (self%polarization == tm_polarization .and. &
236  present(sx) .and. .not. present(sy)) then
237  call ampere_tm_2d_pstd(self, fx, fy, fz, dt, sx)
238  else if (self%polarization == te_polarization .and. &
239  present(sx) .and. present(sy)) then
240  call ampere_te_2d_pstd(self, fx, fy, fz, dt, sx, sy)
241  end if
242 
243  end subroutine sll_s_solve_ampere_2d_pstd
244 
246  subroutine faraday_tm_2d_pstd(self, hx, hy, ez, dt)
247 
248  type(sll_t_maxwell_2d_pstd), intent(inout) :: self
249  sll_real64, dimension(:, :), intent(inout) :: hx
250  sll_real64, dimension(:, :), intent(inout) :: hy
251  sll_real64, dimension(:, :), intent(inout) :: ez
252  sll_int32 :: nc_x
253  sll_int32 :: nc_y
254  sll_real64, intent(in) :: dt
255 
256  sll_real64 :: dt_mu
257  sll_int32 :: i, j
258 
259  nc_x = self%nc_eta1
260  nc_y = self%nc_eta2
261 
262  dt_mu = dt/self%mu_0
263 
264  do i = 1, nc_x
265  d_dy(ez(i, 1:nc_y))
266  hx(i, 1:nc_y) = hx(i, 1:nc_y) - dt_mu*self%d_dy
267  end do
268 
269  do j = 1, nc_y
270  d_dx(ez(1:nc_x, j))
271  hy(1:nc_x, j) = hy(1:nc_x, j) + dt_mu*self%d_dx
272  end do
273 
274  if (size(hx, 2) == nc_y + 1) hx(:, nc_y + 1) = hx(:, 1)
275  if (size(hy, 1) == nc_x + 1) hy(nc_x + 1, :) = hy(1, :)
276 
277  end subroutine faraday_tm_2d_pstd
278 
280  subroutine faraday_te_2d_pstd(self, ex, ey, hz, dt)
281 
282  type(sll_t_maxwell_2d_pstd), intent(inout) :: self
283  sll_real64, dimension(:, :), intent(inout) :: ex
284  sll_real64, dimension(:, :), intent(inout) :: ey
285  sll_real64, dimension(:, :), intent(inout) :: hz
286  sll_int32 :: nc_x
287  sll_int32 :: nc_y
288  sll_real64, intent(in) :: dt
289 
290  sll_real64 :: dt_mu
291  sll_int32 :: i, j
292 
293  nc_x = self%nc_eta1
294  nc_y = self%nc_eta2
295 
296  dt_mu = dt/self%mu_0
297 
298  do i = 1, nc_x
299  d_dy(ex(i, 1:nc_y))
300  hz(i, 1:nc_y) = hz(i, 1:nc_y) + dt_mu*self%d_dy
301  end do
302 
303  do j = 1, nc_y
304  d_dx(ey(1:nc_x, j))
305  hz(1:nc_x, j) = hz(1:nc_x, j) - dt_mu*self%d_dx
306  end do
307 
308  if (size(hz, 1) == nc_x + 1) hz(nc_x + 1, :) = hz(1, :)
309  if (size(hz, 2) == nc_y + 1) hz(:, nc_y + 1) = hz(:, 1)
310 
311  end subroutine faraday_te_2d_pstd
312 
314  subroutine ampere_tm_2d_pstd(self, hx, hy, ez, dt, jz)
315 
316  type(sll_t_maxwell_2d_pstd), intent(inout) :: self
317  sll_int32 :: nc_x
318  sll_int32 :: nc_y
319  sll_real64, dimension(:, :) :: hx
320  sll_real64, dimension(:, :) :: hy
321  sll_real64, dimension(:, :) :: ez
322  sll_real64 :: dt
323  sll_real64, dimension(:, :), optional :: jz
324 
325  sll_real64 :: dt_e
326  sll_int32 :: i, j
327 
328  nc_x = self%nc_eta1
329  nc_y = self%nc_eta2
330 
331  dt_e = dt/self%e_0
332 
333  do j = 1, nc_y
334  d_dx(hy(1:nc_x, j))
335  ez(1:nc_x, j) = ez(1:nc_x, j) + dt_e*self%d_dx
336  end do
337 
338  do i = 1, nc_x
339  d_dy(hx(i, 1:nc_y))
340  ez(i, 1:nc_y) = ez(i, 1:nc_y) - dt_e*self%d_dy
341  end do
342 
343  if (present(jz)) then
344  ez = ez - dt_e*jz
345  end if
346 
347  if (size(ez, 1) == nc_x + 1) ez(nc_x + 1, :) = ez(1, :)
348  if (size(ez, 2) == nc_y + 1) ez(:, nc_y + 1) = ez(:, 1)
349 
350  end subroutine ampere_tm_2d_pstd
351 
353  subroutine ampere_te_2d_pstd(self, ex, ey, hz, dt, jx, jy)
354 
355  type(sll_t_maxwell_2d_pstd), intent(inout) :: self
356  sll_real64, dimension(:, :) :: ex
357  sll_real64, dimension(:, :) :: ey
358  sll_real64, dimension(:, :) :: hz
359  sll_real64 :: dt
360  sll_real64, dimension(:, :), optional :: jx
361  sll_real64, dimension(:, :), optional :: jy
362 
363  sll_real64 :: dt_e
364  sll_int32 :: nc_x
365  sll_int32 :: nc_y
366  sll_int32 :: i, j
367 
368  nc_x = self%nc_eta1
369  nc_y = self%nc_eta2
370 
371  dt_e = dt/self%e_0
372 
373  do j = 1, nc_y
374  d_dx(hz(1:nc_x, j))
375  ey(1:nc_x, j) = ey(1:nc_x, j) - dt_e*self%d_dx
376  end do
377 
378  do i = 1, nc_x
379  d_dy(hz(i, 1:nc_y))
380  ex(i, 1:nc_y) = ex(i, 1:nc_y) + dt_e*self%d_dy
381  end do
382 
383  If (present(jx) .and. present(jy)) then
384  ex = ex - dt_e*jx
385  ey = ey - dt_e*jy
386  end if
387 
388  if (size(ex, 1) == nc_x + 1) ex(nc_x + 1, :) = ex(1, :)
389  if (size(ey, 2) == nc_y + 1) ey(:, nc_y + 1) = ey(:, 1)
390 
391  end subroutine ampere_te_2d_pstd
392 
394  subroutine sll_s_free_maxwell_2d_pstd(self)
395  type(sll_t_maxwell_2d_pstd) :: self
396 
397  call sll_s_fft_free(self%fwx)
398  call sll_s_fft_free(self%fwy)
399  call sll_s_fft_free(self%bwx)
400  call sll_s_fft_free(self%bwy)
401 
402  end subroutine sll_s_free_maxwell_2d_pstd
403 
404 end module sll_m_maxwell_2d_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_exec_r2c_1d(plan, array_in, array_out)
Compute fast Fourier transform in real to complex mode.
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_exec_c2r_1d(plan, array_in, array_out)
Compute fast Fourier transform in complex to real mode.
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 2D with periodic boundary conditions with PSTD method.
subroutine faraday_tm_2d_pstd(self, hx, hy, ez, dt)
Solve faraday equation (hx,hy,ez)
subroutine, public sll_s_free_maxwell_2d_pstd(self)
delete maxwell solver object
subroutine, public sll_s_solve_faraday_2d_pstd(self, fx, fy, fz, dt)
Solve Faraday equation.
subroutine ampere_te_2d_pstd(self, ex, ey, hz, dt, jx, jy)
Solve ampere maxwell equation (ex,ey,hz)
subroutine faraday_te_2d_pstd(self, ex, ey, hz, dt)
Solve faraday equation (ex,ey,hz)
subroutine ampere_tm_2d_pstd(self, hx, hy, ez, dt, jz)
Solve ampere maxwell equation (hx,hy,ez)
subroutine, public sll_s_solve_maxwell_2d_pstd(self, fx, fy, fz, dt)
self routine exists only for testing purpose. Use ampere and faraday in your appication.
subroutine, public sll_s_maxwell_2d_pstd_init(self, xmin, xmax, nc_x, ymin, ymax, nc_y, polarization)
Solve maxwell solver 2d cartesian periodic with PSTD scheme.
subroutine, public sll_s_solve_ampere_2d_pstd(self, fx, fy, fz, dt, sx, sy)
Type for FFT plan in SeLaLib.
    Report Typos and Errors