m_mesh Module


Uses

  • module~~m_mesh~~UsesGraph module~m_mesh m_mesh iso_fortran_env iso_fortran_env module~m_mesh->iso_fortran_env module~m_common m_common module~m_mesh->module~m_common module~m_field m_field module~m_mesh->module~m_field module~m_mesh_content m_mesh_content module~m_mesh->module~m_mesh_content mpi mpi module~m_mesh->mpi module~m_field->module~m_common module~m_mesh_content->module~m_common

Used by

  • module~~m_mesh~~UsedByGraph module~m_mesh m_mesh module~m_allocator m_allocator module~m_allocator->module~m_mesh module~m_base_backend m_base_backend module~m_base_backend->module~m_mesh module~m_base_backend->module~m_allocator module~m_poisson_fft m_poisson_fft module~m_base_backend->module~m_poisson_fft module~m_base_case m_base_case module~m_base_case->module~m_mesh module~m_base_case->module~m_allocator module~m_base_case->module~m_base_backend module~m_solver m_solver module~m_base_case->module~m_solver module~m_case_channel m_case_channel module~m_case_channel->module~m_mesh module~m_case_channel->module~m_allocator module~m_case_channel->module~m_base_backend module~m_case_channel->module~m_base_case module~m_case_channel->module~m_solver module~m_case_generic m_case_generic module~m_case_generic->module~m_mesh module~m_case_generic->module~m_allocator module~m_case_generic->module~m_base_backend module~m_case_generic->module~m_base_case module~m_case_generic->module~m_solver module~m_case_tgv m_case_tgv module~m_case_tgv->module~m_mesh module~m_case_tgv->module~m_allocator module~m_case_tgv->module~m_base_backend module~m_case_tgv->module~m_base_case module~m_case_tgv->module~m_solver module~m_cuda_allocator m_cuda_allocator module~m_cuda_allocator->module~m_mesh module~m_cuda_allocator->module~m_allocator module~m_cuda_backend m_cuda_backend module~m_cuda_backend->module~m_mesh module~m_cuda_backend->module~m_allocator module~m_cuda_backend->module~m_base_backend module~m_cuda_backend->module~m_cuda_allocator module~m_cuda_poisson_fft m_cuda_poisson_fft module~m_cuda_backend->module~m_cuda_poisson_fft module~m_cuda_poisson_fft->module~m_mesh module~m_cuda_poisson_fft->module~m_cuda_allocator module~m_cuda_poisson_fft->module~m_poisson_fft module~m_omp_backend m_omp_backend module~m_omp_backend->module~m_mesh module~m_omp_backend->module~m_allocator module~m_omp_backend->module~m_base_backend module~m_ordering m_ordering module~m_omp_backend->module~m_ordering module~m_omp_poisson_fft m_omp_poisson_fft module~m_omp_poisson_fft->module~m_mesh module~m_omp_poisson_fft->module~m_poisson_fft module~m_ordering->module~m_mesh module~m_poisson_fft->module~m_mesh module~m_solver->module~m_mesh module~m_solver->module~m_allocator module~m_solver->module~m_base_backend module~m_time_integrator m_time_integrator module~m_solver->module~m_time_integrator module~m_vector_calculus m_vector_calculus module~m_solver->module~m_vector_calculus program~xcompact xcompact program~xcompact->module~m_mesh program~xcompact->module~m_allocator program~xcompact->module~m_base_backend program~xcompact->module~m_base_case program~xcompact->module~m_case_channel program~xcompact->module~m_case_generic program~xcompact->module~m_case_tgv program~xcompact->module~m_cuda_allocator program~xcompact->module~m_cuda_backend program~xcompact->module~m_omp_backend module~m_time_integrator->module~m_allocator module~m_time_integrator->module~m_base_backend module~m_vector_calculus->module~m_allocator module~m_vector_calculus->module~m_base_backend proc~init_omp_poisson_fft m_omp_backend::omp_backend_t%init_omp_poisson_fft proc~init_omp_poisson_fft->module~m_omp_poisson_fft

Interfaces

public interface mesh_t

  • public function mesh_init(dims_global, nproc_dir, L_global, BC_x, BC_y, BC_z, stretching, beta, use_2decomp) result(mesh)

    Completely initialise the mesh object. Upon initialisation the mesh object can be read-only and shouldn't be edited Takes as argument global information about the mesh like its length, number of cells and decomposition in each direction

    Arguments

    Type IntentOptional Attributes Name
    integer, intent(in), dimension(3) :: dims_global
    integer, intent(in), dimension(3) :: nproc_dir
    real(kind=dp), intent(in), dimension(3) :: L_global
    character(len=*), intent(in), dimension(2) :: BC_x
    character(len=*), intent(in), dimension(2) :: BC_y
    character(len=*), intent(in), dimension(2) :: BC_z
    character(len=*), intent(in), optional, dimension(3) :: stretching
    real(kind=dp), intent(in), optional, dimension(3) :: beta
    logical, intent(in), optional :: use_2decomp

    Return Value class(mesh_t), allocatable


Derived Types

type, public ::  mesh_t

Components

Type Visibility Attributes Name Initial
type(geo_t), public, allocatable :: geo
class(grid_t), public, allocatable :: grid
class(par_t), public, allocatable :: par

Constructor

public function mesh_init (dims_global, nproc_dir, L_global, BC_x, BC_y, BC_z, stretching, beta, use_2decomp)

Completely initialise the mesh object. Upon initialisation the mesh object can be read-only and shouldn't be edited Takes as argument global information about the mesh like its length, number of cells and decomposition in each direction

Type-Bound Procedures

procedure, public :: get_SZ => get_sz
procedure, public :: get_dims
procedure, public :: get_global_dims
procedure, public :: get_n_groups_dir
procedure, public :: get_n_groups_phi
generic, public :: get_n_groups => get_n_groups_dir, get_n_groups_phi
procedure, public :: get_field_dims_dir
procedure, public :: get_field_dims_phi
procedure, public :: get_field_dims_phi_dataloc
generic, public :: get_field_dims => get_field_dims_dir, get_field_dims_phi, get_field_dims_phi_dataloc
procedure, public :: get_n_dir
procedure, public :: get_n_phi
generic, public :: get_n => get_n_dir, get_n_phi
procedure, public :: get_padded_dims_phi
procedure, public :: get_padded_dims_dir
generic, public :: get_padded_dims => get_padded_dims_dir, get_padded_dims_phi
procedure, public :: get_coordinates
procedure, public :: set_sz
procedure, public :: set_padded_dims

Functions

public function mesh_init(dims_global, nproc_dir, L_global, BC_x, BC_y, BC_z, stretching, beta, use_2decomp) result(mesh)

Completely initialise the mesh object. Upon initialisation the mesh object can be read-only and shouldn't be edited Takes as argument global information about the mesh like its length, number of cells and decomposition in each direction

Arguments

Type IntentOptional Attributes Name
integer, intent(in), dimension(3) :: dims_global
integer, intent(in), dimension(3) :: nproc_dir
real(kind=dp), intent(in), dimension(3) :: L_global
character(len=*), intent(in), dimension(2) :: BC_x
character(len=*), intent(in), dimension(2) :: BC_y
character(len=*), intent(in), dimension(2) :: BC_z
character(len=*), intent(in), optional, dimension(3) :: stretching
real(kind=dp), intent(in), optional, dimension(3) :: beta
logical, intent(in), optional :: use_2decomp

Return Value class(mesh_t), allocatable

public pure function get_sz(self) result(sz)

Getter for parameter SZ

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(in) :: self

Return Value integer

public pure function get_dims(self, data_loc) result(dims)

Getter for local domain dimensions

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(in) :: self
integer, intent(in) :: data_loc

Return Value integer, dimension(3)

public pure function get_global_dims(self, data_loc) result(dims)

Getter for local domain dimensions

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(in) :: self
integer, intent(in) :: data_loc

Return Value integer, dimension(3)

public pure function get_dims_dataloc(data_loc, vert_dims, cell_dims) result(dims)

Getter for domain dimensions

Arguments

Type IntentOptional Attributes Name
integer, intent(in) :: data_loc
integer, intent(in), dimension(3) :: vert_dims
integer, intent(in), dimension(3) :: cell_dims

Return Value integer, dimension(3)

public pure function get_padded_dims_dir(self, dir) result(dims_padded)

Getter for padded dimensions with structure in dir direction

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(in) :: self
integer, intent(in) :: dir

Return Value integer, dimension(3)

public pure function get_padded_dims_phi(self, phi) result(dims_padded)

Getter for padded dimensions for field phi Gets the field direction from the field itself

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(in) :: self
class(field_t), intent(in) :: phi

Return Value integer, dimension(3)

public pure function get_n_groups_dir(self, dir) result(n_groups)

Getter for the number of groups for fields in direction dir

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(in) :: self
integer, intent(in) :: dir

Return Value integer

public pure function get_n_groups_phi(self, phi) result(n_groups)

Getter for the number of groups for fields phi

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(in) :: self
class(field_t), intent(in) :: phi

Return Value integer

public pure function get_field_dims_phi(self, phi) result(dims)

Getter for the dimensions of field phi

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(in) :: self
class(field_t), intent(in) :: phi

Return Value integer, dimension(3)

public pure function get_field_dims_phi_dataloc(self, phi, data_loc) result(dims)

Getter for the dimensions of field phi where data is located on data_loc

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(in) :: self
class(field_t), intent(in) :: phi
integer, intent(in) :: data_loc

Return Value integer, dimension(3)

public pure function get_field_dims_dir(self, dir, data_loc) result(dims)

Getter for the dimensions of an array directed along dir where data would be located on data_loc

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(in) :: self
integer, intent(in) :: dir
integer, intent(in) :: data_loc

Return Value integer, dimension(3)

public pure function get_n_phi(self, phi) result(n)

Getter for the main dimension of field phi

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(in) :: self
class(field_t), intent(in) :: phi

Return Value integer

public pure function get_n_dir(self, dir, data_loc) result(n)

Getter for the main dimension a field oriented along dir with data on data_loc

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(in) :: self
integer, intent(in) :: dir
integer, intent(in) :: data_loc

Return Value integer

public pure function get_coordinates(self, i, j, k) result(xloc)

Get the coordinates of a vertex with i, j, k local indices

Arguments

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

Return Value real(kind=dp), dimension(3)


Subroutines

public subroutine decomposition_generic(grid, par)

Arguments

Type IntentOptional Attributes Name
class(grid_t), intent(inout) :: grid
class(par_t), intent(inout) :: par

public subroutine set_padded_dims(self, vert_dims)

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(inout) :: self
integer, intent(in), dimension(3) :: vert_dims

public subroutine set_sz(self, sz)

Arguments

Type IntentOptional Attributes Name
class(mesh_t), intent(inout) :: self
integer, intent(in) :: sz