39#if ! defined(NO_FDM_MAPROW)
41#endif
43 IMPLICIT NONE
44#if ! defined(NO_FDM_MAPROW)
45#endif
46 TYPE (SMUMPS_ROOT_STRUC ) :: root
47 INTEGER LBUFR, LBUFR_BYTES
48 INTEGER ICNTL( 60 ), KEEP(500)
49 INTEGER(8) KEEP8(150)
50 REAL DKEEP(230)
51 INTEGER COMM_LOAD, ASS_IRECV
52 INTEGER BUFR( LBUFR )
53 INTEGER SLAVEF, NBFIN
54 INTEGER(8) :: LA, IPTRLU, , LRLUS, POSFAC
55 INTEGER IWPOS, IWPOSCB
56 INTEGER N, LIW
57 INTEGER IW( LIW )
58 REAL A( LA )
59 INTEGER, intent(in) :: LRGROUPS(N)
60 INTEGER(8) :: PTRFAC(KEEP(28))
61 INTEGER(8) :: PTRAST(KEEP(28))
62 INTEGER(8) :: PAMASTER(KEEP(28))
63 INTEGER PTRIST(KEEP(28)), PTLUST(KEEP(28))
64 INTEGER STEP(N), PIMASTER(KEEP(28))
65 INTEGER ( KEEP(28) )
66 INTEGER COMP
67 INTEGER NSTK( KEEP(28) )
68 INTEGER PERM(N)
69 INTEGER IFLAG, IERROR, COMM, MYID
70 INTEGER LPOOL, LEAF
71 INTEGER IPOOL( LPOOL )
72 INTEGER INODE_PERE, ISON
73 INTEGER :: NFS4FATHER
74 INTEGER NBROWS_ALREADY_SENT
75 INTEGER NSLAVES_PERE, NFRONT_PERE, NASS_PERE
76 INTEGER LIST_SLAVES_PERE( * )
77 INTEGER LMAP
78 INTEGER TROW( LMAP )
79 DOUBLE PRECISION OPASSW, OPELIW
80 REAL DBLARR(KEEP8(26))
81 INTEGER INTARR(KEEP8(27))
82 INTEGER LPTRAR, NELT
83 INTEGER FRTPTR( N+1 ), FRTELT( NELT )
84 INTEGER ITLOC( N+KEEP(253) ), FILS( N ), DAD( KEEP(28) )
85 REAL :: RHS_MUMPS(KEEP(255))
86 INTEGER(8), INTENT(IN) :: PTRARW( LPTRAR ), PTRAIW( LPTRAR )
87 INTEGER ND( KEEP(28) ), FRERE( KEEP(28) )
88 INTEGER ISTEP_TO_INIV2(KEEP(71)),
89 & TAB_POS_IN_PERE(SLAVEF+2,max(1,KEEP(56)))
90 include 'mpif.h'
91 include 'mumps_tags.h'
92 INTEGER IERR
93 INTEGER :: STATUS(MPI_STATUS_SIZE)
94 INTEGER NOSLA, I
95 INTEGER I_POSMYIDIN_PERE
96 INTEGER INDICE_PERE
97 INTEGER PDEST, PDEST_MASTER
98 LOGICAL :: LOCAL_ASSEMBLY_TO_BE_DONE
99 INTEGER NROWS_TO_SEND
100 INTEGER PDEST_MASTER_ISON, IPOS_IN_SLAVE
101 LOGICAL DESCLU, SLAVE_ISON
102 LOGICAL BLOCKING, SET_IRECV, MESSAGE_RECEIVED
103 INTEGER MSGSOU, MSGTAG
104 INTEGER LP
105 LOGICAL PACKED_CB
106 LOGICAL IS_ERROR_BROADCASTED, IS_ofType5or6
107 INTEGER ITYPE_SON, TYPESPLIT
108 INTEGER :: KEEP253_LOC
109 INTEGER :: NVSCHUR, NSLAVES_L, NROW_L, IROW_L, NASS_L, NELIM_L
110 LOGICAL :: CB_IS_LR
111 INTEGER :: IWXXF_HANDLER
112 REAL :: ADummy(1)
113 REAL, POINTER, DIMENSION(:) :: SON_A
114 INTEGER(8) :: IACHK, RECSIZE
115#if
116 INTEGER :: INFO_TMP(2)
117#endif
118 include 'mumps_headers.h'
119 INTEGER MUMPS_PROCNODE, MUMPS_TYPENODE, MUMPS_TYPESPLIT
121 INTEGER LMAP_LOC, allocok
122 INTEGER, ALLOCATABLE, DIMENSION(:) :: NBROW
123 INTEGER, ALLOCATABLE, DIMENSION(:) :: SLAVES_PERE
124 INTEGER, ALLOCATABLE, DIMENSION(:) :: MAP, PERM_LOC
125 is_error_broadcasted = .false.
127 & keep(199) )
129 & keep(199) )
130 is_oftype5or6 = ((typesplit.EQ.5).OR.(typesplit.EQ.6))
131 lp = icntl(1)
132 IF (icntl(4) .LE. 0) lp = -1
133 cb_is_lr = (iw(ptrist(step(ison))+xxlr).EQ.1 .OR.
134 & iw(ptrist(step(ison))+xxlr).EQ.3)
135 iwxxf_handler = iw(ptrist(step(ison))+xxf)
136#if ! defined(NO_FDM_MAPROW)
137#endif
138 ALLOCATE(slaves_pere(0:
max(1,nslaves_pere)), stat=allocok)
139 if (allocok .GT. 0) THEN
140 IF (lp > 0) THEN
142 & ' : PB allocation SLAVES_PERE in SMUMPS_MAPLIG'
143 ENDIF
144 iflag =-13
145 ierror = nslaves_pere+1
146 GOTO 700
147 endif
148 IF (nslaves_pere.GT.0)
149 &slaves_pere(1:nslaves_pere) = list_slaves_pere(1:nslaves_pere)
150 slaves_pere(0) =
mumps_procnode( procnode_steps(step(inode_pere)),
151 & keep(199) )
152 ALLOCATE(nbrow(0:nslaves_pere), stat=allocok)
153 if (allocok .GT. 0) THEN
154 IF (lp>0) THEN
156 & ' : PB allocation NBROW in SMUMPS_MAPLIG'
157 ENDIF
158 iflag =-13
159 ierror = nslaves_pere+1
160 GOTO 670
161 endif
162 lmap_loc = lmap
163 ALLOCATE(map(lmap_loc), stat=allocok)
164 if (allocok .GT. 0) THEN
165 IF (lp>0) THEN
166 write(lp,*)
myid,
' : PB allocation LMAP in SMUMPS_MAPLIG'
167 ENDIF
168 iflag =-13
169 ierror = lmap
170 GOTO 680
171 endif
172 map( 1 : lmap ) = trow( 1 : lmap )
174 & keep(199))
175 slave_ison = pdest_master_ison .NE.
myid
176 IF (slave_ison) THEN
177 IF ( ptrist(step( ison )) .EQ. 0 ) THEN
179 & ass_irecv,
180 & bufr, lbufr, lbufr_bytes, procnode_steps, posfac,
181 & iwpos, iwposcb, iptrlu,
182 & lrlu, lrlus, n, iw, liw, a, la, ptrist,
183 & ptlust, ptrfac,
184 & ptrast, step, pimaster, pamaster, nstk,
comp,
185 & iflag, ierror, comm,
186 & perm,
187 & ipool, lpool, leaf,
188 & nbfin,
myid, slavef,
189 &
190 & root, opassw, opeliw, itloc, rhs_mumps,
191 & fils, dad, ptrarw, ptraiw,
192 & intarr, dblarr,icntl,keep,keep8,dkeep,nd, frere, lptrar,
193 & nelt, frtptr, frtelt,
194 & istep_to_iniv2, tab_pos_in_pere, .true.
195 & , lrgroups
196 & )
197 IF ( iflag .LT. 0 ) THEN
198 is_error_broadcasted = .true.
199 GOTO 670
200 ENDIF
201 END IF
202#if ! defined(NO_FDM_MAPROW)
203 IF (
204 & ( iw( ptrist(step(ison)) + 1 + keep(ixsz) ) .NE.
205 & iw( ptrist(step(ison)) + 3 + keep(ixsz) ) ) .OR.
206 & ( keep(50) .NE. 0 .AND.
207 & iw( ptrist(step(ison)) + 6 + keep(ixsz) ) .NE. 0 ) )
208 & THEN
209 info_tmp=0
211 & iw(ptrist(step(ison))+xxa),
212 & inode_pere, ison, nslaves_pere, nfront_pere,
213 & nass_pere, lmap, nfs4father,
214 & slaves_pere(1:nslaves_pere),
215 & map,
216 & info_tmp)
217 IF (info_tmp(1) < 0) THEN
218 iflag = info_tmp(1)
219 ierror = info_tmp(2)
220 ENDIF
221 GOTO 670
222 ELSE
223 GOTO 10
224 ENDIF
225#endif
226 DO WHILE (
227 & ( iw( ptrist(step(ison)) + 1 + keep(ixsz) ) .NE.
228 & iw( ptrist(step(ison)) + 3 + keep(ixsz) ) ) .OR.
229 & ( keep(50) .NE. 0 .AND.
230 & iw( ptrist(step(ison)) + 6 + keep(ixsz) ) .NE. 0 ) )
231 IF ( keep(50).eq.0) THEN
232 msgsou = pdest_master_ison
233 msgtag = bloc_facto
234 ELSE
235 IF ( iw( ptrist(step(ison)) + 1 + keep(ixsz) ) .NE.
236 & iw( ptrist(step(ison)) + 3 + keep(ixsz) ) ) THEN
237 msgsou = pdest_master_ison
238 msgtag = bloc_facto_sym
239 ELSE
240 msgsou = mpi_any_source
241 msgtag = bloc_facto_sym_slave
242 END IF
243 END IF
244 blocking = .true.
245 set_irecv= .false.
246 message_received = .false.
248 & ass_irecv, blocking, set_irecv, message_received,
249 & msgsou, msgtag,
250 & status,
251 & bufr, lbufr, lbufr_bytes, procnode_steps, posfac,
252 & iwpos, iwposcb, iptrlu,
253 & lrlu, lrlus, n, iw, liw, a, la, ptrist,
254 & ptlust, ptrfac,
255 & ptrast, step, pimaster, pamaster, nstk,
comp,
256 & iflag, ierror, comm,
257 & perm, ipool, lpool, leaf, nbfin,
myid, slavef,
258 &
259 & root, opassw, opeliw, itloc, rhs_mumps,
260 & fils, dad, ptrarw, ptraiw,
261 & intarr, dblarr,icntl,keep,keep8,dkeep,nd, frere, lptrar,
262 & nelt, frtptr, frtelt,
263 & istep_to_iniv2, tab_pos_in_pere, .true.
264 & , lrgroups
265 & )
266 IF ( iflag .LT. 0 ) THEN
267 is_error_broadcasted = .true.
268 GOTO 670
269 ENDIF
270 END DO
271 ENDIF
272#if ! defined(NO_FDM_MAPROW)
273 10 CONTINUE
274#endif
275 IF ( nslaves_pere .EQ. 0 ) THEN
276 nbrow( 0 ) = lmap_loc
277 ELSE
278 DO i = 0, nslaves_pere
279 nbrow( i ) = 0
280 END DO
281 DO i = 1, lmap_loc
282 indice_pere = map( i )
284 & keep,keep8, inode_pere, step, n, slavef,
285 & istep_to_iniv2, tab_pos_in_pere,
286 &
287 & nass_pere,
288 & nfront_pere - nass_pere,
289 & nslaves_pere,
290 & indice_pere,
291 & nosla,
292 & ipos_in_slave )
293 nbrow( nosla ) = nbrow( nosla ) + 1
294 END DO
295 DO i = 1, nslaves_pere
296 nbrow(i)=nbrow(i)+nbrow(i-1)
297 ENDDO
298 ENDIF
299 ALLOCATE(perm_loc(lmap_loc), stat=allocok)
300 IF (allocok .GT. 0) THEN
301 IF (lp.GT.0) THEN
302 write(lp,*)
myid,
': PB allocation PERM_LOC in SMUMPS_MAPLIG'
303 ENDIF
304 iflag =-13
305 ierror = lmap_loc
306 GOTO 670
307 ENDIF
308 keep253_loc = 0
309 DO i = lmap_loc, 1, -1
310 indice_pere = map( i )
311 IF (indice_pere > nfront_pere - keep(253)) THEN
312 keep253_loc = keep253_loc + 1
313 ENDIF
315 & keep,keep8, inode_pere, step, n, slavef,
316 & istep_to_iniv2, tab_pos_in_pere,
317 &
318 & nass_pere,
319 & nfront_pere - nass_pere,
320 & nslaves_pere,
321 & indice_pere,
322 & nosla,
323 & ipos_in_slave )
324 perm_loc( nbrow( nosla ) ) = i
325 nbrow( nosla ) = nbrow( nosla ) - 1
326 ENDDO
327 DO i = 0, nslaves_pere
328 nbrow(i)=nbrow(i)+1
329 END DO
330 IF ((keep(114).EQ.1) .AND. (keep(50).EQ.2) .AND.
331 & (keep(116).GT.0) .AND. ((lmap_loc-keep253_loc).GT.0)
332 & ) THEN
333 IF (itype_son.EQ.1) THEN
334 nelim_l = iw(ptlust(step(ison))+1+keep(ixsz))
335 nass_l = nelim_l +
336 & iw(ptlust(step(ison))+3+keep(ixsz))
337 irow_l = ptlust(step(ison))+6+keep(ixsz)+nass_l
338 nrow_l = lmap_loc
339 ELSE
340 nrow_l = lmap_loc
341 nslaves_l = iw( ptrist(step( ison )) + 5 + keep(ixsz) )
342 irow_l = ptrist(step(ison)) + 6 + nslaves_l + keep(ixsz)
343 ENDIF
345 & n,
346 & nrow_l-keep253_loc,
347 & keep(116),
348 & iw(irow_l),
349 & perm, nvschur )
350 ELSE
351 nvschur = 0
352 ENDIF
353 pdest_master = slaves_pere(0)
354 i_posmyidin_pere = -99999
355 local_assembly_to_be_done = .false.
356 DO i = 0, nslaves_pere
357 IF (slaves_pere(i) .EQ.
myid)
THEN
358 i_posmyidin_pere = i
359 local_assembly_to_be_done = .true.
360#if ! defined(NO_FDM_DESCBAND)
361 IF (ptrist(step(inode_pere)) .EQ. 0
362 & .AND.
myid .NE. pdest_master)
THEN
364 & ass_irecv,
365 & bufr, lbufr, lbufr_bytes, procnode_steps, posfac,
366 & iwpos, iwposcb, iptrlu,
367 & lrlu, lrlus, n, iw, liw, a, la, ptrist,
368 & ptlust, ptrfac,
369 & ptrast, step, pimaster, pamaster, nstk,
comp,
370 & iflag, ierror, comm,
371 & perm, ipool, lpool, leaf, nbfin,
myid, slavef,
372 &
373 & root, opassw, opeliw, itloc, rhs_mumps,
374 & fils, dad, ptrarw, ptraiw,
375 & intarr, dblarr,icntl,keep,keep8,dkeep,nd, frere, lptrar,
376 & nelt, frtptr, frtelt,
377 & istep_to_iniv2, tab_pos_in_pere, .true.
378 & , lrgroups
379 & )
380 IF ( iflag .LT. 0 ) THEN
381 is_error_broadcasted = .true.
382 GOTO 600
383 ENDIF
384 ENDIF
385#endif
386 ENDIF
387 END DO
388 IF (keep(120).NE.0 .AND. local_assembly_to_be_done) THEN
390 & slaves_pere(i_posmyidin_pere),
391 &
myid, pdest_master, ison, inode_pere,
392 & nslaves_pere, nass_pere, nfront_pere, nfs4father,
393 & lmap_loc, map, nbrow, perm_loc,
394 & is_oftype5or6, iflag, ierror,
395 & n, slavef, keep, ipool, lpool, step,
396 & procnode_steps, comm_load, istep_to_iniv2, tab_pos_in_pere,
397 & keep8, iw, liw, a, la, lrlu, lrlus, iptrlu, iwposcb,
398 & ptrist, ptlust, ptrast, pamaster, pimaster, nd,
399 & nelt, frtptr, frtelt,
400 & opassw, opeliw,
401 & itloc, rhs_mumps, keep253_loc, nvschur,
402 & fils, dad, lptrar, ptrarw, ptraiw, intarr, dblarr, icntl,
403 & itype_son, lrgroups)
404 local_assembly_to_be_done = .false.
405 IF (iflag < 0) THEN
406 GOTO 600
407 ENDIF
408 ENDIF
409 DO i = nslaves_pere, 0, -1
410 pdest = slaves_pere( i )
411 IF ( pdest .NE.
myid )
THEN
412 desclu = .false.
413 nbrows_already_sent = 0
414 IF (i == nslaves_pere) THEN
415 nrows_to_send=lmap_loc-nbrow(i)+1
416 ELSE
417 nrows_to_send=nbrow(i+1)-nbrow(i)
418 ENDIF
419 packed_cb=(iw(ptrist(step(ison))+xxs).EQ.s_cb1comp)
420 ierr = -1
421 DO WHILE (ierr .EQ. -1)
422 IF ( iw( ptrist(step(ison) )+keep(ixsz) )
423 & .GT. n + keep(253) ) THEN
424 WRITE(*,*)
myid,
': Internal error in Maplig'
425 WRITE(*,*)
myid,
': PTRIST(STEP(ISON))/N=',
426 & ptrist(step(ison)), n
427 WRITE(*,*)
myid,
': I, NBROW(I)=',i, nbrow(i)
428 WRITE(*,*)
myid,
': NSLAVES_PERE=',nslaves_pere
429 WRITE(*,*)
myid,
': ISON, INODE_PERE=',ison,inode_pere
430 WRITE(*,*)
myid,
': Son header=',
431 & iw(ptrist(step(ison)): ptrist(step(ison))+5+keep(ixsz))
433 END IF
434 IF (nrows_to_send .EQ. 0 .AND. pdest.NE.pdest_master) THEN
435 ierr = 0
436 cycle
437 ENDIF
438 IF (cb_is_lr) THEN
440 & nbrows_already_sent,
441 & desclu, inode_pere,
442 & nfront_pere, nass_pere, nfs4father,
443 & nslaves_pere, ison,
444 & nrows_to_send, lmap_loc, map,
445 & perm_loc(
min(lmap_loc,nbrow(i))),
446 & iw( ptrist(step(ison))),
447 & adummy, 1_8,
448 & i, pdest, pdest_master,
449 & comm, ierr,
450 & keep,keep8, step, n, slavef,
451 & istep_to_iniv2, tab_pos_in_pere, packed_cb,
452 & keep253_loc, nvschur,
454 & npiv_check = iw(ptlust(step(ison))+3+keep(ixsz)))
455 ELSE
457 & iw(ptrist(step(ison))+xxs),
458 & a, la,
459 & ptrast(step(ison)),
460 & iw(ptrist(step(ison))+xxd),
461 & iw(ptrist(step(ison))+xxr),
462 & son_a, iachk, recsize )
464 & desclu, inode_pere,
465 & nfront_pere, nass_pere, nfs4father,
466 & nslaves_pere, ison,
467 & nrows_to_send, lmap_loc, map,
468 & perm_loc(
min(lmap_loc,nbrow(i))),
469 & iw( ptrist(step(ison))),
470 & son_a(iachk:iachk+recsize-1_8),
471 & recsize,
472 & i, pdest, pdest_master,
473 & comm, ierr,
474 & keep,keep8, step, n, slavef,
475 & istep_to_iniv2, tab_pos_in_pere, packed_cb,
476 & keep253_loc, nvschur,
478 ENDIF
479 IF ( ierr .EQ. -2 ) THEN
480 iflag = -17
481 IF (lp .GT. 0) THEN
482 WRITE(lp,*)
483 & "FAILURE: SEND BUFFER TOO SMALL IN SMUMPS_MAPLIG"
484 ENDIF
485 ierror = (nrows_to_send + 3 )* keep( 34 ) +
486 & nrows_to_send * iw(ptrist(step(ison))+keep(ixsz))
487 & * keep( 35 )
488 GO TO 600
489 END IF
490 IF ( ierr .EQ. -3 ) THEN
491 IF (lp .GT. 0) THEN
492 WRITE(lp,*)
493 & "FAILURE: RECV BUFFER TOO SMALL IN SMUMPS_MAPLIG"
494 ENDIF
495 iflag = -20
496 ierror = (nrows_to_send + 3 )* keep( 34 ) +
497 & nrows_to_send * iw(ptrist(step(ison))+keep(ixsz))
498 & * keep( 35 )
499 GOTO 600
500 ENDIF
501 IF (keep(219).NE.0) THEN
502 IF ( ierr .EQ. -4 ) THEN
503 iflag = -13
504 ierror = nfs4father
505 IF (lp .GT. 0) THEN
506 WRITE(lp, *)
507 & "FAILURE: MAX_ARRAY allocation failed IN SMUMPS_MAPLIG"
508 ENDIF
509 GO TO 600
510 END IF
511 END IF
512 IF ( ierr .EQ. -1 ) THEN
513 IF (local_assembly_to_be_done) THEN
515 & slaves_pere(i_posmyidin_pere),
516 &
myid, pdest_master, ison, inode_pere,
517 & nslaves_pere, nass_pere, nfront_pere, nfs4father,
518 & lmap_loc, map, nbrow, perm_loc,
519 & is_oftype5or6, iflag, ierror,
520 & n, slavef, keep, ipool, lpool, step,
521 & procnode_steps, comm_load, istep_to_iniv2,
522 & tab_pos_in_pere,
523 & keep8, iw, liw, a, la, lrlu, lrlus, iptrlu, iwposcb,
524 & ptrist, ptlust, ptrast, pamaster, pimaster, nd,
525 & nelt, frtptr, frtelt,
526 & opassw, opeliw,
527 & itloc, rhs_mumps, keep253_loc, nvschur,
528 & fils, dad,
529 & lptrar, ptrarw, ptraiw, intarr, dblarr, icntl,
530 & itype_son, lrgroups)
531 local_assembly_to_be_done = .false
532 IF (iflag < 0) THEN
533 GOTO 600
534 ENDIF
535 ELSE
536 blocking = .false.
537 set_irecv = .true.
538 message_received = .false.
540 & ass_irecv, blocking, set_irecv, message_received,
541 & mpi_any_source, mpi_any_tag,
542 & status,
543 & bufr, lbufr, lbufr_bytes, procnode_steps, posfac,
544 & iwpos, iwposcb, iptrlu,
545 & lrlu, lrlus, n, iw, liw, a, la,
546 & ptrist, ptlust, ptrfac,
547 & ptrast, step, pimaster, pamaster, nstk,
comp,
548 & iflag, ierror, comm,
549 & perm, ipool, lpool, leaf, nbfin,
myid, slavef,
550 &
551 & root, opassw, opeliw, itloc, rhs_mumps, fils, dad,
552 & ptrarw, ptraiw,
553 & intarr,dblarr,icntl,keep,keep8,dkeep,nd,frere,lptrar,
554 & nelt, frtptr, frtelt,
555 & istep_to_iniv2, tab_pos_in_pere, .true.
556 & , lrgroups
557 & )
558 IF ( iflag .LT. 0 ) THEN
559 is_error_broadcasted=.true.
560 GOTO 600
561 ENDIF
562 END IF
563 END IF
564 ENDDO
565 ENDIF
566 END DO
567 IF (local_assembly_to_be_done) THEN
569 & slaves_pere(i_posmyidin_pere),
570 &
myid, pdest_master, ison, inode_pere,
571 & nslaves_pere, nass_pere, nfront_pere, nfs4father,
572 & lmap_loc, map, nbrow, perm_loc,
573 & is_oftype5or6, iflag, ierror,
574 & n, slavef, keep, ipool, lpool, step,
575 & procnode_steps, comm_load, istep_to_iniv2, tab_pos_in_pere,
576 & keep8, iw, liw, a, la, lrlu, lrlus, iptrlu, iwposcb,
577 & ptrist, ptlust, ptrast, pamaster, pimaster, nd,
578 & nelt, frtptr, frtelt,
579 & opassw, opeliw,
580 & itloc, rhs_mumps, keep253_loc, nvschur,
581 & fils, dad, lptrar, ptrarw, ptraiw, intarr, dblarr, icntl,
582 & itype_son, lrgroups)
583 local_assembly_to_be_done = .false.
584 IF (iflag < 0) THEN
585 GOTO 600
586 ENDIF
587 ENDIF
588 IF (cb_is_lr) THEN
590 & .false., keep8, keep(34))
591 IF ((keep(486).EQ.3).OR.keep(486).EQ.0) THEN
593 & keep(34))
594 ENDIF
595 ENDIF
596 IF (keep(214) .EQ. 2) THEN
598 & ptrist, ptrast, ptlust, ptrfac, iw, liw, a, la,
599 & lrlu, lrlus, iwpos, iwposcb, posfac,
comp,
600 & iptrlu, opeliw, step, pimaster, pamaster,
601 & iflag, ierror, slavef, procnode_steps, dad,
myid,
602 & comm, keep,keep8, dkeep, itype_son )
603 IF (iflag .LT. 0) THEN
604 is_error_broadcasted = .true.
605 GOTO 600
606 ENDIF
607 ENDIF
609 & a, la, lrlu, lrlus, iwposcb, iptrlu,
610 & step,
myid, keep, keep8, itype_son
611 &)
612 600 CONTINUE
613 DEALLOCATE(perm_loc)
614 670 CONTINUE
615 DEALLOCATE(map)
616 680 CONTINUE
617 DEALLOCATE(nbrow)
618 DEALLOCATE(slaves_pere)
619 700 CONTINUE
620 IF (iflag .LT. 0 .AND. .NOT. is_error_broadcasted) THEN
622 ENDIF
623 RETURN
subroutine, public mumps_fmrd_save_maprow(iwhandler, inode, ison, nslaves_pere, nfront_pere, nass_pere, lmap, nfs4father, slaves_pere, trow, info)
subroutine, public smumps_buf_send_contrib_type2(nbrows_already_sent, desc_in_lu, ipere, nfront_pere, nass_pere, nfs4father, nslaves_pere, ison, nbrow, lmap, maprow, perm, iw_cbson, a_cbson, la_cbson, islave, pdest, pdest_master, comm, ierr, keep, keep8, step, n, slavef, istep_to_iniv2, tab_pos_in_pere, packed_cb, keep253_loc, nvschur, son_niv, myid, npiv_check)
subroutine smumps_get_size_schur_in_front(n, ncb, size_schur, row_indices, perm, nvschur)
subroutine, public smumps_blr_end_front(iwhandler, info1, keep8, k34, lrsolve_act_opt, mtk405)
subroutine, public smumps_blr_free_cb_lrb(iwhandler, free_only_struct, keep8, k34)
subroutine smumps_bdc_error(myid, slavef, comm, keep)
recursive subroutine smumps_treat_descband(inode, comm_load, ass_irecv, bufr, lbufr, lbufr_bytes, procnode_steps, posfac, iwpos, iwposcb, iptrlu, lrlu, lrlus, n, iw, liw, a, la, ptrist, ptlust, ptrfac, ptrast, step, pimaster, pamaster, nstk_s, comp, iflag, ierror, comm, perm, ipool, lpool, leaf, nbfin, myid, slavef root, opassw, opeliw, itloc, rhs_mumps, fils, dad, ptrarw, ptraiw, intarr, dblarr, icntl, keep, keep8, dkeep, nd, frere, lptrar, nelt, frtptr, frtelt istep_to_iniv2, tab_pos_in_pere, stack_right_authorized, lrgroups)
subroutine smumps_local_assembly_type2(i, pdest, myid, pdest_master, ison, ifath, nslaves_pere, nass_pere, nfront_pere, nfs4father, lmap_loc, map, nbrow, perm, is_oftype5or6, iflag, ierror, n, slavef, keep, ipool, lpool, step, procnode_steps, comm_load, istep_to_iniv2, tab_pos_in_pere, keep8, iw, liw, a, la, lrlu, lrlus, iptrlu, iwposcb, ptrist, ptlust, ptrast, pamaster, pimaster, nd, nelt, frtptr, frtelt, opassw, opeliw, itloc, rhs_mumps, keep253_loc, nvschur, fils, dad, lptrar, ptrarw, ptraiw, intarr, dblarr, icntl, son_niv, lrgroups)
recursive subroutine smumps_try_recvtreat(comm_load, ass_irecv, blocking, set_irecv, message_received, msgsou, msgtag, status, bufr, lbufr, lbufr_bytes, procnode_steps, posfac, iwpos, iwposcb, iptrlu, lrlu, lrlus, n, iw, liw, a, la, ptrist, ptlust, ptrfac, ptrast, step, pimaster, pamaster, nstk_s, comp, iflag, ierror, comm, perm, ipool, lpool, leaf, nbfin, myid, slavef root, opassw, opeliw, itloc, rhs_mumps, fils, dad, ptrarw, ptraiw, intarr, dblarr, icntl, keep, keep8, dkeep, nd, frere, lptrar, nelt, frtptr, frtelt istep_to_iniv2, tab_pos_in_pere, stack_right_authorized, lrgroups)