OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
mjwl.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!|| mjwl ../engine/source/materials/mat/mat005/mjwl.F
25!||--- called by ------------------------------------------------------
26!|| mmain ../engine/source/materials/mat_share/mmain.F90
27!||====================================================================
28 SUBROUTINE mjwl(PM ,MAT ,OFF ,SIG ,EINT ,
29 1 PSH ,P0 ,QOLD ,VOL ,BFRAC,
30 2 VOLN ,QNEW ,SOLD1 ,SOLD2 ,SOLD3,
31 3 DVOL ,NEL ,DF ,ABURN ,
32 4 ER1V ,ER2V ,WDR1V ,WDR2V , W1, AMU)
33C-----------------------------------------------
34C I m p l i c i t T y p e s
35C-----------------------------------------------
36#include "implicit_f.inc"
37C-----------------------------------------------
38C G l o b a l P a r a m e t e r s
39C-----------------------------------------------
40#include "mvsiz_p.inc"
41C-----------------------------------------------
42C D u m m y A r g u m e n t s
43C-----------------------------------------------
44 INTEGER MAT(MVSIZ),NEL
45 my_real
46 . PM(NPROPM,*),
47 . OFF(*),SIG(NEL,6),EINT(*),QOLD(*),VOL(*),BFRAC(*),VOLN(MVSIZ),QNEW(*),
48 . psh(*),p0(*),
49 . dvol(*),sold1(*),sold2(*),sold3(*), df(*), er1v(*), er2v(*), wdr1v(*), wdr2v(*), w1(*),
50 . aburn(mvsiz),alpha_unit,amu(*)
51C-----------------------------------------------
52C C o m m o n B l o c k s
53C-----------------------------------------------
54#include "com08_c.inc"
55#include "param_c.inc"
56C-----------------------------------------------
57C L o c a l V a r i a b l e s
58C-----------------------------------------------
59 INTEGER I,QOPT
60 my_real
61 . EINC(MVSIZ) , ESPE(MVSIZ), W1DF(MVSIZ)
62 my_real
63 . tbegin, tend,
64 . volo(mvsiz),facm(mvsiz),pold(mvsiz),pnew(mvsiz),
65 . eadd, lambda,rr,rr2,a,m,n,bulk
66C-----------------------------------------------
67C S o u r c e L i n e s
68C-----------------------------------------------
69 DO i=1,nel
70 dvol(i)=half*dvol(i)
71 pold(i)=third*(sold1(i)+sold2(i)+sold3(i))
72 einc(i)=dvol(i)*(pold(i)-psh(i)-qold(i)-qnew(i))
73 eint(i)=eint(i)+einc(i)
74 qold(i)=qnew(i)
75 volo(i)=voln(i)/df(i)
76 ENDDO
77
78 !================ AFTERBURNING ============================!
79 ! computes E <- E + lambda(t)*E_add
80 qopt = nint(pm(042,mat(1)))
81 eadd = pm(160,mat(1))
82 tbegin = pm(161,mat(1))
83 tend = pm(162,mat(1))
84 rr = pm(163,mat(1))
85 a = pm(164,mat(1))
86 m = pm(165,mat(1))
87 n = pm(166,mat(1))
88 rr2 = pm(167,mat(1))
89 alpha_unit = pm(168,mat(1))
90 bulk = pm(044,mat(1))
91 IF(eadd==zero)THEN
92 !=== no afterburning
93 ! EINT(I) = EINT(I)
94 ELSEIF(qopt==0)THEN
95 !=== instantaneous release
96 DO i=1,nel
97 lambda = zero
98 IF(tt > tend .AND. aburn(i)==one)THEN
99 lambda = one
100 aburn(i) = one
101 ELSEIF (tt <= tbegin)THEN
102 lambda = zero
103 aburn(i) = zero
104 ELSE
105 lambda = one
106 eint(i) = eint(i)+(lambda-aburn(i))*eadd*max(em20,volo(i))
107 aburn(i) = one
108 ENDIF
109 ENDDO
110 ELSEIF(qopt==1)THEN
111 !=== afterburning with constant rate from Tbegin to Tend
112 DO i=1,nel
113 lambda = zero
114 IF(tt > tend .AND. aburn(i)==one)THEN
115 lambda = one
116 aburn(i) = one
117 ELSEIF (tt <= tbegin)THEN
118 lambda = zero
119 aburn(i) = zero
120 ELSE
121 lambda = (tt-tbegin)*rr
122 lambda = min(one,lambda)
123 eint(i) = eint(i)+(lambda-aburn(i))*eadd*max(em20,volo(i))
124 aburn(i) = lambda
125 ENDIF
126 ENDDO
127 ELSEIF(qopt==2)THEN
128 !=== afterburning with linear rate from Tbegin to Tend
129 DO i=1,nel
130 lambda = zero
131 IF(tt > tend .AND. aburn(i)==one)THEN ! .AND. ABURN(I)==ONE needed to add last increment
132 lambda = one
133 aburn(i) = one
134 ELSEIF (tt <= tbegin)THEN
135 lambda = zero
136 aburn(i) = zero
137 ELSE
138 lambda = half*rr*tt**2 - rr*tbegin*tt + rr2
139 lambda = max(zero,min(one,lambda))
140 eint(i) = eint(i)+(lambda-aburn(i))*eadd*max(em20,volo(i))
141 aburn(i) = lambda
142 ENDIF
143 ENDDO
144 ELSEIF(qopt==3)THEN
145 !=== Miller s extension, rate is depedent on Pressure
146 DO i=1,nel
147 lambda = zero
148 IF(-pold(i)-psh(i) > zero )THEN
149 lambda=aburn(i)+ dt1*a*exp( m*log(one+aburn(i)) )*exp(n*log(alpha_unit*(-pold(i)-psh(i))))
150 lambda = max(lambda,zero)
151 lambda = min(lambda,one)
152 eint(i) = eint(i)+(lambda-aburn(i))*eadd*max(em20,volo(i))
153 aburn(i)= lambda
154 ENDIF
155 ENDDO
156 ENDIF
157 !================ END AFTERBURNING ============================!
158
159 DO i=1,nel
160 espe(i)=eint(i)/max(em20,volo(i))
161 w1df(i)=bfrac(i)*w1(i)/df(i)
162 facm(i)=bfrac(i)*(wdr1v(i)*er1v(i)+wdr2v(i)*er2v(i))
163 ENDDO
164
165 DO i=1,nel
166 pnew(i)= - psh(i) + (one - bfrac(i)) * (p0(i) + bulk * amu(i)) +
167 . (facm(i)+(espe(i))*w1df(i))/(one +w1df(i)*dvol(i)/max(em20,volo(i)))
168 ENDDO
169
170 DO i=1,nel
171 !!! Taking -PSH as the minimum value
172 pnew(i)= max(zero - psh(i), pnew(i))*off(i)
173 ENDDO
174
175 DO i=1,nel
176 einc(i)= einc(i)-(pnew(i) + psh(i))*dvol(i)
177 eint(i)=(eint(i)-(pnew(i) + psh(i))*dvol(i))/max(em20,vol(i))
178 ENDDO
179
180 DO i=1,nel
181 sig(i,1)=sig(i,1)*off(i)-pnew(i)
182 sig(i,2)=sig(i,2)*off(i)-pnew(i)
183 sig(i,3)=sig(i,3)*off(i)-pnew(i)
184 ENDDO
185
186C-----------------------------------------------
187 RETURN
188 END
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
subroutine mjwl(pm, mat, off, sig, eint, psh, p0, qold, vol, bfrac, voln, qnew, sold1, sold2, sold3, dvol, nel, df, aburn, er1v, er2v, wdr1v, wdr2v, w1, amu)
Definition mjwl.F:33