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