surfaces Derived Type

type, public :: surfaces

hexahedral structured_grid block surface data


Inherits

type~~surfaces~~InheritsGraph type~surfaces surfaces type~package package type~surfaces->type~package halo_outbox type~flux_planes flux_planes type~package->type~flux_planes surface_normal_fluxes

Inherited by

type~~surfaces~~InheritedByGraph type~surfaces surfaces type~problem_discretization problem_discretization type~problem_discretization->type~surfaces block_surfaces

Contents


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

  • 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

procedure, public, nopass :: get_global_block_partitions

  • 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(:)

procedure, public, nopass :: get_halo_outbox

  • 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

procedure, public, nopass :: get_neighbor_block_id

  • 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

procedure, public, nopass :: get_normal_scalar_fluxes

  • 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

procedure, public, nopass :: get_surface_normal_spacing

  • 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)

procedure, public, nopass :: get_surface_positions

  • 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

procedure, public, nopass :: is_external_boundary

  • 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

procedure, public, nopass :: set_halo_outbox

  • 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

procedure, public, nopass :: set_normal_scalar_fluxes

  • 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

procedure, public, nopass :: set_num_scalars

  • interface

    private module subroutine set_num_scalars(num_scalars)

    allocate surface-normal scalar flux array

    Arguments

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