OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
s10get_x3.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!|| s10get_x3 ../engine/source/elements/solid/solide10/s10get_x3.F
25!||--- called by ------------------------------------------------------
26!|| s10forc3 ../engine/source/elements/solid/solide10/s10forc3.F
27!||====================================================================
28 SUBROUTINE s10get_x3(
29 1 X, XDP, DR, NUMNOD,
30 2 XX, YY, ZZ, NC,
31 3 ISROT, IRESP, NEL )
32C-----------------------------------------------
33C I m p l i c i t T y p e s
34C-----------------------------------------------
35#include "implicit_f.inc"
36C-----------------------------------------------
37C G l o b a l P a r a m e t e r s
38C-----------------------------------------------
39#include "mvsiz_p.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43C-----------------------------------------------
44C D u m m y A r g u m e n t s
45C-----------------------------------------------
46 INTEGER, INTENT(IN) :: ISROT,NUMNOD,IRESP,NEL
47 INTEGER, DIMENSION(MVSIZ,10), INTENT(IN) :: NC
48
49 my_real, DIMENSION(3,NUMNOD), INTENT(IN) :: x,dr
50 DOUBLE PRECISION, DIMENSION(3,NUMNOD), INTENT(IN) ::XDP
51 DOUBLE PRECISION, DIMENSION(MVSIZ,10), INTENT(INOUT) ::
52 . xx, yy, zz
53C-----------------------------------------------
54C L o c a l V a r i a b l e s
55C-----------------------------------------------
56 INTEGER I, IPERM1(10),IPERM2(10),N,N1,N2,NN,IUN,MXT_1
57C REAL
58 my_real
59 . dvx,dvy,dvz,dx,dy,dz
60 DATA iperm1/0,0,0,0,1,2,3,1,2,3/
61 DATA iperm2/0,0,0,0,2,3,1,4,4,4/
62C-----------------------------------------------
63C----------------------------
64C NODAL COORDINATES |
65C----------------------------
66 IF (iresp==1)THEN
67 DO n=1,4
68 DO i=1,nel
69 nn = nc(i,n)
70 xx(i,n)=xdp(1,nn)
71 yy(i,n)=xdp(2,nn)
72 zz(i,n)=xdp(3,nn)
73 END DO
74 END DO
75C
76 IF(isrot==0.OR.isrot==2)THEN
77 DO n=5,10
78 DO i=1,nel
79 nn = nc(i,n)
80 IF(nn/=0)THEN
81 xx(i,n)=xdp(1,nn)
82 yy(i,n)=xdp(2,nn)
83 zz(i,n)=xdp(3,nn)
84 ELSE
85 n1=iperm1(n)
86 n2=iperm2(n)
87 xx(i,n) = half*(xx(i,n1)+xx(i,n2))
88 yy(i,n) = half*(yy(i,n1)+yy(i,n2))
89 zz(i,n) = half*(zz(i,n1)+zz(i,n2))
90 END IF
91 END DO
92 END DO
93 ELSEIF(isrot==1)THEN
94 DO n=5,10
95 DO i=1,nel
96 nn = nc(i,n)
97 n1=iperm1(n)
98 n2=iperm2(n)
99 dx = (yy(i,n2)-yy(i,n1))*(dr(3,nc(i,n2))-dr(3,nc(i,n1)))
100 . - (zz(i,n2)-zz(i,n1))*(dr(2,nc(i,n2))-dr(2,nc(i,n1)))
101 dy = (zz(i,n2)-zz(i,n1))*(dr(1,nc(i,n2))-dr(1,nc(i,n1)))
102 . - (xx(i,n2)-xx(i,n1))*(dr(3,nc(i,n2))-dr(3,nc(i,n1)))
103 dz = (xx(i,n2)-xx(i,n1))*(dr(2,nc(i,n2))-dr(2,nc(i,n1)))
104 . - (yy(i,n2)-yy(i,n1))*(dr(1,nc(i,n2))-dr(1,nc(i,n1)))
105
106 xx(i,n) = half*(xx(i,n1)+xx(i,n2)) + one_over_8 * dx
107 yy(i,n) = half*(yy(i,n1)+yy(i,n2)) + one_over_8 * dy
108 zz(i,n) = half*(zz(i,n1)+zz(i,n2)) + one_over_8 * dz
109 END DO
110 END DO
111 END IF
112 ELSE !DP
113 DO n=1,4
114 DO i=1,nel
115 nn = nc(i,n)
116 xx(i,n)=x(1,nn)
117 yy(i,n)=x(2,nn)
118 zz(i,n)=x(3,nn)
119 END DO
120 END DO
121 IF(isrot==0.OR.isrot==2)THEN
122 DO n=5,10
123 DO i=1,nel
124 nn = nc(i,n)
125 IF(nn/=0)THEN
126 xx(i,n)=x(1,nn)
127 yy(i,n)=x(2,nn)
128 zz(i,n)=x(3,nn)
129 ELSE
130 n1=iperm1(n)
131 n2=iperm2(n)
132 xx(i,n) = half*(xx(i,n1)+xx(i,n2))
133 yy(i,n) = half*(yy(i,n1)+yy(i,n2))
134 zz(i,n) = half*(zz(i,n1)+zz(i,n2))
135 END IF
136 END DO
137 END DO
138 ELSEIF(isrot==1)THEN
139 DO n=5,10
140 DO i=1,nel
141 nn = nc(i,n)
142 n1=iperm1(n)
143 n2=iperm2(n)
144 dx = (yy(i,n2)-yy(i,n1))*(dr(3,nc(i,n2))-dr(3,nc(i,n1)))
145 . - (zz(i,n2)-zz(i,n1))*(dr(2,nc(i,n2))-dr(2,nc(i,n1)))
146 dy = (zz(i,n2)-zz(i,n1))*(dr(1,nc(i,n2))-dr(1,nc(i,n1)))
147 . - (xx(i,n2)-xx(i,n1))*(dr(3,nc(i,n2))-dr(3,nc(i,n1)))
148 dz = (xx(i,n2)-xx(i,n1))*(dr(2,nc(i,n2))-dr(2,nc(i,n1)))
149 . - (yy(i,n2)-yy(i,n1))*(dr(1,nc(i,n2))-dr(1,nc(i,n1)))
150
151 xx(i,n) = half*(xx(i,n1)+xx(i,n2)) + one_over_8 * dx
152 yy(i,n) = half*(yy(i,n1)+yy(i,n2)) + one_over_8 * dy
153 zz(i,n) = half*(zz(i,n1)+zz(i,n2)) + one_over_8 * dz
154 END DO
155 END DO
156 END IF
157 END IF ! (IRESP==1)THEN
158C-----------
159 RETURN
160 END
#define my_real
Definition cppsort.cpp:32
subroutine s10get_x3(x, xdp, dr, numnod, xx, yy, zz, nc, isrot, iresp, nel)
Definition s10get_x3.F:32