OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
dmasanic.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!|| dmasanic ../engine/source/output/anim/generate/dmasanic.F
25!||--- called by ------------------------------------------------------
26!|| genani ../engine/source/output/anim/generate/genani.F
27!||--- uses -----------------------------------------------------
28!|| elbufdef_mod ../common_source/modules/mat_elem/elbufdef_mod.F90
29!|| stack_mod ../engine/share/modules/stack_mod.F
30!||====================================================================
31 SUBROUTINE dmasanic(ELBUF_TAB,X ,D ,GEO ,IPARG,
32 . IXQ ,IXC ,IXTG ,MAS ,PM ,
33 . EL2FA,NBF ,IGEO,STACK)
34C-----------------------------------------------
35C M o d u l e s
36C-----------------------------------------------
37 USE elbufdef_mod
38 USE stack_mod
39C-----------------------------------------------
40C I m p l i c i t T y p e s
41C-----------------------------------------------
42#include "implicit_f.inc"
43C-----------------------------------------------
44C C o m m o n B l o c k s
45C-----------------------------------------------
46#include "com01_c.inc"
47#include "com04_c.inc"
48#include "param_c.inc"
49#include "task_c.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53C REAL
55 . mas(*) ,pm(npropm,*),geo(npropg,*),x(3,*),
56 . d(3,*)
57 INTEGER IPARG(NPARG,*),IXC(NIXC,*),IXTG(NIXTG,*),
58 . IXQ(NIXQ,*),EL2FA(*),NBF,IGEO(NPROPGI,*)
59 TYPE (ELBUF_STRUCT_), TARGET, DIMENSION(NGROUP) :: ELBUF_TAB
60 TYPE (STACK_PLY) :: STACK
61C-----------------------------------------------
62C L o c a l V a r i a b l e s
63C-----------------------------------------------
64C REAL
66 . off, p, vonm2, vonm, s1, s2, s12, s3, VALUE,thk0,a0,al0,
67 . rho0,xx1,xx2,xx3,yy1,yy2,yy3,zz1,zz2,zz3
68 INTEGER I, NG, NEL, NFT, IAD, ITY, LFT, NPT, ISS, ISC,
69 . IADD, N, J, LLT, MLW,
70 . istrain,nn, k1, k2,jturb,mt,jale, imid, ialel,ipid,
71 . n1,n2,n3,n4,
72 . nn1,nn2,nn3,nn4,nn5,nn6,nn7,nn8,nn9,nn10,
73 . offset,nel_old,ity_old,nft_fa,n_fa
74 INTEGER ISUBSTACK,NTHK,IADR,IIGEO,IGTYP
75 REAL R4
76 TYPE(g_bufel_) ,POINTER :: GBUF
77C---+----1----+----2----+----3----+----4----+----5----+----6----+----7--
78 nn1 = 1
79 nn2 = 1
80 nn3 = 1
81 nn4 = nn3 + numelq
82 nn5 = nn4 + numelc
83 nn6 = nn5 + numeltg
84 nn7 = nn6
85 nn8 = nn7
86 nn9 = nn8
87 nn10= nn9
88C-----------------------------------------------
89C
90 nel_old = 0
91 ity_old = 0
92 DO 490 ng=1,ngroup
93 gbuf => elbuf_tab(ng)%GBUF
94 nel =iparg(2,ng)
95 ity =iparg(5,ng)
96 npt =iabs(iparg(6,ng))
97 IF (ispmd==0) THEN
98 IF (ity/=ity_old) THEN
99 nel_old = 0
100 ity_old= ity
101 ENDIF
102 nft_fa = nel_old
103 nel_old = nel_old + nel
104 ENDIF
105 nft =iparg(3,ng)
106 iad =iparg(4,ng)
107 lft=1
108 llt=nel
109 IF (ispmd==0) THEN
110 nft_fa = nel_old - nel
111 ELSE
112 nft_fa = nft
113 ENDIF
114C-----------------------------------------------
115C QUAD
116C-----------------------------------------------
117 IF(ity==2)THEN
118 ialel=(iparg(7,ng)+iparg(11,ng))
119C
120 DO i=lft,llt
121 n = i + nft
122 n_fa = i + nft_fa
123 IF(ialel==0)THEN
124 mt=ixq(1,n)
125 VALUE=pm(89,mt)*gbuf%VOL(i)
126 ELSE
127 off = min(gbuf%OFF(i),one)
128 VALUE=gbuf%RHO(i)*gbuf%VOL(i)*off
129 ENDIF
130 mas(el2fa(nn3+n_fa)) = VALUE
131 ENDDO
132C-----------------------------------------------
133C COQUES 4 N
134C-----------------------------------------------
135 ELSEIF(ity==3)THEN
136C
137 isubstack=iparg(71,ng)
138 igtyp = iparg(38,ng)
139 IF(igtyp /= 17 . and. igtyp /= 51 .AND. igtyp /= 52) THEN
140 DO i=lft,llt
141 n = i + nft
142 n_fa = i + nft_fa
143 rho0 = pm(1,ixc(1,n))
144 thk0 = geo(1,ixc(6,n))
145 n1 = ixc(2,n)
146 n2 = ixc(3,n)
147 n3 = ixc(4,n)
148 n4 = ixc(5,n)
149 xx1 = x(1,n3)-d(1,n3)-x(1,n1)+d(1,n1)
150 yy1 = x(2,n3)-d(2,n3)-x(2,n1)+d(2,n1)
151 zz1 = x(3,n3)-d(3,n3)-x(3,n1)+d(3,n1)
152 xx2 = x(1,n4)-d(1,n4)-x(1,n2)+d(1,n2)
153 yy2 = x(2,n4)-d(2,n4)-x(2,n2)+d(2,n2)
154 zz2 = x(3,n4)-d(3,n4)-x(3,n2)+d(3,n2)
155 xx3 = yy1*zz2 - zz1*yy2
156 yy3 = zz1*xx2 - xx1*zz2
157 zz3 = xx1*yy2 - yy1*xx2
158 a0 = half*sqrt(xx3*xx3 + yy3*yy3 + zz3*zz3)
159 mas(el2fa(nn4+n_fa)) = rho0*thk0*a0
160 ENDDO
161 ELSE
162!! IIGEO = 40 + 5*(ISUBSTACK - 1)
163!! IADR = IGEO(IIGEO + 4,IXC(6,NFT + 1))
164!! NTHK = IADR + 3*NPT
165 DO i=lft,llt
166 n = i + nft
167 n_fa = i + nft_fa
168 rho0 = pm(1,ixc(1,n))
169 thk0 = stack%GEO(1,isubstack)
170 n1 = ixc(2,n)
171 n2 = ixc(3,n)
172 n3 = ixc(4,n)
173 n4 = ixc(5,n)
174 xx1 = x(1,n3)-d(1,n3)-x(1,n1)+d(1,n1)
175 yy1 = x(2,n3)-d(2,n3)-x(2,n1)+d(2,n1)
176 zz1 = x(3,n3)-d(3,n3)-x(3,n1)+d(3,n1)
177 xx2 = x(1,n4)-d(1,n4)-x(1,n2)+d(1,n2)
178 yy2 = x(2,n4)-d(2,n4)-x(2,n2)+d(2,n2)
179 zz2 = x(3,n4)-d(3,n4)-x(3,n2)+d(3,n2)
180 xx3 = yy1*zz2 - zz1*yy2
181 yy3 = zz1*xx2 - xx1*zz2
182 zz3 = xx1*yy2 - yy1*xx2
183 a0 = half*sqrt(xx3*xx3 + yy3*yy3 + zz3*zz3)
184 mas(el2fa(nn4+n_fa)) = rho0*thk0*a0
185 ENDDO
186 ENDIF
187C-----------------------------------------------
188C COQUES 3 N
189C-----------------------------------------------
190 ELSEIF(ity==7)THEN
191C
192 isubstack=iparg(71,ng)
193 igtyp = iparg(38,ng)
194 IF(igtyp /= 17 . and. igtyp /= 51 .AND. igtyp /= 52) THEN
195 DO i=lft,llt
196 n = i + nft
197 n_fa = i + nft_fa
198 rho0 = pm(1,ixtg(1,n))
199 thk0 = geo(1,ixtg(5,n))
200 n1 = ixtg(2,n)
201 n2 = ixtg(3,n)
202 n3 = ixtg(4,n)
203 xx1 = x(1,n2)-d(1,n2)-x(1,n1)+d(1,n1)
204 yy1 = x(2,n2)-d(2,n2)-x(2,n1)+d(2,n1)
205 zz1 = x(3,n2)-d(3,n2)-x(3,n1)+d(3,n1)
206 xx2 = x(1,n3)-d(1,n3)-x(1,n1)+d(1,n1)
207 yy2 = x(2,n3)-d(2,n3)-x(2,n1)+d(2,n1)
208 zz2 = x(3,n3)-d(3,n3)-x(3,n1)+d(3,n1)
209 xx3 = yy1*zz2 - zz1*yy2
210 yy3 = zz1*xx2 - xx1*zz2
211 zz3 = xx1*yy2 - yy1*xx2
212 a0 = half*sqrt(xx3*xx3 + yy3*yy3 + zz3*zz3)
213 mas(el2fa(nn5+n_fa)) = rho0*thk0*a0
214 ENDDO
215 ELSE
216 n = 1 + nft
217!! IIGEO = 40 + 5*(ISUBSTACK - 1)
218!! IADR = IGEO(IIGEO + 4,IXC(6,N))
219!! NTHK = IADR + 3*NPT
220 DO i=lft,llt
221 n = i + nft
222 n_fa = i + nft_fa
223 rho0 = pm(1,ixtg(1,n))
224 thk0 = stack%GEO(1,isubstack)
225 n1 = ixtg(2,n)
226 n2 = ixtg(3,n)
227 n3 = ixtg(4,n)
228 xx1 = x(1,n2)-d(1,n2)-x(1,n1)+d(1,n1)
229 yy1 = x(2,n2)-d(2,n2)-x(2,n1)+d(2,n1)
230 zz1 = x(3,n2)-d(3,n2)-x(3,n1)+d(3,n1)
231 xx2 = x(1,n3)-d(1,n3)-x(1,n1)+d(1,n1)
232 yy2 = x(2,n3)-d(2,n3)-x(2,n1)+d(2,n1)
233 zz2 = x(3,n3)-d(3,n3)-x(3,n1)+d(3,n1)
234 xx3 = yy1*zz2 - zz1*yy2
235 yy3 = zz1*xx2 - xx1*zz2
236 zz3 = xx1*yy2 - yy1*xx2
237 a0 = half*sqrt(xx3*xx3 + yy3*yy3 + zz3*zz3)
238 mas(el2fa(nn5+n_fa)) = rho0*thk0*a0
239 ENDDO
240 ENDIF
241C
242 ELSE
243 ENDIF
244C-----------------------------------------------
245C FIN DE BOUCLE SUR LES OFFSET
246C-----------------------------------------------
247 490 CONTINUE
248C-----------------------------------------------
249C
250 RETURN
251 END
#define my_real
Definition cppsort.cpp:32
subroutine dmasanic(elbuf_tab, x, d, geo, iparg, ixq, ixc, ixtg, mas, pm, el2fa, nbf, igeo, stack)
Definition dmasanic.F:34
#define min(a, b)
Definition macros.h:20