Initiate
Initiate an instance of DOF.
Interface
We can construct DOF_
object by calling the Initiate()
subroutine.
INTERFACE
MODULE PURE SUBROUTINE Initiate( obj, tNodes, Names, spacecompo, &
& timecompo, StorageFMT )
CLASS( DOF_ ), INTENT( INOUT ) :: obj
!! degree of freedom object
INTEGER( I4B ), INTENT( IN ) :: tNodes( : )
!! number of nodes for each physical variable
CHARACTER( LEN = 1 ), INTENT( IN ) :: Names( : )
!! Names of each physical variable
INTEGER( I4B ), INTENT( IN ) :: spacecompo( : )
!! Space component of each physical variable
INTEGER( I4B ), INTENT( IN ) :: timecompo( : )
!! Time component of each physical variable
INTEGER( I4B ), INTENT( IN ) :: StorageFMT
!! Storage format `FMT_DOF`, `FMT_Nodes`
END SUBROUTINE Initiate
END INTERFACE
tNodes
denotes the total number of nodes in each physical variablesNames
is the name of each physical variablesSpaceCompo
is the number of spatial components in each physical variable, if a physical variable is scalar then one can use also use -1 instead of 1 for the total number of space componentsTimeCompo
is the number of time components in each physical variablesStorageFMT
is the storage format, it can beFMT_DOF
orFMT_Nodes
The size of tNodes
, Names
, SpaceCompo
, TimeCompo
vectors should be equal to the total number of physical variables.
- ܀ See example
- ↢
This example show how to create an instance of DOF and use it to create a vector of reals.
PROGRAM main
USE easifemBase
IMPLICIT NONE
TYPE( DOF_ ) :: obj
REAL( DFP ), ALLOCATABLE :: val( : )
CALL Initiate( obj, tNodes=[10], names=["U"], spaceCompo=[3], &
timeCompo=[1], storageFMT = FMT_DOF )
! Initiate a real vector using `DOF_` object.
CALL Initiate( Val=val, obj=obj )
CALL Display( obj, "CALL Initiate( Val=val, obj=obj ) : " )
CALL Deallocate( obj )
END PROGRAM main
Interfaces for constructing vectors using DOF
The Initiate()
method has been extended for constructing
- Rank-1 fortran arrays
- RealVector_
- Vector of RealVector_.
This topic is covered below.
Constructing navtive vectors
- ܀ See Interface
- ܀ See example
- ↢
INTERFACE
MODULE PURE SUBROUTINE Initiate( val, obj )
REAL( DFP ), ALLOCATABLE, INTENT( INOUT ) :: val( : )
!! This vector will be initiated by using obj
CLASS( DOF_ ), INTENT( IN ) :: obj
!! DOF object
END SUBROUTINE Initiate
END INTERFACE
This example show how to initiate an instance of DOF
. Then we use it to create an instance of RealVector
.
PROGRAM main
USE BaseType, ONLY: DOF_
USE GlobalData
USE DOF_Method
IMPLICIT NONE
TYPE(DOF_) :: obj
TYPE(RealVector_) :: val
! Create an instance of[[DOF_]]
CALL Initiate(obj, tNodes=[10], names=["U"], spaceCompo=[3], &
timeCompo=[1], storageFMT=FMT_DOF)
! Initiate a vector of REAL using an instance of[[DOF_]]
CALL Initiate(Val=val, obj=obj)
CALL Display(Val, "CALL Initiate( Val=val, obj=obj ) : ")
CALL DEALLOCATE (obj)
END PROGRAM main
Constructing RealVector
- ܀ Interface
- ️܀ See example
- ↢
PROGRAM main
USE GlobalData
USE BaseType, ONLY: DOF_, RealVector_
USE DOF_Method
USE RealVector_Method, ONLY: Display, RealVector_Initiate => Initiate
IMPLICIT NONE
TYPE(DOF_) :: obj
TYPE(RealVector_), ALLOCATABLE :: val(:)
CALL Initiate(obj, tNodes=[10], names=["U"], spaceCompo=[3], &
timeCompo=[1], storageFMT=FMT_DOF)
CALL RealVector_Initiate(dofobj=obj, obj=val)
CALL Display(val, "CALL Initiate( val=val, obj=obj ) : ")
CALL DEALLOCATE (obj)
END PROGRAM main
Constructing vector of RealVector
- ܀ Interface
- ️܀ See example
- ↢
This example shows the usage of assignment operator to construct an instance of DOF
.
PROGRAM main
USE GlobalData
USE BaseType, ONLY: DOF_
USE DOF_Method
IMPLICIT NONE
TYPE(DOF_) :: obj, anotherObj
CALL Initiate(obj, tNodes=[10], names=["U"], spaceCompo=[3], &
timeCompo=[1], storageFMT=FMT_DOF)
anotherObj = obj
CALL Display(anotherObj, "anotherObj=obj : ")
CALL DEALLOCATE (obj)
CALL DEALLOCATE (anotherObj)
END PROGRAM main
Assignment(=)
We can use an assignment operator to copy the contents of one DOF_
object into another DOF_
object.
- ܀ See example
- ↢
PROGRAM main
USE GlobalData
USE BaseType, ONLY: DOF_
USE DOF_Method
IMPLICIT NONE
TYPE(DOF_) :: obj
obj = DOF(tNodes=[10], names=["U"], spaceCompo=[3], &
timeCompo=[1], storageFMT=FMT_DOF)
CALL Display(obj, "DOF() : ")
CALL DEALLOCATE (obj)
END PROGRAM main
DOF Function
We can also use DOF()
function for the constructing the DOF object.
- ܀ See example
- ↢
PROGRAM main
USE GlobalData
USE BaseType, ONLY: DOF_
USE DOF_Method
IMPLICIT NONE
TYPE(DOF_), POINTER :: obj
obj => DOF_POINTER(tNodes=[10], names=["U"], spaceCompo=[3], &
timeCompo=[1], storageFMT=FMT_DOF)
CALL Display(obj, "DOF() : ")
CALL DEALLOCATE (obj)
END PROGRAM main
DOF_Pointer
We can also use DOF_Pointer()
function for get a pointer to a newly created an instance of DOF_
.
- ܀ See example
- ↢
This example show how to initiate an instance of DOF_ and use it to create a vector of reals.
PROGRAM main
USE GlobalData
USE BaseType, ONLY: DOF_
USE DOF_Method
IMPLICIT NONE
TYPE(DOF_) :: obj
REAL(DFP), ALLOCATABLE :: val(:)
CALL Initiate(obj, tNodes=[10], names=["U"], spaceCompo=[3], &
timeCompo=[1], storageFMT=FMT_DOF)
CALL Initiate(Val=val, obj=obj)
val(1:10) = 1; val(11:20) = 2; val(21:) = 3
CALL Display(Val, obj, "CALL Initiate( Val=val, obj=obj ) : ")
CALL DEALLOCATE (obj)
END PROGRAM main