OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
osborne.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!|| osborne ../common_source/eos/osborne.F
25!||--- called by ------------------------------------------------------
26!|| eosmain ../common_source/eos/eosmain.F
27!||====================================================================
28 SUBROUTINE osborne (IFLAG,NEL ,PM ,OFF ,EINT ,MU ,
29 2 ESPE ,DVOL ,DF ,VNEW ,MAT ,PSH ,
30 3 PNEW ,DPDM ,DPDE )
31C-----------------------------------------------
32C M o d u l e s
33C-----------------------------------------------
34C
35C-----------------------------------------------
36C D e s c r i p t i o n
37C-----------------------------------------------
38C This subroutine contains numerical solving
39C of OSBORNE EOS
40!----------------------------------------------------------------------------
41!! \details STAGGERED SCHEME IS EXECUTED IN TWO PASSES IN EOSMAIN : IFLG=0 THEN IFLG=1
42!! \details COLLOCATED SCHEME IS DOING A SINGLE PASS : IFLG=2
43!! \details
44!! \details STAGGERED SCHEME
45!! \details EOSMAIN / IFLG = 0 : DERIVATIVE CALCULATION FOR SOUND SPEED ESTIMATION c[n+1] REQUIRED FOR PSEUDO-VISCOSITY (DPDE:partial derivative, DPDM:total derivative)
46!! \details MQVISCB : PSEUDO-VISCOSITY Q[n+1]
47!! \details MEINT : INTERNAL ENERGY INTEGRATION FOR E[n+1] : FIRST PART USING P[n], Q[n], and Q[n+1] CONTRIBUTIONS
48!! \details EOSMAIN / IFLG = 1 : UPDATE P[n+1], T[N+1]
49!! \details INTERNAL ENERGY INTEGRATION FOR E[n+1] : LAST PART USING P[n+1] CONTRIBUTION
50!! \details (second order integration dE = -P.dV where P = 0.5(P[n+1] + P[n]) )
51!! \details COLLOCATED SCHEME
52!! \details EOSMAIN / IFLG = 2 : SINGLE PASS FOR P[n+1] AND DERIVATIVES
53!----------------------------------------------------------------------------
54
55C-----------------------------------------------
56C I m p l i c i t T y p e s
57C-----------------------------------------------
58#include "implicit_f.inc"
59#include "comlock.inc"
60C-----------------------------------------------
61C C o m m o n B l o c k s
62C-----------------------------------------------
63#include "param_c.inc"
64#include "com04_c.inc"
65#include "com06_c.inc"
66#include "com08_c.inc"
67#include "vect01_c.inc"
68#include "scr06_c.inc"
69C-----------------------------------------------
70C D u m m y A r g u m e n t s
71C-----------------------------------------------
72 INTEGER MAT(NEL), IFLAG, NEL
73 my_real PM(NPROPM,NUMMAT),
74 . off(nel) ,eint(nel) ,mu(nel) ,
75 . espe(nel) ,dvol(nel) ,df(nel) ,
76 . vnew(nel) ,pnew(nel) ,dpdm(nel), psh(nel) ,
77 . dpde(nel)
78C-----------------------------------------------
79C L o c a l V a r i a b l e s
80C-----------------------------------------------
81 INTEGER I, MX
82 my_real :: P0,E0,DVV,PP,dPdMU
83 my_real :: a1,a2,b0,b1,b2,c0,c1,d0, a2_,rho0
84 my_real :: denom
85C-----------------------------------------------
86C S o u r c e L i n e s
87C-----------------------------------------------
88 IF(iflag == 0) THEN
89 mx = mat(1)
90 rho0 = pm(01,mx)
91 e0 = pm(23,mx)
92 a1 = pm(164,mx)
93 a2 = pm(32,mx)
94 b0 = pm(33,mx)
95 b1 = pm(35,mx)
96 b2 = pm(36,mx)
97 c0 = pm(160,mx)
98 c1 = pm(161,mx)
99 d0 = pm(162,mx)
100 p0 = pm(163,mx)
101 psh(1:nel) = pm(88,mx)
102 DO i=1,nel
103 a2_=a2
104 IF(mu(i)<zero)a2_=-a2
105 denom = (espe(i)+d0)
106 pp = (a1*mu(i)+a2_*mu(i)*mu(i)+(b0+b1*mu(i)+b2*mu(i)*mu(i))*espe(i)+(c1*mu(i)+c0)*espe(i)*espe(i))/denom
107 dpdmu = (a1+2*a2_*mu(i)+(two*b2*mu(i)+b1)*espe(i)+c1*espe(i)*espe(i))/denom
108 dpde(i) = (((b2*mu(i)+b1)*mu(i)+b0)+(two*(c1*mu(i)+c0))*espe(i) - pp/denom)/denom
109 dpdm(i) = dpdmu + dpde(i)*df(i)*df(i)*(pp) !total derivative
110 pnew(i) = pp * off(i) ! P(mu[n+1],E[n])
111 pnew(i) = pnew(i) - psh(i)
112 ENDDO
113
114 ELSEIF(iflag == 1) THEN
115 mx = mat(1)
116 rho0 = pm(01,mx)
117 e0 = pm(23,mx)
118 a1 = pm(164,mx)
119 a2 = pm(32,mx)
120 b0 = pm(33,mx)
121 b1 = pm(35,mx)
122 b2 = pm(36,mx)
123 c0 = pm(160,mx)
124 c1 = pm(161,mx)
125 d0 = pm(162,mx)
126 p0 = pm(163,mx)
127 psh(1:nel) = pm(88,mx)
128 DO i=1,nel
129 a2_=a2
130 IF(mu(i)<zero)a2_=-a2
131 dvv = dvol(i)*df(i) / max(em15,vnew(i)) ! DVOL/V0 car ESPE =EINT/V0
132 dvv = half*dvv ! car 2 iterations
133 denom = (espe(i)+d0)
134 pp = (a1*mu(i)+a2_*mu(i)*mu(i)+(b0+b1*mu(i)+b2*mu(i)*mu(i))*espe(i)+(c1*mu(i)+c0)*espe(i)*espe(i))/denom
135 espe(i) = espe(i) - (pp)*dvv
136 denom = (espe(i)+d0)
137 pp = (a1*mu(i)+a2_*mu(i)*mu(i)+(b0+b1*mu(i)+b2*mu(i)*mu(i))*espe(i)+(c1*mu(i)+c0)*espe(i)*espe(i))/denom
138 espe(i) = espe(i) - (pp)*dvv
139 pnew(i) = pp * off(i) ! P(mu[n+1],E[n+1])
140 eint(i) = eint(i) - half*dvol(i)*(pnew(i))
141 pnew(i) = pnew(i) - psh(i)
142 dpde(i) = (((b2*mu(i)+b1)*mu(i)+b0)+(two*(c1*mu(i)+c0))*espe(i) - pp/denom)/denom
143 ENDDO
144
145 ELSEIF(iflag == 2) THEN
146 mx = mat(1)
147 rho0 = pm(01,mx)
148 e0 = pm(23,mx)
149 a1 = pm(164,mx)
150 a2 = pm(32,mx)
151 b0 = pm(33,mx)
152 b1 = pm(35,mx)
153 b2 = pm(36,mx)
154 c0 = pm(160,mx)
155 c1 = pm(161,mx)
156 d0 = pm(162,mx)
157 p0 = pm(163,mx)
158 psh(1:nel) = pm(88,mx)
159 DO i=1, nel
160 IF (vnew(i) > zero) THEN
161 a2_=a2
162 IF(mu(i)<zero)a2_=-a2
163 denom = (espe(i)+d0)
164 pp = (a1*mu(i)+a2_*mu(i)*mu(i)+(b0+b1*mu(i)+b2*mu(i)*mu(i))*espe(i)+(c1*mu(i)+c0)*espe(i)*espe(i))/denom
165 dpdmu = (a1+2*a2_*mu(i)+(two*b2*mu(i)+b1)*espe(i)+c1*espe(i)*espe(i))/denom
166 dpde(i) = (((b2*mu(i)+b1)*mu(i)+b0)+(two*(c1*mu(i)+c0))*espe(i) - pp/denom)/denom
167 dpdm(i) = dpdmu + dpde(i)*df(i)*df(i)*(pp) !total derivative
168 pnew(i) = pp*off(i)
169 pnew(i) = pnew(i) - psh(i)
170 ENDIF
171 ENDDO
172
173 ENDIF
174
175C-----------------------------------------------
176 RETURN
177 END
#define max(a, b)
Definition macros.h:21
subroutine osborne(iflag, nel, pm, off, eint, mu, espe, dvol, df, vnew, mat, psh, pnew, dpdm, dpde)
Definition osborne.F:31