OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
s8coor3.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!|| s8coor3 ../engine/source/elements/solid/solide8/s8coor3.F
25!||--- called by ------------------------------------------------------
26!|| s8forc3 ../engine/source/elements/solid/solide8/s8forc3.f
27!||====================================================================
28 SUBROUTINE s8coor3(
29 1 OFFG, OFF, X, V,
30 2 IXS, XLOC, YLOC, ZLOC,
31 3 VXLOC, VYLOC, VZLOC, MXT,
32 4 NC, NGL, PID, NEL)
33C-----------------------------------------------
34C I m p l i c i t T y p e s
35C-----------------------------------------------
36#include "implicit_f.inc"
37C-----------------------------------------------
38C G l o b a l P a r a m e t e r s
39C-----------------------------------------------
40#include "mvsiz_p.inc"
41C-----------------------------------------------
42C D u m m y A r g u m e n t s
43C-----------------------------------------------
44 INTEGER, INTENT(IN) :: NEL
45 INTEGER IXS(11,*)
46 my_real X(3,*),V(3,*),OFFG(*),OFF(*)
47 my_real XLOC(MVSIZ,8), YLOC(MVSIZ,8), ZLOC(MVSIZ,8), VXLOC(MVSIZ,8),VYLOC(MVSIZ,8),VZLOC(MVSIZ,8)
48C-----------------------------------------------
49C L o c a l V a r i a b l e s
50C-----------------------------------------------
51 INTEGER NC(8,MVSIZ), MXT(MVSIZ), PID(MVSIZ), NGL(MVSIZ), I, MXT_1
52 my_real VIS(MVSIZ)
53 my_real OFF_L
54C-----------------------------------------------
55 off_l = zero
56 mxt_1 = ixs(1,1)
57 DO i=1,nel
58 ngl(i)=ixs(11,i)
59 mxt(i)=mxt_1
60 pid(i)=ixs(10,i)
61 nc(1,i)=ixs(2,i)
62 nc(2,i)=ixs(3,i)
63 nc(3,i)=ixs(4,i)
64 nc(4,i)=ixs(5,i)
65 nc(5,i)=ixs(6,i)
66 nc(6,i)=ixs(7,i)
67 nc(7,i)=ixs(8,i)
68 nc(8,i)=ixs(9,i)
69 ENDDO
70C
71C----------------------------
72C NODAL COORDINATES |
73C----------------------------
74 DO i=1,nel
75 xloc(i,1)=x(1,nc(1,i))
76 yloc(i,1)=x(2,nc(1,i))
77 zloc(i,1)=x(3,nc(1,i))
78 xloc(i,2)=x(1,nc(2,i))
79 yloc(i,2)=x(2,nc(2,i))
80 zloc(i,2)=x(3,nc(2,i))
81 xloc(i,3)=x(1,nc(3,i))
82 yloc(i,3)=x(2,nc(3,i))
83 zloc(i,3)=x(3,nc(3,i))
84 xloc(i,4)=x(1,nc(4,i))
85 yloc(i,4)=x(2,nc(4,i))
86 zloc(i,4)=x(3,nc(4,i))
87 xloc(i,5)=x(1,nc(5,i))
88 yloc(i,5)=x(2,nc(5,i))
89 zloc(i,5)=x(3,nc(5,i))
90 xloc(i,6)=x(1,nc(6,i))
91 yloc(i,6)=x(2,nc(6,i))
92 zloc(i,6)=x(3,nc(6,i))
93 xloc(i,7)=x(1,nc(7,i))
94 yloc(i,7)=x(2,nc(7,i))
95 zloc(i,7)=x(3,nc(7,i))
96 xloc(i,8)=x(1,nc(8,i))
97 yloc(i,8)=x(2,nc(8,i))
98 zloc(i,8)=x(3,nc(8,i))
99C
100 vxloc(i,1)=v(1,nc(1,i))
101 vyloc(i,1)=v(2,nc(1,i))
102 vzloc(i,1)=v(3,nc(1,i))
103 vxloc(i,2)=v(1,nc(2,i))
104 vyloc(i,2)=v(2,nc(2,i))
105 vzloc(i,2)=v(3,nc(2,i))
106 vxloc(i,3)=v(1,nc(3,i))
107 vyloc(i,3)=v(2,nc(3,i))
108 vzloc(i,3)=v(3,nc(3,i))
109 vxloc(i,4)=v(1,nc(4,i))
110 vyloc(i,4)=v(2,nc(4,i))
111 vzloc(i,4)=v(3,nc(4,i))
112 vxloc(i,5)=v(1,nc(5,i))
113 vyloc(i,5)=v(2,nc(5,i))
114 vzloc(i,5)=v(3,nc(5,i))
115 vxloc(i,6)=v(1,nc(6,i))
116 vyloc(i,6)=v(2,nc(6,i))
117 vzloc(i,6)=v(3,nc(6,i))
118 vxloc(i,7)=v(1,nc(7,i))
119 vyloc(i,7)=v(2,nc(7,i))
120 vzloc(i,7)=v(3,nc(7,i))
121 vxloc(i,8)=v(1,nc(8,i))
122 vyloc(i,8)=v(2,nc(8,i))
123 vzloc(i,8)=v(3,nc(8,i))
124 off(i) = min(one,abs(offg(i)))
125 off_l = min(off_l,offg(i))
126 ENDDO
127 IF(off_l<zero)THEN
128 DO i=1,nel
129 IF(offg(i)<zero)THEN
130 vxloc(i,1)=zero
131 vyloc(i,1)=zero
132 vzloc(i,1)=zero
133 vxloc(i,2)=zero
134 vyloc(i,2)=zero
135 vzloc(i,2)=zero
136 vxloc(i,3)=zero
137 vyloc(i,3)=zero
138 vzloc(i,3)=zero
139 vxloc(i,4)=zero
140 vyloc(i,4)=zero
141 vzloc(i,4)=zero
142 vxloc(i,5)=zero
143 vyloc(i,5)=zero
144 vzloc(i,5)=zero
145 vxloc(i,6)=zero
146 vyloc(i,6)=zero
147 vzloc(i,6)=zero
148 vxloc(i,7)=zero
149 vyloc(i,7)=zero
150 vzloc(i,7)=zero
151 vxloc(i,8)=zero
152 vyloc(i,8)=zero
153 vzloc(i,8)=zero
154 ENDIF
155 ENDDO
156 ENDIF
157C
158 RETURN
159 END
#define min(a, b)
Definition macros.h:20
subroutine s8coor3(offg, off, x, v, ixs, xloc, yloc, zloc, vxloc, vyloc, vzloc, mxt, nc, ngl, pid, nel)
Definition s8coor3.F:33
subroutine s8forc3(timers, output, elbuf_str, pm, geo, ixs, x, a, v, ms, veul, fv, ale_connect, iparg, tf, npf, bufmat, partsav, stifn, fsky, iads, offset, iparts, nel, dt2t, neltst, ityptst, ipm, itask, gresav, grth, igrth, mssa, dmels, table, ioutprt, mat_elem, ng, svis, glob_therm, snpc, numgeo, sbufmat, stf, ntable, sensors)
Definition s8forc3.F:64