Book a Demo!
CoCalc Logo Icon
StoreFeaturesDocsShareSupportNewsAboutPoliciesSign UpSign In
ElmerCSC
GitHub Repository: ElmerCSC/elmerfem
Path: blob/devel/elmerice/Tests/DGsolver/PROG/DGtoNodalVariable.f90
3206 views
1
! This Solver is to write a DG variable into a Nodal Variable
2
! There are two solver
3
! the first write the DG exported variable into a 'true' Nodal variable
4
! the second write this 'true' nodal variable into the primary DG variable
5
RECURSIVE SUBROUTINE DGtoNodalVariable1(Model, Solver, Timestep, TransientSimulation)
6
USE DefUtils
7
USE Materialmodels
8
!-----------------------------------------------------------
9
IMPLICIT NONE
10
!------------ external variables ---------------------------
11
TYPE(Model_t) :: Model
12
TYPE(Solver_t), TARGET :: Solver
13
LOGICAL :: TransientSimulation
14
REAL(KIND=dp) :: Timestep
15
!------------ internal variables ---------------------------
16
REAL(KIND=dp) :: z, D
17
INTEGER :: i, j, k, t, n, dummyInt, Active, Indexes(128)
18
LOGICAL :: GotIt,UnFoundFatal
19
TYPE(Element_t), POINTER :: Element
20
TYPE(Mesh_t), POINTER :: Mesh
21
CHARACTER(LEN=MAX_NAME_LEN) :: InName, OutName, SolverName
22
TYPE(ValueList_t), POINTER :: SolverParams
23
TYPE(Variable_t), POINTER :: InSol, OutSol
24
25
SolverName = 'DGtoNodalVariable1'
26
Mesh => GetMesh()
27
n = Mesh % MaxElementNodes
28
29
SolverParams => GetSolverParams()
30
InName = GetString(SolverParams,'Input Variable Name', GotIt)
31
IF (.NOT.GotIt) THEN
32
WRITE(Message,'(a)')'Keyword >Input Variable Name< not found in Solver section'
33
CALL FATAL(SolverName, Message)
34
END IF
35
36
OutName = GetString(SolverParams,'Output Variable Name', GotIt)
37
IF (.NOT.GotIt) THEN
38
WRITE(Message,'(a)')'Keyword >Output Variable Name< not found in Solver section'
39
CALL FATAL(SolverName, Message)
40
END IF
41
42
InSol => VariableGet(Solver % Mesh % Variables,InName,UnFoundFatal=UnFoundFatal)
43
44
OutSol => VariableGet(Solver % Mesh % Variables,OutName,UnFoundFatal=UnFoundFatal)
45
46
Active = GetNOFActive()
47
DO t = 1, Active
48
Element => GetActiveElement( t )
49
n = GetElementNOfNodes( Element )
50
dummyInt = GetElementDOFs( Indexes )
51
DO i=1,n
52
j = Indexes(i)
53
OutSol % Values(OutSol % Perm(j)) = InSol % Values(InSOl % Perm(j))
54
END DO
55
END DO
56
END SUBROUTINE DGtoNodalVariable1
57
58
RECURSIVE SUBROUTINE DGtoNodalVariable2(Model, Solver, Timestep, TransientSimulation)
59
USE DefUtils
60
USE Materialmodels
61
!-----------------------------------------------------------
62
IMPLICIT NONE
63
!------------ external variables ---------------------------
64
TYPE(Model_t) :: Model
65
TYPE(Solver_t), TARGET :: Solver
66
LOGICAL :: TransientSimulation
67
REAL(KIND=dp) :: Timestep
68
!------------ internal variables ---------------------------
69
REAL(KIND=dp) :: z, D
70
INTEGER :: i, j, k, t, n, dummyInt, Active, Indexes(128)
71
LOGICAL :: GotIt,UnFoundFatal
72
TYPE(Element_t), POINTER :: Element
73
TYPE(Mesh_t), POINTER :: Mesh
74
CHARACTER(LEN=MAX_NAME_LEN) :: InName, OutName, SolverName
75
TYPE(ValueList_t), POINTER :: SolverParams
76
TYPE(Variable_t), POINTER :: OutSol
77
REAL(KIND=dp), ALLOCATABLE :: InValues(:)
78
79
SolverName = 'DGtoNodalVariable2'
80
Mesh => GetMesh()
81
n = Mesh % MaxElementNodes
82
ALLOCATE(InValues(n))
83
84
SolverParams => GetSolverParams()
85
InName = GetString(SolverParams,'Input Variable Name', GotIt)
86
IF (.NOT.GotIt) THEN
87
WRITE(Message,'(a)')'Keyword >Input Variable Name< not found in Solver section'
88
CALL FATAL(SolverName, Message)
89
END IF
90
91
OutName = GetString(SolverParams,'Output Variable Name', GotIt)
92
IF (.NOT.GotIt) THEN
93
WRITE(Message,'(a)')'Keyword >Output Variable Name< not found in Solver section'
94
CALL FATAL(SolverName, Message)
95
END IF
96
97
OutSol => VariableGet(Solver % Mesh % Variables,OutName,UnFoundFatal=UnFoundFatal)
98
99
Active = GetNOFActive()
100
DO t = 1, Active
101
Element => GetActiveElement( t )
102
n = GetElementNOfNodes( Element )
103
dummyInt = GetElementDOFs( Indexes )
104
CALL GetScalarLocalSolution(InValues,TRIM(InName))
105
DO i=1,n
106
j = Indexes(i)
107
OutSol % Values(OutSol % Perm(j)) = InValues(i)
108
END DO
109
END DO
110
DEALLOCATE(InValues)
111
END SUBROUTINE DGtoNodalVariable2
112
113