23 & IKEEP1, IKEEP2, IKEEP3,
24 & IORD, NFSIZ, FILS, FRERE, LISTVAR_SCHUR, SIZE_SCHUR,
25 & ICNTL, INFO, KEEP,KEEP8, NSLAVES, PIV,
26 & CNTL4, COLSCA, ROWSCA
27#if defined(metis) || defined(parmetis) || defined(metis4) || defined(parmetis3)
30 & , norig_arg, sizeofblocks, gcomp_provided_in, gcomp
35 INTEGER,
INTENT(IN) :: N, SIZE_SCHUR, NSLAVES
36 INTEGER(8),
INTENT(IN) :: NZ8
37 INTEGER(8),
INTENT(IN) :: LIWALLOC
38 INTEGER,
INTENT(in) :: LISTVAR_SCHUR(:)
39 INTEGER,
POINTER :: IRN(:), ICN(:)
40 INTEGER,
INTENT(IN) :: ICNTL(60)
41 INTEGER,
INTENT(INOUT) :: IORD
42 INTEGER,
INTENT(INOUT) :: INFO(80), KEEP(500)
43 INTEGER(8),
INTENT(INOUT) :: KEEP8(150)
44 INTEGER,
INTENT(OUT) :: NFSIZ(:), FILS(:), FRERE(:)
45 INTEGER,
INTENT(INOUT) :: PIV(:)
46 INTEGER,
INTENT(INOUT) :: IKEEP1(:), IKEEP2(:), IKEEP3(:)
47 DOUBLE PRECISION :: CNTL4
48 DOUBLE PRECISION,
POINTER :: COLSCA(:), ROWSCA(:)
49#if defined(metis) || defined(parmetis) || defined(metis4) || defined(parmetis3)
50 INTEGER,
INTENT(IN) :: METIS_OPTIONS(40)
52 INTEGER,
INTENT(IN),
OPTIONAL :: NORIG_ARG
53 INTEGER,
INTENT(IN),
OPTIONAL :: SIZEOFBLOCKS(N)
54 LOGICAL,
INTENT(IN),
OPTIONAL :: GCOMP_PROVIDED_IN
56 INTEGER,
DIMENSION(:),
ALLOCATABLE,
TARGET :: IWALLOC
57 INTEGER,
DIMENSION(:),
POINTER :: IW
58 INTEGER(8),
DIMENSION(:),
ALLOCATABLE,
TARGET :: IPEALLOC
59 INTEGER(8),
DIMENSION(:),
POINTER :: IPE
60 INTEGER(8),
DIMENSION(:),
ALLOCATABLE :: IPQ8
61 INTEGER,
DIMENSION(:,:),
ALLOCATABLE :: PTRAR
62 INTEGER,
DIMENSION(:),
ALLOCATABLE :: PARENT
63 INTEGER,
DIMENSION(:),
ALLOCATABLE :: IWL1
65 INTEGER,
DIMENSION(:),
ALLOCATABLE :: WTEMP
67 INTEGER I, K, NCMPA, IN, IFSON
70 INTEGER(8) :: IFIRST, ILAST
72 INTEGER NEMIN, LP, MP, LDIAG, ITEMP, symmetry
74 LOGICAL PROK, COMPRESS_SCHUR, LPOK,
75#if defined(metis) || defined(parmetis) || defined(metis4) || defined(parmetis3)
76#if defined(metis4) || defined(parmetis3)
79 INTEGER METIS_IDX_SIZE
80 INTEGER OPT_METIS_SIZE
82#if defined(scotch) || defined(ptscotch)
83 INTEGER :: SCOTCH_INT_SIZE
86 INTEGER :: PORD_INT_SIZE
88 DOUBLE PRECISION,
DIMENSION(:),
ALLOCATABLE :: COLSCA_TEMP
89 INTEGER THRESH, IVersion
94 parameter(k79ref=12000000_8)
95 INTEGER,
PARAMETER :: LIDUMMY = 1
97 INTEGER MTRANS, COMPRESS,NCMP,IERROR,J,JPERM,NCST
103#if defined(scotch) || defined(ptscotch)
104 INTEGER WEIGHTREQUESTED
106 LOGICAL SCOTCH_SYMBOLIC
107 LOGICAL IDENT,SPLITROOT
108 LOGICAL FREE_CENTRALIZED_MATRIX
109 LOGICAL GCOMP_PROVIDED
110 LOGICAL INPLACE64_GRAPH_COPY, INPLACE64_RESTORE_GRAPH
111 INTEGER(8) :: LIW8, NZG8
112 DOUBLE PRECISION TIMEB
117 EXTERNAL zmumps_ana_l
122 IF (liwalloc.GT.0_8)
THEN
123 ALLOCATE( iwalloc(liwalloc), stat = ierr )
124 IF ( ierr .GT. 0 )
THEN
130 ALLOCATE( iwl1(n), stat = ierr )
131 IF ( ierr .GT. 0 )
THEN
136 ALLOCATE( ipealloc(n+1), stat = ierr )
137 IF ( ierr .GT. 0 )
THEN
139 info( 2 ) = (n+1)*keep(10)
142 ALLOCATE( ptrar(n,3), stat = ierr )
143 IF ( ierr .GT. 0 )
THEN
148 scotch_symbolic=(keep(270).EQ.0)
151 gcomp_provided=.false.
154 IF (
present(norig_arg))
THEN
157 IF (
present(gcomp_provided_in))
158 & gcomp_provided = gcomp_provided_in
159 IF (gcomp_provided.AND.(.NOT.
present(gcomp)))
THEN
161 WRITE(6,*)
" INTERNAL ERROR in MUMPS(ANA_F) ",
162 & gcomp_provided_in,
present(gcomp)
166 IF ( (liwalloc.EQ.0_8).AND.(.not.gcomp_provided))
THEN
168 WRITE(6,*)
" INTERNAL ERROR in MUMPS(ANA_F) ",
169 &
"LIWALLOC, GCOMP_PROVIDED=", liwalloc, gcomp_provided
173 IF (gcomp_provided)
THEN
175 liw8 = nzg8 + int(gcomp%NG,8)+1_8
176 iw => gcomp%ADJ(1:liw8)
177 ipe => gcomp%IPE(1:gcomp%NG+1)
179 ptrar(i,2) = int(ipe(i+1)-ipe(i))
184 iw => iwalloc(1:liw8)
185 ipe => ipealloc(1:n+1)
189 lpok = ((lp.GT.0).AND.(icntl(4).GE.1))
190 prok = ((mp.GT.0).AND.(icntl(4).GE.2))
192 compress_schur = .false.
194 IF (
present(gcomp))
THEN
195 WRITE(mp,
'(A,I10,A,I13,A)')
" Processing a graph of size:", n
196 & ,
" with ", gcomp%NZG,
" edges"
198 WRITE(mp,
'(A,I10)')
" Processing a graph of size:", n
201 IF (gcomp_provided)
THEN
202 free_centralized_matrix = .false.
204 free_centralized_matrix = (
205 & (keep(54).EQ.3).AND.
206 & (keep(494).EQ.0).AND.
210 inplace64_graph_copy = .false.
211 inplace64_restore_graph = .true.
212 IF (keep(1).LT.0) keep(1) = 0
214 IF (ldiag.GT.2 .AND. mp.GT.0)
THEN
215 IF (
present(sizeofblocks))
THEN
217 IF (ldiag.EQ.4) k = gcomp%NG
218 WRITE (mp,99909) n, nzg8, info(1)
220 WRITE(mp,
'(A)')
" Graph adjacency "
222 ifirst = gcomp%IPE(j)
223 ilast=
min(gcomp%IPE(j+1)-1,gcomp%IPE(j)+k-1)
224 write(mp,
'(A,I10)')
" .... node/column:", j
225 write(mp,
'(8X,10I9)')
226 & (gcomp%ADJ(i8),i8=ifirst,ilast)
230 IF (ldiag .EQ.4) j8 = nzg8
231 WRITE (mp,99999) n, nzg8, liw8, info(1)
235 IF (ldiag.EQ.4) k = n
236 IF (iord.EQ.1 .AND. k.GT.0)
THEN
237 WRITE (mp,99997) (ikeep1(i),i=1,k)
241 IF (keep(60).NE.0)
THEN
242 IF ((size_schur.LE.0 ).OR.
243 & (size_schur.GE.n) )
GOTO 90
245#if defined(metis) || defined(parmetis) || defined(metis4) || defined(parmetis3)
246 IF ( ( keep(60).NE.0).AND.(size_schur.GT.0)
248 & ((iord.EQ.7).OR.(iord.EQ.5))
250 compress_schur=.true.
252 ALLOCATE(ipq8(n),stat=ierr)
253 IF ( ierr .GT. 0 )
THEN
255 info( 2 ) = n*keep(10)
258 & ipe(1), ptrar(1,2),
259 & ipq8, iwl1, iwfr8, keep8(126), keep8(127),
260 & info(1), info(2), icntl, symmetry,
261 & keep(50), nbqd, avgdens,
262 & keep(264), keep(265),
263 & listvar_schur(1), size_schur, frere(1), fils(1),
264 & inplace64_graph_copy)
266 inplace64_graph_copy = inplace64_graph_copy.AND.
267 & (.NOT.free_centralized_matrix)
274 IF (gcomp_provided)
THEN
275 iwfr8 = gcomp%NZG+1_8
277 ALLOCATE(ipq8(n),stat=ierr)
278 IF ( ierr .GT. 0 )
THEN
280 info( 2 ) = n*keep(10)
286 & ipe(1), ptrar(1,2),
287 & ipq8, iwl1, iwfr8, keep8(126), keep8(127),
288 & info(1), info(2), icntl, symmetry,
289 & keep(50), nbqd, avgdens, keep(264), keep(265),
290 & .true., inplace64_graph_copy)
292 inplace64_graph_copy = inplace64_graph_copy.AND.
293 & (.NOT.free_centralized_matrix)
296#if defined(metis) || defined(parmetis) || defined(metis4) || defined(parmetis3)
300 IF( keep(50) .EQ. 2 .AND. icntl(12) .EQ. 0 )
THEN
301 IF(keep(95) .NE. 1)
THEN
304 &
'Compressed/constrained ordering set OFF'
309 IF ( (keep(60).NE.0) .AND. (iord.GT.1) .AND.
310 & .NOT. compress_schur )
THEN
314 & .AND. (keep(95) .EQ. 3)
315 & .AND. (iord .EQ. 7) )
THEN
319 & keep(50), nslaves, iord,
322 IF(keep(50) .EQ. 2)
THEN
323 IF(keep(95) .EQ. 3 .AND. iord .NE. 2)
THEN
324 IF (prok)
WRITE(mp,*)
325 &
'WARNING: ZMUMPS_ANA_F constrained ordering not '//
326 &
' available with selected ordering. Move to' //
327 &
' compressed ordering.'
334 compress = keep(95) - 1
335 IF(compress .GT. 0 .AND. keep(52) .EQ. -2)
THEN
336 IF(cntl4 .GE. 0.0d0)
THEN
337 IF (keep(1).LE.8)
THEN
344 IF(mtrans .GT. 0 .AND. keep(50) .EQ. 2)
THEN
347 IF (compress .EQ. 2)
THEN
349 WRITE(*,*)
"IORD not compatible with COMPRESS:",
354 & n,piv(1),frere(1),fils(1),nfsiz(1),ikeep1(1),
355 & ncst,keep,keep8, rowsca(1)
358 IF ( iord .NE. 1 )
THEN
359 IF (compress .GE. 1)
THEN
360 ALLOCATE(ipq8(n),stat=ierr)
361 IF ( ierr .GT. 0 )
THEN
363 info( 2 ) = n*keep(10)
366 & n, nz8, irn(1), icn(1), piv(1),
367 & ncmp, iw(1), liw8, ipe(1), ptrar(1,2), ipq8,
368 & iwl1, fils(1), iwfr8,
369 & ierror, keep, keep8, icntl, inplace64_graph_copy)
373 IF ( (symmetry.LT.minsym).AND.(keep(50).EQ.0) )
THEN
374 IF(keep(23) .EQ. 7 )
THEN
377 ELSE IF(keep(23) .EQ. -9876543)
THEN
380 IF (prok)
WRITE(mp,
'(A)')
381 &
' ... Apply column permutation (already computed)'
385 IF (jperm.NE.j) ident = .false.
390 IF ((j.LE.0).OR.(j.GT.n)) cycle
393 ALLOCATE(colsca_temp(n), stat=ierr)
400 colsca_temp(j)=colsca(j)
403 colsca(fils(j))=colsca_temp(j)
405 DEALLOCATE(colsca_temp)
408 &
' WARNING input matrix data modified'
409 ALLOCATE(ipq8(n),stat=ierr)
410 IF ( ierr .GT. 0 )
THEN
412 info( 2 ) = n*keep(10)
415 & (n,nz8,irn(1), icn(1), iw(1), liw8,
416 & ipe(1), ptrar(1,2),
417 & ipq8, iwl1, iwfr8, keep8(126), keep8(127),
418 & info(1), info(2), icntl, symmetry, keep(50),
419 & nbqd, avgdens, keep(264), keep(265),
420 & .true.,inplace64_graph_copy)
428 ELSE IF (keep(23) .EQ. 7 .OR. keep(23) .EQ. -9876543 )
THEN
429 IF (prok)
WRITE(mp,
'(A)')
430 &
' ... No column permutation'
434 IF (free_centralized_matrix
435 & .AND.compress.EQ.0.AND.(.NOT.compress_schur))
THEN
441 inplace64_restore_graph =
442 & inplace64_restore_graph.AND.(compress.NE.1)
443 ALLOCATE( parent( n ), stat = ierr )
444 IF ( ierr .GT. 0 )
THEN
449 IF (iord.NE.1 .AND. iord.NE.5)
THEN
450 IF ( keep(60) .NE. 0 )
THEN
455 WRITE(mp,
'(A)')
' Ordering based on AMF '
456#if defined(scotch) || defined(ptscotch)
457 ELSE IF (iord.EQ.3)
THEN
458 WRITE(mp,
'(A)')
' Ordering based on SCOTCH '
461 ELSE IF (iord.EQ.4)
THEN
462 WRITE(mp,
'(A)')
' Ordering based on PORD '
464 ELSE IF (iord.EQ.6)
THEN
465 WRITE(mp,
'(A)')
' Ordering based on QAMD '
467 WRITE(mp,
'(A)')
' Ordering based on AMD '
473 IF ( keep(60) .NE. 0 )
THEN
474 CALL mumps_hamd(n, liw8, ipe(1), iwfr8, ptrar(1,2), iw(1),
476 & ikeep2(1), ncmpa, fils(1), ikeep3(1),
479 & listvar_schur(1), size_schur)
480 IF (keep(60)==1)
THEN
481 keep(20) = listvar_schur(1)
483 keep(38) = listvar_schur(1)
488 ELSEIF (iord .EQ. 4)
THEN
489 CALL mumps_pord_intsize(pord_int_size)
491 IF ( (compress .EQ. 1)
493 & ( (norig.NE.n).AND.
present(sizeofblocks) )
495 IF (compress .EQ. 1)
THEN
499 DO i=1+keep(93)/2,ncmp
503 & ( (norig.NE.n).AND.
present(sizeofblocks) )
THEN
506 iwl1(i) = sizeofblocks(i)
509 IF (pord_int_size .EQ. 64)
THEN
510 CALL mumps_pordf_wnd_mixedto64
512 & iwl1, ncmpa, totw, parent,
513 & info(1), lp, lpok, keep(10),
514 & inplace64_graph_copy
516 ELSE IF (pord_int_size .EQ. 32)
THEN
517 CALL mumps_pordf_wnd_mixedto32(ncmp, iwfr8-1_8,
519 & iwl1, ncmpa, totw, parent,
520 & info(1), lp, lpok, keep(10))
523 &
"Internal error in PORD wrappers, PORD_INT_SIZE=",
527 IF ( ncmpa .NE. 0 )
THEN
528 write(6,*)
' Out PORD, NCMPA=', ncmpa
533 IF (info(1) .LT.0)
GOTO 90
534 IF (compress.EQ.1)
THEN
537 & frere(1),ptrar(1,1))
543 IF (pord_int_size.EQ.64)
THEN
544 CALL mumps_pordf_mixedto64(ncmp, iwfr8-1_8, ipe,
546 & iwl1, ncmpa, parent,
547 & info(1), lp, lpok, keep(10),
548 & inplace64_graph_copy
550 ELSE IF (pord_int_size.EQ.32)
THEN
551 CALL mumps_pordf_mixedto32(ncmp, iwfr8-1_8, ipe,
553 & iwl1, ncmpa, parent,
554 & info(1), lp, lpok, keep(10))
557 &
"Internal error in PORD wrappers, PORD_INT_SIZE=",
562 IF ( ncmpa .NE. 0 )
THEN
563 write(6,*)
' Out PORD, NCMPA=', ncmpa
568 IF (info(1) .LT. 0)
GOTO 90
570#if defined(scotch) || defined(ptscotch)
571 ELSEIF (iord .EQ. 3)
THEN
572 CALL mumps_scotch_intsize(scotch_int_size)
573 IF ( (compress .EQ. 1)
575 & ( (norig.NE.n).AND.
present(sizeofblocks) )
578 IF (compress .EQ. 1)
THEN
582 DO i=1+keep(93)/2,ncmp
586 & ( (norig.NE.n).AND.
present(sizeofblocks) )
THEN
588 iwl1(i) = sizeofblocks(i)
597 IF (scotch_int_size.EQ.32)
THEN
598 IF (keep(10).EQ.1)
THEN
602 CALL mumps_scotch_mixedto32(ncmp,
605 & ptrar(1,2), iw, iwl1, ikeep1,
606 & ikeep2, ncmpa, info, lp, lpok,
607 & weightused, weightrequested, scotch_symbolic)
609 ELSE IF (scotch_int_size.EQ.64)
THEN
610 CALL mumps_scotch_mixedto64(ncmp,
613 & ptrar(1,2), iw, iwl1, ikeep1,
614 & ikeep2, ncmpa, info, lp, lpok, keep(10),
615 & inplace64_graph_copy,
616 & weightused, weightrequested, scotch_symbolic)
619 &
"Internal error in SCOTCH wrappers, SCOTCH_INT_SIZE=",
623 IF (info(1) .LT. 0)
GOTO 90
624 IF (.NOT. scotch_symbolic)
THEN
625 IF ( compress .EQ. 1 )
THEN
627 & keep(93),piv(1),ikeep1(1),ikeep2(1))
630 ELSE IF ( (compress .EQ. 1)
632 & ( (norig.NE.n).AND.
present(sizeofblocks).AND.
633 & (weightused.EQ.0) )
637 & frere(1),ptrar(1,1))
643 ELSEIF (iord .EQ. 2)
THEN
646 IF(compress .GE. 1)
THEN
651 DO i=1+keep(93)/2,ncmp
654 totel = keep(93)+keep(94)
659 IF (
present(sizeofblocks))
THEN
660 IF (compress.GE.1)
THEN
663 nbbuck =
max(nbbuck, norig-n)
664 nbbuck =
max(nbbuck, 2*norig)
668 iwl1(i) = sizeofblocks(i)
671 ALLOCATE( wtemp( 0: nbbuck + 1), stat = ierr )
672 IF ( ierr .GT. 0 )
THEN
677 IF(compress .LE. 1)
THEN
679 & (totel, ncmp, compute_perm, nbbuck, liw8, ipe(1),
681 & iw(1), iwl1, ikeep1(1), ikeep2(1), ncmpa, fils(1),
682 & ikeep3(1), ptrar, ptrar(1,3), wtemp, parent(1))
684 IF(prok)
WRITE(mp,
'(A)')
685 &
' Constrained Ordering based on AMF'
688 & iw(1), iwl1, ikeep1(1), ikeep2(1), ncmpa, fils(1),
689 & ikeep3(1), ptrar, ptrar(1,3), wtemp,
690 & nfsiz(1), frere(1), parent(1))
693 ELSEIF (iord .EQ. 6)
THEN
694 ALLOCATE( wtemp( n ), stat = ierr )
695 IF ( ierr .GT. 0 )
THEN
703 IF(compress .EQ. 1)
THEN
708 DO i=1+keep(93)/2,ncmp
711 totel = keep(93)+keep(94)
716 IF (
present(sizeofblocks))
THEN
717 IF (compress.EQ.1)
THEN
723 iwl1(i) = sizeofblocks(i)
727 & (totel,compute_perm,iversion, thresh, wtemp,
728 & ncmp, liw8, ipe(1), iwfr8, ptrar(1,2), iw(1),
729 & iwl1, ikeep1(1), ikeep2(1), ncmpa, fils(1),
730 & ikeep3(1), ptrar, ptrar(1,3), parent(1))
734 IF(compress .EQ. 1)
THEN
739 DO i=1+keep(93)/2,ncmp
742 totel = keep(93)+keep(94)
747 IF (
present(sizeofblocks))
THEN
748 IF (compress.EQ.1)
THEN
754 iwl1(i) = sizeofblocks(i)
758 & ncmp, liw8, ipe(1), iwfr8, ptrar(1,2),
759 & iw(1), iwl1, ikeep1(1), ikeep2(1), ncmpa, fils(1),
760 & ikeep3(1), ptrar, ptrar(1,3), parent(1))
763 IF(compress .GE. 1)
THEN
765 & piv(1),ikeep1(1),ikeep2(1))
770#if defined(scotch) || defined(ptscotch)
772 WRITE( mp,
'(A,F12.4)' )
773 &
' ELAPSED TIME SPENT IN SCOTCH reordering =', timeb
778#if defined(metis) || defined(parmetis) || defined(metis4) || defined(parmetis3)
781 WRITE(mp,
'(A)')
' Ordering based on METIS'
786 CALL mumps_metis_idxsize(metis_idx_size)
787 IF (keep(10).EQ.1.AND.metis_idx_size.NE.64)
THEN
792#if defined(metis4) || defined(parmetis3)
798 IF (compress .EQ. 1)
THEN
802 DO i=keep(93)/2+1,ncmp
805#if defined(metis4) || defined(parmetis3)
806 IF (metis_idx_size .EQ.32)
THEN
807 CALL mumps_metis_nodewnd_mixedto32(
808 & ncmp, ipe, iw, frere,
809 & numflag, metis_options(1), opt_metis_size,
810 & ikeep2, ikeep1, info(1), lp, lpok )
811 ELSE IF (metis_idx_size .EQ.64)
THEN
812 CALL mumps_metis_nodewnd_mixedto64(
813 & ncmp, ipe, iw, frere,
814 & numflag, metis_options(1), opt_metis_size,
815 & ikeep2, ikeep1, info(1), lp, lpok, keep(10),
816 & inplace64_graph_copy )
819 &
"Internal error in METIS wrappers, METIS_IDX_SIZE=",
824 IF ((norig.NE.n).AND.
present(sizeofblocks))
THEN
826 frere(i) = sizeofblocks(i)
828 IF (metis_idx_size .EQ.32)
THEN
829 CALL mumps_metis_nodewnd_mixedto32(
830 & ncmp, ipe, iw, frere,
831 & numflag, metis_options(1), opt_metis_size,
832 & ikeep2, ikeep1, info(1), lp, lpok )
833 ELSE IF (metis_idx_size .EQ.64)
THEN
834 CALL mumps_metis_nodewnd_mixedto64(
835 & ncmp, ipe, iw, frere,
836 & numflag, metis_options(1), opt_metis_size,
837 & ikeep2, ikeep1, info(1), lp, lpok, keep(10),
838 & inplace64_graph_copy )
841 &
"Internal error in METIS wrappers, METIS_IDX_SIZE=",
846 IF (metis_idx_size .EQ.32)
THEN
847 CALL mumps_metis_nodend_mixedto32(
848 & ncmp, ipe, iw, numflag,
849 & metis_options(1), opt_metis_size,
850 & ikeep2, ikeep1, info(1), lp, lpok )
851 ELSE IF (metis_idx_size .EQ.64)
THEN
852 CALL mumps_metis_nodend_mixedto64(
853 & ncmp, ipe, iw, numflag,
854 & metis_options(1), opt_metis_size,
855 & ikeep2, ikeep1, info(1), lp,lpok,keep(10),
856 & liw8, inplace64_graph_copy,
857 & inplace64_restore_graph)
860 &
"Internal error in METIS wrappers, METIS_IDX_SIZE=",
868 IF (
present(sizeofblocks))
THEN
870 frere(i) = sizeofblocks(i)
878 IF (metis_idx_size .EQ. 32)
THEN
879 CALL mumps_metis_nodend_mixedto32(
880 & ncmp, ipe, iw, frere,
881 & metis_options(1), opt_metis_size,
882 & ikeep2, ikeep1, info(1), lp, lpok )
883 ELSE IF (metis_idx_size .EQ. 64)
THEN
884 CALL mumps_metis_nodend_mixedto64(
885 & ncmp, ipe, iw, frere,
886 & metis_options(1), opt_metis_size,
887 & ikeep2, ikeep1, info(1), lp,lpok,keep(10),
888 & liw8, inplace64_graph_copy,
889 & inplace64_restore_graph)
891 IF (lpok)
WRITE(lp,*)
892 &
"Internal error in METIS wrappers, METIS_IDX_SIZE=",
897 IF (info(1) .LT.0)
GOTO 90
900 WRITE( mp, '(a,f12.4)
' )
901 & ' elapsed time spent in metis reordering =
', TIMEB
903 IF ( COMPRESS_SCHUR ) THEN
904 CALL ZMUMPS_EXPAND_PERM_SCHUR(
905 & N, NCMP, IKEEP1(1),IKEEP2(1),
906 & LISTVAR_SCHUR(1), SIZE_SCHUR, FILS(1))
909.EQ.
IF (COMPRESS 1) THEN
910 CALL ZMUMPS_EXPAND_PERMUTATION(N,NCMP,KEEP(94),
911 & KEEP(93),PIV(1),IKEEP1(1),IKEEP2(1))
918 WRITE(MP,'(a)
') ' ordering given is used
'
921.EQ..OR..EQ..OR..EQ.
IF (IORD1 IORD5 COMPRESS-1
922.OR..EQ..AND..NOT.
& ( (IORD3)(SCOTCH_SYMBOLIC) )
924.NE..AND..AND..EQ.
& ( (NORIGN)present(SIZEOFBLOCKS) (IORD3)
925.AND..EQ.
& (WEIGHTUSED0)
928.EQ..OR..EQ..OR..EQ.
IF ((KEEP(106)1)(KEEP(106)2)(KEEP(106)4)
929.OR..NE.
& (KEEP(60)0)) THEN
930.EQ.
IF ( COMPRESS -1 ) THEN
931 ALLOCATE(IPQ8(N),stat=IERR)
932.GT.
IF ( IERR 0 ) THEN
934 INFO( 2 ) = N*KEEP(10)
936 CALL ZMUMPS_ANA_GNEW(N,NZ8,IRN(1),ICN(1),IW(1),LIW8,
937 & IPE(1), PTRAR(1,2),
938 & IPQ8, IWL1, IWFR8, KEEP8(126), KEEP8(127),
939 & INFO(1), INFO(2), ICNTL, symmetry, KEEP(50),
940 & NBQD, AvgDens, KEEP(264),KEEP(265), .TRUE.,
941 & INPLACE64_GRAPH_COPY)
945.EQ.
IF (KEEP(106)2) THEN
947 WRITE(MP,*) " SYMBOLIC based on column counts "
949 IF (present(SIZEOFBLOCKS)) THEN
951 FRERE(I) = SIZEOFBLOCKS(I)
956 CALL MUMPS_WRAP_GINP94 (
957 & N, IPE(1), IW(1), IWFR8,
960 & KEEP(60), LISTVAR_SCHUR(1), SIZE_SCHUR,
963 & IKEEP2(1), IKEEP3(1), NFSIZ(1),
964 & PTRAR(1,1), PTRAR(1,2), PTRAR(1,3),
966.LT.
IF (INFO(1)0) GOTO 90
967.EQ..AND..EQ..AND.
ELSE IF ((KEEP(106)4)(KEEP(60)0)
968.NOT..OR..EQ.
& (present(SIZEOFBLOCKS) (NORIGN))
970 WRITE(MP,*) " Undefined option for ICNTL(58) "
974 ALLOCATE( WTEMP ( 2*N ), stat = IERR )
975.GT.
IF ( IERR 0 ) THEN
981 IF (KEEP(60) == 0) THEN
987 IF (present(SIZEOFBLOCKS)) THEN
989 IWL1(I) = SIZEOFBLOCKS(I)
996 CALL MUMPS_SYMQAMD(THRESH, WTEMP,
997 & N, TOTEL, LIW8, IPE(1), IWFR8, PTRAR(1,2), IW(1),
998 & IWL1(1), WTEMP(N+1),
999 & IKEEP2(1), NCMPA, FILS(1), IKEEP3(1), PTRAR,
1000 & PTRAR(1,3),IKEEP1(1), LISTVAR_SCHUR(1), ITEMP,
1005 CALL ZMUMPS_ANA_J(N, NZ8, IRN(1), ICN(1), IKEEP1(1), IW(1),
1007 & PTRAR(1,2), IWL1, IWFR8,
1008 & INFO(1),INFO(2), MP)
1009.EQ.
IF (KEEP(60) 0) THEN
1014 CALL ZMUMPS_ANA_K(N, IPE(1), IW(1), LIW8, IWFR8, IKEEP1(1),
1016 & PTRAR, NCMPA, ITEMP, PARENT)
1019.NE.
IF (KEEP(60) 0) THEN
1020 IF (KEEP(60)==1) THEN
1021 KEEP(20) = LISTVAR_SCHUR(1)
1023 KEEP(38) = LISTVAR_SCHUR(1)
1028 & (N, PARENT, IWL1, IKEEP1(1), IKEEP2(1), IKEEP3(1),
1029 & NFSIZ, INFO(6), FILS(1), FRERE(1), PTRAR(1,3),
1032 IF (allocated(IPEALLOC)) DEALLOCATE(IPEALLOC)
1033 ALLOCATE(WTEMP(N), stat=IERR)
1034.GT.
IF ( IERR 0 ) THEN
1039 IF (present(SIZEOFBLOCKS)) THEN
1040 CALL ZMUMPS_ANA_LNEW
1041 & (N, PARENT, IWL1, IKEEP1(1), IKEEP2(1), IKEEP3(1),
1042 & NFSIZ(1), PTRAR, INFO(6), FILS(1), FRERE(1),
1043 & PTRAR(1,3), NEMIN, WTEMP, KEEP(60),
1044 & KEEP(20),KEEP(38),PTRAR(1,2),KEEP(104),IW(1),KEEP(50),
1045.EQ.
& ICNTL(13), KEEP(37), KEEP(197), NSLAVES, KEEP(250)1
1046 & , .TRUE. , SIZEOFBLOCKS, N
1049 CALL ZMUMPS_ANA_LNEW
1050 & (N, PARENT, IWL1, IKEEP1(1), IKEEP2(1), IKEEP3(1),
1051 & NFSIZ(1), PTRAR, INFO(6), FILS(1), FRERE(1),
1052 & PTRAR(1,3), NEMIN, WTEMP, KEEP(60),
1053 & KEEP(20),KEEP(38),PTRAR(1,2),KEEP(104),IW(1),KEEP(50),
1054.EQ.
& ICNTL(13), KEEP(37), KEEP(197), NSLAVES, KEEP(250)1
1055 & , .FALSE., IDUMMY, LIDUMMY )
1059.NE.
IF (KEEP(60)0) THEN
1060 IF (KEEP(60)==1) THEN
1069 IF (KEEP(60)==1) THEN
1075 FILS(IN) = LISTVAR_SCHUR (I)
1081 CALL ZMUMPS_ANA_M(IKEEP2(1),
1082 & PTRAR(1,3), INFO(6),
1083 & INFO(5), KEEP(2), KEEP(50),
1084 & KEEP8(101), KEEP(108), KEEP(5),
1085 & KEEP(6), KEEP(226), KEEP(253))
1087.NE.
IF ( KEEP(53) 0 ) THEN
1088 CALL MUMPS_MAKE1ROOT( N, FRERE(1), FILS(1), NFSIZ(1),
1091.AND..GT.
IF ( (KEEP(48) == 4 KEEP8(21)0_8)
1093.AND..GT.
& (KEEP (48)==5 KEEP8(21) 0_8 )
1095.NE..AND..GT.
& (KEEP(24)0KEEP8(21)0_8) ) THEN
1096 CALL ZMUMPS_SET_K821_SURFACE(KEEP8(21), KEEP(2),
1097 & KEEP(48), KEEP(50), NSLAVES)
1099.LT..OR..GT.
IF (KEEP(210)0KEEP(210)2) THEN
1102.EQ..AND..GT.
IF (KEEP(210)0KEEP(201)0) THEN
1105.EQ..AND..EQ.
IF (KEEP(210)0KEEP(201)0) THEN
1108.EQ.
IF (KEEP(210)2) THEN
1109 KEEP8(79)=huge(KEEP8(79))
1111.EQ..AND..LE.
IF (KEEP(210)1KEEP8(79)0_8) THEN
1112 KEEP8(79)=K79REF * int(NSLAVES,8)
1114.EQ..OR..EQ..OR.
IF ( (KEEP(79)0)(KEEP(79)2)
1115.EQ..OR..EQ..OR.
& (KEEP(79)3)(KEEP(79)5)
1118.EQ.
IF (KEEP(210)1) THEN
1120.GE.
IF ( KEEP(62)1) THEN
1122 IF (present(SIZEOFBLOCKS)) THEN
1124 IWL1(I) = SIZEOFBLOCKS(I)
1127 CALL ZMUMPS_CUTNODES(N, FRERE(1), FILS(1), NFSIZ(1),
1128 & IWL1(1), N, INFO(6),
1129 & NSLAVES, KEEP,KEEP8, SPLITROOT,
1130 & MP, LDIAG, INFO(1), INFO(2))
1131.LT.
IF (INFO(1)0) GOTO 90
1133 WRITE(MP,*) " Number of split nodes in pre-splitting=",
1139.GT..AND..GT..OR.
SPLITROOT = ((ICNTL(13)0 NSLAVESICNTL(13))
1141.NE.
IF (KEEP(53) 0) THEN
1144.AND..EQ.
SPLITROOT = (SPLITROOT( (KEEP(60)0) ))
1147 IF (present(SIZEOFBLOCKS)) THEN
1149 IWL1(I) = SIZEOFBLOCKS(I)
1152 CALL ZMUMPS_CUTNODES(N, FRERE(1), FILS(1), NFSIZ(1),
1153 & IWL1(1), N, INFO(6),
1154 & NSLAVES, KEEP,KEEP8, SPLITROOT,
1155 & MP, LDIAG, INFO(1), INFO(2))
1156.LT.
IF (INFO(1)0) GOTO 90
1157.NE.
IF ( KEEP(53) 0 ) THEN
1158 CALL MUMPS_MAKE1ROOT( N, FRERE(1), FILS(1), NFSIZ(1),
1162.GT..AND..GT.
IF (LDIAG2 MP0) THEN
1164.EQ.
IF (LDIAG4) K = N
1165.GT.
IF (K0) WRITE (MP,99987) (NFSIZ(I),I=1,K)
1166.GT.
IF (K0) WRITE (MP,99989) (FILS(I),I=1,K)
1167.GT.
IF (K0) WRITE (MP,99988) (FRERE(I),I=1,K)
1171.NE.
IF (INFO(1) 0) THEN
1172.GT..AND..GE.
IF ((LP0)(ICNTL(4)1))
1173 & WRITE (LP,99996) INFO(1), INFO(2)
1175 IF (allocated(IWALLOC)) DEALLOCATE(IWALLOC)
1176 IF (allocated(IWL1)) DEALLOCATE(IWL1)
1177 IF (allocated(IPEALLOC)) DEALLOCATE(IPEALLOC)
1178 IF (allocated(PTRAR)) DEALLOCATE(PTRAR)
1179 IF (allocated(PARENT)) DEALLOCATE(PARENT)
118199999 FORMAT (/'entering ordering phase with ...
'/
1182 & ' n nnz liw info(1)
'/,
1183 & 6X, I10, I11, I12, I10)
118499998 FORMAT ('matrix entries: irn() icn()
'/
1185 & (I12, I9, I12, I9, I12, I9))
118699909 FORMAT (/'entering ordering phase with graph dimensions ...
'/
1187 & ' |v| |e| info(1)
'/,
1188 & 10X, I10, I13, I10)
118999997 FORMAT ('ikeep1(.)=
', 10I8/(12X, 10I8))
1191 & (/'** error/warning
return ** from analysis * info(1:2)=
',
119399989 FORMAT ('fils(.) =
', 10I9/(11X, 10I9))
119499988 FORMAT ('frere(.) =
', 10I9/(11X, 10I9))
119599987 FORMAT ('nfsiz(.) =
', 10I9/(11X, 10I9))
2406 & FILS, FRERE, ND, NEMIN, SUBORD, KEEP60,
2407 & KEEP20, KEEP38, NAMALG,NAMALGMAX,
2408 & CUMUL,KEEP50, ICNTL13, KEEP37, KEEP197, NSLAVES,
2409 & ALLOW_AMALG_TINY_NODES
2410 & , BLKON, SIZEOFBLOCKS, LSIZEOFBLOCKS
2413 INTEGER N, NSTEPS, KEEP60, KEEP20, KEEP38, KEEP50
2414 INTEGER ND(N), NFSIZ(N)
2415 INTEGER (N), FILS(N), FRERE(N), (N)
2416 INTEGER NV(N), IPS(N), NE(N), NA(N), NODE(N)
2417 INTEGER NEMIN,AMALG_COUNT
2418 INTEGER NAMALG(N),NAMALGMAX, CUMUL(N)
2419 DOUBLE PRECISION SIZE_DADI_AMALGAMATED,
2420 DOUBLE PRECISION ACCU, FLOPS_FATHER, FLOPS_SON,
2421 & flops_avant, flops_apres
2422 INTEGER ICNTL13, KEEP37, NSLAVES
2423 LOGICAL ALLOW_AMALG_TINY_NODES
2425 LOGICAL,
INTENT(IN) :: BLKON
2426 INTEGER,
INTENT(IN) :: LSIZEOFBLOCKS
2427 INTEGER,
INTENT(IN) :: SIZEOFBLOCKS(LSIZEOFBLOCKS)
2428#if defined(NOAMALGTOFATHER)
2431 INTEGER I,IF,,NR,INS
2432 INTEGER K,L,ISON,IN,,INO
2436#if defined(NOAMALGTOFATHER)
2437 INTEGER INB,INF,INFS,INL,INSW,INT1,NR1
2441 LOGICAL AMALG_TO_father_OK
2452 node(i) = sizeofblocks(i)
2457 frere(1:n) = ipe(1:n)
2462 IF (nv(i).EQ.0)
THEN
2463 IF (subord(if).NE.0) subord(i) = subord(if)
2466 node(if) = node(if)+sizeofblocks(i)
2468 node(if) = node(if)+1
2470 maxnode =
max(node(if),maxnode)
2482 maxnode = int(dble(maxnode)*dble(nemin) / dble(100))
2483 maxnode =
max(maxnode,2000)
2484#if defined(NOAMALGTOFATHER)
2490 1000
IF (nr1.GT.n)
GO TO 1151
2493 1070 inl = fils(ins)
2498 1080
IF (frere(ins).LT.0)
THEN
2503 IF (frere(ins).EQ.0)
THEN
2508 IF (nv(inb).GE.nv(ins))
THEN
2513 1090 inf = frere(inf)
2514 IF (inf.GT.0)
GO TO 1090
2517 IF (infs.EQ.ins)
THEN
2520 frere(ins) = frere(inb)
2524 1100 infs = frere(insw)
2525 IF (infs.NE.ins)
THEN
2529 frere(ins) = frere(inb)
2544 amalg_to_father_ok=.false.
2554 IF (ips(i).GE.0)
EXIT
2561#if ! defined(NOAMALGTOFATHER)
2563 IF ( (dadi.NE.0) .AND.
2566 & ( (keep20.NE.dadi).AND.(keep38.NE.dadi) )
2569 accu = dble(2)*dble(node(i))*dble(nv(dadi)-nv(i)+node(i))
2570 size_dadi_amalgamated =
2571 & dble(nv(dadi)+node(i)) *
2572 & dble(nv(dadi)+node(i))
2573 percent_fill = dble(100) * accu / size_dadi_amalgamated
2574 accu = accu + dble(cumul(i))
2575 amalg_to_father_ok = (
2576 & ( (node(i).LE.maxnode).AND.(node(dadi).LE.maxnode) )
2578 & ( (node(i).LE.nemin.and. node(dadi).GT. maxnode)
2579 & .OR.(node(dadi).LE.nemin .and. node(i).GT.maxnode)))
2580 amalg_to_father_ok = ( amalg_to_father_ok .AND.
2581 & ( percent_fill < dble(nemin) ) )
2582 IF (keep197 .EQ. 1 )
THEN
2583 amalg_to_father_ok = amalg_to_father_ok.OR.
2584 & ( node(i).LE.2*nemin .AND. node(dadi).LT.4*nemin)
2586 amalg_to_father_ok = ( amalg_to_father_ok .AND.
2587 & ( accu / size_dadi_amalgamated .LE. dble(nemin)) )
2588 IF (amalg_to_father_ok)
THEN
2590 & keep50,1,flops_son)
2593 & keep50,1,flops_father)
2594 flops_avant = flops_father+flops_son
2595 & +
max(dble(200.0) * dble(nv(i)-node(i))
2596 & * dble(nv(i)-node(i)),
2599 & node(dadi)+node(i),
2600 & node(dadi)+node(i),
2601 & keep50,1,flops_apres)
2602 IF (flops_apres.GT.flops_avant*
2603 & (dble(1)+dble(
max(8,nemin)-8)/dble(100)))
THEN
2604 amalg_to_father_ok = .false.
2607 IF ( (nv(i).GT. 50*nv(dadi)).AND. (nslaves.GT.1)
2608 & .AND. (icntl13.LE.0)
2609 & .AND. (nv(i).GT. keep37) )
THEN
2610 IF ( ( accu / size_dadi_amalgamated ) .LT. 0.2 )
THEN
2611 amalg_to_father_ok = .true.
2614 IF ( allow_amalg_tiny_nodes .AND.
2615 & node(i) * 900 .LE. nv(dadi) - namalg(dadi))
THEN
2616 IF ( namalg(dadi) < (nv(dadi)-namalg(dadi))/50 )
THEN
2617 amalg_to_father_ok = .true.
2618 namalg(dadi) = namalg(dadi) + node(i)
2621 IF ( dadi .EQ. -frere(i)
2622 & .AND. -fils(dadi).EQ.i
2624 amalg_to_father_ok = ( amalg_to_father_ok .OR.
2625 & ( nv(i)-node(i).EQ.nv(dadi)) )
2627 IF (amalg_to_father_ok)
THEN
2628 cumul(dadi)=cumul(dadi)+nint(accu)
2629 namalg(dadi) = namalg(dadi) + namalg(i)
2630 amalg_count = amalg_count+1
2632 75
IF (subord(in).EQ.0)
GOTO 76
2639 IF (ifson.EQ.i)
THEN
2640 IF (fils(i).LT.0)
THEN
2641 fils(dadi) = fils(i)
2644 IF (frere(i).GT.0)
THEN
2645 fils(dadi) = -frere(i)
2655 IF (in.NE.i)
GOTO 77
2656 IF (fils(i) .LT.0)
THEN
2657 frere(ins) = -fils(i)
2659 frere(ins) = frere(i)
2666 IF (in.GT.0)
GOTO 79
2667 frere(ino) = frere(i)
2669 node(dadi) = node(dadi)+ node(i)
2670 nv(dadi) = nv(dadi) + node(i)
2671 na(il+1) = na(il+1) + na(il)
2676 ne(is) = ne(is) + node(i)
2677 IF (il.LT.n) na(il+1) = na(il+1) + 1
2684 777
IF (subord(in).EQ.0)
GO TO 778
2690 778
IF (na(is).LE.0)
GO TO 110
2691#
if defined(noamalgtofather)
2692 IF ( (keep60.NE.0).AND.
2693 & (ne(is).EQ.nd(is)) )
GOTO 110
2694 IF (nd(is-1)-ne(is-1).EQ.nd(is))
THEN
2697 IF(namalg(is-1) .GE. namalgmax)
THEN
2700 IF ((ne(is-1).GE.nemin).AND.
2701 & (ne(is).GE.nemin) )
GO TO 110
2702 IF (2*ne(is-1)*(nd(is)-nd(is-1)+ne(is-1)).GE.
2703 & ((nd(is)+ne(is-1))*
2704 & (nd(is)+ne(is-1))*nemin/100))
GO TO 110
2705 namalg(is-1) = namalg(is-1)+1
2706 100 na(is-1) = na(is-1) + na(is) - 1
2707 nd(is-1) = nd(is) + ne(is-1)
2708 ne(is-1) = ne(is) + ne(is-1)
2715 IF (in.GT.0)
GO TO 102
2718 888
IF (subord(in).EQ.0)
GO TO 889
2721 889 subord(in) = ino
2723 IF (ifson.EQ.ino)
THEN
2730 IF (in.NE.ino)
GO TO 105
2738 IF (in.EQ.0)
GO TO 120
2741 IF (in.GT.0)
GO TO 108
2748 IF (ib.GT.0) na(il) = 0
2757 IF (nv(i).EQ.0)
THEN
2761 nfsiz(i) = nd(node(i))
2762 IF (subord(i) .NE.0)
THEN
2765 DO WHILE (subord(ino).NE.0)
3030 & ( inode, n, frere, fils, nfsiz, nsteps, nslaves, keep,keep8,
3031 & tot_cut, strat, depth, k79, splitroot, mp, ldiag,
3032 & blkon, sizeofblocks, lsizeofblocks )
3035 INTEGER inode, n, nsteps, nslaves, keep(500), strat,
3036 & depth, tot_cut, mp, ldiag
3037 INTEGER(8) keep8(150)
3038 INTEGER frere( n ), fils( n ), nfsiz( n )
3041 INTEGER lsizeofblocks
3042 INTEGER (lsizeofblocks)
3043 INTEGER i, in, npiv, nfront, nslaves_estim
3044 DOUBLE PRECISION wk_slave, wk_master
3045 INTEGER inode_son, inode_fath, in_son, in_fath, in_grandfath
3046 INTEGER npiv_compg, npiv_son_compg, npiv_fath_compg
3047 INTEGER npiv_son, npiv_fath, npiv_temp
3048 INTEGER ncb, nslavesmin, nslavesmax
3053 IF ( (keep(210).EQ.1.AND.keep(60).EQ.0) .OR.
3054 & (splitroot) )
THEN
3055 IF ( frere( inode ) .eq. 0 )
THEN
3056 nfront = nfsiz( inode )
3062 npiv_compg = npiv_compg + 1
3069 IF ( int(nfront,8)*int(nfront,8).GT.k79
3075 IF ( frere( inode ) .eq. 0 )
RETURN
3076 nfront = nfsiz( inode )
3082 npiv = npiv + sizeofblocks(in)
3084 npiv_compg = npiv_compg + 1
3087 IF (.NOT.blkon) npiv = npiv_compg
3089 IF ( (nfront - (npiv/2)) .LE. keep(9))
RETURN
3090 IF ((keep(50) == 0.and.int(nfront,8) * int(npiv,8) >
3091 &(keep(50) .NE.0.and.int(npiv,8) * int(npiv,8) > k79 ))
GOTO 333
3092 IF (keep(210).EQ.1)
THEN
3095 nslaves_estim = 32+nslaves
3098 & ( nslaves, keep(48), keep8(21), keep(50),
3099 & nfront, ncb, keep(375), keep(119))
3101 & ( nslaves, keep(48), keep8(21), keep(50),
3102 & nfront, ncb, keep(375), keep(119))
3103 nslaves_estim =
max(1,
3104 & nint( dble(nslavesmax-nslavesmin)/dble(3) )
3106 nslaves_estim =
min(nslaves_estim, nslaves-1)
3108 IF ( keep(50) .eq. 0 )
THEN
3109 wk_master = 0.6667d0 *
3110 & dble(npiv)*dble(npiv)*dble(npiv) +
3111 & dble(npiv)*dble(npiv)*dble(ncb)
3112 wk_slave = dble( npiv ) * dble( ncb ) *
3113 & ( 2.0d0 * dble(nfront) - dble(npiv) )
3114 & / dble(nslaves_estim)
3116 wk_master = dble(npiv)*dble(npiv)*dble(npiv) / dble(3)
3118 & (dble(npiv)*dble(ncb)*dble(nfront))
3119 & / dble(nslaves_estim)
3121 IF (keep(210).EQ.1)
THEN
3122 IF ( dble( 100 + strat )
3123 & * wk_slave / dble(100) .GE. wk_master )
RETURN
3125 IF ( dble( 100 + strat *
max( depth-1, 1 ) )
3126 & * wk_slave / dble(100) .GE. wk_master )
RETURN
3129 IF (npiv .LE. 1 )
RETURN
3130 npiv_son =
max(npiv/2,1)
3131 npiv_fath = npiv - npiv_son
3133 IF (ncb .ne .0)
THEN
3134 WRITE(*,*)
"Error splitting"
3137 npiv_fath =
min(int(sqrt(dble(k79))), int(npiv/2))
3138 npiv_son = npiv - npiv_fath
3145 DO WHILE (in_son > 0)
3146 npiv_temp = npiv_temp + sizeofblocks(in_son)
3147 npiv_son_compg = npiv_son_compg +1
3148 IF (npiv_temp.GE.npiv_son)
EXIT
3149 in_son = fils( in_son )
3151 npiv_fath_compg = npiv_compg - npiv_son_compg
3152 npiv_son = npiv_temp
3153 npiv_fath = npiv - npiv_son
3155 npiv_son_compg = npiv_son
3156 npiv_fath_compg = npiv_fath
3158 DO i = 1, npiv_son_compg - 1
3159 in_son = fils( in_son )
3162 IF (npiv_fath_compg.EQ.0)
RETURN
3164 tot_cut = tot_cut + 1
3165 inode_fath = fils( in_son )
3166 IF ( inode_fath .LT. 0 )
THEN
3167 write(*,*)
'Error: INODE_FATH < 0 ', inode_fath
3169 in_fath = inode_fath
3170 DO WHILE ( fils( in_fath ) > 0 )
3171 in_fath = fils( in_fath )
3173 frere( inode_fath ) = frere( inode_son )
3174 frere( inode_son ) = - inode_fath
3175 fils( in_son ) = fils( in_fath )
3176 fils( in_fath ) = - inode_son
3177 in = frere( inode_fath )
3181 IF ( in .eq. 0 )
GO TO 10
3183 DO WHILE ( fils( in ) > 0 )
3187 IF ( fils( in_grandfath ) .eq. - inode_son )
THEN
3188 fils( in_grandfath ) = -inode_fath
3192 DO WHILE ( frere( in ) > 0 )
3193 IF ( frere( in ) .eq. inode_son )
THEN
3194 frere( in ) = inode_fath
3199 WRITE(*,*)
'ERROR 2 in SPLIT NODE',
3200 & in_grandfath, in, frere(in)
3203 nfsiz(inode_son) = nfront
3204 nfsiz(inode_fath) = nfront - npiv_son
3205 keep(2) =
max( keep(2), nfront - npiv_son )
3210 & ( inode_fath, n, frere, fils, nfsiz, nsteps,
3211 & nslaves, keep,keep8, tot_cut, strat, depth,
3212 & k79, splitroot, mp, ldiag,
3213 & blkon, sizeofblocks, lsizeofblocks )
3214 IF (.NOT. splitroot)
THEN
3216 & ( inode_son, n, frere, fils, nfsiz, nsteps,
3217 & nslaves, keep,keep8, tot_cut, strat, depth,
3218 & k79, splitroot, mp, ldiag,
3219 & blkon, sizeofblocks, lsizeofblocks )
3609 & IP,IRN,A,LA,NUM,PERM,LIW,IW,LDW,DW,
3611 & ICNTL,CNTL,INFO, INFOMUMPS)
3613 INTEGER :: NICNTL, NCNTL, NINFO, INFOMUMPS(80)
3614 parameter(nicntl=10, ncntl=10, ninfo=10)
3615 INTEGER :: JOB,M,N,NUM
3616 INTEGER(8),
INTENT(IN) :: NE, LIW,LDW, LA
3617 INTEGER(8) :: IP(N+1), IPQ8(N)
3618 INTEGER :: IRN(NE),PERM(M),IW(LIW)
3619 INTEGER :: ICNTL(NICNTL),INFO(NINFO)
3620 DOUBLE PRECISION :: A(LA)
3621 DOUBLE PRECISION :: DW(LDW),CNTL(NCNTL)
3622 INTEGER(8),
DIMENSION(:),
ALLOCATABLE :: IWtemp8
3624 INTEGER :: I,J,WARN1,WARN2,WARN4
3626 DOUBLE PRECISION :: FACT,ZERO,ONE,RINF,RINF2,RINF3
3627 parameter(zero=0.0d+00,one=1.0d+0)
3632 rinf2 = huge(rinf2)/dble(2*n)
3637 IF (job.LT.1 .OR. job.GT.6)
THEN
3640 IF (icntl(1).GE.0)
WRITE(icntl(1),9001) info(1),
'JOB',job
3643 IF (m.LT.1 .OR. m.LT.n)
THEN
3646 IF (icntl(1).GE.0)
WRITE(icntl(1),9001) info(1),
'M',m
3652 IF (icntl(1).GE.0)
WRITE(icntl(1),9001) info(1),
'N',n
3658 IF (icntl(1).GE.0)
WRITE(icntl(1),9001) info(1),
'NE',ne
3661 IF (job.EQ.1) k = int(4*n + m,8)
3662 IF (job.EQ.2) k = int(n + 2*m,8)
3663 IF (job.EQ.3) k = int(8*n + 2*m + ne,8)
3664 IF (job.EQ.4) k = int(n + m,8)
3665 IF (job.EQ.5) k = int(3*n + 2*m,8)
3666 IF (job.EQ.6) k = int(3*n + 2*m + ne,8)
3670 IF (icntl(1).GE.0)
WRITE(icntl(1),9004) info(1),k
3674 IF (job.EQ.2) k = int( m,8)
3675 IF (job.EQ.3) k = int(1,8)
3676 IF (job.EQ.4) k = int( 2*m,8)
3677 IF (job.EQ.5) k = int(n + 2*m,8)
3678 IF (job.EQ.6) k = int(n + 3*m,8)
3679 IF (ldw .LT. k)
THEN
3682 IF (icntl(1).GE.0)
WRITE(icntl(1),9005) info(1),k
3686 IF (icntl(5).EQ.0)
THEN
3691 DO 4 k = ip(j),ip(j+1)-1_8
3693 IF (i.LT.1 .OR. i.GT.m)
THEN
3696 IF (icntl(1).GE.0)
WRITE(icntl(1),9006) info(1),j,i
3699 IF (iw(i).EQ.j)
THEN
3702 IF (icntl(1).GE.0)
WRITE(icntl(1),9007) info(1),j,i
3710 IF (icntl(3).GT.0)
THEN
3711 IF (icntl(4).EQ.0 .OR. icntl(4).EQ.1)
THEN
3712 WRITE(icntl(3),9020) job,m,n,ne
3713 IF (icntl(4).EQ.0)
THEN
3714 WRITE(icntl(3),9021) (ip(j),j=1,
min(10,n+1))
3715 WRITE(icntl(3),9022) (irn(k),k=1_8,
min(10_8,ne))
3716 IF (job.GT.1)
WRITE(icntl(3),9023)
3717 & (a(k),k=1_8,
min(10_8,ne))
3718 ELSEIF (icntl(4).EQ.1)
THEN
3719 WRITE(icntl(3),9021) (ip(j),j=1,n+1)
3720 WRITE(icntl(3),9022) (irn(k),k=1_8,ne)
3721 IF (job.GT.1)
WRITE(icntl(3),9023) (a(k),k=1_8,ne)
3723 WRITE(icntl(3),9024) (icntl(j),j=1,nicntl)
3724 WRITE(icntl(3),9025) (cntl(j),j=1,ncntl)
3732 iw(j) = int(ip(j+1) - ip(j))
3735 & iw(n+1),iw(2*n+1),iw(3*n+1),iw(3*n+m+1))
3739 dw(1) =
max(zero,cntl(1))
3741 & iw(1),ipq8,iw(n+1),iw(n+m+1),dw,rinf2)
3749 fact =
max(zero,cntl(1))
3751 & iw(ne+n+1),iw(ne+2*n+1),iw(ne+3*n+1),iw(ne+4*n+1),
3752 & iw(ne+5*n+1),iw(ne+5*n+m+1),fact,rinf2)
3755 IF ((job.EQ.4).OR.(job.EQ.5).or.(job.EQ.6))
THEN
3756 ALLOCATE(iwtemp8(m+n+n), stat=allocok)
3757 IF (allocok.GT.0)
THEN
3759 infomumps(2) = m+n+n
3766 DO 30 k = ip(j),ip(j+1)-1_8
3767 IF (abs(a(k)).GT.fact) fact = abs(a(k))
3769 IF(fact .GT. rinf3) rinf3 = fact
3770 DO 40 k = ip(j),ip(j+1)-1_8
3771 a(k) = fact - abs(a(k))
3774 dw(1) =
max(zero,cntl(1))
3776 iwtemp8(1) = int(job,8)
3778 & iwtemp8(1),iw(1),iwtemp8(n+1),ipq8,iw(n+1),
3780 & dw(1),dw(m+1),rinf2)
3784 IF (job.EQ.5 .or. job.EQ.6)
THEN
3789 DO 60 k = ip(j),ip(j+1)-1_8
3790 IF (a(k).GT.fact) fact = a(k)
3793 IF (fact.NE.zero)
THEN
3795 IF(fact .GT. rinf3) rinf3=fact
3796 DO 70 k = ip(j),ip(j+1)-1_8
3797 IF (a(k).NE.zero)
THEN
3798 a(k) = fact - log(a(k))
3799 IF(a(k) .GT. rinf3) rinf3=a(k)
3805 DO 71 k = ip(j),ip(j+1)-1_8
3813 iw(3*n+2*m+k) = irn(k)
3819 DO 62 k = ip(j),ip(j+1)-1_8
3821 IF (a(k).GT.dw(2*m+n+i))
THEN
3827 IF (dw(2*m+n+i).NE.zero)
THEN
3828 dw(2*m+n+i) = 1.0d0/dw(2*m+n+i)
3832 DO 65 k = ip(j),ip(j+1)-1
3834 a(k) = dw(2*m+n+i) * a(k)
3839 IF (ip(j).NE.ip(j+1))
THEN
3845 IF (fact.NE.zero)
THEN
3847 DO 170 k = ip(j),ip(j+1)-1_8
3848 IF (a(k).NE.zero)
THEN
3849 a(k) = fact - log(a(k))
3850 IF(a(k) .GT. rinf3) rinf3=a(k)
3856 DO 171 k = ip(j),ip(j+1)-1_8
3862 dw(1) =
max(zero,cntl(1))
3865 iwtemp8(1) = int(job,8)
3868 & iwtemp8(1),iw(1),iwtemp8(n+1),ipq8,iw(n+1),
3870 & dw(1),dw(m+1),rinf2)
3874 & iwtemp8(1),iw(1),iwtemp8(n+1),ipq8,iw(n+1),
3876 & dw(1),dw(m+1),rinf2)
3878 IF ((job.EQ.5).or.(job.EQ.6))
THEN
3883 IF (dw(2*m+n+i).NE.0.0d0)
THEN
3884 dw(i) = dw(i) + log(dw(2*m+n+i))
3890 IF (dw(2*m+j).NE.zero)
THEN
3891 dw(m+j) = dw(m+j) - log(dw(2*m+j))
3897 fact = 0.5d0*log(rinf2)
3899 IF (dw(i).LT.fact)
GO TO 86
3904 IF (dw(m+j).LT.fact)
GO TO 87
3909 90
IF (infomumps(1).LT.0)
RETURN
3910 IF (num.LT.n) warn1 = 1
3911 IF (job.EQ.4 .OR. job.EQ.5 .OR. job.EQ.6)
THEN
3912 IF (cntl(1).LT.zero) warn4 = 4
3914 IF (info(1).EQ.0)
THEN
3915 info(1) = warn1 + warn2 + warn4
3916 IF (info(1).GT.0 .AND. icntl(2).GT.0)
THEN
3917 WRITE(icntl(2),9010) info(1)
3918 IF (warn1.EQ.1)
WRITE(icntl(2),9011)
3919 IF (warn2.EQ.2)
WRITE(icntl(2),9012)
3920 IF (warn4.EQ.4)
WRITE(icntl(2),9014)
3923 IF (icntl(3).GE.0)
THEN
3924 IF (icntl(4).EQ.0 .OR. icntl(4).EQ.1)
THEN
3925 WRITE(icntl(3),9030) (info(j),j=1,2)
3926 WRITE(icntl(3),9031) num
3927 IF (icntl(4).EQ.0)
THEN
3928 WRITE(icntl(3),9032) (perm(j),j=1,
min(10,m))
3929 IF (job.EQ.5 .OR. job.EQ.6)
THEN
3930 WRITE(icntl(3),9033) (dw(j),j=1,
min(10,m))
3931 WRITE(icntl(3),9034) (dw(m+j),j=1,
min(10,n))
3933 ELSEIF (icntl(4).EQ.1)
THEN
3934 WRITE(icntl(3),9032) (perm(j),j=1,m)
3935 IF (job.EQ.5 .OR. job.EQ.6)
THEN
3936 WRITE(icntl(3),9033) (dw(j),j=1,m)
3937 WRITE(icntl(3),9034) (dw(m+j),j=1,n)
3943 9001
FORMAT (
' ****** Error in ZMUMPS_MTRANSA. INFO(1) = ',i2,
3944 &
' because ',(a),
' = ',i14)
3945 9004
FORMAT (
' ****** Error in ZMUMPS_MTRANSA. INFO(1) = ',i2/
3946 &
' LIW too small, must be at least ',i14)
3947 9005
FORMAT (
' ****** Error in ZMUMPS_MTRANSA. INFO(1) = ',i2/
3948 &
' LDW too small, must be at least ',i14)
3949 9006
FORMAT (
' ****** Error in ZMUMPS_MTRANSA. INFO(1) = ',i2/
3951 &
' contains an entry with invalid row index ',i8)
3952 9007
FORMAT (
' ****** Error in ZMUMPS_MTRANSA. INFO(1) = ',i2/
3954 &
' contains two or more entries with row index ',i8)
3955 9010
FORMAT (
' ****** Warning from ZMUMPS_MTRANSA. INFO(1) = ',i2)
3956 9011
FORMAT (
' - The matrix is structurally singular.')
3957 9012
FORMAT (
' - Some scaling factors may be too large.')
3958 9014
FORMAT (
' - CNTL(1) is negative and was treated as zero.')
3959 9020
FORMAT (
' ****** Input parameters for ZMUMPS_MTRANSA:'/
3960 &
' JOB =',i10/
' M =',i10/
' N =',i10/
' NE =',i14)
3961 9021
FORMAT (
' IP(1:N+1) = ',8i8/(15x,8i8))
3962 9022
FORMAT (
' IRN(1:NE) = ',8i8/(15x,8i8))
3963 9023
FORMAT (
' A(1:NE) = ',4(1pd14.4)/(15x,4(1pd14.4)))
3964 9024
FORMAT (
' ICNTL(1:10) = ',8i8/(15x,2i8))
3965 9025
FORMAT (
' CNTL(1:10) = ',4(1pd14.4)/(15x,4(1pd14.4)))
3966 9030
FORMAT (
' ****** Output parameters for ZMUMPS_MTRANSA:'/
3967 &
' INFO(1:2) = ',2i8)
3968 9031
FORMAT (
' NUM = ',i8)
3969 9032
FORMAT (
' PERM(1:M) = ',8i8/(15x,8i8))
3970 9033
FORMAT (
' DW(1:M) = ',5(f11.3)/(15x,5(f11.3)))
3971 9034
FORMAT (
' DW(M+1:M+N) = ',5(f11.3)/(15x,5(f11.3)))