OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
init_tg.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!|| init_tg ../starter/source/fluid/init_tg.F
25!||--- called by ------------------------------------------------------
26!|| hm_read_bem ../starter/source/loads/bem/hm_read_bem.F
27!||====================================================================
28 SUBROUTINE init_tg(IFLOW, IBUF, ELEM, X, XS, YS, ZS, XD, YD, ZD,
29 . RFLOW, NORMAL, TA, AF, COSG, DCP)
30C-----------------------------------------------
31C I m p l i c i t T y p e s
32C-----------------------------------------------
33#include "implicit_f.inc"
34C-----------------------------------------------
35C C o m m o n B l o c k s
36C-----------------------------------------------
37#include "units_c.inc"
38C-----------------------------------------------
39C D u m m y A r g u m e n t s
40C-----------------------------------------------
41 INTEGER IFLOW(*), IBUF(*), ELEM(3,*)
42 my_real x(3,*), af(*), rflow(*), normal(3,*), ta(*), cosg(*), dcp(*)
43 my_real xs, ys, zs, xd, yd, zd
44C-----------------------------------------------
45C L o c a l V a r i a b l e s
46C-----------------------------------------------
47 INTEGER ILVOUT, NEL, IWAVE, FREESURF
48 INTEGER N1, N2, N3, NN1, NN2, NN3, IEL, JEL
49 my_real x1, y1, z1, x2, y2, z2, x3, y3, z3,
50 . xp, yp, zp, x12, y12, z12, x13, y13, z13,
51 . nrx, nry, nrz, area2, dcs, ssp,
52 . xc, yc, zc, dirx, diry, dirz
53C
54 ilvout = iflow(17)
55 nel = iflow(6)
56 iwave = iflow(22)
57 freesurf= iflow(25)
58C-------------------------------------------------------------------
59C Compute Area Normal and Arrival Time
60C-------------------------------------------------------------------
61 ssp=rflow(2)
62 IF(iwave==1) THEN
63 xc =rflow(9)
64 yc =rflow(10)
65 zc =rflow(11)
66 dcs=rflow(12)
67 ELSEIF(iwave==2) THEN
68 dirx=rflow(9)
69 diry=rflow(10)
70 dirz=rflow(11)
71 ENDIF
72 DO iel=1,nel
73 n1=elem(1,iel)
74 n2=elem(2,iel)
75 n3=elem(3,iel)
76 nn1=ibuf(n1)
77 nn2=ibuf(n2)
78 nn3=ibuf(n3)
79 x1=x(1,nn1)
80 x2=x(1,nn2)
81 x3=x(1,nn3)
82 y1=x(2,nn1)
83 y2=x(2,nn2)
84 y3=x(2,nn3)
85 z1=x(3,nn1)
86 z2=x(3,nn2)
87 z3=x(3,nn3)
88C Normale
89 x12=x2-x1
90 y12=y2-y1
91 z12=z2-z1
92 x13=x3-x1
93 y13=y3-y1
94 z13=z3-z1
95 nrx=y12*z13-z12*y13
96 nry=z12*x13-x12*z13
97 nrz=x12*y13-y12*x13
98 area2=sqrt(nrx**2+nry**2+nrz**2)
99 normal(1,iel)=nrx/area2
100 normal(2,iel)=nry/area2
101 normal(3,iel)=nrz/area2
102 af(iel)=half*area2
103C Centroid
104 xp=third*(x1+x2+x3)
105 yp=third*(y1+y2+y3)
106 zp=third*(z1+z2+z3)
107C Arrival time
108 IF(iwave==1) THEN
109 dcp(iel) = sqrt((xp-xc)**2+(yp-yc)**2+(zp-zc)**2)
110 ta(iel) = (dcp(iel)-dcs)/ssp
111 cosg(iel)= (nrx*(xp-xc)+nry*(yp-yc)+nrz*(zp-zc))/(area2*dcp(iel))
112 IF(freesurf == 2) THEN
113 jel=iel+nel
114 dcp(jel) = sqrt((xp-xd)**2+(yp-yd)**2+(zp-zd)**2)
115 ta(jel) = (dcp(jel)-dcs)/ssp
116 cosg(jel)= (nrx*(xp-xd)+nry*(yp-yd)+nrz*(zp-zd))/(area2*dcp(jel))
117 ENDIF
118 ELSEIF(iwave==2) THEN
119 dcp(iel) = (xp-xs)*dirx+(yp-xs)*diry+(zp-zs)*dirz
120 ta(iel) = dcp(iel)/ssp
121 cosg(iel)= (nrx*dirx+nry*diry+nrz*dirz)/area2
122 ENDIF
123 ENDDO
124
125 IF(ilvout>=2) THEN
126C---+----1----+----2----+----3----+----4----+----5----+----6----+----7----+----8----+----9----+----1----+----2----+----3--
127 WRITE (iout,'(//7X,2A)') 'ELEMENT ARRIVAL TIME AREA DISTANCE DIR.COSINE ',
128 . 'NORMAL-X NORMAL-Y NORMAL-Z'
129 DO iel = 1,nel
130 WRITE (iout,'(5X,I10,7E13.5)')iel,ta(iel),af(iel),dcp(iel),cosg(iel),normal(1,iel),normal(2,iel),normal(3,iel)
131 ENDDO
132 IF(freesurf == 2) THEN
133 WRITE (iout,'(//7X,2A)') 'ELEMENT ARRIVAL TIME AREA DISTANCE DIR.COSINE '
134 DO iel = 1,nel
135 jel=iel+nel
136 WRITE (iout,'(5X,I10,7E13.5)')iel,ta(jel),af(iel),dcp(jel),cosg(jel)
137 ENDDO
138 ENDIF
139 ENDIF
140 RETURN
141 END
142
143
#define my_real
Definition cppsort.cpp:32
subroutine init_tg(iflow, ibuf, elem, x, xs, ys, zs, xd, yd, zd, rflow, normal, ta, af, cosg, dcp)
Definition init_tg.F:30