27 use,
intrinsic :: iso_fortran_env
59 real(real64),
allocatable :: dop(:, :, :)
60 complex(real64),
allocatable :: zop(:, :, :)
61 logical :: in_device_memory = .false.
62 type(accel_mem_t) :: op_buffer
66 real(real64),
allocatable,
public :: qq(:)
67 real(real64),
public :: singularity =
m_zero
68 real(real64),
public :: mu =
m_zero
69 real(real64),
public :: alpha =
m_zero
70 real(real64),
public :: beta =
m_zero
80 type(cube_t),
target,
intent(in) :: cube
81 type(cube_function_t),
intent(inout) :: cf
82 logical,
optional,
intent(in) :: force_alloc
85 logical :: is_allocated
89 assert(.not.
associated(cf%fs))
90 assert(
allocated(cube%fft))
94 n1 = max(1, cube%fs_n(1))
95 n2 = max(1, cube%fs_n(2))
96 n3 = max(1, cube%fs_n(3))
98 is_allocated = .false.
100 select case (cube%fft%library)
102 if (.not. cf%forced_alloc)
then
103 is_allocated = .
true.
104 if (any(cube%fs_n(1:3) == 0))
then
105 cf%fs => cube%fft%fs_data(1:1,1:1,1:1)
107 cf%fs => cube%fft%fs_data(1:n3,1:n1,1:n2)
110 is_allocated = .
true.
111 safe_allocate(cf%fs(1:n3, 1:n1, 1:n2))
114 if (cf%in_device_memory)
then
115 is_allocated = .
true.
120 if (.not. cf%forced_alloc)
then
121 is_allocated = .
true.
122 cf%fs => cube%fft%fs_data(1:cube%fs_n(1), 1:cube%fs_n(2), 1:cube%fs_n(3))
126 if (.not. is_allocated)
then
127 safe_allocate(cf%fs(1:cube%fs_n(1), 1:cube%fs_n(2), 1:cube%fs_n(3)))
137 type(cube_t),
intent(in) :: cube
138 type(cube_function_t),
intent(inout) :: cf
140 logical :: deallocated
144 assert(
allocated(cube%fft))
146 deallocated = .false.
148 select case (cube%fft%library)
150 if (.not. cf%forced_alloc)
then
155 if (cf%in_device_memory)
then
160 if (.not. cf%forced_alloc)
then
166 if (.not. deallocated)
then
167 assert(
associated(cf%fs))
168 safe_deallocate_p(cf%fs)
181 if (this%in_device_memory)
then
183 this%in_device_memory = .false.
185 safe_deallocate_a(this%dop)
186 safe_deallocate_a(this%zop)
187 safe_deallocate_a(this%qq)
194#include "fourier_space_inc.F90"
197#include "complex.F90"
198#include "fourier_space_inc.F90"
integer, parameter, public accel_mem_read_write
subroutine, public accel_release_buffer(this)
Fast Fourier Transform module. This module provides a single interface that works with different FFT ...
integer, parameter, public fftlib_accel
integer, parameter, public fftlib_pfft
integer, parameter, public fftlib_fftw
subroutine, public zfourier_space_op_apply(this, cube, cf)
Applies a multiplication factor to the Fourier space grid. This is a local function.
subroutine, public dfourier_space_op_apply(this, cube, cf)
Applies a multiplication factor to the Fourier space grid. This is a local function.
subroutine, public fourier_space_op_end(this)
subroutine, public dfourier_space_op_init(this, cube, op, in_device)
subroutine, public zcube_function_fs2rs(cube, cf)
subroutine, public dcube_function_fs2rs(cube, cf)
subroutine, public cube_function_free_fs(cube, cf)
Deallocates the Fourier space grid.
subroutine, public zfourier_space_op_init(this, cube, op, in_device)
subroutine, public zcube_function_rs2fs(cube, cf)
The following routines convert the function between real space and Fourier space Note that the dimens...
subroutine, public cube_function_alloc_fs(cube, cf, force_alloc)
Allocates locally the Fourier space grid, if PFFT library is not used. Otherwise, it assigns the PFFT...
subroutine, public dcube_function_rs2fs(cube, cf)
The following routines convert the function between real space and Fourier space Note that the dimens...
real(real64), parameter, public m_zero
This module is intended to contain "only mathematical" functions and procedures.
The low level module to work with the PFFT library. http:
type(type_t), public type_cmplx