OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i21tri.F File Reference
#include "implicit_f.inc"
#include "mvsiz_p.inc"
#include "com01_c.inc"
#include "com04_c.inc"
#include "param_c.inc"
#include "vect07_c.inc"

Go to the source code of this file.

Functions/Subroutines

subroutine i21tri (bpe, pe, bpn, pn, add, irect, x, nb_nc, nb_ec, xyzm, i_add, nsv, i_amax, xmax, ymax, zmax, maxsiz, i_stok, i_mem, nb_n_b, cand_n, cand_e, nsn, noint, tzinf, maxbox, minbox, j_stok, msr, xm0, multimp, itab, gap, gap_s, igap, gapmin, gapmax, marge, depth, drad, id, titr, ix1, ix2, ix3, ix4, nsvg, x1, x2, x3, x4, y1, y2, y3, y4, z1, z2, z3, z4, xi, yi, zi, x0, y0, z0, stif, nx1, ny1, nz1, nx2, ny2, nz2, nx3, ny3, nz3, nx4, ny4, nz4, p1, p2, p3, p4, lb1, lb2, lb3, lb4, lc1, lc2, lc3, lc4, pene, prov_n, prov_e, n11, n21, n31, dgapload)

Function/Subroutine Documentation

◆ i21tri()

subroutine i21tri ( integer, dimension(*) bpe,
integer, dimension(*) pe,
integer, dimension(*) bpn,
integer, dimension(*) pn,
integer, dimension(2,0:*) add,
integer, dimension(4,*) irect,
x,
integer nb_nc,
integer nb_ec,
xyzm,
integer i_add,
integer, dimension(*) nsv,
integer i_amax,
xmax,
ymax,
zmax,
integer maxsiz,
integer i_stok,
integer i_mem,
integer nb_n_b,
integer, dimension(*) cand_n,
integer, dimension(*) cand_e,
integer nsn,
integer noint,
tzinf,
maxbox,
minbox,
integer j_stok,
integer, dimension(*) msr,
xm0,
integer multimp,
integer, dimension(*) itab,
gap,
gap_s,
integer igap,
gapmin,
gapmax,
marge,
depth,
drad,
integer id,
character(len=nchartitle) titr,
integer, dimension(mvsiz), intent(inout) ix1,
integer, dimension(mvsiz), intent(inout) ix2,
integer, dimension(mvsiz), intent(inout) ix3,
integer, dimension(mvsiz), intent(inout) ix4,
integer, dimension(mvsiz), intent(inout) nsvg,
intent(inout) x1,
intent(inout) x2,
intent(inout) x3,
intent(inout) x4,
intent(inout) y1,
intent(inout) y2,
intent(inout) y3,
intent(inout) y4,
intent(inout) z1,
intent(inout) z2,
intent(inout) z3,
intent(inout) z4,
intent(inout) xi,
intent(inout) yi,
intent(inout) zi,
intent(inout) x0,
intent(inout) y0,
intent(inout) z0,
intent(inout) stif,
intent(inout) nx1,
intent(inout) ny1,
intent(inout) nz1,
intent(inout) nx2,
intent(inout) ny2,
intent(inout) nz2,
intent(inout) nx3,
intent(inout) ny3,
intent(inout) nz3,
intent(inout) nx4,
intent(inout) ny4,
intent(inout) nz4,
intent(inout) p1,
intent(inout) p2,
intent(inout) p3,
intent(inout) p4,
intent(inout) lb1,
intent(inout) lb2,
intent(inout) lb3,
intent(inout) lb4,
intent(inout) lc1,
intent(inout) lc2,
intent(inout) lc3,
intent(inout) lc4,
intent(inout) pene,
integer, dimension(mvsiz), intent(inout) prov_n,
integer, dimension(mvsiz), intent(inout) prov_e,
intent(inout) n11,
intent(inout) n21,
intent(inout) n31,
intent(in) dgapload )

Definition at line 37 of file i21tri.F.

58 USE message_mod
60C-----------------------------------------------
61C I m p l i c i t T y p e s
62C-----------------------------------------------
63#include "implicit_f.inc"
64C-----------------------------------------------
65C G l o b a l P a r a m e t e r s
66C-----------------------------------------------
67#include "mvsiz_p.inc"
68C-----------------------------------------------
69C C o m m o n B l o c k s
70C-----------------------------------------------
71#include "com01_c.inc"
72#include "com04_c.inc"
73#include "param_c.inc"
74#include "vect07_c.inc"
75C-----------------------------------------------
76C D u m m y A r g u m e n t s
77C-----------------------------------------------
78 INTEGER NB_NC,NB_EC,I_ADD,MAXSIZ,I_STOK,J_STOK,I_MEM
79 INTEGER I_BID, I_AMAX,NB_N_B, NOINT, NSN,MULTIMP, IGAP
80 INTEGER ADD(2,0:*),IRECT(4,*),BPE(*),PE(*),BPN(*),PN(*)
81 INTEGER NSV(*),CAND_N(*),CAND_E(*), ITAB(*), MSR(*)
82 INTEGER, DIMENSION(MVSIZ), INTENT(INOUT) ::PROV_N,PROV_E
83 INTEGER, DIMENSION(MVSIZ), INTENT(INOUT) :: IX1,IX2,IX3,IX4,NSVG
84 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: x1,x2,x3,x4
85 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: y1,y2,y3,y4
86 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: z1,z2,z3,z4
87 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: xi,yi,zi
88 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: x0,y0,z0,stif
89 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: n11,n21,n31,pene
90 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: nx1,ny1,nz1
91 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: nx2,ny2,nz2
92 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: nx3,ny3,nz3
93 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: nx4,ny4,nz4
94 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: p1,p2,p3,p4
95 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: lb1,lb2,lb3,lb4
96 my_real, DIMENSION(MVSIZ), INTENT(INOUT) :: lc1,lc2,lc3,lc4
97C REAL
99 . x(3,*),xyzm(6,*),tzinf,dbuc,
100 . maxbox,minbox, xmax, ymax, zmax,
101 . gap, gap_s(*),
102 . gapmin, gapmax, marge, gapsmx, bgapsmx, depth, xm0(3,*), drad
103 my_real , INTENT(IN) :: dgapload
104 INTEGER ID
105 CHARACTER(LEN=NCHARTITLE) :: TITR
106C-----------------------------------------------
107C L o c a l V a r i a b l e s
108C-----------------------------------------------
109 INTEGER NB_NCN,NB_ECN,ADDNN,ADDNE,IPOS,I,IP,J
110 INTEGER INF,SUP,DIR,N1,N2,N3,N4,NN,NE
111C REAL
112 my_real
113 . bid,dx,dy,dz,dsup,seuil,xmx,xmn,gapsmax,
114 . gapv(mvsiz)
115C-----------------------------------------------
116C ROLE DE LA ROUTINE:
117C ===================
118C CLASSE LES ELETS DE BPE ET LES NOEUDS DE BPN EN TWO ZONES
119C > OU < A UNE FRONTIERE ICI DETERMINEE ET SORT LE TOUT
120C DANS bpe,hpe, et bpn,hpn
121C-----------------------------------------------
122C D u m m y A r g u m e n t s
123C
124C NOM DESCRIPTION E/S
125C
126C BPE TABLEAU DES FACETTES A TRIER E/S
127C ET DU RESULTAT COTE MAX
128C PE TABLEAU DES FACETTES S
129C RESULTAT COTE MIN
130C BPN TABLEAU DES NOEUDS A TRIER E/S
131C ET DU RESULTAT COTE MAX
132C PN TABLEAU DES NOEUDS S
133C RESULTAT COTE MIN
134C ADD(2,*) TABLEAU DES ADRESSES E/S
135C 1.......ADRESSES NOEUDS
136C 2.......ADRESSES ELEMENTS
137C ZYZM(6,*) TABLEAU DES XYZMIN E/S
138C 1.......XMIN BOITE
139C 2.......YMIN BOITE
140C 3.......ZMIN BOITE
141C 4.......XMAX BOITE
142C 5.......YMAX BOITE
143C 6.......ZMAX BOITE
144C IRECT(4,*) TABLEAU DES CONEC FACETTES E
145C X(3,*) COORDONNEES NODALES E
146C NB_NC NOMBRE DE NOEUDS CANDIDATS E/S
147C NB_EC NOMBRE D'ELTS CANDIDATS E/S
148C I_ADD POSITION DANS LE TAB DES ADRESSES E/S
149C NSV NOS SYSTEMES DES NOEUDS E
150C XMAX plus grande abcisse existante E
151C XMAX plus grande ordonn. existante E
152C XMAX plus grande cote existante E
153C MAXSIZ TAILLE MEMOIRE MAX POSSIBLE E
154C I_STOK niveau de stockage des couples
155C candidats impact E/S
156C CAND_N boites resultats noeuds
157C CAND_E adresses des boites resultat elements
158C MULTIMP*NSN TAILLE MAX ADMISE MAINTENANT POUR LES
159C COUPLES NOEUDS,ELT CANDIDATS
160C NOINT NUMERO USER DE L'INTERFACE
161C TZINF TAILLE ZONE INFLUENCE
162C MAXBOX TAILLE MAX BUCKET
163C MINBOX TAILLE MIN BUCKET
164C=======================================================================
165C
166C
167C 1- TEST ARRET = BOITE VIDE
168C BOITE TROP PETITE
169C BOITE NE CONTENANT QU'ONE NOEUD
170C PLUS DE MEMOIRE DISPONIBLE
171C
172C-----------------------------------------------------------
173C
174C IF(MEMX>ADD(2,1)+NB_EC)THEN
175C WRITE(ISTDO,*)' *******MEM MAX=',MEMX
176C MEMX=-1
177C ELSEIF(MEMX/=-1)THEN
178C MEMX=ADD(2,1)+NB_EC
179C ENDIF
180C--------------------TEST SUR BOITE VIDES--------------
181C
182 IF(nb_ec==0.OR.nb_nc==0) THEN
183C write(6,*)" BOITE VIDE"
184C IL FAUT COPIER LES BAS DES PILES DANS BAS_DE_PILE CORRESPONDANTS
185C AVANT DE REDESCENDRE DANS LA BRANCHE MITOYENNE
186 CALL i7dstk(i_add,nb_nc,nb_ec,add,bpn,pn,bpe,pe)
187 RETURN
188 ENDIF
189C
190C-------------------TEST SUR FIN DE BRANCHE / MEMOIRE DEPASSEE------------
191C
192 dx = xyzm(4,i_add) - xyzm(1,i_add)
193 dy = xyzm(5,i_add) - xyzm(2,i_add)
194 dz = xyzm(6,i_add) - xyzm(3,i_add)
195 dsup= max(dx,dy,dz)
196C
197 IF(add(2,1)+nb_ec>=maxsiz) THEN
198C PLUS DE PLACE DANS LA PILE DES ELEMENTS BOITES TROP PETITES
199 IF ( nb_n_b == numnod) THEN
200C WRITE(IOUT,*)'***ERROR INFINITE LOOP DETECTED '
201C WRITE(ISTDO,*)'***ERROR INFINITE LOOP DETECTED '
202C CALL ARRET(2)
203 IF (istamping == 1) THEN
204 CALL ancmsg(msgid=775,
205 . msgtype=msgerror,
206 . anmode=aninfo,
207 . i1=id,
208 . c1=titr)
209 ELSE
210 CALL ancmsg(msgid=685,
211 . msgtype=msgerror,
212 . anmode=aninfo,
213 . i1=id,
214 . c1=titr)
215 ENDIF
216 ENDIF
217 i_mem = 1
218 RETURN
219 ENDIF
220 IF(dsup<minbox.OR.
221 . nb_nc<=nb_n_b.AND.dsup<maxbox.OR.
222 . nb_nc<=nb_n_b.AND.nb_ec==1) THEN
223C
224C write(6,*)" NOUVELLE BOITE "
225C 1- STOCKAGE DU OU DES NOEUD CANDIDAT ET DES ELTS CORRESP.
226C VIRER LES INUTILES
227 DO 20 i=1,nb_ec
228 ne = bpe(i)
229 n1=msr(irect(1,ne))
230 n2=msr(irect(2,ne))
231 n3=msr(irect(3,ne))
232 n4=msr(irect(4,ne))
233 DO 20 j=1,nb_nc
234 nn=nsv(bpn(j))
235 IF(nn/=n1.AND.nn/=n2.AND.nn/=n3.AND.nn/=n4) THEN
236 j_stok = j_stok + 1
237 prov_n(j_stok) = bpn(j)
238 prov_e(j_stok) = ne
239 IF(j_stok==nvsiz) THEN
240 lft = 1
241 llt = nvsiz
242 nft = 0
243 j_stok = 0
244 CALL i21cor3t(x ,irect,nsv ,prov_e ,prov_n,
245 2 gapv ,igap ,gap ,gap_s,gapmin ,
246 3 gapmax,xm0 ,depth ,drad ,ix1 ,
247 4 ix2 ,ix3 ,ix4 ,nsvg ,x1 ,
248 5 x2 ,x3 ,x4 ,y1 ,y2 ,
249 6 y3 ,y4 ,z1 ,z2 ,z3 ,
250 7 z4 ,xi ,yi ,zi ,dgapload)
251 CALL i7dst3(ix3,ix4,x1 ,x2 ,x3 ,
252 1 x4 ,y1 ,y2 ,y3 ,y4 ,
253 2 z1 ,z2 ,z3 ,z4 ,xi ,
254 3 yi ,zi ,x0 ,y0 ,z0 ,
255 4 nx1,ny1,nz1,nx2,ny2,
256 5 nz2,nx3,ny3,nz3,nx4,
257 6 ny4,nz4,p1 ,p2 ,p3 ,
258 7 p4 ,lb1,lb2,lb3,lb4,
259 8 lc1,lc2,lc3,lc4,llt)
260 CALL i7pen3(marge,gapv,n11,n21,n31,
261 1 pene ,nx1 ,ny1,nz1,nx2,
262 2 ny2 ,nz2 ,nx3,ny3,nz3,
263 3 nx4 ,ny4 ,nz4,p1 ,p2 ,
264 4 p3 ,p4,llt)
265 IF(i_stok+nvsiz<multimp*nsn) THEN
266 CALL i7cmp3(i_stok,cand_e ,cand_n,1,pene,
267 1 prov_n,prov_e)
268 ELSE
269 i_bid = 0
270 CALL i7cmp3(i_bid,cand_e,cand_n,0,pene,
271 1 prov_n,prov_e)
272 IF(i_stok+i_bid<multimp*nsn) THEN
273 CALL i7cmp3(i_stok,cand_e,cand_n,1,pene,
274 1 prov_n,prov_e)
275 ELSE
276 i_mem = 2 ! TOO MANY POSSIBLE IMPACTS : return to upgrade Multimp
277 RETURN
278 ENDIF
279 ENDIF
280 ENDIF
281C write(6,*)"Noeud candidat",BPN(J)
282C write(6,*)"Element candidat",NE
283 ENDIF
284 20 CONTINUE
285C IL FAUT COPIER LES BAS DES PILES DANS BAS_DE_PILE CORRESPONDANTS
286C AVANT DE REDESCENDRE DANS LA BRANCHE MITOYENNE
287 CALL i7dstk(i_add,nb_nc,nb_ec,add,bpn,pn,bpe,pe)
288 RETURN
289 ENDIF
290C
291C-----------------------------------------------------------
292C
293C
294C 2- PHASE DE TRI SUR LA MEDIANE SELON LA + GDE DIRECTION
295C
296C
297C-----------------------------------------------------------
298C
299C
300C 1- DETERMINER LA DIRECTION A DIVISER X,Y OU Z
301C
302 dir = 1
303 IF(dy==dsup) THEN
304 dir = 2
305 ELSE IF(dz==dsup) THEN
306 dir = 3
307 ENDIF
308 seuil =(xyzm(dir+3,i_add)+xyzm(dir,i_add))/2
309C
310C 2- DIVISER LES NOEUDS EN TWO ZONES
311C
312 nb_ncn= 0
313 addnn= add(1,1)
314 inf = 0
315 sup = 0
316 IF(igap==0)THEN
317 DO i=1,nb_nc
318 IF(x(dir,nsv(bpn(i)))<seuil) THEN
319C ON STOCKE DANS LE BAS DE LA PILE BP
320 addnn = addnn + 1
321 pn(addnn) = bpn(i)
322 inf = 1
323 ELSE
324 nb_ncn = nb_ncn + 1
325 bpn(nb_ncn) = bpn(i)
326C ON STOCKE EN ECRASANT PROGRESSIVEMENT BPN
327 sup = 1
328 ENDIF
329 END DO
330 ELSE
331 gapsmx = zero
332 bgapsmx = zero
333 DO i=1,nb_nc
334 IF(x(dir,nsv(bpn(i)))<seuil) THEN
335C ON STOCKE DANS LE BAS DE LA PILE BP
336 addnn = addnn + 1
337 pn(addnn) = bpn(i)
338 gapsmx = max(gapsmx,max(gap_s(bpn(i)),depth,drad))
339 inf = 1
340 ELSE
341C ON STOCKE EN ECRASANT PROGRESSIVEMENT BPN
342 nb_ncn = nb_ncn + 1
343 bpn(nb_ncn) = bpn(i)
344 bgapsmx = max(bgapsmx,max(gap_s(bpn(i)),depth,drad))
345 sup = 1
346 ENDIF
347 END DO
348 END IF
349CC
350CC 3- DIVISER LES ELEMENTS
351CC
352C NB_ECN= 0
353C ADDNE= ADD(2,1)
354C SEUILI = SEUIL-TZINF
355C SEUILS = SEUIL+TZINF
356C DO 85 I=1,NB_EC
357C INF = 0
358C SUP = 0
359C DO 80 J=1,4
360C IP = IRECT(J,BPE(I))
361C IF(X(DIR,IP)<SEUILS) THEN
362C INF = 1
363C IF(SUP==1) GOTO 81
364C ENDIF
365C IF(X(DIR,IP)>=SEUILI) THEN
366C SUP = 1
367C IF(INF==1) GOTO 81
368C ENDIF
369C 80 CONTINUE
370C
371C 81 CONTINUE
372C IF(INF==1) THEN
373C ON STOCKE DANS LE BAS DE LA PILE BP
374C ADDNE = ADDNE + 1
375C PE(ADDNE) = BPE(I)
376C ENDIF
377C IF(SUP==1) THEN
378C ON STOCKE EN ECRASANT PROGRESSIVEMENT BPE
379C NB_ECN = NB_ECN + 1
380C BPE(NB_ECN) = BPE(I)
381C ENDIF
382C 85 CONTINUE
383C
384C 3- DIVISER LES ELEMENTS
385C
386C 2 LIGNES PROV POUR TEST
387C INF = 1
388C SUP = 1
389C
390 nb_ecn= 0
391 addne= add(2,1)
392 IF(igap==0)THEN
393 DO i=1,nb_ec
394 xmx = max(xm0(dir,irect(1,bpe(i))),xm0(dir,irect(2,bpe(i))),
395 . xm0(dir,irect(3,bpe(i))),xm0(dir,irect(4,bpe(i))))
396 . + tzinf
397 xmn = min(xm0(dir,irect(1,bpe(i))),xm0(dir,irect(2,bpe(i))),
398 . xm0(dir,irect(3,bpe(i))),xm0(dir,irect(4,bpe(i))))
399 . - tzinf
400 IF(xmn<seuil.AND.inf==1) THEN
401C ON STOCKE DANS LE BAS DE LA PILE BP
402 addne = addne + 1
403 pe(addne) = bpe(i)
404 ENDIF
405 IF(xmx>=seuil.AND.sup==1) THEN
406C ON STOCKE EN ECRASANT PROGRESSIVEMENT BPE
407 nb_ecn = nb_ecn + 1
408 bpe(nb_ecn) = bpe(i)
409 ENDIF
410 ENDDO
411 ELSE
412 DO i=1,nb_ec
413 xmn = min(xm0(dir,irect(1,bpe(i))),xm0(dir,irect(2,bpe(i))),
414 . xm0(dir,irect(3,bpe(i))),xm0(dir,irect(4,bpe(i))))
415 - -max(min(max(gapsmx,gapmin),gapmax)+dgapload,depth,drad)
416 - -marge
417 IF(xmn<seuil.AND.inf==1) THEN
418C ON STOCKE DANS LE BAS DE LA PILE BP
419 addne = addne + 1
420 pe(addne) = bpe(i)
421 ENDIF
422 xmx = max(xm0(dir,irect(1,bpe(i))),xm0(dir,irect(2,bpe(i))),
423 . xm0(dir,irect(3,bpe(i))),xm0(dir,irect(4,bpe(i))))
424 + +max(min(max(bgapsmx,gapmin),gapmax)+dgapload,depth,drad)
425 + +marge
426 IF(xmx>=seuil.AND.sup==1) THEN
427C ON STOCKE EN ECRASANT PROGRESSIVEMENT BPE
428 nb_ecn = nb_ecn + 1
429 bpe(nb_ecn) = bpe(i)
430 ENDIF
431 ENDDO
432 END IF
433C
434C 4- REMPLIR LES TABLEAUX D'ADRESSES
435C
436 add(1,2) = addnn
437 add(2,2) = addne
438C-----on remplit les min de la boite suivante et les max de la courante
439C (i.e. seuil est un max pour la courante)
440C on va redescendre et donc on definit une nouvelle boite
441C on remplit les max de la nouvelle boite
442C initialises dans i7buc1 a 1.E30 comme ca on recupere
443C soit XMAX soit le max de la boite
444 xyzm(1,i_add+1) = xyzm(1,i_add)
445 xyzm(2,i_add+1) = xyzm(2,i_add)
446 xyzm(3,i_add+1) = xyzm(3,i_add)
447 xyzm(4,i_add+1) = xyzm(4,i_add)
448 xyzm(5,i_add+1) = xyzm(5,i_add)
449 xyzm(6,i_add+1) = xyzm(6,i_add)
450 xyzm(dir,i_add+1) = seuil
451 xyzm(dir+3,i_add) = seuil
452C
453 nb_nc = nb_ncn
454 nb_ec = nb_ecn
455C on incremente le niveau de descente avant de sortir
456 i_add = i_add + 1
457 IF(i_add>=1000) THEN
458C TROP NIVEAUX PILE ON VAS LES PRENDRE PLUS GRANDES...
459 IF ( nb_n_b == numnod) THEN
460C WRITE(IOUT,*)'***COMPUTATION STOPPED WHILE INFINITELY LOOPING'
461C WRITE(ISTDO,*)'***COMPUTATION STOPPED WHILE INFINITELY LOOPING'
462C CALL ARRET(2)
463 IF (istamping == 1) THEN
464 CALL ancmsg(msgid=775,
465 . msgtype=msgerror,
466 . anmode=aninfo,
467 . i1=id,
468 . c1=titr)
469 ELSE
470 CALL ancmsg(msgid=685,
471 . msgtype=msgerror,
472 . anmode=aninfo,
473 . i1=id,
474 . c1=titr)
475 ENDIF
476 ENDIF
477 i_mem = 1
478 RETURN
479 ENDIF
480C
481C ce return n'est atteint que dans le cas ok = 0
482 RETURN
#define my_real
Definition cppsort.cpp:32
subroutine i7cmp3(i_stok, cand_e, cand_n, iflag, pene, prov_n, prov_e)
Definition i7cmp3.F:82
subroutine ymax(idn, fac, npc, pld, stiffmin, stiffmax, stiffini, stiffavg)
Definition law100_upd.F:272
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
initmumps id
integer, parameter nchartitle
subroutine i21cor3t(x, irect, nsv, cand_e, cand_n, gapv, igap, gap, gap_s, gapmin, gapmax, xm0, depth, drad, ix1, ix2, ix3, ix4, nsvg, x1, x2, x3, x4, y1, y2, y3, y4, z1, z2, z3, z4, xi, yi, zi, dgapload)
Definition i21cor3t.F:36
subroutine i7dst3(ix3, ix4, x1, x2, x3, x4, y1, y2, y3, y4, z1, z2, z3, z4, xi, yi, zi, x0, y0, z0, nx1, ny1, nz1, nx2, ny2, nz2, nx3, ny3, nz3, nx4, ny4, nz4, p1, p2, p3, p4, lb1, lb2, lb3, lb4, lc1, lc2, lc3, lc4, last)
Definition i7dst3.F:46
subroutine i7dstk(i_add, nb_nc, nb_ec, add, bpn, pn, bpe, pe)
Definition i7dstk.F:34
subroutine i7pen3(marge, gapv, n1, n2, n3, pene, nx1, ny1, nz1, nx2, ny2, nz2, nx3, ny3, nz3, nx4, ny4, nz4, p1, p2, p3, p4, last)
Definition i7pen3.F:43
subroutine ancmsg(msgid, msgtype, anmode, i1, i2, i3, i4, i5, i6, i7, i8, i9, i10, i11, i12, i13, i14, i15, i16, i17, i18, i19, i20, r1, r2, r3, r4, r5, r6, r7, r8, r9, c1, c2, c3, c4, c5, c6, c7, c8, c9, prmode)
Definition message.F:889