OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
m37init.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!|| m37init ../starter/source/materials/mat/mat037/m37init.F
25!||--- called by ------------------------------------------------------
26!|| matini ../starter/source/materials/mat_share/matini.F
27!||--- uses -----------------------------------------------------
28!||====================================================================
29 SUBROUTINE m37init(
30 . IPM ,PM ,
31 . NGL ,NUVAR ,UVAR ,UPARAM ,X ,
32 . MAT ,IPARG ,IFORM ,IX ,NIX ,
33 . ILOADP ,FACLOAD ,GBUF ,NEL)
34C-----------------------------------------------
35C D e s c r i p t i o n
36C-----------------------------------------------
37C This subroutine is initializing cell based on law37
38C In case of /LOAD/HYDRO is attached to it then
39C Pressure is computed so that P(t=0) = P0 + DP
40C where DP=rho0.g.h
41C and h is signed distance from water/air free surface
42C which is defined by B and n in input
43C-----------------------------------------------
44C M o d u l e s
45C-----------------------------------------------
46 USE elbufdef_mod
47C-----------------------------------------------
48C I m p l i c i t T y p e s
49C-----------------------------------------------
50#include "implicit_f.inc"
51C-----------------------------------------------
52C C o m m o n B l o c k s
53C-----------------------------------------------
54#include "com04_c.inc"
55#include "param_c.inc"
56#include "vect01_c.inc"
57#include "mvsiz_p.inc"
58C-----------------------------------------------
59C D u m m y A r g u m e n t s
60C-----------------------------------------------
61 INTEGER :: IPM(NPROPMI,NUMMAT),NGL(MVSIZ) ,MAT(MVSIZ), IPARG(NPARG) ,IFORM,NIX,IX(NIX,*)
62 my_real :: PM(NPROPM,NUMMAT),X(3,NUMNOD), UVAR(LLT,NUVAR)
63 INTEGER,INTENT(IN) :: ILOADP(SIZLOADP,*),NEL
64 my_real,INTENT(IN) :: FACLOAD(LFACLOAD,*)
65 TYPE(g_bufel_), INTENT(INOUT),TARGET :: GBUF
66C-----------------------------------------------
67C L o c a l V a r i a b l e s
68C-----------------------------------------------
69 INTEGER :: I,J,NUVAR, GG1, GG2, GG3, ISFLUID,NL
70 INTEGER :: NPH,IFLG,IE,IADBUF,NUPARAM, M_UID,M_IID,IGRAV
71 my_real :: MFRAC, A, MU1P1, MU1P2, RHO1, RHO2, RHO10, RHO20, C1, GAM, PMIN, P0, MU2P1, RHO,P,A1,PSH,DEPTH,Z(3)
72 my_real :: UPARAM(*),XBAS,YBAS,ZBAS,NX,NY,NZ,GRAV, BZ(3),DOTPROD, DELTA_P, RHO0_LIQ,RHO0_GAS, RHO_LIQ,RHO_GAS
73 my_real :: pold,height
74 my_real :: n(3,8)
75C-----------------------------------------------
76
77 !---------------------------------!
78 ! CELL INIT. (UVAR ARRAY) !
79 !---------------------------------!
80 !UVAR(I,1) : massic percentage of liquid * global density (rho1*V1/V : it needs to give liquid mass multiplying by element volume in aleconve.F)
81 !UVAR(I,2) : density of gas
82 !UVAR(I,3) : density of liquid
83 !UVAR(I,4) : volumetric fraction of liquid
84 !UVAR(I,5) : volumetric fraction of gas
85 DO i=lft,llt
86 ie = i+nft
87 c1 = uparam(4)
88 gam = uparam(5)
89 pmin = uparam(8)
90 p0 = uparam(9)
91 rho10 = uparam(11)
92 rho20 = uparam(12)
93 a1 = uparam(10)
94 p = -p0
95 rho = rho10 * a1 + (one-a1)*rho20
96 IF(gam*c1>=em30)THEN !if Liquid and gas correctly defined
97 mu1p1 = one !(P/C1+ONE)
98 mu2p1 = one !( ONE+P/P0)**(ONE/GAM)
99 rho1 = rho10*mu1p1
100 rho2 = rho20*mu2p1
101 a = (rho-rho2)/(rho1-rho2)
102 uvar(i,1) = a*rho1
103 uvar(i,2) = rho2
104 uvar(i,3) = rho1
105 uvar(i,4) = a
106 IF(uvar(i,4)<em20)uvar(i,4)=zero
107 uvar(i,5) = one-uvar(i,4)
108 !SOUNDSP(I) = A*SQRT(C1/RHO1) + (ONE-A) * SQRT(GAM*P0/RHO2) -> check sigeps37.F (starter)
109 ELSE !boundary element
110 uvar(i,3) = rho
111 ENDIF
112 ENDDO
113
114C-----------------------------------------------
115 RETURN
116 END SUBROUTINE m37init
subroutine m37init(ipm, pm, ngl, nuvar, uvar, uparam, x, mat, iparg, iform, ix, nix, iloadp, facload, gbuf, nel)
Definition m37init.F:34