problem_discretization_interface Module

Encapsulate the problem geometry, grid points, and dependent variables


Uses

  • module~~problem_discretization_interface~~UsesGraph module~problem_discretization_interface problem_discretization_interface module~kind_parameters kind_parameters module~problem_discretization_interface->module~kind_parameters module~cylinder_2d_interface cylinder_2d_interface module~problem_discretization_interface->module~cylinder_2d_interface module~surfaces_interface surfaces_interface module~problem_discretization_interface->module~surfaces_interface module~sphere_1d_interface sphere_1d_interface module~problem_discretization_interface->module~sphere_1d_interface module~differentiable_field_interface differentiable_field_interface module~problem_discretization_interface->module~differentiable_field_interface module~package_interface package_interface module~problem_discretization_interface->module~package_interface module~plate_3d_interface plate_3d_interface module~problem_discretization_interface->module~plate_3d_interface module~structured_grid_interface structured_grid_interface module~problem_discretization_interface->module~structured_grid_interface module~geometry_interface geometry_interface module~problem_discretization_interface->module~geometry_interface module~object_interface object_interface module~problem_discretization_interface->module~object_interface iso_fortran_env iso_fortran_env module~kind_parameters->iso_fortran_env module~cylinder_2d_interface->module~kind_parameters module~cylinder_2d_interface->module~geometry_interface json_module json_module module~cylinder_2d_interface->json_module module~block_metadata_interface block_metadata_interface module~cylinder_2d_interface->module~block_metadata_interface module~surfaces_interface->module~kind_parameters module~surfaces_interface->module~package_interface iso_c_binding iso_c_binding module~surfaces_interface->iso_c_binding module~sphere_1d_interface->module~kind_parameters module~sphere_1d_interface->module~geometry_interface module~sphere_1d_interface->json_module module~sphere_1d_interface->module~block_metadata_interface module~grid_interface grid_interface module~differentiable_field_interface->module~grid_interface module~package_interface->module~kind_parameters module~plate_3d_interface->module~kind_parameters module~plate_3d_interface->module~geometry_interface module~plate_3d_interface->json_module module~plate_3d_interface->module~block_metadata_interface module~structured_grid_interface->module~kind_parameters module~structured_grid_interface->module~surfaces_interface module~structured_grid_interface->module~differentiable_field_interface module~structured_grid_interface->module~geometry_interface module~structured_grid_interface->module~grid_interface module~structured_grid_interface->module~block_metadata_interface module~grid_interface->module~object_interface module~units_interface units_interface module~grid_interface->module~units_interface module~block_metadata_interface->module~kind_parameters module~block_metadata_interface->iso_c_binding module~units_interface->module~object_interface

Used by

  • module~~problem_discretization_interface~~UsedByGraph module~problem_discretization_interface problem_discretization_interface module~define_problem_discretization define_problem_discretization module~define_problem_discretization->module~problem_discretization_interface

Contents


Interfaces

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

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

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

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)

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

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

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

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

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

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)

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

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

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

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

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

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

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

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

Derived Types

type, public, extends(object) :: problem_discretization

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
procedure, public :: block_indicial_coordinates
procedure, public :: block_load
procedure, public :: get_block_surfaces
procedure, public :: get_global_block_shape
procedure, public :: get_surface_packages
procedure, public :: initialize_from_cylinder_2d
procedure, public :: initialize_from_plate_3d
procedure, public :: initialize_from_sphere_1d
procedure, public :: mark_as_defined
procedure, public :: my_blocks
procedure, public :: num_scalar_flux_divergences
procedure, public :: num_scalars
procedure, public :: partition
procedure, public :: set_analytical_scalars
procedure, public :: set_scalar_flux_divergence
procedure, public :: solve_governing_equations
procedure, public :: user_defined
procedure, public :: user_defined_vertices
procedure, public :: write_output