cartesian_grid Derived Type

type, public, extends(structured_grid) :: cartesian_grid


Inherits

type~~cartesian_grid~~InheritsGraph type~cartesian_grid cartesian_grid type~structured_grid structured_grid type~cartesian_grid->type~structured_grid type~block_metadata block_metadata type~structured_grid->type~block_metadata metadata type~grid grid type~structured_grid->type~grid type~subdomain_t subdomain_t type~block_metadata->type~subdomain_t subdomain type~units units type~grid->type~units units_ type~object object type~grid->type~object type~units->type~object

Contents


Components

TypeVisibility AttributesNameInitial
procedure, public :: get_block_identifier
procedure, public :: get_scalar_identifier
procedure, public :: set_block_identifier
procedure, public :: set_scalar_identifier

Type-Bound Procedures

procedure, public :: block_coordinates_in_bounds

  • interface

    private pure module function block_coordinates_in_bounds(this, ijk) result(in_bounds)

    Arguments

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

    Return Value logical

procedure, public :: block_identifier

  • interface

    private pure module function block_identifier(this, ijk) result(n)

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

    Arguments

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

    Return Value integer

procedure, public :: block_identifier_in_bounds

  • interface

    private pure module function block_identifier_in_bounds(this, id) result(in_bounds)

    Arguments

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

    Return Value logical

generic, public :: block_in_bounds => block_identifier_in_bounds, block_coordinates_in_bounds

procedure, public :: block_indicial_coordinates

  • interface

    private pure module function block_indicial_coordinates(this, n) result(ijk)

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

    Arguments

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

    Return Value integer, dimension(:), allocatable

procedure, public :: build_surfaces

  • interface

    private module subroutine build_surfaces(this, problem_geometry, vertices, block_faces, block_partitions, num_scalars)

    allocate the surfaces array for use in halo exchanges and boundary conditions

    Arguments

    Type IntentOptional AttributesName
    class(cartesian_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

procedure, public :: clone

procedure, public :: compare

  • 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

procedure, public :: diffusion_coefficient

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

procedure, public :: div_scalar_flux

  • interface

    private pure module subroutine div_scalar_flux(this, vertices, block_surfaces, div_flux)

    communicate scalar fluxes between block neighbors in a halo exchange; compute scalar flux divergence at block boundaries

    Arguments

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

procedure, public :: free_tensor_indices

  • 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

procedure, public :: get_global_block_shape

  • 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

procedure, public :: get_scalar

  • 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

procedure, public :: get_tag

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

procedure, public :: get_units

  • interface

    private impure elemental module function get_units(this) result(this_units)

    Arguments

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

    Return Value type(units)

procedure, public :: increment_scalar

  • 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

procedure, public :: mark_as_defined

  • interface

    private pure module subroutine mark_as_defined(this)

    Mark the object as user-defined

    Arguments

    Type IntentOptional AttributesName
    class(object), intent(inout) :: this

procedure, public :: num_cells

  • 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

procedure, public :: num_time_stamps

  • 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

procedure, public :: set_global_block_shape

  • 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

procedure, public :: set_metadata

procedure, public :: set_scalar

  • 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

procedure, public :: set_units

  • interface

    private impure elemental module subroutine set_units(this, units_obj)

    Arguments

    Type IntentOptional AttributesName
    class(grid), intent(inout) :: this
    type(units), intent(in) :: units_obj

procedure, public :: set_up_div_scalar_flux

  • interface

    private module subroutine set_up_div_scalar_flux(this, vertices, block_surfaces, div_flux_internal_points)

    define the scalar flux divergence at points internal to grid blocks grid; define block-surface data on halo blocks

    Arguments

    Type IntentOptional AttributesName
    class(cartesian_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

procedure, public :: set_vector_components

  • 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

procedure, public :: space_dimension

  • 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

procedure, public :: subtract

  • 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

procedure, public :: user_defined

  • interface

    private pure module function user_defined(this) result(is_defined)

    Return a boolean result indicating whether this object has been initialized since its declaration

    Arguments

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

    Return Value logical

procedure, public :: vectors

  • 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

procedure, public :: write_formatted

  • 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