OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i6damp.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!|| i6damp ../engine/source/interfaces/inter3d/i6damp.f
25!||--- called by ------------------------------------------------------
26!|| i6main ../engine/source/interfaces/inter3d/i6main.F
27!||--- calls -----------------------------------------------------
28!|| ninterp ../engine/source/interfaces/int14/ninterp.F
29!||====================================================================
30 SUBROUTINE i6damp(
31 1 V, NPC, TF, IRECT,
32 2 MSR, NSV, IRTL, IRTLO,
33 3 CST, ES, EM, VISC,
34 4 NDAMP1, NDAMP2, LOLD, MASS,
35 5 VNI, ASCALF, ASCALV, FSCALV,
36 6 H1, H2, H3, H4,
37 7 FNI, FXI, FYI, FZI,
38 8 FX1, FX2, FX3, FX4,
39 9 FY1, FY2, FY3, FY4,
40 A FZ1, FZ2, FZ3, FZ4,
41 B LFT, LLT, NFT)
42C-----------------------------------------------
43C I m p l i c i t T y p e s
44C-----------------------------------------------
45#include "implicit_f.inc"
46C-----------------------------------------------
47C G l o b a l P a r a m e t e r s
48C-----------------------------------------------
49#include "mvsiz_p.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 INTEGER, INTENT(INOUT) :: LFT
54 INTEGER, INTENT(INOUT) :: LLT
55 INTEGER, INTENT(INOUT) :: NFT
56 INTEGER NDAMP1 ,NDAMP2
57 INTEGER IRECT(4,*),MSR(*),NSV(*),IRTL(*),IRTLO(*),NPC(*),LOLD(*)
58C REAL
59 my_real
60 . VISC,ASCALF,ASCALV,FSCALV
61 my_real
62 . V(3,*),CST(2,*),ES(*),EM(*),TF(*),MASS(*),VNI(*)
63 my_real, DIMENSION(MVSIZ), INTENT(IN) :: H1,H2,H3,H4,FNI
64 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: fxi,fyi,fzi
65 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: fx1,fx2,fx3,fx4
66 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: fy1,fy2,fy3,fy4
67 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: fz1,fz2,fz3,fz4
68C-----------------------------------------------
69C C o m m o n B l o c k s
70C-----------------------------------------------
71C-----------------------------------------------
72C L o c a l V a r i a b l e s
73C-----------------------------------------------
74 INTEGER I,IG,IL, L, J3, J2, J1, I3, I2, I1
75C REAL
76 my_real
77 . fdamp
78 my_real
79 . vis(llt),viscv(llt),fact(llt),xx(llt)
80C-----------------------------------------------
81C Coefficient d'amortissement
82C--------------------------------
83 IF (ndamp1 > 0) THEN ! velocity function
84 DO i=lft,llt
85 xx(i) = vni(i)*ascalv
86 ENDDO
87 CALL ninterp(ndamp1,npc,tf,llt,xx,viscv)
88 ELSE
89 viscv(1:llt) = zero
90 ENDIF
91c
92 IF (ndamp2 > 0) THEN ! Force amplification factor
93 DO i=lft,llt
94 xx(i) = fni(i)*ascalf
95 ENDDO
96 CALL ninterp(ndamp2,npc,tf,llt,xx,fact)
97 ELSE
98 fact(1:llt) = one
99 ENDIF
100C--------------------------------
101 DO i=lft,llt
102 il = i+nft
103 fxi(i) = zero
104 fyi(i) = zero
105 fzi(i) = zero
106c
107 IF (lold(i) /= 0) THEN
108 ig = nsv(il)
109 l = irtl(il)
110c
111 fdamp = - (visc*vni(i) + fscalv*viscv(i))*fact(i)
112c
113c FXI(I) = N1(I)*FDAMP
114c FYI(I) = N2(I)*FDAMP
115c FZI(I) = N3(I)*FDAMP
116 fxi(i) = fdamp
117 fyi(i) = fdamp
118 fzi(i) = fdamp
119c
120 fx1(i)=fxi(i)*h1(i)
121 fy1(i)=fyi(i)*h1(i)
122 fz1(i)=fzi(i)*h1(i)
123C
124 fx2(i)=fxi(i)*h2(i)
125 fy2(i)=fyi(i)*h2(i)
126 fz2(i)=fzi(i)*h2(i)
127C
128 fx3(i)=fxi(i)*h3(i)
129 fy3(i)=fyi(i)*h3(i)
130 fz3(i)=fzi(i)*h3(i)
131C
132 fx4(i)=fxi(i)*h4(i)
133 fy4(i)=fyi(i)*h4(i)
134 fz4(i)=fzi(i)*h4(i)
135c
136c Force visc main
137c
138 j3=3*irect(1,l)
139 j2=j3-1
140 j1=j2-1
141 em(j1)=em(j1)+fx1(i)
142 em(j2)=em(j2)+fy1(i)
143 em(j3)=em(j3)+fz1(i)
144C
145 j3=3*irect(2,l)
146 j2=j3-1
147 j1=j2-1
148 em(j1)=em(j1)+fx2(i)
149 em(j2)=em(j2)+fy2(i)
150 em(j3)=em(j3)+fz2(i)
151C
152 j3=3*irect(3,l)
153 j2=j3-1
154 j1=j2-1
155 em(j1)=em(j1)+fx3(i)
156 em(j2)=em(j2)+fy3(i)
157 em(j3)=em(j3)+fz3(i)
158C
159 j3=3*irect(4,l)
160 j2=j3-1
161 j1=j2-1
162 em(j1)=em(j1)+fx4(i)
163 em(j2)=em(j2)+fy4(i)
164 em(j3)=em(j3)+fz4(i)
165c
166c Force visc secnd
167c
168 i3 = 3*il
169 i2 = i3-1
170 i1 = i2-1
171 es(i1) = es(i1)-fxi(i)
172 es(i2) = es(i2)-fyi(i)
173 es(i3) = es(i3)-fzi(i)
174c
175 ENDIF ! LOLD
176C
177 ENDDO ! I=LFT,LLT
178C-----------
179 RETURN
180 END
subroutine i6damp(v, npc, tf, irect, msr, nsv, irtl, irtlo, cst, es, em, visc, ndamp1, ndamp2, lold, mass, vni, ascalf, ascalv, fscalv, h1, h2, h3, h4, fni, fxi, fyi, fzi, fx1, fx2, fx3, fx4, fy1, fy2, fy3, fy4, fz1, fz2, fz3, fz4, lft, llt, nft)
Definition i6damp.F:42
subroutine ninterp(ifunc, npc, pld, npoint, xv, yv)
Definition ninterp.F:32