Skip to main content

Initiate

Inherited from AbstractMeshField

Initiate

Initiate an instance of AbstractMeshField_.

@ConstructorMethods

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 to Example 4 are related to the Initiate by using Parameters.
  • Example 6 and Example 7 are related to the Initiate by using UserFunction.

Example 1

Click here to see the example

Example 1 (Initiate by Parameter)

info

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 ScalarMeshField_.

PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE( HDF5File_ ) :: meshfile
TYPE( Mesh_ ) :: amesh
TYPE( ScalarMeshField_ ) :: 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 ScalarMeshField_.

CALL FPL_INIT(); CALL param%initiate()
CALL SetScalarMeshFieldParam( &
& param=param, &
& name='aScalar', &
& varType = Constant, &
& fieldType=TypeField%normal, &
& engine='NATIVE_SERIAL', &
& defineOn=Nodal, &
& nns=6 )
CALL obj%Initiate( param=param, mesh=amesh )
CALL obj%Display( 'obj: ' )

The above code will initiate an instance of ScalarMeshField_, which will contain following data.

Object INITIATED: TRUE
name: aScalar
prefix: ScalarMeshField
fieldType: NORMAL
engine: NATIVE_SERIAL
tSize: 484
defineOn: Nodal
rank: Scalar
varType: Constant
shape:
-------
6
0
0
0
0
0
val: ALLOCATED
mesh: ASSOCIATED

Let's try to understand the following situation:

  • We save data in a two dimensional array val.
  • The number of rows in val for above example is 1. Because, we have set varType=Constant, all nodes (we have specified 6 nodes) in an element have same value of scalar field. Read more about the Shape method.
  • The number of columns in val is 484, which denotes the total number of elements in the mesh.

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

Example 2 (Initiate by Parameter)

info

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 ScalarMeshField_.

PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE( HDF5File_ ) :: meshfile
TYPE( Mesh_ ) :: amesh
TYPE( ScalarMeshField_ ) :: 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 ScalarMeshField_.

CALL FPL_INIT(); CALL param%initiate()
CALL SetScalarMeshFieldParam( &
& param=param, &
& name='aScalar', &
& varType = Constant, &
& fieldType=TypeField%Constant, &
& engine='NATIVE_SERIAL', &
& defineOn=Nodal, &
& nns=6 )
CALL obj%Initiate( param=param, mesh=amesh )
CALL obj%Display( 'obj: ' )

The above code will initiate an instance of ScalarMeshField_, which will contain following data.

Object INITIATED: TRUE
name: aScalar
prefix: ScalarMeshField
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:

  • Internally, we save data in a two dimensional array val.
  • The number of rows in val for above example is 1 (this because the scalar data is constant inside the element).
  • Because, we have set varType=Constant, all nodes (we have specified 6 nodes) in an element have same value of scalar field. Read more about the Shape method.
  • The number of columns in val is 1, this is because the fieldType=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

Example 3 (Initiate by Parameter)

info

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 ScalarMeshField_.

PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE( HDF5File_ ) :: meshfile
TYPE( Mesh_ ) :: amesh
TYPE( ScalarMeshField_ ) :: 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 ScalarMeshField_.

CALL FPL_INIT(); CALL param%initiate()
CALL SetScalarMeshFieldParam( &
& param=param, &
& name='aScalar', &
& varType = Space, &
& fieldType=TypeField%Normal, &
& engine='NATIVE_SERIAL', &
& defineOn=Nodal, &
& nns=6 )
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 ScalarMeshField_, which will contain following data.

Object INITIATED: TRUE
name: aScalar
prefix: ScalarMeshField
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 val for above example is 6. This is because we have set varType=Space, which means the scalar data changes in Space inside the element.
  • The number of columns in val is 484 (which is the total number of elements in the mesh), this is because the fieldType=Regular (i.e., changes across all the elements).
  • Because, we have set varType=Space, therefore val(1:6) denotes the value of scalar field at 6 nodes of element. Read more about the Shape method.

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

Example 4 (Initiate by Parameter)

info

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 ScalarMeshField_.

PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE( HDF5File_ ) :: meshfile
TYPE( Mesh_ ) :: amesh
TYPE( ScalarMeshField_ ) :: 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 ScalarMeshField_.

CALL FPL_INIT(); CALL param%initiate()
CALL SetScalarMeshFieldParam( &
& param=param, &
& name='aScalar', &
& varType =Time, &
& fieldType=TypeField%Normal, &
& engine='NATIVE_SERIAL', &
& defineOn=Nodal, &
& nns=6 )
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 ScalarMeshField_, which will contain following data.

Object INITIATED: TRUE
name: aScalar
prefix: ScalarMeshField
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 val for above example is 6. This is because we have set varType=Time, which means the scalar data changes in Time inside the element.
  • Because, we have set varType=Time, therefore val(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 val is 484 (which is the total number of elements in the mesh), this is because the fieldType=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 6

Click here to see the example

Example 6 (Initiate by UserFunction)

info

Initiate an instance of ScalarMeshField_ by using a UserFunction_. The user function is constant in this example.

PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE(HDF5File_) :: meshfile
TYPE(Mesh_) :: amesh
TYPE(ScalarMeshField_) :: obj
TYPE(ParameterList_) :: param
TYPE(UserFunction_) :: func

CALL meshfile%Initiate(FileName="./mesh.h5", MODE="READ")
CALL meshfile%OPEN()
CALL amesh%Initiate(hdf5=meshfile, group="/surfaceEntities_1")

CALL FPL_INIT(); CALL param%initiate()
CALL SetUserFunctionParam(param=param, name="func", returnType=Scalar, &
& argType=Constant)
CALL func%Initiate(param)
CALL func%Set(scalarValue=2.0_DFP)
CALL obj%Initiate(mesh=amesh, func=func, name="func", engine="NATIVE_SERIAL")

CALL obj%DEALLOCATE()
CALL amesh%DEALLOCATE()
CALL meshfile%CLOSE()
CALL meshfile%DEALLOCATE()
CALL param%DEALLOCATE(); CALL FPL_FINALIZE()
END PROGRAM main

Example 7

Click here to see the example

Example 7 (Initiate by UserFunction)

info

This example shows how to initiate an instance of ScalarMeshField_ by using a UserFunction. The user function is space dependent in this example.

PROGRAM main
USE easifemBase
USE easifemClasses
IMPLICIT NONE
TYPE(HDF5File_) :: meshfile
CLASS(Mesh_), POINTER :: amesh => NULL()
TYPE(Domain_) :: dom
TYPE(ScalarMeshField_) :: obj
TYPE(ParameterList_) :: param
TYPE(UserFunction_) :: func
PROCEDURE(iface_ScalarFunction), POINTER :: func_ptr => NULL()

CALL meshfile%Initiate(FileName="./mesh.h5", MODE="READ")
CALL meshfile%OPEN()

CALL dom%Initiate(meshfile, "")
amesh => dom%GetMeshPointer(dim=dom%GetNSD(), entityNum=1)

CALL FPL_INIT(); CALL param%Initiate()
CALL SetUserFunctionParam(param=param, name="func", returnType=Scalar, &
& argType=Space)
CALL func%Initiate(param)
func_ptr => func1
CALL func%Set(scalarFunction=func_ptr)

CALL obj%Initiate(mesh=amesh, func=func, name="func", engine="NATIVE_SERIAL")

CALL obj%DEALLOCATE()
CALL amesh%DEALLOCATE()
CALL meshfile%CLOSE()
CALL meshfile%DEALLOCATE()
CALL param%DEALLOCATE(); CALL FPL_FINALIZE()

CONTAINS
PURE FUNCTION func1(x) RESULT(ans)
REAL(DFP), OPTIONAL, INTENT(IN) :: x(:)
REAL(DFP) :: ans
ans = x(1) + x(2)
END FUNCTION func1
END PROGRAM main