1 SUBROUTINE pdpttrsv( UPLO, N, NRHS, D, E, JA, DESCA, B, IB, DESCB,
2 $ AF, LAF, WORK, LWORK, INFO )
11 INTEGER IB, INFO, JA, LAF, LWORK, N, NRHS
14 INTEGER DESCA( * ), DESCB( * )
15 DOUBLE PRECISION AF( * ), B( * ), D( * ), E( * ), WORK( * )
374 parameter( one = 1.0d+0 )
375 DOUBLE PRECISION ZERO
376 parameter( zero = 0.0d+0 )
378 parameter( int_one = 1 )
379 INTEGER DESCMULT, BIGNUM
380 parameter( descmult = 100, bignum = descmult*descmult )
381 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
382 $ lld_, mb_, m_, nb_, n_, rsrc_
383 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
384 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
385 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
388 INTEGER CSRC, FIRST_PROC, ICTXT, ICTXT_NEW, ICTXT_SAVE,
389 $ idum1, idum3, ja_new, level_dist, llda, lldb,
390 $ mycol, myrow, my_num_cols, nb, np, npcol,
391 $ nprow, np_save, odd_size, part_offset,
392 $ part_size, return_code, store_m_b, store_n_a,
393 $ temp, work_size_min
396 INTEGER DESCA_1XP( 7 ), DESCB_PX1( 7 ),
397 $ param_check( 15, 3 )
400 EXTERNAL blacs_gridexit, blacs_gridinfo, daxpy,
407 EXTERNAL lsame, numroc
424 temp = desca( dtype_ )
425 IF( temp.EQ.502 )
THEN
427 desca( dtype_ ) = 501
432 desca( dtype_ ) = temp
434 IF( return_code.NE.0 )
THEN
440 IF( return_code.NE.0 )
THEN
447 IF( desca_1xp( 2 ).NE.descb_px1( 2 ) )
THEN
455 IF( desca_1xp( 4 ).NE.descb_px1( 4 ) )
THEN
461 IF( desca_1xp( 5 ).NE.descb_px1( 5 ) )
THEN
467 ictxt = desca_1xp( 2 )
468 csrc = desca_1xp( 5 )
470 llda = desca_1xp( 6 )
471 store_n_a = desca_1xp( 3 )
472 lldb = descb_px1( 6 )
473 store_m_b = descb_px1( 3 )
478 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
483 IF( lsame( uplo,
'U' ) )
THEN
485 ELSE IF( lsame( uplo,
'L' ) )
THEN
491 IF( lwork.LT.-1 )
THEN
493 ELSE IF( lwork.EQ.-1 )
THEN
503 IF( n+ja-1.GT.store_n_a )
THEN
507 IF( n+ib-1.GT.store_m_b )
THEN
511 IF( lldb.LT.nb )
THEN
527 IF( nprow.NE.1 )
THEN
531 IF( n.GT.np*nb-mod( ja-1, nb ) )
THEN
534 $
'PDPTTRSV, D&C alg.: only 1 block per proc',
539 IF( ( ja+n-1.GT.nb ) .AND. ( nb.LT.2*int_one ) )
THEN
541 CALL pxerbla( ictxt,
'PDPTTRSV, D&C alg.: NB too small',
547 work_size_min = int_one*nrhs
549 work( 1 ) = work_size_min
551 IF( lwork.LT.work_size_min )
THEN
552 IF( lwork.NE.-1 )
THEN
554 CALL pxerbla( ictxt,
'PDPTTRSV: worksize error', -info )
561 param_check( 15, 1 ) = descb( 5 )
562 param_check( 14, 1 ) = descb( 4 )
563 param_check( 13, 1 ) = descb( 3 )
564 param_check( 12, 1 ) = descb( 2 )
565 param_check( 11, 1 ) = descb( 1 )
566 param_check( 10, 1 ) = ib
567 param_check( 9, 1 ) = desca( 5 )
568 param_check( 8, 1 ) = desca( 4 )
569 param_check( 7, 1 ) = desca( 3 )
570 param_check( 6, 1 ) = desca( 1 )
571 param_check( 5, 1 ) = ja
572 param_check( 4, 1 ) = nrhs
573 param_check( 3, 1 ) = n
574 param_check( 2, 1 ) = idum3
575 param_check( 1, 1 ) = idum1
577 param_check( 15, 2 ) = 1005
578 param_check( 14, 2 ) = 1004
579 param_check( 13, 2 ) = 1003
580 param_check( 12, 2 ) = 1002
581 param_check( 11, 2 ) = 1001
582 param_check( 10, 2 ) = 9
583 param_check( 9, 2 ) = 705
584 param_check( 8, 2 ) = 704
585 param_check( 7, 2 ) = 703
586 param_check( 6, 2 ) = 701
587 param_check( 5, 2 ) = 6
588 param_check( 4, 2 ) = 3
589 param_check( 3, 2 ) = 2
590 param_check( 2, 2 ) = 14
591 param_check( 1, 2 ) = 1
599 ELSE IF( info.LT.-descmult )
THEN
602 info = -info*descmult
607 CALL globchk( ictxt, 15, param_check, 15, param_check( 1, 3 ),
613 IF( info.EQ.bignum )
THEN
615 ELSE IF( mod( info, descmult ).EQ.0 )
THEN
616 info = -info / descmult
622 CALL pxerbla( ictxt,
'PDPTTRSV', -info )
638 part_offset = nb*( ( ja-1 ) / ( npcol*nb ) )
640 IF( ( mycol-csrc ).LT.( ja-part_offset-1 ) / nb )
THEN
641 part_offset = part_offset + nb
644 IF( mycol.LT.csrc )
THEN
645 part_offset = part_offset - nb
654 first_proc = mod( ( ja-1 ) / nb+csrc, npcol )
658 ja_new = mod( ja-1, nb ) + 1
663 np = ( ja_new+n-2 ) / nb + 1
667 CALL reshape( ictxt, int_one, ictxt_new, int_one, first_proc,
674 desca_1xp( 2 ) = ictxt_new
675 descb_px1( 2 ) = ictxt_new
679 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
683 IF( myrow.LT.0 )
THEN
696 my_num_cols = numroc( n, part_size, mycol, 0, npcol )
700 IF( mycol.EQ.0 )
THEN
701 part_offset = part_offset + mod( ja_new-1, part_size )
702 my_num_cols = my_num_cols - mod( ja_new-1, part_size )
707 odd_size = my_num_cols
708 IF( mycol.LT.np-1 )
THEN
709 odd_size = odd_size - int_one
716 IF( lsame( uplo,
'L' ) )
THEN
728 CALL dpttrsv(
'N', odd_size, nrhs, d( part_offset+1 ),
729 $ e( part_offset+1 ), b( part_offset+1 ), lldb,
733 IF( mycol.LT.np-1 )
THEN
737 CALL daxpy( nrhs, -e( part_offset+odd_size ),
738 $ b( part_offset+odd_size ), lldb,
739 $ b( part_offset+odd_size+1 ), lldb )
744 IF( mycol.NE.0 )
THEN
748 CALL dgemm(
'T',
'N', 1, nrhs, odd_size, -one, af( 1 ),
749 $ odd_size, b( part_offset+1 ), lldb, zero,
750 $ work( 1+int_one-1 ), int_one )
761 IF( mycol.GT.0 )
THEN
763 CALL dgesd2d( ictxt, int_one, nrhs, work( 1 ), int_one, 0,
770 IF( mycol.LT.npcol-1 )
THEN
772 CALL dgerv2d( ictxt, int_one, nrhs, work( 1 ), int_one, 0,
777 CALL dmatadd( int_one, nrhs, one, work( 1 ), int_one, one,
778 $ b( part_offset+odd_size+1 ), lldb )
785 IF( mycol.EQ.npcol-1 )
THEN
800 IF( mod( ( mycol+1 ) / level_dist, 2 ).NE.0 )
805 IF( mycol-level_dist.GE.0 )
THEN
807 CALL dgerv2d( ictxt, int_one, nrhs, work( 1 ), int_one, 0,
810 CALL dmatadd( int_one, nrhs, one, work( 1 ), int_one, one,
811 $ b( part_offset+odd_size+1 ), lldb )
817 IF( mycol+level_dist.LT.npcol-1 )
THEN
819 CALL dgerv2d( ictxt, int_one, nrhs, work( 1 ), int_one, 0,
822 CALL dmatadd( int_one, nrhs, one, work( 1 ), int_one, one,
823 $ b( part_offset+odd_size+1 ), lldb )
827 level_dist = level_dist*2
840 CALL dtrtrs(
'L',
'N',
'U', int_one, nrhs, af( odd_size+2 ),
841 $ int_one, b( part_offset+odd_size+1 ), lldb, info )
850 IF( mycol / level_dist.LE.( npcol-1 ) / level_dist-2 )
THEN
854 CALL dgemm(
'T',
'N', int_one, nrhs, int_one, -one,
855 $ af( ( odd_size )*1+1 ), int_one,
856 $ b( part_offset+odd_size+1 ), lldb, zero,
857 $ work( 1 ), int_one )
861 CALL dgesd2d( ictxt, int_one, nrhs, work( 1 ), int_one, 0,
868 IF( ( mycol / level_dist.GT.0 ) .AND.
869 $ ( mycol / level_dist.LE.( npcol-1 ) / level_dist-1 ) )
THEN
875 CALL dgemm(
'N',
'N', int_one, nrhs, int_one, -one,
876 $ af( odd_size*1+2+1 ), int_one,
877 $ b( part_offset+odd_size+1 ), lldb, zero,
878 $ work( 1 ), int_one )
882 CALL dgesd2d( ictxt, int_one, nrhs, work( 1 ), int_one, 0,
902 IF( mycol.EQ.npcol-1 )
THEN
910 IF( mod( ( mycol+1 ) / level_dist, 2 ).NE.0 )
913 level_dist = level_dist*2
919 IF( ( mycol / level_dist.GT.0 ) .AND.
920 $ ( mycol / level_dist.LE.( npcol-1 ) / level_dist-1 ) )
THEN
924 CALL dgerv2d( ictxt, int_one, nrhs, work( 1 ), int_one, 0,
931 CALL dgemm(
'T',
'N', int_one, nrhs, int_one, -one,
932 $ af( odd_size*1+2+1 ), int_one, work( 1 ),
933 $ int_one, one, b( part_offset+odd_size+1 ),
939 IF( mycol / level_dist.LE.( npcol-1 ) / level_dist-2 )
THEN
943 CALL dgerv2d( ictxt, int_one, nrhs, work( 1 ), int_one, 0,
948 CALL dgemm(
'N',
'N', int_one, nrhs, int_one, -one,
949 $ af( ( odd_size )*1+1 ), int_one, work( 1 ),
950 $ int_one, one, b( part_offset+odd_size+1 ),
959 CALL dtrtrs(
'L',
'T',
'U', int_one, nrhs, af( odd_size+2 ),
960 $ int_one, b( part_offset+odd_size+1 ), lldb, info )
971 IF( level_dist.EQ.1 )
974 level_dist = level_dist / 2
978 IF( mycol+level_dist.LT.npcol-1 )
THEN
980 CALL dgesd2d( ictxt, int_one, nrhs,
981 $ b( part_offset+odd_size+1 ), lldb, 0,
988 IF( mycol-level_dist.GE.0 )
THEN
990 CALL dgesd2d( ictxt, int_one, nrhs,
991 $ b( part_offset+odd_size+1 ), lldb, 0,
1010 IF( mycol.LT.npcol-1 )
THEN
1012 CALL dgesd2d( ictxt, int_one, nrhs,
1013 $ b( part_offset+odd_size+1 ), lldb, 0,
1020 IF( mycol.GT.0 )
THEN
1022 CALL dgerv2d( ictxt, int_one, nrhs, work( 1 ), int_one, 0,
1033 IF( mycol.NE.0 )
THEN
1037 CALL dgemm(
'N',
'N', odd_size, nrhs, 1, -one, af( 1 ),
1038 $ odd_size, work( 1+int_one-1 ), int_one, one,
1039 $ b( part_offset+1 ), lldb )
1044 IF( mycol.LT.np-1 )
THEN
1048 CALL daxpy( nrhs, -( e( part_offset+odd_size ) ),
1049 $ b( part_offset+odd_size+1 ), lldb,
1050 $ b( part_offset+odd_size ), lldb )
1056 CALL dpttrsv(
'T', odd_size, nrhs, d( part_offset+1 ),
1057 $ e( part_offset+1 ), b( part_offset+1 ), lldb,
1068 IF( ictxt_save.NE.ictxt_new )
THEN
1069 CALL blacs_gridexit( ictxt_new )
1081 work( 1 ) = work_size_min