structured_grid_interface Module

Hexahedral, structured-grid block encapsulating nodal data and deferring coordinate-specific procedures to child classes


Uses

  • module~~structured_grid_interface~~UsesGraph module~structured_grid_interface structured_grid_interface module~kind_parameters kind_parameters module~structured_grid_interface->module~kind_parameters module~surfaces_interface surfaces_interface module~structured_grid_interface->module~surfaces_interface module~differentiable_field_interface differentiable_field_interface module~structured_grid_interface->module~differentiable_field_interface module~grid_interface grid_interface module~structured_grid_interface->module~grid_interface module~geometry_interface geometry_interface module~structured_grid_interface->module~geometry_interface module~block_metadata_interface block_metadata_interface module~structured_grid_interface->module~block_metadata_interface iso_fortran_env iso_fortran_env module~kind_parameters->iso_fortran_env 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 module~differentiable_field_interface->module~grid_interface module~units_interface units_interface module~grid_interface->module~units_interface module~object_interface object_interface module~grid_interface->module~object_interface module~block_metadata_interface->module~kind_parameters module~block_metadata_interface->iso_c_binding module~package_interface->module~kind_parameters module~units_interface->module~object_interface

Used by

  • module~~structured_grid_interface~~UsedByGraph module~structured_grid_interface structured_grid_interface module~cartesian_grid_interface cartesian_grid_interface module~cartesian_grid_interface->module~structured_grid_interface module~problem_discretization_interface problem_discretization_interface module~problem_discretization_interface->module~structured_grid_interface module~cylindrical_grid_interface cylindrical_grid_interface module~cylindrical_grid_interface->module~structured_grid_interface module~curvilinear_grid_interface curvilinear_grid_interface module~curvilinear_grid_interface->module~structured_grid_interface module~spherical_grid_interface spherical_grid_interface module~spherical_grid_interface->module~structured_grid_interface module~structured_grid_implementation structured_grid_implementation module~structured_grid_implementation->module~structured_grid_interface module~spherical_grid_implementation spherical_grid_implementation module~spherical_grid_implementation->module~spherical_grid_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 module~cartesian_grid_implementation cartesian_grid_implementation module~cartesian_grid_implementation->module~cartesian_grid_interface proc~initialize_from_cylinder_2d initialize_from_cylinder_2d proc~initialize_from_cylinder_2d->module~cylindrical_grid_interface module~cylindrical_grid_implementation cylindrical_grid_implementation module~cylindrical_grid_implementation->module~cylindrical_grid_interface proc~laplacian laplacian proc~laplacian->module~cartesian_grid_interface

Contents


Variables

TypeVisibility AttributesNameInitial
integer, private, parameter:: max_space_dims =3
integer, private, parameter:: num_bounds =2
integer, private, parameter:: undefined =-1

Interfaces

interface

interface

  • private pure module subroutine compare(this, reference, tolerance)

    verify

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this
    class(structured_grid), intent(in) :: reference
    real(kind=r8k), intent(in) :: tolerance

interface

  • private pure module function diffusion_coefficient(this, temperature) result(coefficient)

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this
    real(kind=r8k), intent(in) :: temperature

    Return Value real(kind=r8k)

interface

  • private pure module function free_tensor_indices(this) result(num_free_indices)

    result is number of free tensor indices for quantity stored on a structured grid (e.g., 3 for vector quantity)

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this

    Return Value integer

interface

  • private pure module function get_block_identifier(this) result(this_block_id)

    result is the block identification tag

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this

    Return Value integer

interface

  • private pure module function get_global_block_shape(this) result(shape_array)

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this

    Return Value integer, dimension(:), allocatable

interface

  • private pure module function get_scalar(this) result(scalar_values)

    result is an array of scalar values at grid vertices

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this

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

interface

  • private pure module function get_scalar_identifier(this) result(this_scalar_id)

    result is the block identification tag

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this

    Return Value integer

interface

  • private pure module function get_tag(this) result(this_tag)

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this

    Return Value integer(kind=tag_kind)

interface

  • private pure module subroutine increment_scalar(this, scalar)

    increment this%nodal_values by the provided array

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(inout) :: this
    real(kind=r8k), intent(in), dimension(:,:,:):: scalar

interface

  • private elemental module function num_cells(this) result(cell_count)

    result is number of 3D grid points stored for a given quantity on a structured grid

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this

    Return Value integer

interface

  • private pure module function num_time_stamps(this) result(num_times)

    result is number of instances of time stored for a given quantity on a structured grid

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this

    Return Value integer

interface

  • private module subroutine set_block_identifier(this, id)

    set block identification tag

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(inout) :: this
    integer, intent(in) :: id

interface

  • private module subroutine set_global_block_shape(this, shape_array)

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(inout) :: this
    integer, intent(in), dimension(:):: shape_array

interface

interface

  • private pure module subroutine set_scalar(this, scalar)

    set this%nodal_values to the provided array

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(inout) :: this
    real(kind=r8k), intent(in), dimension(:,:,:):: scalar

interface

  • private module subroutine set_scalar_identifier(this, id)

    set block identification tag

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(inout) :: this
    integer, intent(in) :: id

interface

  • private pure module subroutine set_vector_components(this, x_nodes, y_nodes, z_nodes)

    set this%nodal_values to provided vector field components

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(inout) :: this
    real(kind=r8k), intent(in), dimension(:,:,:):: x_nodes
    real(kind=r8k), intent(in), dimension(:,:,:):: y_nodes
    real(kind=r8k), intent(in), dimension(:,:,:):: z_nodes

interface

  • private pure module function space_dimension(this) result(num_dimensions)

    result is the number of independent spatial dimensions in the structured grid (e.g., 2 for axisymmetric grid)

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this

    Return Value integer

interface

  • private module function subtract(this, rhs) result(difference)

    result contains the difference between this and rhs nodal_values components

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this
    class(structured_grid), intent(in) :: rhs

    Return Value class(structured_grid), allocatable

interface

  • private pure module function vectors(this) result(vectors3d)

    result is an array of 3D vectors

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this

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

interface

  • private module subroutine write_formatted(this, unit, iotype, v_list, iostat, iomsg)

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this
    integer, intent(in) :: unit
    character(len=*), intent(in) :: iotype
    integer, intent(in) :: v_list(:)
    integer, intent(out) :: iostat
    character(len=*), intent(inout) :: iomsg

Abstract Interfaces

abstract interface

  • private pure function block_id_in_bounds_interface(this, id) result(in_bounds)

    verify block identifier

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this
    integer, intent(in) :: id

    Return Value logical

abstract interface

  • private pure function block_identifier_interface(this, ijk) result(n)

    calculate the 1D block identifier associated with the provided 3D block location

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this
    integer, intent(in), dimension(:):: ijk

    Return Value integer

abstract interface

  • private pure function block_ijk_in_bounds_interface(this, ijk) result(in_bounds)

    verify block indicial coordinates

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this
    integer, intent(in), dimension(:):: ijk

    Return Value logical

abstract interface

  • private pure function block_indices_interface(this, n) result(ijk)

    calculate the 3D location of the block that has the provided 1D block identifier

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this
    integer, intent(in) :: n

    Return Value integer, dimension(:), allocatable

abstract interface

  • private subroutine build_surfaces_interface(this, problem_geometry, vertices, block_faces, block_partitions, num_scalars)

    allocate coarray for communicating across structured_grid blocks

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this
    class(geometry), intent(in) :: problem_geometry
    class(structured_grid), intent(in), dimension(:), allocatable:: vertices
    type(surfaces), intent(inout) :: block_faces
    integer, intent(in), dimension(:):: block_partitions
    integer, intent(in) :: num_scalars

abstract interface

  • private pure subroutine div_scalar_flux_interface(this, vertices, block_surfaces, div_flux)

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this
    class(structured_grid), intent(in) :: vertices
    type(surfaces), intent(in) :: block_surfaces
    class(structured_grid), intent(inout) :: div_flux

abstract interface

  • private subroutine set_up_div_scalar_flux_interface(this, vertices, block_surfaces, div_flux_internal_points)

    Arguments

    Type IntentOptional AttributesName
    class(structured_grid), intent(in) :: this
    class(structured_grid), intent(in) :: vertices
    type(surfaces), intent(inout) :: block_surfaces
    class(structured_grid), intent(inout) :: div_flux_internal_points

Derived Types

type, public, abstract, extends(grid) :: structured_grid

Morfeus structured grid class

Components

TypeVisibility AttributesNameInitial
procedure, public :: get_block_identifier
procedure, public :: get_scalar_identifier
procedure, public :: set_block_identifier
procedure, public :: set_scalar_identifier
integer, private :: block_id =undefined
integer, private :: global_bounds(num_bounds,max_space_dims) =undefined
type(block_metadata), private :: metadata
real(kind=r8k), private, allocatable:: nodal_values(:,:,:,:,:,:)

3 dims for indexing through 3D space 2 dims for tensor free indices to handle scalars, vectors, & dyads 1 dim for instances in time

integer, private :: scalar_id =undefined

Type-Bound Procedures

procedure(block_ijk_in_bounds_interface), public :: block_coordinates_in_bounds
procedure(block_identifier_interface), public :: block_identifier
procedure(block_id_in_bounds_interface), public :: block_identifier_in_bounds
generic, public :: block_in_bounds => block_identifier_in_bounds, block_coordinates_in_bounds
procedure(block_indices_interface), public :: block_indicial_coordinates
procedure(build_surfaces_interface), public :: build_surfaces
procedure, public :: clone
procedure, public :: compare
procedure, public :: diffusion_coefficient
procedure(div_scalar_flux_interface), public :: div_scalar_flux
procedure, public :: free_tensor_indices
procedure, public :: get_global_block_shape
procedure, public :: get_scalar
procedure, public :: get_tag
procedure, public :: get_units
procedure, public :: increment_scalar
procedure, public :: mark_as_defined
procedure, public :: num_cells
procedure, public :: num_time_stamps
procedure, public :: set_global_block_shape
procedure, public :: set_metadata
procedure, public :: set_scalar
procedure, public :: set_units
procedure(set_up_div_scalar_flux_interface), public :: set_up_div_scalar_flux
procedure, public :: set_vector_components
procedure, public :: space_dimension
procedure, public :: subtract
procedure, public :: user_defined
procedure, public :: vectors
procedure, public :: write_formatted