OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
law42_upd.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!|| law42_upd ../starter/source/materials/mat/mat042/law42_upd.F
25!||--- called by ------------------------------------------------------
26!|| updmat ../starter/source/materials/updmat.F
27!||--- uses -----------------------------------------------------
28!|| message_mod ../starter/share/message_module/message_mod.F
29!|| table_mod ../starter/share/modules1/table_mod.F
30!||====================================================================
31 SUBROUTINE law42_upd(MAT_PARAM,IOUT,TITR ,MAT_ID,PM, GAMA_INF)
32C-----------------------------------------------
33C M o d u l e s
34C-----------------------------------------------
35 USE message_mod
36 USE table_mod
38 USE matparam_def_mod
39C-----------------------------------------------
40C I m p l i c i t T y p e s
41C-----------------------------------------------
42#include "implicit_f.inc"
43C-----------------------------------------------
44C C o m m o n B l o c k s
45C-----------------------------------------------
46#include "param_c.inc"
47C-----------------------------------------------
48C D u m m y A r g u m e n t s
49C-----------------------------------------------
50 CHARACTER(LEN=NCHARTITLE) :: TITR
51 INTEGER MAT_ID,IOUT
52 my_real, DIMENSION(NPROPM) ,INTENT(INOUT) :: pm
53 my_real , INTENT(IN) :: gama_inf
54 TYPE(matparam_struct_) ,INTENT(INOUT) :: MAT_PARAM
55C-----------------------------------------------
56C L o c a l V a r i a b l e s
57C-----------------------------------------------
58 INTEGER I,K,NDATA,INDX,NORDER
59 my_real :: mu(10),al(10)
60 my_real :: lam_min,lam_max,strain_min,strain_max,
61 . d11,d22,d12,lam1,lam2,lam3,lam12,invd1,invd2,gs,bulk,young,nu
62 my_real , DIMENSION(:), ALLOCATABLE :: stress,stretch
63 INTEGER , DIMENSION(:), ALLOCATABLE :: ITAB_ON_A,INDEX
64
65C=======================================================================
66! CHECK the material stability (Drucker proguer conditions)
67!====================================================================
68 ndata = 10000 ! La=0.1,10, EM3!!
69 lam_min = em3
70 lam_max = ten
71
72 norder = mat_param%IPARAM(1) ! Order of Ogden model
73C
74 IF (gama_inf < one) THEN
75 gs = zero
76 DO i=1,norder
77 mu(i) = mat_param%UPARAM(i) / gama_inf
78 al(i) = mat_param%UPARAM(10+i)
79 gs = gs + mu(i)*al(i)
80 mat_param%UPARAM(i) = mu(i)
81 ENDDO
82 nu = mat_param%UPARAM(22)
83 bulk = gs*(one+nu)/max(em20,three*(one-two*nu))
84 mat_param%UPARAM(21) = bulk
85 !! parameters
86 young = gs*(one + nu)
87 pm(20) = young
88 pm(22) = gs !! TWO*G
89 pm(24) = young/(one - nu**2)
90 pm(32) = bulk
91 pm(100) = bulk
92C Formulation for solid elements time step computation.
93 pm(105) = gs/(bulk + two_third*gs)
94 !!
95 WRITE(iout,2000) mat_id
96 WRITE(iout,2100) half*gs,bulk
97 WRITE(iout,2200) mu(1),mu(2),mu(3),mu(4),mu(5),mu(6),mu(7),mu(8),mu(9),mu(10)
98 ELSE
99 DO i=1,norder
100 mu(i) = mat_param%UPARAM(i)
101 al(i) = mat_param%UPARAM(10+i)
102 ENDDO
103 ENDIF
104C
105 ALLOCATE (stretch(ndata))
106 ALLOCATE (stress(ndata))
107 ALLOCATE (itab_on_a(ndata))
108 ALLOCATE (index(ndata))
109 stretch(1)=lam_min
110 itab_on_a = 0
111 DO k= 2,ndata
112 stretch(k)=stretch(k-1) + em3
113 ENDDO
114 stress=zero
115C
116 WRITE(iout,1000)mat_id
117C Tension/compression
118 indx =0
119 DO i = 1, ndata
120 d11= zero
121 d22= zero
122 d12= zero
123 lam1 =stretch(i)
124 lam2 = one/sqrt(lam1)
125 lam3 = lam2
126C
127 DO k=1,norder
128 lam12 = (lam1*lam2)**(-al(k))
129 d11 = d11 + al(k)*mu(k) * (lam1**al(k) + lam12 )
130 d22 = d22 + al(k)*mu(k) * (lam2**al(k) + lam12 )
131 d12 = d12 + al(k)*mu(k) * lam12
132 ENDDO
133
134 invd1 = d11 + d22
135 invd2 = d11*d22 - d12**2
136 IF (invd1 > 0 .AND. invd2 > 0) THEN
137 indx = indx +1
138 itab_on_a(indx) = 1
139 index(indx) = i
140 ENDIF
141 ENDDO
142 IF(indx > 0 .AND. indx < ndata) THEN
143 WRITE(iout,1010)
144 i = index(1) - 1
145 IF(i > 1) THEN
146 strain_min = stretch(i) - one
147 WRITE(iout,1100)strain_min
148 ENDIF
149 i = index(indx) + 1
150 IF(i <= ndata)THEN
151 strain_max = stretch(i) - one
152 WRITE(iout,1200)strain_max
153 ENDIF
154 ENDIF
155C Biaxial
156 indx =0
157 DO i = 1, ndata
158 d11= zero
159 d22= zero
160 d12= zero
161 lam1 =stretch(i)
162 lam2 = lam1
163 lam3 = one/lam1/lam1
164C
165 DO k=1,norder
166 lam12 = (lam1*lam2)**(-al(k))
167 d11 = d11 + al(k)*mu(k) * (lam1**al(k) + lam12 )
168 d22 = d22 + al(k)*mu(k) * (lam2**al(k) + lam12 )
169 d12 = d12 + al(k)*mu(k) * lam12
170 ENDDO
171
172 invd1 = d11 + d22
173 invd2 = d11*d22 - d12**2
174 IF (invd1 > 0 .AND. invd2 > 0) THEN
175 indx = indx + 1
176 itab_on_a(indx) = 1
177 index(indx) = i
178 ENDIF
179 ENDDO
180 IF(indx > 0 .AND. indx < ndata) THEN
181 WRITE(iout,1020)
182 i = index(1) - 1
183 IF(i > 1) THEN
184 strain_min = stretch(i) - one
185 WRITE(iout,1100)strain_min
186 ENDIF
187 i = index(indx) + 1
188 IF(i <= ndata)THEN
189 strain_max = stretch(i) - one
190 WRITE(iout,1200)strain_max
191 ENDIF
192 ENDIF
193C shear test
194 indx =0
195 DO i = 1, ndata
196 d11= zero
197 d22= zero
198 d12= zero
199 lam1 =stretch(i)
200 lam2 = one
201 lam3 = one/lam1
202C
203 DO k=1,norder
204 lam12 = (lam1*lam2)**(-al(k))
205 d11 = d11 + al(k)*mu(k) * (lam1**al(k) + lam12 )
206 d22 = d22 + al(k)*mu(k) * (lam2**al(k) + lam12 )
207 d12 = d12 + al(k)*mu(k) * lam12
208 ENDDO
209
210 invd1 = d11 + d22
211 invd2 = d11*d22 - d12**2
212 IF (invd1 > 0 .AND. invd2 > 0) THEN
213 indx = indx +1
214 itab_on_a(indx) = 1
215 index(indx) = i
216 ENDIF
217 ENDDO
218 IF(indx > 0 .AND. indx < ndata) THEN
219 WRITE(iout,1030)
220 i = index(1) - 1
221 IF(i > 1) THEN
222 strain_min = stretch(i) - one
223 WRITE(iout,1100)strain_min
224 ENDIF
225 i = index(indx) + 1
226 IF(i <= ndata)THEN
227 strain_max = stretch(i) - one
228 WRITE(iout,1200)strain_max
229 ENDIF
230 ENDIF
231C
232 DEALLOCATE (stretch)
233 DEALLOCATE (stress)
234 DEALLOCATE (itab_on_a)
235 DEALLOCATE (index)
236 RETURN
237 1000 FORMAT
238 & (//5x, 'CHECK THE DRUCKER PRAGER STABILITY CONDITIONS ' ,/,
239 & 5x, ' -----------------------------------------------', /,
240 & 5x, 'MATERIAL LAW = OGDEN (LAW42) ',/,
241 & 5x, 'MATERIAL NUMBER =',i10,//)
242 1010 FORMAT(
243 & 7x,'TEST TYPE = UNIXIAL ')
244 1020 FORMAT(//,
245 & 7x,'TEST TYPE = BIAXIAL ')
246 1030 FORMAT(//,
247 & 7x,'TEST TYPE = PLANAR (SHEAR)')
248 1100 FORMAT(
249 & 8x,'COMPRESSION: UNSTABLE AT A NOMINAL STRAIN LESS THAN ',1pg20.13)
250 1200 FORMAT(
251 & 8x,'TENSION: UNSTABLE AT A NOMINAL STRAIN LARGER THAN ',1pg20.13)
252 2000 FORMAT
253 & (//5x, 'MODIFIED MATERIAL RIGIDITY ' ,/,
254 & 5x, ' ---------------------------', /,
255 & 5x, 'MATERIAL LAW = LAW42 ',/,
256 & 5x, 'MATERIAL NUMBER =',i10,//)
257 2100 FORMAT (
258 & 5x,'INITIAL SHEAR MODULUS . . . . . . . . .=',e12.4/
259 & 5x,'INITIAL BULK MODULUS. . .. . . . . . .=',e12.4//)
260 2200 FORMAT
261 & (5x, 'MU1 . . . . . . . . . . . . . . . . . .=',1pg20.13/
262 & 5x, 'MU2 . . . . . . . . . . . . . . . . . .=',1pg20.13/
263 & 5x, 'MU3 . . . . . . . . . . . . . . . . . .=',1pg20.13/
264 & 5x, 'MU4 . . . . . . . . . . . . . . . . . .=',1pg20.13/
265 & 5x, 'MU5 . . . . . . . . . . . . . . . . . .=',1pg20.13/
266 & 5x, 'MU6 . . . . . . . . . . . . . . . . . .=',1pg20.13/
267 & 5x, 'MU7 . . . . . . . . . . . . . . . . . .=',1pg20.13/
268 & 5x, 'MU8 . . . . . . . . . . . . . . . . . .=',1pg20.13/
269 & 5x, 'MU9 . . . . . . . . . . . . . . . . . .=',1pg20.13/
270 & 5x, 'MU10. . . . . . . . . . . . . . . . . .=',1pg20.13/)
271c-----------
272 END
#define my_real
Definition cppsort.cpp:32
subroutine law42_upd(mat_param, iout, titr, mat_id, pm, gama_inf)
Definition law42_upd.F:32
#define max(a, b)
Definition macros.h:21
integer, parameter nchartitle