m_cuda_backend Module


Uses

  • module~~m_cuda_backend~~UsesGraph module~m_cuda_backend m_cuda_backend cudafor cudafor module~m_cuda_backend->cudafor iso_fortran_env iso_fortran_env module~m_cuda_backend->iso_fortran_env module~m_allocator m_allocator module~m_cuda_backend->module~m_allocator module~m_base_backend m_base_backend module~m_cuda_backend->module~m_base_backend module~m_common m_common module~m_cuda_backend->module~m_common module~m_cuda_allocator m_cuda_allocator module~m_cuda_backend->module~m_cuda_allocator module~m_cuda_common m_cuda_common module~m_cuda_backend->module~m_cuda_common module~m_cuda_exec_dist m_cuda_exec_dist module~m_cuda_backend->module~m_cuda_exec_dist module~m_cuda_kernels_dist m_cuda_kernels_dist module~m_cuda_backend->module~m_cuda_kernels_dist module~m_cuda_kernels_fieldops m_cuda_kernels_fieldops module~m_cuda_backend->module~m_cuda_kernels_fieldops module~m_cuda_kernels_reorder m_cuda_kernels_reorder module~m_cuda_backend->module~m_cuda_kernels_reorder module~m_cuda_poisson_fft m_cuda_poisson_fft module~m_cuda_backend->module~m_cuda_poisson_fft module~m_cuda_sendrecv m_cuda_sendrecv module~m_cuda_backend->module~m_cuda_sendrecv module~m_cuda_tdsops m_cuda_tdsops module~m_cuda_backend->module~m_cuda_tdsops module~m_field m_field module~m_cuda_backend->module~m_field module~m_mesh m_mesh module~m_cuda_backend->module~m_mesh module~m_tdsops m_tdsops module~m_cuda_backend->module~m_tdsops mpi mpi module~m_cuda_backend->mpi module~m_allocator->iso_fortran_env module~m_allocator->module~m_common module~m_allocator->module~m_field module~m_allocator->module~m_mesh 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_cuda_allocator->module~m_allocator module~m_cuda_allocator->module~m_common module~m_cuda_allocator->module~m_field module~m_cuda_allocator->module~m_mesh module~m_cuda_exec_dist->cudafor module~m_cuda_exec_dist->module~m_common module~m_cuda_exec_dist->module~m_cuda_common module~m_cuda_exec_dist->module~m_cuda_kernels_dist module~m_cuda_exec_dist->module~m_cuda_sendrecv module~m_cuda_exec_dist->module~m_cuda_tdsops module~m_cuda_exec_dist->mpi module~m_cuda_kernels_dist->cudafor module~m_cuda_kernels_dist->module~m_common module~m_cuda_kernels_fieldops->cudafor module~m_cuda_kernels_fieldops->module~m_common module~m_cuda_kernels_fieldops->module~m_cuda_common module~m_cuda_kernels_reorder->cudafor module~m_cuda_kernels_reorder->module~m_common module~m_cuda_kernels_reorder->module~m_cuda_common module~m_cuda_poisson_fft->cudafor module~m_cuda_poisson_fft->iso_fortran_env module~m_cuda_poisson_fft->module~m_common module~m_cuda_poisson_fft->module~m_cuda_allocator module~m_cuda_poisson_fft->module~m_field module~m_cuda_poisson_fft->module~m_mesh module~m_cuda_poisson_fft->module~m_tdsops module~m_cuda_poisson_fft->mpi cufft cufft module~m_cuda_poisson_fft->cufft cufftXt cufftXt module~m_cuda_poisson_fft->cufftXt iso_c_binding iso_c_binding module~m_cuda_poisson_fft->iso_c_binding module~m_cuda_spectral m_cuda_spectral module~m_cuda_poisson_fft->module~m_cuda_spectral module~m_cuda_poisson_fft->module~m_poisson_fft module~m_cuda_sendrecv->cudafor module~m_cuda_sendrecv->module~m_common module~m_cuda_sendrecv->mpi module~m_cuda_tdsops->iso_fortran_env module~m_cuda_tdsops->module~m_common module~m_cuda_tdsops->module~m_tdsops module~m_field->module~m_common module~m_mesh->iso_fortran_env module~m_mesh->module~m_common module~m_mesh->module~m_field module~m_mesh->mpi module~m_mesh_content m_mesh_content module~m_mesh->module~m_mesh_content module~m_tdsops->iso_fortran_env module~m_tdsops->module~m_common module~m_cuda_spectral->cudafor module~m_cuda_spectral->module~m_common module~m_mesh_content->module~m_common 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_cuda_backend~~UsedByGraph module~m_cuda_backend m_cuda_backend program~xcompact xcompact program~xcompact->module~m_cuda_backend

Interfaces

public interface cuda_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(cuda_backend_t)


Derived Types

type, public, extends(base_backend_t) ::  cuda_backend_t

Components

Type Visibility Attributes Name Initial
real(kind=dp), public :: nu
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, device, allocatable, dimension(:, :, :) :: u_recv_s_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: u_recv_e_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: u_send_s_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: u_send_e_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: v_recv_s_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: v_recv_e_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: v_send_s_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: v_send_e_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: w_recv_s_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: w_recv_e_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: w_send_s_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: w_send_e_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: du_send_s_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: du_send_e_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: du_recv_s_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: du_recv_e_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: dud_send_s_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: dud_send_e_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: dud_recv_s_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: dud_recv_e_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: d2u_send_s_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: d2u_send_e_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: d2u_recv_s_dev
real(kind=dp), public, device, allocatable, dimension(:, :, :) :: d2u_recv_e_dev
type(dim3), public :: xblocks
type(dim3), public :: xthreads
type(dim3), public :: yblocks
type(dim3), public :: ythreads
type(dim3), public :: zblocks
type(dim3), public :: zthreads

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_cuda_tdsops
procedure, public :: transeq_x => transeq_x_cuda
procedure, public :: transeq_y => transeq_y_cuda
procedure, public :: transeq_z => transeq_z_cuda
procedure, public :: tds_solve => tds_solve_cuda
procedure, public :: reorder => reorder_cuda
procedure, public :: sum_yintox => sum_yintox_cuda
procedure, public :: sum_zintox => sum_zintox_cuda
procedure, public :: vecadd => vecadd_cuda
procedure, public :: scalar_product => scalar_product_cuda
procedure, public :: field_max_mean => field_max_mean_cuda
procedure, public :: field_scale => field_scale_cuda
procedure, public :: field_shift => field_shift_cuda
procedure, public :: field_set_face => field_set_face_cuda
procedure, public :: field_volume_integral => field_volume_integral_cuda
procedure, public :: copy_data_to_f => copy_data_to_f_cuda
procedure, public :: copy_f_to_data => copy_f_to_data_cuda
procedure, public :: init_poisson_fft => init_cuda_poisson_fft
procedure, public :: transeq_cuda_dist
procedure, public :: transeq_cuda_thom
procedure, public :: tds_solve_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(cuda_backend_t)

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

m_base_backend

Arguments

Type IntentOptional Attributes Name
class(cuda_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_cuda(self, f) result(s)

volume integral of a field

Arguments

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

Return Value real(kind=dp)


Subroutines

public subroutine alloc_cuda_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(cuda_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_cuda(self, du, dv, dw, u, v, w, dirps)

Arguments

Type IntentOptional Attributes Name
class(cuda_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
type(dirps_t), intent(in) :: dirps

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

Arguments

Type IntentOptional Attributes Name
class(cuda_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
type(dirps_t), intent(in) :: dirps

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

Arguments

Type IntentOptional Attributes Name
class(cuda_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
type(dirps_t), intent(in) :: dirps

public subroutine transeq_cuda_dist(self, du, dv, dw, u, v, w, dirps, blocks, threads)

Arguments

Type IntentOptional Attributes Name
class(cuda_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
type(dirps_t), intent(in) :: dirps
type(dim3), intent(in) :: blocks
type(dim3), intent(in) :: threads

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

Thomas algorithm implementation. So much more easier than the distributed algorithm. It is intended to work only on a single rank so there is no MPI communication.

Arguments

Type IntentOptional Attributes Name
class(cuda_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
type(dirps_t), intent(in) :: dirps

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

Arguments

Type IntentOptional Attributes Name
class(cuda_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, blocks, threads)

Arguments

Type IntentOptional Attributes Name
class(cuda_backend_t) :: self
class(field_t), intent(inout) :: du
class(field_t), intent(in) :: u
class(tdsops_t), intent(in) :: tdsops
type(dim3), intent(in) :: blocks
type(dim3), intent(in) :: threads

public subroutine reorder_cuda(self, u_o, u_i, direction)

Arguments

Type IntentOptional Attributes Name
class(cuda_backend_t) :: self
class(field_t), intent(inout) :: u_o
class(field_t), intent(in) :: u_i
integer, intent(in) :: direction

public subroutine sum_yintox_cuda(self, u, u_y)

Arguments

Type IntentOptional Attributes Name
class(cuda_backend_t) :: self
class(field_t), intent(inout) :: u
class(field_t), intent(in) :: u_y

public subroutine sum_zintox_cuda(self, u, u_z)

Arguments

Type IntentOptional Attributes Name
class(cuda_backend_t) :: self
class(field_t), intent(inout) :: u
class(field_t), intent(in) :: u_z

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

Arguments

Type IntentOptional Attributes Name
class(cuda_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 copy_into_buffers(u_send_s_dev, u_send_e_dev, u_dev, n)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(out), device, dimension(:, :, :) :: u_send_s_dev
real(kind=dp), intent(out), device, dimension(:, :, :) :: u_send_e_dev
real(kind=dp), intent(in), device, dimension(:, :, :) :: u_dev
integer, intent(in) :: n

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

m_base_backend

Arguments

Type IntentOptional Attributes Name
class(cuda_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_cuda(self, f, a)

Arguments

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

public subroutine field_shift_cuda(self, f, a)

Arguments

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

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

m_base_backend

Arguments

Type IntentOptional Attributes Name
class(cuda_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_cuda(self, f, data)

Arguments

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

public subroutine copy_f_to_data_cuda(self, data, f)

Arguments

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

public subroutine init_cuda_poisson_fft(self, mesh, xdirps, ydirps, zdirps)

Arguments

Type IntentOptional Attributes Name
class(cuda_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

public subroutine resolve_field_t(u_dev, u)

Arguments

Type IntentOptional Attributes Name
real(kind=dp), intent(out), device, pointer, dimension(:, :, :) :: u_dev
class(field_t), intent(in) :: u