vector_field Derived Type

type, public, extends(field) :: vector_field


Inherits

type~~vector_field~~InheritsGraph type~vector_field vector_field type~vector vector type~vector_field->type~vector x, xp, bx type~field field type~vector_field->type~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~vector face_cntr, af, df, cell_cntr 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~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

Contents

Source Code


Components

TypeVisibility AttributesNameInitial
type(vector), private, allocatable:: bx(:)
integer, private, allocatable:: mat(:)
type(vector), private, allocatable:: x(:)
type(vector), private, allocatable:: xp(:)

Constructor

public interface vector_field

  • public function vector_field_(base, x, bx)

    Default public constructor, necessary with ifort

    Arguments

    Type IntentOptional AttributesName
    type(field), intent(in) :: base
    type(vector), intent(in) :: x(:)
    type(vector), intent(in) :: bx(:)

    Return Value type(vector_field)


Type-Bound Procedures

generic, public :: assignment(=) => assign_vector_field_s, assign_vector_field_v

User-defined assignments

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, check_mesh_consistency_vf

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

procedure, public :: create_vector_field

  • interface

    ----- Getters for Additional Members -----

    Read more…

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

    Constructor Mandatory arguments

    Arguments

    Type IntentOptional AttributesName
    class(vector_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
    type(vector), intent(in), optional :: x0
    character(len=*), intent(in), optional :: name

generic, public :: dim_ => get_field_dim

generic, public :: fld_size => get_field_size

procedure, public :: free_field

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine free_field(fld)

    Destructor

    Arguments

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

generic, public :: get_base => get_vector_field_base

generic, public :: get_bx => get_vector_field_bx_r, get_vector_field_bx_v

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)

generic, public :: get_x => get_vector_field_x_r, get_vector_field_x_v

generic, public :: get_xp => get_vector_field_xp_r, get_vector_field_xp_v

generic, public :: interp_on_faces => interp_on_faces_v

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

    ----- Getters for Additional Members -----

    Read more…

    private module function nemo_sizeof(fld)

    Arguments

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

generic, public :: operator(*) => vector_field_scal

Algebra operations

generic, public :: operator(+) => vector_field_sum

generic, public :: operator(-) => vector_field_dif

generic, public :: set_field_bound_element => set_vector_field_bound_element

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

generic, public :: set_field_element => set_vector_field_element

generic, public :: set_field_group => set_vector_field_group

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

generic, public :: set_x => set_vector_field_x

generic, public :: update_field => update_vector_field

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

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine assign_vector_field_s(f, x)

    Arguments

    Type IntentOptional AttributesName
    class(vector_field), intent(inout) :: f
    type(vector), intent(in) :: x

procedure, private :: assign_vector_field_v

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine assign_vector_field_v(f, x)

    Arguments

    Type IntentOptional AttributesName
    class(vector_field), intent(inout) :: f
    type(vector), intent(in) :: x(:)

procedure, private :: check_mesh_consistency_vf

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine check_mesh_consistency_vf(f1, f2, where)

    Arguments

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

procedure, private :: get_vector_field_base

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine get_vector_field_base(fld, base)

    Arguments

    Type IntentOptional AttributesName
    class(vector_field), intent(in) :: fld
    type(field), intent(out) :: base

procedure, private :: get_vector_field_bx_r

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine get_vector_field_bx_r(fld, bx)

    Arguments

    Type IntentOptional AttributesName
    class(vector_field), intent(in) :: fld
    real(kind=psb_dpk_), intent(out), allocatable:: bx(:,:)

procedure, private :: get_vector_field_bx_v

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine get_vector_field_bx_v(fld, bx)

    Arguments

    Type IntentOptional AttributesName
    class(vector_field), intent(in) :: fld
    type(vector), intent(out), allocatable:: bx(:)

procedure, private :: get_vector_field_x_r

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine get_vector_field_x_r(fld, x)

    Arguments

    Type IntentOptional AttributesName
    class(vector_field), intent(in) :: fld
    real(kind=psb_dpk_), intent(out), allocatable:: x(:,:)

procedure, private :: get_vector_field_x_v

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine get_vector_field_x_v(fld, x)

    Arguments

    Type IntentOptional AttributesName
    class(vector_field), intent(in) :: fld
    type(vector), intent(out), allocatable:: x(:)

procedure, private :: get_vector_field_xp_r

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine get_vector_field_xp_r(fld, xp)

    Arguments

    Type IntentOptional AttributesName
    class(vector_field), intent(in) :: fld
    real(kind=psb_dpk_), intent(out), allocatable:: xp(:,:)

procedure, private :: get_vector_field_xp_v

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine get_vector_field_xp_v(fld, xp)

    Arguments

    Type IntentOptional AttributesName
    class(vector_field), intent(in) :: fld
    type(vector), intent(out), allocatable:: xp(:)

procedure, private :: interp_on_faces_v

procedure, private :: set_vector_field_bound_element

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine set_vector_field_bound_element(f, i, x)

    Arguments

    Type IntentOptional AttributesName
    class(vector_field), intent(inout) :: f
    integer, intent(in) :: i
    type(vector), intent(in) :: x

procedure, private :: set_vector_field_element

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine set_vector_field_element(f, i, x)

    Arguments

    Type IntentOptional AttributesName
    class(vector_field), intent(inout) :: f
    integer, intent(in) :: i
    type(vector), intent(in) :: x

procedure, private :: set_vector_field_group

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine set_vector_field_group(f, ig, x)

    Arguments

    Type IntentOptional AttributesName
    class(vector_field), intent(inout) :: f
    integer, intent(in) :: ig
    type(vector), intent(in) :: x

procedure, private :: set_vector_field_x

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine set_vector_field_x(fld, x)

    Arguments

    Type IntentOptional AttributesName
    class(vector_field), intent(inout) :: fld
    real(kind=psb_dpk_), intent(in), allocatable:: x(:,:)

procedure, private :: update_vector_field

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module subroutine update_vector_field(fld)

    Arguments

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

procedure, private :: vector_field_dif

procedure, private, pass(f2) :: vector_field_scal

Algebra operations

  • interface

    ----- Getters for Additional Members -----

    Read more…

    private module function vector_field_scal(a, f2) result(r)

    Arguments

    Type IntentOptional AttributesName
    real(kind=psb_dpk_), intent(in) :: a
    class(vector_field), intent(in) :: f2

    Return Value type(vector_field)

procedure, private :: vector_field_sum

Source Code

    TYPE, EXTENDS(field) :: vector_field
        PRIVATE
        TYPE(vector), ALLOCATABLE :: x(:)
        TYPE(vector), ALLOCATABLE :: xp(:)
        TYPE(vector), ALLOCATABLE :: bx(:)
        INTEGER, ALLOCATABLE :: mat(:)
    CONTAINS
        PROCEDURE, PUBLIC :: create_vector_field
        PROCEDURE, PUBLIC :: free_field
        PROCEDURE, PRIVATE :: get_vector_field_base
        GENERIC, PUBLIC :: get_base => get_vector_field_base
        PROCEDURE, PRIVATE :: get_vector_field_x_r, get_vector_field_x_v
        GENERIC, PUBLIC :: get_x => get_vector_field_x_r, get_vector_field_x_v
        PROCEDURE, PRIVATE :: get_vector_field_xp_r, get_vector_field_xp_v
        GENERIC, PUBLIC :: get_xp => get_vector_field_xp_r, get_vector_field_xp_v
        PROCEDURE, PRIVATE :: get_vector_field_bx_r, get_vector_field_bx_v
        GENERIC, PUBLIC :: get_bx => get_vector_field_bx_r, get_vector_field_bx_v
        PROCEDURE, PRIVATE :: update_vector_field
        GENERIC, PUBLIC :: update_field => update_vector_field
        PROCEDURE, PRIVATE :: set_vector_field_element, set_vector_field_group
        GENERIC, PUBLIC :: set_field_element => set_vector_field_element
        GENERIC, PUBLIC :: set_field_group => set_vector_field_group
        PROCEDURE, PRIVATE :: set_vector_field_bound_element
        GENERIC, PUBLIC :: set_field_bound_element => set_vector_field_bound_element
        PROCEDURE, PRIVATE :: set_vector_field_x
        GENERIC, PUBLIC :: set_x => set_vector_field_x
        PROCEDURE, PRIVATE :: interp_on_faces_v
        GENERIC, PUBLIC :: interp_on_faces => interp_on_faces_v
        PROCEDURE, PRIVATE :: vector_field_sum, vector_field_dif
        PROCEDURE, PASS(f2), PRIVATE :: vector_field_scal     !! Algebra operations
        PROCEDURE, PRIVATE :: assign_vector_field_s, assign_vector_field_v
        GENERIC :: ASSIGNMENT(=) => assign_vector_field_s, assign_vector_field_v !! User-defined assignments
        GENERIC :: OPERATOR(+) => vector_field_sum
        GENERIC :: OPERATOR(-) => vector_field_dif
        GENERIC :: OPERATOR(*) => vector_field_scal     !! Algebra operations
        PROCEDURE, PUBLIC:: nemo_sizeof
        PROCEDURE, PRIVATE :: check_mesh_consistency_vf
        GENERIC, PUBLIC :: check_mesh_consistency => check_mesh_consistency_vf
    END TYPE vector_field