Path: blob/devel/elmerice/Tests/DGsolver/PROG/DGtoNodalVariable.f90
3206 views
! This Solver is to write a DG variable into a Nodal Variable1! There are two solver2! the first write the DG exported variable into a 'true' Nodal variable3! the second write this 'true' nodal variable into the primary DG variable4RECURSIVE SUBROUTINE DGtoNodalVariable1(Model, Solver, Timestep, TransientSimulation)5USE DefUtils6USE Materialmodels7!-----------------------------------------------------------8IMPLICIT NONE9!------------ external variables ---------------------------10TYPE(Model_t) :: Model11TYPE(Solver_t), TARGET :: Solver12LOGICAL :: TransientSimulation13REAL(KIND=dp) :: Timestep14!------------ internal variables ---------------------------15REAL(KIND=dp) :: z, D16INTEGER :: i, j, k, t, n, dummyInt, Active, Indexes(128)17LOGICAL :: GotIt,UnFoundFatal18TYPE(Element_t), POINTER :: Element19TYPE(Mesh_t), POINTER :: Mesh20CHARACTER(LEN=MAX_NAME_LEN) :: InName, OutName, SolverName21TYPE(ValueList_t), POINTER :: SolverParams22TYPE(Variable_t), POINTER :: InSol, OutSol2324SolverName = 'DGtoNodalVariable1'25Mesh => GetMesh()26n = Mesh % MaxElementNodes2728SolverParams => GetSolverParams()29InName = GetString(SolverParams,'Input Variable Name', GotIt)30IF (.NOT.GotIt) THEN31WRITE(Message,'(a)')'Keyword >Input Variable Name< not found in Solver section'32CALL FATAL(SolverName, Message)33END IF3435OutName = GetString(SolverParams,'Output Variable Name', GotIt)36IF (.NOT.GotIt) THEN37WRITE(Message,'(a)')'Keyword >Output Variable Name< not found in Solver section'38CALL FATAL(SolverName, Message)39END IF4041InSol => VariableGet(Solver % Mesh % Variables,InName,UnFoundFatal=UnFoundFatal)4243OutSol => VariableGet(Solver % Mesh % Variables,OutName,UnFoundFatal=UnFoundFatal)4445Active = GetNOFActive()46DO t = 1, Active47Element => GetActiveElement( t )48n = GetElementNOfNodes( Element )49dummyInt = GetElementDOFs( Indexes )50DO i=1,n51j = Indexes(i)52OutSol % Values(OutSol % Perm(j)) = InSol % Values(InSOl % Perm(j))53END DO54END DO55END SUBROUTINE DGtoNodalVariable15657RECURSIVE SUBROUTINE DGtoNodalVariable2(Model, Solver, Timestep, TransientSimulation)58USE DefUtils59USE Materialmodels60!-----------------------------------------------------------61IMPLICIT NONE62!------------ external variables ---------------------------63TYPE(Model_t) :: Model64TYPE(Solver_t), TARGET :: Solver65LOGICAL :: TransientSimulation66REAL(KIND=dp) :: Timestep67!------------ internal variables ---------------------------68REAL(KIND=dp) :: z, D69INTEGER :: i, j, k, t, n, dummyInt, Active, Indexes(128)70LOGICAL :: GotIt,UnFoundFatal71TYPE(Element_t), POINTER :: Element72TYPE(Mesh_t), POINTER :: Mesh73CHARACTER(LEN=MAX_NAME_LEN) :: InName, OutName, SolverName74TYPE(ValueList_t), POINTER :: SolverParams75TYPE(Variable_t), POINTER :: OutSol76REAL(KIND=dp), ALLOCATABLE :: InValues(:)7778SolverName = 'DGtoNodalVariable2'79Mesh => GetMesh()80n = Mesh % MaxElementNodes81ALLOCATE(InValues(n))8283SolverParams => GetSolverParams()84InName = GetString(SolverParams,'Input Variable Name', GotIt)85IF (.NOT.GotIt) THEN86WRITE(Message,'(a)')'Keyword >Input Variable Name< not found in Solver section'87CALL FATAL(SolverName, Message)88END IF8990OutName = GetString(SolverParams,'Output Variable Name', GotIt)91IF (.NOT.GotIt) THEN92WRITE(Message,'(a)')'Keyword >Output Variable Name< not found in Solver section'93CALL FATAL(SolverName, Message)94END IF9596OutSol => VariableGet(Solver % Mesh % Variables,OutName,UnFoundFatal=UnFoundFatal)9798Active = GetNOFActive()99DO t = 1, Active100Element => GetActiveElement( t )101n = GetElementNOfNodes( Element )102dummyInt = GetElementDOFs( Indexes )103CALL GetScalarLocalSolution(InValues,TRIM(InName))104DO i=1,n105j = Indexes(i)106OutSol % Values(OutSol % Perm(j)) = InValues(i)107END DO108END DO109DEALLOCATE(InValues)110END SUBROUTINE DGtoNodalVariable2111112113