OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
sgcoor3.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!|| sgcoor3 ../engine/source/elements/solid/solide/sgcoor3.F
25!||--- called by ------------------------------------------------------
26!|| s4forc3 ../engine/source/elements/solid/solide4/s4forc3.F
27!|| s8eforc3 ../engine/source/elements/solid/solide8e/s8eforc3.F
28!|| s8zforc3 ../engine/source/elements/solid/solide8z/s8zforc3.F
29!|| sforc3 ../engine/source/elements/solid/solide/sforc3.F
30!|| szforc3 ../engine/source/elements/solid/solidez/szforc3.F
31!||====================================================================
32 SUBROUTINE sgcoor3(
33 1 TIME, NPE, X, IXS,
34 2 X0, Y0, Z0, VX0,
35 3 VY0, VZ0, SAV, D,
36 4 OFF, OFF0, NEL, XDP,
37 5 MTN, ISMSTR)
38C-----------------------------------------------
39C I m p l i c i t T y p e s
40C-----------------------------------------------
41#include "implicit_f.inc"
42C-----------------------------------------------
43C G l o b a l P a r a m e t e r s
44C-----------------------------------------------
45#include "mvsiz_p.inc"
46C-----------------------------------------------
47C C o m m o n B l o c k s
48C-----------------------------------------------
49#include "scr18_c.inc"
50#include "scr05_c.inc"
51C-----------------------------------------------
52C D u m m y A r g u m e n t s
53C-----------------------------------------------
54 INTEGER, INTENT(IN) :: MTN
55 INTEGER, INTENT(IN) :: ISMSTR
56 INTEGER NPE,NEL
57 INTEGER IXS(NIXS,*)
58C REAL
60 . x(3,*),time,d(3,*),off(*),off0(*),
61 . vx0(mvsiz,npe),vy0(mvsiz,npe),vz0(mvsiz,npe)
62 DOUBLE PRECISION
63 . X0(MVSIZ,NPE), Y0(MVSIZ,NPE), Z0(MVSIZ,NPE),
64 . sav(nel,3*(npe-1)),xdp(3,*),xd,yd,zd
65C-----------------------------------------------
66C L o c a l V a r i a b l e s
67C-----------------------------------------------
68 INTEGER I,NPE1,N,N2,N3
69 INTEGER NC(MVSIZ,NPE)
70C REAL
71C-----------------------------------------------
72C
73 npe1=npe-1
74 IF (npe==4) THEN
75 DO i=1,nel
76 nc(i,1)=ixs(2,i)
77 nc(i,2)=ixs(4,i)
78 nc(i,3)=ixs(7,i)
79 nc(i,4)=ixs(6,i)
80 ENDDO
81 ELSE
82 DO n=1,npe
83 DO i=1,nel
84 nc(i,n)=ixs(n+1,i)
85 ENDDO
86 ENDDO
87 ENDIF
88C----------------------------
89C NODAL COORDINATES INITIALES |
90C----------------------------
91 DO n=1,npe1
92 n2 = n + npe1
93 n3 = n2 + npe1
94 DO i=1,nel
95 x0(i,n)=sav(i,n)
96 y0(i,n)=sav(i,n2)
97 z0(i,n)=sav(i,n3)
98 ENDDO
99 ENDDO
100C--------ISMSTR == 12 diff format of SAV
101 IF (ismstr == 12.AND.idtmin(1)==3 .AND.mtn==1) THEN
102 DO n=1,npe1
103 n2 = 3*(n-1)+1
104 DO i=1,nel
105 IF (off(i) <= one ) cycle
106 x0(i,n)=sav(i,n2)
107 y0(i,n)=sav(i,n2+1)
108 z0(i,n)=sav(i,n2+2)
109 ENDDO
110 ENDDO
111 END IF !(ISMSTR == 12.AND.IDTMIN(1)==3) THEN
112C----------------------------
113C DISPLACEMENT |
114C----------------------------
115 IF(iresp==1)THEN
116 DO n=1,npe1
117 DO i=1,nel
118 n2 = nc(i,n)
119 n3 = nc(i,npe)
120 xd =xdp(1,n2)-xdp(1,n3)-x0(i,n)
121 yd =xdp(2,n2)-xdp(2,n3)-y0(i,n)
122 zd =xdp(3,n2)-xdp(3,n3)-z0(i,n)
123 vx0(i,n) = xd
124 vy0(i,n) = yd
125 vz0(i,n) = zd
126 ENDDO
127 ENDDO
128 ELSE
129 DO n=1,npe1
130 DO i=1,nel
131 n2 = nc(i,n)
132 n3 = nc(i,npe)
133 vx0(i,n)=x(1,n2)-x(1,n3)-x0(i,n)
134 vy0(i,n)=x(2,n2)-x(2,n3)-y0(i,n)
135 vz0(i,n)=x(3,n2)-x(3,n3)-z0(i,n)
136 ENDDO
137 ENDDO
138 END IF !(IRESP==1)THEN
139C
140 DO i=1,nel
141 x0(i,npe)=zero
142 y0(i,npe)=zero
143 z0(i,npe)=zero
144 vx0(i,npe)=zero
145 vy0(i,npe)=zero
146 vz0(i,npe)=zero
147 ENDDO
148C
149 IF (ismstr == 12.AND.idtmin(1)==3) THEN
150 DO i=1,nel
151 off0(i)=off(i)
152 ENDDO
153C-------law1 special two increment
154 IF (mtn/=1) THEN
155 DO n=1,npe1
156 DO i=1,nel
157 IF (off(i) <= one ) cycle
158 vx0(i,n)=d(1,nc(i,n))-d(1,nc(i,npe))
159 vy0(i,n)=d(2,nc(i,n))-d(2,nc(i,npe))
160 vz0(i,n)=d(3,nc(i,n))-d(3,nc(i,npe))
161 ENDDO
162 ENDDO
163 DO n=1,npe1
164 n2 = 3*(n-1)+1
165 DO i=1,nel
166 IF (off(i) <= one ) cycle
167 x0(i,n)=sav(i,n2)
168 y0(i,n)=sav(i,n2+1)
169 z0(i,n)=sav(i,n2+2)
170 ENDDO
171 ENDDO
172 END IF
173 END IF !(ISMSTR == 10.AND.IDTMIN(1)==3) THEN
174C
175 RETURN
176 END
#define my_real
Definition cppsort.cpp:32
subroutine sgcoor3(time, npe, x, ixs, x0, y0, z0, vx0, vy0, vz0, sav, d, off, off0, nel, xdp, mtn, ismstr)
Definition sgcoor3.F:38