Report Typos and Errors    
Semi-Lagrangian Library
Modular library for kinetic and gyrokinetic simulations of plasmas in fusion energy devices.
sll_m_maxwell_2d_fdtd.F90
Go to the documentation of this file.
1 ! Copyright INRIA
2 !
3 ! This code SeLaLib (for Semi-Lagrangian-Library)
4 ! is a parallel library for simulating the plasma turbulence
5 ! in a tokamak.
6 !
7 ! This software is governed by the CeCILL-B license
8 ! under French law and abiding by the rules of distribution
9 ! of free software. You can use, modify and redistribute
10 ! the software under the terms of the CeCILL-B license as
11 ! circulated by CEA, CNRS and INRIA at the following URL
12 ! "http://www.cecill.info".
13 !
14 !**************************************************************
39 
40 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
41 #include "sll_memory.h"
42 #include "sll_working_precision.h"
43 #include "sll_maxwell_solvers_macros.h"
44 
45  implicit none
46 
47  public :: &
48  sll_o_create, &
51 
52  private
53 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
54 
56  interface sll_o_create
57  module procedure initialize_maxwell_2d_fdtd
58  module procedure initialize_maxwell_2d_fdtd_alt
59  end interface sll_o_create
61  interface sll_o_solve
62  module procedure solve_maxwell_2d_fdtd
63  end interface sll_o_solve
65  interface sll_solve_ampere
66  module procedure ampere_2d_fdtd
67  end interface sll_solve_ampere
70  module procedure ampere_2d_fdtd
71  end interface sll_solve_faraday
72 
76  private
77  sll_int32 :: nc_eta1
78  sll_int32 :: nc_eta2
79  sll_int32 :: polarization
80  sll_real64 :: e_0
81  sll_real64 :: mu_0
82  sll_real64 :: c
83  sll_real64 :: eta1_min
84  sll_real64 :: eta1_max
85  sll_real64 :: delta_eta1
86  sll_real64 :: eta2_min
87  sll_real64 :: eta2_max
88  sll_real64 :: delta_eta2
89  sll_int32 :: i1
90  sll_int32 :: j1
91  sll_int32 :: i2
92  sll_int32 :: j2
93  sll_real64 :: dx
94  sll_real64 :: dy
95  end type sll_t_maxwell_2d_fdtd
96 
97 contains
98 
100  subroutine initialize_maxwell_2d_fdtd_alt(self, x1, x2, nc_x, &
101  y1, y2, nc_y, polarization)
102 
103  type(sll_t_maxwell_2d_fdtd) :: self
104  sll_real64 :: x1
105  sll_real64 :: y1
106  sll_real64 :: x2
107  sll_real64 :: y2
108  sll_int32 :: nc_x
109  sll_int32 :: nc_y
110  sll_int32 :: polarization
111 
112  self%c = 1.0_f64
113  self%e_0 = 1.0_f64
114 
115  self%dx = (x2 - x1)/nc_x
116  self%dy = (y2 - y1)/nc_y
117  self%i1 = 1
118  self%j1 = nc_x + 1
119  self%i2 = 1
120  self%j2 = nc_y + 1
121 
122  self%polarization = polarization
123 
124  end subroutine initialize_maxwell_2d_fdtd_alt
125 
127  subroutine initialize_maxwell_2d_fdtd(self, i1, j1, i2, j2, dx, dy, polarization)
128 
129  type(sll_t_maxwell_2d_fdtd) :: self
130  sll_int32 :: i1
131  sll_int32 :: j1
132  sll_int32 :: i2
133  sll_int32 :: j2
134  sll_real64 :: dx
135  sll_real64 :: dy
136  sll_int32 :: polarization
137  !sll_int32 :: error !< error code
138 
139  self%c = 1.0_f64
140  self%e_0 = 1.0_f64
141 
142  self%dx = dx
143  self%dy = dy
144  self%i1 = i1
145  self%j1 = j1
146  self%i2 = i2
147  self%j2 = j2
148  self%polarization = polarization
149 
150  end subroutine initialize_maxwell_2d_fdtd
151 
154  subroutine solve_maxwell_2d_fdtd(self, fx, fy, fz, dt)
155 
156  type(sll_t_maxwell_2d_fdtd) :: self
157  sll_real64, dimension(:, :) :: fx
158  sll_real64, dimension(:, :) :: fy
159  sll_real64, dimension(:, :) :: fz
160  sll_real64, intent(in) :: dt
161 
162  call faraday_2d_fdtd(self, fx, fy, fz, 0.5*dt)
163  call bc_periodic_2d_fdtd(self, fx, fy, fz, dt)
164  call ampere_2d_fdtd(self, fx, fy, fz, dt)
165  call bc_periodic_2d_fdtd(self, fx, fy, fz, dt)
166  call faraday_2d_fdtd(self, fx, fy, fz, 0.5*dt)
167  call bc_periodic_2d_fdtd(self, fx, fy, fz, dt)
168 
169  end subroutine solve_maxwell_2d_fdtd
170 
171 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
172 
174  subroutine faraday_2d_fdtd(self, fx, fy, fz, dt)
175 
176  type(sll_t_maxwell_2d_fdtd) :: self
177  sll_real64, dimension(:, :), target :: fx
178  sll_real64, dimension(:, :), target :: fy
179  sll_real64, dimension(:, :), target :: fz
180  sll_real64, intent(in) :: dt
181  sll_int32 :: i, j
182  sll_real64 :: dex_dy, dey_dx, dez_dx, dez_dy
183  sll_real64 :: dx, dy
184  sll_int32 :: i1, j1, i2, j2
185  sll_real64, dimension(:, :), pointer :: ex
186  sll_real64, dimension(:, :), pointer :: ey
187  sll_real64, dimension(:, :), pointer :: ez
188  sll_real64, dimension(:, :), pointer :: bx
189  sll_real64, dimension(:, :), pointer :: by
190  sll_real64, dimension(:, :), pointer :: bz
191 
192  dx = self%dx
193  dy = self%dy
194 
195 !*** On utilise l'equation de Faraday sur un demi pas
196 !*** de temps pour le calcul du champ magnetique Bz
197 !*** a l'instant n puis n+1/2
198 
199  i1 = self%i1
200  j1 = self%j1
201  i2 = self%i2
202  j2 = self%j2
203 
204  if (self%polarization == te_polarization) then
205 
206  ex => fx; ey => fy; bz => fz
207  do i = i1, j1 - 1
208  do j = i2, j2 - 1
209  dex_dy = (ex(i, j + 1) - ex(i, j))/dy
210  dey_dx = (ey(i + 1, j) - ey(i, j))/dx
211  bz(i, j) = bz(i, j) + dt*(dex_dy - dey_dx)
212  end do
213  end do
214 
215  end if
216 
217  if (self%polarization == tm_polarization) then
218 
219  bx => fx; by => fy; ez => fz
220  do i = i1, j1
221  do j = i2 + 1, j2
222  dez_dy = (ez(i, j) - ez(i, j - 1))/dy
223  bx(i, j) = bx(i, j) - dt*dez_dy
224  end do
225  end do
226 
227  do i = i1 + 1, j1
228  do j = i2, j2
229  dez_dx = (ez(i, j) - ez(i - 1, j))/dx
230  by(i, j) = by(i, j) + dt*dez_dx
231  end do
232  end do
233 
234  end if
235 
236  end subroutine faraday_2d_fdtd
237 
238 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
239 
241  subroutine ampere_2d_fdtd(self, fx, fy, fz, dt, jx, jy)
242 
243  type(sll_t_maxwell_2d_fdtd) :: self
244  sll_int32 :: i1, j1, i2, j2
245  sll_real64, dimension(:, :), intent(inout), target :: fx
246  sll_real64, dimension(:, :), intent(inout), target :: fy
247  sll_real64, dimension(:, :), intent(inout), target :: fz
248  sll_real64, dimension(:, :), intent(in), optional :: jx
249  sll_real64, dimension(:, :), intent(in), optional :: jy
250  sll_int32 :: i, j
251  sll_real64 :: dbz_dx, dbz_dy, dbx_dy, dby_dx
252  sll_real64, intent(in) :: dt
253  sll_real64 :: dx, dy
254  sll_real64 :: csq
255  sll_real64, dimension(:, :), pointer :: ex
256  sll_real64, dimension(:, :), pointer :: ey
257  sll_real64, dimension(:, :), pointer :: ez
258  sll_real64, dimension(:, :), pointer :: bx
259  sll_real64, dimension(:, :), pointer :: by
260  sll_real64, dimension(:, :), pointer :: bz
261 
262  i1 = self%i1
263  j1 = self%j1
264  i2 = self%i2
265  j2 = self%j2
266 
267  csq = self%c*self%c
268  dx = self%dx
269  dy = self%dy
270 
271 !*** Calcul du champ electrique E au temps n+1
272 !*** sur les points internes du maillage
273 !*** Ex aux points (i+1/2,j)
274 !*** Ey aux points (i,j+1/2)
275 
276  if (self%polarization == te_polarization) then
277 
278  ex => fx; ey => fy; bz => fz
279 
280  do i = i1, j1
281  do j = i2 + 1, j2
282  dbz_dy = (bz(i, j) - bz(i, j - 1))/dy
283  ex(i, j) = ex(i, j) + dt*csq*dbz_dy
284  end do
285  end do
286 
287  do i = i1 + 1, j1
288  do j = i2, j2
289  dbz_dx = (bz(i, j) - bz(i - 1, j))/dx
290  ey(i, j) = ey(i, j) - dt*csq*dbz_dx
291  end do
292  end do
293 
294  if (present(jx) .and. present(jy)) then
295 
296  ex(i1:j1, i2 + 1:j2) = ex(i1:j1, i2 + 1:j2) - dt*jx(i1:j1, i2 + 1:j2)/self%e_0
297  ey(i1 + 1:j1, i2:j2) = ey(i1 + 1:j1, i2:j2) - dt*jy(i1 + 1:j1, i2:j2)/self%e_0
298 
299  end if
300 
301  end if
302 
303  if (self%polarization == tm_polarization) then
304 
305  bx => fx; by => fy; ez => fz
306 
307  do i = i1, j1 - 1
308  do j = i2, j2 - 1
309  dbx_dy = (bx(i, j + 1) - bx(i, j))/dy
310  dby_dx = (by(i + 1, j) - by(i, j))/dx
311  ez(i, j) = ez(i, j) - dt*(dbx_dy - dby_dx)
312  end do
313  end do
314 
315  if (present(jx) .and. .not. present(jy)) then
316 
317  ez(i1:j1 - 1, i2:j2 - 1) = ez(i1:j1 - 1, i2:j2 - 1) - dt*jx(i1:j1 - 1, i2:j2 - 1)/self%e_0
318 
319  end if
320 
321  end if
322 
323  end subroutine ampere_2d_fdtd
324 
325 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
326 
328  subroutine bc_periodic_2d_fdtd(self, fx, fy, fz, dt)
329 
330  type(sll_t_maxwell_2d_fdtd) :: self
331  sll_int32 :: i1, j1, i2, j2
332  sll_real64, dimension(:, :), intent(inout) :: fx
333  sll_real64, dimension(:, :), intent(inout) :: fy
334  sll_real64, dimension(:, :), intent(inout) :: fz
335  sll_real64 :: dbz_dx, dbz_dy, dez_dx, dez_dy
336  sll_real64, intent(in) :: dt
337  sll_real64 :: dx, dy
338  sll_int32 :: i, j
339  sll_real64 :: csq
340 
341  i1 = self%i1
342  j1 = self%j1
343  i2 = self%i2
344  j2 = self%j2
345 
346  csq = self%c*self%c
347  dx = self%dx
348  dy = self%dy
349 
350  fz(i1:j1 - 1, j2) = fz(i1:j1 - 1, i2)
351  fz(j1, i2:j2 - 1) = fz(i1, i2:j2 - 1)
352 
353  fz(j1, j2) = fz(i1, i2)
354 
355  if (self%polarization == te_polarization) then
356  do i = i1, j1
357  dbz_dy = (fz(i, i2) - fz(i, j2 - 1))/dy
358  fx(i, i2) = fx(i, j2) + dt*csq*dbz_dy
359  end do
360 
361  do j = i2, j2
362  dbz_dx = (fz(i1, j) - fz(j1 - 1, j))/dx
363  fy(i1, j) = fy(j1, j) - dt*csq*dbz_dx
364  end do
365  end if
366 
367  if (self%polarization == tm_polarization) then
368  do i = i1, j1
369  dez_dy = (fz(i, i2) - fz(i, j2 - 1))/dy
370  fx(i, i2) = fx(i, j2) - dt*csq*dez_dy
371  end do
372 
373  do j = i2, j2
374  dez_dx = (fz(i1, j) - fz(j1 - 1, j))/dx
375  fy(i1, j) = fy(j1, j) + dt*csq*dez_dx
376  end do
377  end if
378 
379  end subroutine bc_periodic_2d_fdtd
380 
381 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
382 
383 !PN DEFINED BUT NOT USED
384 !PN !> Set periodic bounday conditions
385 !PN subroutine bc_metallic_2d_fdtd(self, fx, fy, fz, side)
386 !PN
387 !PN type(sll_t_maxwell_2d_fdtd) :: self !< maxwell object
388 !PN sll_int32, intent(in) :: side !< which domain edge
389 !PN sll_real64, dimension(:,:), target :: fx !< Ex or Bx
390 !PN sll_real64, dimension(:,:), target :: fy !< Ey or By
391 !PN sll_real64, dimension(:,:), target :: fz !< Bz or Ez
392 !PN sll_real64, dimension(:,:), pointer :: bx, by, ez
393 !PN sll_real64, dimension(:,:), pointer :: ex, ey, bz
394 !PN sll_int32 :: i1, j1, i2, j2
395 !PN
396 !PN i1 = self%i1
397 !PN j1 = self%j1
398 !PN i2 = self%i2
399 !PN j2 = self%j2
400 !PN
401 !PN if (self%polarization == TE_POLARIZATION) then
402 !PN ex => fx; ey => fy; bz => fz
403 !PN select case(side)
404 !PN case(SOUTH)
405 !PN ex(i1:j1,i2) = 0._f64
406 !PN case(NORTH)
407 !PN bz(i1:j1,j2) = bz(i1:j1,j2-1)
408 !PN case(WEST)
409 !PN ey(i1,i2:j2) = 0._f64
410 !PN case(EAST)
411 !PN bz(j1,i2:j2) = bz(j1-1,i2:j2)
412 !PN end select
413 !PN end if
414 !PN
415 !PN if (self%polarization == TM_POLARIZATION) then
416 !PN bx => fx; by => fy; ez => fz
417 !PN select case(side)
418 !PN case(SOUTH)
419 !PN bx(i1:j1,i2) = 0.0_f64
420 !PN case(NORTH)
421 !PN ez(i1:j1,j2) = ez(i1:j1,j2-1)
422 !PN case(WEST)
423 !PN by(i1,i2:j2) = 0._f64
424 !PN case(EAST)
425 !PN ez(j1,i2:j2) = ez(j1-1,i2:j2)
426 !PN end select
427 !PN end if
428 !PN
429 !PN end subroutine bc_metallic_2d_fdtd
430 !PN
431 !PN !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
432 !PN
433 !PN !> Bundary conditions
434 !PN subroutine bc_silver_muller_2d_fdtd( self, ex, ey, bz, ccall, dt )
435 !PN
436 !PN type(sll_t_maxwell_2d_fdtd) :: self !< maxwell object
437 !PN sll_int32, intent(in) :: ccall !< domain edge (N,S,E,W)
438 !PN sll_int32 :: i1, j1, i2, j2
439 !PN sll_real64 :: a11,a12,a21,a22,b1,b2,dis
440 !PN sll_int32 :: i, j
441 !PN sll_real64, intent(in) :: dt !< time step
442 !PN sll_real64 :: dx, dy, c, csq
443 !PN sll_real64, dimension(:,:), pointer :: ex !< x electric field
444 !PN sll_real64, dimension(:,:), pointer :: ey !< y electric field
445 !PN sll_real64, dimension(:,:), pointer :: bz !< z magnetic field
446 !PN
447 !PN c = self%c
448 !PN csq = c * c
449 !PN dx = self%dx
450 !PN dy = self%dy
451 !PN
452 !PN i1 = self%i1
453 !PN j1 = self%j1
454 !PN i2 = self%i2
455 !PN j2 = self%j2
456 !PN
457 !PN !Conditions de Silver-Muller
458 !PN !------------------------------------
459 !PN !Ey = -c Bz sur la frontiere ouest
460 !PN !Ey = c Bz sur la frontiere est
461 !PN !Ex = -c Bz sur la frontiere nord
462 !PN !Ex = c Bz sur la frontiere sud
463 !PN
464 !PN !On effectue le calcul de B sur les points fictifs du maillage
465 !PN !simultanement avec la prise en compte des conditions limites sur
466 !PN !E. Pour cela, on resout sur les points frontieres, l'equation de la
467 !PN !condition limite en moyennant en temps pour E et en espace pour B puis
468 !PN !l'equation d'Ampere
469 !PN
470 !PN select case (ccall)
471 !PN
472 !PN case (NORTH)
473 !PN !Frontiere Nord : Ex = -c Bz
474 !PN do i = i1, j1
475 !PN
476 !PN a11 = 1.0_f64; a12 = + c
477 !PN a21 = 1.0_f64/dt; a22 = - csq / dy
478 !PN b1 = - ex(i,j2) - c * bz(i,j2-1)
479 !PN b2 = ex(i,j2)/dt - csq/dy*bz(i,j2-1)
480 !PN
481 !PN dis = a11*a22-a21*a12
482 !PN
483 !PN !ex(i,j2) = (b1*a22-b2*a12)/dis
484 !PN bz(i,j2) = (a11*b2-a21*b1)/dis
485 !PN
486 !PN end do
487 !PN
488 !PN case (SOUTH)
489 !PN
490 !PN !Frontiere Sud : Ex = c Bz
491 !PN do i = i1, j1
492 !PN
493 !PN a11 = 1.0_f64; a12 = - c
494 !PN a21 = 1.0_f64/dt; a22 = csq / dy
495 !PN b1 = - ex(i,i2) + c * bz(i,i2+1)
496 !PN b2 = ex(i,i2)/dt + csq / dy * bz(i,i2+1)
497 !PN
498 !PN dis = a11*a22-a21*a12
499 !PN
500 !PN ex(i,i2) = (b1*a22-b2*a12)/dis
501 !PN !bz(i,i2) = (a11*b2-a21*b1)/dis
502 !PN
503 !PN end do
504 !PN
505 !PN case (EAST)
506 !PN
507 !PN !Frontiere Est : Ey = c Bz
508 !PN do j = i2, j2
509 !PN
510 !PN a11 = 1.0_f64; a12 = - c
511 !PN a21 = 1.0_f64/dt; a22 = + csq / dx
512 !PN b1 = - ey(j1,j) + c * bz(j1-1,j)
513 !PN b2 = ey(j1,j)/dt + csq/dx*bz(j1-1,j)
514 !PN
515 !PN dis = a11*a22-a21*a12
516 !PN
517 !PN !ey(j1,j) = (b1*a22-b2*a12)/dis
518 !PN bz(j1,j) = (a11*b2-a21*b1)/dis
519 !PN
520 !PN end do
521 !PN
522 !PN case (WEST)
523 !PN
524 !PN !Frontiere Ouest : Ey = -c Bz
525 !PN do j = i2, j2
526 !PN
527 !PN a11 = 1.0_f64; a12 = + c
528 !PN a21 = 1.0_f64/dt; a22 = - csq / dx
529 !PN b1 = - ey(i1,j) - c * bz(i1+1,j)
530 !PN b2 = ey(i1,j)/dt - csq/dx*bz(i1+1,j)
531 !PN
532 !PN dis = a11*a22-a21*a12
533 !PN
534 !PN ey(i1,j) = (b1*a22-b2*a12)/dis
535 !PN !bz(i1,j) = (a11*b2-a21*b1)/dis
536 !PN
537 !PN end do
538 !PN
539 !PN end select
540 !PN
541 !PN end subroutine bc_silver_muller_2d_fdtd
542 
543 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
544 
545 end module sll_m_maxwell_2d_fdtd
Initialize maxwell solver 2d with FDTD scheme.
Solve maxwell solver 2d with FDTD scheme.
Implements the Maxwell solver in 2D with FDTD method.
subroutine bc_periodic_2d_fdtd(self, fx, fy, fz, dt)
Set boundary conditions.
subroutine initialize_maxwell_2d_fdtd_alt(self, x1, x2, nc_x, y1, y2, nc_y, polarization)
Initilialize the maxwell solver.
subroutine ampere_2d_fdtd(self, fx, fy, fz, dt, jx, jy)
Solve ampere-maxwell equation with FDTD scheme.
subroutine initialize_maxwell_2d_fdtd(self, i1, j1, i2, j2, dx, dy, polarization)
Initilialize the maxwell solver.
subroutine solve_maxwell_2d_fdtd(self, fx, fy, fz, dt)
self routine exists only for testing purpose. Use ampere and faraday in your appication.
subroutine faraday_2d_fdtd(self, fx, fy, fz, dt)
Solve Faraday equation.
Object with data to solve Maxwell equation Maxwell in TE mode: (Ex,Ey,Bz)
    Report Typos and Errors