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 ../engine/source/output/anim/generate/dmasanif.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!||====================================================================
30 SUBROUTINE dmasanif(ELBUF_TAB,X ,D ,GEO ,IPARG,
31 . IXT ,IXP ,IXR ,MAS ,PM ,
32 . EL2FA ,NBF )
33C-----------------------------------------------
34C M o d u l e s
35C-----------------------------------------------
36 USE elbufdef_mod
37C-----------------------------------------------
38C I m p l i c i t T y p e s
39C-----------------------------------------------
40#include "implicit_f.inc"
41C-----------------------------------------------
42C C o m m o n B l o c k s
43C-----------------------------------------------
44#include "com01_c.inc"
45#include "com04_c.inc"
46#include "param_c.inc"
47#include "task_c.inc"
48C-----------------------------------------------
49C D u m m y A r g u m e n t s
50C-----------------------------------------------
51 my_real :: mas(*) ,pm(npropm,*),geo(npropg,*),x(3,*), d(3,*)
52 INTEGER IPARG(NPARG,*),IXT(NIXT,*),IXP(NIXP,*),IXR(NIXR,*),EL2FA(*),NBF
53C
54 TYPE (ELBUF_STRUCT_), DIMENSION(NGROUP), TARGET :: ELBUF_TAB
55C-----------------------------------------------
56C L o c a l V a r i a b l e s
57C-----------------------------------------------
59 . off, p, vonm2, vonm, s1, s2, s12, s3, VALUE,thk0,a0,al0,
60 . rho0,xx1,xx2,xx3,yy1,yy2,yy3,zz1,zz2,zz3
61 INTEGER I, NG, NEL, NFT, IAD, ITY, LFT, NPT, ISS, ISC,
62 . IADD, N, J, LLT, MLW, NB1, NB2, NB3, NB4, NB5,NB6,
63 . nb7, nb8, nb9, nb10, nb11, nb12, nb13, nb14, nb15, nb16,
64 . istrain,nn, k1, k2,jturb,mt,jale, imid, ialel,ipid,
65 . n1,n2,n3,n4,
66 . nn1,nn2,nn3,nn4,nn5,nn6,nn7,nn8,nn9,nn10,
67 . offset,nel_old,ity_old,nft_fa,n_fa,
68 . 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
81 nn9 = nn8 + numelr
82 nn10= nn9
83C-----------------------------------------------
84 nel_old = 0
85 ity_old = 0
86 DO ng=1,ngroup
87 mlw =iparg(1,ng)
88 nel =iparg(2,ng)
89 ity =iparg(5,ng)
90 gbuf => elbuf_tab(ng)%GBUF
91 IF (ispmd == 0) THEN
92 IF (ity /= ity_old) THEN
93 nel_old = 0
94 ity_old= ity
95 ENDIF
96 nft_fa = nel_old
97 nel_old = nel_old + nel
98 ENDIF
99 nft =iparg(3,ng)
100 iad =iparg(4,ng)
101 lft=1
102 llt=nel
103 IF (ispmd == 0) THEN
104 nft_fa = nel_old - nel
105 ELSE
106 nft_fa = nft
107 ENDIF
108C-----------------------------------------------
109C TRUSS
110C-----------------------------------------------
111 IF (ity == 4) THEN
112 DO i=lft,llt
113 n = i + nft
114 n_fa = i + nft_fa
115 rho0 = pm(1,ixt(1,n))
116 a0 = geo(1,ixt(4,n))
117 n1 = ixt(2,n)
118 n2 = ixt(3,n)
119 xx1 = x(1,n2)-d(1,n2)-x(1,n1)+d(1,n1)
120 yy1 = x(2,n2)-d(2,n2)-x(2,n1)+d(2,n1)
121 zz1 = x(3,n2)-d(3,n2)-x(3,n1)+d(3,n1)
122 al0 = sqrt(xx1*xx1 + yy1*yy1 + zz1*zz1)
123 mas(el2fa(nn6+n_fa)) = rho0*al0*a0
124 ENDDO
125C-----------------------------------------------
126C POUTRES
127C-----------------------------------------------
128 ELSEIF (ity == 5) THEN
129 DO i=lft,llt
130 n = i + nft
131 n_fa = i + nft_fa
132 rho0 = pm(1,ixp(1,n))
133 a0 = geo(1,ixp(5,n))
134 n1 = ixp(2,n)
135 n2 = ixp(3,n)
136 xx1 = x(1,n2)-d(1,n2)-x(1,n1)+d(1,n1)
137 yy1 = x(2,n2)-d(2,n2)-x(2,n1)+d(2,n1)
138 zz1 = x(3,n2)-d(3,n2)-x(3,n1)+d(3,n1)
139 al0 = sqrt(xx1*xx1 + yy1*yy1 + zz1*zz1)
140 mas(el2fa(nn7+n_fa)) = rho0*al0*a0
141 ENDDO
142C-----------------------------------------------
143C RESSORTS
144C-----------------------------------------------
145 ELSEIF (ity == 6) THEN
146 IF(mlw==3)THEN
147 DO i=lft,llt
148 n = i + nft
149 n_fa = i + nft_fa
150 mas(el2fa(nn8+n_fa)) = half*geo(1,ixr(1,n))
151 mas(el2fa(nn8+n_fa)+1) = half*geo(1,ixr(1,n))
152 ENDDO
153 ELSEIF (mlw == 5) THEN
154c NB1 =IAD - 1
155c NB2 =NB1 + NEL
156c NUVAR = NINT(GEO(25,IXR(1,1+NFT)))
157c NB3 =NB2 + 3*NEL
158c NB4 =NB3 + NEL
159c NB5 =NB4 + 3*NEL
160c NB6 =NB5
161c NB7 =NB6
162c NB8 =NB7
163c NB9 =NB8 + 3*NEL
164c NB10=NB9 + 3*NEL
165c NB11=NB10
166c NB12=NB11
167c NB13=NB12
168c NB14=NB13
169c NB15 = NB14 + 3*NEL
170c NB16 = NB15 + NUVAR*NEL
171 DO i=lft,llt
172 n = i + nft
173 n_fa = i + nft_fa
174 mas(el2fa(nn8+n_fa)) = gbuf%MASS(i)
175cc MAS(EL2FA(NN8+N_FA)) = BUFEL(NB16+I)
176 ENDDO
177 ELSE
178 DO i=lft,llt
179 n = i + nft
180 n_fa = i + nft_fa
181 mas(el2fa(nn8+n_fa)) = geo(1,ixr(1,n))
182 ENDDO
183 ENDIF ! IF(MLW)
184 ENDIF ! IF (ITY)
185C-----------------------------------------------
186C FIN DE BOUCLE SUR LES OFFSET
187C-----------------------------------------------
188 ENDDO
189C-----------------------------------------------
190 RETURN
191 END
#define my_real
Definition cppsort.cpp:32
subroutine dmasanif(elbuf_tab, x, d, geo, iparg, ixt, ixp, ixr, mas, pm, el2fa, nbf)
Definition dmasanif.F:33