OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
nsvisul.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!|| nsvisul ../engine/source/materials/mat_share/nsvisul.F
25!||--- called by ------------------------------------------------------
26!|| mulaw ../engine/source/materials/mat_share/mulaw.F90
27!|| usermat_solid ../engine/source/materials/mat_share/usermat_solid.F
28!||====================================================================
29 SUBROUTINE nsvisul(NEL ,OFF ,RHO ,GEO ,
30 2 PID ,SSP ,AIRE ,VOL ,D1 ,
31 3 D2 ,D3 ,D4 ,D5 ,D6 ,
32 4 SV1 ,SV2 ,SV3 ,SV4 ,SV5 ,
33 5 SV6 ,S3 ,E3 ,RHO0,RHOREF)
34C-----------------------------------------------
35C I m p l i c i t T y p e s
36C-----------------------------------------------
37#include "implicit_f.inc"
38C-----------------------------------------------
39C G l o b a l P a r a m e t e r s
40C-----------------------------------------------
41#include "mvsiz_p.inc"
42C-----------------------------------------------
43C C o m m o n B l o c k s
44C-----------------------------------------------
45#include "com01_c.inc"
46#include "param_c.inc"
47C-----------------------------------------------
48C D u m m y A r g u m e n t s
49C-----------------------------------------------
50 INTEGER NEL
51 INTEGER PID(*)
52 my_real
53 . OFF(*), RHO(*),GEO(NPROPG,*), SSP(*),
54 . aire(*), vol(*), d1(*), d2(*), d3(*),
55 . d4(*), d5(*), d6(*),sv1(*), sv2(*), sv3(*),
56 . sv4(*), sv5(*), sv6(*),s3(*),e3(*),rho0(*),rhoref(*)
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60 INTEGER I
61 my_real
62 . DD(MVSIZ), AL(MVSIZ), NRHO(MVSIZ), CNS1, CNS2, CNS3, DAV, PVIS
63c=======================================================================
64 dd(1:nel)=-d1(1:nel)-d2(1:nel)-d3(1:nel)
65C
66 IF(n2d > 0) THEN
67 DO i=1,nel
68 al(i)=zero
69 IF(off(i) >= one)al(i)=sqrt(aire(i))
70 ENDDO
71 ELSE
72 DO i=1,nel
73 al(i)=zero
74 IF(off(i) >= one) al(i)=exp(third*log(vol(i)))
75 ENDDO
76 ENDIF
77C-----------------------------------------------
78C Large strain :: Critical damping D = L * rho * c, c = sqrt(A11/rho)
79C BUT c is computed as sqrt(A11/rho0) for most of the materials
80C <=> D = L * sqrt(rho) * sqrt(rho0) * sqrt(A11/rho0)
81C Note : if for a given material, c is computed as sqrt(A11/rho),
82C ---- then damping will result in L * sqrt(rho) * sqrt(rho0) * c
83C and will be in the ratio sqrt(rho0) / sqrt(rho) wrt critical damping
84C < 1 in compression
85C > 1 in tension
86C this ratio will be more likely limited.
87C
88C Small strain :: Critical damping D = L * rhoref * c, c = sqrt(A11/rhoref)
89C BUT c is computed as sqrt(A11/rho0) for most of the materials
90C <=> D = L * sqrt(rhoref) * sqrt(rho0) * sqrt(A11/rho0)
91C
92C-----------------------------------------------
93 DO i=1,nel
94 nrho(i) = sqrt(rhoref(i)*rho0(i))
95 ENDDO
96C
97 IF(geo(16,pid(1)) >= zero)THEN
98 DO i=1,nel
99 cns1=geo(16,pid(1))*al(i)*nrho(i)*ssp(i)*off(i)
100 cns2=geo(17,pid(1))*al(i)*nrho(i)*ssp(i)*off(i)
101 cns3=half*cns2
102 dav=dd(i) * third
103 pvis=-cns1*dd(i)
104 sv1(i)= sv1(i) + cns2 *(d1(i)+dav)+pvis
105 sv2(i)= sv2(i) + cns2 *(d2(i)+dav)+pvis
106 sv3(i)= sv3(i) + cns2 *(d3(i)+dav)+pvis
107 sv4(i)= sv4(i) + cns3 * d4(i)
108 sv5(i)= sv5(i) + cns3 * d5(i)
109 sv6(i)= sv6(i) + cns3 * d6(i)
110C IF(GEO(16,PID(I)) /= ZERO .OR. GEO(17,PID(I))/=ZERO) ISVIS = 1
111 ENDDO
112 ELSE
113 DO i=1,nel
114 cns1=geo(16,pid(1))*nrho(i)*ssp(i)**2*off(i)
115 cns2=geo(17,pid(1))*nrho(i)*ssp(i)**2*off(i)
116 cns3=half*cns2
117 dav=dd(i) * third
118 pvis=-cns1*dd(i)
119 sv1(i)= sv1(i) + cns2 *(d1(i)+dav)+pvis
120 sv2(i)= sv2(i) + cns2 *(d2(i)+dav)+pvis
121 sv3(i)= sv3(i) + cns2 *(d3(i)+dav)+pvis
122 sv4(i)= sv4(i) + cns3 * d4(i)
123 sv5(i)= sv5(i) + cns3 * d5(i)
124 sv6(i)= sv6(i) + cns3 * d6(i)
125C IF(GEO(16,PID(I)) /= ZERO .OR. GEO(17,PID(I))/=ZERO) ISVIS = 1
126 ENDDO
127 END IF
128C
129 RETURN
130 END
subroutine nsvisul(nel, off, rho, geo, pid, ssp, aire, vol, d1, d2, d3, d4, d5, d6, sv1, sv2, sv3, sv4, sv5, sv6, s3, e3, rho0, rhoref)
Definition nsvisul.F:34