Book a Demo!
CoCalc Logo Icon
StoreFeaturesDocsShareSupportNewsAboutPoliciesSign UpSign In
ElmerCSC
GitHub Repository: ElmerCSC/elmerfem
Path: blob/devel/elmerice/Solvers/GetHydrostaticLoads.F90
3203 views
1
!/*****************************************************************************/
2
! *
3
! * Elmer/Ice, a glaciological add-on to Elmer
4
! * http://elmerice.elmerfem.org
5
! *
6
! *
7
! * This program is free software; you can redistribute it and/or
8
! * modify it under the terms of the GNU General Public License
9
! * as published by the Free Software Foundation; either version 2
10
! * of the License, or (at your option) any later version.
11
! *
12
! * This program is distributed in the hope that it will be useful,
13
! * but WITHOUT ANY WARRANTY; without even the implied warranty of
14
! * MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
15
! * GNU General Public License for more details.
16
! *
17
! * You should have received a copy of the GNU General Public License
18
! * along with this program (in file fem/GPL-2); if not, write to the
19
! * Free Software Foundation, Inc., 51 Franklin Street, Fifth Floor,
20
! * Boston, MA 02110-1301, USA.
21
! *
22
! *****************************************************************************/
23
! ******************************************************************************
24
! *
25
! * Authors: Olivier Gagliardini, Ga¨el Durand, Mondher Chekki
26
! * Email:
27
! * Web: http://elmerice.elmerfem.org
28
! *
29
! * Original Date:
30
! *
31
! *****************************************************************************
32
!> Computes nodes surface loads from surface pressure
33
SUBROUTINE GetHydrostaticLoads( Model,Solver,dt,TransientSimulation )
34
35
!------------------------------------------------------------------------------
36
!******************************************************************************
37
!
38
!
39
! TODO: switch y and z as DIM=3
40
!
41
! ARGUMENTS:
42
!
43
! TYPE(Model_t) :: Model,
44
! INPUT: All model information (mesh, materials, BCs, etc...)
45
!
46
! TYPE(Solver_t) :: Solver
47
! INPUT: Linear & nonlinear equation solver options
48
!
49
! REAL(KIND=dp) :: dt,
50
! INPUT: Timestep size for time dependent simulations
51
!
52
! LOGICAL :: TransientSimulation
53
! INPUT: Steady state or transient simulation
54
!
55
!******************************************************************************
56
USE DefUtils
57
USE ElmerIceUtils
58
59
IMPLICIT NONE
60
!------------------------------------------------------------------------------
61
TYPE(Solver_t) :: Solver
62
TYPE(Model_t) :: Model
63
64
REAL(KIND=dp) :: dt
65
LOGICAL :: TransientSimulation
66
!------------------------------------------------------------------------------
67
! Local variables
68
!------------------------------------------------------------------------------
69
TYPE(Element_t),POINTER :: Element
70
TYPE(ValueList_t), POINTER :: BC
71
TYPE(Variable_t), POINTER :: PointerToVariable
72
TYPE(Solver_t), POINTER :: PointerToSolver
73
TYPE(Nodes_t), SAVE :: Nodes
74
TYPE(GaussIntegrationPoints_t) :: IP
75
76
LOGICAL :: AllocationsDone = .FALSE., GotIt, stat, Active
77
78
INTEGER :: i, j, n, m, t, p, Nn, istat, DIM, jdim
79
INTEGER, POINTER :: Permutation(:)
80
81
REAL(KIND=dp), POINTER :: VariableValues(:)
82
REAL(KIND=dp) :: Norm, Normal(3), PwVector(3), pwi, s
83
REAL(KIND=dp) :: detJ
84
85
REAL(KIND=dp), ALLOCATABLE :: pwt(:), Basis(:), dBasisdx(:,:), &
86
ddBasisddx(:,:,:)
87
88
CHARACTER(LEN=MAX_NAME_LEN) :: VarName
89
CHARACTER(LEN=MAX_NAME_LEN),PARAMETER :: SolverName='GetHydrostaticLoads'
90
91
SAVE AllocationsDone, DIM, pwt
92
SAVE Basis, dBasisdx, ddBasisddx
93
94
!------------------------------------------------------------------------------
95
96
PointerToVariable => Solver % Variable
97
IF (.NOT.ASSOCIATED(PointerToVariable)) &
98
CALL FATAL(SolverName,"Variable not associated")
99
Permutation => PointerToVariable % Perm
100
VariableValues => PointerToVariable % Values
101
102
Active = ANY(Permutation > 0)
103
104
!--------------------------------------------------------------
105
!Allocate some permanent storage, this is done first time only:
106
!--------------------------------------------------------------
107
108
IF ( (.NOT. AllocationsDone) .OR. Solver % MeshChanged ) THEN
109
DIM = CoordinateSystemDimension()
110
n = Solver % Mesh % MaxElementNodes ! just big enough for elemental arrays
111
m = Model % Mesh % NumberOfNodes
112
IF (AllocationsDone) DEALLOCATE(pwt, Basis, dBasisdx, ddBasisddx)
113
114
ALLOCATE(pwt(n), Basis(n), dBasisdx(n,3), ddBasisddx(n,3,3), STAT=istat )
115
116
IF ( istat /= 0 ) THEN
117
CALL FATAL( SolverName, 'Memory allocation error.' )
118
END IF
119
120
AllocationsDone = .TRUE.
121
CALL INFO( SolverName, 'Memory allocation done.',Level=1 )
122
123
END IF
124
125
!--------------------------------------------
126
! Calculate the water force for each elements
127
!--------------------------------------------
128
129
VariableValues = 0.0_dp
130
131
DO t = Model % Mesh % NumberOfBulkElements+1,&
132
Model % Mesh % NumberOfBulkElements + Model % Mesh % NumberOfBoundaryElements
133
Element => Model % Mesh % Elements(t)
134
IF (.NOT.ASSOCIATED(Element)) THEN
135
WRITE(Message,*) 'Element no. ', t,' not associated'
136
CALL FATAL(SolverName,Message)
137
END IF
138
Model % CurrentElement => Element
139
140
IF (ParEnv % myPe .NE. Element % partIndex) CYCLE
141
n = GetElementNOFNodes( Element )
142
143
!Does this element contribute to any basal nodes?
144
IF(.NOT. ANY(Permutation(Element % NodeIndexes(1:n)) > 0)) CYCLE
145
146
BC => GetBC( Element )
147
IF (.NOT.ASSOCIATED(BC)) CYCLE
148
149
pwt(1:n) = -1.0 * ListGetReal(BC, 'External Pressure', n, &
150
Element % NodeIndexes , GotIt)
151
152
!Is there an external pressure to consider?
153
IF(.NOT. GotIt) CYCLE
154
IF(ALL(pwt(1:n) == 0.0)) CYCLE
155
156
! Integration
157
!
158
CALL GetElementNodes( Nodes, Element )
159
IP = GaussPoints( Element )
160
DO p = 1, IP % n
161
162
stat = ElementInfo( Element, Nodes, IP % U(p), IP % V(p), &
163
IP % W(p), detJ, Basis, dBasisdx, ddBasisddx, .FALSE.)
164
s = detJ * IP % S(p)
165
166
Normal = NormalVector( Element, Nodes, IP % U(p), IP % V(p), .TRUE.)
167
!
168
! Value of pwt at integration point
169
!
170
pwi = SUM(pwt(1:n)*Basis(1:n))
171
!
172
! Compute pw_x, pw_y, pw_z
173
!
174
PwVector(1:DIM) = pwi * Normal(1:DIM)
175
176
DO i = 1, n
177
Nn = Permutation(Element % NodeIndexes(i))
178
IF(Nn <= 0) CYCLE
179
DO j = 1, DIM
180
VariableValues(DIM*(Nn-1)+j) = VariableValues(DIM*(Nn-1)+j) + PwVector(j) * s * Basis(i)
181
END DO
182
END DO
183
184
END DO
185
186
END DO
187
188
IF(Active .NEQV. ASSOCIATED(Solver % Matrix)) CALL Fatal(SolverName, &
189
"Inconsistency between allocation of matrix and number of active nodes")
190
191
IF(Active) THEN
192
DO jdim=1, DIM
193
IF (DIM > 1) THEN
194
VarName=ComponentNameStr( Solver % Variable % Name, jdim )
195
ELSE
196
VarName=GetVarName(Solver % Variable)
197
ENDIF
198
IF (jdim .eq. 1 ) THEN
199
IF ( ParEnv % PEs >1 ) CALL ParallelSumVector( Solver % Matrix, VariableValues)
200
END IF
201
!------------------------------------------------------------------------------
202
! Update Periodic Nodes
203
!------------------------------------------------------------------------------
204
CALL UpdatePeriodicNodes(Model, Solver, VarName, PointerToVariable, jdim)
205
ENDDO
206
END IF
207
208
CALL INFO(SolverName, 'End', level=3)
209
210
!------------------------------------------------------------------------------
211
END SUBROUTINE GetHydrostaticLoads
212
!------------------------------------------------------------------------------
213
214
215
216
217