OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
dxyzsect.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!|| dxyzsect ../starter/source/output/anim/dxyzsect.F
25!||--- called by ------------------------------------------------------
26!|| genani1 ../starter/source/output/anim/genani1.F
27!||--- calls -----------------------------------------------------
28!|| dxwalc ../starter/source/output/anim/dxwalc.F
29!|| dxwall ../starter/source/output/anim/dxwall.F
30!|| dxwalp ../starter/source/output/anim/dxwalp.F
31!|| dxwals ../starter/source/output/anim/dxwals.F
32!||====================================================================
33 SUBROUTINE dxyzsect (NSTRF,RWBUF,NPRW ,X , XMIN,
34 2 YMIN ,ZMIN ,XMAX ,YMAX , ZMAX,
35 3 ITAB)
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 "param_c.inc"
44#include "com04_c.inc"
45C-----------------------------------------------
46C D u m m y A r g u m e n t s
47C-----------------------------------------------
48 INTEGER NSTRF(*),NPRW(*),ITAB(*)
49 my_real
50 . rwbuf(nrwlp,*),x(3,*),xmin ,ymin ,zmin ,xmax ,ymax, zmax
51C-----------------------------------------------
52C L o c a l V a r i a b l e s
53C-----------------------------------------------
54 INTEGER J, I, K, K0, K1, N, NSEG, N1, N2, N3, N4,MSR, ITYP
55 my_real
56 . xx1, yy1, zz1, xx2, yy2, zz2, xx3, yy3, zz3,
57 . xx4, yy4, zz4, d13, xxc, yyc, zzc, al4,xwl,ywl,zwl,
58 . pmain,loc_proc
59
60 my_real
61 . xsec(3,3,nsect)
62 REAL R4,SBUF(3*NSECT)
63CC-----------------------------------------------
64 k1=1
65C
66 k1 = 33
67 DO i=1,nsect
68 n1 = nstrf(k1+1)
69 n2 = nstrf(k1+2)
70 n3 = nstrf(k1+3)
71 xx1=x(1,n1)
72 yy1=x(2,n1)
73 zz1=x(3,n1)
74 xx2=x(1,n2)
75 yy2=x(2,n2)
76 zz2=x(3,n2)
77 xx3=x(1,n3)
78 yy3=x(2,n3)
79 zz3=x(3,n3)
80 xx4=xx2-xx1
81 yy4=yy2-yy1
82 zz4=zz2-zz1
83 al4=sqrt(xx4**2+yy4**2+zz4**2)
84 xx4=xx4/max(al4,em20)
85 yy4=yy4/max(al4,em20)
86 zz4=zz4/max(al4,em20)
87C
88 d13=(xx3-xx1)*xx4+(yy3-yy1)*yy4+(zz3-zz1)*zz4
89 xxc=xx1+d13*xx4
90 yyc=yy1+d13*yy4
91 zzc=zz1+d13*zz4
92C
93 r4 = xxc
94 CALL write_r_c(r4,1)
95 r4 = yyc
96 CALL write_r_c(r4,1)
97 r4 = zzc
98 CALL write_r_c(r4,1)
99C
100
101 k1= nstrf(k1+22)+2
102 ENDDO
103C
104 k=1
105 DO n=1,nrwall
106 n2=n +nrwall
107 n3=n2+nrwall
108 n4=n3+nrwall
109 msr = nprw(n3)
110 IF(msr==0)THEN
111 xwl=rwbuf(4,n)
112 ywl=rwbuf(5,n)
113 zwl=rwbuf(6,n)
114 ELSE
115 xwl=x(1,msr)
116 ywl=x(2,msr)
117 zwl=x(3,msr)
118 ENDIF
119 ityp= nprw(n4)
120 IF(ityp==4)THEN
121 xwl = xwl + half*(rwbuf(7,n)+rwbuf(10,n))
122 ywl = ywl + half*(rwbuf(8,n)+rwbuf(11,n))
123 zwl = zwl + half*(rwbuf(9,n)+rwbuf(12,n))
124 ENDIF
125 k=k+nprw(n)
126 IF(nprw(n4)==-1)k=k+nint(rwbuf(8,n))
127 r4 = xwl
128 CALL write_r_c(r4,1)
129 r4 = ywl
130 CALL write_r_c(r4,1)
131 r4 = zwl
132 CALL write_r_c(r4,1)
133 ENDDO
134C
135 k=1
136 DO n=1,nrwall
137 n2=n +nrwall
138 n3=n2+nrwall
139 n4=n3+nrwall
140 ityp= nprw(n4)
141
142 IF(iabs(ityp)==1)THEN
143 CALL dxwall(x,rwbuf(1,n),nprw(n3),xmin ,ymin ,
144 . zmin ,xmax ,ymax , zmax)
145 ELSEIF(ityp==2)THEN
146 CALL dxwalc(x,rwbuf(1,n),nprw(n3),xmin ,ymin ,
147 . zmin ,xmax ,ymax , zmax)
148 ELSEIF(ityp==3)THEN
149 CALL dxwals(x,rwbuf(1,n),nprw(n3))
150 ELSEIF(ityp==4)THEN
151 CALL dxwalp(x,rwbuf(1,n),nprw(n3))
152 ENDIF
153 k=k+nprw(n)
154 IF(nprw(n4)==-1)k=k+nint(rwbuf(8,n))
155 ENDDO
156C
157 RETURN
158 END
subroutine ymax(idn, fac, npc, pld, stiffmin, stiffmax, stiffini, stiffavg)
Definition law100_upd.F:272
#define max(a, b)
Definition macros.h:21
subroutine dxwalc(x, rwl, msr, xmin, ymin, zmin, xmax, ymax, zmax)
Definition dxwalc.F:32
subroutine dxwall(x, rwl, msr, xmin, ymin, zmin, xmax, ymax, zmax)
Definition dxwall.F:32
subroutine dxwalp(x, rwl, msr)
Definition dxwalp.F:30
subroutine dxwals(x, rwl, msr)
Definition dxwals.F:30
subroutine dxyzsect(nstrf, rwbuf, nprw, x, xmin, ymin, zmin, xmax, ymax, zmax, itab)
Definition dxyzsect.F:36
void write_r_c(float *w, int *len)