OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
s10cndv.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!|| s10cndv ../engine/source/elements/solid/solide10/s10cndv.F
25!||--- called by ------------------------------------------------------
26!|| resol ../engine/source/engine/resol.F
27!||====================================================================
28 SUBROUTINE s10cndv(ICNDS10 ,VND ,V )
29C-----------------------------------------------
30C I m p l i c i t T y p e s
31C-----------------------------------------------
32#include "implicit_f.inc"
33C-----------------------------------------------
34C C o m m o n B l o c k s
35C-----------------------------------------------
36#include "com04_c.inc"
37C-----------------------------------------------
38C D u m m y A r g u m e n t s
39C-----------------------------------------------
40 INTEGER ICNDS10(3,*)
42 . v(3,*),vnd(3,*)
43C-----------------------------------------------
44C L o c a l V a r i a b l e s
45C-----------------------------------------------
46 INTEGER I,ND,N1,N2
48 . vx,vy,vz
49C======================================================================|
50 DO i=1,ns10e
51 nd = icnds10(1,i)
52 n1 = icnds10(2,i)
53 n2 = icnds10(3,i)
54 vx = half*(v(1,n1) + v(1,n2))
55 vy = half*(v(2,n1) + v(2,n2))
56 vz = half*(v(3,n1) + v(3,n2))
57 IF (nd<0) THEN
58 nd = -nd
59 v(1,nd) = vx
60 v(2,nd) = vy
61 v(3,nd) = vz
62 ELSE
63 v(1,nd) = v(1,nd)-vnd(1,i) + vx
64 v(2,nd) = v(2,nd)-vnd(2,i) + vy
65 v(3,nd) = v(3,nd)-vnd(3,i) + vz
66 END IF
67 vnd(1,i) = vx
68 vnd(2,i) = vy
69 vnd(3,i) = vz
70 END DO
71C----6---------------------------------------------------------------7---------8
72 RETURN
73 1005 FORMAT(3x,1pe10.3)
74 END
75!||====================================================================
76!|| s10mvnd ../engine/source/elements/solid/solide10/s10cndv.F
77!||--- called by ------------------------------------------------------
78!|| sortie_main ../engine/source/output/sortie_main.F
79!||====================================================================
80 SUBROUTINE s10mvnd(ICNDS10 ,VND ,V )
81C-----------------------------------------------
82C I m p l i c i t T y p e s
83C-----------------------------------------------
84#include "implicit_f.inc"
85C-----------------------------------------------
86C C o m m o n B l o c k s
87C-----------------------------------------------
88#include "com04_c.inc"
89C-----------------------------------------------
90C D u m m y A r g u m e n t s
91C-----------------------------------------------
92 INTEGER ICNDS10(3,*)
94 . v(3,*),vnd(3,*)
95C-----------------------------------------------
96C L o c a l V a r i a b l e s
97C-----------------------------------------------
98 INTEGER I,ND,N1,N2
100 . vx,vy,vz
101C======================================================================|
102C---relative velocity for KE compute----
103 DO i=1,ns10e
104 nd = icnds10(1,i)
105 IF (nd>0) THEN
106 v(1,nd) = v(1,nd)-vnd(1,i)
107 v(2,nd) = v(2,nd)-vnd(2,i)
108 v(3,nd) = v(3,nd)-vnd(3,i)
109 ELSEIF (nd<0) THEN
110 nd = -nd
111 v(1,nd) = zero
112 v(2,nd) = zero
113 v(3,nd) = zero
114 END IF
115 END DO
116C----6---------------------------------------------------------------7---------8
117 RETURN
118 END
119!||====================================================================
120!|| s10prtv ../engine/source/elements/solid/solide10/s10cndv.F
121!||====================================================================
122 SUBROUTINE s10prtv(ICNDS10 ,V ,itab)
123C-----------------------------------------------
124C I m p l i c i t T y p e s
125C-----------------------------------------------
126#include "implicit_f.inc"
127C-----------------------------------------------
128C C o m m o n B l o c k s
129C-----------------------------------------------
130#include "com04_c.inc"
131#include "units_c.inc"
132C-----------------------------------------------
133C D u m m y A r g u m e n t s
134C-----------------------------------------------
135 INTEGER ICNDS10(3,*),itab(*)
136 my_real
137 . v(3,*)
138C-----------------------------------------------
139C L o c a l V a r i a b l e s
140C-----------------------------------------------
141 INTEGER I,ND,N1,N2
142C======================================================================|
143 DO i=1,ns10e
144 nd = iabs(icnds10(1,i))
145 n1 = icnds10(2,i)
146 n2 = icnds10(3,i)
147 write(iout,*)'ND,N1,N2,ND_id,I=',itab(nd),itab(n1),itab(n2),icnds10(1,i),i
148 write(iout,*)v(1,nd),v(1,n1) , v(1,n2)
149 write(iout,*)v(2,nd),v(2,n1) , v(2,n2)
150 write(iout,*)v(3,nd),v(3,n1) , v(3,n2)
151 END DO
152C----6---------------------------------------------------------------7---------8
153 RETURN
154 END
155!||====================================================================
156!|| s10cndi2a ../engine/source/elements/solid/solide10/s10cndv.F
157!||--- called by ------------------------------------------------------
158!|| resol ../engine/source/engine/resol.F
159!||====================================================================
160 SUBROUTINE s10cndi2a(ICNDS10 ,ITAGND ,A )
161C-----------------------------------------------
162C I m p l i c i t T y p e s
163C-----------------------------------------------
164#include "implicit_f.inc"
165C-----------------------------------------------
166C C o m m o n B l o c k s
167C-----------------------------------------------
168#include "com04_c.inc"
169C-----------------------------------------------
170C D u m m y A r g u m e n t s
171C-----------------------------------------------
172 INTEGER ICNDS10(3,*),ITAGND(*)
173 my_real
174 . a(3,*)
175C-----------------------------------------------
176C L o c a l V a r i a b l e s
177C-----------------------------------------------
178 INTEGER I,ND,N1,N2
179 my_real
180 . ax,ay,az
181C======================================================================|
182C----for Nd as main of int2 only; Ad-> acce absolu
183 DO i=1,ns10e
184 nd = icnds10(1,i)
185 IF (iabs(itagnd(iabs(nd)))>ns10e) THEN
186 n1 = icnds10(2,i)
187 n2 = icnds10(3,i)
188 ax = half*(a(1,n1) + a(1,n2))
189 ay = half*(a(2,n1) + a(2,n2))
190 az = half*(a(3,n1) + a(3,n2))
191 IF (nd<0) THEN
192 nd = -nd
193 a(1,nd) = ax
194 a(2,nd) = ay
195 a(3,nd) = az
196 ELSE
197 a(1,nd) = a(1,nd) + ax
198 a(2,nd) = a(2,nd) + ay
199 a(3,nd) = a(3,nd) + az
200 END IF
201 END IF !(IABS(ITAGND(IABS(ND)))>NS10E) THEN
202 END DO
203C----6---------------------------------------------------------------7---------8
204 RETURN
205 END
206!||====================================================================
207!|| s10cndi2a1 ../engine/source/elements/solid/solide10/s10cndv.F
208!||--- called by ------------------------------------------------------
209!|| resol ../engine/source/engine/resol.F
210!||====================================================================
211 SUBROUTINE s10cndi2a1(ICNDS10 ,ITAGND ,A )
212C-----------------------------------------------
213C I m p l i c i t T y p e s
214C-----------------------------------------------
215#include "implicit_f.inc"
216C-----------------------------------------------
217C C o m m o n B l o c k s
218C-----------------------------------------------
219#include "com04_c.inc"
220C-----------------------------------------------
221C D u m m y A r g u m e n t s
222C-----------------------------------------------
223 INTEGER ICNDS10(3,*),ITAGND(*)
224C REAL
225 my_real
226 . a(3,*)
227C-----------------------------------------------
228C L o c a l V a r i a b l e s
229C-----------------------------------------------
230 INTEGER I,ND,N1,N2
231C REAL
232 my_real
233 . ax,ay,az
234C======================================================================|
235C----for Nd as main of int2 only; Ad-> acce relative
236 DO i=1,ns10e
237 nd = icnds10(1,i)
238 IF (nd>0.AND.iabs(itagnd(iabs(nd)))>ns10e) THEN
239 n1 = icnds10(2,i)
240 n2 = icnds10(3,i)
241 ax = half*(a(1,n1) + a(1,n2))
242 ay = half*(a(2,n1) + a(2,n2))
243 az = half*(a(3,n1) + a(3,n2))
244 a(1,nd) = a(1,nd) - ax
245 a(2,nd) = a(2,nd) - ay
246 a(3,nd) = a(3,nd) - az
247 END IF !(IABS(ITAGND(IABS(ND)))>NS10E) THEN
248 END DO
249C----6---------------------------------------------------------------7---------8
250 RETURN
251 END
252!||====================================================================
253!|| s10getvdm ../engine/source/elements/solid/solide10/s10cndv.F
254!||--- called by ------------------------------------------------------
255!|| resol ../engine/source/engine/resol.F
256!||====================================================================
257 SUBROUTINE s10getvdm(ICNDS10 ,V,VND,VMD)
258C-----------------------------------------------
259C I m p l i c i t T y p e s
260C-----------------------------------------------
261#include "implicit_f.inc"
262C-----------------------------------------------
263C C o m m o n B l o c k s
264C-----------------------------------------------
265#include "com04_c.inc"
266C-----------------------------------------------
267C D u m m y A r g u m e n t s
268C-----------------------------------------------
269 INTEGER ICNDS10(3,*)
270C REAL
271 my_real
272 . v(3,*),vnd(3,*),vmd(3,*)
273C-----------------------------------------------
274C L o c a l V a r i a b l e s
275C-----------------------------------------------
276 INTEGER I,ND,N1,N2
277C REAL
278 my_real
279 . vx,vy,vz
280C======================================================================|
281 vmd(1:3,1:numnod) = v(1:3,1:numnod)
282 DO i=1,ns10e
283 nd = iabs(icnds10(1,i))
284 vmd(1:3,nd) = v(1:3,nd)-vnd(1:3,i)
285 END DO
286C----6---------------------------------------------------------------7---------8
287 RETURN
288 END SUBROUTINE s10getvdm
#define my_real
Definition cppsort.cpp:32
subroutine s10prtv(icnds10, v, itab)
Definition s10cndv.F:123
subroutine s10cndv(icnds10, vnd, v)
Definition s10cndv.F:29
subroutine s10mvnd(icnds10, vnd, v)
Definition s10cndv.F:81
subroutine s10getvdm(icnds10, v, vnd, vmd)
Definition s10cndv.F:258
subroutine s10cndi2a(icnds10, itagnd, a)
Definition s10cndv.F:161
subroutine s10cndi2a1(icnds10, itagnd, a)
Definition s10cndv.F:212