OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
nsvis_stab11.F File Reference
#include "implicit_f.inc"
#include "mvsiz_p.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine nsvis_stab11 (sig, c1, g2, vol, d1, d2, d3, d4, d5, d6, rhoref, npg, nel)

Function/Subroutine Documentation

◆ nsvis_stab11()

subroutine nsvis_stab11 ( intent(inout) sig,
intent(in) c1,
intent(in) g2,
intent(in) vol,
intent(in) d1,
intent(in) d2,
intent(in) d3,
intent(in) d4,
intent(in) d5,
intent(in) d6,
intent(in) rhoref,
integer, intent(in) npg,
integer, intent(in) nel )

Definition at line 28 of file nsvis_stab11.F.

31C-----------------------------------------------
32C I m p l i c i t T y p e s
33C-----------------------------------------------
34#include "implicit_f.inc"
35C-----------------------------------------------
36C G l o b a l P a r a m e t e r s
37C-----------------------------------------------
38#include "mvsiz_p.inc"
39C-----------------------------------------------
40C C o m m o n B l o c k s
41C-----------------------------------------------
42C-----------------------------------------------
43C D u m m y A r g u m e n t s
44C-----------------------------------------------
45C REAL
46 INTEGER, INTENT(IN) ::NEL,NPG
47 my_real, DIMENSION(MVSIZ),INTENT(IN) :: vol,
48 . d1, d2, d3,d4, d5, d6,rhoref
49 my_real, INTENT(IN) :: c1,g2
50 my_real, DIMENSION(NEL,6), INTENT(INOUT) :: sig
51C-----------------------------------------------
52C L o c a l V a r i a b l e s
53C-----------------------------------------------
54 INTEGER I, MT
55C REAL
57 . dd, al, cns1, cns2, cns3,ssp1,mu,
58 . dav, pvis, nrho,jac,fac,tol,ff,rhossp,facg
59#ifdef MYREAL8
60 my_real, PARAMETER :: real_three = 3.0d0
61 my_real, PARAMETER :: real_one = 1.0d0
62#else
63 my_real, PARAMETER :: real_three = 3.0
64 my_real, PARAMETER :: real_one = 1.0
65#endif
66C-----------------------------------------------
67 mu =zep02
68 ssp1 = two_third*g2+c1
69 DO i=1,nel
70 ff = -min(sig(i,1),sig(i,2),sig(i,3))
71 IF (two*ff <=g2 ) cycle
72 al = (npg*vol(i))**(real_one/real_three)
73 rhossp = sqrt(ssp1*rhoref(i))
74 cns2=mu*al*rhossp
75 cns3=half*cns2
76 dd =-d1(i)-d2(i)-d3(i)
77 dav=dd * third
78 sig(i,1)=sig(i,1) + cns2 *(d1(i)+dav)
79 sig(i,2)=sig(i,2) + cns2 *(d2(i)+dav)
80 sig(i,3)=sig(i,3) + cns2 *(d3(i)+dav)
81 sig(i,4)=sig(i,4) + cns3 * d4(i)
82 sig(i,5)=sig(i,5) + cns3 * d5(i)
83 sig(i,6)=sig(i,6) + cns3 * d6(i)
84 ENDDO
85C
86 RETURN
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20