Report Typos and Errors    
Semi-Lagrangian Library
Modular library for kinetic and gyrokinetic simulations of plasmas in fusion energy devices.
sll_m_poisson_1d_periodic.F90
Go to the documentation of this file.
1 !**************************************************************
2 ! Copyright INRIA
3 ! Authors :
4 ! CALVI project team
5 !
6 ! This code SeLaLib (for Semi-Lagrangian-Library)
7 ! is a parallel library for simulating the plasma turbulence
8 ! in a tokamak.
9 !
10 ! This software is governed by the CeCILL-B license
11 ! under French law and abiding by the rules of distribution
12 ! of free software. You can use, modify and redistribute
13 ! the software under the terms of the CeCILL-B license as
14 ! circulated by CEA, CNRS and INRIA at the following URL
15 ! "http://www.cecill.info".
16 !**************************************************************
17 
22 
23 !+++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
24 #include "sll_assert.h"
25 #include "sll_memory.h"
26 #include "sll_working_precision.h"
27 #include "sll_errors.h"
28 
29  use sll_m_constants, only: &
30  sll_p_pi
31  use sll_m_poisson_1d_base, only: &
33 
34  implicit none
35 
36  public :: &
38  sll_o_new, &
41  sll_o_solve, &
43 
44  private
45 
48  sll_int32 :: nc_eta1
49  sll_real64 :: eta1_min
50  sll_real64 :: eta1_max
51  sll_real64, dimension(:), pointer :: wsave
52  sll_real64, dimension(:), pointer :: work
54 
56 
58 
59  contains
60  procedure, pass(poisson) :: init => &
62  procedure, pass(poisson) :: compute_phi_from_rho => &
64  procedure, pass(poisson) :: compute_e_from_rho => &
66 
68 
70  interface sll_o_new
71  module procedure new_poisson_1d_periodic
72  end interface
73 
75  interface sll_o_initialize
76  module procedure initialize_poisson_1d_periodic
77  end interface
78 
80  interface sll_o_solve
81  module procedure solve_poisson_1d_periodic
82  end interface
83 
84 contains
85 
88  function new_poisson_1d_periodic(eta1_min, eta1_max, nc_eta1, error) &
89  result(self)
90  type(sll_t_poisson_1d_periodic), pointer :: self
91  sll_int32, intent(in) :: nc_eta1
92  sll_int32, intent(out) :: error
93  sll_real64, intent(in) :: eta1_min
94  sll_real64, intent(in) :: eta1_max
95 
96  sll_allocate(self, error)
97  call initialize_poisson_1d_periodic(self, eta1_min, eta1_max, nc_eta1, error)
98 
99  end function new_poisson_1d_periodic
100 
102  subroutine initialize_poisson_1d_periodic(self, eta1_min, eta1_max, nc_eta1, error)
103 
104  type(sll_t_poisson_1d_periodic), intent(out) :: self
105  sll_int32, intent(in) :: nc_eta1
106  sll_int32, intent(out) :: error
107  sll_real64, intent(in) :: eta1_min
108  sll_real64, intent(in) :: eta1_max
109 
110  error = 0
111  ! geometry
112  self%nc_eta1 = nc_eta1
113  self%eta1_min = eta1_min
114  self%eta1_max = eta1_max
115 
116  sll_allocate(self%wsave(2*self%nc_eta1 + 15), error)
117 
118  call dffti(self%nc_eta1, self%wsave)
119 
120  ! Allocate auxiliary arrays for fft in order to keep rhs unchanged
121  sll_allocate(self%work(nc_eta1 + 1), error)
122 
123  end subroutine initialize_poisson_1d_periodic
124 
125  subroutine solve_poisson_1d_periodic(self, field, rhs)
126 
127  type(sll_t_poisson_1d_periodic), intent(inout) :: self
128  sll_real64, dimension(:), intent(out) :: field
129  sll_real64, dimension(:), intent(in) :: rhs
130  sll_int32 :: ik
131  sll_real64 :: kx0, kx, k2
132 
133  ! Check that field and rhs are both associated to the
134  ! same mesh with the right number of cells
135  ! that has been initialized in new_poisson_1d_periodic
136  sll_assert(size(field) == self%nc_eta1 + 1)
137  sll_assert(size(rhs) == self%nc_eta1 + 1)
138 
139  ! copy rhs into auxiliary array for fftpack
140  ! in order to keep rhs unchanged
141  self%work = rhs
142 
143  ! Forward FFT
144  call dfftf(self%nc_eta1, self%work, self%wsave)
145 
146  self%work = self%work/real(self%nc_eta1, f64) ! normalize FFT
147 
148  kx0 = 2_f64*sll_p_pi/(self%eta1_max - self%eta1_min)
149 
150  ! La moyenne de Ex est nulle donc les composantes de Fourier
151  ! correspondant a k=0 sont nulles
152  field(1) = 0.0_f64
153 
154  ! Calcul des autres composantes de Fourier
155  do ik = 1, (self%nc_eta1 - 2)/2
156  kx = real(ik, f64)*kx0
157  k2 = kx*kx
158  field(2*ik) = kx/k2*self%work(2*ik + 1)
159  field(2*ik + 1) = -kx/k2*self%work(2*ik)
160  self%work(2*ik) = 1.0_f64/k2*self%work(2*ik)
161  self%work(2*ik + 1) = 1.0_f64/k2*self%work(2*ik + 1)
162  end do
163 
164  field(self%nc_eta1) = 0.0_f64 ! because Im(rhs/2)=0
165 
166  ! Backward FFT
167 
168  call dfftb(self%nc_eta1, field, self%wsave)
169 
170  ! complete last term by periodicity
171  field(self%nc_eta1 + 1) = field(1)
172 
173  end subroutine solve_poisson_1d_periodic
174 
176  eta1_min, &
177  eta1_max, &
178  nc_eta1) &
179  result(poisson)
180 
181  type(sll_c_poisson_1d_periodic), pointer :: poisson
182  sll_real64, intent(in) :: eta1_min
183  sll_real64, intent(in) :: eta1_max
184  sll_int32, intent(in) :: nc_eta1
185  sll_int32 :: ierr
186 
187  sll_allocate(poisson, ierr)
189  poisson, &
190  eta1_min, &
191  eta1_max, &
192  nc_eta1)
193  end function sll_f_new_poisson_1d_periodic
194 
196  poisson, &
197  eta1_min, &
198  eta1_max, &
199  nc_eta1)
200  class(sll_c_poisson_1d_periodic) :: poisson
201  sll_real64, intent(in) :: eta1_min
202  sll_real64, intent(in) :: eta1_max
203  sll_int32, intent(in) :: nc_eta1
204  sll_int32 :: ierr
205 
206  call initialize_poisson_1d_periodic(poisson%poiss, eta1_min, eta1_max, nc_eta1, ierr)
207 
209 
210  ! solves -\Delta phi = rho in 2d
211  subroutine compute_phi_from_rho_1d_periodic(poisson, phi, rho)
212  class(sll_c_poisson_1d_periodic) :: poisson
213  sll_real64, dimension(:), intent(in) :: rho
214  sll_real64, dimension(:), intent(out) :: phi
215 
216  sll_error('compute_phi_from_rho_1d_periodic', 'not implemented yet')
217 
218  end subroutine compute_phi_from_rho_1d_periodic
219 
220  ! solves E = -\nabla Phi with -\Delta phi = rho in 2d
221  subroutine compute_e_from_rho_1d_periodic(poisson, E, rho)
222  class(sll_c_poisson_1d_periodic) :: poisson
223  sll_real64, dimension(:), intent(in) :: rho
224  sll_real64, dimension(:), intent(out) :: e
225 
226  call sll_o_solve(poisson%poiss, e, rho)
227 
228  end subroutine compute_e_from_rho_1d_periodic
229 
230 end module sll_m_poisson_1d_periodic
sll_o_initialize a sll_o_new poisson solver on 1d mesh
Create a sll_o_new poisson solver on 1d mesh.
sll_o_solve the Poisson equation on 1d mesh and compute the potential
Fortran module where set some physical and mathematical constants.
real(kind=f64), parameter, public sll_p_pi
Module interface to solve Poisson equation in 1D.
Module to sll_o_solve Poisson equation on one dimensional mesh using FFT transform.
subroutine solve_poisson_1d_periodic(self, field, rhs)
type(sll_c_poisson_1d_periodic) function, pointer, public sll_f_new_poisson_1d_periodic(eta1_min, eta1_max, nc_eta1)
subroutine compute_e_from_rho_1d_periodic(poisson, E, rho)
type(sll_t_poisson_1d_periodic) function, pointer new_poisson_1d_periodic(eta1_min, eta1_max, nc_eta1, error)
Create a sll_o_new solver.
subroutine initialize_poisson_1d_periodic(self, eta1_min, eta1_max, nc_eta1, error)
sll_o_initialize the solver
subroutine compute_phi_from_rho_1d_periodic(poisson, phi, rho)
subroutine initialize_poisson_1d_periodic_wrapper(poisson, eta1_min, eta1_max, nc_eta1)
    Report Typos and Errors