OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
hm_read_fail_syazwan.F
Go to the documentation of this file.
1Copyright> OpenRadioss
2Copyright> Copyright (C) 1986-2025 Altair Engineering Inc.
3Copyright>
4Copyright> This program is free software: you can redistribute it and/or modify
5Copyright> it under the terms of the GNU Affero General Public License as published by
6Copyright> the Free Software Foundation, either version 3 of the License, or
7Copyright> (at your option) any later version.
8Copyright>
9Copyright> This program is distributed in the hope that it will be useful,
10Copyright> but WITHOUT ANY WARRANTY; without even the implied warranty of
11Copyright> MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
12Copyright> GNU Affero General Public License for more details.
13Copyright>
14Copyright> You should have received a copy of the GNU Affero General Public License
15Copyright> along with this program. If not, see <https://www.gnu.org/licenses/>.
16Copyright>
17Copyright>
18Copyright> Commercial Alternative: Altair Radioss Software
19Copyright>
20Copyright> As an alternative to this open-source version, Altair also offers Altair Radioss
21Copyright> software under a commercial license. Contact Altair to discuss further if the
22Copyright> commercial version may interest you: https://www.altair.com/radioss/.
23!||====================================================================
24!|| hm_read_fail_syazwan ../starter/source/materials/fail/syazwan/hm_read_fail_syazwan.f
25!||--- called by ------------------------------------------------------
26!|| hm_read_fail ../starter/source/materials/fail/hm_read_fail.F
27!||--- calls -----------------------------------------------------
28!|| ancmsg ../starter/source/output/message/message.F
29!|| hm_get_floatv ../starter/source/devtools/hm_reader/hm_get_floatv.F
30!|| hm_get_floatv_dim ../starter/source/devtools/hm_reader/hm_get_floatv_dim.F
31!|| hm_get_intv ../starter/source/devtools/hm_reader/hm_get_intv.f
32!|| hm_option_is_encrypted ../starter/source/devtools/hm_reader/hm_option_is_encrypted.F
33!||--- uses -----------------------------------------------------
34!|| hm_option_read_mod ../starter/share/modules1/hm_option_read_mod.F
35!|| message_mod ../starter/share/message_module/message_mod.F
36!|| submodel_mod ../starter/share/modules1/submodel_mod.F
37!||====================================================================
39 . FAIL ,MAT_ID ,FAIL_ID ,IRUPT ,
40 . TITR ,LSUBMODEL,UNITAB )
41C-----------------------------------------------
42c ROUTINE DESCRIPTION :
43c Syazwan failure model
44C-----------------------------------------------
45C M o d u l e s
46C-----------------------------------------------
47 USE fail_param_mod
48 USE unitab_mod
49 USE message_mod
50 USE submodel_mod
52C-----------------------------------------------
53C I m p l i c i t T y p e s
54C-----------------------------------------------
55#include "implicit_f.inc"
56C----------+---------+---+---+--------------------------------------------
57C C o m m o n B l o c k s
58C----------+---------+---+---+--------------------------------------------
59#include "units_c.inc"
60C-----------------------------------------------
61C D u m m y A r g u m e n t s
62C-----------------------------------------------
63 INTEGER ,INTENT(IN) :: FAIL_ID ! failure model ID
64 INTEGER ,INTENT(IN) :: MAT_ID ! material law ID
65 INTEGER ,INTENT(IN) :: IRUPT ! failure model type number
66 CHARACTER ,INTENT(IN) :: TITR*500 ! material model title
67 TYPE(UNIT_TYPE_) ,INTENT(IN) :: UNITAB ! table of input units
68 TYPE(submodel_data),INTENT(IN) :: LSUBMODEL(*) ! submodel table
69 TYPE(fail_param_) ,INTENT(INOUT) :: FAIL ! failure model data structure
70C-----------------------------------------------
71C L o c a l V a r i a b l e s
72C-----------------------------------------------
73 my_real c1,c2,c3,c4,c5,c6
74 my_real dam_sf,max_dam,n_val,softexp
75 my_real ref_len,ref_siz_unit,reg_scale
76 my_real eps_bicomp,eps_comp,eps_cisail,eps_tens,
77 . eps_plane,eps_bitrac,epfmin,epf_comp,
78 . epf_shear,epf_tens,epf_plstrn,epf_biax
79 my_real triax,lodep,cos3theta,epsfail
80 DOUBLE PRECISION :: EPF(6),MAT(6,6)
81 INTEGER ICARD,IFORM,DINIT,INST,REG_FUNC,INFO,IPIV(6),I,FAILIP
82 LOGICAL :: IS_AVAILABLE,IS_ENCRYPTED,NEGATIVE
83C-----------------------------------------------
84 is_encrypted = .false.
85 is_available = .false.
86C--------------------------------------------------
87C EXTRACT DATA (IS OPTION CRYPTED)
88C--------------------------------------------------
89 CALL hm_option_is_encrypted(is_encrypted)
90C--------------------------------------------------
91C EXTRACT DATAS
92C--------------------------------------------------
93 ! 1st Line : failure criterion parameters
94 CALL hm_get_intv ('ICARD' ,icard ,is_available,lsubmodel)
95 IF (icard <= 0) icard = 1
96 icard = min(icard,2)
97 CALL hm_get_floatv ('EPFMIN' ,epfmin ,is_available,lsubmodel,unitab)
98 CALL hm_get_intv ('FAILIP' ,failip ,is_available,lsubmodel)
99 ! 2nd Line : failure criterion parameters
100 IF (icard == 1) THEN
101 CALL hm_get_floatv ('C1' ,c1 ,is_available,lsubmodel,unitab)
102 CALL hm_get_floatv ('C2' ,c2 ,is_available,lsubmodel,unitab)
103 CALL hm_get_floatv ('C3' ,c3 ,is_available,lsubmodel,unitab)
104 CALL hm_get_floatv ('C4' ,c4 ,is_available,lsubmodel,unitab)
105 CALL hm_get_floatv ('C5' ,c5 ,is_available,lsubmodel,unitab)
106 CALL hm_get_floatv ('C6' ,c6 ,is_available,lsubmodel,unitab)
107 ELSE
108 CALL hm_get_floatv ('EPF_COMP' ,epf_comp ,is_available,lsubmodel,unitab)
109 CALL hm_get_floatv ('EPF_SHEAR' ,epf_shear ,is_available,lsubmodel,unitab)
110 CALL hm_get_floatv ('EPF_TENS' ,epf_tens ,is_available,lsubmodel,unitab)
111 CALL hm_get_floatv ('EPF_PLSTRN',epf_plstrn,is_available,lsubmodel,unitab)
112 CALL hm_get_floatv ('EPF_BIAX' ,epf_biax ,is_available,lsubmodel,unitab)
113 ENDIF
114 ! 3rd Line : Damage initialization control
115 CALL hm_get_intv ('DINIT' ,dinit ,is_available,lsubmodel)
116 CALL hm_get_floatv ('DAM_SF' ,dam_sf ,is_available,lsubmodel,unitab)
117 CALL hm_get_floatv ('MAX_DAM' ,max_dam ,is_available,lsubmodel,unitab)
118 ! 4th Line : Instability + stress softening
119 CALL hm_get_intv ('INST' ,inst ,is_available,lsubmodel)
120 CALL hm_get_intv ('IFORM' ,iform ,is_available,lsubmodel)
121 CALL hm_get_floatv ('N_VAL' ,n_val ,is_available,lsubmodel,unitab)
122 CALL hm_get_floatv ('SOFTEXP' ,softexp ,is_available,lsubmodel,unitab)
123 ! 5th Line : Element size regularization control
124 CALL hm_get_intv ('REG_FUNC' ,reg_func,is_available,lsubmodel)
125 CALL hm_get_floatv ('REF_LEN' ,ref_len ,is_available,lsubmodel,unitab)
126 IF (reg_func > 0 .AND. ref_len == zero) THEN
127 CALL hm_get_floatv_dim('REF_LEN',ref_siz_unit,is_available, lsubmodel, unitab)
128 ref_len = one*ref_siz_unit
129 ENDIF
130 CALL hm_get_floatv ('REG_SCALE',reg_scale,is_available,lsubmodel,unitab)
131 IF (reg_func > 0 .AND. reg_scale == zero) reg_scale = one
132C--------------------------------------------------
133C COMPUTE C PARAMETERS IF ICARD = 2
134C--------------------------------------------------
135 IF (icard == 2) THEN
136 ! Filling failure strain vector
137 epf(1) = zero ! IMPOSE MINIMUM VALUE IN PLANE STRAIN
138 epf(2) = epf_comp ! COMP
139 epf(3) = epf_shear ! CISAIL
140 epf(4) = epf_tens ! TENS
141 epf(5) = epf_plstrn ! PLANE STRAIN
142 epf(6) = epf_biax ! BITRAC
143
144 ! Filling the linear system Matrix
145 mat(1:6,1:6) = zero
146 ! -> Impose minimum value in plane strain
147 mat(1,1) = zero
148 mat(1,2) = one
149 mat(1,3) = -18.0d0/pi
150 mat(1,4) = two/sqrt(three)
151 mat(1,5) = zero
152 mat(1,6) = -18.0d0/(pi*sqrt(three))
153 ! -> Compression
154 mat(2,1) = one
155 mat(2,2) = -third
156 mat(2,3) = -one
157 mat(2,4) = one/nine
158 mat(2,5) = one
159 mat(2,6) = third
160 ! -> Shear
161 mat(3,1) = one
162 mat(5,2) = zero
163 mat(5,3) = zero
164 mat(5,4) = zero
165 mat(5,5) = zero
166 mat(5,6) = zero
167 ! -> Traction
168 mat(4,1) = one
169 mat(4,2) = third
170 mat(4,3) = one
171 mat(4,4) = one/nine
172 mat(4,5) = one
173 mat(4,6) = third
174 ! -> Plane strain
175 mat(5,1) = one
176 mat(5,2) = one/sqrt(three)
177 mat(5,3) = zero
178 mat(5,4) = third
179 mat(5,5) = zero
180 mat(5,6) = zero
181 ! -> Bitraction
182 mat(6,1) = one
183 mat(6,2) = two_third
184 mat(6,3) = -one
185 mat(6,4) = four/nine
186 mat(6,5) = one
187 mat(6,6) = -two_third
188c
189 ! Solve linear system
190#ifndef WITHOUT_LINALG
191 CALL dgesv(6, 1, mat, 6, ipiv, epf, 6, info)
192#else
193 WRITE(6,*) "Error: Blas/Lapack required"
194#endif
195c
196 ! Copy C parameters
197 c1 = epf(1)
198 c2 = epf(2)
199 c3 = epf(3)
200 c4 = epf(4)
201 c5 = epf(5)
202 c6 = epf(6)
203c
204 ENDIF
205C--------------------------------------------------
206C CHECK VALUES
207C--------------------------------------------------
208 ! Formulation for instability strain
209 IF (iform <= 0) iform = 1
210 iform = min(iform,2)
211 ! Damage initialization scale factor
212 dam_sf = max(dam_sf,zero)
213 IF (dam_sf == zero) dam_sf = one
214 ! Maximal damage for initialization
215 IF (max_dam == zero) max_dam = one
216 max_dam = min(max_dam,one)
217 max_dam = max(max_dam,zero)
218 ! Plastic strain at instability value (N_VAL)
219 IF(inst==1 .AND. n_val==zero) THEN
220 n_val = fourth
221 ENDIF
222 ! Softening exponent
223 IF (softexp == zero) softexp = one
224 softexp = max(em06,softexp)
225 ! Minimum plastic strain at failure
226 epfmin = max(zero,epfmin)
227 ! Check if criterion takes negative values
228 triax = -two_third
229 negative = .false.
230 DO i = 1,1001
231 cos3theta = -half*twenty7*triax*(triax**2 - third)
232 IF (cos3theta < -one ) cos3theta = -one
233 IF (cos3theta > one ) cos3theta = one
234 lodep = one - two*acos(cos3theta)/pi
235 epsfail = c1 + c2*triax + c3*lodep + c4*(triax**2) +
236 . c5*(lodep**2) + c6*triax*lodep
237 IF (epsfail <= epfmin) THEN
238 negative = .true.
239 EXIT
240 ENDIF
241 triax = triax + (two*two_third)/ep03
242 ENDDO
243 IF (negative) THEN
244 CALL ancmsg(msgid=2091, msgtype=msgwarning, anmode=aninfo_blind_1,
245 . i1=mat_id,
246 . c1=titr,
247 . r1=epfmin)
248 ENDIF
249 ! Default value for NUMFIP
250 IF (failip == 0) failip = 1
251C--------------------------------------------------
252C SAVE PARAMETERS
253C--------------------------------------------------
254 fail%KEYWORD = 'SYAZWAN'
255 fail%IRUPT = irupt
256 fail%FAIL_ID = fail_id
257 fail%NUPARAM = 17
258 fail%NIPARAM = 0
259 fail%NUVAR = 3
260 fail%NFUNC = 1
261 fail%NTABLE = 0
262 fail%NMOD = 0
263c
264 ALLOCATE (fail%UPARAM(fail%NUPARAM))
265 ALLOCATE (fail%IPARAM(fail%NIPARAM))
266 ALLOCATE (fail%IFUNC (fail%NFUNC))
267 ALLOCATE (fail%TABLE (fail%NTABLE))
268c
269 fail%IFUNC(1) = reg_func
270c
271 fail%UPARAM(1) = c1
272 fail%UPARAM(2) = c2
273 fail%UPARAM(3) = c3
274 fail%UPARAM(4) = c4
275 fail%UPARAM(5) = c5
276 fail%UPARAM(6) = c6
277 fail%UPARAM(7) = iform
278 fail%UPARAM(8) = dinit
279 fail%UPARAM(9) = dam_sf
280 fail%UPARAM(10) = max_dam
281 fail%UPARAM(11) = inst
282 fail%UPARAM(12) = n_val
283 fail%UPARAM(13) = softexp
284 fail%UPARAM(14) = ref_len
285 fail%UPARAM(15) = reg_scale
286 fail%UPARAM(16) = epfmin
287 fail%UPARAM(17) = failip
288C--------------------------------------------------
289C PRINT OUT PARAMETERS
290C--------------------------------------------------
291 IF (is_encrypted) THEN
292 WRITE(iout,'(5X,A,//)')'CONFIDENTIAL DATA'
293 ELSE
294 WRITE(iout,1000)
295 IF (icard == 2) THEN
296 WRITE(iout,1100) epf_comp,epf_shear,epf_tens,
297 . epf_plstrn,epf_biax,
298 . c1,c2,c3,c4,c5,c6
299 ELSE
300 WRITE(iout,1200) c1,c2,c3,c4,c5,c6
301 ENDIF
302 WRITE(iout,1300) epfmin,failip
303 WRITE(iout,1400) dinit,dam_sf,max_dam
304 WRITE(iout,1500) inst,iform,n_val,softexp
305 IF (reg_func > 0) THEN
306 WRITE(iout,1600) reg_func,ref_len,reg_scale
307 ENDIF
308 ENDIF
309C---
310C
311 1000 FORMAT(
312 & 5x,' --------------------------------------------------------',/,
313 & 5x,' SYAZWAN FAILURE CRITERION ',/,
314 & 5x,' --------------------------------------------------------',/)
315 1100 FORMAT(
316 & 5x,'PLAST. STRAIN AT FAILURE IN UNIAXIAL COMP . . . . . . . =',1pg20.13/
317 & 5x,'PLAST. STRAIN AT FAILURE IN SHEAR . . . . . . . . . . . =',1pg20.13/
318 & 5x,'PLAST. STRAIN AT FAILURE IN UNIAXIAL TENS . . . . . . . =',1pg20.13/
319 & 5x,'PLAST. STRAIN AT FAILURE IN PLANE STRAIN. . . . . . . . =',1pg20.13/
320 & 5x,'PLAST. STRAIN AT FAILURE IN BIAXIAL TENS. . . . . . . . =',1pg20.13/
321 & 5x,' ',/,
322 & 5x,'CORRESPONDING C PARAMETERS: ',/,
323 & 5x,'1ST FAILURE PARAMETER (C1). . . . . . . . . . . . . . . =',1pg20.13/
324 & 5x,'2ND FAILURE PARAMETER (C2). . . . . . . . . . . . . . . =',1pg20.13/
325 & 5x,'3RD FAILURE PARAMETER (C3). . . . . . . . . . . . . . . =',1pg20.13/
326 & 5x,'4TH FAILURE PARAMETER (C4). . . . . . . . . . . . . . . =',1pg20.13/
327 & 5x,'5TH FAILURE PARAMETER (C5). . . . . . . . . . . . . . . =',1pg20.13/
328 & 5x,'6TH FAILURE PARAMETER (C6). . . . . . . . . . . . . . . =',1pg20.13/)
329 1200 FORMAT(
330 & 5x,'1ST FAILURE PARAMETER (C1). . . . . . . . . . . . . . . =',1pg20.13/
331 & 5x,'2ND FAILURE PARAMETER (C2). . . . . . . . . . . . . . . =',1pg20.13/
332 & 5x,'3RD FAILURE PARAMETER (C3). . . . . . . . . . . . . . . =',1pg20.13/
333 & 5x,'4th failure parameter(c4). . . . . . . . . . . . . . . =',1PG20.13/
334 & 5X,'5th failure parameter(c5). . . . . . . . . . . . . . . =',1PG20.13/
335 & 5X,'6th failure parameter(c6). . . . . . . . . . . . . . . =',1PG20.13/)
336 1300 FORMAT(
337 & 5X,'minimum plastic strain at failure(epfmin) . . . . . . =',1PG20.13/
338 & 5X,'num. of failed intg. pts. prior to solid elm. deletion. =',I10/)
339 1400 FORMAT(
340 & 5X,'damage variable initialization flag(dinit) . . . . . . =',I10/,
341 & 5X,' dinit = 0: no damage initialization ',/,
342 & 5X,' dinit = 1: damage initialization from strain tensor ',/,
343 & 5X,'damage initialization scale factor. . . . . . . . . . . =',1PG20.13/
344 & 5X,'damage initialization maximal VALUE . . . . . . . . . . =',1PG20.13/)
345 1500 FORMAT(
346 & 5X,'instability flag(inst) . . . . . . . . . . . . . . . . =',I10/,
347 & 5X,' inst = 0: no necking instability ',/,
348 & 5X,' inst = 1: necking instability activated ',/,
349 & 5X,'instability formulation flag(iform) . . . . . . . . . =',I10/,
350 & 5X,' iform = 1: incremental formulation(default) ',/,
351 & 5X,' iform = 2: direct formulation ',/,
352 & 5X,"HOLLOMON's law n VALUE . . . . . . . . . . . . . . . . =",1PG20.13/
353 & 5X,'STRESS SOFTENING EXPONENT (SOFTEXP) . . . . . . . . . . =',1PG20.13/)
354 1600 FORMAT(
355 & 5X,'ELEMENT SIZE SCALING FUNCTION ID . . . . . . . . . . . .=',I10/
356 & 5X,' REFERENCE ELEMENT SIZE . . . . . . . . . . . . . . .=',1PG20.13/
357 & 5X,' SCALE FACTOR . . . . . . . . . . . . . . . . . . . .=',1PG20.13/)
358
359 END
#define my_real
Definition cppsort.cpp:32
subroutine dgesv(n, nrhs, a, lda, ipiv, b, ldb, info)
DGESV computes the solution to system of linear equations A * X = B for GE matrices
Definition dgesv.f:122
subroutine hm_get_floatv(name, rval, is_available, lsubmodel, unitab)
subroutine hm_get_floatv_dim(name, dim_fac, is_available, lsubmodel, unitab)
subroutine hm_get_intv(name, ival, is_available, lsubmodel)
subroutine hm_option_is_encrypted(is_encrypted)
subroutine hm_read_fail_syazwan(fail, mat_id, fail_id, irupt, titr, lsubmodel, unitab)
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889
program starter
Definition starter.F:39