OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
polynomial51.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!|| polyun51 ../engine/source/materials/mat/mat051/polynomial51.F
25!||--- called by ------------------------------------------------------
26!|| sigeps51 ../engine/source/materials/mat/mat051/sigeps51.F90
27!||====================================================================
28 SUBROUTINE polyun51 (
29 . C0 ,C1 ,C2 ,C3 ,C4 , C5 ,GG,
30 . VOLUME ,DVOL ,VOLD ,
31 . RHO ,MASA ,RHOA0 ,DD ,MU , MUP1 ,
32 . POLD ,PEXT ,P ,PM ,Q ,
33 . RHO0E ,EINTA ,VISCMAX ,XL ,SSP ,
34 . QA ,QB )
35C-----------------------------------------------
36C I m p l i c i t T y p e s
37C-----------------------------------------------
38#include "implicit_f.inc"
39C-----------------------------------------------
40C I N P U T O U T P U T A r g u m e n t s
41C-----------------------------------------------
42 my_real,INTENT(IN) :: c0,c1,c2,c3,c5,c4,gg,volume,vold,masa ,rhoa0,dd, pold,pext,pm
43 my_real,INTENT(IN) :: rho0e,xl, qa,qb
44 my_real,INTENT(INOUT) :: einta
45 my_real,INTENT(INOUT) :: p, dvol, rho, mu, viscmax, q, ssp
46C-----------------------------------------------
47C L o c a l V a r i a b l e s
48C-----------------------------------------------
49 my_real :: aa,bb,dpdv,dpdmu,v0,qal,qbl,mup1
50C-----------------------------------------------
51C L o c a l V a r i a b l e s
52C-----------------------------------------------
53 v0 = masa / rhoa0
54 dvol = volume - vold
55 rho = masa/volume
56 mup1 = rho/rhoa0
57 mu = mup1 - one
58
59 dpdv = (-(c1 + (c2 + c2 + three*c3*mu)*max(zero,mu) + c5*rho0e )*mup1*mup1 -(c4 + c5*mu)*(pold+pext) ) / v0
60 dpdmu = -dpdv*volume/mup1
61 dpdmu = abs(dpdmu)
62 ssp = sqrt((dpdmu + two_third*gg)/rhoa0)
63 qal = qa*xl
64 qal = qal*qal
65 qbl = qb*xl
66 viscmax = rho*(qal*max(zero,dd) + qbl*ssp)
67 q = viscmax*max(zero,dd)
68
69 aa = (c4 + c5*mu)/v0
70 bb = half*(volume-vold)
71
72 !first torder
73 p = ( c0 + c1*mu+ max(mu,zero)*(c2*mu + c3*mu*mu) + aa*einta )
74 p = max(p,pm)
75 !second order
76 !P = ( PEXT+C0 + C1*MU+ MAX(MU,ZERO)*(C2*MU + C3*MU*MU) + AA*EINTA ) / (ONE+AA*BB)
77 !P = MAX(P,PM)-PEXT
78 !EINTA = EINTA - BB*(P+PEXT+Q) !2nd order integration (semi-implicit)
79
80
81
82
83 dpdv = (-(c1 + (c2 + c2 + three*c3*mu)*max(zero,mu) + c5*rho0e )*mup1*mup1 -(c4 + c5*mu)*(p+pext) ) / v0
84 dpdmu = -dpdv*volume/mup1
85 dpdmu = abs(dpdmu)
86 ssp = sqrt((dpdmu + two_third*gg)/rhoa0)
87
88 RETURN
89 END
90
91!||====================================================================
92!|| poly51 ../engine/source/materials/mat/mat051/polynomial51.F
93!||--- called by ------------------------------------------------------
94!|| sigeps51 ../engine/source/materials/mat/mat051/sigeps51.F90
95!||====================================================================
96 SUBROUTINE poly51 (C01,C11,C21,C31,C41,C51,GG1,
97 . V10,V1,V1OLD,MU1,MUP1,EINT1,
98 . PEXT,P1,PM1,P1I,
99 . RHO1,RHO10,MAS1,SSP1,DVDP1,DPDV1, E_INF,
100 . FLAG)
101C-----------------------------------------------
102C I m p l i c i t T y p e s
103C-----------------------------------------------
104#include "implicit_f.inc"
105C-----------------------------------------------
106C I N P U T O U T P U T A r g u m e n t s
107C-----------------------------------------------
108 my_real,INTENT(IN) :: c01,c11,c21,c31,c41,c51,gg1,
109 . v10,v1,v1old,
110 . pext,pm1,p1i,
111 . rho10,mas1,e_inf
112 my_real,INTENT(INOUT) :: dvdp1,p1,ssp1,dpdv1,eint1,mu1,mup1,rho1
113 INTEGER FLAG
114C-----------------------------------------------
115C L o c a l V a r i a b l e s
116C-----------------------------------------------
117 my_real AA,BB,DVDP1I
118C------------------------
119 dvdp1i = dvdp1
120 IF (flag == 1) rho1 = mas1/v1
121 mup1 = rho1/rho10
122 mu1 = mup1 - one
123 aa = (c41 + c51*mu1)/v10
124 bb = half*(v1-v1old)
125 IF (flag == 1) eint1 = eint1 - (p1i+pext+pext)*bb
126 IF (flag == 1) THEN
127 p1 = ( c01 + c11*mu1 + max(mu1,zero)*(c21*mu1 + c31*mu1*mu1) + aa*eint1 ) / (one+aa*bb)
128 ELSE
129 p1 = ( c01 + c11*mu1 + max(mu1,zero)*(c21*mu1 + c31*mu1*mu1) + aa*eint1 )
130 ENDIF
131 p1 = max(p1,pm1)
132 IF (flag == 1) eint1 = eint1 - p1*bb
133 IF (flag == 1) eint1 = max(eint1, e_inf*v10)
134
135 dpdv1 = (-(c11 + (c21 + c21 + three*c31*mu1)*max(zero,mu1) + c51*eint1/v10 )*mup1*mup1 -(c41 + c51*mu1)*(p1+pext) ) / v10
136 ssp1 = (-dpdv1*v1/mup1 + two_third*gg1)/rho10
137 ssp1 = sqrt(abs(ssp1))
138
139 IF(abs(dpdv1)<em20)THEN
140 dvdp1 = zero
141 ELSE
142 dvdp1 = one/dpdv1
143 ENDIF
144
145 RETURN
146 END
#define my_real
Definition cppsort.cpp:32
#define max(a, b)
Definition macros.h:21
subroutine poly51(c01, c11, c21, c31, c41, c51, gg1, v10, v1, v1old, mu1, mup1, eint1, pext, p1, pm1, p1i, rho1, rho10, mas1, ssp1, dvdp1, dpdv1, e_inf, flag)
subroutine polyun51(c0, c1, c2, c3, c4, c5, gg, volume, dvol, vold, rho, masa, rhoa0, dd, mu, mup1, pold, pext, p, pm, q, rho0e, einta, viscmax, xl, ssp, qa, qb)