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 ../starter/source/output/anim/dmasanic.F
25!||--- called by ------------------------------------------------------
26!|| genani1 ../starter/source/output/anim/genani1.F
27!||--- uses -----------------------------------------------------
28!||====================================================================
29 SUBROUTINE dmasanic(ELBUF_TAB,X ,D ,GEO ,IPARG,
30 . IXQ ,IXC ,IXTG ,MAS ,PM ,
31 . EL2FA,NBF)
32C-----------------------------------------------
33C M o d u l e s
34C-----------------------------------------------
35 USE elbufdef_mod
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43#include "com01_c.inc"
44#include "com04_c.inc"
45#include "param_c.inc"
46C-----------------------------------------------
47C D u m m y A r g u m e n t s
48C-----------------------------------------------
49C REAL
50 my_real
51 . mas(*) ,pm(npropm,*),geo(npropg,*),x(3,*),
52 . d(3,*)
53 INTEGER IPARG(NPARG,*),IXC(NIXC,*),IXTG(NIXTG,*),
54 . IXQ(NIXQ,*),EL2FA(*),NBF
55 TYPE (ELBUF_STRUCT_), TARGET, DIMENSION(NGROUP) :: ELBUF_TAB
56C-----------------------------------------------
57C L o c a l V a r i a b l e s
58C-----------------------------------------------
59C REAL
60 my_real
61 . off,a0,thk0,rho0,xx1,xx2,xx3,yy1,yy2,yy3,zz1,zz2,zz3,VALUE
62 INTEGER I, NG, NEL, NFT, ITY, LFT, IALEL,MT,LLT,
63 . N,N1,N2,N3,N4,NN1,NN2,NN3,NN4,NN5,NN6,NN7,NN8,NN9,NN10,
64 . nft_fa,n_fa
65 TYPE(g_bufel_) ,POINTER :: GBUF
66C---+----1----+----2----+----3----+----4----+----5----+----6----+----7--
67 nn1 = 1
68 nn2 = 1
69 nn3 = 1
70 nn4 = nn3 + numelq
71 nn5 = nn4 + numelc
72 nn6 = nn5 + numeltg
73 nn7 = nn6
74 nn8 = nn7
75 nn9 = nn8
76C-----------------------------------------------
77 DO 490 ng=1,ngroup
78 gbuf => elbuf_tab(ng)%GBUF
79 nel =iparg(2,ng)
80 ity =iparg(5,ng)
81 nft =iparg(3,ng)
82 lft=1
83 llt=nel
84 nft_fa = nft
85C-----------------------------------------------
86C QUAD
87C-----------------------------------------------
88 IF(ity==2)THEN
89 ialel=(iparg(7,ng)+iparg(11,ng))
90C
91 DO i=lft,llt
92 n = i + nft
93 n_fa = i + nft_fa
94 IF(ialel==0)THEN
95 mt=ixq(1,n)
96 VALUE = pm(89,mt)* gbuf%VOL(i)
97 ELSE
98 off = min(gbuf%OFF(i),one)
99 VALUE= gbuf%RHO(i)*gbuf%VOL(i)*off
100 ENDIF
101 mas(el2fa(nn3+n_fa)) = VALUE
102 ENDDO
103C-----------------------------------------------
104C COQUES 4 N
105C-----------------------------------------------
106 ELSEIF(ity==3)THEN
107C
108 DO i=lft,llt
109 n = i + nft
110 n_fa = i + nft_fa
111 rho0 = pm(1,ixc(1,n))
112 thk0 = geo(1,ixc(6,n))
113 n1 = ixc(2,n)
114 n2 = ixc(3,n)
115 n3 = ixc(4,n)
116 n4 = ixc(5,n)
117 xx1 = x(1,n3)-d(1,n3)-x(1,n1)+d(1,n1)
118 yy1 = x(2,n3)-d(2,n3)-x(2,n1)+d(2,n1)
119 zz1 = x(3,n3)-d(3,n3)-x(3,n1)+d(3,n1)
120 xx2 = x(1,n4)-d(1,n4)-x(1,n2)+d(1,n2)
121 yy2 = x(2,n4)-d(2,n4)-x(2,n2)+d(2,n2)
122 zz2 = x(3,n4)-d(3,n4)-x(3,n2)+d(3,n2)
123 xx3 = yy1*zz2 - zz1*yy2
124 yy3 = zz1*xx2 - xx1*zz2
125 zz3 = xx1*yy2 - yy1*xx2
126 a0 = half*sqrt(xx3*xx3 + yy3*yy3 + zz3*zz3)
127 mas(el2fa(nn4+n_fa)) = rho0*thk0*a0
128 ENDDO
129C-----------------------------------------------
130C COQUES 3 N
131C-----------------------------------------------
132 ELSEIF(ity==7)THEN
133C
134 DO i=lft,llt
135 n = i + nft
136 n_fa = i + nft_fa
137 rho0 = pm(1,ixtg(1,n))
138 thk0 = geo(1,ixtg(5,n))
139 n1 = ixtg(2,n)
140 n2 = ixtg(3,n)
141 n3 = ixtg(4,n)
142 xx1 = x(1,n2)-d(1,n2)-x(1,n1)+d(1,n1)
143 yy1 = x(2,n2)-d(2,n2)-x(2,n1)+d(2,n1)
144 zz1 = x(3,n2)-d(3,n2)-x(3,n1)+d(3,n1)
145 xx2 = x(1,n3)-d(1,n3)-x(1,n1)+d(1,n1)
146 yy2 = x(2,n3)-d(2,n3)-x(2,n1)+d(2,n1)
147 zz2 = x(3,n3)-d(3,n3)-x(3,n1)+d(3,n1)
148 xx3 = yy1*zz2 - zz1*yy2
149 yy3 = zz1*xx2 - xx1*zz2
150 zz3 = xx1*yy2 - yy1*xx2
151 a0 = half*sqrt(xx3*xx3 + yy3*yy3 + zz3*zz3)
152 mas(el2fa(nn5+n_fa)) = rho0*thk0*a0
153 ENDDO
154C
155 ELSE
156 ENDIF
157C-----------------------------------------------
158 490 CONTINUE
159C-----------------------------------------------
160C
161 RETURN
162 END
#define my_real
Definition cppsort.cpp:32
#define min(a, b)
Definition macros.h:20
subroutine dmasanic(elbuf_tab, x, d, geo, iparg, ixq, ixc, ixtg, mas, pm, el2fa, nbf)
Definition dmasanic.F:32