Book a Demo!
CoCalc Logo Icon
StoreFeaturesDocsShareSupportNewsAboutPoliciesSign UpSign In
ElmerCSC
GitHub Repository: ElmerCSC/elmerfem
Path: blob/devel/elmerice/Tests/Grounded/PROG/bedrock.f90
3206 views
1
SUBROUTINE bedrock( Model,Solver,dt,TransientSimulation )
2
3
!*************************************************************************
4
!
5
! creates a synthetic bedrock variable
6
!
7
!*************************************************************************
8
9
USE DefUtils
10
IMPLICIT NONE
11
12
!-----------------------------------------------------------------------------
13
TYPE(Solver_t) :: Solver
14
TYPE(Model_t) :: Model
15
16
REAL(KIND=dp) :: dt
17
LOGICAL :: TransientSimulation
18
!------------------------------------------------------------------------------
19
! Local variables
20
!------------------------------------------------------------------------------
21
TYPE(Element_t),POINTER :: Element
22
TYPE(Variable_t), POINTER :: PointerToVariable
23
TYPE(Nodes_t), SAVE :: Nodes
24
TYPE(ValueList_t), POINTER :: SolverParams
25
26
INTEGER :: ii, tt, nn, jj, DIM
27
INTEGER, POINTER :: Permutation(:)
28
29
REAL(KIND=dp), POINTER :: VariableValues(:)
30
REAL(KIND=dp) :: x, y, z
31
32
REAL(KIND=dp) :: fbed
33
34
35
!-----------------------------------------------------------------------------
36
37
PointerToVariable => Solver % Variable
38
Permutation => PointerToVariable % Perm
39
VariableValues => PointerToVariable % Values
40
41
DIM = CoordinateSystemDimension()
42
43
SolverParams => GetSolverParams()
44
45
! the bedrock is never changed, so it is filled in the firsttime
46
DO tt = 1, Solver % NumberOfActiveElements
47
Element => GetActiveElement(tt)
48
nn = GetElementNOFNodes()
49
50
CALL GetElementNodes( Nodes )
51
DO ii = 1, nn
52
IF ( Permutation(Element % NodeIndexes(ii)) == 0 ) CYCLE
53
54
x = Model % Nodes % x(Element % NodeIndexes(ii))
55
56
IF (DIM==3) THEN
57
y = Model % Nodes % y(Element % NodeIndexes(ii))
58
VariableValues(Permutation(Element % NodeIndexes(ii))) = fbed(x,y)
59
ELSE IF (DIM==2) THEN
60
VariableValues(Permutation(Element % NodeIndexes(ii))) = fbed(x,0.0_dp)
61
END IF
62
63
END DO
64
65
END DO
66
67
END SUBROUTINE bedrock
68
69