mesh Derived Type

type, public, extends(grid) :: mesh

Encapsulate mesh connectivity, component parts, metrics, surfaces, and linear algebraic descriptors


Inherits

type~~mesh~~InheritsGraph type~mesh mesh type~face face type~mesh->type~face faces type~vertex vertex type~mesh->type~vertex verts type~least_squares least_squares type~mesh->type~least_squares lsr type~keytable keytable type~mesh->type~keytable ov2c_sup, c2ov_sup, ov2f_sup, f2ov_sup type~connectivity connectivity type~mesh->type~connectivity v2c, v2f, f2c, c2g, v2v, f2f, c2c, v2b, f2b type~vector vector type~mesh->type~vector face_cntr, af, df, cell_cntr type~surface surface type~mesh->type~surface surf type~grid grid type~mesh->type~grid type~cell cell type~mesh->type~cell cells psb_desc_type psb_desc_type type~mesh->psb_desc_type desc_v, desc_f, desc_c type~vertex->type~vector position type~a_row a_row type~keytable->type~a_row row type~plane plane type~surface->type~plane my_plane type~cylinder cylinder type~surface->type~cylinder my_cylinder type~units units type~grid->type~units units_ type~object object type~grid->type~object type~units->type~object type~plane->type~vector normal type~cylinder->type~vector center, axis

Inherited by

type~~mesh~~InheritedByGraph type~mesh mesh type~pde pde type~pde->type~mesh msh type~field field type~field->type~mesh msh type~scalar_field scalar_field type~scalar_field->type~field type~vector_field vector_field type~vector_field->type~field type~scalar_pde scalar_pde type~scalar_pde->type~pde type~vector_pde vector_pde type~vector_pde->type~pde

Contents

Source Code


Components

TypeVisibility AttributesNameInitial
type(vector), public, allocatable:: af(:)
real(kind=psb_dpk_), public, allocatable:: area(:)
type(connectivity), public :: c2c
type(connectivity), public :: c2g
type(keytable), public :: c2ov_sup
type(vector), public, allocatable:: cell_cntr(:)
type(cell), public, allocatable:: cells(:)
type(psb_desc_type), public :: desc_c
type(psb_desc_type), public :: desc_f
type(psb_desc_type), public :: desc_v
type(vector), public, allocatable:: df(:)
real(kind=psb_dpk_), public, allocatable:: dist(:)
type(connectivity), public :: f2b
type(connectivity), public :: f2c
type(connectivity), public :: f2f
type(keytable), public :: f2ov_sup
type(vector), public, allocatable:: face_cntr(:)
type(face), public, allocatable:: faces(:)
character(len=nlen), public :: id
real(kind=psb_dpk_), public, allocatable:: interp(:)
type(least_squares), public, allocatable:: lsr(:)
integer, public :: nbc
integer, public :: ncd
integer, public :: ngp
type(keytable), public :: ov2c_sup
type(keytable), public :: ov2f_sup
logical, public :: set =.false.
type(surface), public, allocatable:: surf(:)
type(connectivity), public :: v2b
type(connectivity), public :: v2c
type(connectivity), public :: v2f
type(connectivity), public :: v2v
type(vertex), public, allocatable:: verts(:)
real(kind=psb_dpk_), public, allocatable:: vol(:)

Type-Bound Procedures

procedure, public :: check_mesh_unused_el

Check routines

  • interface

    ----- Constructors -----

    Read more…

    private module subroutine check_mesh_unused_el(msh)

    Scans through numerous connectivities, ensuring that in each one, all faces & cells are referenced at least once.

    Arguments

    Type IntentOptional AttributesName
    class(mesh), intent(in) :: msh

procedure, public :: create_mesh

Constructor

  • interface

    ----- Constructors -----

    Read more…

    private module subroutine create_mesh(msh, input_file, sec)

    Global constructor

    Arguments

    Type IntentOptional AttributesName
    class(mesh), intent(out) :: msh
    character(len=*), intent(in) :: input_file
    character(len=*), intent(in) :: sec

procedure, public :: free_mesh

Destructor

  • interface

    ----- Constructors -----

    Read more…

    private module subroutine free_mesh(msh)

    ----- Destructor -----

    Arguments

    Type IntentOptional AttributesName
    class(mesh), intent(inout) :: msh

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

generic, public :: nemo_sizeof => nemo_mesh_sizeof

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 :: 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, private :: nemo_mesh_sizeof

  • interface

    ----- Constructors -----

    Read more…

    private module function nemo_mesh_sizeof(msh)

    Arguments

    Type IntentOptional AttributesName
    class(mesh), intent(in) :: msh

    Return Value integer(kind=nemo_int_long_)

Source Code

    TYPE, EXTENDS(grid) :: mesh
      !! Encapsulate mesh connectivity, component parts, metrics, surfaces, and linear algebraic descriptors
        LOGICAL :: set = .FALSE.   ! Indicates if the mesh been created yet
        CHARACTER(len=nlen) :: id  ! Mesh ID
        INTEGER :: nbc             ! Number of BCs
        INTEGER :: ngp             ! Number of element groups
        INTEGER :: ncd             ! Dimensionality of the mesh (2d or 3d)

        ! Connectivity data
        TYPE(connectivity) :: v2c, v2f, f2c, c2g         ! From mesh importing
        TYPE(connectivity) :: v2v, f2f, c2c              ! Adjacency graphs
        TYPE(keytable)     :: ov2c_sup,c2ov_sup          ! Supplemental v2c/c2v connectivity
        TYPE(keytable)     :: ov2f_sup,f2ov_sup          ! Supplemental v2f/f2v connectivity
        TYPE(connectivity) :: v2b, f2b                   ! Boundary related

        ! Mesh sub-elements
        TYPE(vertex), ALLOCATABLE :: verts(:)            ! Vertex coordinates
        TYPE(face), ALLOCATABLE :: faces(:)              ! Faces description
        TYPE(cell), ALLOCATABLE :: cells(:)              ! Cells description

        ! PSBLAS descriptors
        TYPE(psb_desc_type) :: desc_v     ! Vertices
        TYPE(psb_desc_type) :: desc_f     ! Faces
        TYPE(psb_desc_type) :: desc_c     ! Cells

        ! Face-related metrics (see below for details)
        REAL(psb_dpk_), ALLOCATABLE :: area(:)
        REAL(psb_dpk_), ALLOCATABLE :: dist(:)
        REAL(psb_dpk_), ALLOCATABLE :: interp(:)
        TYPE(vector), ALLOCATABLE :: face_cntr(:)
        TYPE(vector), ALLOCATABLE :: af(:)
        TYPE(vector), ALLOCATABLE :: df(:)

        ! Cell-related metrics (see below for details)
        REAL(psb_dpk_), ALLOCATABLE :: vol(:)
        TYPE(vector), ALLOCATABLE :: cell_cntr(:)

        ! Metrics for cell-centered Least Squares Regression
        TYPE(least_squares), ALLOCATABLE :: lsr(:)

        ! Surface geometry and location
        TYPE(surface), ALLOCATABLE :: surf(:)
    CONTAINS
        PROCEDURE :: create_mesh          !! Constructor
        PROCEDURE :: free_mesh            !! Destructor
        PROCEDURE :: check_mesh_unused_el !! Check routines
        PROCEDURE, PRIVATE :: nemo_mesh_sizeof
        GENERIC, PUBLIC :: nemo_sizeof => nemo_mesh_sizeof
        !        PROCEDURE :: check_mesh_consistency
    END TYPE mesh