OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
jwl.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!|| jwl ../common_source/eos/jwl.F
25!||--- called by ------------------------------------------------------
26!|| eosmain ../common_source/eos/eosmain.F
27!||====================================================================
28 SUBROUTINE jwl
29 1 (iflag,nel ,pm ,off ,eint ,mu ,mu2 ,
30 2 espe ,dvol ,df ,vnew ,mat ,psh ,
31 3 pnew ,dpdm ,dpde )
32C-----------------------------------------------
33C D e s c r i p t i o n
34C-----------------------------------------------
35C This subroutine contains numerical solving
36C of JWL EOS
37!----------------------------------------------------------------------------
38!! \details STAGGERED SCHEME IS EXECUTED IN TWO PASSES IN EOSMAIN : IFLG=0 THEN IFLG=1
39!! \details COLLOCATED SCHEME IS DOING A SINGLE PASS : IFLG=2
40!! \details
41!! \details STAGGERED SCHEME
42!! \details EOSMAIN / IFLG = 0 : DERIVATIVE CALCULATION FOR SOUND SPEED ESTIMATION c[n+1] REQUIRED FOR PSEUDO-VISCOSITY (DPDE:partial derivative, DPDM:total derivative)
43!! \details MQVISCB : PSEUDO-VISCOSITY Q[n+1]
44!! \details MEINT : INTERNAL ENERGY INTEGRATION FOR E[n+1] : FIRST PART USING P[n], Q[n], and Q[n+1] CONTRIBUTIONS
45!! \details EOSMAIN / IFLG = 1 : UPDATE P[n+1], T[N+1]
46!! \details INTERNAL ENERGY INTEGRATION FOR E[n+1] : LAST PART USING P[n+1] CONTRIBUTION
47!! \details (second order integration dE = -P.dV where P = 0.5(P[n+1] + P[n]) )
48!! \details COLLOCATED SCHEME
49!! \details EOSMAIN / IFLG = 2 : SINGLE PASS FOR P[n+1] AND DERIVATIVES
50!----------------------------------------------------------------------------
51C-----------------------------------------------
52C I m p l i c i t T y p e s
53C-----------------------------------------------
54#include "implicit_f.inc"
55#include "comlock.inc"
56C-----------------------------------------------
57C C o m m o n B l o c k s
58C-----------------------------------------------
59#include "param_c.inc"
60#include "com04_c.inc"
61#include "com06_c.inc"
62#include "com08_c.inc"
63#include "vect01_c.inc"
64#include "scr06_c.inc"
65C-----------------------------------------------
66C D u m m y A r g u m e n t s
67C-----------------------------------------------
68 INTEGER MAT(NEL), IFLAG, NEL
69 my_real pm(npropm,nummat),
70 . off(nel) ,eint(nel) ,mu(nel) ,
71 . mu2(nel) ,espe(nel) ,dvol(nel) ,df(nel) ,
72 . vnew(nel) ,pnew(nel) ,dpdm(nel),
73 . dpde(nel)
74 my_real, INTENT(INOUT) :: psh(nel)
75C-----------------------------------------------
76C L o c a l V a r i a b l e s
77C-----------------------------------------------
78 INTEGER I,MX,IBFRAC
79 my_real vdet,bfrac(nel),
80 . rho0 , aa , bb , r1,
81 . r2, w1, bhe, p0, bulk,
82 . r1df,r2df,er1df,er2df,dpdmu
83C-----------------------------------------------
84C S o u r c e L i n e s
85C-----------------------------------------------
86
87 IF(iflag == 0) THEN
88
89 ELSEIF(iflag == 1) THEN
90
91 ELSEIF(iflag == 2) THEN
92 mx = mat(1)
93 rho0 = pm( 1,mx)
94 aa = pm(33,mx)
95 bb = pm(34,mx)
96 r1 = pm(35,mx)
97 r2 = pm(36,mx)
98 w1 = pm(45,mx)
99 vdet = pm(38,mx)
100 bhe = pm(40,mx)
101 p0 = pm(31,mx)
102 bulk = pm(44,mx)
103 ibfrac = nint(pm(41,mx))
104 psh(1:nel) = pm(88,mx)
105 DO i=1,nel
106 bfrac(i)=one
107 ENDDO
108 DO i=1, nel
109 IF (vnew(i) > zero) THEN
110 r1df = r1*df(i)
111 r2df = r2*df(i)
112 er1df = exp(-r1df)
113 er2df = exp(-r2df)
114 pnew(i) = - psh(i) + aa*(one-w1/r1df)*er1df + bb*(one-w1/r2df)*er2df + w1*espe(i)/df(i)
115 pnew(i) = max(zero - psh(i), pnew(i))
116 ! dPdE : partial derivative
117 ! dPdmu : partial derivative
118 ! DPDM : total derivative
119 dpde(i) = w1/df(i)
120 dpdmu =
121 . -aa*w1*er1df/r1 + aa*(one-w1/(r1df))*r1df*r1df*er1df
122 . -bb*w1*er2df/r2 + bb*(one-w1/(r2df))*r2df*r2df*er2df
123 . +w1*espe(i)
124 dpdm(i) = dpdmu + (pnew(i)+psh(i))*df(i)*df(i)*dpde(i)
125 ENDIF
126 ENDDO
127 ENDIF
128
129C-----------------------------------------------
130 RETURN
131 END
#define my_real
Definition cppsort.cpp:32
subroutine jwl(iflag, nel, pm, off, eint, mu, mu2, espe, dvol, df, vnew, mat, psh, pnew, dpdm, dpde)
Definition jwl.F:32
#define max(a, b)
Definition macros.h:21