m_omp_backend Module


Uses

  • module~~m_omp_backend~~UsesGraph module~m_omp_backend m_omp_backend module~m_allocator m_allocator module~m_omp_backend->module~m_allocator module~m_base_backend m_base_backend module~m_omp_backend->module~m_base_backend module~m_common m_common module~m_omp_backend->module~m_common module~m_field m_field module~m_omp_backend->module~m_field module~m_mesh m_mesh module~m_omp_backend->module~m_mesh module~m_omp_common m_omp_common module~m_omp_backend->module~m_omp_common module~m_omp_exec_dist m_omp_exec_dist module~m_omp_backend->module~m_omp_exec_dist module~m_omp_sendrecv m_omp_sendrecv module~m_omp_backend->module~m_omp_sendrecv module~m_ordering m_ordering module~m_omp_backend->module~m_ordering module~m_tdsops m_tdsops module~m_omp_backend->module~m_tdsops mpi mpi module~m_omp_backend->mpi module~m_allocator->module~m_common module~m_allocator->module~m_field iso_fortran_env iso_fortran_env module~m_allocator->iso_fortran_env module~m_base_backend->module~m_allocator module~m_base_backend->module~m_common module~m_base_backend->module~m_field module~m_base_backend->module~m_mesh module~m_base_backend->module~m_tdsops module~m_base_backend->mpi module~m_poisson_fft m_poisson_fft module~m_base_backend->module~m_poisson_fft module~m_field->module~m_common module~m_mesh->module~m_common module~m_mesh->module~m_field module~m_mesh->mpi module~m_mesh->iso_fortran_env module~m_mesh_content m_mesh_content module~m_mesh->module~m_mesh_content module~m_omp_exec_dist->module~m_common module~m_omp_exec_dist->module~m_omp_common module~m_omp_exec_dist->module~m_omp_sendrecv module~m_omp_exec_dist->module~m_tdsops module~m_omp_exec_dist->mpi module~m_omp_kernels_dist m_omp_kernels_dist module~m_omp_exec_dist->module~m_omp_kernels_dist module~m_omp_sendrecv->module~m_common module~m_omp_sendrecv->mpi module~m_ordering->module~m_common module~m_tdsops->module~m_common module~m_tdsops->iso_fortran_env module~m_mesh_content->module~m_common module~m_omp_kernels_dist->module~m_common module~m_omp_kernels_dist->module~m_omp_common omp_lib omp_lib module~m_omp_kernels_dist->omp_lib module~m_poisson_fft->module~m_common module~m_poisson_fft->module~m_field module~m_poisson_fft->module~m_mesh module~m_poisson_fft->module~m_tdsops

Used by

  • module~~m_omp_backend~~UsedByGraph module~m_omp_backend m_omp_backend program~xcompact xcompact program~xcompact->module~m_omp_backend

Interfaces

public interface omp_backend_t

  • public function init(mesh, allocator) result(backend)

    Arguments

    Type IntentOptional Attributes Name
    type(mesh_t), intent(inout), target :: mesh
    class(allocator_t), intent(inout), target :: allocator

    Return Value type(omp_backend_t)


Derived Types

type, public, extends(base_backend_t) ::  omp_backend_t

Components

Type Visibility Attributes Name Initial
integer, public :: n_halo = 4

DistD2 implementation is hardcoded for 4 halo layers for all backends

type(mesh_t), public, pointer :: mesh
class(allocator_t), public, pointer :: allocator
class(poisson_fft_t), public, pointer :: poisson_fft
integer, public :: MPI_FP_PREC = dp
real(kind=dp), public, allocatable, dimension(:, :, :) :: u_recv_s
real(kind=dp), public, allocatable, dimension(:, :, :) :: u_recv_e
real(kind=dp), public, allocatable, dimension(:, :, :) :: u_send_s
real(kind=dp), public, allocatable, dimension(:, :, :) :: u_send_e
real(kind=dp), public, allocatable, dimension(:, :, :) :: v_recv_s
real(kind=dp), public, allocatable, dimension(:, :, :) :: v_recv_e
real(kind=dp), public, allocatable, dimension(:, :, :) :: v_send_s
real(kind=dp), public, allocatable, dimension(:, :, :) :: v_send_e
real(kind=dp), public, allocatable, dimension(:, :, :) :: w_recv_s
real(kind=dp), public, allocatable, dimension(:, :, :) :: w_recv_e
real(kind=dp), public, allocatable, dimension(:, :, :) :: w_send_s
real(kind=dp), public, allocatable, dimension(:, :, :) :: w_send_e
real(kind=dp), public, allocatable, dimension(:, :, :) :: du_send_s
real(kind=dp), public, allocatable, dimension(:, :, :) :: du_send_e
real(kind=dp), public, allocatable, dimension(:, :, :) :: du_recv_s
real(kind=dp), public, allocatable, dimension(:, :, :) :: du_recv_e
real(kind=dp), public, allocatable, dimension(:, :, :) :: dud_send_s
real(kind=dp), public, allocatable, dimension(:, :, :) :: dud_send_e
real(kind=dp), public, allocatable, dimension(:, :, :) :: dud_recv_s
real(kind=dp), public, allocatable, dimension(:, :, :) :: dud_recv_e
real(kind=dp), public, allocatable, dimension(:, :, :) :: d2u_send_s
real(kind=dp), public, allocatable, dimension(:, :, :) :: d2u_send_e
real(kind=dp), public, allocatable, dimension(:, :, :) :: d2u_recv_s
real(kind=dp), public, allocatable, dimension(:, :, :) :: d2u_recv_e

Constructor

public function init (mesh, allocator)

Type-Bound Procedures

procedure, public :: base_init
procedure, public :: get_field_data
procedure, public :: set_field_data
procedure, public :: alloc_tdsops => alloc_omp_tdsops
procedure, public :: transeq_x => transeq_x_omp
procedure, public :: transeq_y => transeq_y_omp
procedure, public :: transeq_z => transeq_z_omp
procedure, public :: transeq_species => transeq_species_omp
procedure, public :: tds_solve => tds_solve_omp
procedure, public :: reorder => reorder_omp
procedure, public :: sum_yintox => sum_yintox_omp
procedure, public :: sum_zintox => sum_zintox_omp
procedure, public :: veccopy => veccopy_omp
procedure, public :: vecadd => vecadd_omp
procedure, public :: vecmult => vecmult_omp
procedure, public :: scalar_product => scalar_product_omp
procedure, public :: field_max_mean => field_max_mean_omp
procedure, public :: field_scale => field_scale_omp
procedure, public :: field_shift => field_shift_omp
procedure, public :: field_set_face => field_set_face_omp
procedure, public :: field_volume_integral => field_volume_integral_omp
procedure, public :: copy_data_to_f => copy_data_to_f_omp
procedure, public :: copy_f_to_data => copy_f_to_data_omp
procedure, public :: init_poisson_fft => init_omp_poisson_fft
procedure, public :: transeq_omp_dist

Functions

public function init(mesh, allocator) result(backend)

Arguments

Type IntentOptional Attributes Name
type(mesh_t), intent(inout), target :: mesh
class(allocator_t), intent(inout), target :: allocator

Return Value type(omp_backend_t)

public function scalar_product_omp(self, x, y) result(s)

m_base_backend

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(in) :: x
class(field_t), intent(in) :: y

Return Value real(kind=dp)

public function field_volume_integral_omp(self, f) result(s)

volume integral of a field

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(in) :: f

Return Value real(kind=dp)


Subroutines

public subroutine alloc_omp_tdsops(self, tdsops, n_tds, delta, operation, scheme, bc_start, bc_end, stretch, stretch_correct, n_halo, from_to, sym, c_nu, nu0_nu)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(tdsops_t), intent(inout), allocatable :: tdsops
integer, intent(in) :: n_tds
real(kind=dp), intent(in) :: delta
character(len=*), intent(in) :: operation
character(len=*), intent(in) :: scheme
integer, intent(in) :: bc_start
integer, intent(in) :: bc_end
real(kind=dp), intent(in), optional :: stretch(:)
real(kind=dp), intent(in), optional :: stretch_correct(:)
integer, intent(in), optional :: n_halo
character(len=*), intent(in), optional :: from_to
logical, intent(in), optional :: sym
real(kind=dp), intent(in), optional :: c_nu
real(kind=dp), intent(in), optional :: nu0_nu

public subroutine transeq_x_omp(self, du, dv, dw, u, v, w, nu, dirps)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: du
class(field_t), intent(inout) :: dv
class(field_t), intent(inout) :: dw
class(field_t), intent(in) :: u
class(field_t), intent(in) :: v
class(field_t), intent(in) :: w
real(kind=dp), intent(in) :: nu
type(dirps_t), intent(in) :: dirps

public subroutine transeq_y_omp(self, du, dv, dw, u, v, w, nu, dirps)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: du
class(field_t), intent(inout) :: dv
class(field_t), intent(inout) :: dw
class(field_t), intent(in) :: u
class(field_t), intent(in) :: v
class(field_t), intent(in) :: w
real(kind=dp), intent(in) :: nu
type(dirps_t), intent(in) :: dirps

public subroutine transeq_z_omp(self, du, dv, dw, u, v, w, nu, dirps)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: du
class(field_t), intent(inout) :: dv
class(field_t), intent(inout) :: dw
class(field_t), intent(in) :: u
class(field_t), intent(in) :: v
class(field_t), intent(in) :: w
real(kind=dp), intent(in) :: nu
type(dirps_t), intent(in) :: dirps

public subroutine transeq_species_omp(self, dspec, uvw, spec, nu, dirps, sync)

Compute the convection and diffusion for the given field in the given direction. Halo exchange for the given field is necessary When sync is true, halo exchange of momentum is necessary

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: dspec
class(field_t), intent(in) :: uvw
class(field_t), intent(in) :: spec
real(kind=dp), intent(in) :: nu
type(dirps_t), intent(in) :: dirps
logical, intent(in) :: sync

public subroutine transeq_omp_dist(self, du, dv, dw, u, v, w, nu, dirps)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: du
class(field_t), intent(inout) :: dv
class(field_t), intent(inout) :: dw
class(field_t), intent(in) :: u
class(field_t), intent(in) :: v
class(field_t), intent(in) :: w
real(kind=dp), intent(in) :: nu
type(dirps_t), intent(in) :: dirps

public subroutine tds_solve_omp(self, du, u, tdsops)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: du
class(field_t), intent(in) :: u
class(tdsops_t), intent(in) :: tdsops

public subroutine tds_solve_dist(self, du, u, tdsops)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: du
class(field_t), intent(in) :: u
class(tdsops_t), intent(in) :: tdsops

public subroutine reorder_omp(self, u_, u, direction)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: u_
class(field_t), intent(in) :: u
integer, intent(in) :: direction

public subroutine sum_yintox_omp(self, u, u_)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: u
class(field_t), intent(in) :: u_

public subroutine sum_zintox_omp(self, u, u_)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: u
class(field_t), intent(in) :: u_

public subroutine sum_intox_omp(self, u, u_, dir_to)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: u
class(field_t), intent(in) :: u_
integer, intent(in) :: dir_to

public subroutine veccopy_omp(self, dst, src)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: dst
class(field_t), intent(in) :: src

public subroutine vecadd_omp(self, a, x, b, y)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
real(kind=dp), intent(in) :: a
class(field_t), intent(in) :: x
real(kind=dp), intent(in) :: b
class(field_t), intent(inout) :: y

public subroutine vecmult_omp(self, y, x)

m_base_backend

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: y
class(field_t), intent(in) :: x

public subroutine copy_into_buffers(u_send_s, u_send_e, u, n, n_groups)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(out), dimension(:, :, :) :: u_send_s
real(kind=dp), intent(out), dimension(:, :, :) :: u_send_e
real(kind=dp), intent(in), dimension(:, :, :) :: u
integer, intent(in) :: n
integer, intent(in) :: n_groups

public subroutine field_max_mean_omp(self, max_val, mean_val, f, enforced_data_loc)

m_base_backend

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
real(kind=dp), intent(out) :: max_val
real(kind=dp), intent(out) :: mean_val
class(field_t), intent(in) :: f
integer, intent(in), optional :: enforced_data_loc

public subroutine field_scale_omp(self, f, a)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(in) :: f
real(kind=dp), intent(in) :: a

public subroutine field_shift_omp(self, f, a)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(in) :: f
real(kind=dp), intent(in) :: a

public subroutine field_set_face_omp(self, f, c_start, c_end, face)

m_base_backend

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t) :: self
class(field_t), intent(inout) :: f
real(kind=dp), intent(in) :: c_start
real(kind=dp), intent(in) :: c_end
integer, intent(in) :: face

public subroutine copy_data_to_f_omp(self, f, data)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t), intent(inout) :: self
class(field_t), intent(inout) :: f
real(kind=dp), intent(in), dimension(:, :, :) :: data

public subroutine copy_f_to_data_omp(self, data, f)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_t), intent(inout) :: self
real(kind=dp), intent(out), dimension(:, :, :) :: data
class(field_t), intent(in) :: f

public subroutine init_omp_poisson_fft(self, mesh, xdirps, ydirps, zdirps, lowmem)

Arguments

Type IntentOptional Attributes Name
class(omp_backend_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
logical, intent(in), optional :: lowmem