OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i17xsave.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/.
23C | I17MAIN_TRI /int17/i17main_lag.F
24!||====================================================================
25!|| i17xsave ../engine/source/interfaces/int17/i17xsave.F
26!||--- called by ------------------------------------------------------
27!|| i17main_tri ../engine/source/interfaces/int17/i17main_pena.F
28!||====================================================================
29 SUBROUTINE i17xsave(
30 1 X ,V ,A ,IXS ,IXS16 ,
31 2 NMES ,NME_T ,ESH_T ,NELEM ,NELES ,
32 3 EMINXM,ITASK ,XSAV ,XMIN ,YMIN ,
33 4 ZMIN ,XMAX ,YMAX ,ZMAX )
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 "com08_c.inc"
45#include "task_c.inc"
46C-----------------------------------------------
47C D u m m y A r g u m e n t s
48C-----------------------------------------------
49 INTEGER NMES,NME_T,ESH_T,NMN,ITASK,
50 . NELEM(*),NELES(*),IXS(NIXS,*),IXS16(8,*)
51 my_real
52 . XMAX, YMAX, ZMAX, XMIN, YMIN, ZMIN,
53 . x(3,*), v(3,*), a(3,*), eminxm(6,*), xsav(3,*)
54C-----------------------------------------------
55C L o c a l V a r i a b l e s
56C-----------------------------------------------
57 INTEGER NMES_F, NMES_L, I, J, K
58C-----------------------------------------------
59C S o u r c e L i n e s
60C-----------------------------------------------
61C
62 nmes_f = 1 + itask*nmes / nthread
63 nmes_l = (itask+1)*nmes / nthread
64C
65 xmin=ep30
66 xmax=-ep30
67 ymin=ep30
68 ymax=-ep30
69 zmin=ep30
70 zmax=-ep30
71C
72 DO k=1,8
73 DO i=1+esh_t,nme_t+esh_t
74 j=ixs(k+1,nelem(i))
75 xsav(1,j) = x(1,j)+dt2*(v(1,j)+dt12*a(1,j))
76 xsav(2,j) = x(2,j)+dt2*(v(2,j)+dt12*a(2,j))
77 xsav(3,j) = x(3,j)+dt2*(v(3,j)+dt12*a(3,j))
78 j=ixs16(k,nelem(i)-numels8-numels10-numels20)
79 xsav(1,j) = x(1,j)+dt2*(v(1,j)+dt12*a(1,j))
80 xsav(2,j) = x(2,j)+dt2*(v(2,j)+dt12*a(2,j))
81 xsav(3,j) = x(3,j)+dt2*(v(3,j)+dt12*a(3,j))
82C
83 xmin = min( xmin , eminxm(1,i) )
84 ymin = min( ymin , eminxm(2,i) )
85 zmin = min( zmin , eminxm(3,i) )
86 xmax = max( xmax , eminxm(4,i) )
87 ymax = max( ymax , eminxm(5,i) )
88 zmax = max( zmax , eminxm(6,i) )
89 ENDDO
90 DO i=nmes_f,nmes_l
91 j=ixs(k+1,neles(i))
92 xsav(1,j) = x(1,j)+dt2*(v(1,j)+dt12*a(1,j))
93 xsav(2,j) = x(2,j)+dt2*(v(2,j)+dt12*a(2,j))
94 xsav(3,j) = x(3,j)+dt2*(v(3,j)+dt12*a(3,j))
95 j=ixs16(k,neles(i)-numels8-numels10-numels20)
96 xsav(1,j) = x(1,j)+dt2*(v(1,j)+dt12*a(1,j))
97 xsav(2,j) = x(2,j)+dt2*(v(2,j)+dt12*a(2,j))
98 xsav(3,j) = x(3,j)+dt2*(v(3,j)+dt12*a(3,j))
99 ENDDO
100 ENDDO
101C
102 RETURN
103 END
subroutine i17xsave(x, v, a, ixs, ixs16, nmes, nme_t, esh_t, nelem, neles, eminxm, itask, xsav, xmin, ymin, zmin, xmax, ymax, zmax)
Definition i17xsave.F:34
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21