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

Go to the source code of this file.

Functions/Subroutines

subroutine nsvis_sm12 (offg, mu, ssp, vol, d1, d2, d3, d4, d5, d6, vol0, rho0, sti, nel, svis)

Function/Subroutine Documentation

◆ nsvis_sm12()

subroutine nsvis_sm12 ( intent(in) offg,
intent(in) mu,
intent(in) ssp,
intent(in) vol,
intent(in) d1,
intent(in) d2,
intent(in) d3,
intent(in) d4,
intent(in) d5,
intent(in) d6,
intent(in) vol0,
intent(in) rho0,
intent(inout) sti,
integer, intent(in) nel,
intent(inout) svis )

Definition at line 30 of file nsvis_sm12.F.

33C-----------------------------------------------
34C I m p l i c i t T y p e s
35C-----------------------------------------------
36#include "implicit_f.inc"
37C-----------------------------------------------
38C G l o b a l P a r a m e t e r s
39C-----------------------------------------------
40#include "mvsiz_p.inc"
41C-----------------------------------------------
42C D u m m y A r g u m e n t s
43C-----------------------------------------------
44C REAL
45 INTEGER, INTENT(IN) ::NEL
46 my_real, DIMENSION(MVSIZ),INTENT(IN) :: vol,
47 . d1, d2, d3,d4, d5, d6,ssp
48 my_real, DIMENSION(NEL),INTENT(IN) :: offg,vol0
49 my_real, DIMENSION(MVSIZ),INTENT(INOUT) :: sti
50 my_real, INTENT(IN) :: rho0,mu
51 my_real, DIMENSION(MVSIZ,6), INTENT(INOUT) :: svis
52C-----------------------------------------------
53C L o c a l V a r i a b l e s
54C-----------------------------------------------
55 INTEGER I, MT
56C REAL
58 . dd, al, cns1, cns2, cns3,
59 . dav, pvis, nrho,jac,fac,tol
60#ifdef MYREAL8
61 my_real, PARAMETER :: real_three = 3.0d0
62 my_real, PARAMETER :: real_one = 1.0d0
63#else
64 my_real, PARAMETER :: real_three = 3.0
65 my_real, PARAMETER :: real_one = 1.0
66#endif
67C-----------------------------------------------
68 tol = one-em02
69 IF (mu>zero) THEN
70 DO i=1,nel
71 jac = vol(i)/vol0(i)
72 IF (offg(i)<=one.OR.jac>tol) cycle
73 al = vol(i)**(real_one/real_three)
74 nrho = rho0/jac
75 cns2=mu*al*nrho*ssp(i)
76 cns3=half*cns2
77 dd =-d1(i)-d2(i)-d3(i)
78 dav=dd * third
79 svis(i,1)=svis(i,1) + cns2 *(d1(i)+dav)
80 svis(i,2)=svis(i,2) + cns2 *(d2(i)+dav)
81 svis(i,3)=svis(i,3) + cns2 *(d3(i)+dav)
82 svis(i,4)=svis(i,4) + cns3 * d4(i)
83 svis(i,5)=svis(i,5) + cns3 * d5(i)
84 svis(i,6)=svis(i,6) + cns3 * d6(i)
85 ENDDO
86 END IF !(MU>ZERO) THEN
87C
88 RETURN
#define my_real
Definition cppsort.cpp:32