Introduction
- 5: VMS based stabilized STFEM with equal order interpolation
- 1: pressure-velocity are solved in coupled manner, block structure of linear solver
- 1: Meshwise constant material properties
Stabilization parameters
ComputeStabParam1
ComputeStabParam2
ComputeStabParam3
- For the fluid, we use definition 1
- For porous medium we use definition 2
ComputeStabParam4
- For the fluid, we use definition 1
- For porous medium we use definition following definition of .
ComputeStabParam5
- Fluid: Definition 1
- Porous medium we use following definition:
Some element lengths
Getting-Started
Structure
TYPE, EXTENDS(AbstractSTDBE_) :: STDBE511_
Methods
Following methods have been implemented:
AddSurrogate
, Add surrogate to the exception handler of the moduleCheckEssentialParam
check essential parametersInitiate
, Initiate the kernelsInitiateFields
Set
ApplyDirichletBC
Assemble
AssembleRHS
AssembleTanmat
Solve
Update
UpdateIteration
isConverged
isSteadyState
ComputeStabParam
Submodules
Methods are implemented in following submodules.
STDBE511_Class@ConstructorMethods.F90
STDBE511_Class@GetMethods.F90
STDBE511_Class@InitiateFieldsMethods.F90
STDBE511_Class@SetMethods.F90
STDBE511_Class@IOMethods.F90
STDBE511_Class@AssembleMethods.F90
STDBE511_Class@AssembleTanmatMethods.F90
STDBE511_Class@AssembleRHSMethods.F90
STDBE511_Class@SolveMethods.F90
STDBE511_Class@UpdateMethods.F90
STDBE511_Class@ConvergenceMethods.F90
STDBE511_Class@BCMethods.F90
STDBE511_Class@ApplyDirichletBCMethods.F90
STDBE511_Class@MaterialMethods.F90
STDBE511_Class@StabParamMethods.F90
ConstructorMethods
SetSTDBE511Param@ConstructorMethods
This subroutine sets the essential parameter in the kernel
INTERFACE
MODULE SUBROUTINE SetSTDBE511Param( &
& param, &
& stabParamOption, &
& domainFile,&
& materialInterfaces, &
& engine, &
& coordinateSystem, &
& nnt, &
& dt, &
& startTime, &
& endTime, &
& maxIter, &
& rtoleranceForPressure, &
& rtoleranceForVelocity, &
& atoleranceForPressure, &
& atoleranceForVelocity, &
& toleranceForSteadyState, &
& tPorousMaterials, &
& tFluidMaterials, &
& tDirichletBCForPressure, &
& tDirichletBCForVelocity, &
& baseInterpolationForSpace, &
& baseContinuityForSpace, &
& quadratureTypeForSpace, &
& baseContinuityForTime,&
& baseInterpolationForTime, &
& quadratureTypeForTime)
!!
TYPE(ParameterList_), INTENT(INOUT) :: param
INTEGER(I4B), INTENT(IN) :: stabParamOption
CHARACTER(LEN=*), INTENT(IN) :: domainFile
INTEGER(I4B), OPTIONAL, INTENT(IN) :: materialInterfaces(:)
CHARACTER(LEN=*), INTENT(IN) :: engine
INTEGER(I4B), INTENT(IN) :: coordinateSystem
INTEGER(I4B), INTENT(IN) :: nnt
REAL(DFP), INTENT(IN) :: dt
REAL(DFP), OPTIONAL, INTENT(IN) :: startTime
REAL(DFP), INTENT(IN) :: endTime
INTEGER(I4B), INTENT(IN) :: maxIter
REAL(DFP), INTENT(IN) :: rtoleranceForPressure
REAL(DFP), INTENT(IN) :: rtoleranceForVelocity
REAL(DFP), INTENT(IN) :: atoleranceForPressure
REAL(DFP), INTENT(IN) :: atoleranceForVelocity
REAL(DFP), INTENT(IN) :: toleranceForSteadyState
INTEGER(I4B), INTENT(IN) :: tPorousMaterials
INTEGER(I4B), OPTIONAL, INTENT(IN) :: tFluidMaterials
INTEGER(I4B), OPTIONAL, INTENT(IN) :: tDirichletBCForPressure
INTEGER(I4B), OPTIONAL, INTENT(IN) :: tDirichletBCForVelocity
CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: baseInterpolationForSpace
CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: baseContinuityForSpace
CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: quadratureTypeForSpace
CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: baseInterpolationForTime
CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: baseContinuityForTime
CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: quadratureTypeForTime
END SUBROUTINE SetSTDBE511Param
END INTERFACE
The meaning of each parameter is given below:
param
, [[ParameterList_]] to be constructedstabParamOption
, stabilization parameter see, [[#Stabilization parameters]]domainFile
, Domain file name for pressure and velocitymaterialInterfaces
, porous-fluid-interfaceengine
, enginecoordinateSystem
, coordinate systemnnt
, number of nodes in timedt
, Initial time incrementstartTime
, Starting time t0 of simulation, default=0.0endTime
, Final time of simulationmaxIter
, maximum iteration for Newton-method or inexact Newton methodsrtoleranceForPressure
, relative tolerance for convergence in pressurertoleranceForVelocity
, relative tolerance for convergence in velocityatoleranceForPressure
, absolute tolerance for convergence in pressureatoleranceForVelocity
, absolute tolerance for convergence in velocitytoleranceForSteadyState
, tolerance for steady statetPorousMaterials
, total number of porous materialstFluidMaterials
, total number of fluid materials; default=1tDirichletBCForPressure
, total number of Dirichlet domain for pressure, default=0tDirichletBCForVelocity
, total number of Dirichlet domain for velocity, default=0baseInterpolationForSpace
, type of interpolation function used for basis functionbaseContinuityForSpace
, type of continuity of basis function for pressurequadratureTypeForSpace
, type of quadrature for pressure fieldbaseInterpolationForTime
, type of interpolation function used for TimebaseContinuityForTime
, type of continuity of basis function for TimequadratureTypeForTime
, type of quadrature for time
AddSurrogate
Add surrogate to the module [[ExceptionHandler_]]
INTERFACE
MODULE SUBROUTINE AddSurrogate(obj, UserObj)
CLASS(STDBE511_), INTENT(INOUT) :: obj
TYPE(ExceptionHandler_), INTENT(IN) :: UserObj
END SUBROUTINE AddSurrogate
END INTERFACE
CheckEssentialParam
Checks the essential parameters in the param of kernels
INTERFACE
MODULE SUBROUTINE CheckEssentialParam(obj, param, prefix)
CLASS(STDBE511_), INTENT(INOUT) :: obj
TYPE(ParameterList_), INTENT(IN) :: param
CHARACTER(LEN=*), OPTIONAL, INTENT(IN) :: prefix
END SUBROUTINE CheckEssentialParam
END INTERFACE
Initiate
- This routine initiates the kernel.
- Here
param
contains all the necessary components for initiating the state of the kernel. - Here
dom
is an instance of [[Domain_]], and it acts as a target of the kernel's domain pointerdomForPressure
anddomForVelocity
. domains
is a one dimensional array of [[Domain_]] pointer- The size of
domains
should be 2 domains(1)
acts as target fordomForVelocity
.domains(2)
acts as a target fordomForPressure
.
No additional, memory is allocated for it. In this way, several kernels can work on a common domain.
INTERFACE
MODULE SUBROUTINE Initiate(obj, param, dom, domains)
CLASS(STDBE511_), INTENT(INOUT) :: obj
TYPE(ParameterList_), INTENT(IN) :: param
CLASS(Domain_), OPTIONAL, TARGET, INTENT(INOUT) :: dom
TYPE(DomainPointer_), OPTIONAL, TARGET, INTENT(INOUT) :: domains(:)
END SUBROUTINE Initiate
END INTERFACE
GetMethods
Currently, there are no methods in these submodules.
InitiateFieldsMethods
InitiateFields
Initiate the matrix and vector fields for kernel. These methods are called internally when we call set method [[#Set]].
INTERFACE
MODULE SUBROUTINE InitiateFields(obj)
CLASS(STDBE511_), INTENT(INOUT) :: obj
END SUBROUTINE InitiateFields
END INTERFACE
This routine performs following tasks.
tanmat
instance of [[BlockMatrixField_]]- Set precondition to ILUD (incomplete LU decomposition)
- Pass information of
tanmat
tolinsol
rhs
instance of [[BlockNodeField_]]sol
instance of [[BlockNodeField_]]nodeCoord
instance of [[VectorField_]]stNodeCoord
instance of [[../STVectorField/STVectorField_]]pressure
instance of [[STScalarField_]]velocity
instance of [[../STVectorField/STVectorField_]]pressure0
instance of [[ScalarField_]]velocity0
instance of [[VectorField_]]linssol
set Dirichlet boundary condition indices by calling [[LinSolver_#SetDirichletBCIndices]]
SetMethods
Set
This routine is the most important one. This routine should be called before starting the main computation. After initiating the kernel, we have all the information to construct the state of the kernel. This routine checks all the options. This routine, then sets pointer to the appropriate pointers.
Internally this routine calls:
- [[Abstract#Set]]
- [[#InitiateFields]]
This routine also fixes the procedure pointer: ComputeStabParam
INTERFACE
MODULE SUBROUTINE Set(obj)
CLASS(STDBE511_), INTENT(INOUT) :: obj
END SUBROUTINE Set
END INTERFACE
IOMethods
Currently, there are no methods in this submodules. Please see, [[../AbstractSTDBE/AbstractSTDBE_#IOMethods]]
AssembleMethods
Assemble
This routine should be called after calling [[#AssembleTanmat]] and [[#AssembleRHS]] as it computes the norm of rhs
, and precondition of tangent matrix.
INTERFACE
MODULE SUBROUTINE Assemble(obj)
CLASS(STDBE511_), INTENT(INOUT) :: obj
END SUBROUTINE Assemble
END INTERFACE
AssembleTanmatMethods
AssembleTanmat
Assemble tangent matrix.
INTERFACE
MODULE SUBROUTINE AssembleTanMat(obj)
CLASS(STDBE511_), INTENT(INOUT) :: obj
END SUBROUTINE AssembleTanMat
END INTERFACE
AssembleRHSMethods
AssembleRHS
Assemble rhs
.
INTERFACE
MODULE SUBROUTINE AssembleRHS(obj)
CLASS(STDBE511_), INTENT(INOUT) :: obj
END SUBROUTINE AssembleRHS
END INTERFACE
SolveMethods
Solve
This subroutine solves the system of linear equation.
INTERFACE
MODULE SUBROUTINE Solve(obj)
CLASS(STDBE511_), INTENT(INOUT) :: obj
END SUBROUTINE Solve
END INTERFACE
UpdateMethods
UpdateIteration
This subroutine update the state of the kernel during an iteration.
- It extracts
velocity
fromsol
- It extracts
pressure
fromsol
If reset
is true then it sets sol
to zero.
INTERFACE
MODULE SUBROUTINE UpdateIteration(obj, reset)
CLASS(STDBE511_), INTENT(INOUT) :: obj
LOGICAL(LGT), INTENT(IN) :: reset
END SUBROUTINE UpdateIteration
END INTERFACE
Update
This subroutine update the state of the kernel after convergence.
- Update
currentTime
- Get
velocity0
fromvelocity
- Get
pressure0
frompressure
If reset
is true then reset velocity
, pressure
and sol
to zero.
INTERFACE
MODULE SUBROUTINE Update(obj, reset)
CLASS(STDBE511_), INTENT(INOUT) :: obj
LOGICAL(LGT), INTENT(IN) :: reset
END SUBROUTINE Update
END INTERFACE
ConvergenceMethods
IsConverged
It returns true if the iteration in the kernel is converged
INTERFACE
MODULE FUNCTION IsConverged(obj) RESULT(Ans)
CLASS(STDBE511_), INTENT(INOUT) :: obj
LOGICAL(LGT) :: Ans
END FUNCTION IsConverged
END INTERFACE
IsSteadyState
Returns true if steady state is achieved
INTERFACE
MODULE FUNCTION IsSteadyState(obj) RESULT(Ans)
CLASS(STDBE511_), INTENT(INOUT) :: obj
LOGICAL(LGT) :: ans
END FUNCTION IsSteadyState
END INTERFACE
BCMethods
Currently, there are no methods, see [[../AbstractSTDBE/AbstractSTDBE_#BCMethods]] for implementations.
ApplyDirichletBCMethods
ApplyDirichletBC
INTERFACE
MODULE SUBROUTINE ApplyDirichletBC(obj)
CLASS(STDBE511_), INTENT(INOUT) :: obj
END SUBROUTINE ApplyDirichletBC
END INTERFACE
MaterialMethods
Currently, there are no methods, see [[../AbstractSTDBE/AbstractSTDBE_#MaterialMethods]] for implementations.