Book a Demo!
CoCalc Logo Icon
StoreFeaturesDocsShareSupportNewsAboutPoliciesSign UpSign In
ElmerCSC
GitHub Repository: ElmerCSC/elmerfem
Path: blob/devel/elmerice/Tests/DGsolver/PROG/InitializeDGVariable.f90
3206 views
1
! This Solver initialize the two DG variable (have to be run to time)
2
RECURSIVE SUBROUTINE InitializeDGVariable(Model, Solver, Timestep, TransientSimulation)
3
USE DefUtils
4
USE Materialmodels
5
!-----------------------------------------------------------
6
IMPLICIT NONE
7
!------------ external variables ---------------------------
8
TYPE(Model_t) :: Model
9
TYPE(Solver_t), TARGET :: Solver
10
LOGICAL :: TransientSimulation
11
REAL(KIND=dp) :: Timestep
12
!------------ internal variables ---------------------------
13
REAL(KIND=dp) :: z, D
14
INTEGER :: i, j, k, t, n, dummyInt, Active, Indexes(128)
15
LOGICAL :: GotIt,UnFoundFatal
16
TYPE(Element_t), POINTER :: Element
17
TYPE(Mesh_t), POINTER :: Mesh
18
TYPE(Nodes_t) :: ElementNodes
19
CHARACTER(LEN=MAX_NAME_LEN) :: VariableName, SolverName
20
TYPE(ValueList_t), POINTER :: SolverParams
21
TYPE(Variable_t), POINTER :: VarSol
22
REAL(KIND=dp), ALLOCATABLE :: Depth(:)
23
24
SolverName = 'InitializeDGVariable'
25
Mesh => GetMesh()
26
n = Mesh % MaxElementNodes
27
ALLOCATE(ElementNodes % x(n), ElementNodes % y(n), ElementNodes % z(n), &
28
Depth(n))
29
30
SolverParams => GetSolverParams()
31
VariableName = GetString(SolverParams,'Initialized Variable Name', GotIt)
32
IF (.NOT.GotIt) THEN
33
WRITE(Message,'(a)')'Keyword >Initialized Variable Name< not found in Solver section'
34
CALL FATAL(SolverName, Message)
35
END IF
36
37
VarSol => VariableGet(Solver % Mesh % Variables,VariableName,UnFoundFatal=UnFoundFatal)
38
39
Active = GetNOFActive()
40
DO t = 1, Active
41
Element => GetActiveElement( t )
42
n = GetElementNOfNodes( Element )
43
dummyInt = GetElementDOFs( Indexes )
44
CALL GetElementNodes( ElementNodes )
45
! Non DG other variable should be read like this
46
! Don't use their perm and the j indexes as it will be wrong
47
! when the solver is called for a DG variable
48
CALL GetScalarLocalSolution(Depth,'Depth')
49
DO i=1,n
50
j = Indexes(i)
51
z = ElementNodes % z(i)
52
D = Depth(i)
53
VarSol % Values(VarSol % Perm(j)) = 1.0_dp - 0.6_dp*z/100.0
54
write(*,*)t,i,j,k, z+D
55
56
END DO
57
END DO
58
59
DEALLOCATE(ElementNodes % x, ElementNodes % y, ElementNodes % z, Depth)
60
END SUBROUTINE InitializeDGVariable
61
62