1 SUBROUTINE pdgbdcmv( LDBW, BWL, BWU, TRANS, N, A, JA, DESCA, NRHS,
2 $ B, IB, DESCB, X, WORK, LWORK, INFO )
13 INTEGER BWL, BWU, IB, INFO, JA, LDBW, LWORK, N, NRHS
16 INTEGER DESCA( * ), DESCB( * )
17 DOUBLE PRECISION A( * ), B( * ), WORK( * ), X( * )
323 DOUBLE PRECISION ONE, ZERO
324 parameter( one = 1.0d+0 )
325 parameter( zero = 0.0d+0 )
327 parameter( int_one = 1 )
328 INTEGER DESCMULT, BIGNUM
329 parameter(descmult = 100, bignum = descmult * descmult)
330 INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
331 $ lld_, mb_, m_, nb_, n_, rsrc_
332 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
333 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
334 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
337 INTEGER CSRC, DL_N_M, DL_N_N, DL_P_M, DL_P_N, DU_N_M,
338 $ du_n_n, du_p_m, du_p_n, first_proc, i, ictxt,
339 $ ictxt_new, ictxt_save, idum2, idum3, j, ja_new,
340 $ llda, lldb, max_bw, mycol, myrow, my_num_cols,
341 $ nb, np, npcol, nprow, np_save, odd_size, ofst,
342 $ part_offset, part_size, store_m_b, store_n_a
346 INTEGER PARAM_CHECK( 17, 3 )
354 EXTERNAL lsame, numroc
357 INTRINSIC ichar,
min, mod
365 ictxt = desca( ctxt_ )
366 csrc = desca( csrc_ )
369 store_n_a = desca( n_ )
371 store_m_b = descb( m_ )
376 max_bw =
max(bwl,bwu)
378 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
383 IF( lsame( trans,
'N' ) )
THEN
385 ELSE IF ( lsame( trans,
'T' ) )
THEN
387 ELSE IF ( lsame( trans,
'C' ) )
THEN
393 IF( lwork .LT. -1)
THEN
395 ELSE IF ( lwork .EQ. -1 )
THEN
405 IF( n+ja-1 .GT. store_n_a )
THEN
406 info = -( 8*100 + 6 )
409 IF(( bwl .GT. n-1 ) .OR.
410 $ ( bwl .LT. 0 ) )
THEN
414 IF(( bwu .GT. n-1 ) .OR.
415 $ ( bwu .LT. 0 ) )
THEN
419 IF( llda .LT. (bwl+bwu+1) )
THEN
420 info = -( 8*100 + 6 )
424 info = -( 8*100 + 4 )
429 IF( nprow .NE. 1 )
THEN
433 IF( n .GT. np*nb-mod( ja-1, nb ))
THEN
436 $
'PDDBDCMV, D&C alg.: only 1 block per proc',
441 IF((ja+n-1.GT.nb) .AND. ( nb.LT.2*
max(bwl,bwu) ))
THEN
444 $
'PDDBDCMV, D&C alg.: NB too small',
452 param_check( 17, 1 ) = descb(5)
453 param_check( 16, 1 ) = descb(4)
454 param_check( 15, 1 ) = descb(3)
455 param_check( 14, 1 ) = descb(2)
456 param_check( 13, 1 ) = descb(1)
457 param_check( 12, 1 ) = ib
458 param_check( 11, 1 ) = desca(5)
459 param_check( 10, 1 ) = desca(4)
460 param_check( 9, 1 ) = desca(3)
461 param_check( 8, 1 ) = desca(1)
462 param_check( 7, 1 ) = ja
463 param_check( 6, 1 ) = nrhs
464 param_check( 5, 1 ) = bwu
465 param_check( 4, 1 ) = bwl
466 param_check( 3, 1 ) = n
467 param_check( 2, 1 ) = idum3
468 param_check( 1, 1 ) = idum2
470 param_check( 17, 2 ) = 1105
471 param_check( 16, 2 ) = 1104
472 param_check( 15, 2 ) = 1103
473 param_check( 14, 2 ) = 1102
474 param_check( 13, 2 ) = 1101
475 param_check( 12, 2 ) = 10
476 param_check( 11, 2 ) = 805
477 param_check( 10, 2 ) = 804
478 param_check( 9, 2 ) = 803
479 param_check( 8, 2 ) = 801
480 param_check( 7, 2 ) = 7
481 param_check( 6, 2 ) = 5
482 param_check( 5, 2 ) = 4
483 param_check( 4, 2 ) = 3
484 param_check( 3, 2 ) = 2
485 param_check( 2, 2 ) = 15
486 param_check( 1, 2 ) = 1
494 ELSE IF( info.LT.-descmult )
THEN
497 info = -info * descmult
502 CALL globchk( ictxt, 17, param_check, 17,
503 $ param_check( 1, 3 ), info )
508 IF( info.EQ.bignum )
THEN
510 ELSE IF( mod( info, descmult ) .EQ. 0 )
THEN
511 info = -info / descmult
517 CALL pxerbla( ictxt,
'PDDBDCMV', -info )
530 part_offset = nb*( (ja-1)/(npcol*nb) )
532 IF ( (mycol-csrc) .LT. (ja-part_offset-1)/nb )
THEN
533 part_offset = part_offset + nb
536 IF ( mycol .LT. csrc )
THEN
537 part_offset = part_offset - nb
546 first_proc = mod( ( ja-1 )/nb+csrc, npcol )
550 ja_new = mod( ja-1, nb ) + 1
555 np = ( ja_new+n-2 )/nb + 1
559 CALL reshape( ictxt, int_one, ictxt_new, int_one,
560 $ first_proc, int_one, np )
569 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
573 IF( myrow .LT. 0 )
THEN
586 my_num_cols = numroc( n, part_size, mycol, 0, npcol )
590 IF ( mycol .EQ. 0 )
THEN
591 part_offset = part_offset+mod( ja_new-1, part_size )
592 my_num_cols = my_num_cols - mod(ja_new-1, part_size )
597 ofst = part_offset*llda
601 odd_size = my_num_cols
602 IF ( mycol .LT. np-1 )
THEN
603 odd_size = odd_size - max_bw
611 $ numroc( n, part_size, mycol, 0, npcol)
614 DO 4502 i=1,numroc_size
615 x( (j-1)*lldb + i ) = zero
619 DO 5642 i=1, (max_bw+2)*max_bw
628 IF ( lsame( trans,
'N' ) )
THEN
632 IF( mycol .GT. 0 )
THEN
635 $ numroc( n, part_size, mycol, 0, npcol ) )
637 $ numroc( n, part_size, mycol-1, 0, npcol ) )
640 $ numroc( n, part_size, mycol-1, 0, npcol ) )
642 $ numroc( n, part_size, mycol, 0, npcol ) )
645 IF( mycol .LT. npcol-1 )
THEN
648 $ numroc( n, part_size, mycol+1, 0, npcol ) )
650 $ numroc( n, part_size, mycol, 0, npcol ) )
653 $ numroc( n, part_size, mycol, 0, npcol ) )
655 $ numroc( n, part_size, mycol+1, 0, npcol ) )
661 CALL dgbmv( trans, numroc_size, numroc_size, bwl, bwu, one,
662 $ a( ofst+1 ), llda, b(part_offset+1), 1, zero,
663 $ x( part_offset+1 ), 1 )
667 IF ( mycol .LT. npcol-1 )
THEN
672 $ b( numroc_size-dl_n_n+1 ),
673 $ 1, work( max_bw*max_bw+1+bwl-dl_n_n ), 1 )
675 CALL dtrmv(
'U',
'N',
'N', bwl,
676 $ a( llda*( numroc_size-bwl )+1+bwu+bwl ), llda-1,
677 $ work( max_bw*max_bw+1 ), 1)
681 IF( dl_n_m .GT. dl_n_n )
THEN
682 DO 10 i = dl_n_m-dl_n_n, dl_n_m
683 work( max_bw*max_bw+i ) = 0
689 CALL dgesd2d( ictxt, bwl, 1,
690 $ work( max_bw*max_bw+1 ), bwl, myrow, mycol+1 )
694 IF ( mycol .GT. 0 )
THEN
696 DO 20 i=1, max_bw*( max_bw+2 )
704 CALL dcopy( du_p_n, b( 1 ), 1,
705 $ work( max_bw*max_bw+1 ), 1)
712 $ work( max_bw*max_bw+1 ), 1 )
716 IF( du_p_n .GT. du_p_m )
THEN
717 DO 30 i=1, du_p_n-du_p_m
718 work( max_bw*max_bw+i ) = 0
724 CALL dgesd2d( ictxt, bwu, 1, work(max_bw*max_bw+1 ),
725 $ bwu, myrow, mycol-1 )
729 CALL dgerv2d( ictxt, bwl, 1, work( max_bw*max_bw+1 ),
730 $ bwl, myrow, mycol-1 )
734 CALL daxpy( bwl, one,
735 $ work( max_bw*max_bw+1 ), 1,
742 IF( mycol .LT. npcol-1 )
THEN
746 CALL dgerv2d( ictxt, bwu, 1, work( max_bw*max_bw+1 ),
747 $ bwu, myrow, mycol+1 )
751 CALL daxpy( bwu, one,
752 $ work( max_bw*max_bw+1 ), 1,
753 $ x( numroc_size-bwu+1 ), 1)
764 IF ( lsame( trans,
'T' ) )
THEN
768 IF( mycol .GT. 0 )
THEN
771 $ numroc( n, part_size, mycol, 0, npcol ) )
773 $ numroc( n, part_size, mycol-1, 0, npcol ) )
776 $ numroc( n, part_size, mycol-1, 0, npcol ) )
778 $ numroc( n, part_size, mycol, 0, npcol ) )
781 IF( mycol .LT. npcol-1 )
THEN
784 $ numroc( n, part_size, mycol+1, 0, npcol ) )
786 $ numroc( n, part_size, mycol, 0, npcol ) )
789 $ numroc( n, part_size, mycol, 0, npcol ) )
791 $ numroc( n, part_size, mycol+1, 0, npcol ) )
795 IF( mycol .GT. 0 )
THEN
800 CALL dlatcpy(
'L', bwu, bwu, a( ofst+1 ),
801 $ llda-1, work( 1 ), max_bw )
805 CALL dtrsd2d(ictxt,
'U',
'N',
808 $ max_bw, myrow, mycol-1 )
812 IF( mycol .LT. npcol-1 )
THEN
818 $ a( llda*( numroc_size-bwl )+1+bwu+bwl ),
819 $ llda-1, work( 1 ), max_bw )
823 CALL dtrsd2d(ictxt,
'L',
'N',
826 $ max_bw, myrow, mycol+1 )
832 CALL dgbmv( trans, numroc_size, numroc_size, bwl, bwu, one,
833 $ a( ofst+1 ), llda, b(part_offset+1), 1, zero,
834 $ x( part_offset+1 ), 1 )
838 IF ( mycol .LT. npcol-1 )
THEN
843 $ b( numroc_size-dl_n_n+1 ),
844 $ 1, work( max_bw*max_bw+1+bwu-dl_n_n ), 1 )
848 CALL dtrrv2d(ictxt,
'U',
'N',
850 $ work( 1 ), max_bw, myrow, mycol+1 )
852 CALL dtrmv(
'U',
'N',
'N', bwu,
854 $ work( max_bw*max_bw+1 ), 1)
858 IF( dl_n_m .GT. dl_n_n )
THEN
859 DO 40 i = dl_n_m-dl_n_n, dl_n_m
860 work( max_bw*max_bw+i ) = 0
866 CALL dgesd2d( ictxt, bwu, 1,
867 $ work( max_bw*max_bw+1 ), bwu, myrow, mycol+1 )
871 IF ( mycol .GT. 0 )
THEN
873 DO 50 i=1, max_bw*( max_bw+2 )
881 CALL dcopy( du_p_n, b( 1 ), 1,
882 $ work( max_bw*max_bw+1 ), 1)
886 CALL dtrrv2d(ictxt,
'L',
'N',
888 $ work( 1 ), max_bw, myrow, mycol-1 )
895 $ work( max_bw*max_bw+1 ), 1 )
899 IF( du_p_n .GT. du_p_m )
THEN
900 DO 60 i=1, du_p_n-du_p_m
901 work( max_bw*max_bw+i ) = 0
907 CALL dgesd2d( ictxt, bwl, 1, work(max_bw*max_bw+1 ),
908 $ bwl, myrow, mycol-1 )
912 CALL dgerv2d( ictxt, bwu, 1, work( max_bw*max_bw+1 ),
913 $ bwu, myrow, mycol-1 )
917 CALL daxpy( bwu, one,
918 $ work( max_bw*max_bw+1 ), 1,
925 IF( mycol .LT. npcol-1 )
THEN
929 CALL dgerv2d( ictxt, bwl, 1, work( max_bw*max_bw+1 ),
930 $ bwl, myrow, mycol+1 )
934 CALL daxpy( bwl, one,
935 $ work( max_bw*max_bw+1 ), 1,
936 $ x( numroc_size-bwl+1 ), 1)
948 IF( ictxt_save .NE. ictxt_new )
THEN
949 CALL blacs_gridexit( ictxt_new )