OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
dmasanif.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!|| dmasanif ../starter/source/output/anim/dmasanif.F
25!||--- called by ------------------------------------------------------
26!|| genani1 ../starter/source/output/anim/genani1.F
27!||--- uses -----------------------------------------------------
28!||====================================================================
29 SUBROUTINE dmasanif(X ,D ,ELBUF_TAB,GEO ,IPARG,
30 . IXT ,IXP ,IXR ,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,*),
54 . IXT(NIXT,*),IXP(NIXP,*),IXR(NIXR,*),EL2FA(*),NBF
55C
56 TYPE (ELBUF_STRUCT_), TARGET, DIMENSION(NGROUP) :: ELBUF_TAB
57C-----------------------------------------------
58C L o c a l V a r i a b l e s
59C-----------------------------------------------
60C REAL
61 my_real
62 . off, p, vonm2, vonm, s1, s2, s12, s3, VALUE,a0,al0,
63 . rho0,xx1,xx2,xx3,yy1,yy2,yy3,zz1,zz2,zz3
64 INTEGER I, NG, NEL, NFT, ITY, LFT, NPT, ISS, ISC,
65 . IADD, N, J, LLT, MLW,
66 . istrain,nn, k1, k2,jturb,mt,
67 . n1,n2,n3,n4,nn1,nn2,nn3,nn4,nn5,nn6,nn7,nn8,
68 . offset,nel_old,ity_old,nft_fa,n_fa,nuvar
69 REAL R4
70C
71 TYPE(g_bufel_) ,POINTER :: GBUF
72C-----------------------------------------------
73 nn1 = 1
74 nn2 = 1
75 nn3 = 1
76 nn4 = nn3
77 nn5 = nn4
78 nn6 = nn5
79 nn7 = nn6 + numelt
80 nn8 = nn7 + numelp
81C-----------------------------------------------
82C
83 nel_old = 0
84 ity_old = 0
85 DO 490 ng=1,ngroup
86 mlw =iparg(1,ng)
87 nel =iparg(2,ng)
88 ity =iparg(5,ng)
89 nft =iparg(3,ng)
90 lft=1
91 llt=nel
92 nft_fa = nft
93C
94 gbuf => elbuf_tab(ng)%GBUF
95C-----------------------------------------------
96C TRUSS
97C-----------------------------------------------
98 IF(ity==4)THEN
99 DO i=lft,llt
100 n = i + nft
101 n_fa = i + nft_fa
102 rho0 = pm(1,ixt(1,n))
103 a0 = geo(1,ixt(4,n))
104 n1 = ixt(2,n)
105 n2 = ixt(3,n)
106 xx1 = x(1,n2)-d(1,n2)-x(1,n1)+d(1,n1)
107 yy1 = x(2,n2)-d(2,n2)-x(2,n1)+d(2,n1)
108 zz1 = x(3,n2)-d(3,n2)-x(3,n1)+d(3,n1)
109 al0 = half*sqrt(xx1*xx1 + yy1*yy1 + zz1*zz1)
110 mas(el2fa(nn6+n_fa)) = rho0*al0*a0
111 ENDDO
112C-----------------------------------------------
113C POUTRES
114C-----------------------------------------------
115 ELSEIF(ity==5)THEN
116 DO i=lft,llt
117 n = i + nft
118 n_fa = i + nft_fa
119 rho0 = pm(1,ixp(1,n))
120 a0 = geo(1,ixp(5,n))
121 n1 = ixp(2,n)
122 n2 = ixp(3,n)
123 xx1 = x(1,n2)-d(1,n2)-x(1,n1)+d(1,n1)
124 yy1 = x(2,n2)-d(2,n2)-x(2,n1)+d(2,n1)
125 zz1 = x(3,n2)-d(3,n2)-x(3,n1)+d(3,n1)
126 al0 = half*sqrt(xx1*xx1 + yy1*yy1 + zz1*zz1)
127 mas(el2fa(nn7+n_fa)) = rho0*al0*a0
128 ENDDO
129C-----------------------------------------------
130C RESSORTS
131C-----------------------------------------------
132 ELSEIF(ity==6)THEN
133 IF(mlw==3)THEN
134 DO i=lft,llt
135 n = i + nft
136 n_fa = i + nft_fa
137 mas(el2fa(nn8+n_fa)) = half*geo(1,ixr(1,n))
138 mas(el2fa(nn8+n_fa)+1) = half*geo(1,ixr(1,n))
139 ENDDO
140 ELSEIF(mlw==5) THEN
141cc NB1 =IAD - 1
142cc NB2 =NB1 + NEL
143 nuvar = nint(geo(25,ixr(1,1+nft)))
144cc NB3 =NB2 + 3*NEL
145cc NB4 =NB3 + NEL
146cc NB5 =NB4 + 3*NEL
147cc NB6 =NB5
148cc NB7 =NB6
149cc NB8 =NB7
150cc NB9 =NB8 + 3*NEL
151cc NB10=NB9 + 3*NEL
152cc NB11=NB10
153cc NB12=NB11
154cc NB13=NB12
155cc NB14=NB13
156cc NB15 = NB14 + 3*NEL
157cc NB16 = NB15 + NUVAR*NEL
158 DO i=lft,llt
159 n = i + nft
160 n_fa = i + nft_fa
161 mas(el2fa(nn8+n_fa)) = gbuf%MASS(i)
162cc MAS(EL2FA(NN8+N_FA)) = BUFEL(NB16+I)
163 ENDDO
164 ELSE
165 DO i=lft,llt
166 n = i + nft
167 n_fa = i + nft_fa
168 mas(el2fa(nn8+n_fa)) = geo(1,ixr(1,n))
169 ENDDO
170 ENDIF
171 ELSE
172 ENDIF
173C-----------------------------------------------
174C FIN DE BOUCLE SUR LES OFFSET
175C-----------------------------------------------
176 490 CONTINUE
177C-----------------------------------------------
178C
179 RETURN
180 END
#define my_real
Definition cppsort.cpp:32
subroutine dmasanif(x, d, elbuf_tab, geo, iparg, ixt, ixp, ixr, mas, pm, el2fa, nbf)
Definition dmasanif.F:32