surfaces_interface Module

Encapsulate block boundary data for structured_grid halo exchanges


Uses

  • module~~surfaces_interface~~UsesGraph module~surfaces_interface surfaces_interface module~kind_parameters kind_parameters module~surfaces_interface->module~kind_parameters module~package_interface package_interface module~surfaces_interface->module~package_interface iso_c_binding iso_c_binding module~surfaces_interface->iso_c_binding iso_fortran_env iso_fortran_env module~kind_parameters->iso_fortran_env module~package_interface->module~kind_parameters

Used by

  • module~~surfaces_interface~~UsedByGraph module~surfaces_interface surfaces_interface module~spherical_grid_implementation spherical_grid_implementation module~spherical_grid_implementation->module~surfaces_interface module~spherical_grid_interface spherical_grid_interface module~spherical_grid_implementation->module~spherical_grid_interface module~cartesian_grid_interface cartesian_grid_interface module~cartesian_grid_interface->module~surfaces_interface module~structured_grid_interface structured_grid_interface module~cartesian_grid_interface->module~structured_grid_interface module~problem_discretization_interface problem_discretization_interface module~problem_discretization_interface->module~surfaces_interface module~problem_discretization_interface->module~structured_grid_interface module~cylindrical_grid_interface cylindrical_grid_interface module~cylindrical_grid_interface->module~surfaces_interface module~cylindrical_grid_interface->module~structured_grid_interface module~cartesian_grid_implementation cartesian_grid_implementation module~cartesian_grid_implementation->module~surfaces_interface module~cartesian_grid_implementation->module~cartesian_grid_interface module~surfaces_implementation surfaces_implementation module~surfaces_implementation->module~surfaces_interface module~spherical_grid_interface->module~surfaces_interface module~spherical_grid_interface->module~structured_grid_interface module~cylindrical_grid_implementation cylindrical_grid_implementation module~cylindrical_grid_implementation->module~surfaces_interface module~cylindrical_grid_implementation->module~cylindrical_grid_interface module~structured_grid_interface->module~surfaces_interface module~define_problem_discretization define_problem_discretization module~define_problem_discretization->module~problem_discretization_interface proc~initialize_from_plate_3d initialize_from_plate_3d proc~initialize_from_plate_3d->module~cartesian_grid_interface proc~initialize_from_sphere_1d initialize_from_sphere_1d proc~initialize_from_sphere_1d->module~spherical_grid_interface proc~evaluate evaluate proc~evaluate->module~cartesian_grid_interface proc~initialize_from_cylinder_2d initialize_from_cylinder_2d proc~initialize_from_cylinder_2d->module~cylindrical_grid_interface module~curvilinear_grid_interface curvilinear_grid_interface module~curvilinear_grid_interface->module~structured_grid_interface proc~laplacian laplacian proc~laplacian->module~cartesian_grid_interface module~structured_grid_implementation structured_grid_implementation module~structured_grid_implementation->module~structured_grid_interface

Contents


Variables

TypeVisibility AttributesNameInitial
character(len=*), public, parameter, dimension(*):: coordinate_name =["x", "y", "z"]
character(len=*), public, parameter, dimension(*):: face_name =["backward", "forward "]

Enumerations

enum, bind(c)

Enumerators

enumerator:: backward = 1

surface outward-normal direction: 'forward'/'backward' -> direction of increasing/decreasing coordinate values

enumerator:: forward = 2

surface outward-normal direction: 'forward'/'backward' -> direction of increasing/decreasing coordinate values

enumerator:: x_dir = 1
enumerator:: y_dir = 2
enumerator:: z_dir = 3

Description

array indices


Interfaces

interface

  • private pure module function get_block_image(block_id) result(image)

    result is the image that owns the given structured_grid block

    Arguments

    Type IntentOptional AttributesName
    integer, intent(in) :: block_id

    Return Value integer

interface

  • private pure module function get_global_block_partitions() result(block_partitions)

    result contains the block identifiers that start the subrange of blocks owned by each image such that [block_partitions(me), block_partitions(me+1)-1] = spans the block identifiers owned by image me

    Arguments

    None

    Return Value integer, allocatable, dimension(:)

interface

  • private module function get_halo_outbox() result(singleton_halo_outbox)

    output singleton_halo_outbox of shape [number of blocks, space_dimension, size([backward,forward])]

    Arguments

    None

    Return Value type(package), dimension(:,:,:), allocatable

interface

  • private pure module function get_neighbor_block_id(my_block_id, coordinate_direction, face_direction) result(neighbor_block_id)

    result is the block_id of the neighbor adjacent to the image that owns the given structured_grid block

    Arguments

    Type IntentOptional AttributesName
    integer, intent(in) :: my_block_id
    integer, intent(in) :: coordinate_direction
    integer, intent(in) :: face_direction

    Return Value integer

interface

  • private pure module function get_normal_scalar_fluxes(image, block_id, coordinate_direction, face_direction, scalar_id) result(fluxes)

    result contains the the surface-normal component of the designated scalar flus at the designated grid block surface

    Arguments

    Type IntentOptional AttributesName
    integer, intent(in) :: image
    integer, intent(in) :: block_id
    integer, intent(in) :: coordinate_direction
    integer, intent(in) :: face_direction
    integer, intent(in) :: scalar_id

    Return Value real(kind=r8k), allocatable, dimension(:,:)

    surface-normal scalar flux components: shape = [Ny, Nz] or [Nx, Nz] or [Nx, Ny] depending on orientation

interface

  • private pure module function get_surface_normal_spacing(image, block_id, coordinate_direction, face_direction) result(dx_normal)

    result is the distance to the nearest plane inside the specified block at the specified boundary

    Arguments

    Type IntentOptional AttributesName
    integer, intent(in) :: image
    integer, intent(in) :: block_id
    integer, intent(in) :: coordinate_direction
    integer(kind=enumeration), intent(in) :: face_direction

    Return Value real(kind=r8k)

interface

  • private pure module function get_surface_positions(image, block_id, coordinate_direction, face_direction) result(positions)

    result contains the vertices inside the designated grid block surface

    Arguments

    Type IntentOptional AttributesName
    integer, intent(in) :: image
    integer, intent(in) :: block_id
    integer, intent(in) :: coordinate_direction
    integer, intent(in) :: face_direction

    Return Value real(kind=r8k), allocatable, dimension(:,:,:,:)

    surface vertices: shape=[Nx,Ny,Nz,space_dim] where findloc(shape(positions, value=1)) designates surface-normal direction

interface

  • private elemental module function is_external_boundary(block_id, coordinate_direction, face) result(is_external)

    result is .true. if the identified structured_grid block surface corresponds to a problem domain boundary

    Arguments

    Type IntentOptional AttributesName
    integer, intent(in) :: block_id
    integer, intent(in) :: coordinate_direction
    integer(kind=enumeration), intent(in) :: face

    Return Value logical

interface

  • private module subroutine set_halo_outbox(my_halo_outbox, block_partitions)

    define halo_outbox component array

    Arguments

    Type IntentOptional AttributesName
    type(package), intent(in), dimension(:,:,:):: my_halo_outbox
    integer, intent(in), dimension(:):: block_partitions

interface

  • private module subroutine set_normal_scalar_fluxes(block_id, coordinate_direction, face, s_flux_normal, scalar_id)

    define halo outbox for a specific surface

    Arguments

    Type IntentOptional AttributesName
    integer, intent(in) :: block_id
    integer, intent(in) :: coordinate_direction
    integer(kind=enumeration), intent(in) :: face
    real(kind=r8k), intent(in), dimension(:,:):: s_flux_normal

    surface-normal scalar flux components: shape = [Ny, Nz] or [Nx, Nz] or [Nx, Ny]

    integer, intent(in) :: scalar_id

interface

  • private module subroutine set_num_scalars(num_scalars)

    allocate surface-normal scalar flux array

    Arguments

    Type IntentOptional AttributesName
    integer, intent(in) :: num_scalars

Derived Types

type, public :: surfaces

hexahedral structured_grid block surface data

Components

TypeVisibility AttributesNameInitial
type(package), private, allocatable, dimension(:,:,:):: halo_outbox

allocate to dimensions [number of blocks, space_dimension, size([forward, backward]))

Type-Bound Procedures

procedure, public, nopass :: get_block_image
procedure, public, nopass :: get_global_block_partitions
procedure, public, nopass :: get_halo_outbox
procedure, public, nopass :: get_neighbor_block_id
procedure, public, nopass :: get_normal_scalar_fluxes
procedure, public, nopass :: get_surface_normal_spacing
procedure, public, nopass :: get_surface_positions
procedure, public, nopass :: is_external_boundary
procedure, public, nopass :: set_halo_outbox
procedure, public, nopass :: set_normal_scalar_fluxes
procedure, public, nopass :: set_num_scalars