OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
powder_burn.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!|| powder_burn ../common_source/eos/powder_burn.F
25!||--- called by ------------------------------------------------------
26!|| eosmain ../common_source/eos/eosmain.F
27!||--- uses -----------------------------------------------------
28!|| constant_mod ../common_source/modules/constant_mod.F
29!|| matparam_def_mod ../common_source/modules/mat_elem/matparam_def_mod.F90
30!||====================================================================
31 SUBROUTINE powder_burn (
32 1 IFLAG , NEL ,PM ,OFF , EINT ,MU ,MU2 ,
33 2 ESPE , DVOL ,DF ,VNEW , MAT ,PSH ,
34 3 PNEW , DPDM ,DPDE ,MAT_PARAM ,
35 4 VAREOS, NVAREOS,NPROPM,NUMMAT ,DT1 ,RHO0 ,BFRAC)
36C-----------------------------------------------
37C M o d u l e s
38C-----------------------------------------------
39C
40C-----------------------------------------------
41C D e s c r i p t i o n
42C-----------------------------------------------
43C This is a template to introduce numerical solving of Deflagration EoS (experimental) based on LAW105 Implementation
44!----------------------------------------------------------------------------
45!! \details STAGGERED SCHEME IS EXECUTED IN TWO PASSES IN EOSMAIN : IFLG=0 THEN IFLG=1
46!! \details COLLOCATED SCHEME IS DOING A SINGLE PASS : IFLG=2
47!! \details
48!! \details STAGGERED SCHEME
49!! \details EOSMAIN / IFLG = 0 : DERIVATIVE CALCULATION FOR SOUND SPEED ESTIMATION c[n+1] REQUIRED FOR PSEUDO-VISCOSITY (DPDE:partial derivative, DPDM:total derivative)
50!! \details MQVISCB : PSEUDO-VISCOSITY Q[n+1]
51!! \details MEINT : INTERNAL ENERGY INTEGRATION FOR E[n+1] : FIRST PART USING P[n], Q[n], and Q[n+1] CONTRIBUTIONS
52!! \details EOSMAIN / IFLG = 1 : UPDATE P[n+1], T[N+1]
53!! \details INTERNAL ENERGY INTEGRATION FOR E[n+1] : LAST PART USING P[n+1] CONTRIBUTION
54!! \details (second order integration dE = -P.dV where P = 0.5(P[n+1] + P[n]) )
55!! \details COLLOCATED SCHEME
56!! \details EOSMAIN / IFLG = 2 : SINGLE PASS FOR P[n+1] AND DERIVATIVES
57!----------------------------------------------------------------------------
58C-----------------------------------------------
59C M o d u l e s
60C-----------------------------------------------
61 USE matparam_def_mod, ONLY : matparam_struct_
62 use constant_mod , only : zero, one, zep07, three100, em04
63C-----------------------------------------------
64C I m p l i c i t T y p e s
65C-----------------------------------------------
66 implicit none
67C-----------------------------------------------
68C I n c l u d e F i l e s
69C-----------------------------------------------
70#include "my_real.inc"
71#include "comlock.inc"
72#include "com06_c.inc"
73C-----------------------------------------------
74C D u m m y A r g u m e n t s
75C-----------------------------------------------
76 INTEGER,INTENT(IN) :: NVAREOS,NUMMAT,NPROPM
77 INTEGER MAT(NEL), IFLAG, NEL
78 my_real,INTENT(IN) :: PM(NPROPM,NUMMAT),OFF(NEL),MU(NEL),MU2(NEL),DVOL(NEL),DF(NEL),VNEW(NEL)
79 my_real,INTENT(INOUT) :: PNEW(NEL),DPDM(NEL),DPDE(NEL),EINT(NEL),RHO0(NEL),ESPE(NEL)
80 my_real,INTENT(INOUT) :: vareos(nel,nvareos),bfrac(nel)
81 my_real,INTENT(IN) :: dt1
82 TYPE(matparam_struct_), INTENT(IN) :: MAT_PARAM !< material data structure
83C-----------------------------------------------
84C L o c a l V a r i a b l e s
85C-----------------------------------------------
86 INTEGER I
87 my_real :: bulk,P0,PSH,DD,EG,Gr,CC,ALPHA,FSCALE_B,FSCALE_P,FSCALE_G,FSCALE_RHO, C1,C2
88 my_real :: TMP, TMP2
89 my_real :: compac
90 my_real :: total_bfrac
91 my_real :: dpdm_gas, dpdm_powder
92 my_real :: mass,ps,pg,rho_s, rho_g,pold
93 my_real :: rho(nel)
94 INTEGER :: funcb,funcg
95C-----------------------------------------------
96C E x t e r n a l F u n c t i o n s
97C-----------------------------------------------
98 my_real,EXTERNAL :: finter
99 ! EXTERNAL FINTER
100 ! Y = FINTER(IFUNC(J),X,NPF,TF,DYDX)
101 ! Y : y = f(x)
102 ! X : x
103 ! dydx : f'(x) = dy/dx
104 ! IFUNC(J): FUNCTION INDEX
105 ! J : FIRST(J=1), SECOND(J=2) .. FUNCTION USED FOR THIS LAW
106 ! NPF,TF : FUNCTION PARAMETER
107C-----------------------------------------------
108C S o u r c e L i n e s
109C-----------------------------------------------
110
111 ! --- STAGGERED SCHEME IFLG=0
112 IF(IFLAG == 0) THEN
113 BULK = MAT_PARAM%EOS%UPARAM(01)
114 P0 = MAT_PARAM%EOS%UPARAM(02)
115 PSH = MAT_PARAM%EOS%UPARAM(03)
116 DD = MAT_PARAM%EOS%UPARAM(04)
117 EG = MAT_PARAM%EOS%UPARAM(05)
118 Gr = MAT_PARAM%EOS%UPARAM(06)
119 CC = MAT_PARAM%EOS%UPARAM(07)
120 ALPHA = MAT_PARAM%EOS%UPARAM(08)
121 FSCALE_B = MAT_PARAM%EOS%UPARAM(09)
122 FSCALE_P = MAT_PARAM%EOS%UPARAM(10)
123 FSCALE_G = MAT_PARAM%EOS%UPARAM(11)
124 FSCALE_RHO = MAT_PARAM%EOS%UPARAM(12)
125 C1 = MAT_PARAM%EOS%UPARAM(13)
126 C2 = MAT_PARAM%EOS%UPARAM(14)
127 funcb = MAT_PARAM%EOS%FUNC(1)
128 funcg = MAT_PARAM%EOS%FUNC(2)
129 compac = one - zep07 !1-0.07 = 0.93
130 TOTAL_BFRAC = zero
131 IF(DT1 == ZERO)THEN
132 DO I=1,NEL
133 ESPE(I) = EG
134 EINT(I) = EG*RHO0(I)*VNEW(I)
135 VAREOS(I,1) = P0 !PS
136 VAREOS(I,2) = ZERO !PG
137 VAREOS(I,3) = RHO0(I)/compac !RHO_S
138 VAREOS(I,4) = ZERO !RHO_G
139 VAREOS(I,5) = P0 !POLD
140 VAREOS(I,6) = ZERO !F(t_old)
141 VAREOS(I,7) = RHO0(I)*VNEW(I) !Mass0
142 DPDM(I) = BULK
143 dPdE(I) = ZERO
144 ENDDO
145 ENDIF
146 DO I=1,NEL
147 !--------------------------------!
148 ! INIT. !
149 !--------------------------------!
150 RHO(I) = RHO0(I) * (ONE + MU(I))
151 MASS = RHO(I)*VNEW(I)
152 ESPE = EINT(I)/MASS
153 PS =VAREOS(I,1)
154 PG =VAREOS(I,2)
155 RHO_S=VAREOS(I,3)
156 RHO_G=VAREOS(I,4)
157 POLD =VAREOS(I,5)
158 !--------------------------------------------------------------------!
159 ! SOUND SPEED DERIVATIVE !
160 ! DPDM ! dP/dmu total derivative !
161 ! dPdE ! partial derivative (where E=Eint/V0 , and rho0V0=rho.V) !
162 !--------------------------------------------------------------------!
163 TMP = (one+mu(i))*rho0(i)/DD
164 TMP2 = (one+mu(i)) ; TMP2=TMP2*TMP2
165 DPDM_gas = EG*exp(TMP)*(one+TMP) + Pg/TMP2*(one+mu(i))*exp(TMP)
166 DPDM_powder = BULK
167 DPDM(I) = TOTAL_BFRAC * DPDM_gas + (one-TOTAL_BFRAC)*DPDM_powder !total derivative of mixture
168 dPdE(I) = TOTAL_BFRAC * (one+mu(i)*TMP) !partial derivative of mixture
169 ENDDO
170
171 ELSEIF(IFLAG == 1) THEN
172
173 ELSEIF (IFLAG == 2) THEN
174 DO I=1, NEL
175 IF (VNEW(I) > ZERO) THEN
176 PNEW(I) = zero
177 DPDM(I) = zero !total derivative
178 DPDE(I) = zero !partial derivative
179 ENDIF
180 ENDDO
181
182 ENDIF
183C-----------------------------------------------
184 RETURN
185 END
subroutine powder_burn(iflag, nel, pm, off, eint, mu, mu2, espe, dvol, df, vnew, mat, psh, pnew, dpdm, dpde, mat_param, vareos, nvareos, npropm, nummat, dt1, rho0, bfrac)
Definition powder_burn.F:36