poisson_fft_t Derived Type

type, public, abstract :: poisson_fft_t

FFT based Poisson solver


Inherited by

type~~poisson_fft_t~~InheritedByGraph type~poisson_fft_t poisson_fft_t type~base_backend_t base_backend_t type~base_backend_t->type~poisson_fft_t poisson_fft type~cuda_poisson_fft_t cuda_poisson_fft_t type~cuda_poisson_fft_t->type~poisson_fft_t type~omp_poisson_fft_t omp_poisson_fft_t type~omp_poisson_fft_t->type~poisson_fft_t type~cuda_backend_t cuda_backend_t type~cuda_backend_t->type~base_backend_t type~ibm_t ibm_t type~ibm_t->type~base_backend_t backend type~omp_backend_t omp_backend_t type~omp_backend_t->type~base_backend_t type~solver_t solver_t type~solver_t->type~base_backend_t backend type~solver_t->type~ibm_t ibm type~time_intg_t time_intg_t type~solver_t->type~time_intg_t time_integrator type~vector_calculus_t vector_calculus_t type~solver_t->type~vector_calculus_t vector_calculus type~time_intg_t->type~base_backend_t backend type~vector_calculus_t->type~base_backend_t backend type~base_case_t base_case_t type~base_case_t->type~solver_t solver type~case_channel_t case_channel_t type~case_channel_t->type~base_case_t type~case_generic_t case_generic_t type~case_generic_t->type~base_case_t type~case_tgv_t case_tgv_t type~case_tgv_t->type~base_case_t

Components

Type Visibility Attributes Name Initial
integer, public :: nx_glob

Global dimensions

integer, public :: ny_glob

Global dimensions

integer, public :: nz_glob

Global dimensions

integer, public :: nx_loc

Local dimensions

integer, public :: ny_loc

Local dimensions

integer, public :: nz_loc

Local dimensions

integer, public :: nx_perm

Local dimensions in the permuted slabs

integer, public :: ny_perm

Local dimensions in the permuted slabs

integer, public :: nz_perm

Local dimensions in the permuted slabs

integer, public :: nx_spec

Local dimensions in the permuted slabs in spectral space

integer, public :: ny_spec

Local dimensions in the permuted slabs in spectral space

integer, public :: nz_spec

Local dimensions in the permuted slabs in spectral space

integer, public :: x_sp_st

Offset in y and z directions in the permuted slabs in spectral space

integer, public :: y_sp_st

Offset in y and z directions in the permuted slabs in spectral space

integer, public :: z_sp_st

Offset in y and z directions in the permuted slabs in spectral space

complex(kind=dp), public, allocatable, dimension(:, :, :) :: waves

Local domain sized array storing the spectral equivalence constants

real(kind=dp), public, allocatable, dimension(:) :: ax

Wave numbers in x, y, and z

real(kind=dp), public, allocatable, dimension(:) :: bx

Wave numbers in x, y, and z

real(kind=dp), public, allocatable, dimension(:) :: ay

Wave numbers in x, y, and z

real(kind=dp), public, allocatable, dimension(:) :: by

Wave numbers in x, y, and z

real(kind=dp), public, allocatable, dimension(:) :: az

Wave numbers in x, y, and z

real(kind=dp), public, allocatable, dimension(:) :: bz

Wave numbers in x, y, and z

complex(kind=dp), public, allocatable, dimension(:) :: kx

Wave numbers in x, y, and z

complex(kind=dp), public, allocatable, dimension(:) :: ky

Wave numbers in x, y, and z

complex(kind=dp), public, allocatable, dimension(:) :: kz

Wave numbers in x, y, and z

complex(kind=dp), public, allocatable, dimension(:) :: exs

Wave numbers in x, y, and z

complex(kind=dp), public, allocatable, dimension(:) :: eys

Wave numbers in x, y, and z

complex(kind=dp), public, allocatable, dimension(:) :: ezs

Wave numbers in x, y, and z

complex(kind=dp), public, allocatable, dimension(:) :: k2x

Wave numbers in x, y, and z

complex(kind=dp), public, allocatable, dimension(:) :: k2y

Wave numbers in x, y, and z

complex(kind=dp), public, allocatable, dimension(:) :: k2z

Wave numbers in x, y, and z

real(kind=dp), public, allocatable, dimension(:) :: trans_x_re

Staggared grid transformation

real(kind=dp), public, allocatable, dimension(:) :: trans_x_im

Staggared grid transformation

real(kind=dp), public, allocatable, dimension(:) :: trans_y_re

Staggared grid transformation

real(kind=dp), public, allocatable, dimension(:) :: trans_y_im

Staggared grid transformation

real(kind=dp), public, allocatable, dimension(:) :: trans_z_re

Staggared grid transformation

real(kind=dp), public, allocatable, dimension(:) :: trans_z_im

Staggared grid transformation

logical, public :: periodic_x

Periodicity in x, y, and z

logical, public :: periodic_y

Periodicity in x, y, and z

logical, public :: periodic_z

Periodicity in x, y, and z

logical, public :: stretched_y = .false.

Periodicity in x, y, and z

logical, public :: stretched_y_sym

Periodicity in x, y, and z

real(kind=dp), public, allocatable, dimension(:, :, :, :) :: a_odd_re

Stretching operator matrices

real(kind=dp), public, allocatable, dimension(:, :, :, :) :: a_odd_im

Stretching operator matrices

real(kind=dp), public, allocatable, dimension(:, :, :, :) :: a_even_re

Stretching operator matrices

real(kind=dp), public, allocatable, dimension(:, :, :, :) :: a_even_im

Stretching operator matrices

real(kind=dp), public, allocatable, dimension(:, :, :, :) :: a_re

Stretching operator matrices

real(kind=dp), public, allocatable, dimension(:, :, :, :) :: a_im

Stretching operator matrices

logical, public :: lowmem = .false.

lowmem option, only used in CUDA backend

procedure(poisson_xxx), public, pointer :: poisson => null()

Procedure pointer to BC specific poisson solvers


Type-Bound Procedures

procedure(fft_forward), public, deferred :: fft_forward

  • subroutine fft_forward(self, f_in) Prototype

    Arguments

    Type IntentOptional Attributes Name
    class(poisson_fft_t) :: self
    class(field_t), intent(in) :: f_in

procedure(fft_backward), public, deferred :: fft_backward

  • subroutine fft_backward(self, f_out) Prototype

    Arguments

    Type IntentOptional Attributes Name
    class(poisson_fft_t) :: self
    class(field_t), intent(inout) :: f_out

procedure(fft_postprocess), public, deferred :: fft_postprocess_000

  • subroutine fft_postprocess(self) Prototype

    Arguments

    Type IntentOptional Attributes Name
    class(poisson_fft_t) :: self

procedure(fft_postprocess), public, deferred :: fft_postprocess_010

  • subroutine fft_postprocess(self) Prototype

    Arguments

    Type IntentOptional Attributes Name
    class(poisson_fft_t) :: self

procedure(field_process), public, deferred :: enforce_periodicity_y

  • subroutine field_process(self, f_out, f_in) Prototype

    Arguments

    Type IntentOptional Attributes Name
    class(poisson_fft_t) :: self
    class(field_t), intent(inout) :: f_out
    class(field_t), intent(in) :: f_in

procedure(field_process), public, deferred :: undo_periodicity_y

  • subroutine field_process(self, f_out, f_in) Prototype

    Arguments

    Type IntentOptional Attributes Name
    class(poisson_fft_t) :: self
    class(field_t), intent(inout) :: f_out
    class(field_t), intent(in) :: f_in

procedure, public :: base_init

  • public subroutine base_init(self, mesh, xdirps, ydirps, zdirps, n_spec, n_sp_st)

    Arguments

    Type IntentOptional Attributes Name
    class(poisson_fft_t) :: self
    type(mesh_t), intent(in) :: mesh
    type(dirps_t), intent(in) :: xdirps
    type(dirps_t), intent(in) :: ydirps
    type(dirps_t), intent(in) :: zdirps
    integer, intent(in), dimension(3) :: n_spec
    integer, intent(in), dimension(3) :: n_sp_st

procedure, public :: solve_poisson

procedure, public :: stretching_matrix

  • public subroutine stretching_matrix(self, geo, xdirps, ydirps, zdirps)

    Stretching necessitates a special operation in spectral space. The coefficients for the operation are stored in matrix form.

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(poisson_fft_t) :: self
    type(geo_t), intent(in) :: geo
    type(dirps_t), intent(in) :: xdirps
    type(dirps_t), intent(in) :: ydirps
    type(dirps_t), intent(in) :: zdirps

procedure, public :: waves_set

  • public subroutine waves_set(self, geo, xdirps, ydirps, zdirps)

    Spectral equivalence constants

    Read more…

    Arguments

    Type IntentOptional Attributes Name
    class(poisson_fft_t) :: self
    type(geo_t), intent(in) :: geo
    type(dirps_t), intent(in) :: xdirps
    type(dirps_t), intent(in) :: ydirps
    type(dirps_t), intent(in) :: zdirps

procedure, public :: get_km

  • public function get_km(self, i, j, k) result(km)

    Arguments

    Type IntentOptional Attributes Name
    class(poisson_fft_t) :: self
    integer, intent(in) :: i
    integer, intent(in) :: j
    integer, intent(in) :: k

    Return Value complex(kind=dp)

procedure, public :: get_km_re

  • public function get_km_re(self, i, j, k) result(re)

    Arguments

    Type IntentOptional Attributes Name
    class(poisson_fft_t) :: self
    integer, intent(in) :: i
    integer, intent(in) :: j
    integer, intent(in) :: k

    Return Value real(kind=dp)

procedure, public :: get_km_im

  • public function get_km_im(self, i, j, k) result(re)

    Arguments

    Type IntentOptional Attributes Name
    class(poisson_fft_t) :: self
    integer, intent(in) :: i
    integer, intent(in) :: j
    integer, intent(in) :: k

    Return Value real(kind=dp)