1025
1036 IMPLICIT NONE
1037 TYPE (CMUMPS_ROOT_STRUC) :: root
1038 INTEGER COMM_LOAD, ASS_IRECV
1039 INTEGER N,LIW,NSTEPS, NBFIN
1040 INTEGER KEEP(500), ICNTL(60)
1041 INTEGER(8) KEEP8(150)
1042 REAL DKEEP(230)
1043 INTEGER(8) :: LRLUS, LRLU, IPTRLU, POSFAC, LA
1044 INTEGER, INTENT(INOUT) :: INFO(2)
1045 INTEGER INODE, MAXFRW, LPOOL, LEAF,
1046 & IWPOS, IWPOSCB, COMP, SLAVEF
1047 COMPLEX, TARGET :: A(LA)
1048 INTEGER, intent(in) :: LRGROUPS(N)
1049 DOUBLE PRECISION OPASSW, OPELIW
1050 INTEGER COMM, MYID, LBUFR, LBUFR_BYTES
1051 INTEGER, DIMENSION(0:SLAVEF - 1) :: MEM_DISTRIB
1052 INTEGER IPOOL(LPOOL)
1053 INTEGER(8) :: PTRAST(KEEP(28))
1054 INTEGER(8) :: PTRFAC(KEEP(28))
1055 INTEGER(8) :: PAMASTER(KEEP(28))
1056 INTEGER(8), INTENT(IN) :: PTRARW(N), PTRAIW(N)
1057 INTEGER IW(LIW), ITLOC(N+KEEP(253)),
1058 & ND(KEEP(28)),
1059 & FILS(N), FRERE(KEEP(28)), DAD (KEEP(28)),
1060 & PTRIST(KEEP(28)), PTLUST(KEEP(28)),
1061 & STEP(N),
1062 & PIMASTER(KEEP(28)),
1063 & NSTK_S(KEEP(28)), PERM(N)
1064 COMPLEX :: RHS_MUMPS(KEEP(255))
1065 INTEGER CAND(SLAVEF+1, max(1,KEEP(56)))
1066 INTEGER ISTEP_TO_INIV2(KEEP(71)),
1067 & TAB_POS_IN_PERE(SLAVEF+2,max(1,KEEP(56)))
1068 INTEGER PROCNODE_STEPS(KEEP(28)), BUFR(LBUFR)
1069 INTEGER(8), INTENT(IN) :: LINTARR,LDBLARR
1070 COMPLEX DBLARR(LDBLARR)
1071 INTEGER INTARR(LINTARR)
1072 include 'mpif.h'
1073 INTEGER :: IERR
1074 INTEGER :: STATUS(MPI_STATUS_SIZE)
1075
1076 INTEGER LP, HS, HF, HF_OLD, NCBSON, NSLAVES_OLD
1077 LOGICAL LPOK
1078 INTEGER NCBSON_MAX
1079 INTEGER IN,NUMSTK,NASS,ISON,IFSON,NASS1,IELL
1080 INTEGER :: IBC_SOURCE
1081 COMPLEX, DIMENSION(:), POINTER :: SON_A
1082 INTEGER :: MAXWASTEDPROCS
1083 parameter(maxwastedprocs=1)
1084 INTEGER NFS4FATHER, ESTIM_NFS4FATHER_ATSON
1085 INTEGER IFATH
1086 INTEGER I
1087 INTEGER NFRONT,NFRONT_EFF,ISTCHK,ISTCHK_CB_RIGHT,LSTK,LREQ
1088 INTEGER :: SON_XXS
1089 INTEGER(8) :: LAELL8
1090 INTEGER LREQ_OOC
1091 INTEGER NBPANELS_L, NBPANELS_U
1092 LOGICAL PACKED_CB, IS_CB_LR
1093 INTEGER(8) :: LCB
1094 LOGICAL :: IS_DYNAMIC_CB
1095 INTEGER(8) :: DYN_SIZE
1096 INTEGER NCB
1097 INTEGER MP
1098 INTEGER :: K1, K2, KK, KK1
1099 INTEGER :: J253
1100 INTEGER(8) :: JK8, AINPUT8, J18, J28, J38, J48, JJ8
1101 INTEGER(8) :: LAPOS2, JJ2, JJ3
1102 INTEGER(8) :: ICT13
1103 INTEGER(8) :: IACHK, APOS, APOS2, POSELT, ICT12, POSEL1
1104#if
1105 INTEGER :: TOPDIAG
1106#endif
1107
1108
1109 INTEGER NELIM,NPIVS,NCOLS,NROWS,
1110 & IORG
1111 INTEGER LDAFS, LDA_SON, IJROW, IBROT
1112 INTEGER NBCOL,NUMORG,IOLDPS, NUMORG_SPLIT
1113 INTEGER NSLAVES, NSLSON
1114 INTEGER NBLIG, PTRCOL, PTRROW, PDEST
1115 INTEGER PDEST1(1)
1116 INTEGER :: ISLAVE
1117 INTEGER TYPESPLIT
1118 INTEGER ISON_IN_PLACE
1119 LOGICAL IS_ofType5or6, SPLIT_MAP_RESTART
1120 INTEGER NMB_OF_CAND, NMB_OF_CAND_ORIG
1121 LOGICAL SAME_PROC, NIV1, SON_LEVEL2
1122 LOGICAL BLOCKING, SET_IRECV, MESSAGE_RECEIVED
1123 INTEGER TROW_SIZE, INDX, FIRST_INDEX, SHIFT_INDEX
1124 INTEGER LRSTATUS
1125 LOGICAL COMPRESS_PANEL, LR_ACTIVATED, COMPRESS_CB,
1126 & OOCWRITE_COMPATIBLE_WITH_BLR
1127 INTEGER IZERO
1128 INTEGER IDUMMY(1)
1129 parameter( izero = 0 )
1130 INTEGER MUMPS_PROCNODE, MUMPS_TYPENODE, MUMPS_TYPESPLIT
1132 COMPLEX ZERO
1133 REAL RZERO
1134 parameter( rzero = 0.0e0 )
1135 parameter( zero = (0.0e0,0.0e0) )
1136 INTEGER NELT, LPTRAR
1137 logical :: force_cand
1138 INTEGER ETATASS
1139 include 'mumps_headers.h'
1140 INTEGER(8) :: APOSMAX
1141 REAL MAXARR
1142 INTEGER INIV2, SIZE_TMP_SLAVES_LIST, allocok
1143 INTEGER NCB_SPLIT, SIZE_LIST_SPLIT, NBSPLIT
1144 INTEGER, ALLOCATABLE, DIMENSION(:) :: TMP_SLAVES_LIST, COPY_CAND
1145 INTEGER, ALLOCATABLE, DIMENSION(:) :: SONROWS_PER_ROW
1146 INTEGER, POINTER, DIMENSION(:) :: BEGS_BLR
1147 INTEGER :: NB_BLR, NPARTSCB, NPARTSASS, MAXI_CLUSTER,
1148 & IBCKSZ2, MINSIZE
1149
1150 mp = icntl(2)
1151 lp = icntl(1)
1152 lpok = ((lp.GT.0).AND.(icntl(4).GE.1))
1153 is_oftype5or6 = .false.
1154 packed_cb = .false.
1155 etatass = 0
1156 in = inode
1157 nsteps = nsteps + 1
1158 keep(429) = keep(429)+1
1159 numorg = 0
1160 DO WHILE (in.GT.0)
1161 numorg = numorg + 1
1162 in = fils(in)
1163 ENDDO
1164 numstk = 0
1165 nass = 0
1166 ifson = -in
1167 ison = ifson
1168 ncbson_max = 0
1169 nelt = 1
1170 lptrar = 1
1171 DO WHILE (ison .GT. 0)
1172 numstk = numstk + 1
1173 IF ( keep(48)==5 .AND.
1175 & keep(199)) .EQ. 1) THEN
1176 ncbson_max =
1177 &
max(ncbson_max,iw(pimaster(step(ison))+keep(ixsz)))
1178 ENDIF
1179 nass = nass + iw(pimaster(step(ison)) + 1 + keep(ixsz))
1180 ison = frere(step(ison))
1181 ENDDO
1182 nfront = nd(step(inode)) + nass + keep(253)
1183 nass1 = nass + numorg
1184 ncb = nfront - nass1
1186 & keep(489), keep(490), keep(491), keep(492),
1187 & keep(20), keep(60), dad(step(inode)), keep(38),
1188 & lrstatus, n, lrgroups)
1189 compress_panel = (lrstatus.GE.2)
1190 compress_cb = ((lrstatus.EQ.1).OR.
1191 & (lrstatus.EQ.3))
1192 lr_activated = (lrstatus.GT.0)
1193 IF (compress_cb.AND.(.NOT.compress_panel)) THEN
1194 compress_panel = .true.
1195 lrstatus = 3
1196 ENDIF
1197 oocwrite_compatible_with_blr =
1198 & ( .NOT.lr_activated.OR.(.NOT.compress_panel).OR.
1199 & (keep(486).NE.2)
1200 & )
1201 IF((keep(24).eq.0).or.(keep(24).eq.1)) then
1202 force_cand=.false.
1203 ELSE
1204 force_cand=(mod(keep(24),2).eq.0)
1205 end if
1207 & keep(199))
1208 is_oftype5or6 = (typesplit.EQ.5 .OR. typesplit.EQ.6)
1209 istchk = pimaster(step(ifson))
1210 pdest = istchk + 6 + keep(ixsz)
1211 nslson = iw(istchk + keep(ixsz) + 5)
1212 split_map_restart = .false.
1213 IF (force_cand) THEN
1214 iniv2 = istep_to_iniv2( step( inode ))
1215 nmb_of_cand = cand( slavef+1, iniv2 )
1216 nmb_of_cand_orig = nmb_of_cand
1217 size_tmp_slaves_list = nmb_of_cand
1218 IF (is_oftype5or6) THEN
1219 DO i=nmb_of_cand+1,slavef
1220 IF ( cand( i, iniv2 ).LT.0) EXIT
1221 nmb_of_cand = nmb_of_cand +1
1222 ENDDO
1223 size_tmp_slaves_list = nslson-1
1224 IF (inode.EQ.-999999) THEN
1225 split_map_restart = .true.
1226 ENDIF
1227 ENDIF
1228 IF (is_oftype5or6.AND.split_map_restart) THEN
1229 typesplit = 4
1230 is_oftype5or6 = .false.
1231 size_tmp_slaves_list = nmb_of_cand
1232 cand(slavef+1, iniv2) = size_tmp_slaves_list
1233 ENDIF
1234 ELSE
1235 iniv2 = 1
1236 size_tmp_slaves_list = slavef - 1
1237 nmb_of_cand = slavef - 1
1238 nmb_of_cand_orig = slavef - 1
1239 ENDIF
1240 ALLOCATE(tmp_slaves_list(size_tmp_slaves_list),stat=allocok)
1241 IF (allocok > 0 ) THEN
1242 GOTO 265
1243 ENDIF
1244 IF ( (typesplit.EQ.4)
1245 & .OR.(typesplit.EQ.5).OR.(typesplit.EQ.6)
1246 & ) THEN
1247 IF (typesplit.EQ.4) THEN
1248 ALLOCATE(copy_cand(slavef+1),stat=allocok)
1249 IF (allocok > 0 ) THEN
1250 GOTO 245
1251 ENDIF
1253 & inode, step, n, slavef,
1254 & procnode_steps, keep, dad, fils,
1255 & cand(1,iniv2), icntl, copy_cand,
1256 & nbsplit, numorg_split, tmp_slaves_list(1),
1257 & size_tmp_slaves_list
1258 & )
1259 ncb_split = ncb-numorg_split
1260 size_list_split = size_tmp_slaves_list - nbsplit
1262 & icntl, copy_cand,
1263 & mem_distrib(0), ncb_split, nfront, nslaves,
1264 & tab_pos_in_pere(1,iniv2),
1265 & tmp_slaves_list(nbsplit+1),
1266 & size_list_split,inode
1267 & )
1268 DEALLOCATE (copy_cand)
1270 & inode, step, n, slavef, nbsplit, ncb,
1271 & procnode_steps, keep, dad, fils,
1272 & icntl,
1273 & tab_pos_in_pere(1,iniv2),
1274 & nslaves
1275 & )
1276 IF (split_map_restart) THEN
1277 is_oftype5or6 = .true.
1279 & keep(199))
1280 cand( slavef+1, iniv2 ) = nmb_of_cand_orig
1281 ENDIF
1282 ELSE
1283 istchk = pimaster(step(ifson))
1284 pdest = istchk + 6 + keep(ixsz)
1285 nslson = iw(istchk + keep(ixsz) + 5)
1286 IF (keep(376) .EQ. 1) THEN
1287 nfront = iw( pimaster(step(ifson)) + keep(ixsz))
1288 ENDIF
1290 & inode, typesplit, ifson,
1291 & cand(1,iniv2), nmb_of_cand_orig,
1292 & iw(pdest), nslson,
1293 & step, n, slavef,
1294 & procnode_steps, keep, dad, fils,
1295 & icntl, istep_to_iniv2, iniv2,
1296 & tab_pos_in_pere, nslaves,
1297 & tmp_slaves_list,
1298 & size_tmp_slaves_list
1299 & )
1300 ENDIF
1301 ELSE
1303 & icntl, cand(1,iniv2),
1304 & mem_distrib(0), ncb, nfront, nslaves,
1305 & tab_pos_in_pere(1,iniv2),
1306 & tmp_slaves_list,
1307 & size_tmp_slaves_list,inode
1308 & )
1309 ENDIF
1310 hf = nslaves + 6 + keep(ixsz)
1311 lreq_ooc = 0
1312 IF (keep(201).EQ.1.AND.oocwrite_compatible_with_blr) THEN
1314 & nbpanels_l, nbpanels_u, lreq_ooc)
1315 ENDIF
1316 lreq = hf + 2 * nfront + lreq_ooc
1317 IF ((iwpos + lreq -1) .GT. iwposcb) THEN
1319 & iw, liw, a, la,
1320 & lrlu, iptrlu,
1321 & iwpos, iwposcb, ptrist, ptrast,
1322 & step, pimaster, pamaster,
1323 & lrlus,keep(ixsz),
1325 & procnode_steps, dad)
1326 IF (lrlu .NE. lrlus) THEN
1327 IF (lpok) THEN
1328 WRITE(lp, * ) 'PB compress CMUMPS_FAC_ASM_NIV2 ',
1329 & 'LRLU,LRLUS=',lrlu,lrlus
1330 ENDIF
1331 GOTO 270
1332 ENDIF
1333 IF ((iwpos + lreq -1) .GT. iwposcb) GOTO 270
1334 ENDIF
1335 ioldps = iwpos
1336 iwpos = iwpos + lreq
1337 niv1 = .false.
1338 ALLOCATE(sonrows_per_row(nfront-nass1), stat=allocok)
1339 IF (allocok > 0) THEN
1340 GOTO 275
1341 ENDIF
1342 ison_in_place = -9999
1344 &
myid, inode, n, ioldps, hf, lp, lpok,
1345 & nfront, nfront_eff, perm, dad,
1346 & nass1, nass, numstk, numorg, iwposcb, iwpos,
1347 & ifson, step, pimaster, ptrist, ptraiw, iw, liw,
1348 & intarr, lintarr, itloc, fils, frere,
1349 & son_level2, niv1, keep,keep8, info(1),
1350 & ison_in_place,
1351 & procnode_steps, slavef, sonrows_per_row,
1352 & nfront-nass1)
1353 IF (info(1).LT.0) GOTO 250
1354 IF ( nfront .NE. nfront_eff ) THEN
1355 IF (
1356 & (typesplit.EQ.5) .OR. (typesplit.EQ.6)) THEN
1357 WRITE(*,*) ' Internal error 1 in fac_ass due to splitting ',
1358 & ' INODE, NFRONT, NFRONT_EFF =', inode, nfront, nfront_eff
1359 WRITE(*,*) ' SPLITTING NOT YET READY FOR THAT'
1361 ENDIF
1362 IF (nfront.GT.nfront_eff) THEN
1363 ncb = nfront_eff - nass1
1364 nslaves_old = nslaves
1365 hf_old = hf
1366 IF (typesplit.EQ.4) THEN
1367 ALLOCATE(copy_cand(slavef+1),stat=allocok)
1368 IF (allocok > 0 ) THEN
1369 GOTO 245
1370 ENDIF
1372 & inode, step, n, slavef,
1373 & procnode_steps, keep, dad, fils,
1374 & cand(1,iniv2), icntl, copy_cand,
1375 & nbsplit, numorg_split, tmp_slaves_list(1),
1376 & size_tmp_slaves_list
1377 & )
1378 ncb_split = ncb-numorg_split
1379 size_list_split = size_tmp_slaves_list - nbsplit
1381 & slavef, keep,keep8,
1382 & icntl, copy_cand,
1383 & mem_distrib(0), ncb_split, nfront_eff, nslaves,
1384 & tab_pos_in_pere(1,iniv2),
1385 & tmp_slaves_list(nbsplit+1),
1386 & size_list_split,inode
1387 & )
1388 DEALLOCATE (copy_cand)
1390 & inode, step, n, slavef, nbsplit, ncb,
1391 & procnode_steps, keep, dad, fils,
1392 & icntl,
1393 & tab_pos_in_pere(1,iniv2),
1394 & nslaves
1395 & )
1396 ELSE
1398 & slavef, keep, keep8, icntl,
1399 & cand(1,iniv2),
1400 & mem_distrib(0), ncb, nfront_eff, nslaves,
1401 & tab_pos_in_pere(1,iniv2),
1402 & tmp_slaves_list, size_tmp_slaves_list,inode
1403 & )
1404 ENDIF
1405 hf = nslaves + 6 + keep(ixsz)
1406 iwpos = iwpos - ((2*nfront)-(2*nfront_eff)) -
1407 & (nslaves_old - nslaves)
1408 IF (nslaves_old .NE. nslaves) THEN
1409 IF (nslaves_old > nslaves) THEN
1410 DO kk=0,2*nfront_eff-1
1411 iw(ioldps+hf+kk)=iw(ioldps+hf_old+kk)
1412 ENDDO
1413 ELSE
1414 IF (iwpos - 1 > iwposcb ) GOTO 270
1415 DO kk=2*nfront_eff-1, 0, -1
1416 iw(ioldps+hf+kk) = iw(ioldps+hf_old+kk)
1417 ENDDO
1418 END IF
1419 END IF
1420 nfront = nfront_eff
1421 lreq = hf + 2 * nfront + lreq_ooc
1422 ELSE
1423 IF (lpok) THEN
1424 WRITE(lp,*)
myid,
': INTERNAL ERROR 2 ',
1425 & ' IN CMUMPS_FAC_ASM_NIV2 , INODE=',
1426 & inode, ' NFRONT, NFRONT_EFF=', nfront, nfront_eff
1427 ENDIF
1428 GOTO 270
1429 ENDIF
1430 ENDIF
1431 IF (keep(201).EQ.1.AND.keep(50).NE.1.AND.
1432 & oocwrite_compatible_with_blr) THEN
1434 & nbpanels_l, nbpanels_u, nass1,
1435 & ioldps + hf + 2 * nfront, iw, liw)
1436 ENDIF
1437 maxfrw = max0(maxfrw, nfront)
1438 ptlust(step(inode)) = ioldps
1439 iw(ioldps+keep(ixsz)) = nfront
1440 iw(ioldps + 1+keep(ixsz)) = 0
1441 iw(ioldps + 2+keep(ixsz)) = -nass1
1442 iw(ioldps + 3+keep(ixsz)) = -nass1
1443 iw(ioldps + 4+keep(ixsz)) = step(inode)
1444 iw(ioldps+5+keep(ixsz)) = nslaves
1445 iw(ioldps+6+keep(ixsz):ioldps+5+keep(ixsz)+nslaves)=
1446 & tmp_slaves_list(1:nslaves)
1447 estim_nfs4father_atson = -9999
1448 IF (keep(219).NE.0.AND.keep(50).EQ.2) THEN
1449 ifath = dad( step( inode) )
1450 IF (ifath.NE.0) THEN
1451 IF (compress_cb.AND.
1453 & .EQ. 2 ) THEN
1454 ioldps = ptlust(step(inode))
1456 & n, inode, ifath, fils, perm, keep,
1457 & ioldps, hf, iw, liw, nfront, nass1,
1458 & estim_nfs4father_atson
1459 & )
1460 ENDIF
1461 ENDIF
1462 ENDIF
1464 & tab_pos_in_pere(1,istep_to_iniv2(step(inode))),
1465 & nass1, keep, keep8, iw(ioldps+6+keep(ixsz)), nslaves,inode)
1466 IF(keep(86).EQ.1)THEN
1467 IF(mod(keep(24),2).eq.0)THEN
1469 & cand(slavef+1,iniv2),
1470 & cand(1,iniv2),
1471 & tab_pos_in_pere(1,istep_to_iniv2(step(inode))),
1472 & nass1, keep,keep8, tmp_slaves_list,
1473 & nslaves,inode)
1474 ELSEIF((keep(24).EQ.0).OR.(keep(24).EQ.1))THEN
1476 & slavef-1,
1477 & tmp_slaves_list,
1478 & tab_pos_in_pere(1,istep_to_iniv2(step(inode))),
1479 & nass1, keep,keep8, tmp_slaves_list,
1480 & nslaves,inode)
1481 ENDIF
1482 ENDIF
1483 DEALLOCATE(tmp_slaves_list)
1484 IF (keep(50).EQ.0) THEN
1485 laell8 = int(nass1,8) * int(nfront,8)
1486 ldafs = nfront
1487 ELSE
1488 laell8 = int(nass1,8)*int(nass1,8)
1489 IF(keep(219).NE.0.AND.keep(50) .EQ. 2)
1490 & laell8 = laell8+int(nass1,8)
1491 ldafs = nass1
1492 ENDIF
1494 & (0, laell8, .false.,
1495 & keep(1), keep8(1),
1496 & n,iw,liw,a,la,
1497 & lrlu,iptrlu,iwpos,iwposcb,
1498 & ptrist,ptrast,
1499 & step, pimaster,pamaster,lrlus,
1500 & keep(ixsz),
comp, dkeep(97),
myid,
1501 & slavef, procnode_steps, dad,
1502 & info(1), info(2))
1503 IF (info(1).LT.0) GOTO 490
1504 lrlu = lrlu - laell8
1505 lrlus = lrlus - laell8
1506 keep8(67) =
min(lrlus, keep8(67))
1507 keep8(69) = keep8(69) + laell8
1508 keep8(68) =
max(keep8(69), keep8(68))
1509 poselt = posfac
1510 ptrast(step(inode)) = poselt
1511 ptrfac(step(inode)) = poselt
1512 posfac = posfac + laell8
1513 iw(ioldps+xxi) = lreq
1516 iw(ioldps+xxs) = -9999
1517 iw(ioldps+xxn) = -99999
1518 iw(ioldps+xxp) = -99999
1519 iw(ioldps+xxa) = -99999
1520 iw(ioldps+xxf) = -99999
1521 iw(ioldps+xxlr)= lrstatus
1522 iw(ioldps+xxg) = memnotpinned
1524 & keep,keep8,lrlus)
1525 posel1 = poselt - int(ldafs,8)
1526#if defined(ZERO_TRIANGLE)
1527 lapos2 = poselt + laell8 - 1_8
1528 a(poselt:lapos2) = zero
1529#else
1530 IF ( keep(50) .eq. 0 .OR. ldafs .lt. keep(63) ) THEN
1531 lapos2 = poselt + laell8 - 1_8
1532
1533
1534
1535#if defined(__ve__)
1536
1537#endif
1538 DO jj8 = poselt, lapos2
1539 a(jj8) = zero
1540 ENDDO
1541
1542 ELSE
1543 topdiag =
max(keep(7), keep(8))-1
1544 IF (lr_activated) THEN
1545 NULLIFY(begs_blr)
1546 CALL get_cut(iw(ioldps+hf:ioldps+hf+nfront-1), nass1,
1547 & 0, lrgroups, npartscb,
1548 & npartsass, begs_blr)
1549 nb_blr = npartsass + npartscb
1551 DEALLOCATE(begs_blr)
1553 minsize = int(ibcksz2 / 2)
1554 topdiag =
max(2*minsize + maxi_cluster-1, topdiag)
1555 ENDIF
1556
1557
1558 apos = poselt
1559#if defined(__ve__)
1560
1561#endif
1562
1563
1564 DO jj8 = 0_8, int(ldafs-1,8)
1565 apos = poselt + jj8 * int(ldafs,8)
1566 jj3 =
min( int(ldafs,8) - 1_8, jj8 + topdiag )
1567 a(apos:apos+jj3) = zero
1568 END DO
1569
1570 IF (keep(219).NE.0.AND.keep(50).EQ.2) THEN
1571 aposmax = poselt + int(nass1,8)*int(nass1,8)
1572 a(aposmax:aposmax+int(ldafs-1,8))=zero
1573 ENDIF
1574 END IF
1575#endif
1576 IF ((numstk.NE.0).AND.(nass.NE.0)) THEN
1577 ison = ifson
1578 DO 220 iell = 1, numstk
1579 istchk = pimaster(step(ison))
1580 nelim = iw(istchk + keep(ixsz) + 1)
1581 IF (nelim.EQ.0) GOTO 210
1582 lstk = iw(istchk + keep(ixsz))
1583 npivs = iw(istchk + 3+keep(ixsz))
1584 IF (npivs.LT.0) npivs=0
1585 nslson = iw(istchk + 5+keep(ixsz))
1586 hs = 6 + nslson + keep(ixsz)
1587 ncols = npivs + lstk
1588 same_proc = (istchk.LT.iwpos)
1589 IF ( same_proc ) THEN
1590 istchk_cb_right=ptrist(step(ison))
1591 ELSE
1592 istchk_cb_right=istchk
1593 ENDIF
1594 son_xxs = iw(istchk_cb_right + xxs)
1595 packed_cb = ( son_xxs .EQ. s_cb1comp )
1596 IF (.NOT.same_proc) THEN
1597 nrows = iw(istchk + keep(ixsz) + 2)
1598 ELSE
1599 nrows = ncols
1600 ENDIF
1601 IF (keep(50).EQ.0) THEN
1602 lda_son = lstk
1603 lcb = int(nelim,8)*int(lstk,8)
1604 ELSE
1605 IF (nslson.EQ.0) THEN
1606 IF (same_proc) THEN
1607 is_cb_lr = iw(istchk_cb_right+xxlr).EQ. 1 .OR.
1608 & iw(istchk_cb_right+xxlr).EQ. 3
1609 IF (is_cb_lr) THEN
1610 lda_son = nelim
1611 ELSE
1612 lda_son = lstk
1613 ENDIF
1614 ELSE
1615 lda_son = lstk
1616 ENDIF
1617 ELSE
1618 lda_son = nelim
1619 ENDIF
1620 IF (packed_cb) THEN
1621 lcb = (int(nelim,8)*int(nelim+1,8))/2_8
1622 ELSE
1623 lcb = int(lda_son,8)*int(nelim,8)
1624 ENDIF
1625 ENDIF
1626 IF (keep(50) .EQ. 0) THEN
1627 opassw = opassw + dble(lcb)
1628 ELSE
1629 opassw = opassw + int(nelim,8)*int(nelim+1,8)/2_8
1630 ENDIF
1631 is_dynamic_cb =
1633 & istchk_cb_right+xxd+1))
1634 IF ( is_dynamic_cb ) THEN
1635 CALL mumps_geti8(dyn_size, iw(istchk_cb_right+xxd))
1637 & son_a )
1638 iachk = 1_8
1639 ELSE
1640 iachk = pamaster(step(ison))
1641 son_a=>a
1642 ENDIF
1643 k1 = istchk + hs + nrows + npivs
1644 k2 = k1 + nelim - 1
1645 IF (keep(50).eq.0) THEN
1646 IF (is_oftype5or6) THEN
1647 apos = poselt
1648 DO jj8 = 1_8, int(nelim,8)*int(lstk,8)
1649 a(apos+jj8-1_8) = a(apos+jj8-1_8) + son_a(iachk+jj8-1_8)
1650 ENDDO
1651 ELSE
1652 DO 170 kk = k1, k2
1653 apos = posel1 + int(iw(kk),8) * int(ldafs,8)
1654 DO 160 kk1 = 1, lstk
1655 jj2 = apos + int(iw(k1 + kk1 - 1),8) - 1_8
1656 a(jj2) = a(jj2) + son_a(iachk + int(kk1 - 1,8))
1657 160 CONTINUE
1658 iachk = iachk + int(lstk,8)
1659 170 CONTINUE
1660 ENDIF
1661 ELSE
1662 IF (lcb .GT. 0) THEN
1664 & poselt, ldafs, nass1,
1665 & lda_son, lcb,
1666 & iw( k1 ), nelim, nelim, etatass,
1667 & packed_cb
1668
1669 & )
1670 ENDIF
1671 ENDIF
1672 210 ison = frere(step(ison))
1673 220 CONTINUE
1674 ENDIF
1675 ibrot = inode
1676 aposmax = poselt + int(nass1,8)*int(nass1,8)
1677 DO 260 iorg = 1, numorg
1678 jk8 = ptraiw(ibrot)
1679 ainput8 = ptrarw(ibrot)
1680 jj8 = jk8 + 1_8
1681 j18 = jj8 + 1_8
1682 j28 = j18 + intarr(jk8)
1683 j38 = j28 + 1_8
1684 j48 = j28 - intarr(jj8)
1685 ijrow = intarr(j18)
1686 ict12 = poselt + int(ijrow - 1 - ldafs, 8)
1687 maxarr = rzero
1688 DO jj8 = j18, j28
1689 IF (keep(219).NE.0) THEN
1690 IF (intarr(jj8).LE.nass1) THEN
1691 apos2 = ict12 + int(intarr(jj8),8) * int(ldafs,8)
1692 a(apos2) = a(apos2) + dblarr(ainput8)
1693 ELSEIF (keep(50).EQ.2) THEN
1694 maxarr =
max(maxarr,abs(dblarr(ainput8)))
1695 ENDIF
1696 ELSE
1697 IF (intarr(jj8).LE.nass1) THEN
1698 apos2 = ict12 + int(intarr(jj8),8) * int(ldafs,8)
1699 a(apos2) = a(apos2) + dblarr(ainput8)
1700 ENDIF
1701 ENDIF
1702 ainput8 = ainput8 + 1_8
1703 ENDDO
1704 IF(keep(219).NE.0.AND.keep(50) .EQ. 2) THEN
1705 a(aposmax+int(ijrow-1,8)) =
cmplx(maxarr,kind=kind(a))
1706 ENDIF
1707 IF (j38 .GT. j48) GOTO 255
1708 ict13 = poselt + int(ijrow - 1,8) * int(ldafs,8)
1709 nbcol = int(j48 - j38 + 1_8)
1710 DO jj8 = 1_8, int(nbcol,8)
1711 jj3 = ict13 + int(intarr(j38 + jj8 - 1_8),8) - 1_8
1712 a(jj3) = a(jj3) + dblarr(ainput8 + jj8 - 1_8)
1713 ENDDO
1714 255 CONTINUE
1715 IF (keep(50).EQ.0) THEN
1716 DO j253 = 1, keep(253)
1717 apos = poselt +
1718 & int(ijrow-1,8) * int(ldafs,8) +
1719 & int(ldafs-keep(253)+j253-1,8)
1720 a(apos) = a(apos) + rhs_mumps( (j253-1)*keep(254)+ibrot )
1721 ENDDO
1722 ENDIF
1723 ibrot = fils(ibrot)
1724 260 CONTINUE
1725 ptrcol = ioldps + hf + nfront
1726 ptrrow = ioldps + hf + nass1
1727 pdest = ioldps + 6 + keep(ixsz)
1729 DO islave = 1, nslaves
1731 & keep,keep8, inode, step, n, slavef,
1732 & istep_to_iniv2, tab_pos_in_pere,
1733 & islave, ncb,
1734 & nslaves,
1735 & nblig, first_index )
1736 shift_index = first_index - 1
1737 ierr = -1
1738 DO WHILE (ierr .EQ.-1)
1739 IF ( keep(50) .eq. 0 ) THEN
1740 nbcol = nfront
1742 & sum(sonrows_per_row(first_index:first_index+nblig-1)),
1743 & nblig, iw(ptrrow), nbcol, iw(ptrcol), nass1,
1744 & izero, idummy,
1745 & nslaves,
1746 & estim_nfs4father_atson,
1747 & iw(pdest), ibc_source, nfront, comm, keep, ierr
1748 & , iw(ioldps+xxlr)
1749 & )
1750 ELSE
1751 nbcol = nass1+shift_index+nblig
1753 & sum(sonrows_per_row(first_index:first_index+nblig-1)),
1754 & nblig, iw(ptrrow), nbcol, iw(ptrcol), nass1,
1755 & nslaves-islave,
1756 & iw( ptlust(step(inode))+6+keep(ixsz)+islave),
1757 & nslaves,
1758 & estim_nfs4father_atson,
1759 & iw(pdest), ibc_source, nfront, comm, keep, ierr
1760 & , iw(ioldps+xxlr)
1761 & )
1762 ENDIF
1763 IF (ierr.EQ.-1) THEN
1764 blocking = .false.
1765 set_irecv = .true.
1766 message_received = .false.
1768 & blocking, set_irecv, message_received,
1769 & mpi_any_source, mpi_any_tag,
1770 & status, bufr, lbufr,
1771 & lbufr_bytes,
1772 & procnode_steps, posfac, iwpos, iwposcb, iptrlu,
1773 & lrlu, lrlus, n, iw, liw, a, la, ptrist,
1774 & ptlust, ptrfac,
1775 & ptrast, step, pimaster, pamaster, nstk_s,
comp, info(1),
1776 & info(2), comm,
1777 & perm,
1778 & ipool, lpool, leaf, nbfin,
myid, slavef,
1779 & root, opassw, opeliw, itloc, rhs_mumps,
1780 & fils, dad, ptrarw, ptraiw,
1781 & intarr, dblarr, icntl, keep,keep8,dkeep, nd, frere,
1782 & lptrar, nelt, iw, iw,
1783 & istep_to_iniv2, tab_pos_in_pere, .true.
1784 & , lrgroups
1785 & )
1786 IF ( info(1) .LT. 0 ) GOTO 500
1787 IF (message_received) THEN
1788 ioldps = ptlust(step(inode))
1789 ptrcol = ioldps + hf + nfront
1790 ptrrow = ioldps + hf + nass1 + shift_index
1791 ENDIF
1792 ENDIF
1793 ENDDO
1794 IF (ierr .EQ. -2) GOTO 300
1795 IF (ierr .EQ. -3) GOTO 305
1796 ptrrow = ptrrow + nblig
1797 pdest = pdest + 1
1798 ENDDO
1799 DEALLOCATE(sonrows_per_row)
1800 IF (numstk.EQ.0) GOTO 500
1801 ison = ifson
1802 DO iell = 1, numstk
1803 istchk = pimaster(step(ison))
1804 nelim = iw(istchk + 1 + keep(ixsz))
1805 lstk = iw(istchk + keep(ixsz))
1806 npivs = iw(istchk + 3 + keep(ixsz))
1807 IF ( npivs .LT. 0 ) npivs = 0
1808 nslson = iw(istchk + 5 + keep(ixsz))
1809 hs = 6 + nslson + keep(ixsz)
1810 ncols = npivs + lstk
1811 same_proc = (istchk.LT.iwpos)
1812 IF (.NOT.same_proc) THEN
1813 nrows = iw(istchk + 2 + keep(ixsz) )
1814 ELSE
1815 nrows = ncols
1816 ENDIF
1817 pdest = istchk + 6 + keep(ixsz)
1818 ncbson = lstk - nelim
1819 ptrcol = istchk + hs + nrows + npivs + nelim
1820 IF (keep(219).NE.0.AND.keep(50).EQ.2) THEN
1821 nfs4father = ncbson
1822 DO i=0,ncbson-1
1823 IF(iw(ptrcol+i) .GT. nass1) THEN
1824 nfs4father = i
1825 EXIT
1826 ENDIF
1827 ENDDO
1828 nfs4father = nfs4father + nelim
1829 ELSE
1830 nfs4father = 0
1831 ENDIF
1832 IF (nslson.EQ.0) THEN
1833 nslson = 1
1835 & keep(199))
1836 IF (pdest1(1).EQ.
myid)
THEN
1838 & bufr, lbufr, lbufr_bytes,
1839 & inode, ison, nslaves,
1840 & iw( ptlust(step(inode)) + 6 +keep(ixsz)),
1841 & nfront, nass1, nfs4father, ncbson, iw( ptrcol ),
1842 & procnode_steps,
1843 & slavef, posfac, iwpos, iwposcb, iptrlu, lrlu,
1844 & lrlus, n, iw, liw, a, la,
1845 & ptrist, ptlust, ptrfac, ptrast, step,
1846 & pimaster, pamaster, nstk_s,
comp,
1847 & info(1), info(2),
myid, comm, perm,
1848 & ipool, lpool, leaf,
1849 & nbfin, icntl, keep, keep8, dkeep, root,
1850 & opassw, opeliw,
1851 & itloc, rhs_mumps, fils, dad,
1852 & ptrarw, ptraiw, intarr, dblarr,
1853 & nd, frere, lptrar, nelt, iw, iw,
1854 & istep_to_iniv2, tab_pos_in_pere,
1855 & lrgroups )
1856 IF ( info(1) .LT. 0 ) GOTO 500
1857 ELSE
1858 ierr = -1
1859 DO WHILE (ierr.EQ.-1)
1860 ptrcol = pimaster(step(ison)) + hs + nrows + npivs + nelim
1862 & inode, nfront,nass1,nfs4father,
1864 & nslaves, iw( ptlust(step(inode)) + 6 +keep(ixsz)),
1865 & iw(ptrcol), ncbson,
1866 & comm, ierr, pdest1, nslson, slavef,
1867 & keep,keep8, step, n,
1868 & istep_to_iniv2, tab_pos_in_pere
1869 & )
1870 IF (ierr.EQ.-1) THEN
1871 blocking = .false.
1872 set_irecv = .true.
1873 message_received = .false.
1875 & blocking, set_irecv, message_received,
1876 & mpi_any_source, mpi_any_tag,
1877 & status, bufr, lbufr, lbufr_bytes,
1878 & procnode_steps, posfac, iwpos, iwposcb, iptrlu,
1879 & lrlu, lrlus, n, iw, liw, a, la, ptrist,
1880 & ptlust, ptrfac,
1881 & ptrast, step, pimaster, pamaster, nstk_s,
comp, info(1),
1882 & info(2), comm,
1883 & perm,
1884 & ipool, lpool, leaf, nbfin,
myid, slavef,
1885 & root,opassw, opeliw, itloc, rhs_mumps, fils, dad,
1886 & ptrarw, ptraiw,
1887 & intarr, dblarr, icntl, keep,keep8,dkeep, nd, frere,
1888 & lptrar,
1889 & nelt, iw, iw,
1890 & istep_to_iniv2, tab_pos_in_pere, .true.
1891 & , lrgroups
1892 & )
1893 IF ( info(1) .LT. 0 ) GOTO 500
1894 ENDIF
1895 ENDDO
1896 IF (ierr .EQ. -2) GOTO 290
1897 IF (ierr .EQ. -3) GOTO 295
1898 ENDIF
1899 ELSE
1900 IF (pimaster(step(ison)).GT.0) THEN
1901 ierr = -1
1902 DO WHILE (ierr.EQ.-1)
1903 ptrcol = pimaster(step(ison)) + hs + nrows + npivs + nelim
1904 pdest = pimaster(step(ison)) + 6 + keep(ixsz)
1906 & inode, nfront, nass1, nfs4father,
1908 & nslaves, iw(ptlust(step(inode))+6+keep(ixsz)),
1909 & iw(ptrcol), ncbson,
1910 & comm, ierr, iw(pdest), nslson, slavef,
1911 & keep,keep8, step, n,
1912 & istep_to_iniv2, tab_pos_in_pere
1913 & )
1914 IF (ierr.EQ.-1) THEN
1915 blocking = .false.
1916 set_irecv = .true.
1917 message_received = .false.
1919 & blocking, set_irecv, message_received,
1920 & mpi_any_source, mpi_any_tag,
1921 & status, bufr, lbufr,
1922 & lbufr_bytes,
1923 & procnode_steps, posfac, iwpos, iwposcb, iptrlu,
1924 & lrlu, lrlus, n, iw, liw, a, la, ptrist,
1925 & ptlust, ptrfac,
1926 & ptrast, step, pimaster, pamaster, nstk_s,
comp, info(1),
1927 & info(2), comm,
1928 & perm,
1929 & ipool, lpool, leaf, nbfin,
myid, slavef,
1930 & root,opassw, opeliw, itloc, rhs_mumps,
1931 & fils, dad, ptrarw, ptraiw,
1932 & intarr, dblarr, icntl, keep,keep8,dkeep, nd, frere,
1933 & lptrar, nelt, iw, iw,
1934 & istep_to_iniv2, tab_pos_in_pere, .true.
1935 & , lrgroups
1936 & )
1937 IF ( info(1) .LT. 0 ) GOTO 500
1938 ENDIF
1939 ENDDO
1940 IF (ierr .EQ. -2) GOTO 290
1941 IF (ierr .EQ. -3) GOTO 295
1942 ENDIF
1943 DO islave = 0, nslson-1
1944 IF (iw(pdest+islave).EQ.
myid)
THEN
1946 & keep,keep8, ison, step, n, slavef,
1947 & istep_to_iniv2, tab_pos_in_pere,
1948 & islave+1, ncbson,
1949 & nslson,
1950 & trow_size, first_index )
1951 shift_index = first_index - 1
1952 indx = ptrcol + shift_index
1954 & bufr, lbufr, lbufr_bytes,
1955 & inode, ison, nslaves,
1956 & iw( ptlust(step(inode))+6+keep(ixsz)),
1957 & nfront, nass1,nfs4father,
1958 & trow_size, iw( indx ),
1959 & procnode_steps,
1960 & slavef, posfac, iwpos, iwposcb, iptrlu, lrlu,
1961 & lrlus, n, iw, liw, a, la,
1962 & ptrist, ptlust, ptrfac, ptrast, step,
1963 & pimaster, pamaster, nstk_s,
comp, info(1), info(2),
1964 &
myid, comm, perm, ipool, lpool, leaf,
1965 & nbfin, icntl, keep,keep8,dkeep, root,
1966 & opassw, opeliw, itloc, rhs_mumps, fils, dad,
1967 & ptrarw, ptraiw,
1968 & intarr, dblarr, nd, frere, lptrar, nelt, iw,
1969 & iw,
1970 &
1971 & istep_to_iniv2, tab_pos_in_pere, lrgroups)
1972 IF ( info(1) .LT. 0 ) GOTO 500
1973 EXIT
1974 ENDIF
1975 ENDDO
1976 ENDIF
1977 ison = frere(step(ison))
1978 ENDDO
1979 GOTO 500
1980 250 CONTINUE
1981 IF (info(1).EQ.-13) THEN
1982 IF (lpok) THEN
1983 WRITE( lp, * )
1984 & ' FAILURE IN INTEGER DYNAMIC ALLOCATION DURING
1985 & CMUMPS_FAC_ASM_NIV2'
1986 ENDIF
1987 info(2) = numstk + 1
1988 ENDIF
1989 GOTO 490
1990 245 CONTINUE
1991 IF (lpok) THEN
1992 WRITE( lp, * ) ' FAILURE ALLOCATING COPY_CAND',
1993 & ' DURING CMUMPS_FAC_ASM_NIV2'
1994 ENDIF
1995 info(1) = -13
1996 info(2) = slavef+1
1997 GOTO 490
1998 265 CONTINUE
1999 IF (lpok) THEN
2000 WRITE( lp, * ) ' FAILURE ALLOCATING TMP_SLAVES_LIST',
2001 & ' DURING CMUMPS_FAC_ASM_NIV2'
2002 ENDIF
2003 info(1) = -13
2004 info(2) = size_tmp_slaves_list
2005 GOTO 490
2006 270 CONTINUE
2007 info(1) = -8
2008 info(2) = lreq
2009 IF (lpok) THEN
2010 WRITE( lp, * )
2011 & ' FAILURE IN INTEGER ALLOCATION DURING CMUMPS_FAC_ASM_NIV2'
2012 ENDIF
2013 GOTO 490
2014 275 CONTINUE
2015 IF (lpok) THEN
2016 WRITE( lp, * ) ' FAILURE ALLOCATING SONROWS_PER_ROW',
2017 & ' DURING CMUMPS_FAC_ASM_NIV2'
2018 ENDIF
2019 info(1) = -13
2020 info(2) = nfront-nass1
2021 GOTO 490
2022 290 CONTINUE
2023 IF ((icntl(1) .GT. 0) .AND. (icntl(4) .GE. 1)) THEN
2024 lp = icntl(1)
2025 WRITE( lp, * )
2026 &' FAILURE, SEND BUFFER TOO SMALL (1) DURING CMUMPS_FAC_ASM_NIV2'
2027 ENDIF
2028 info(1) = -17
2029 lreq = ncbson + 6 + nslson+keep(ixsz)
2030 info(2) = lreq * keep( 34 )
2031 GOTO 490
2032 295 CONTINUE
2033 IF ((icntl(1) .GT. 0) .AND. (icntl(4) .GE. 1)) THEN
2034 lp = icntl(1)
2035 WRITE( lp, * )
2036 &' FAILURE, RECV BUFFER TOO SMALL (1) DURING CMUMPS_FAC_ASM_NIV2'
2037 ENDIF
2038 info(1) = -20
2039 lreq = ncbson + 6 + nslson+keep(ixsz)
2040 info(2) = lreq * keep( 34 )
2041 GOTO 490
2042 300 CONTINUE
2043 IF ((icntl(1) .GT. 0) .AND. (icntl(4) .GE. 1)) THEN
2044 lp = icntl(1)
2045 WRITE( lp, * )
2046 &' FAILURE, SEND BUFFER TOO SMALL (2)',
2047 &' DURING CMUMPS_FAC_ASM_NIV2'
2048 ENDIF
2049 info(1) = -17
2050 lreq = nblig + nbcol + 4 + keep(ixsz)
2051 info(2) = lreq * keep( 34 )
2052 GOTO 490
2053 305 CONTINUE
2054 IF ((icntl(1) .GT. 0) .AND. (icntl(4) .GE. 1)) THEN
2055 lp = icntl(1)
2056 WRITE( lp, * )
2057 &' FAILURE, RECV BUFFER TOO SMALL (2)',
2058 &' DURING CMUMPS_FAC_ASM_NIV2'
2059 ENDIF
2060 info(1) = -20
2061 lreq = nblig + nbcol + 4 + keep(ixsz)
2062 info(2) = lreq * keep( 34 )
2063 GOTO 490
2065 500 CONTINUE
2066 RETURN
subroutine cmumps_maplig_fils_niv1(comm_load, ass_irecv, bufr, lbufr, lbufr_bytes inode_pere, ison, nslaves_pere, list_slaves_pere, nfront_pere, nass_pere, nfs4father, lmap, trow, procnode_steps, slavef, posfac, iwpos, iwposcb, iptrlu, lrlu, lrlus, n, iw, liw, a, la, ptrist, ptlust, ptrfac, ptrast, step, pimaster, pamaster, nstk, comp, iflag, ierror, myid, comm, perm, ipool, lpool, leaf, nbfin, icntl, keep, keep8, dkeep, root, opassw, opeliw, itloc, rhs_mumps, fils, dad, ptrarw, ptraiw, intarr, dblarr, nd, frere, lptrar, nelt, frtptr, frtelt, istep_to_iniv2, tab_pos_in_pere, lrgroups)
subroutine, public cmumps_buf_send_desc_bande(inode, nbprocfils, nlig, ilig, ncol, icol, nass, nslaves_hdr, list_slaves, nslaves, estim_nfs4father_atson, dest, ibc_source, nfront, comm, keep, ierr, lrstatus)
logical function cmumps_dm_is_dynamic(ixxd)
subroutine, public cmumps_load_set_partition(ncbson_max, slavef, keep, keep8, icntl, cand_of_node, mem_distrib, ncb, nfront, nslaves_node, tab_pos, slaves_list, size_slaves_list, inode)
subroutine, public cmumps_split_prep_partition(inode, step, n, slavef, procnode_steps, keep, dad, fils, cand, icntl, copy_cand, nbsplit, numorg_split, slaves_list, size_slaves_list)
subroutine, public cmumps_split_propagate_parti(inode, typesplit, ifson, cand, size_cand, son_slave_list, nslson, step, n, slavef, procnode_steps, keep, dad, fils, icntl, istep_to_iniv2, iniv2, tab_pos_in_pere, nslaves_node, slaves_list, size_slaves_list)
subroutine, public cmumps_load_send_md_info(slavef, nmb_of_cand, list_of_cand, tab_pos, nass, keep, keep8, list_slaves, nslaves, inode)
subroutine, public cmumps_split_post_partition(inode, step, n, slavef, nbsplit, ncb, procnode_steps, keep, dad, fils, icntl, tab_pos, nslaves_node)
subroutine, public cmumps_load_master_2_all(myid, slavef, comm, tab_pos, nass, keep, keep8, list_slaves, nslaves, inode)