OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i16buce.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!|| i16buce ../engine/source/interfaces/int16/i16buce.F
25!||--- called by ------------------------------------------------------
26!|| i16main ../engine/source/interfaces/int16/i16main.F
27!||--- calls -----------------------------------------------------
28!|| i16tri ../engine/source/interfaces/int16/i16tri.F
29!||====================================================================
30 SUBROUTINE i16buce(
31 1 NSV ,IXS ,IXS16 ,IXS20 ,NELEM ,
32 2 NME ,MWA ,NSN ,CAND_E ,CAND_N ,
33 3 NOINT ,I_STOK_GLOB,TZINF ,MINBOX ,EMINX ,
34 4 XSAV ,ITASK ,X ,V ,A ,
35 5 MX_CAND ,IXS10 ,ESH_T)
36C-----------------------------------------------
37C I m p l i c i t T y p e s
38C-----------------------------------------------
39#include "implicit_f.inc"
40#include "comlock.inc"
41C-----------------------------------------------
42C C o m m o n B l o c k s
43C-----------------------------------------------
44#include "units_c.inc"
45#include "warn_c.inc"
46#include "com01_c.inc"
47#include "com04_c.inc"
48#include "com08_c.inc"
49#include "task_c.inc"
50C-----------------------------------------------
51C D u m m y A r g u m e n t s
52C-----------------------------------------------
53 INTEGER NME, NSN, NOINT,IDT,ITASK,MX_CAND,
54 . ESH_T, I_STOK_GLOB
55 INTEGER CAND_E(*),CAND_N(*),IXS(NIXS,*),IXS16(8,*),
56 . NSV(*),MWA(*),NELEM(*),IXS20(12,*),IXS10(6,*)
57C REAL
59 . tzinf,minbox
61 . x(3,*),eminx(6,*),xsav(3,*),v(3,*) ,a(3,*)
62C-----------------------------------------------
63C L o c a l V a r i a b l e s
64C-----------------------------------------------
65C
66 INTEGER I, J, K, CONT,NB_N_B,I_STOK ,NSNF,NSNL,
67 . IP0, IP1, IP2, IP21, IP22, IP31, MAXSIZ,
68 . NE,N8,N10,N20,N16
69C-----------------------------------------------
70C S o u r c e L i n e s
71C-----------------------------------------------
72 IF (debug(3)>=1) THEN
73#include "lockon.inc"
74 WRITE(istdo,*)'** NEW SORT FOR INTERFACE NUMBER ',noint,
75 . ' AT CYCLE ',ncycle
76 WRITE(iout,*)'** NEW SORT FOR INTERFACE NUMBER ',noint,
77 . ' AT CYCLE ',ncycle
78#include "lockoff.inc"
79 ENDIF
80C-----------------------------------------------
81 nsnf = 1 + itask*nsn / nthread
82 nsnl = (itask+1)*nsn / nthread
83 DO i=nsnf,nsnl
84 j=nsv(i)
85 xsav(1,j) = x(1,j)+dt2*(v(1,j)+dt12*a(1,j))
86 xsav(2,j) = x(2,j)+dt2*(v(2,j)+dt12*a(2,j))
87 xsav(3,j) = x(3,j)+dt2*(v(3,j)+dt12*a(3,j))
88 END DO
89 DO k=1,8
90 DO i=1+esh_t,nme+esh_t
91 j=ixs(k+1,nelem(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 ENDDO
96 ENDDO
97 DO i=1+esh_t,nme+esh_t
98 ne=nelem(i)
99 n8 = ne
100 n10 = n8-numels8
101 n20 = n10-numels10
102 n16 = n20-numels20
103 IF(n16>0)THEN
104 DO k=1,8
105 j=ixs16(k,n16)
106 xsav(1,j) = x(1,j)+dt2*(v(1,j)+dt12*a(1,j))
107 xsav(2,j) = x(2,j)+dt2*(v(2,j)+dt12*a(2,j))
108 xsav(3,j) = x(3,j)+dt2*(v(3,j)+dt12*a(3,j))
109 ENDDO
110 ELSEIF(n20>0)THEN
111 DO k=1,12
112 j=ixs20(k,n20)
113 IF(j/=0)THEN
114 xsav(1,j) = x(1,j)+dt2*(v(1,j)+dt12*a(1,j))
115 xsav(2,j) = x(2,j)+dt2*(v(2,j)+dt12*a(2,j))
116 xsav(3,j) = x(3,j)+dt2*(v(3,j)+dt12*a(3,j))
117 ENDIF
118 ENDDO
119 ELSEIF(n10>0)THEN
120 DO k=1,6
121 j=ixs10(k,n10)
122 xsav(1,j) = x(1,j)+dt2*(v(1,j)+dt12*a(1,j))
123 xsav(2,j) = x(2,j)+dt2*(v(2,j)+dt12*a(2,j))
124 xsav(3,j) = x(3,j)+dt2*(v(3,j)+dt12*a(3,j))
125 ENDDO
126 ENDIF
127 ENDDO
128C-----------------------------------------------
129 nb_n_b = 1
130C Fin initialisation
131C-----------------------------------------------
132C
133C-----2- TRI PAR BOITES DES ELEMENTS ET DES NOEUDS
134C
135C-----------------------------------------------
136C SI ON A PAS ASSEZ DE MEMOIRE POUR LES PILES ON RECOMMENCE LE TRI
137C EN INCREMENTANT LE NB_N_B (NOMBRE DE NOEUDS PAR BOITE FINIE)
138C POINTEUR NOM TAILLE
139C P0........ NSN + 3
140C P1........Elt Bas Pile NME
141C P2........Elt PILE 2*NME
142C P21.......BPN NSN
143C P22.......PN NSN
144 maxsiz = 3*(nme+100)
145 ip1 = 1
146 ip2 = ip1+nme+100
147 ip21= ip2+maxsiz
148 ip22= ip21+nsn
149 ip31= ip22+nsn
150C-----------------------------------------------
151C nouvelle phase de tri
152C-----------------------------------------------
153 cont = 1
154C-----------------------------------------------
155C Boucle sur les retris
156C-----------------------------------------------
157 DO WHILE (cont/=0)
158 CALL i16tri(
159 1 mwa(ip1),mwa(ip2) ,mwa(ip21),mwa(ip22),nsn ,
160 2 tzinf ,ixs ,ixs16 ,ixs20 ,nelem ,
161 3 nsv ,maxsiz ,cand_n ,cand_e ,minbox ,
162 5 cont ,nb_n_b ,eminx ,i_stok_glob,nme ,
163 6 itask ,noint ,x ,v ,a ,
164 7 mx_cand ,ixs10 ,esh_t )
165 ENDDO
166C
167 RETURN
168 END
#define my_real
Definition cppsort.cpp:32
subroutine i16buce(nsv, ixs, ixs16, ixs20, nelem, nme, mwa, nsn, cand_e, cand_n, noint, i_stok_glob, tzinf, minbox, eminx, xsav, itask, x, v, a, mx_cand, ixs10, esh_t)
Definition i16buce.F:36
subroutine i16tri(bpe, pe, bpn, pn, nsn, tzinf, ixs, ixs16, ixs20, nelem, nsv, maxsiz, cand_n, cand_e, minbox, cont, nb_n_b, eminx, i_stok_glob, nme, itask, noint, x, v, a, mx_cand, ixs10, esh_t)
Definition i16tri.F:42