Initiate
Inherited from AbstractMeshField
Initiate
Initiate an instance of AbstractMeshField_.
Interface 1 (Initiate by using param)
INTERFACE AbstractMeshFieldInitiate
  MODULE SUBROUTINE Initiate1(obj, param, mesh)
    CLASS(AbstractMeshField_), INTENT(INOUT) :: obj
    TYPE(ParameterList_), INTENT(IN) :: param
    TYPE(Mesh_), TARGET, INTENT(IN) :: mesh
  END SUBROUTINE Initiate1
END INTERFACE AbstractMeshFieldInitiate
Interface 2 (Initiate by copying)
INTERFACE
  MODULE SUBROUTINE Initiate2(obj, obj2, copyFull, copyStructure, &
    & usePointer)
    CLASS(AbstractMeshField_), INTENT(INOUT) :: obj
    CLASS(AbstractMeshField_), INTENT(INOUT) :: obj2
    LOGICAL(LGT), OPTIONAL, INTENT(IN) :: copyFull
    LOGICAL(LGT), OPTIONAL, INTENT(IN) :: copyStructure
    LOGICAL(LGT), OPTIONAL, INTENT(IN) :: usePointer
  END SUBROUTINE Initiate2
END INTERFACE
Interface 3 (Initiate by AbstractMaterial)
INTERFACE
  MODULE SUBROUTINE Initiate3(obj, mesh, material, name, engine)
    CLASS(AbstractMeshField_), INTENT(INOUT) :: obj
    !! AbstractMeshField
    TYPE(Mesh_), TARGET, INTENT(IN) :: mesh
    !! mesh
    CLASS(AbstractMaterial_), INTENT(INOUT) :: material
    !! Abstract material
    CHARACTER(*), INTENT(IN) :: name
    !! name of the AbstractMeshField
    CHARACTER(*), INTENT(IN) :: engine
    !! engine of the AbstractMeshField
  END SUBROUTINE Initiate3
END INTERFACE
Interface 4 (Initiate by UserFunction)
INTERFACE
  MODULE SUBROUTINE Initiate4(obj, mesh, func, name, engine, nnt)
    CLASS(AbstractMeshField_), INTENT(INOUT) :: obj
    !! AbstractMeshField
    TYPE(Mesh_), TARGET, INTENT(IN) :: mesh
    !! mesh
    CLASS(UserFunction_), INTENT(INOUT) :: func
    !! Abstract material
    CHARACTER(*), INTENT(IN) :: name
    !! name of the AbstractMeshField
    CHARACTER(*), INTENT(IN) :: engine
    !! engine of the AbstractMeshField
    INTEGER(I4B), OPTIONAL, INTENT(IN) :: nnt
    !! number of nodes in time
  END SUBROUTINE Initiate4
END INTERFACE
Example 1
Click here to see the example
This example shows how to initiate an instance of Mesh by reading data from mesh file, which is in HDF5File_ format. We will also construct an instance of STScalarMeshField_.
PROGRAM main
  USE easifemBase
  USE easifemClasses
  IMPLICIT NONE
  TYPE( HDF5File_ ) :: meshfile
  TYPE( Mesh_ ) :: amesh
  TYPE( STScalarMeshField_ ) :: obj
  TYPE( ParameterList_ ) :: param
Step 1:
Initiate and open the mesh file which is in HDF5File_ format.
CALL meshfile%Initiate( FileName="./mesh.h5", MODE="READ" )
CALL meshfile%Open()
CALL amesh%Initiate(hdf5=meshfile, group="/surfaceEntities_1" )
Step 2:
Initiate an instance of STScalarMeshField_.
CALL FPL_INIT(); CALL param%initiate()
CALL SetSTScalarMeshFieldParam( &
  & param=param, &
  & name='aScalar', &
  & varType = Constant, &
  & fieldType=TypeField%normal, &
  & engine='NATIVE_SERIAL', &
  & defineOn=Nodal, &
  & nns=6,  &
  & nnt=2 )
CALL obj%Initiate( param=param, mesh=amesh)
CALL obj%Display( 'obj: ' )
The above code will initiate an instance of STScalarMeshField_, which will contain following data.
Object INITIATED: TRUE
name: aScalar
prefix: STScalarMeshField
fieldType: NORMAL
engine: NATIVE_SERIAL
tSize: 484
defineOn: Nodal
rank: Scalar
varType: Constant
shape:
-------
   1
val ALLOCATED: TRUE
mesh ASSOCIATED: TRUE
Let's try to understand the following situation:
- We save data in a two dimensional array val.
- The number of rows in valfor above example isnns=1.
- Because, we have set varType=Constant, all nodes (we have specified 6 nodes in space and 2 nodes in time) in an element have constant value. Read more about the Shape method.
- The number of columns in valis484, which is same as the total number of elements in the mesh. This is because we have usedfieldType=normalin the above example.
Step 3:
  CALL obj%Deallocate()
  CALL amesh%Deallocate()
  CALL meshfile%Close()
  CALL meshfile%Deallocate()
  CALL param%Deallocate(); CALL FPL_FINALIZE()
END PROGRAM main
Example 2
Click here to see the example
This example shows how to initiate an instance of Mesh by reading data from mesh file, which is in HDF5File_ format. We will also construct an instance of STScalarMeshField_.
PROGRAM main
  USE easifemBase
  USE easifemClasses
  IMPLICIT NONE
  TYPE( HDF5File_ ) :: meshfile
  TYPE( Mesh_ ) :: amesh
  TYPE( STScalarMeshField_ ) :: obj
  TYPE( ParameterList_ ) :: param
Step 1:
Initiate and open the mesh file which is in HDF5File_ format.
CALL meshfile%Initiate( FileName="./mesh.h5", MODE="READ" )
CALL meshfile%Open()
CALL amesh%Initiate(hdf5=meshfile, group="/surfaceEntities_1" )
Step 2:
Initiate an instance of STScalarMeshField_.
CALL FPL_INIT(); CALL param%initiate()
CALL SetSTScalarMeshFieldParam( &
  & param=param, &
  & name='aScalar', &
  & varType = Constant, &
  & fieldType=TypeField%Constant, &
  & engine='NATIVE_SERIAL', &
  & defineOn=Nodal, &
  & nns=6,  &
  & nnt=2 )
CALL obj%Initiate( param=param, mesh=amesh )
CALL obj%Display( 'obj: ' )
The above code will initiate an instance of STScalarMeshField_, which will the contain following data.
Object INITIATED: TRUE
name: aScalar
prefix: STScalarMeshField
fieldType: CONSTANT
engine: NATIVE_SERIAL
tSize: 1
defineOn: Nodal
rank: Scalar
varType: Constant
shape:
-------
   1
val ALLOCATED: TRUE
mesh ASSOCIATED: TRUE
Let's try to understand the above code:
- We save data in a two dimensional array val.
- The number of rows in valfor above example is 1. This is because the scalar data is constant in space and time inside the element. Because, we have setvarType=Constant, all nodes (we have specified 6 nodes in space and 2 nodes in time) in an element has constant value. Read more about the Shape method.
- The number of columns in valis1, this is because thefieldType=Constant(i.e., constant across all the elements).
Step 3:
  CALL obj%Deallocate()
  CALL amesh%Deallocate()
  CALL meshfile%Close()
  CALL meshfile%Deallocate()
  CALL param%Deallocate(); CALL FPL_FINALIZE()
END PROGRAM main
Example 3
Click here to see the example
This example shows how to initiate an instance of Mesh by reading data from mesh file, which is in HDF5File_ format. We will also construct an instance of STScalarMeshField_.
PROGRAM main
  USE easifemBase
  USE easifemClasses
  IMPLICIT NONE
  TYPE( HDF5File_ ) :: meshfile
  TYPE( Mesh_ ) :: amesh
  TYPE( STScalarMeshField_ ) :: obj
  TYPE( ParameterList_ ) :: param
Step 1:
Initiate and open the mesh file which is in HDF5File_ format.
CALL meshfile%Initiate( FileName="./mesh.h5", MODE="READ" )
CALL meshfile%Open()
CALL amesh%Initiate(hdf5=meshfile, group="/surfaceEntities_1" )
Step 2:
Initiate an instance of STScalarMeshField_.
CALL FPL_INIT(); CALL param%initiate()
CALL SetSTScalarMeshFieldParam( &
  & param=param, &
  & name='aScalar', &
  & varType = Space, &
  & fieldType=TypeField%Normal, &
  & engine='NATIVE_SERIAL', &
  & defineOn=Nodal, &
  & nns=6, nnt=2 )
CALL obj%Initiate( param=param, mesh=amesh )
CALL obj%Display( 'obj: ' )
The above code will initiate an instance of STScalarMeshField_, which will contain following data.
Object INITIATED: TRUE
name: aScalar
prefix: STScalarMeshField
fieldType: NORMAL
engine: NATIVE_SERIAL
tSize: 484
defineOn: Nodal
rank: Scalar
varType: Space
shape:
-------
   6
val ALLOCATED: TRUE
mesh ASSOCIATED: TRUE
Let's try to understand the above code:
- We save data in a two dimensional array val.
- The number of rows in valfor above example is6. This is because we have setvarType=Space, which means the scalar data changes inSpaceinside the element. Note that the data does not change in time in an element.
- Because, we have set varType=Space, thereforeval(1:6)denotes the value of scalar field at 6 nodes of element. Read more about the Shape method.
- The number of columns in valis484(which is the total number of elements in the mesh), this is because thefieldType=Regular(i.e., changes across all the elements).
Step 3:
  CALL obj%Deallocate()
  CALL amesh%Deallocate()
  CALL meshfile%Close()
  CALL meshfile%Deallocate()
  CALL param%Deallocate(); CALL FPL_FINALIZE()
END PROGRAM main
Example 4
Click here to see the example
This example shows how to initiate an instance of Mesh by reading data from mesh file, which is in HDF5File_ format. We will also construct an instance of STScalarMeshField_.
PROGRAM main
  USE easifemBase
  USE easifemClasses
  IMPLICIT NONE
  TYPE( HDF5File_ ) :: meshfile
  TYPE( Mesh_ ) :: amesh
  TYPE( STScalarMeshField_ ) :: obj
  TYPE( ParameterList_ ) :: param
Step 1:
Initiate and open the mesh file which is in HDF5File_ format.
CALL meshfile%Initiate( FileName="./mesh.h5", MODE="READ" )
CALL meshfile%Open()
CALL amesh%Initiate(hdf5=meshfile, group="/surfaceEntities_1" )
Step 2:
Initiate an instance of STScalarMeshField_.
CALL FPL_INIT(); CALL param%initiate()
CALL SetSTScalarMeshFieldParam( &
  & param=param, &
  & name='aScalar', &
  & varType =Time, &
  & fieldType=TypeField%Normal, &
  & engine='NATIVE_SERIAL', &
  & defineOn=Nodal, &
  & nns=6, nnt=2 )
CALL obj%Initiate( param=param, mesh=amesh )
CALL obj%Display( 'obj: ' )
call display(amesh%GetTotalElements(), "total elements: " )
The above code will initiate an instance of STScalarMeshField_, which will contain following data.
Object INITIATED: TRUE
name: aScalar
prefix: STScalarMeshField
fieldType: NORMAL
engine: NATIVE_SERIAL
tSize: 484
defineOn: Nodal
rank: Scalar
varType: Time
shape:
-------
   6
val ALLOCATED: TRUE
mesh ASSOCIATED: TRUE
total elements: 484
Let's try to understand the above code:
- We save data in a two dimensional array val.
- The number of rows in valfor above example is6. This is because we have setvarType=Time, which means the scalar data changes inTime(and remains constant in space) inside the element.
- Because, we have set varType=Time, thereforeval(1:6, iel)denotes the value of scalar field at 6 time-nodes of element. Read more about the Shape method.
- The number of columns in valis484(which is the total number of elements in the mesh), this is because thefieldType=Regular(i.e., changes across all the elements).
Step 3:
  CALL obj%Deallocate()
  CALL amesh%Deallocate()
  CALL meshfile%Close()
  CALL meshfile%Deallocate()
  CALL param%Deallocate(); CALL FPL_FINALIZE()
END PROGRAM main
Example 5
Click here to see the example
This example shows how to initiate an instance of Mesh by reading data from mesh file, which is in HDF5File_ format. We will also construct an instance of STScalarMeshField_.
PROGRAM main
  USE easifemBase
  USE easifemClasses
  IMPLICIT NONE
  TYPE( HDF5File_ ) :: meshfile
  TYPE( Mesh_ ) :: amesh
  TYPE( STScalarMeshField_ ) :: obj
  TYPE( ParameterList_ ) :: param
Step 1:
Initiate and open the mesh file which is in HDF5File_ format.
CALL meshfile%Initiate( FileName="./mesh.h5", MODE="READ" )
CALL meshfile%Open()
CALL amesh%Initiate(hdf5=meshfile, group="/surfaceEntities_1" )
Step 2:
Initiate an instance of STScalarMeshField_.
CALL FPL_INIT(); CALL param%initiate()
CALL SetSTScalarMeshFieldParam( &
  & param=param, &
  & name='aScalar', &
  & varType =Time, &
  & fieldType=TypeField%Normal, &
  & engine='NATIVE_SERIAL', &
  & defineOn=Nodal, &
  & nns=6, nnt=2 )
CALL obj%Initiate( param=param, mesh=amesh )
CALL obj%Display( 'obj: ' )
call display(amesh%GetTotalElements(), "total elements: " )
The above code will initiate an instance of STScalarMeshField_, which will contain following data.
Object INITIATED: TRUE
name: aScalar
prefix: STScalarMeshField
fieldType: NORMAL
engine: NATIVE_SERIAL
tSize: 484
defineOn: Nodal
rank: Scalar
varType: Time
shape:
-------
   6
val ALLOCATED: TRUE
mesh ASSOCIATED: TRUE
total elements: 484
Let's try to understand the above code:
- We save data in a two dimensional array val.
- The number of rows in valfor above example is6. This is because we have setvarType=Time, which means the scalar data changes inTime(and remains constant in space) inside the element.
- Because, we have set varType=Time, thereforeval(1:6, iel)denotes the value of scalar field at 6 time-nodes of element. Read more about the Shape method.
- The number of columns in valis484(which is the total number of elements in the mesh), this is because thefieldType=Regular(i.e., changes across all the elements).
Step 3:
  CALL obj%Deallocate()
  CALL amesh%Deallocate()
  CALL meshfile%Close()
  CALL meshfile%Deallocate()
  CALL param%Deallocate(); CALL FPL_FINALIZE()
END PROGRAM main