Path: blob/devel/elmerice/Tests/DGsolver/PROG/InitializeDGVariable.f90
3206 views
! This Solver initialize the two DG variable (have to be run to time)1RECURSIVE SUBROUTINE InitializeDGVariable(Model, Solver, Timestep, TransientSimulation)2USE DefUtils3USE Materialmodels4!-----------------------------------------------------------5IMPLICIT NONE6!------------ external variables ---------------------------7TYPE(Model_t) :: Model8TYPE(Solver_t), TARGET :: Solver9LOGICAL :: TransientSimulation10REAL(KIND=dp) :: Timestep11!------------ internal variables ---------------------------12REAL(KIND=dp) :: z, D13INTEGER :: i, j, k, t, n, dummyInt, Active, Indexes(128)14LOGICAL :: GotIt,UnFoundFatal15TYPE(Element_t), POINTER :: Element16TYPE(Mesh_t), POINTER :: Mesh17TYPE(Nodes_t) :: ElementNodes18CHARACTER(LEN=MAX_NAME_LEN) :: VariableName, SolverName19TYPE(ValueList_t), POINTER :: SolverParams20TYPE(Variable_t), POINTER :: VarSol21REAL(KIND=dp), ALLOCATABLE :: Depth(:)2223SolverName = 'InitializeDGVariable'24Mesh => GetMesh()25n = Mesh % MaxElementNodes26ALLOCATE(ElementNodes % x(n), ElementNodes % y(n), ElementNodes % z(n), &27Depth(n))2829SolverParams => GetSolverParams()30VariableName = GetString(SolverParams,'Initialized Variable Name', GotIt)31IF (.NOT.GotIt) THEN32WRITE(Message,'(a)')'Keyword >Initialized Variable Name< not found in Solver section'33CALL FATAL(SolverName, Message)34END IF3536VarSol => VariableGet(Solver % Mesh % Variables,VariableName,UnFoundFatal=UnFoundFatal)3738Active = GetNOFActive()39DO t = 1, Active40Element => GetActiveElement( t )41n = GetElementNOfNodes( Element )42dummyInt = GetElementDOFs( Indexes )43CALL GetElementNodes( ElementNodes )44! Non DG other variable should be read like this45! Don't use their perm and the j indexes as it will be wrong46! when the solver is called for a DG variable47CALL GetScalarLocalSolution(Depth,'Depth')48DO i=1,n49j = Indexes(i)50z = ElementNodes % z(i)51D = Depth(i)52VarSol % Values(VarSol % Perm(j)) = 1.0_dp - 0.6_dp*z/100.053write(*,*)t,i,j,k, z+D5455END DO56END DO5758DEALLOCATE(ElementNodes % x, ElementNodes % y, ElementNodes % z, Depth)59END SUBROUTINE InitializeDGVariable606162