OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
s8eselecsht.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!|| s8eselecsht ../engine/source/elements/solid/solide8e/s8eselecsht.F
25!||--- called by ------------------------------------------------------
26!|| s8eforc3 ../engine/source/elements/solid/solide8e/s8eforc3.F
27!||====================================================================
28 SUBROUTINE s8eselecsht(
29 1 NPTR, NPTS, NPTT, NNPT,
30 2 MFXX, MFXY, MFXZ, MFYX,
31 3 MFYY, MFYZ, MFZX, MFZY,
32 4 MFZZ, BXX, BYY, BZZ,
33 5 BXY, BYZ, BXZ, I_SH,
34 6 OFFG, NEL, ISMSTR)
35C-----------------------------------------------
36C I m p l i c i t T y p e s
37C-----------------------------------------------
38#include "implicit_f.inc"
39C-----------------------------------------------
40C G l o b a l P a r a m e t e r s
41C-----------------------------------------------
42#include "mvsiz_p.inc"
43C-----------------------------------------------
44C C o m m o n B l o c k s
45C-----------------------------------------------
46C-----------------------------------------------
47C D u m m y A r g u m e n t s
48C-----------------------------------------------
49 INTEGER, INTENT(IN) :: NEL
50 INTEGER, INTENT(IN) :: ISMSTR
51 INTEGER NPTR,NPTS,NPTT,NNPT ,I_SH
52C REAL
53 my_real
54 . MFXX(MVSIZ,NNPT),MFXY(MVSIZ,NNPT),MFXZ(MVSIZ,NNPT),
55 . mfyx(mvsiz,nnpt),mfyy(mvsiz,nnpt),mfyz(mvsiz,nnpt),
56 . mfzx(mvsiz,nnpt),mfzy(mvsiz,nnpt),mfzz(mvsiz,nnpt),
57 . bxx(mvsiz,nnpt),byy(mvsiz,nnpt),bzz(mvsiz,nnpt),
58 . bxy(mvsiz,nnpt),bxz(mvsiz,nnpt),byz(mvsiz,nnpt),offg(*)
59C-----------------------------------------------
60C L o c a l V a r i a b l e s
61C-----------------------------------------------
62 INTEGER I, J ,IR,IS,IT,IP
63 my_real
64 . B0XY(MVSIZ,2),B0XZ(MVSIZ,2),B0YZ(MVSIZ,2),
65 . B0YX(MVSIZ,2),B0ZX(MVSIZ,2),B0ZY(MVSIZ,2)
66C------------
67 IF (ISMSTR/=11) then
68 DO ip = 1,nnpt
69 DO i=1,nel
70C ----[B]=[MF+1][MF+1]^t -1
71 IF (ismstr==12.AND.offg(i) >one) cycle
72 bxx(i,ip)=mfxx(i,ip)*(two+mfxx(i,ip))+
73 . mfxy(i,ip)*mfxy(i,ip)+mfxz(i,ip)*mfxz(i,ip)
74 byy(i,ip)=mfyy(i,ip)*(two+mfyy(i,ip))+
75 . mfyx(i,ip)*mfyx(i,ip)+mfyz(i,ip)*mfyz(i,ip)
76 bzz(i,ip)=mfzz(i,ip)*(two+mfzz(i,ip))+
77 . mfzx(i,ip)*mfzx(i,ip)+mfzy(i,ip)*mfzy(i,ip)
78 bxy(i,ip)=mfxy(i,ip)+mfyx(i,ip)+mfxx(i,ip)*mfyx(i,ip)+
79 . mfxy(i,ip)*mfyy(i,ip)+mfxz(i,ip)*mfyz(i,ip)
80 bxz(i,ip)=mfxz(i,ip)+mfzx(i,ip)+mfxx(i,ip)*mfzx(i,ip)+
81 . mfxy(i,ip)*mfzy(i,ip)+mfxz(i,ip)*mfzz(i,ip)
82 byz(i,ip)=mfzy(i,ip)+mfyz(i,ip)+mfzx(i,ip)*mfyx(i,ip)+
83 . mfzy(i,ip)*mfyy(i,ip)+mfzz(i,ip)*mfyz(i,ip)
84 ENDDO
85 END DO !IP = 1
86 END IF !(ISMSTR/=11) THEN
87C
88 DO ir = 1,2
89 b0xy(1:nel,ir) = zero
90 b0xz(1:nel,ir) = zero
91 b0yz(1:nel,ir) = zero
92 END DO !IR = 1,2
93C
94 IF (ismstr==11) THEN
95 DO ir = 1,2
96 b0yx(1:nel,ir) = zero
97 b0zx(1:nel,ir) = zero
98 b0zy(1:nel,ir) = zero
99 END DO !IR = 1,2
100 DO ir=1,nptr
101 DO is=1,npts
102 DO it=1,nptt
103C-----------
104 ip = ir + ( (is-1) + (it-1)*npts )*nptr
105C
106C------ moyen in 3 directions
107 DO i=1,nel
108 b0xy(i,ir) = b0xy(i,ir)+mfxy(i,ip)
109 b0xz(i,it) = b0xz(i,it)+mfxz(i,ip)
110 b0yz(i,is) = b0yz(i,is)+mfyz(i,ip)
111 b0yx(i,ir) = b0yx(i,ir)+mfyx(i,ip)
112 b0zx(i,it) = b0zx(i,it)+mfzx(i,ip)
113 b0zy(i,is) = b0zy(i,is)+mfzy(i,ip)
114 END DO
115 ENDDO ! IT=1,NPTT
116 ENDDO ! is=1,npts
117 ENDDO ! IR=1,NPTR
118C
119 DO ir = 1,2
120 DO i=1,nel
121 b0xy(i,ir) = b0xy(i,ir)*fourth
122 b0xz(i,ir) = b0xz(i,ir)*fourth
123 b0yz(i,ir) = b0yz(i,ir)*fourth
124 b0yx(i,ir) = b0yx(i,ir)*fourth
125 b0zx(i,ir) = b0zx(i,ir)*fourth
126 b0zy(i,ir) = b0zy(i,ir)*fourth
127 END DO
128 END DO !IR = 1,2
129C---------takes the selective mean values-----
130 DO ir=1,nptr
131 DO is=1,npts
132 DO it=1,nptt
133C-----------
134 ip = ir + ( (is-1) + (it-1)*npts )*nptr
135C
136 DO i=1,nel
137 mfxy(i,ip) = b0xy(i,ir)
138 mfxz(i,ip) = b0xz(i,it)
139 mfyz(i,ip) = b0yz(i,is)
140 mfyx(i,ip) = b0yx(i,ir)
141 mfzx(i,ip) = b0zx(i,it)
142 mfzy(i,ip) = b0zy(i,is)
143 END DO
144 ENDDO ! IT=1,NPTT
145 ENDDO ! IS=1,NPTS
146 ENDDO ! IR=1,NPTR
147 ELSE
148 DO ir=1,nptr
149 DO is=1,npts
150 DO it=1,nptt
151C-----------
152 ip = ir + ( (is-1) + (it-1)*npts )*nptr
153C
154C------ moyen in 3 directions
155 DO i=1,nel
156 IF (ismstr==12.AND.offg(i) >one) cycle
157 b0xy(i,ir) = b0xy(i,ir)+bxy(i,ip)
158 b0xz(i,it) = b0xz(i,it)+bxz(i,ip)
159 b0yz(i,is) = b0yz(i,is)+byz(i,ip)
160 END DO
161 ENDDO ! IT=1,NPTT
162 ENDDO ! IS=1,NPTS
163 ENDDO ! IR=1,NPTR
164C
165 DO ir = 1,2
166 DO i=1,nel
167 IF (ismstr==12.AND.offg(i) >one) cycle
168 b0xy(i,ir) = b0xy(i,ir)*fourth
169 b0xz(i,ir) = b0xz(i,ir)*fourth
170 b0yz(i,ir) = b0yz(i,ir)*fourth
171 END DO
172 END DO !IR = 1,2
173C---------takes the selective mean values-----
174 DO ir=1,nptr
175 DO is=1,npts
176 DO it=1,nptt
177C-----------
178 ip = ir + ( (is-1) + (it-1)*npts )*nptr
179C
180 DO i=1,nel
181 IF (ismstr==12.AND.offg(i) >one) cycle
182 bxy(i,ip) = b0xy(i,ir)
183 bxz(i,ip) = b0xz(i,it)
184 byz(i,ip) = b0yz(i,is)
185 END DO
186 ENDDO ! IT=1,NPTT
187 ENDDO ! IS=1,NPTS
188 ENDDO ! IR=1,NPTR
189 END IF !(ISMSTR==11) THEN
190C
191 RETURN
192 END
subroutine s8eselecsht(nptr, npts, nptt, nnpt, mfxx, mfxy, mfxz, mfyx, mfyy, mfyz, mfzx, mfzy, mfzz, bxx, byy, bzz, bxy, byz, bxz, i_sh, offg, nel, ismstr)
Definition s8eselecsht.F:35