OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
frho3.F File Reference
#include "implicit_f.inc"
#include "comlock.inc"
#include "mvsiz_p.inc"
#include "units_c.inc"
#include "scr06_c.inc"
#include "com08_c.inc"
#include "lockon.inc"
#include "lockoff.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine frho3 (uvar, rho0, dxx, dyy, dzz, flux, flu1, voln, ngl, mat, off, nel)

Function/Subroutine Documentation

◆ frho3()

subroutine frho3 ( target uvar,
rho0,
dxx,
dyy,
dzz,
flux,
flu1,
voln,
integer, dimension(*) ngl,
integer, dimension(*) mat,
off,
integer nel )

Definition at line 30 of file frho3.F.

32C-----------------------------------------------
33C M o d u l e s
34C-----------------------------------------------
35 USE ale_mod
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40#include "comlock.inc"
41C-----------------------------------------------
42C G l o b a l P a r a m e t e r s
43C-----------------------------------------------
44#include "mvsiz_p.inc"
45C-----------------------------------------------
46C C o m m o n B l o c k s
47C-----------------------------------------------
48#include "units_c.inc"
49#include "scr06_c.inc"
50#include "com08_c.inc"
51C-----------------------------------------------
52C D u m m y A r g u m e n t s
53C-----------------------------------------------
54 INTEGER NGL(*),MAT(*),NEL
55 my_real uvar(nel,*),flux(mvsiz,6), flu1(*), voln(*), dxx(*),dyy(*),dzz(*),off(*),rho0(*)
56 TARGET :: uvar
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 my_real dvv, e0(nel),vavg,rv,rvp
61 INTEGER I, J,COUNT,LIST(NEL),II
62 my_real, DIMENSION(:), POINTER :: volo,rhon,eint,dvol
63C-----------------------------------------------
64 rhon => uvar(1:nel,1)
65 eint => uvar(1:nel,2)
66 volo => uvar(1:nel,3)
67 dvol => uvar(1:nel,4)
68C
69C incompressible flow avoir plus en cas de besoin
70C INCOMP = 1 not tested
71 IF(ale%GLOBAL%INCOMP == 1)THEN
72 e0 = zero !
73 DO i=1,nel
74 dvv=dt1*(dxx(i)+dyy(i)+dzz(i))
75 rhon(i)=rhon(i)-dvv*rho0(i)
76 vavg=half*(voln(i)+volo(i))
77 dvol(i)=vavg*dvv
78 eint(i)=eint(i)*volo(i)-e0(i)*dvv*vavg
79 ENDDO
80C compresssible flow
81 ELSE
82 DO i=1,nel
83 rhon(i) = rhon(i)/voln(i)
84
85 dvol(i) = voln(i)
86 . - volo(i)+0.5*dt1*(flu1(i)+flux(i,1)+flux(i,2)
87 . + flux(i,3)+flux(i,4)+flux(i,5)+flux(i,6) )
88 volo(i)=voln(i)
89 rhon(i) = max(rhon(i) , em30)
90
91 ENDDO
92 ENDIF
93C
94 count=0
95 DO i=1,nel
96 IF(rhon(i) <= zero .AND. off(i)/= zero)THEN
97 count = count + 1
98 list(count)=i
99 ENDIF
100 ENDDO
101 DO ii=1,count
102 i=list(ii)
103#include "lockon.inc"
104 WRITE(iout,1000) ngl(i),rhon(i)
105 WRITE(istdo,1000) ngl(i),rhon(i)
106#include "lockoff.inc"
107 1000 FORMAT('-STOP GAZ ',i8,' HAS NEGATIVE RHO',g12.5)
108 ENDDO
109C
110 RETURN
#define my_real
Definition cppsort.cpp:32
#define max(a, b)
Definition macros.h:21
type(ale_) ale
Definition ale_mod.F:249