1 SUBROUTINE pspttrf( N, D, E, JA, DESCA, AF, LAF, WORK, LWORK,
10 INTEGER INFO, JA, LAF, LWORK, N
14 REAL AF( * ), D( * ), E( * ), WORK( * )
350 parameter( one = 1.0e+0 )
352 parameter( zero = 0.0e+0 )
354 parameter( int_one = 1 )
355 INTEGER DESCMULT, BIGNUM
356 parameter( descmult = 100, bignum = descmult*descmult )
357 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
358 $ lld_, mb_, m_, nb_, n_, rsrc_
359 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
360 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
361 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
364 INTEGER COMM_PROC, CSRC, FIRST_PROC, I, ICTXT,
365 $ ictxt_new, ictxt_save, idum3, int_temp, ja_new,
366 $ laf_min, level_dist, llda, mycol, myrow,
367 $ my_num_cols, nb, np, npcol, nprow, np_save,
368 $ odd_size, part_offset, part_size, return_code,
369 $ store_n_a, temp, work_size_min
372 INTEGER DESCA_1XP( 7 ), PARAM_CHECK( 7, 3 )
398 temp = desca( dtype_ )
399 IF( temp.EQ.502 )
THEN
401 desca( dtype_ ) = 501
406 desca( dtype_ ) = temp
408 IF( return_code.NE.0 )
THEN
414 ictxt = desca_1xp( 2 )
415 csrc = desca_1xp( 5 )
417 llda = desca_1xp( 6 )
418 store_n_a = desca_1xp( 3 )
423 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
428 IF( lwork.LT.-1 )
THEN
430 ELSE IF( lwork.EQ.-1 )
THEN
440 IF( n+ja-1.GT.store_n_a )
THEN
446 IF( nprow.NE.1 )
THEN
450 IF( n.GT.np*nb-mod( ja-1, nb ) )
THEN
452 CALL pxerbla( ictxt,
'PSPTTRF, D&C alg.: only 1 block per proc'
457 IF( ( ja+n-1.GT.nb ) .AND. ( nb.LT.2*int_one ) )
THEN
459 CALL pxerbla( ictxt,
'PSPTTRF, D&C alg.: NB too small', -info )
466 laf_min = ( 12*npcol+3*nb )
468 IF( laf.LT.laf_min )
THEN
472 CALL pxerbla( ictxt,
'PSPTTRF: auxiliary storage error ',
479 work_size_min = 8*npcol
481 work( 1 ) = work_size_min
483 IF( lwork.LT.work_size_min )
THEN
484 IF( lwork.NE.-1 )
THEN
486 CALL pxerbla( ictxt,
'PSPTTRF: worksize error ', -info )
493 param_check( 7, 1 ) = desca( 5 )
494 param_check( 6, 1 ) = desca( 4 )
495 param_check( 5, 1 ) = desca( 3 )
496 param_check( 4, 1 ) = desca( 1 )
497 param_check( 3, 1 ) = ja
498 param_check( 2, 1 ) = n
499 param_check( 1, 1 ) = idum3
501 param_check( 7, 2 ) = 505
502 param_check( 6, 2 ) = 504
503 param_check( 5, 2 ) = 503
504 param_check( 4, 2 ) = 501
505 param_check( 3, 2 ) = 4
506 param_check( 2, 2 ) = 1
507 param_check( 1, 2 ) = 9
515 ELSE IF( info.LT.-descmult )
THEN
518 info = -info*descmult
523 CALL globchk( ictxt, 7, param_check, 7, param_check( 1, 3 ),
529 IF( info.EQ.bignum )
THEN
531 ELSE IF( mod( info, descmult ).EQ.0 )
THEN
532 info = -info / descmult
538 CALL pxerbla( ictxt,
'PSPTTRF', -info )
551 part_offset = nb*( ( ja-1 ) / ( npcol*nb ) )
553 IF( ( mycol-csrc ).LT.( ja-part_offset-1 ) / nb )
THEN
554 part_offset = part_offset + nb
557 IF( mycol.LT.csrc )
THEN
558 part_offset = part_offset - nb
567 first_proc = mod( ( ja-1 ) / nb+csrc, npcol )
571 ja_new = mod( ja-1, nb ) + 1
576 np = ( ja_new+n-2 ) / nb + 1
580 CALL reshape( ictxt, int_one, ictxt_new, int_one, first_proc,
587 desca_1xp( 2 ) = ictxt_new
591 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
595 IF( myrow.LT.0 )
THEN
608 my_num_cols = numroc( n, part_size, mycol, 0, npcol )
612 IF( mycol.EQ.0 )
THEN
613 part_offset = part_offset + mod( ja_new-1, part_size )
614 my_num_cols = my_num_cols - mod( ja_new-1, part_size )
619 odd_size = my_num_cols
620 IF( mycol.LT.np-1 )
THEN
621 odd_size = odd_size - int_one
639 IF( mycol.LT.np-1 )
THEN
645 CALL strsd2d( ictxt,
'U',
'N', 1, 1,
646 $ e( part_offset+odd_size+1 ), llda-1, 0, mycol+1 )
654 CALL spttrf( odd_size, d( part_offset+1 ), e( part_offset+1 ),
663 IF( mycol.LT.np-1 )
THEN
670 e( part_offset+odd_size ) = e( part_offset+odd_size ) /
671 $ d( part_offset+odd_size )
678 d( part_offset+odd_size+1 ) = d( part_offset+odd_size+1 ) -
679 $ d( part_offset+odd_size )*
680 $ ( e( part_offset+odd_size )*
681 $ ( e( part_offset+odd_size ) ) )
690 IF( mycol.NE.0 )
THEN
697 CALL strrv2d( ictxt,
'U',
'N', 1, 1, af( 1 ), odd_size, 0,
704 CALL spttrsv(
'N', odd_size, int_one, d( part_offset+1 ),
705 $ e( part_offset+1 ), af( 1 ), odd_size, info )
709 DO 30 i = 1, odd_size
710 af( i ) = af( i ) / d( part_offset+i )
720 int_temp = odd_size*int_one + 2 + 1
723 DO 40 i = 1, odd_size
724 af( int_temp ) = af( int_temp ) -
725 $ d( part_offset+i )*( af( i )*
733 CALL sgesd2d( ictxt, int_one, int_one, af( odd_size+3 ),
734 $ int_one, 0, mycol-1 )
737 IF( mycol.LT.np-1 )
THEN
744 af( odd_size+1 ) = -d( part_offset+odd_size )*
745 $ ( e( part_offset+odd_size )*
760 CALL igamx2d( ictxt,
'A',
' ', 1, 1, info, 1, info, info, -1, 0,
763 IF( mycol.EQ.0 )
THEN
764 CALL igebs2d( ictxt,
'A',
' ', 1, 1, info, 1 )
766 CALL igebr2d( ictxt,
'A',
' ', 1, 1, info, 1, 0, 0 )
784 IF( mycol.EQ.npcol-1 )
THEN
792 IF( ( mod( mycol+1, 2 ).EQ.0 ) .AND. ( mycol.GT.0 ) )
THEN
794 CALL sgesd2d( ictxt, int_one, int_one, af( odd_size+1 ),
795 $ int_one, 0, mycol-1 )
802 af( odd_size+2 ) = real( d( part_offset+odd_size+1 ) )
806 IF( mycol.LT.npcol-1 )
THEN
808 CALL sgerv2d( ictxt, int_one, int_one, af( odd_size+2+1 ),
809 $ int_one, 0, mycol+1 )
813 af( odd_size+2 ) = af( odd_size+2 ) + af( odd_size+3 )
828 IF( mod( ( mycol+1 ) / level_dist, 2 ).NE.0 )
833 IF( mycol-level_dist.GE.0 )
THEN
834 CALL sgerv2d( ictxt, int_one, int_one, work( 1 ), int_one, 0,
837 af( odd_size+2 ) = af( odd_size+2 ) + work( 1 )
843 IF( mycol+level_dist.LT.npcol-1 )
THEN
844 CALL sgerv2d( ictxt, int_one, int_one, work( 1 ), int_one, 0,
847 af( odd_size+2 ) = af( odd_size+2 ) + work( 1 )
851 level_dist = level_dist*2
860 IF( af( odd_size+2 ).EQ.zero )
THEN
869 IF( level_dist.EQ.1 )
THEN
870 comm_proc = mycol + 1
875 af( odd_size+3 ) = af( odd_size+1 )
878 comm_proc = mycol + level_dist / 2
881 IF( mycol / level_dist.LE.( npcol-1 ) / level_dist-2 )
THEN
883 CALL sgerv2d( ictxt, int_one, int_one, af( odd_size+1 ),
884 $ int_one, 0, comm_proc )
892 af( odd_size+1 ) = af( odd_size+1 ) / af( odd_size+2 )
899 work( 1 ) = -one*af( odd_size+1 )*af( odd_size+2 )*
900 $ ( af( odd_size+1 ) )
904 CALL sgesd2d( ictxt, int_one, int_one, work( 1 ), int_one, 0,
915 IF( ( mycol / level_dist.GT.0 ) .AND.
916 $ ( mycol / level_dist.LE.( npcol-1 ) / level_dist-1 ) )
THEN
918 IF( level_dist.GT.1 )
THEN
923 CALL sgerv2d( ictxt, int_one, int_one, af( odd_size+2+1 ),
924 $ int_one, 0, mycol-level_dist / 2 )
933 af( odd_size+3 ) = ( af( odd_size+3 ) ) / af( odd_size+2 )
941 work( 1 ) = -one*af( odd_size+3 )*af( odd_size+2 )*
942 $ ( af( odd_size+3 ) )
946 CALL sgesd2d( ictxt, int_one, int_one, work( 1 ), int_one, 0,
951 IF( mycol / level_dist.LE.( npcol-1 ) / level_dist-2 )
THEN
955 IF( ( mod( mycol / ( 2*level_dist ), 2 ) ).EQ.0 )
THEN
956 comm_proc = mycol + level_dist
958 comm_proc = mycol - level_dist
965 work( 1 ) = -one*af( odd_size+3 )*af( odd_size+2 )*
970 CALL sgesd2d( ictxt, int_one, int_one, work( 1 ), int_one,
986 IF( ictxt_save.NE.ictxt_new )
THEN
987 CALL blacs_gridexit( ictxt_new )
999 work( 1 ) = work_size_min
1003 CALL igamx2d( ictxt,
'A',
' ', 1, 1, info, 1, info, info, -1, 0,
1006 IF( mycol.EQ.0 )
THEN
1007 CALL igebs2d( ictxt,
'A',
' ', 1, 1, info, 1 )
1009 CALL igebr2d( ictxt,
'A',
' ', 1, 1, info, 1, 0, 0 )