OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
sesame.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!|| sesame ../common_source/eos/sesame.F
25!||--- called by ------------------------------------------------------
26!|| eosmain ../common_source/eos/eosmain.F
27!||--- calls -----------------------------------------------------
28!|| mintp1_rt ../common_source/eos/mintp1_rt.F
29!|| mintp_re ../common_source/eos/mintp_re.F
30!|| mintp_rt ../common_source/eos/mintp_rt.F
31!||====================================================================
32 SUBROUTINE sesame(IFLAG,NEL, PM ,OFF ,EINT ,RHO ,RHO0 ,
33 2 ESPE ,DVOL ,MAT ,PNEW ,DPDM ,DPDE ,THETA ,
34 3 BUFMAT)
35C-----------------------------------------------
36C D e s c r i p t i o n
37C-----------------------------------------------
38C This subroutine contains numerical solving
39C of SESAME 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!----------------------------------------------------------------------------C-----------------------------------------------
54C I m p l i c i t T y p e s
55C-----------------------------------------------
56#include "implicit_f.inc"
57C-----------------------------------------------
58C C o m m o n B l o c k s
59C-----------------------------------------------
60#include "param_c.inc"
61#include "vect01_c.inc"
62#include "com04_c.inc"
63#include "tabsiz_c.inc"
64C-----------------------------------------------
65C D u m m y A r g u m e n t s
66C-----------------------------------------------
67 INTEGER MAT(NEL), IFLAG, NEL
68 my_real PM(NPROPM,NUMMAT), BUFMAT(SBUFMAT),
69 . off(nel) , eint(nel), rho(nel) , rho0(nel),
70 . espe(nel), dvol(nel), pnew(nel),
71 . dpdm(nel), dpde(nel), theta(nel)
72C-----------------------------------------------
73C L o c a l V a r i a b l e s
74C-----------------------------------------------
75 INTEGER I, MX, NR, NT, IDR, IDT, IDP, IDE
76 my_real ESPEM, PRES, DTDE, DPDR, DPDT
77 my_real pc(nel)
78C-----------------------------------------------
79C S o u r c e L i n e s
80C-----------------------------------------------
81 IF(iflag == 0) THEN
82 DO i=1,nel
83 mx = mat(i)
84 pc(i) = pm(37,mx)
85 nr = nint(pm(33,mx))
86 nt = nint(pm(34,mx))
87 idr = nint(pm(35,mx))
88 idt = idr + nr
89 idp = idt + nt
90 ide = idp + nr * nt
91 espem = espe(i)/rho0(i)
92 dtde = zero
93 CALL mintp_re(bufmat(idr),nr,bufmat(idt),nt,bufmat(ide),rho(i),theta(i),espem,dtde)
94 CALL mintp1_rt(bufmat(idr),nr,bufmat(idt),nt,bufmat(idp),rho(i),theta(i),pres,dpdr,dpdt)
95 dpdm(i) = rho0(i)*dpdr
96 dpde(i) = dpdt*dtde/rho0(i)
97 pnew(i) = max(pres,pc(i))*off(i)! P(mu[n+1],E[n])
98 ENDDO
99
100 ELSEIF(iflag == 1) THEN
101 DO i=1,nel
102 mx = mat(i)
103 pc(i) = pm(37,mx)
104 nr = nint(pm(33,mx))
105 nt = nint(pm(34,mx))
106 idr = nint(pm(35,mx))
107 idt = idr + nr
108 idp = idt + nt
109 ide = idp + nr * nt
110 espem=espe(i)/rho0(i)
111 CALL mintp_re(bufmat(idr),nr,bufmat(idt),nt,bufmat(ide),rho(i),theta(i),espem,dtde)
112 CALL mintp_rt(bufmat(idr),nr,bufmat(idt),nt,bufmat(idp),rho(i),theta(i),pnew(i),dpdr)
113 pnew(i)= max(pnew(i),pc(i))*off(i)! P(mu[n+1],E[n+1])
114 eint(i)= eint(i)-half*dvol(i)*pnew(i)
115 ENDDO
116
117 ELSEIF(iflag == 2) THEN
118 DO i=1, nel
119 mx = mat(i)
120 nr = nint(pm(33,mx))
121 nt = nint(pm(34,mx))
122 pc(i) = pm(37,mx)
123 idr = nint(pm(35,mx))
124 idt = idr + nr
125 idp = idt + nt
126 ide = idp + nr * nt
127 espem = espe(i)/rho0(i)
128 CALL mintp_re(bufmat(idr),nr,bufmat(idt),nt,bufmat(ide),rho(i),theta(i),espem,dtde)
129 CALL mintp1_rt(bufmat(idr),nr,bufmat(idt),nt,bufmat(idp),rho(i),theta(i),pres,dpdr,dpdt)
130 dpdm(i) = rho0(i)*dpdr
131 dpde(i) = dpdt*dtde/rho0(i)
132 pnew(i) = max(pres,pc(i))*off(i)
133 ENDDO
134 ENDIF
135C-----------------------------------------------
136 RETURN
137 END
#define max(a, b)
Definition macros.h:21
subroutine mintp1_rt(xx, nx, yy, ny, zz, x, y, z, dzdx, dzdy)
Definition mintp1_rt.F:31
subroutine mintp_re(xx, nx, yy, ny, zz, x, y, z, dydz)
Definition mintp_re.F:34
subroutine mintp_rt(xx, nx, yy, ny, zz, x, y, z, dzdx)
Definition mintp_rt.F:35
subroutine sesame(iflag, nel, pm, off, eint, rho, rho0, espe, dvol, mat, pnew, dpdm, dpde, theta, bufmat)
Definition sesame.F:35