SetSteadyStokes111Param
Set SteadyStokes111 parameter.
Interface
INTERFACE
MODULE SUBROUTINE setSteadyStokes111Param( &
& param, &
& isConservativeForm, &
& gravity, &
& isSubscalePressure, &
& isBoundarySubscale, &
& stabParamOption, &
& domainFile,&
& materialInterfaces, &
& engine, &
& coordinateSystem, &
& nnt, &
& dt, &
& startTime, &
& endTime, &
& maxIter, &
& rtoleranceForPressure, &
& rtoleranceForVelocity, &
& atoleranceForPressure, &
& atoleranceForVelocity, &
& toleranceForSteadyState, &
& tFluidMaterials, &
& tDirichletBCForPressure, &
& tDirichletBCForVelocity, &
& baseInterpolationForSpace, &
& baseContinuityForSpace, &
& quadratureTypeForSpace, &
& baseInterpolationForTime, &
& baseContinuityForTime, &
& quadratureTypeForTime, &
& postProcessOpt, &
& refPressureNode, &
& refPressure)
!!
TYPE(ParameterList_), INTENT(INOUT) :: param
CHARACTER(*), INTENT(IN) :: domainFile
!! Mesh/domain file for pressure and velocity
LOGICAL(LGT), OPTIONAL, INTENT(IN) :: isConservativeForm
!! True if we are using conservative form
REAL(DFP), OPTIONAL, INTENT(IN) :: gravity(3)
!! Acceleration due to gravity, default is zero
!! If gravity is zero then we use piezometric pressure
!! If gravity is nonzero then we use thermodynamic pressure
LOGICAL(LGT), OPTIONAL, INTENT(IN) :: isSubscalePressure
!! If true then we consider the subscale pressure in stabilization
LOGICAL(LGT), OPTIONAL, INTENT(IN) :: isBoundarySubscale
!! If true then we consider the subscale at interelement boundary
INTEGER(I4B), OPTIONAL, INTENT(IN) :: stabParamOption
!! option for stabilization parameter, default is 1
INTEGER(I4B), OPTIONAL, INTENT(IN) :: materialInterfaces(:)
!! porous-fluid-interface
CHARACTER(*), OPTIONAL, INTENT(IN) :: engine
!! engine, default value is "NATIVE_SERIAL"
INTEGER(I4B), OPTIONAL, INTENT(IN) :: coordinateSystem
!! coordinate system, default value is KERNEL_CARTESIAN
INTEGER(I4B), OPTIONAL, INTENT(IN) :: nnt
!! number of nodes in time, it has no effect, so ignore it
REAL(DFP), OPTIONAL, INTENT(IN) :: dt
!! Initial time increment, has no effect
REAL(DFP), OPTIONAL, INTENT(IN) :: startTime
!! Starting time t0 of simulation, default=0.0, has no effect
REAL(DFP), OPTIONAL, INTENT(IN) :: endTime
!! Final time of simulation, default 0.0, has no effect
INTEGER(I4B), OPTIONAL, INTENT(IN) :: maxIter
!! maximum iteration for Newton-method
REAL(DFP), OPTIONAL, INTENT(IN) :: rtoleranceForPressure
!! toleranceForPressure
REAL(DFP), OPTIONAL, INTENT(IN) :: rtoleranceForVelocity
!! toleranceForVelocity
REAL(DFP), OPTIONAL, INTENT(IN) :: atoleranceForPressure
!! toleranceForPressure
REAL(DFP), OPTIONAL, INTENT(IN) :: atoleranceForVelocity
!! toleranceForVelocity
REAL(DFP), OPTIONAL, INTENT(IN) :: toleranceForSteadyState
!!
INTEGER(I4B), OPTIONAL, INTENT(IN) :: tFluidMaterials
!! Total number of fluid materials; default=1
INTEGER(I4B), OPTIONAL, INTENT(IN) :: tDirichletBCForPressure
!! Total number of Dirichlet domain for pressure, default=0
INTEGER(I4B), OPTIONAL, INTENT(IN) :: tDirichletBCForVelocity
!! Total number of Dirichlet domain for velocity, default=0
CHARACTER(*), OPTIONAL, INTENT(IN) :: baseInterpolationForSpace
!! Type of interpolation function used for basis function
CHARACTER(*), OPTIONAL, INTENT(IN) :: baseContinuityForSpace
!! Type of continuity of basis function for pressure
CHARACTER(*), OPTIONAL, INTENT(IN) :: quadratureTypeForSpace
!! Type of quadrature for pressure field
CHARACTER(*), OPTIONAL, INTENT(IN) :: baseInterpolationForTime
!! Type of interpolation function used for Time
CHARACTER(*), OPTIONAL, INTENT(IN) :: baseContinuityForTime
!! Type of continuity of basis function for Time
CHARACTER(*), OPTIONAL, INTENT(IN) :: quadratureTypeForTime
!! Type of quadrature for time
INTEGER(I4B), OPTIONAL, INTENT(IN) :: postProcessOpt
!! postProcessing option
INTEGER(I4B), OPTIONAL, INTENT(IN) :: refPressureNode
REAL(DFP), OPTIONAL, INTENT(IN) :: refPressure
END SUBROUTINE setSteadyStokes111Param
END INTERFACE
isConservativeForm: optional, default is .TRUE.gravity: optional, default is 0isSubscalePressure, optional, default is.FALSE.isBoundarySubscale, optional, default is.FALSE.stabParamOption, optional, default is 1domainFile: domainFile for pressure and velocitymaterialInterfaces, optional, default is 0engine, optional, default is NATIVE_SERIALCoordinateSystem, optional, default is KERNEL_CARTESIANnnt, optional, default 1dt, optional, default 0startTime, optional, default is 0endTime, optional, default is 0maxIterrtoleranceForPressure: optional, default is 1.0E-6rtoleranceForVelocity: optional, default is 1.0E-6atoleranceForPressure: optional, default is 1.0E-6atoleranceForVelocity: optional, default is 1.0E-6toleranceForSteadyState: optional, default is 1.0E-6tFluidMaterials, optional, default is 1tDirichletBCForPressure, optional, default is 0tDirichletBCForVelocity, optional, default is 0baseInterpolationForSpace, optionalbaseContinuityForSpace, optionalquadratureTypeForSpace, optional
Example
This example shows how to set the parameters for steady stokes flow kernel
PROGRAM main
USE easifemBase
USE easifemClasses
USE easifemMaterials
USE easifemKernels
USE SteadyStokes111_Class
IMPLICIT NONE
TYPE( SteadyStokes111_ ) :: obj
TYPE( ParameterList_ ) :: param
TYPE( HDF5File_ ) :: domainFile
TYPE( Domain_ ) :: dom
INTEGER( I4B ), PARAMETER :: refPressureNode=2
REAL( DFP ), PARAMETER :: refPressure = 0.0_DFP
INTEGER( I4B ), PARAMETER :: tDirichletBCForVelocity = 2
INTEGER( I4B ), PARAMETER :: tDirichletBCForPressure = 0
INTEGER( I4B ), PARAMETER :: tFluidMaterials= 1
INTEGER( I4B ), PARAMETER :: stabParamOption= 1
LOGICAL( LGT ), PARAMETER :: isSubscalePressure = .FALSE.
LOGICAL( LGT ), PARAMETER :: isBoundarySubscale = .FALSE.
REAL( DFP ), PARAMETER :: gravity(3)=[0.0, -9.8, 0.0]
LOGICAL( LGT ), PARAMETER :: isConservativeForm = .TRUE.
CHARACTER( * ), PARAMETER :: engine="NATIVE_SERIAL"
CHARACTER( * ), PARAMETER :: domainFileName="./mesh.h5"
INTEGER( I4B ), PARAMETER :: CoordinateSystem = KERNEL_CARTESIAN
INTEGER( I4B ), PARAMETER :: maxIter = 100
REAL( DFP ), PARAMETER :: rtoleranceForPressure = 1.0E-6
REAL( DFP ), PARAMETER :: rtoleranceForVelocity = 1.0E-6
REAL( DFP ), PARAMETER :: atoleranceForPressure = 1.0E-6
REAL( DFP ), PARAMETER :: atoleranceForVelocity = 1.0E-6
REAL( DFP ), PARAMETER :: toleranceForSteadyState = 1.0E-6
CHARACTER(*), PARAMETER :: baseInterpolationForSpace="LagrangeInterpolation"
CHARACTER(*), PARAMETER :: baseContinuityForSpace="H1"
CHARACTER(*), PARAMETER :: quadratureTypeForSpace="GaussLegendre"
Set parameters for kernel.
CALL FPL_INIT(); CALL param%Initiate()
Set parameters for the kernel.
CALL SetSteadyStokes111Param( &
& param=param, &
& isConservativeForm=isConservativeForm, &
& gravity = gravity, &
& isSubscalePressure = isSubscalePressure, &
& isBoundarySubscale = isBoundarySubscale, &
& stabParamOption = stabParamOption, &
& domainFile = domainFileName, &
& engine=engine, &
& CoordinateSystem=KERNEL_CARTESIAN, &
& maxIter =maxIter, &
& rtoleranceForPressure = rtoleranceForPressure, &
& rtoleranceForVelocity = rtoleranceForVelocity, &
& atoleranceForPressure = atoleranceForPressure, &
& atoleranceForVelocity = atoleranceForVelocity, &
& toleranceForSteadyState = toleranceForSteadyState, &
& tFluidMaterials=tFluidMaterials, &
& tDirichletBCForPressure=tDirichletBCForPressure, &
& tDirichletBCForVelocity=tDirichletBCForVelocity, &
& baseInterpolationForSpace=baseInterpolationForSpace, &
& baseContinuityForSpace=baseContinuityForSpace, &
& quadratureTypeForSpace=quadratureTypeForSpace, &
& refPressureNode=refPressureNode, &
& refPressure=refPressure &
& )
Let us print the parameter list.
CALL param%Print()
Let us check the essential parameter.
CALL obj%CheckEssentialParam( param )
CALL param%Deallocate(); CALL FPL_FINALIZE()
END PROGRAM main