problem_discretization Derived Type

type, public, extends(object) :: problem_discretization


Inherits

type~~problem_discretization~~InheritsGraph type~problem_discretization problem_discretization type~surfaces surfaces type~problem_discretization->type~surfaces block_surfaces type~structured_grid structured_grid type~problem_discretization->type~structured_grid block_map, vertices, scalar_fields, scalar_flux_divergence type~object object type~problem_discretization->type~object type~geometry geometry type~problem_discretization->type~geometry problem_geometry type~package package type~surfaces->type~package halo_outbox 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~grid->type~object type~units units type~grid->type~units units_ type~flux_planes flux_planes type~package->type~flux_planes surface_normal_fluxes type~units->type~object

Contents


Components

TypeVisibility AttributesNameInitial
class(structured_grid), private, allocatable:: block_map

hook for invoking block_indicial_coordinates and block_identifier

integer, private, allocatable, dimension(:):: block_partitions

block ownership specification

type(surfaces), private :: block_surfaces

global surface information with singleton communication buffers

real(kind=r8k), private :: end_time
class(geometry), private, allocatable:: problem_geometry

description of problem domain and material identities; child types: plate_3D, cylinder_2D, sphere_1D

class(structured_grid), private, allocatable:: scalar_fields(:,:)

scalar values at the grid nodes: size(scalar_fields,1)==size(vertices), size(scalar_fields,2)==number of scalar fields

class(structured_grid), private, allocatable:: scalar_flux_divergence(:,:)

div( D grad(s)): same dimensions as scalar_fields

class(structured_grid), private, allocatable:: vertices(:)

grid nodal locations: size(vertices) == number of blocks owned by the executing image


Type-Bound Procedures

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(problem_discretization), intent(in) :: this
    integer, intent(in) :: ijk(:)

    Return Value integer

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(problem_discretization), intent(in) :: this
    integer, intent(in) :: n

    Return Value integer, dimension(:), allocatable, (:)

procedure, public :: block_load

  • interface

    private pure module function block_load(this) result(num_blocks)

    the result is a measure of the workload partitioned to the executing image

    Arguments

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

    Return Value integer

procedure, public :: get_block_surfaces

  • interface

    private module function get_block_surfaces(this) result(this_block_surfaces)

    get surfaces owned by this image

    Arguments

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

    Return Value type(surfaces)

procedure, public :: get_global_block_shape

  • interface

    private module function get_global_block_shape(this) result(block_shape)

    result is shape of array of structured_grid blocks

    Arguments

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

    Return Value integer, dimension(:), allocatable

procedure, public :: get_surface_packages

  • interface

    private module function get_surface_packages(this) result(this_surface_packages)

    get surface data packages of this image

    Arguments

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

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

procedure, public :: initialize_from_cylinder_2d

  • interface

    private module subroutine initialize_from_cylinder_2d(this, cylinder_2d_geometry)

    Define a grid with points covering each structured-grid block in a 2D cylinder

    Arguments

    Type IntentOptional AttributesName
    class(problem_discretization), intent(inout) :: this
    type(cylinder_2d), intent(in) :: cylinder_2d_geometry

procedure, public :: initialize_from_plate_3d

  • interface

    private module subroutine initialize_from_plate_3d(this, plate_3d_geometry)

    Define a grid with points covering each structured-grid block in a 3D plate

    Arguments

    Type IntentOptional AttributesName
    class(problem_discretization), intent(inout) :: this
    type(plate_3d), intent(in) :: plate_3d_geometry

procedure, public :: initialize_from_sphere_1d

  • interface

    private module subroutine initialize_from_sphere_1d(this, sphere_1d_geometry)

    Define a grid with points covering each structured-grid block in a 1D sphere

    Arguments

    Type IntentOptional AttributesName
    class(problem_discretization), intent(inout) :: this
    type(sphere_1d), intent(in) :: sphere_1d_geometry

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 :: my_blocks

  • interface

    private pure module function my_blocks(this) result(block_identifier_range)

    Result contains the first & last identifiers for blocks owned by this image

    Arguments

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

    Return Value integer (num_bounds)

procedure, public :: num_scalar_flux_divergences

  • interface

    private pure module function num_scalar_flux_divergences(this) result(num_divergences)

    Result contains the total number of scalar_field components

    Arguments

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

    Return Value integer

procedure, public :: num_scalars

  • interface

    private pure module function num_scalars(this) result(num_scalar_fields)

    Result contains the total number of scalar_field components

    Arguments

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

    Return Value integer

procedure, public :: partition

  • interface

    private module subroutine partition(this, global_block_shape, prototype)

    Define the distribution of blocks across images for the given shape of the block-structured partitions (impure because of image-control statement in emulated co_sum -- may be pure when replaced by intrinsic co_sum)

    Arguments

    Type IntentOptional AttributesName
    class(problem_discretization), intent(inout) :: this
    integer, intent(in) :: global_block_shape(:)
    class(structured_grid), intent(in) :: prototype

procedure, public :: set_analytical_scalars

  • interface

    private module subroutine set_analytical_scalars(this, scalar_setters)

    Use functions to define scalar values at vertex locations

    Arguments

    Type IntentOptional AttributesName
    class(problem_discretization), intent(inout) :: this
    class(differentiable_field), intent(in), dimension(:):: scalar_setters

procedure, public :: set_scalar_flux_divergence

  • interface

    private module subroutine set_scalar_flux_divergence(this, exact_result)

    Compute and store div( D grad( S )) for each scalar S and diffusion coefficient D

    Arguments

    Type IntentOptional AttributesName
    class(problem_discretization), intent(inout) :: this
    class(differentiable_field), intent(in), optional dimension(:):: exact_result

procedure, public :: solve_governing_equations

  • interface

    private module subroutine solve_governing_equations(this, duration)

    advance the governing equations for the specified time duration

    Arguments

    Type IntentOptional AttributesName
    class(problem_discretization), intent(in) :: this
    real(kind=r8k), intent(in) :: duration

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 :: user_defined_vertices

  • interface

    private module subroutine user_defined_vertices(this, x_nodes, y_nodes, z_nodes, block_identifier)

    Define the vertex locations within the specified structured_grid block

    Arguments

    Type IntentOptional AttributesName
    class(problem_discretization), intent(inout) :: this
    real(kind=r8k), intent(in) :: x_nodes(:,:,:)
    real(kind=r8k), intent(in) :: y_nodes(:,:,:)
    real(kind=r8k), intent(in) :: z_nodes(:,:,:)
    integer, intent(in) :: block_identifier

procedure, public :: write_output

  • interface

    private module subroutine write_output(this, filename)

    Generic write output interface

    Arguments

    Type IntentOptional AttributesName
    class(problem_discretization), intent(in) :: this
    character(len=*), intent(in) :: filename