OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
inigrav_m37.F File Reference
#include "implicit_f.inc"
#include "param_c.inc"
#include "com01_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine inigrav_m37 (nelg, nel, ng, matid, ipm, grav0, depth, pm, bufmat, elbuf_tab, psurf, list)

Function/Subroutine Documentation

◆ inigrav_m37()

subroutine inigrav_m37 ( integer, intent(in) nelg,
integer, intent(in) nel,
integer, intent(in) ng,
integer, intent(in) matid,
integer, dimension(npropmi, *), intent(in) ipm,
intent(in) grav0,
dimension(*), intent(in) depth,
dimension(npropm, *), intent(in) pm,
dimension(*), intent(in) bufmat,
type(elbuf_struct_), dimension(ngroup), intent(in), target elbuf_tab,
intent(inout) psurf,
integer, dimension(nel), intent(in) list )

Definition at line 29 of file inigrav_m37.F.

30C-----------------------------------------------
31C M o d u l e s
32C-----------------------------------------------
33 USE elbufdef_mod
34C-----------------------------------------------
35C I m p l i c i t T y p e s
36C-----------------------------------------------
37#include "implicit_f.inc"
38C-----------------------------------------------
39C C o m m o n B l o c k s
40C-----------------------------------------------
41! NPROPMI, NPROPM
42#include "param_c.inc"
43! NGROUP
44#include "com01_c.inc"
45C-----------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER, INTENT(IN) :: NEL, NG, MATID, IPM(NPROPMI, *), LIST(NEL),NELG
49 my_real, INTENT(IN) :: grav0, depth(*), pm(npropm, *), bufmat(*)
50 my_real, INTENT(INOUT) :: psurf
51 TYPE(ELBUF_STRUCT_), DIMENSION(NGROUP), TARGET, INTENT(IN) :: ELBUF_TAB
52C-----------------------------------------------
53C L o c a l V a r i a b l e s
54C-----------------------------------------------
55 INTEGER :: I,ISOLVER, K
56 my_real :: r1, c1, p0, pgrav, rho10, rho20, rho1, rho2, gam, rho0,
57 . alpha1, alpha2,psh
58 TYPE(G_BUFEL_), POINTER :: GBUF
59 TYPE(BUF_MAT_) ,POINTER :: MBUF
60C-----------------------------------------------
61C S o u r c e L i n e s
62C-----------------------------------------------
63
64C LIST IS SUBGROUP TO TREAT : ONLY ELEM WITH RELEVANT PARTS ARE KEPT
65C NEL IS ISEZ OF LIST
66C NELG IS SIZE OF ORIGINAL GROUP : needed to shift indexes in GBUF%SIG & MBUF%VAR
67
68C Global buffer
69 gbuf => elbuf_tab(ng)%GBUF
70C Material buffer
71 mbuf => elbuf_tab(ng)%BUFLY(1)%MAT(1,1,1)
72C EOS parameters, common
73 p0 = bufmat(9)
74 psh= bufmat(16)
75C EOS parameters mat 1:
76 rho10 = bufmat(11)
77 c1 = bufmat(4)
78 r1 = bufmat(6)
79C EOS parameters mat2:
80 gam = bufmat(5)
81 rho20 = bufmat(12)
82 isolver = bufmat(17)
83
84 IF(psurf==zero .AND. isolver<=1)THEN
85 psurf=p0 !historical solver requires a total pressure formulation
86 print *, "**WARNING : INIGRAV CARD, PREF PARAMETER MUST BE A TOTAL PRESSURE WITH LAW37, SETTING PREF=P0"
87 ENDIF
88
89 DO k = 1, nel
90 i = list(k)
91 alpha1 = mbuf%VAR(i + (4 - 1) * nelg)
92 alpha2 = one - alpha1
93 rho0 = alpha1 * rho10 + alpha2 * rho20
94 pgrav = psurf - rho0 * grav0 * depth(k)
95 rho1 = (pgrav-p0)/r1 + rho10
96 rho2 = rho20 * (pgrav/p0) ** (one / gam)
97 gbuf%RHO(i) = alpha1 * rho1 + alpha2 * rho2
98 mbuf%VAR(i + (4 - 1) * nelg) = alpha1
99 mbuf%VAR(i + (5 - 1) * nelg) = one - alpha1
100 mbuf%VAR(i + (2 - 1) * nelg) = rho2
101 mbuf%VAR(i + (3 - 1) * nelg) = rho1
102 mbuf%VAR(i + (1 - 1) * nelg) = alpha1 * rho1
103 gbuf%SIG(i) = - (pgrav-p0-psh)
104 gbuf%SIG(i + nelg) = - (pgrav-p0-psh)
105 gbuf%SIG(i + 2 * nelg) = - (pgrav-p0-psh)
106 ENDDO
107
#define my_real
Definition cppsort.cpp:32
#define alpha2
Definition eval.h:48