OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
i17main_pena.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_LAG split in 3 routines for SPMD reorganization
24!||====================================================================
25!|| i17main_crit_tri ../engine/source/interfaces/int17/i17main_pena.F
26!||--- called by ------------------------------------------------------
27!|| inttri ../engine/source/interfaces/intsort/inttri.F
28!||--- calls -----------------------------------------------------
29!|| i17crit ../engine/source/interfaces/int17/i17crit.F
30!||--- uses -----------------------------------------------------
31!|| groupdef_mod ../common_source/modules/groupdef_mod.F
32!|| intbufdef_mod ../common_source/modules/interfaces/intbufdef_mod.F90
33!||====================================================================
34 SUBROUTINE i17main_crit_tri(
35 1 IPARI ,INTBUF_TAB ,X ,NIN ,
36 2 ITASK ,IGRBRIC ,EMINX ,NME ,
37 3 NMES ,XSLV _L ,XMSR_L ,SIZE_T ,IXS ,
38 4 IXS16 ,IXS20 )
39C-----------------------------------------------
40C M o d u l e s
41C-----------------------------------------------
42 USE intbufdef_mod
43 USE groupdef_mod
44C-----------------------------------------------
45C D u m m y A r g u m e n t s
46C
47C-------------------------------------------------------------------------------
48C NOM DIMENSION DESCRIPTION E/S
49C-------------------------------------------------------------------------------
50C
51C NIN 1 NUMERO INTERFACE E
52C
53C IPARI NPARI,NINTER PARAMETRES D'INTERFACE E
54C
55C X 3,NUMNOD COORDONNEES E
56C
57C V 3,NUMNOD VITESSES E
58C
59C EMINX 6*(NME+NMES) MIN MAX DE CHAQUE ELEMENT TMP_GLOBAL
60C
61C WAT 4*(NME+100)+4*(NMES+100) TABLEAUX DE TRI TMP_TASK
62C
63C-----------------------------------------------
64C I m p l i c i t T y p e s
65C-----------------------------------------------
66#include "implicit_f.inc"
67C-----------------------------------------------
68C C o m m o n B l o c k s
69C-----------------------------------------------
70#include "com04_c.inc"
71#include "com08_c.inc"
72#include "param_c.inc"
73C-----------------------------------------------
74C D u m m y A r g u m e n t s
75C-----------------------------------------------
76 INTEGER NIN,ITASK ,NC,N_MUL_MX ,NKMAX , NME, NMES
77 INTEGER IPARI(NPARI,NINTER),
78 . IXS(NIXS,*) ,IXS16(8,*) ,IXS20(12,*)
79C REAL
80 my_real
81 . x(3,*), eminx(6,*), size_t(*),
82 . xslv_l(*), xmsr_l(*)
83
84 TYPE(intbuf_struct_) INTBUF_TAB
85C-----------------------------------------------
86 TYPE (GROUP_) , DIMENSION(NGRBRIC) :: IGRBRIC
87C-----------------------------------------------
88C L o c a l V a r i a b l e s
89C-----------------------------------------------
90 INTEGER NAD,EAD,LWAT,
91 . IGN,IGE,MULTIMP,NOINT,I,MX_CAND
92C REAL
93 my_real
94 . startt, stopt,xx,xy,xz,tzinf,minbox,
95 . azero(3,numnod)
96C-----------------------------------------------
97C S o u r c e L i n e s
98C-----------------------------------------------
99 DO i=1,numnod
100 azero(1,i) = zero
101 azero(2,i) = zero
102 azero(3,i) = zero
103 ENDDO
104 multimp = ipari(23,nin)
105 ign = ipari(36,nin)
106 ige = ipari(34,nin)
107 mx_cand=multimp*ipari(18,nin)
108 startt = intbuf_tab%VARIABLES(3)
109 stopt = intbuf_tab%VARIABLES(11)
110 IF(startt>tt) RETURN
111 IF(tt>stopt) RETURN
112C -------------------------------------------------------------
113C=======================================================================
114C TEST pour savoir s'il faut retrier + initialisation
115C=======================================================================
116C SIZE_T(NIN)=ZERO init dans inttri
117 CALL i17crit(
118 1 x ,azero ,azero ,igrbric(ige)%ENTITY ,eminx ,
119 2 nme ,itask ,intbuf_tab%XSAV,ixs ,ixs16 ,
120 3 ixs20 ,xmsr_l ,size_t(nin))
121C -------------------------------------------------------------
122C CALL MY_BARRIER inutile
123C -------------------------------------------------------------
124 CALL i17crit(
125 1 x ,azero ,azero ,igrbric(ign)%ENTITY,eminx(1,nme+1),
126 2 nmes ,itask ,intbuf_tab%XSAV,ixs ,ixs16 ,
127 3 ixs20 ,xslv_l ,size_t(nin) )
128C
129 RETURN
130 END
131C
132!||====================================================================
133!|| i17main_tri ../engine/source/interfaces/int17/i17main_pena.F
134!||--- called by ------------------------------------------------------
135!|| inttri ../engine/source/interfaces/intsort/inttri.F
136!||--- calls -----------------------------------------------------
137!|| ancmsg ../engine/source/output/message/message.F
138!|| arret ../engine/source/system/arret.F
139!|| i17buce_pena ../engine/source/interfaces/int17/i17buce.F
140!|| i17frot ../engine/source/interfaces/int17/i17main_pena.F
141!|| i17xsave ../engine/source/interfaces/int17/i17xsave.F
142!|| my_barrier ../engine/source/system/machine.F
143!|| spmd_tri17box ../engine/source/mpi/interfaces/spmd_tri17box.F
144!|| spmd_tri17gat ../engine/source/mpi/interfaces/spmd_i7crit.F
145!|| startime ../engine/source/system/timer_mod.F90
146!|| stoptime ../engine/source/system/timer_mod.F90
147!||--- uses -----------------------------------------------------
148!|| groupdef_mod ../common_source/modules/groupdef_mod.F
149!|| intbufdef_mod ../common_source/modules/interfaces/intbufdef_mod.F90
150!|| message_mod ../engine/share/message_module/message_mod.F
151!|| timer_mod ../engine/source/system/timer_mod.F90
152!||====================================================================
153 SUBROUTINE i17main_tri(TIMERS,
154 1 IPARI ,INTBUF_TAB ,X ,NIN ,
155 2 ITASK ,IGRBRIC ,NME ,NMES ,
156 3 EMINX ,IXS ,IXS16 ,IXS20 ,WEIGHT ,
157 3 ISENDTO,IRECVFROM ,RETRI ,IAD_ELEM,FR_ELEM ,
158 4 ITAB ,V ,NME_T ,ESH_T )
159C-----------------------------------------------
160C M o d u l e s
161C-----------------------------------------------
162 USE timer_mod
163 USE message_mod
164 USE intbufdef_mod
165 USE groupdef_mod
166C-----------------------------------------------
167C D u m m y A r g u m e n t s
168C
169C-------------------------------------------------------------------------------
170C NOM DIMENSION DESCRIPTION E/S
171C-------------------------------------------------------------------------------
172C
173C NIN 1 NUMERO INTERFACE E
174C
175C IPARI NPARI,NINTER PARAMETRES D'INTERFACE E
176C
177C X 3,NUMNOD COORDONNEES E
178C
179C V 3,NUMNOD VITESSES E
180C
181C EMINX 6*NME<6*NUMELS MIN MAX DE CHAQUE ELEMENT TMP_GLOBAL
182C
183C WAT 4*(NME+100)+4*(NMES+100) TABLEAUX DE TRI TMP_TASK
184C
185C-----------------------------------------------
186C I m p l i c i t T y p e s
187C-----------------------------------------------
188#include "implicit_f.inc"
189#include "comlock.inc"
190C-----------------------------------------------
191C C o m m o n B l o c k s
192C-----------------------------------------------
193#include "com01_c.inc"
194#include "com04_c.inc"
195#include "com08_c.inc"
196#include "param_c.inc"
197#include "timeri_c.inc"
198 COMMON /i17mainc/bminma,nmesr
199 INTEGER NMESR
200 my_real
201 . BMINMA(6)
202C-----------------------------------------------
203C D u m m y A r g u m e n t s
204C-----------------------------------------------
205 TYPE(TIMER_), INTENT(INOUT) :: TIMERS
206 INTEGER NIN,ITASK , NME, NMES, RETRI, NME_T, ESH_T
207 INTEGER IPARI(NPARI,NINTER),
208 . ixs(nixs,*) ,ixs16(8,*) ,ixs20(12,*),weight(*),
209 . isendto(*),irecvfrom(*),iad_elem(*),fr_elem(*),
210 . itab(*)
211C REAL
212 my_real
213 . x(3,*), v(3,*), eminx(6,*)
214
215 TYPE(intbuf_struct_) INTBUF_TAB
216C-----------------------------------------------
217 TYPE (GROUP_) , DIMENSION(NGRBRIC) :: IGRBRIC
218C-----------------------------------------------
219C L o c a l V a r i a b l e s
220C-----------------------------------------------
221 INTEGER NAD,EAD,LWAT,RESULT,
222 . IGN,IGE,MULTIMP,NOINT,I,MX_CAND, NB_N_B
223C REAL
224 my_real
225 . startt, stopt,xx,xy,xz,tzinf,minbox,dist,
226 . xmaxl, ymaxl, zmaxl, xminl, yminl, zminl,
227 . azero(3,numnod)
228C-----------------------------------------------
229C S o u r c e L i n e s
230C-----------------------------------------------
231 DO i=1,numnod
232 azero(1,i) = zero
233 azero(2,i) = zero
234 azero(3,i) = zero
235 ENDDO
236 noint = ipari(15,nin)
237 multimp = ipari(23,nin)
238 ign = ipari(36,nin)
239 ige = ipari(34,nin)
240 lwat = 4*(nme+100)+4*(nmes+100)
241C
242 mx_cand=multimp*ipari(18,nin)
243 startt = intbuf_tab%VARIABLES(3)
244 stopt = intbuf_tab%VARIABLES(11)
245 IF(startt>tt) RETURN
246 IF(tt>stopt) RETURN
247C -------------------------------------------------------------
248C -------------------------------------------------------------
249C-----------------------------------------------
250C frottement (deplace de i7for3 a ici pour maj avant echange SPMD)
251C-----------------------------------------------
252 CALL i17frot(
253 1 itask,intbuf_tab%FROTM,intbuf_tab%FROTS,nme,nmes)
254C=======================================================================
255C TEST pour savoir s'il faut retrier + initialisation
256C=======================================================================
257 dist = intbuf_tab%VARIABLES(5)
258 CALL my_barrier
259C -------------------------------------------------------------
260 IF(dist<zero) THEN
261 retri=1
262 tzinf = intbuf_tab%VARIABLES(8)
263 minbox = intbuf_tab%VARIABLES(12)
264 intbuf_tab%VARIABLES(5) = abs(intbuf_tab%VARIABLES(5))
265C BMINMA inverse par rapport aux autres interfaces de contact
266 bminma(1)=ep30
267 bminma(2)=ep30
268 bminma(3)=ep30
269 bminma(4)=-ep30
270 bminma(5)=-ep30
271 bminma(6)=-ep30
272C=======================================================================
273C TRI
274C=======================================================================
275 ipari(35,nin) = 0
276C BARRIER INIT BMINMA
277 CALL my_barrier
278C -------------------------------------------------------------
279C CALCUL BORNE DOMAINE REMONTE DANS I17XSAVE
280C -------------------------------------------------------------
281 CALL i17xsave(
282 1 x ,v ,azero ,ixs ,ixs16,
283 2 nmes ,nme_t ,esh_t ,igrbric(ige)%ENTITY,igrbric(ign)%ENTITY,
284 3 eminx ,itask ,intbuf_tab%XSAV,xminl ,yminl ,
285 3 zminl ,xmaxl ,ymaxl ,zmaxl )
286#include "lockon.inc"
287 bminma(1) = min(bminma(1),xminl)
288 bminma(2) = min(bminma(2),yminl)
289 bminma(3) = min(bminma(3),zminl)
290 bminma(4) = max(bminma(4),xmaxl)
291 bminma(5) = max(bminma(5),ymaxl)
292 bminma(6) = max(bminma(6),zmaxl)
293#include "lockoff.inc"
294C BARRIER BMINMA
295 CALL my_barrier
296 IF(itask==0)THEN
297 IF(abs(bminma(6)-bminma(3))>2*ep30.OR.
298 + abs(bminma(5)-bminma(2))>2*ep30.OR.
299 + abs(bminma(4)-bminma(1))>2*ep30)THEN
300 CALL ancmsg(msgid=87,anmode=aninfo,
301 . i1=noint)
302 CALL arret(2)
303 END IF
304 bminma(1) = bminma(1) - tzinf
305 bminma(2) = bminma(2) - tzinf
306 bminma(3) = bminma(3) - tzinf
307 bminma(4) = bminma(4) + tzinf
308 bminma(5) = bminma(5) + tzinf
309 bminma(6) = bminma(6) + tzinf
310 nmesr = 0
311 IF(nspmd>1)THEN
312C -------------------------------------------------------------
313C recuperation des noeuds remote NMESR stockes dans XREM
314C -------------------------------------------------------------
315 CALL spmd_tri17box(
316 1 igrbric(ign)%ENTITY ,nmes ,x ,v ,intbuf_tab%FROTS ,
317 2 intbuf_tab%KS,bminma ,weight,nin ,isendto ,
318 3 irecvfrom ,nmesr ,ixs ,ixs16,eminx(1,nme+1))
319 END IF
320 END IF
321 nb_n_b = 1
322C -------------------------------------------------------------
323 CALL my_barrier
324C -------------------------------------------------------------
325 CALL i17buce_pena(
326 1 igrbric(ign)%ENTITY,ixs ,ixs16 ,ixs20 ,igrbric(ige)%ENTITY,
327 2 nme_t ,lwat ,nmes ,intbuf_tab%CAND_E,
328 . intbuf_tab%CAND_N,
329 3 noint ,ipari(35,nin) ,tzinf ,minbox ,eminx ,
330 4 intbuf_tab%XSAV,itask ,x ,azero ,azero ,
331 5 mx_cand ,eminx(1,nme+1),esh_t ,intbuf_tab%FROTS,intbuf_tab%KS,
332 6 nin ,nmesr ,nb_n_b ,bminma )
333C -------------------------------------------------------------
334 CALL my_barrier
335C -------------------------------------------------------------
336 IF(nspmd>1)THEN
337!$OMP SINGLE
338 IF (imonm > 0) CALL startime(timers,26)
339 intbuf_tab%VARIABLES(5) = -intbuf_tab%VARIABLES(5)
340 result = 0
341C comm SPMD apres tri (compactage)
342 CALL spmd_tri17gat(
343 1 result ,nmes ,intbuf_tab%CAND_N,ipari(35,nin),nin,
344 2 nmesr )
345C sauvegarde des candidats additionnels dans IPARI(24) pas besoin car pas de inacti
346c IPARI(24,NIN) = NMESR
347 IF (imonm > 0) CALL stoptime(timers,26)
348!$OMP END SINGLE
349
350 END IF
351 ENDIF
352C
353 RETURN
354 END
355C
356!||====================================================================
357!|| i17main_pena ../engine/source/interfaces/int17/i17main_pena.F
358!||--- called by ------------------------------------------------------
359!|| i7mainf ../engine/source/interfaces/int07/i7mainf.f
360!||--- calls -----------------------------------------------------
361!|| i17for3 ../engine/source/interfaces/int17/i17for3.F
362!|| my_barrier ../engine/source/system/machine.F
363!||--- uses -----------------------------------------------------
364!|| groupdef_mod ../common_source/modules/groupdef_mod.F
365!|| h3d_mod ../engine/share/modules/h3d_mod.F
366!|| intbufdef_mod ../common_source/modules/interfaces/intbufdef_mod.f90
367!||====================================================================
368 SUBROUTINE i17main_pena(
369 1 NIN ,IPARI ,INTBUF_TAB ,X ,V ,
370 2 A ,ITASK ,IGRBRIC ,EMINX ,MS ,
371 3 IXS ,IXS16 ,IXS20 ,STIFN ,FSKYI ,ISKY ,
372 4 FSAV ,FCONT ,NISKYFI ,H3D_DATA)
373C-----------------------------------------------
374C M o d u l e s
375C-----------------------------------------------
376 USE intbufdef_mod
377 USE h3d_mod
378 USE groupdef_mod
379C-----------------------------------------------
380C D u m m y A r g u m e n t s
381C
382C-------------------------------------------------------------------------------
383C NOM DIMENSION DESCRIPTION E/S
384C-------------------------------------------------------------------------------
385C
386C NIN 1 NUMERO INTERFACE E
387C
388C IPARI NPARI,NINTER PARAMETRES D'INTERFACE E
389C
390C X 3,NUMNOD COORDONNEES E
391C
392C V 3,NUMNOD VITESSES E
393C
394C EMINX 6*NME<6*NUMELS MIN MAX DE CHAQUE ELEMENT TMP_GLOBAL
395C
396C
397C-----------------------------------------------
398C I m p l i c i t T y p e s
399C-----------------------------------------------
400#include "implicit_f.inc"
401C-----------------------------------------------
402C C o m m o n B l o c k s
403C-----------------------------------------------
404#include "com04_c.inc"
405#include "com08_c.inc"
406#include "param_c.inc"
407#include "parit_c.inc"
408C-----------------------------------------------
409C D u m m y A r g u m e n t s
410C-----------------------------------------------
411 INTEGER NIN,ITASK,NISKYFI
412 INTEGER IPARI(NPARI,NINTER),
413 . IXS(NIXS,*) ,IXS16(8,*) ,IXS20(12,*) ,ISKY(*)
414C REAL
415 my_real
416 . X(3,*), V(3,*), A(3,*), MS(*),EMINX(6,*),STIFN(*),
417 . FSKYI(*), FSAV(*),FCONT(3,*)
418
419 TYPE(INTBUF_STRUCT_) INTBUF_TAB
420 TYPE(H3D_DATABASE) :: H3D_DATA
421C-----------------------------------------------
422 TYPE (GROUP_) , DIMENSION(NGRBRIC) :: IGRBRIC
423C-----------------------------------------------
424C L o c a l V a r i a b l e s
425C-----------------------------------------------
426 INTEGER NME,NAD,EAD,
427 . IGN,IGE,MULTIMP,NOINT,I,MX_CAND,NMES,LSKYI17
428C REAL
429 my_real
430 . startt, stopt
431C-----------------------------------------------
432C S o u r c e L i n e s
433C-----------------------------------------------
434 noint = ipari(15,nin)
435 multimp = ipari(23,nin)
436 ign = ipari(36,nin)
437 ige = ipari(34,nin)
438 nmes =igrbric(ign)%NENTITY
439 nme =igrbric(ige)%NENTITY
440 mx_cand=multimp*ipari(18,nin)
441 IF(iparit/=0)THEN
442C LSKYI17=MX_CAND
443C LSKYI17 fonction de IMAXIMP : nombre d'impacts max defini dans starter/lecint
444 lskyi17=max(mx_cand,multimp*ipari(5,nin)*8)
445 ELSE
446 lskyi17=0
447 END IF
448 startt = intbuf_tab%VARIABLES(3)
449 stopt = intbuf_tab%VARIABLES(11)
450 IF(startt>tt) RETURN
451 IF(tt>stopt) RETURN
452C -------------------------------------------------------------
453C -------------------------------------------------------------
454 CALL my_barrier
455C=======================================================================
456C CONTACT
457C=======================================================================
458 CALL i17for3(
459 1 x ,v ,intbuf_tab%CAND_N,intbuf_tab%CAND_E,ipari(35,nin) ,
460 2 ixs ,ixs16 ,eminx ,igrbric(ign)%ENTITY,igrbric(ige)%ENTITY,
461 3 itask ,a ,ipari(30,nin),nin ,eminx(1,nme+1),
462 4 stifn ,fskyi ,isky ,nme ,nmes ,
463 5 intbuf_tab%FROTM,intbuf_tab%FROTS,intbuf_tab%KM,intbuf_tab%KS,
464 5 intbuf_tab%VARIABLES(1) ,
465 6 fsav ,fcont ,ms ,niskyfi ,lskyi17 ,
466 7 noint ,h3d_data)
467C -------------------------------------------------------------
468 CALL my_barrier
469C -------------------------------------------------------------
470 RETURN
471 END
472C
473!||====================================================================
474!|| i17frot ../engine/source/interfaces/int17/i17main_pena.F
475!||--- called by ------------------------------------------------------
476!|| i17main_tri ../engine/source/interfaces/int17/i17main_pena.F
477!||====================================================================
478 SUBROUTINE i17frot(ITASK,FROTM,FROTS,NME,NSE)
479C-----------------------------------------------
480C I m p l i c i t T y p e s
481C-----------------------------------------------
482#include "implicit_f.inc"
483C-----------------------------------------------
484C C o m m o n B l o c k s
485C-----------------------------------------------
486#include "task_c.inc"
487C-----------------------------------------------
488C D u m m y A r g u m e n t s
489C-----------------------------------------------
490 INTEGER ITASK,NME,NSE
491C REAL
492 my_real
493 . frotm(7,*),frots(7,*)
494C-----------------------------------------------
495C L o c a l V a r i a b l e s
496C-----------------------------------------------
497 INTEGER I,NMEF,NMEL,NSEF,NSEL
498 my_real
499 . AA
500C-----------------------------------------------
501 NMEF = 1 + itask*nme / nthread
502 nmel = (itask+1)*nme / nthread
503 nsef = 1 + itask*nse / nthread
504 nsel = (itask+1)*nse / nthread
505C-----------------------------------------------
506C frottement (ancienne contrainte de frottement)
507C-----------------------------------------------
508 DO i=nmef,nmel
509 aa = one/max(em20,frotm(4,i))
510 frotm(5,i)=aa*frotm(1,i)
511 frotm(6,i)=aa*frotm(2,i)
512 frotm(7,i)=aa*frotm(3,i)
513C
514 frotm(1,i)=zero
515 frotm(2,i)=zero
516 frotm(3,i)=zero
517 frotm(4,i)=zero
518 ENDDO
519C
520 DO i=nsef,nsel
521 aa = one/max(em20,frots(4,i))
522 frots(5,i)=aa*frots(1,i)
523 frots(6,i)=aa*frots(2,i)
524 frots(7,i)=aa*frots(3,i)
525C
526 frots(1,i)=zero
527 frots(2,i)=zero
528 frots(3,i)=zero
529 frots(4,i)=zero
530 ENDDO
531C
532 RETURN
533 END
#define my_real
Definition cppsort.cpp:32
subroutine i17buce_pena(neles, ixs, ixs16, ixs20, nelem, nme, lwat, nmes, cand_e, cand_n, noint, i_stok_glob, tzinf, minbox, eminxm, xsav, itask, x, v, a, mx_cand, eminxs, esh_t, frots, ks, nin, nmesr, nb_n_b, bminma)
Definition i17buce.F:41
subroutine i17crit(x, v, a, nelem, eminx, nme, itask, xsav, ixs, ixs16, ixs20, xmsr_g, size_t_g)
Definition i17crit.F:37
subroutine i17for3(x, v, candn, cande, i_stok, ixs, ixs16, eminxm, neles, nelem, itask, a, itied, nint, eminxs, stifn, fskyi, isky, nme, nse, frotm, frots, km, ks, fric, fsav, fcont, ms, niskyfi, lskyi17, noint, h3d_data)
Definition i17for3.F:49
subroutine i17main_tri(timers, ipari, intbuf_tab, x, nin, itask, igrbric, nme, nmes, eminx, ixs, ixs16, ixs20, weight, isendto, irecvfrom, retri, iad_elem, fr_elem, itab, v, nme_t, esh_t)
subroutine i17frot(itask, frotm, frots, nme, nse)
subroutine i17main_pena(nin, ipari, intbuf_tab, x, v, a, itask, igrbric, eminx, ms, ixs, ixs16, ixs20, stifn, fskyi, isky, fsav, fcont, niskyfi, h3d_data)
subroutine i17main_crit_tri(ipari, intbuf_tab, x, nin, itask, igrbric, eminx, nme, nmes, xslv _l, xmsr_l, size_t, ixs, ixs16, ixs20)
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
subroutine i7mainf(timers, ipari, x, a, ale_connectivity, xcell, icodt, fsav, v, ms, dt2t, neltst, ityptst, itab, stifn, fskyi, isky, fcont, nin, lindmax, kinet, jtask, nb_jlt, nb_jlt_new, nb_stok_n, elbuf_tab, niskyfi, newfront, nstrf, secfcum, igroups, icontact, viscn, num_imp, ns_imp, ne_imp, ind_imp, fsavsub, nrtmdim, igrbric, eminx, ixs, ixs16, ixs20, fncont, ftcont, iad_elem, fr_elem, rcontact, acontact, pcontact, temp, fthe, ftheskyi, pm, iparg, iad17, mskyi_sms, iskyi_sms, nodnx_sms, ms0, qfricint, npc, tf, condn, condnskyi, intbuf_tab, nodadt_therm, theaccfact, fbsav6, isensint, dimfb, ixig3d, kxig3d, wige, knot, igeo, multi_fvm, h3d_data, intbuf_fric_tab, knotlocpc, knotlocel, itask, tagncont, kloadpinter, loadpinter, loadp_hyd_inter, dgaploadint, s_loadpinter, interefric, s_xcell_remote, xcell_remote)
Definition i7mainf.F:89
#define min(a, b)
Definition macros.h:20
#define max(a, b)
Definition macros.h:21
subroutine spmd_tri17gat(result, nmes, cand_n, i_stok, nin, nmesr)
subroutine spmd_tri17box(nelems, nmes, x, v, frots, ks, bminmal, weight, nin, isendto, ircvfrom, nmesr, ixs, ixs16, eminxs)
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
subroutine arret(nn)
Definition arret.F:87
subroutine my_barrier
Definition machine.F:31
subroutine startime(event, itask)
Definition timer.F:93
subroutine stoptime(event, itask)
Definition timer.F:135