OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
m26law.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!|| m26law ../engine/source/materials/mat/mat026/m26law.F
25!||--- called by ------------------------------------------------------
26!|| mmain ../engine/source/materials/mat_share/mmain.F90
27!||====================================================================
28 SUBROUTINE m26law(PM ,OFF ,SIG ,RHO,
29 2 EPXE ,THETA ,EPD ,Z ,
30 3 MAT ,VOLN ,DVOL ,D1 ,
31 4 D2 ,D3 ,D4 ,D5 ,
32 5 D6 ,NEL, P, RHO0, DF)
33C
34C LOI DE COMPORTEMENT TYPE JOHNSON - COOK - SESAME
35C
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C G l o b a l P a r a m e t e r s
42C-----------------------------------------------
43#include "mvsiz_p.inc"
44C-----------------------------------------------
45C C o m m o n B l o c k s
46C-----------------------------------------------
47#include "com08_c.inc"
48#include "param_c.inc"
49C-----------------------------------------------
50C D u m m y A r g u m e n t s
51C-----------------------------------------------
52 INTEGER MAT(*),NEL
53 my_real
54 . PM(NPROPM,*), OFF(*), SIG(NEL,6), RHO(*), EPXE(*), THETA(*),
55 . EPD(*), Z(*), VOLN(MVSIZ), DVOL(*), D1(*), D2(*), D3(*), D4(*),
56 . d5(*), d6(*), p(*), rho0(*), df(*)
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 INTEGER I, MX
61 my_real
62 . G(MVSIZ), G1(MVSIZ), G2(MVSIZ), AK(MVSIZ), QH(MVSIZ), TMELT(MVSIZ),
63 . AJ2(MVSIZ), DMU(MVSIZ), DAV(MVSIZ), EPMX(MVSIZ),
64 . thetl(mvsiz), ca(mvsiz), cb(mvsiz), cc(mvsiz), cn(mvsiz), epdr(mvsiz), cmx(mvsiz),
65 . sigmx(mvsiz), tstar, ct, ce, ch, scale,
66 . rho0_1, ca_1, cb_1, cn_1, cc_1,
67 . cmx_1, tmelt_1, epdr_1, thetl_1,epmx_1,
68 . sigmx_1
69C-----------------------------------------------
70C
71 mx =mat(1)
72C
73 rho0_1 =pm( 1,mx)
74 ca_1 =pm(38,mx)
75 cb_1 =pm(39,mx)
76 cn_1 =pm(40,mx)
77 cc_1 =pm(43,mx)
78 cmx_1 =pm(45,mx)
79 tmelt_1=pm(46,mx)
80 epdr_1 =pm(44,mx)
81 thetl_1=pm(47,mx)
82 epmx_1 =pm(41,mx)
83 sigmx_1=pm(42,mx)
84C
85 DO 10 i=1,nel
86 rho0(i) =rho0_1
87 g(i) =pm(22,mx)*off(i)
88 ca(i) =ca_1
89 cb(i) =cb_1
90 cn(i) =cn_1
91 cc(i) =cc_1
92 cmx(i) =cmx_1
93 tmelt(i)=tmelt_1
94 epdr(i) =epdr_1
95C SPH(I) =PM(48,MX)
96C PC(I) =PM(37,MX)
97 thetl(i)=thetl_1
98 epmx(i) =epmx_1
99 sigmx(i)=sigmx_1
100 10 CONTINUE
101C
102 DO 15 i=1,nel
103 15 df(i)=rho0(i)/rho(i)
104C
105 DO 30 i=1,nel
106 p(i) =-third*(sig(i,1)+sig(i,2)+sig(i,3))
107 dav(i)=-third*(d1(i)+d2(i)+d3(i))
108 g1(i)=dt1*g(i)
109 g2(i)=two*g1(i)
110 dmu(i)=-dvol(i)/voln(i)
111 30 CONTINUE
112C-------------------------------
113C CONTRAINTES DEVIATORIQUES
114C-------------------------------
115 DO 40 i=1,nel
116 sig(i,1)=sig(i,1)+p(i)+g2(i)*(d1(i)+dav(i))
117 sig(i,2)=sig(i,2)+p(i)+g2(i)*(d2(i)+dav(i))
118 sig(i,3)=sig(i,3)+p(i)+g2(i)*(d3(i)+dav(i))
119 sig(i,4)=sig(i,4)+g1(i)*d4(i)
120 sig(i,5)=sig(i,5)+g1(i)*d5(i)
121 40 sig(i,6)=sig(i,6)+g1(i)*d6(i)
122C
123 DO 50 i=1,nel
124 aj2(i)=half*(sig(i,1)**2+sig(i,2)**2+sig(i,3)**2)
125 1 +sig(i,4)**2+sig(i,5)**2+sig(i,6)**2
126 50 aj2(i)=sqrt(3.*aj2(i))
127C
128 DO 90 i=1,nel
129 IF(theta(i)>=tmelt(i)) GOTO 90
130C
131 tstar=0.
132 ct=1.
133 IF(theta(i)<=three100) GOTO 60
134 tstar=(theta(i)-three100)/(tmelt(i)-three100)
135 IF(theta(i)>thetl(i)) cmx(i)=one
136 ct=one -tstar**cmx(i)
137C
138 60 ce=one
139C
140 epd(i)=off(i)* max( abs(d1(i)), abs(d2(i)), abs(d3(i)),
141 . half*abs(d4(i)),.5*abs(d5(i)),.5*abs(d6(i)))
142C----------------------------------------------------------
143 IF(epd(i)<=epdr(i)) GOTO 70
144 ce=one + cc(i) * log(epd(i)/epdr(i))
145C
146 70 ch=ca(i)
147 IF(epxe(i)<=zero) GOTO 80
148 ch=ca(i)+cb(i)*epxe(i)**cn(i)
149 IF(epxe(i)>epmx(i)) ch=ca(i)+cb(i)*epmx(i)**cn(i)
150C
151 80 ak(i)= min(sigmx(i),ch)*ce*ct
152C-----------------------
153C MODULE ECROUISSAGE
154C-----------------------
155 IF(cn(i)>=1) THEN
156 qh(i)= (cb(i)*cn(i)*epxe(i)**(cn(i)-one))*ce*ct
157 ELSE
158 IF(epxe(i)/=zero)THEN
159 qh(i)= (cb(i)*cn(i)/epxe(i)**(one-cn(i)))*ce*ct
160 ELSE
161 qh(i)=zero
162 ENDIF
163 ENDIF
164 90 CONTINUE
165C
166 DO 110 i=1,nel
167 IF(theta(i)>=tmelt(i)) GOTO 100
168 IF(aj2(i)<=ak(i)) GOTO 110
169C
170 scale=zero
171 IF(aj2(i)/=zero) scale=ak(i)/aj2(i)
172 sig(i,1)=scale*sig(i,1)
173 sig(i,2)=scale*sig(i,2)
174 sig(i,3)=scale*sig(i,3)
175 sig(i,4)=scale*sig(i,4)
176 sig(i,5)=scale*sig(i,5)
177 sig(i,6)=scale*sig(i,6)
178 epxe(i)=epxe(i)+(one-scale)*aj2(i)/(three*g(i)+qh(i))
179 GOTO 110
180C
181 100 ak(i)=zero
182 epxe(i)=zero
183 sig(i,1)=zero
184 sig(i,2)=zero
185 sig(i,3)=zero
186 sig(i,4)=zero
187 sig(i,5)=zero
188 sig(i,6)=zero
189C
190 110 CONTINUE
191 RETURN
192 END
subroutine m26law(pm, off, sig, rho, epxe, theta, epd, z, mat, voln, dvol, d1, d2, d3, d4, d5, d6, nel, p, rho0, df)
Definition m26law.F:33
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21