OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i18xsave.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!|| i18xsave ../engine/source/interfaces/int18/i18xsave.F
25!||--- called by ------------------------------------------------------
26!|| i7main_tri ../engine/source/interfaces/intsort/i7main_tri.f
27!||====================================================================
28 SUBROUTINE i18xsave(
29 1 X ,NSV , MSR , NSN , NMN ,
30 2 ITASK ,XSAV , XMIN , YMIN , ZMIN ,
31 3 XMAX ,YMAX , ZMAX , C_MAX , CURV_MAX,
32 4 ICURV ,IRECT, NRTM_T, SX , SY ,
33 5 SZ ,SX2 , SY2 , SZ2 , NMN_L )
34C sauvegarde des XSAV et calcul borne domaine
35C-----------------------------------------------
36C I m p l i c i t T y p e s
37C-----------------------------------------------
38#include "implicit_f.inc"
39#include "comlock.inc"
40C-----------------------------------------------
41C C o m m o n B l o c k s
42C-----------------------------------------------
43#include "com04_c.inc"
44#include "task_c.inc"
45#include "impl1_c.inc"
46C-----------------------------------------------
47C D u m m y A r g u m e n t s
48C-----------------------------------------------
49 INTEGER NSN,NMN,ITASK, ICURV, NRTM_T,
50 . NSV(*),MSR(*), IRECT(4,*),NMN_L,NTY,INACTI
51 my_real
52 . XMAX, YMAX, ZMAX, XMIN, YMIN, ZMIN, C_MAX,
53 . SX, SY, SZ, SX2, SY2, SZ2,
54 . x(3,*), xsav(3,*), curv_max(*)
55C-----------------------------------------------
56C L o c a l V a r i a b l e s
57C-----------------------------------------------
58 INTEGER NSNF,NMNF,NSNL,NMNL,I, J, II
59 my_real
60 . XXX, YYY, ZZZ
61C-----------------------------------------------
62C S o u r c e L i n e s
63C-----------------------------------------------
64C
65 nsnf=1+itask*nsn/nthread
66 nsnl=(itask+1)*nsn/nthread
67 nmnf=1+itask*nmn/nthread
68 nmnl=(itask+1)*nmn/nthread
69
70 xmin=ep30
71 xmax=-ep30
72 ymin=ep30
73 ymax=-ep30
74 zmin=ep30
75 zmax=-ep30
76
77 sx=zero
78 sy=zero
79 sz=zero
80 sx2=zero
81 sy2=zero
82 sz2=zero
83 nmn_l = 0
84
85 IF(nsn+nmn < numnod)THEN
86 DO i=nsnf,nsnl
87 j=nsv(i)
88 IF(j>0.AND.inconv==1)THEN
89 xsav(1,i)=x(1,j)
90 xsav(2,i)=x(2,j)
91 xsav(3,i)=x(3,j)
92 ENDIF
93 END DO
94
95 DO i=nmnf,nmnl
96 ii = i+nsn
97 j=msr(i)
98 ! msr < 0 <=> shooting nodes
99 IF(j>0) THEN
100 xmin= min(xmin,x(1,j))
101 ymin= min(ymin,x(2,j))
102 zmin= min(zmin,x(3,j))
103 xmax= max(xmax,x(1,j))
104 ymax= max(ymax,x(2,j))
105 zmax= max(zmax,x(3,j))
106 IF (inconv==1) THEN
107 xsav(1,ii)=x(1,j)
108 xsav(2,ii)=x(2,j)
109 xsav(3,ii)=x(3,j)
110 END IF
111 sx=sx+x(1,j)
112 sy=sy+x(2,j)
113 sz=sz+x(3,j)
114 sx2=sx2+x(1,j)**2
115 sy2=sy2+x(2,j)**2
116 sz2=sz2+x(3,j)**2
117 nmn_l= nmn_l + 1
118 ENDIF
119 END DO
120 ELSE
121C
122 DO i=nsnf,nsnl
123 j=nsv(i)
124 IF(j>0.AND.inconv==1)THEN
125 xsav(1,j)=x(1,j)
126 xsav(2,j)=x(2,j)
127 xsav(3,j)=x(3,j)
128 END IF
129 END DO
130 DO i=nmnf,nmnl
131 j=msr(i)
132 ! msr < 0 <=> shooting nodes
133 IF(j>0) THEN
134 xmin= min(xmin,x(1,j))
135 ymin= min(ymin,x(2,j))
136 zmin= min(zmin,x(3,j))
137 xmax= max(xmax,x(1,j))
138 ymax= max(ymax,x(2,j))
139 zmax= max(zmax,x(3,j))
140 IF (inconv==1) THEN
141 xsav(1,j)=x(1,j)
142 xsav(2,j)=x(2,j)
143 xsav(3,j)=x(3,j)
144 END IF
145 sx=sx+x(1,j)
146 sy=sy+x(2,j)
147 sz=sz+x(3,j)
148 sx2=sx2+x(1,j)**2
149 sy2=sy2+x(2,j)**2
150 sz2=sz2+x(3,j)**2
151 nmn_l= nmn_l + 1
152 END IF
153 END DO
154 ENDIF
155C
156 c_max = zero
157 DO i=1,nrtm_t
158 curv_max(i)=zero
159 ENDDO
160C
161 RETURN
162 END
subroutine i18xsave(x, nsv, msr, nsn, nmn, itask, xsav, xmin, ymin, zmin, xmax, ymax, zmax, c_max, curv_max, icurv, irect, nrtm_t, sx, sy, sz, sx2, sy2, sz2, nmn_l)
Definition i18xsave.F:34
subroutine i7main_tri(timers, ipari, x, v, ms, nin, itask, mwag, weight, isendto, ircvfrom, retri, iad_elem, fr_elem, itab, kinet, temp, nrtm_t, renum, nsnfiold, eshift, num_imp, ind_imp, nodnx_sms, intbuf_tab, h3d_data, ixs, multi_fvm, glob_therm)
Definition i7main_tri.F:66
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21