Book a Demo!
CoCalc Logo Icon
StoreFeaturesDocsShareSupportNewsAboutPoliciesSign UpSign In
ElmerCSC
GitHub Repository: ElmerCSC/elmerfem
Path: blob/devel/elmerice/UserFunctions/USF_Damage.F90
3196 views
1
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
2
! USF_Damage.f90
3
! Last modif : 12 December 2014
4
! Computes the evolution of damage and computes the Enhancement factor of the Glen's law
5
! as a function of damage evolution
6
!
7
!
8
! (1) Enhancement Factor
9
! Need some inputs in the sif file.
10
! Parameters:
11
! Glen Exponent
12
!
13
!
14
! (2) SourceDamage
15
! Need some inputs in the sif file.
16
! Parameters:
17
! Damage Enhancement Factor
18
! Damage Parameter sigmath
19
!
20
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
21
22
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
23
!
24
! EnhancementFactor
25
!
26
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
27
28
FUNCTION EnhancementFactor ( Model, nodenumber, D) RESULT(E)
29
USE types
30
USE CoordinateSystems
31
USE SolverUtils
32
USE ElementDescription
33
USE DefUtils
34
IMPLICIT NONE
35
TYPE(Model_t) :: Model
36
TYPE(ValueList_t), POINTER :: Material
37
TYPE(Solver_t), TARGET :: Solver
38
REAL(KIND=dp) :: D, E, n
39
INTEGER :: nodenumber
40
LOGICAL :: FirstTime=.TRUE., GotIt
41
42
SAVE FirstTime, n
43
44
IF (FirstTime) THEN
45
FirstTime = .False.
46
47
Material => GetMaterial()
48
n = GetConstReal( Material, 'Glen Exponent', GotIt )
49
IF (.NOT.GotIt) THEN
50
WRITE(Message,'(A)') 'Variable Glen Exponent not found. &
51
&Setting to 3.0'
52
CALL INFO('Damage EnhancementFactor', Message, level=2)
53
n = 3.0_dp
54
ELSE
55
WRITE(Message,'(A,F10.4)') 'n = ', n
56
CALL INFO('Damage EnhancementFactor', Message, level=2)
57
END IF
58
END IF
59
60
E = (1.0 - D)**(-n)
61
62
! write(*,*) D
63
! write(*,*)'E', E
64
END FUNCTION EnhancementFactor
65
66
67
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
68
!
69
! SourceDamage
70
!
71
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
72
73
FUNCTION SourceDamage (Model, nodenumber, D) RESULT(Source)
74
75
76
USE types
77
USE CoordinateSystems
78
USE SolverUtils
79
USE ElementDescription
80
USE DefUtils
81
USE GeneralUtils
82
IMPLICIT NONE
83
TYPE(Model_t) :: Model
84
REAL (KIND=dp) :: D, Source
85
INTEGER :: nodenumber
86
87
TYPE(Solver_t):: Solver
88
TYPE(ValueList_t), POINTER :: Material, Constants
89
TYPE(Variable_t), POINTER :: StressVariable, FlowVariable, ChiVariable, PSeaDVariable
90
REAL(KIND=dp), POINTER :: StressValues(:), FlowValues(:), ChiValues(:), PSeaDValues(:)
91
INTEGER, POINTER :: StressPerm(:), FlowPerm(:), ChiPerm(:), PSeaDPerm(:)
92
93
INTEGER :: Ind(3,3), DIM, i, j, indice(3), infor
94
REAL (KIND=dp) :: Sig(3,3), SigDev(3,3), EigVect(3,3), EigValues(3),tmp
95
REAL (KIND=dp) :: SigmaI, SigmaII, Chi, B, sigmath, pwater
96
REAL (KIND=DP) :: EI(3),Dumy(1),Work(24), sigmath_var, stress_threshold
97
REAL (KIND=DP) :: u, v, nbrPi, s
98
LOGICAL :: GotIt, FirstTime = .TRUE., Cauchy, UnFoundFatal=.TRUE.
99
CHARACTER*20 :: USF_Name='SourceDamage'
100
101
102
SAVE :: Ind, DIM, sigmath, B
103
SAVE :: FirstTime, Cauchy
104
105
106
IF (FirstTime) THEN
107
FirstTime = .FALSE.
108
DIM = CoordinateSystemDimension()
109
110
DO i=1, 3
111
Ind(i,i) = i
112
END DO
113
Ind(1,2) = 4
114
Ind(2,1) = 4
115
Ind(2,3) = 5
116
Ind(3,2) = 5
117
Ind(3,1) = 6
118
Ind(1,3) = 6
119
120
Material => GetMaterial()
121
!Read the coefficients B and sigmath
122
123
B = GetConstReal( Material, 'Damage Enhancement Factor', GotIt )
124
IF (.NOT.GotIt) THEN
125
CALL FATAL('Damage Source', 'Damage Enhancement Factor B not Found')
126
ELSE
127
WRITE(Message,'(A,F10.4)') 'Damage Enhancement Factor = ', B
128
CALL INFO('Damage Source', Message, level=2)
129
ENDIF
130
131
sigmath = GetConstReal( Material, 'Damage Parameter sigmath', GotIt )
132
IF (.NOT.GotIt) THEN
133
CALL FATAL('Damage Source', 'Damage Parameter Sigmath not Found')
134
ELSE
135
WRITE(Message,'(A,F10.4)') 'Damage Parameter sigmath = ', sigmath
136
CALL INFO('Damage Source', Message, level=2)
137
ENDIF
138
139
! Cauchy or deviatoric stresses ?
140
Cauchy = ListGetLogical( Material , 'Cauchy', Gotit )
141
WRITE(Message,'(A,L1)') 'Cauchy stress tensor computed ? ', Cauchy
142
CALL INFO('Damage Source', Message, level=2)
143
END IF ! FirstTime
144
145
146
! Get the Stress
147
StressVariable => VariableGet( Model % Variables, 'Stress',UnFoundFatal=UnFoundFatal)
148
StressPerm => StressVariable % Perm
149
StressValues => StressVariable % Values
150
151
! Get Chi variable (positive where damage increases)
152
ChiVariable => VariableGet( Model % Variables, 'Chi',UnFoundFatal=UnFoundFatal)
153
ChiPerm => ChiVariable % Perm
154
ChiValues => ChiVariable % Values
155
156
! Get the Sea Damage Pressure
157
PSeaDVariable => VariableGet( Model % Variables, 'PSeaD' )
158
IF ( ASSOCIATED( PSeaDVariable ) ) THEN
159
PSeaDPerm => PSeaDVariable % Perm
160
PSeaDValues => PSeaDVariable % Values
161
ELSE
162
CALL WARN('Damage Source', 'PSeaD not associated, basal pressure not taken into account in damage formation' )
163
CALL WARN('Damage Source', 'Taking default value PSeaD=0.0')
164
END IF
165
166
! Get the variables to compute the hydrostatic pressure
167
FlowVariable => VariableGet( Model % Variables, 'Flow Solution',UnFoundFatal=UnFoundFatal)
168
FlowPerm => FlowVariable % Perm
169
FlowValues => FlowVariable % Values
170
171
Sig = 0.0
172
DO i=1, DIM
173
DO j= 1, DIM
174
Sig(i,j) = &
175
StressValues( 2*DIM *(StressPerm(Nodenumber)-1) + Ind(i,j) )
176
END DO
177
END DO
178
IF (DIM==2) Sig(3,3) = StressValues( 2*DIM *(StressPerm(Nodenumber)-1) + Ind(3,3))
179
180
! S = sigma + p
181
! Need Cauchy Stress and Deviatoric Stress
182
IF (.NOT.Cauchy) THEN ! If Deviatoric Stress is computed, then, get the
183
! Cauchy Stress
184
SigDev = Sig
185
DO i=1,3
186
Sig(i,i) = SigDev(i,i) - FlowValues((DIM+1)*FlowPerm(Nodenumber))
187
END DO
188
ELSE ! If the Cauchy Stress is computed, then get the Deviatoric Stress
189
DO i=1,3
190
SigDev(i,i) = Sig(i,i) + FlowValues((DIM+1)*FlowPerm(Nodenumber))
191
!write(*,*)Sig(i,1), Sig(i,2), Sig(i,3)
192
END DO
193
END IF
194
195
196
! Compute the principal stresses:
197
198
! Get the principal stresses
199
CALL DGEEV('N','N',3,Sig,3,EigValues,EI,Dumy,1,Dumy,1,Work,24,infor )
200
IF (infor.ne.0) &
201
CALL FATAL('Compute EigenValues', 'Failed to compute EigenValues')
202
203
! Get the eigenvectors (if necessary)
204
CALL DGEEV('N','V',3,Sig,3,EigValues,EI,Dumy,1,EigVect,3,Work,24,infor )
205
IF (infor.ne.0) &
206
CALL FATAL('Compute EigenVectors', 'Failed to compute EigenVectors')
207
208
indice = (/(i,i=1,3)/)
209
CALL sortd(3,EigValues,indice)
210
211
SigmaI = EigValues(3)
212
SigmaII = EigValues(2)
213
214
!SigmaI = MAXVAL(EigValues)
215
!write(*,*)'SigI',SigmaI,EigValues
216
nbrPi = 3.141592_dp
217
218
u = EvenRandom()
219
v = EvenRandom()
220
221
! Determination of the stress threshold
222
Constants => GetConstants()
223
s = GetConstReal( Constants, 'Dev Tensile Strength Modifier', GotIt)
224
IF (.NOT.GotIt) THEN
225
CALL FATAL('USF_Damage','No "Dev tensile strength modifier" given, set &
226
to 0.05')
227
END IF
228
229
! Get a normal distribution of mean 0 and std dev "s" using two random numbers
230
! "u" and "v"
231
sigmath_var = ABS(0+s*SQRT(-2.0_dp*LOG((1.0_dp-u)))*COS(2.0_dp*nbrPi*v))
232
233
stress_threshold = sigmath*(1+sigmath_var)
234
235
! Get the Sea pressure at the node
236
237
IF ( ASSOCIATED( PSeaDVariable ) ) THEN
238
pwater = PseaDValues ( PSeaDPerm (nodenumber) )
239
ELSE
240
pwater = 0.0_dp
241
END IF
242
243
! Damage Criterion
244
Chi = 1.0_dp / (1.0_dp - D) * (SigmaI + pwater) - stress_threshold
245
246
! Save Chi in ChiVariable
247
ChiValues(ChiPerm(nodenumber)) = Chi
248
249
! Advection-Reaction Source term :
250
Source = B * MAX(Chi,0.0_dp)
251
252
END FUNCTION SourceDamage
253
254