field Derived Type

type, public, extends(grid) :: field


Inherits

type~~field~~InheritsGraph type~field field type~dimensions dimensions type~field->type~dimensions dim type~bc_poly bc_poly type~field->type~bc_poly bc type~matptr matptr type~field->type~matptr mats type~mesh mesh type~field->type~mesh msh type~grid grid type~field->type~grid type~bc_wall bc_wall type~bc_poly->type~bc_wall wall type~bc_math bc_math type~bc_poly->type~bc_math math type~motion motion type~bc_poly->type~motion mot type~material material type~matptr->type~material mat type~mesh->type~grid 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~connectivity connectivity type~mesh->type~connectivity v2c, v2f, f2c, c2g, v2v, f2f, c2c, v2b, f2b type~keytable keytable type~mesh->type~keytable ov2c_sup, c2ov_sup, ov2f_sup, f2ov_sup type~vector vector type~mesh->type~vector face_cntr, af, df, cell_cntr type~surface surface type~mesh->type~surface surf 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~units units type~grid->type~units units_ type~object object type~grid->type~object type~units->type~object type~bc_wall->type~bc_math temp, pressure, conc, vel, pos, stress type~vertex->type~vector position type~a_row a_row type~keytable->type~a_row row type~cylinder cylinder type~surface->type~cylinder my_cylinder type~plane plane type~surface->type~plane my_plane type~motion->type~vector law_y type~cylinder->type~vector center, axis type~plane->type~vector normal

Inherited by

type~~field~~InheritedByGraph type~field field type~scalar_field scalar_field type~scalar_field->type~field type~vector_field vector_field type~vector_field->type~field

Contents

Source Code


Components

TypeVisibility AttributesNameInitial
type(bc_poly), private, pointer:: bc(:)=> null()
type(dimensions), private :: dim
type(matptr), private, pointer:: mats(:)=> null()
type(mesh), private, pointer:: msh=> null()
character(len=:), private, allocatable:: name
logical, private :: on_faces

Type-Bound Procedures

procedure, public :: bc_

  • interface

    ----- Destructor -----

    Read more…

    private module function bc_(fld)

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(in), target:: fld

    Return Value type(bc_poly), pointer, (:)

procedure, public :: check_field_operands

  • interface

    ----- Destructor -----

    Read more…

    private module subroutine check_field_operands(f1, f2, where)

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(in) :: f1
    type(field), intent(in) :: f2
    character(len=*), intent(in) :: where

generic, public :: check_mesh_consistency => check_mesh_consistency_bf

procedure, public :: create_field

  • interface

    ----- Destructor -----

    Read more…

    private module subroutine create_field(fld, msh, dim, bc, mats, on_faces, name)

    Constructor Mandatory arguments

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(out) :: fld
    type(mesh), intent(in), target:: msh

    Optional arguments

    type(dimensions), intent(in), optional :: dim
    type(bc_poly), intent(in), optional target:: bc(:)
    type(matptr), intent(in), optional target:: mats(:)
    logical, intent(in), optional :: on_faces
    character(len=*), intent(in), optional :: name

generic, public :: dim_ => get_field_dim

generic, public :: fld_size => get_field_size

procedure, public :: free_field

Constructor/destructor

  • interface

    ----- Destructor -----

    Read more…

    private module subroutine free_field(fld)

    Destructor

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(inout) :: fld

generic, public :: get_material => get_field_mat_sub

procedure, public :: get_mesh

  • interface

    ----- Destructor -----

    Read more…

    private module subroutine get_mesh(fld, msh)

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(in) :: fld
    type(mesh), pointer:: 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

procedure, public :: mat_

  • interface

    ----- Destructor -----

    Read more…

    private module function mat_(fld, i)

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(in) :: fld
    integer, intent(in), optional :: i

    Return Value type(material), pointer

procedure, public :: msh_

  • interface

    ----- Destructor -----

    Read more…

    private module function msh_(fld)

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(in), target:: fld

    Return Value type(mesh), pointer

procedure, public :: name_

  • interface

    ----- Destructor -----

    Read more…

    private module function name_(fld)

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(in) :: fld

    Return Value character(len=:), allocatable

procedure, public :: nemo_sizeof

  • interface

    ----- Destructor -----

    Read more…

    private module function nemo_sizeof(fld)

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(in) :: fld

    Return Value integer(kind=nemo_int_long_)

procedure, public :: on_faces_

Getters

  • interface

    ----- Destructor -----

    Read more…

    private module function on_faces_(fld)

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(in) :: fld

    Return Value logical

procedure, public :: set_field_dim

  • interface

    ----- Destructor -----

    Read more…

    private module subroutine set_field_dim(fld, dim)

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(inout) :: fld
    type(dimensions), intent(in) :: dim

procedure, public :: set_field_on_faces

Setters

  • interface

    ----- Destructor -----

    Read more…

    private module subroutine set_field_on_faces(fld, on_faces)

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(inout) :: fld
    logical, intent(in) :: on_faces

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

  • interface

    ----- Destructor -----

    Read more…

    private module subroutine check_mesh_consistency_bf(f1, f2, where)

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(in) :: f1
    type(field), intent(in) :: f2
    character(len=*), intent(in) :: where

procedure, private :: get_field_dim

Getters

procedure, private :: get_field_mat_sub

  • interface

    ----- Destructor -----

    Read more…

    private module subroutine get_field_mat_sub(fld, i, mat)

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(in) :: fld
    integer, intent(in), optional :: i
    type(material), pointer:: mat

procedure, private :: get_field_size

  • interface

    ----- Destructor -----

    Read more…

    private module function get_field_size(fld) result(isize)

    Arguments

    Type IntentOptional AttributesName
    class(field), intent(in) :: fld

    Return Value integer (2)

Source Code

    TYPE, EXTENDS(grid) :: field
        PRIVATE
        CHARACTER(len=:), ALLOCATABLE :: name
        TYPE(dimensions)        :: dim
        TYPE(mesh),     POINTER :: msh   => NULL()
        LOGICAL                 :: on_faces
        TYPE(bc_poly),  POINTER :: bc(:) => NULL()
        TYPE(matptr),   POINTER :: mats(:) => NULL()
    CONTAINS
        PROCEDURE :: create_field, free_field          !! Constructor/destructor
        PROCEDURE, PUBLIC :: on_faces_                 !! Getters
        PROCEDURE, PRIVATE :: get_field_size, get_field_mat_sub
        PROCEDURE, PUBLIC :: mat_
        PROCEDURE, PUBLIC :: bc_
        GENERIC, PUBLIC :: fld_size => get_field_size
        GENERIC, PUBLIC :: get_material => get_field_mat_sub
        PROCEDURE, PRIVATE :: get_field_dim            !! Getters
        PROCEDURE, PUBLIC :: msh_
        GENERIC, PUBLIC :: dim_ => get_field_dim
        PROCEDURE, PUBLIC :: name_
        PROCEDURE :: set_field_dim, set_field_on_faces !! Setters
        PROCEDURE :: check_field_operands
        PROCEDURE, PUBLIC :: nemo_sizeof
        PROCEDURE, PUBLIC :: get_mesh
        PROCEDURE, PRIVATE :: check_mesh_consistency_bf
        GENERIC, PUBLIC :: check_mesh_consistency => check_mesh_consistency_bf
    END TYPE field