OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i20xsave.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!|| i20xsave ../engine/source/interfaces/intsort/i20xsave.F
25!||--- called by ------------------------------------------------------
26!|| i20main_tri ../engine/source/interfaces/intsort/i20main_tri.F
27!||====================================================================
28 SUBROUTINE i20xsave(
29 1 ITASK ,XA ,NTY ,NSN ,
30 2 NMN ,NSNE ,NMNE ,NLN ,
31 3 NSV ,MSR ,XSAV ,
32 4 NSVE ,MSRE ,XSAVE ,
33 5 XMIN ,YMIN ,ZMIN ,XMAX ,
34 6 YMAX ,ZMAX ,C_MAX ,CURV_MAX,
35 7 ICURV ,IRECT ,NRTM_T,XMINE ,
36 8 YMINE ,ZMINE ,XMAXE ,YMAXE ,
37 9 ZMAXE )
38C sauvegarde des XSAV
39C-----------------------------------------------
40C I m p l i c i t T y p e s
41C-----------------------------------------------
42#include "implicit_f.inc"
43C-----------------------------------------------
44C C o m m o n B l o c k s
45C-----------------------------------------------
46#include "task_c.inc"
47C-----------------------------------------------
48C D u m m y A r g u m e n t s
49C-----------------------------------------------
50 INTEGER NSN,NMN,ITASK,NTY, ICURV, NRTM_T,NLN,
51 . NSV(*),MSR(*)
52 INTEGER NSNE,NMNE,NSVE(*),MSRE(*), IRECT(4,*)
53 my_real
54 . XMIN, YMIN, ZMIN, XMAX, YMAX, ZMAX, C_MAX,
55 . XMINE, YMINE, ZMINE, XMAXE, YMAXE, ZMAXE,
56 . XA(3,*),XSAV(3,*),XSAVE(3,*),
57 . CURV_MAX(*)
58C-----------------------------------------------
59C L o c a l V a r i a b l e s
60C-----------------------------------------------
61 INTEGER NSNF,NMNF,NSNL,NMNL,I, J, II
62 INTEGER NSNEF,NMNEF,NSNEL,NMNEL
63 my_real
64 . XXX, YYY, ZZZ
65C-----------------------------------------------
66C S o u r c e L i n e s
67C-----------------------------------------------
68
69 NSNF=1+itask*nsn/nthread
70 nsnl=(itask+1)*nsn/nthread
71 nmnf=1+itask*nmn/nthread
72 nmnl=(itask+1)*nmn/nthread
73
74 nsnef=1+itask*nsne/nthread
75 nsnel=(itask+1)*nsne/nthread
76 nmnef=1+itask*nmne/nthread
77 nmnel=(itask+1)*nmne/nthread
78
79 xmin=ep30
80 xmax=-ep30
81 ymin=ep30
82 ymax=-ep30
83 zmin=ep30
84 zmax=-ep30
85
86 xmine=ep30
87 xmaxe=-ep30
88 ymine=ep30
89 ymaxe=-ep30
90 zmine=ep30
91 zmaxe=-ep30
92
93
94 DO i=nsnf,nsnl
95 j=abs(nsv(i))
96 xsav(1,i)=xa(1,j)
97 xsav(2,i)=xa(2,j)
98 xsav(3,i)=xa(3,j)
99 END DO
100 DO i=nmnf,nmnl
101 ii = i+nsn
102 j=msr(i)
103C msr < 0 <=> shooting nodes
104 IF(j>0) THEN
105 xmin= min(xmin,xa(1,j))
106 ymin= min(ymin,xa(2,j))
107 zmin= min(zmin,xa(3,j))
108 xmax= max(xmax,xa(1,j))
109 ymax= max(ymax,xa(2,j))
110 zmax= max(zmax,xa(3,j))
111 xsav(1,ii)=xa(1,j)
112 xsav(2,ii)=xa(2,j)
113 xsav(3,ii)=xa(3,j)
114 END IF
115 END DO
116
117 c_max = zero
118 IF(icurv/=0)THEN
119 DO i=1,nrtm_t
120 xxx=max(xa(1,irect(1,i)),xa(1,irect(2,i)),
121 . xa(1,irect(3,i)),xa(1,irect(4,i)))
122 . -min(xa(1,irect(1,i)),xa(1,irect(2,i)),
123 . xa(1,irect(3,i)),xa(1,irect(4,i)))
124 yyy=max(xa(2,irect(1,i)),xa(2,irect(2,i)),
125 . xa(2,irect(3,i)),xa(2,irect(4,i)))
126 . -min(xa(2,irect(1,i)),xa(2,irect(2,i)),
127 . xa(2,irect(3,i)),xa(2,irect(4,i)))
128 zzz=max(xa(3,irect(1,i)),xa(3,irect(2,i)),
129 . xa(3,irect(3,i)),xa(3,irect(4,i)))
130 . -min(xa(3,irect(1,i)),xa(3,irect(2,i)),
131 . xa(3,irect(3,i)),xa(3,irect(4,i)))
132 curv_max(i) = half * max(xxx,yyy,zzz)
133 c_max = max(c_max,curv_max(i))
134 ENDDO
135 ELSE
136 DO i=1,nrtm_t
137 curv_max(i)=zero
138 ENDDO
139 ENDIF
140
141 DO i=nsnef,nsnel
142 j=abs(nsve(i))
143 xsave(1,i)=xa(1,j)
144 xsave(2,i)=xa(2,j)
145 xsave(3,i)=xa(3,j)
146 END DO
147
148 DO i=nmnef,nmnel
149 ii = i+nsne
150 j=msre(i)
151C msr < 0 <=> shooting nodes
152 IF(j>0) THEN
153 xmine= min(xmine,xa(1,j))
154 ymine= min(ymine,xa(2,j))
155 zmine= min(zmine,xa(3,j))
156 xmaxe= max(xmaxe,xa(1,j))
157 ymaxe= max(ymaxe,xa(2,j))
158 zmaxe= max(zmaxe,xa(3,j))
159 xsave(1,ii)=xa(1,j)
160 xsave(2,ii)=xa(2,j)
161 xsave(3,ii)=xa(3,j)
162 END IF
163 END DO
164
165
166 RETURN
167 END
subroutine i20xsave(itask, xa, nty, nsn, nmn, nsne, nmne, nln, nsv, msr, xsav, nsve, msre, xsave, xmin, ymin, zmin, xmax, ymax, zmax, c_max, curv_max, icurv, irect, nrtm_t, xmine, ymine, zmine, xmaxe, ymaxe, zmaxe)
Definition i20xsave.F:38
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21