6 
    7      IMPLICIT NONE
    8
    9
   10
   11
   12
   13
   14      CHARACTER          JOBZ, RANGE, UPLO
   15 
   16      INTEGER            IA, IL, INFO, IU, IZ, JA, JZ, LIWORK, LRWORK,
   17     $                   LWORK, M, N, NZ
   18      DOUBLE PRECISION VL, VU
   19
   20
   21      INTEGER            DESCA( * ), DESCZ( * ), IWORK( * )
   22      DOUBLE PRECISION   W( * ), RWORK( * )
   23      COMPLEX*16         A( * ), WORK( * ), Z( * )
   24
   25
   26
   27
   28
   29
   30
   31
   32
   33
   34
   35
   36
   37
   38
   39
   40
   41
   42
   43
   44
   45
   46
   47
   48
   49
   50
   51
   52
   53
   54
   55
   56
   57
   58
   59
   60
   61
   62
   63
   64
   65
   66
   67
   68
   69
   70
   71
   72
   73
   74
   75
   76
   77
   78
   79
   80
   81
   82
   83
   84
   85
   86
   87
   88
   89
   90
   91
   92
   93
   94
   95
   96
   97
   98
   99
  100
  101
  102
  103
  104
  105
  106
  107
  108
  109
  110
  111
  112
  113
  114
  115
  116
  117
  118
  119
  120
  121
  122
  123
  124
  125
  126
  127
  128
  129
  130
  131
  132
  133
  134
  135
  136
  137
  138
  139
  140
  141
  142
  143
  144
  145
  146
  147
  148
  149
  150
  151
  152
  153
  154
  155
  156
  157
  158
  159
  160
  161
  162
  163
  164
  165
  166
  167
  168
  169
  170
  171
  172
  173
  174
  175
  176
  177
  178
  179
  180
  181
  182
  183
  184
  185
  186
  187
  188
  189
  190
  191
  192
  193
  194
  195
  196
  197
  198
  199
  200
  201
  202
  203
  204
  205
  206
  207
  208
  209
  210
  211
  212
  213
  214
  215
  216
  217
  218
  219
  220
  221
  222
  223
  224
  225
  226
  227
  228
  229
  230
  231
  232
  233
  234
  235
  236
  237
  238
  239
  240
  241
  242
  243
  244
  245
  246
  247
  248
  249
  250
  251
  252
  253
  254
  255
  256
  257
  258
  259
  260
  261
  262
  263
  264
  265
  266
  267
  268
  269
  270
  271
  272
  273
  274
  275
  276
  277
  278
  279
  280
  281
  282
  283
  284
  285
  286
  287
  288
  289
  290
  291
  292
  293
  294
  295
  296
  297
  298
  299
  300
  301
  302
  303
  304
  305
  306
  307
  308
  309
  310
  311
  312
  313
  314
  315
  316
  317
  318
  319
  320
  321      INTEGER            CTXT_, M_, N_,
  322     $                   MB_, NB_, RSRC_, CSRC_
  323      parameter( ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
  324     $                   rsrc_ = 7, csrc_ = 8 )
  325      DOUBLE PRECISION   ZERO
  326      parameter( zero = 0.0d0 )
  327
  328
  329      LOGICAL            ALLEIG, COLBRT, DOBCST, FINISH, FIRST, INDEIG,
  330     $                   LOWER, LQUERY, VALEIG, VSTART, WANTZ
  331      INTEGER            ANB, DOL, DOU, DSTCOL, DSTROW, EIGCNT, FRSTCL,
  332     $                   I, IAROW, ICTXT, IIL, IINDERR, IINDWLC, IINFO,
  333     $                   IIU, IM, INDD, INDD2, INDE, INDE2, INDERR,
  334     $                   INDILU, INDRTAU, INDRW, INDRWORK, INDTAU,
  335     $                   INDWLC, INDWORK, IPIL, IPIU, IPROC, IZROW,
  336     $                   LASTCL, LENGTHI, LENGTHI2, LIWMIN, LLRWORK,
  337     $                   LLWORK, LRWMIN, LRWOPT, LWMIN, LWOPT, MAXCLS,
  338     $                   MQ00, MYCOL, MYIL, MYIU, MYPROC, MYROW, MZ, NB,
  339     $                   NDEPTH, NEEDIL, NEEDIU, NHETRD_LWOPT, NNP,
  340     $                   NP00, NPCOL, NPROCS, NPROW, NPS, NSPLIT,
  341     $                   OFFSET, PARITY, RLENGTHI, RLENGTHI2, RSTARTI,
  342     $                   SIZE1, SIZE2, SQNPC, SRCCOL, SRCROW, STARTI,
  343     $                   ZOFFSET
  344 
  345      DOUBLE PRECISION            PIVMIN, SAFMIN, SCALE, VLL, VUU, WL,
  346     $                            WU
  347
  348
  349      INTEGER            IDUM1( 4 ), IDUM2( 4 )
  350
  351
  352      LOGICAL            LSAME
  353      INTEGER            ICEIL, INDXG2P, NUMROC, PJLAENV
  354      DOUBLE PRECISION   PDLAMCH
  357
  358
  359      EXTERNAL            blacs_gridinfo, 
chk1mat, dcopy, dgebr2d,
 
  360     $                    dgebs2d, dgerv2d, dgesd2d, dlarrc, 
dlasrt2,
 
  362     $                    igebs2d, igerv2d, igesd2d, igsum2d, 
pchk1mat,
 
  365
  366
  367      INTRINSIC           abs, dble, dcmplx, ichar, int, 
max, 
min, mod,
 
  368     $                    sqrt
  369
  370
  371
  372 
  373      info = 0
  374 
  375
  376
  377
  378
  379
  380      wantz = 
lsame( jobz, 
'V' )
 
  381      lower = 
lsame( uplo, 
'L' )
 
  382      alleig = 
lsame( range, 
'A' )
 
  383      valeig = 
lsame( range, 
'V' )
 
  384      indeig = 
lsame( range, 
'I' )
 
  385      lquery = ( lwork.EQ.-1 .OR. lrwork.EQ.-1 .OR. liwork.EQ.-1 )
  386 
  387
  388
  389
  390
  391
  392      ictxt = desca( ctxt_ )
  393      safmin = 
pdlamch( ictxt, 
'Safe minimum' )
 
  394 
  395
  396
  397
  398
  399
  400      indtau = 1
  401      indwork = indtau + n
  402      llwork = lwork - indwork + 1
  403 
  404
  405
  406
  407
  408
  409      indrtau = 1
  410      indd = indrtau + n
  411      inde = indd + n + 1
  412      indd2 = inde + n + 1
  413      inde2 = indd2 + n
  414      indrwork = inde2 + n
  415      llrwork = lrwork - indrwork + 1
  416 
  417
  418
  419
  420
  421
  422      CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
  423 
  424 
  425      nprocs = nprow * npcol
  426      myproc = myrow * npcol + mycol
  427      IF( nprow.EQ.-1 ) THEN
  428         info = -( 800+ctxt_ )
  429      ELSE IF( wantz ) THEN
  430         IF( ictxt.NE.descz( ctxt_ ) ) THEN
  431            info = -( 2100+ctxt_ )
  432         END IF
  433      END IF
  434 
  435
  436
  437
  438
  439
  440      IF ( alleig ) THEN
  441         mz = n
  442      ELSE IF ( indeig ) THEN
  443         mz = iu - il + 1
  444      ELSE
  445
  446         mz = n
  447      END IF
  448
  449      nb =  desca( nb_ )
  450      np00 = 
numroc( n, nb, 0, 0, nprow )
 
  451      mq00 = 
numroc( mz, nb, 0, 0, npcol )            
 
  452      IF ( wantz ) THEN
  453         indrw = indrwork + 
max(18*n, np00*mq00 + 2*nb*nb)
 
  454         lrwmin = indrw - 1 + (
iceil(mz, nprocs) + 2)*n
 
  455         lwmin = n + 
max((np00 + mq00 + nb) * nb, 3 * nb)
 
  456      ELSE
  457         indrw = indrwork + 12*n
  458         lrwmin = indrw - 1
  459         lwmin = n + 
max( nb*( np00 + 1 ), 3 * nb ) 
 
  460      END IF
  461 
  462
  463      lrwmin = 
max(3, lrwmin)
 
  464      lrwopt = lrwmin
  465      lwmin = 
max(3, lwmin)
 
  466      lwopt = lwmin
  467
  468      anb = 
pjlaenv( ictxt, 3, 
'PZHETTRD', 
'L', 0, 0, 0, 0 )
 
  469      sqnpc = int( sqrt( dble( nprocs ) ) )
  470      nps = 
max( 
numroc( n, 1, 0, 0, sqnpc ), 2*anb )
 
  471      nhetrd_lwopt = 2*( anb+1 )*( 4*nps+2 ) + ( nps+4 )*nps
  472      lwopt = 
max( lwopt, n+nhetrd_lwopt )
 
  473
  474      size1 = indrw - indrwork
  475 
  476
  477
  478
  479
  480
  481      nnp = 
max( n, nprocs+1, 4 )
 
  482      IF ( wantz ) THEN
  483        liwmin = 12*nnp + 2*n 
  484      ELSE
  485        liwmin = 10*nnp + 2*n
  486      END IF
  487 
  488
  489
  490
  491
  492
  493
  494      indilu = liwmin - 2*nprocs + 1            
  495      size2 = indilu - 2*n 
  496        
  497 
  498
  499
  500
  501
  502
  503      IF( info.EQ.0 ) THEN
  504         CALL chk1mat( n, 4, n, 4, ia, ja, desca, 8, info )
 
  505         IF( wantz )
  506     $      
CALL chk1mat( n, 4, n, 4, iz, jz, descz, 21, info )
 
  507
  508         IF( info.EQ.0 ) THEN
  509            IF( .NOT.( wantz .OR. 
lsame( jobz, 
'N' ) ) ) 
THEN 
  510               info = -1
  511            ELSE IF( .NOT.( alleig .OR. valeig .OR. indeig ) ) THEN
  512               info = -2
  513            ELSE IF( .NOT.( lower .OR. 
lsame( uplo, 
'U' ) ) ) 
THEN 
  514               info = -3
  515            ELSE IF( mod( ia-1, desca( mb_ ) ).NE.0 ) THEN
  516               info = -6
  517            ELSE IF( valeig .AND. n.GT.0 .AND. vu.LE.vl ) THEN
  518               info = -10
  519            ELSE IF( indeig .AND. ( il.LT.1 .OR. il.GT.
max( 1, n ) ) )
 
  520     $                THEN
  521               info = -11
  522            ELSE IF( indeig .AND. ( iu.LT.
min( n, il ) .OR. iu.GT.n ))
 
  523     $                THEN
  524               info = -12
  525            ELSE IF( lwork.LT.lwmin .AND. .NOT.lquery ) THEN
  526               info = -21
  527            ELSE IF( lrwork.LT.lrwmin .AND. .NOT.lquery ) THEN
  528               info = -23
  529            ELSE IF( liwork.LT.liwmin .AND. .NOT.lquery ) THEN
  530               info = -25
  531            ELSE IF( desca( mb_ ).NE.desca( nb_ ) ) THEN
  532               info = -( 800+nb_ )
  533            END IF
  534            IF( wantz ) THEN
  535               iarow = 
indxg2p( 1, desca( nb_ ), myrow, 
 
  536     $                       desca( rsrc_ ), nprow )
  537               izrow = 
indxg2p( 1, desca( nb_ ), myrow, 
 
  538     $                          descz( rsrc_ ), nprow )
  539               IF( iarow.NE.izrow ) THEN
  540                  info = -19
  541               ELSE IF( mod( ia-1, desca( mb_ ) ).NE.
  542     $             mod( iz-1, descz( mb_ ) ) ) THEN
  543                  info = -19
  544               ELSE IF( desca( m_ ).NE.descz( m_ ) ) THEN
  545                  info = -( 2100+m_ )
  546               ELSE IF( desca( n_ ).NE.descz( n_ ) ) THEN
  547                  info = -( 2100+n_ )
  548               ELSE IF( desca( mb_ ).NE.descz( mb_ ) ) THEN
  549                  info = -( 2100+mb_ )
  550               ELSE IF( desca( nb_ ).NE.descz( nb_ ) ) THEN
  551                  info = -( 2100+nb_ )
  552               ELSE IF( desca( rsrc_ ).NE.descz( rsrc_ ) ) THEN
  553                  info = -( 2100+rsrc_ )
  554               ELSE IF( desca( csrc_ ).NE.descz( csrc_ ) ) THEN
  555                  info = -( 2100+csrc_ )
  556               ELSE IF( ictxt.NE.descz( ctxt_ ) ) THEN
  557                  info = -( 2100+ctxt_ )
  558               END IF
  559            END IF
  560         END IF
  561         idum2( 1 ) = 1
  562         IF( lower ) THEN
  563            idum1( 2 ) = ichar( 'L' )
  564         ELSE
  565            idum1( 2 ) = ichar( 'U' )
  566         END IF
  567         idum2( 2 ) = 2
  568         IF( alleig ) THEN
  569            idum1( 3 ) = ichar( 'A' )
  570         ELSE IF( indeig ) THEN
  571            idum1( 3 ) = ichar( 'I' )
  572         ELSE
  573            idum1( 3 ) = ichar( 'V' )
  574         END IF
  575         idum2( 3 ) = 3
  576         IF( lquery ) THEN
  577            idum1( 4 ) = -1
  578         ELSE
  579            idum1( 4 ) = 1
  580         END IF
  581         idum2( 4 ) = 4
  582         IF( wantz ) THEN
  583            idum1( 1 ) = ichar( 'V' )
  584            CALL pchk2mat( n, 4, n, 4, ia, ja, desca, 8, n, 4, n, 4,iz,
 
  585     $                     jz, descz, 21, 4, idum1, idum2, info )
  586         ELSE
  587            idum1( 1 ) = ichar( 'N' )
  588            CALL pchk1mat( n, 4, n, 4, ia, ja, desca, 8, 4, idum1,
 
  589     $                     idum2, info )
  590         END IF
  591         work( 1 ) = dcmplx( lwopt )
  592         rwork( 1 ) = dble( lrwopt )
  593         iwork( 1 ) = liwmin
  594      END IF
  595
  596      IF( info.NE.0 ) THEN
  597         CALL pxerbla( ictxt, 
'PZHEEVR', -info )
 
  598         RETURN
  599      ELSE IF( lquery ) THEN
  600         RETURN
  601      END IF
  602 
  603
  604
  605
  606
  607
  608      IF( n.EQ.0 ) THEN
  609         IF( wantz ) THEN
  610            nz = 0
  611         END IF
  612         m = 0
  613         work( 1 ) = dcmplx( lwopt )
  614         rwork( 1 ) = dble( lrwopt )
  615         iwork( 1 ) = liwmin
  616         RETURN
  617      END IF
  618 
  619      IF( valeig ) THEN
  620         vll = vl
  621         vuu = vu
  622      ELSE
  623         vll = zero
  624         vuu = zero
  625      END IF
  626
  627
  628
  629
  630
  631
  632
  633
  634
  635 
  636 
  637      CALL pzhentrd( uplo, n, a, ia, ja, desca, rwork( indd ),
 
  638     $               rwork( inde ), work( indtau ), work( indwork ),
  639     $               llwork, rwork( indrwork ), llrwork,iinfo )
  640 
  641 
  642      IF (iinfo .NE. 0) THEN
  643         CALL pxerbla( ictxt, 
'PZHENTRD', -iinfo )
 
  644         RETURN
  645      END IF
  646 
  647
  648
  649
  650
  651
  652      offset = 0
  653      IF( ia.EQ.1 .AND. ja.EQ.1 .AND. 
  654     $    desca( rsrc_ ).EQ.0 .AND. desca( csrc_ ).EQ.0 )
  655     $   THEN
  656         CALL pdlared1d( n, ia, ja, desca, rwork( indd ), 
 
  657     $                   rwork( indd2 ), rwork( indrwork ), llrwork )
  658
  659         CALL pdlared1d( n, ia, ja, desca, rwork( inde ), 
 
  660     $                   rwork( inde2 ), rwork( indrwork ), llrwork )
  661         IF( .NOT.lower )
  662     $      offset = 1
  663      ELSE
  664         DO 10 i = 1, n
  665            CALL pzelget( 
'A', 
' ', work( indwork ), a, 
 
  666     $                    i+ia-1, i+ja-1, desca )
  667            rwork( indd2+i-1 ) = dble( work( indwork ) )
  668   10    CONTINUE
  669         IF( 
lsame( uplo, 
'U' ) ) 
THEN 
  670            DO 20 i = 1, n - 1
  671               CALL pzelget( 
'A', 
' ', work( indwork ), a, 
 
  672     $                       i+ia-1, i+ja, desca )
  673               rwork( inde2+i-1 ) = dble( work( indwork ) )
  674   20       CONTINUE
  675         ELSE
  676            DO 30 i = 1, n - 1
  677               CALL pzelget( 
'A', 
' ', work( indwork ), a,
 
  678     $                       i+ia, i+ja-1, desca )
  679               rwork( inde2+i-1 ) = dble( work( indwork ) )
  680   30       CONTINUE
  681         END IF
  682      END IF
  683 
  684 
  685 
  686 
  687
  688
  689
  690
  691
  692      IF ( alleig ) THEN 
  693         iil = 1
  694         iiu = n
  695      ELSE IF ( indeig ) THEN
  696         iil = il
  697         iiu = iu
  698      ELSE IF ( valeig ) THEN
  699         CALL dlarrc('T', n, vll, vuu, rwork( indd2 ), 
  700     $    rwork( inde2 + offset ), safmin, eigcnt, iil, iiu, info)
  701
  702         mz = eigcnt
  703         iil = iil + 1
  704      ENDIF
  705 
  706      IF(mz.EQ.0) THEN
  707         m = 0
  708         IF( wantz ) THEN
  709            nz = 0
  710         END IF
  711         work( 1 ) = dble( lwopt )
  712         iwork( 1 ) = liwmin
  713         RETURN
  714      END IF
  715 
  716      myil = 0
  717      myiu = 0
  718      m = 0
  719      im = 0
  720 
  721
  722
  723
  724
  725
  726 
  727
  728
  729
  730      CALL pmpim2( iil, iiu, nprocs,
 
  731     $             iwork(indilu), iwork(indilu+nprocs) )
  732
  733
  734
  735      myil = iwork(indilu+myproc)
  736      myiu = iwork(indilu+nprocs+myproc)
  737 
  738 
  739      zoffset = 
max(0, myil - iil - 1)
 
  740      first = ( myil .EQ. iil )
  741 
  742 
  743
  744
  745
  746
  747
  748      IF(.NOT.wantz) THEN
  749
  750
  751
  752         iinfo = 0
  753         IF ( myil.GT.0 ) THEN
  754            dol = 1
  755            dou = myiu - myil + 1
  756            CALL dstegr2( jobz, 
'I', n,  rwork( indd2 ),
 
  757     $                  rwork( inde2+offset ), vll, vuu, myil, myiu,
  758     $                  im, w( 1 ), rwork( indrw ), n, 
  759     $                  myiu - myil + 1,
  760     $                  iwork( 1 ), rwork( indrwork ), size1, 
  761     $                  iwork( 2*n+1 ), size2, 
  762     $                  dol, dou, zoffset, iinfo )
  763
  764
  765
  766            DO 49 i = 1, im
  767              w( myil-iil+i ) = w( i )
  768 49         CONTINUE
  769
  770
  771         END IF
  772         IF (iinfo .NE. 0) THEN
  773            CALL pxerbla( ictxt, 
'DSTEGR2', -iinfo )
 
  774            RETURN
  775         END IF
  776      ELSEIF ( wantz .AND. nprocs.EQ.1 ) THEN
  777
  778
  779
  780         iinfo = 0
  781         IF ( myil.GT.0 ) THEN
  782            dol = myil - iil + 1
  783            dou = myiu - iil + 1
  784            CALL dstegr2( jobz, 
'I', n,  rwork( indd2 ),
 
  785     $                  rwork( inde2+offset ), vll, vuu, iil, iiu,
  786     $                  im, w( 1 ), rwork( indrw ), n, 
  787     $                  n,
  788     $                  iwork( 1 ), rwork( indrwork ), size1, 
  789     $                  iwork( 2*n+1 ), size2, dol, dou,
  790     $                  zoffset, iinfo )
  791         ENDIF
  792         IF (iinfo .NE. 0) THEN
  793            CALL pxerbla( ictxt, 
'DSTEGR2', -iinfo )
 
  794            RETURN
  795         END IF
  796      ELSEIF ( wantz ) THEN
  797
  798
  799
  800         iinfo = 0
  801
  802         IF ( myil.GT.0 ) THEN
  803            dol = myil - iil + 1
  804            dou = myiu - iil + 1
  805            CALL dstegr2a( jobz, 
'I', n,  rwork( indd2 ),
 
  806     $                  rwork( inde2+offset ), vll, vuu, iil, iiu,
  807     $                  im, w( 1 ), rwork( indrw ), n, 
  808     $                  n, rwork( indrwork ), size1, 
  809     $                  iwork( 2*n+1 ), size2, dol, 
  810     $                  dou, needil, neediu,
  811     $                  inderr, nsplit, pivmin, scale, wl, wu,
  812     $                  iinfo )
  813         ENDIF
  814         IF (iinfo .NE. 0) THEN
  815            CALL pxerbla( ictxt, 
'DSTEGR2A', -iinfo )
 
  816            RETURN
  817         END IF
  818
  819
  820
  821
  822
  823
  824         vstart = .true.
  825         finish = (myil.LE.0)
  826
  827         iinderr = indrwork + inderr - 1
  828 
  829
  830 
  831 
  832
  833
  834
  835
  836
  837
  838
  839
  840
  841 
  842         dobcst = .false.
  843         IF(dobcst) THEN
  844
  845
  846            DO 45 i = 2, nprocs
  847               IF (myproc .EQ. (i - 1)) THEN
  848                  dstrow = 0
  849                  dstcol = 0
  850                  starti = dol
  851                  iwork(1) = starti
  852                  IF(myil.GT.0) THEN
  853                     lengthi = myiu - myil + 1
  854                  ELSE
  855                     lengthi = 0
  856                  ENDIF
  857                  iwork(2) = lengthi
  858                  CALL igesd2d( ictxt, 2, 1, iwork, 2, 
  859     $                    dstrow, dstcol )
  860                  IF (( starti.GE.1 ) .AND. ( lengthi.GE.1 )) THEN
  861                     lengthi2 = 2*lengthi
  862
  863                     CALL dcopy(lengthi,w( starti ),1,
  864     $                          rwork( indd ), 1)                    
  865
  866                     CALL dcopy(lengthi,rwork(iinderr+starti-1),1,
  867     $                          rwork( indd+lengthi ), 1)               
  868
  869                     CALL dgesd2d( ictxt, lengthi2, 
  870     $                    1, rwork( indd ), lengthi2,
  871     $                    dstrow, dstcol )
  872                  END IF
  873               ELSE IF (myproc .EQ. 0) THEN
  874                  srcrow = (i-1) / npcol
  875                  srccol = mod(i-1, npcol)
  876                  CALL igerv2d( ictxt, 2, 1, iwork, 2, 
  877     $                    srcrow, srccol )
  878                  starti = iwork(1)
  879                  lengthi = iwork(2)
  880                  IF (( starti.GE.1 ) .AND. ( lengthi.GE.1 )) THEN
  881                     lengthi2 = 2*lengthi
  882
  883                     CALL dgerv2d( ictxt, lengthi2, 1,
  884     $                 rwork(indd), lengthi2, srcrow, srccol )
  885
  886                     CALL dcopy( lengthi, rwork(indd), 1,
  887     $                          w( starti ), 1)                    
  888
  889                     CALL dcopy(lengthi,rwork(indd+lengthi),1,
  890     $                          rwork( iinderr+starti-1 ), 1)     
  891                  END IF
  892               END IF
  893  45        CONTINUE
  894            lengthi = iiu - iil + 1
  895            lengthi2 = lengthi * 2
  896            IF (myproc .EQ. 0) THEN
  897
  898               CALL dcopy(lengthi,w ,1, rwork( indd ), 1)               
  899               CALL dcopy(lengthi,rwork( iinderr ),1,
  900     $                          rwork( indd+lengthi ), 1)               
  901               CALL dgebs2d( ictxt, 'A', ' ', lengthi2, 1, 
  902     $              rwork(indd), lengthi2 )
  903            ELSE
  904               srcrow = 0
  905               srccol = 0
  906               CALL dgebr2d( ictxt, 'A', ' ', lengthi2, 1,
  907     $             rwork(indd), lengthi2, srcrow, srccol )
  908               CALL dcopy( lengthi, rwork(indd), 1, w, 1)
  909               CALL dcopy(lengthi,rwork(indd+lengthi),1,
  910     $                          rwork( iinderr ), 1)                   
  911            END IF
  912         ELSE
  913
  914 
  915
  916            IF( (nprocs.GT.1).AND.(myil.GT.0) ) THEN
  917               CALL pmpcol( myproc, nprocs, iil, needil, neediu, 
 
  918     $                   iwork(indilu), iwork(indilu+nprocs),
  919     $                   colbrt, frstcl, lastcl )
  920            ELSE
  921               colbrt = .false.
  922            ENDIF
  923 
  924            IF(colbrt) THEN
  925
  926
  927               DO 47 iproc = frstcl, lastcl
  928                  IF (myproc .EQ. iproc) THEN
  929                     starti = dol
  930                     iwork(1) = starti
  931                     lengthi = myiu - myil + 1
  932                     iwork(2) = lengthi
  933                     
  934                     IF ((starti.GE.1) .AND. (lengthi.GE.1)) THEN
  935
  936                        CALL dcopy(lengthi,w( starti ),1,
  937     $                              rwork(indd), 1)                    
  938
  939                        CALL dcopy(lengthi,
  940     $                          rwork( iinderr+starti-1 ),1,
  941     $                          rwork(indd+lengthi), 1)                 
  942                     ENDIF
  943 
  944                     DO 46 i = frstcl, lastcl                      
  945                        IF(i.EQ.myproc) GOTO 46
  946                        dstrow = i/ npcol
  947                        dstcol = mod(i, npcol)
  948                        CALL igesd2d( ictxt, 2, 1, iwork, 2, 
  949     $                             dstrow, dstcol )
  950                        IF ((starti.GE.1) .AND. (lengthi.GE.1)) THEN
  951                           lengthi2 = 2*lengthi
  952
  953                           CALL dgesd2d( ictxt, lengthi2, 
  954     $                          1, rwork(indd), lengthi2,
  955     $                          dstrow, dstcol )
  956                        END IF
  957  46                 CONTINUE
  958                  ELSE
  959                     srcrow = iproc / npcol
  960                     srccol = mod(iproc, npcol)
  961                     CALL igerv2d( ictxt, 2, 1, iwork, 2, 
  962     $                             srcrow, srccol )
  963                     rstarti = iwork(1)
  964                     rlengthi = iwork(2)
  965                     IF ((rstarti.GE.1 ) .AND. (rlengthi.GE.1 )) THEN
  966                        rlengthi2 = 2*rlengthi
  967                        CALL dgerv2d( ictxt, rlengthi2, 1,
  968     $                      rwork(inde), rlengthi2,
  969     $                      srcrow, srccol )
  970
  971                        CALL dcopy( rlengthi,rwork(inde), 1,
  972     $                          w( rstarti ), 1)                    
  973
  974                        CALL dcopy(rlengthi,rwork(inde+rlengthi),1,
  975     $                          rwork( iinderr+rstarti-1 ), 1)          
  976                     END IF
  977                  END IF
  978  47           CONTINUE
  979            ENDIF
  980         ENDIF
  981 
  982
  983
  984
  985
  986
  987
  988 100     CONTINUE
  989         IF ( myil.GT.0 ) THEN
  990            CALL dstegr2b( jobz, n,  rwork( indd2 ),
 
  991     $                  rwork( inde2+offset ), 
  992     $                  im, w( 1 ), rwork( indrw ), n, n,
  993     $                  iwork( 1 ), rwork( indrwork ), size1, 
  994     $                  iwork( 2*n+1 ), size2, dol, 
  995     $                  dou, needil, neediu, indwlc,
  996     $                  pivmin, scale, wl, wu,
  997     $                  vstart, finish, 
  998     $                  maxcls, ndepth, parity, zoffset, iinfo )
  999            iindwlc = indrwork + indwlc - 1
 1000            IF(.NOT.finish) THEN
 1001               IF((needil.LT.dol).OR.(neediu.GT.dou)) THEN
 1002                  CALL pmpcol( myproc, nprocs, iil, needil, neediu,
 
 1003     $                 iwork(indilu), iwork(indilu+nprocs),
 1004     $                   colbrt, frstcl, lastcl )
 1005               ELSE
 1006                  colbrt = .false.
 1007                  frstcl = myproc
 1008                  lastcl = myproc
 1009               ENDIF
 1010
 1011
 1012
 1013
 1014               IF(colbrt) THEN
 1015                  DO 147 iproc = frstcl, lastcl
 1016                     IF (myproc .EQ. iproc) THEN
 1017                        starti = dol
 1018                        iwork(1) = starti
 1019                        IF(myil.GT.0) THEN
 1020                           lengthi = myiu - myil + 1
 1021                        ELSE
 1022                           lengthi = 0
 1023                        ENDIF
 1024                        iwork(2) = lengthi
 1025                        IF ((starti.GE.1).AND.(lengthi.GE.1)) THEN
 1026
 1027                           CALL dcopy(lengthi,
 1028     $                          rwork( iindwlc+starti-1 ),1,
 1029     $                          rwork(indd), 1)                    
 1030
 1031                           CALL dcopy(lengthi,
 1032     $                          rwork( iinderr+starti-1 ),1,
 1033     $                          rwork(indd+lengthi), 1)                 
 1034                        ENDIF
 1035                      
 1036                        DO 146 i = frstcl, lastcl                      
 1037                           IF(i.EQ.myproc) GOTO 146
 1038                           dstrow = i/ npcol
 1039                           dstcol = mod(i, npcol)
 1040                           CALL igesd2d( ictxt, 2, 1, iwork, 2, 
 1041     $                             dstrow, dstcol )
 1042                           IF ((starti.GE.1).AND.(lengthi.GE.1)) THEN
 1043                              lengthi2 = 2*lengthi
 1044
 1045                              CALL dgesd2d( ictxt, lengthi2, 
 1046     $                             1, rwork(indd), lengthi2,
 1047     $                             dstrow, dstcol )
 1048                           END IF
 1049 146                    CONTINUE
 1050                     ELSE
 1051                        srcrow = iproc / npcol
 1052                        srccol = mod(iproc, npcol)
 1053                        CALL igerv2d( ictxt, 2, 1, iwork, 2, 
 1054     $                             srcrow, srccol )
 1055                        rstarti = iwork(1)
 1056                        rlengthi = iwork(2)
 1057                        IF ((rstarti.GE.1).AND.(rlengthi.GE.1)) THEN
 1058                           rlengthi2 = 2*rlengthi
 1059                           CALL dgerv2d( ictxt,rlengthi2, 1,
 1060     $                         rwork(inde),rlengthi2,
 1061     $                         srcrow, srccol )
 1062
 1063                           CALL dcopy(rlengthi,rwork(inde), 1,
 1064     $                          rwork( iindwlc+rstarti-1 ), 1)        
 1065
 1066                           CALL dcopy(rlengthi,rwork(inde+rlengthi),
 1067     $                          1,rwork( iinderr+rstarti-1 ), 1)        
 1068                        END IF
 1069                      END IF
 1070 147              CONTINUE
 1071               ENDIF
 1072               GOTO 100         
 1073            ENDIF
 1074         ENDIF
 1075         IF (iinfo .NE. 0) THEN
 1076            CALL pxerbla( ictxt, 
'DSTEGR2B', -iinfo )
 
 1077            RETURN
 1078         END IF
 1079
 1080      ENDIF
 1081 
 1082
 1083
 1084
 1085
 1086
 1087
 1088
 1089 
 1090
 1091
 1092
 1093
 1094
 1095
 1096 
 1097      DO 50 i = 2, nprocs
 1098         IF (myproc .EQ. (i - 1)) THEN
 1099            dstrow = 0
 1100            dstcol = 0
 1101            starti = myil - iil + 1
 1102            iwork(1) = starti
 1103            IF(myil.GT.0) THEN
 1104               lengthi = myiu - myil + 1
 1105            ELSE
 1106               lengthi = 0
 1107            ENDIF
 1108            iwork(2) = lengthi
 1109            CALL igesd2d( ictxt, 2, 1, iwork, 2, 
 1110     $                    dstrow, dstcol )
 1111            IF ((starti.GE.1).AND.(lengthi.GE.1)) THEN
 1112               CALL dgesd2d( ictxt, lengthi, 
 1113     $              1, w( starti ), lengthi,
 1114     $              dstrow, dstcol )
 1115            ENDIF
 1116         ELSE IF (myproc .EQ. 0) THEN
 1117            srcrow = (i-1) / npcol
 1118            srccol = mod(i-1, npcol)
 1119            CALL igerv2d( ictxt, 2, 1, iwork, 2, 
 1120     $                    srcrow, srccol )
 1121            starti = iwork(1)
 1122            lengthi = iwork(2)
 1123            IF ((starti.GE.1).AND.(lengthi.GE.1)) THEN
 1124               CALL dgerv2d( ictxt, lengthi, 1,
 1125     $                 w( starti ), lengthi, srcrow, srccol )
 1126            ENDIF
 1127         ENDIF
 1128   50 CONTINUE
 1129 
 1130
 1131      m = im
 1132      CALL igsum2d( ictxt, 'A', ' ', 1, 1, m, 1, -1, -1 )
 1133 
 1134
 1135      IF (myproc .EQ. 0) THEN
 1136
 1137         CALL dgebs2d( ictxt, 'A', ' ', m, 1, w, m )
 1138      ELSE
 1139         srcrow = 0
 1140         srccol = 0
 1141         CALL dgebr2d( ictxt, 'A', ' ', m, 1,
 1142     $           w, m, srcrow, srccol )
 1143      END IF
 1144
 1145
 1146
 1147
 1148      DO 160 i = 1, m
 1149         iwork( nprocs+1+i ) = i
 1150  160 CONTINUE
 1151      CALL dlasrt2( 
'I', m, w, iwork( nprocs+2 ), iinfo )
 
 1152      IF (iinfo.NE.0) THEN
 1153         CALL pxerbla( ictxt, 
'DLASRT2', -iinfo )
 
 1154         RETURN
 1155      END IF
 1156 
 1157
 1158
 1159
 1160
 1161
 1162      IF ( wantz ) THEN
 1163         DO 170 i = 1, m
 1164            iwork( m+nprocs+1+iwork( nprocs+1+i ) ) = i
 1165  170    CONTINUE
 1166
 1167         iwork( 1 ) = 0
 1168         DO 180 i = 1, nprocs
 1169
 1170
 1171            ipil = iwork(indilu+i-1)
 1172            ipiu = iwork(indilu+nprocs+i-1)
 1173            IF (ipil .EQ. 0) THEN
 1174               iwork( i + 1 ) = iwork( i )
 1175            ELSE
 1176               iwork( i + 1 ) = iwork( i ) + ipiu - ipil + 1
 1177            ENDIF
 1178  180    CONTINUE
 1179 
 1180         IF ( first ) THEN
 1181            CALL pzlaevswp(n, rwork( indrw ), n, z, iz, jz, 
 
 1182     $       descz, iwork( 1 ), iwork( nprocs+m+2 ), rwork( indrwork ), 
 1183     $       size1 )
 1184         ELSE
 1185            CALL pzlaevswp(n, rwork( indrw + n ), n, z, iz, jz, 
 
 1186     $       descz, iwork( 1 ), iwork( nprocs+m+2 ), rwork( indrwork ),
 1187     $       size1 )
 1188         END IF
 1189
 1190         nz = m
 1191
 1192 
 1193
 1194
 1195
 1196
 1197
 1198         IF( nz.GT.0 ) THEN
 1199           CALL pzunmtr( 
'L', uplo, 
'N', n, nz, a, ia, ja, desca,
 
 1200     $                    work( indtau ), z, iz, jz, descz,
 1201     $                    work( indwork ), llwork, iinfo )
 1202         END IF
 1203         IF (iinfo.NE.0) THEN
 1204            CALL pxerbla( ictxt, 
'PZUNMTR', -iinfo )
 
 1205            RETURN
 1206         END IF
 1207
 1208 
 1209      END IF
 1210
 1211      work( 1 ) = dcmplx( lwopt )
 1212      rwork( 1 ) = dble( lrwopt )
 1213      iwork( 1 ) = liwmin
 1214 
 1215      RETURN
 1216
 1217
 1218
subroutine chk1mat(ma, mapos0, na, napos0, ia, ja, desca, descapos0, info)
 
subroutine dlasrt2(id, n, d, key, info)
 
subroutine dstegr2(jobz, range, n, d, e, vl, vu, il, iu, m, w, z, ldz, nzc, isuppz, work, lwork, iwork, liwork, dol, dou, zoffset, info)
 
subroutine dstegr2a(jobz, range, n, d, e, vl, vu, il, iu, m, w, z, ldz, nzc, work, lwork, iwork, liwork, dol, dou, needil, neediu, inderr, nsplit, pivmin, scale, wl, wu, info)
 
subroutine dstegr2b(jobz, n, d, e, m, w, z, ldz, nzc, isuppz, work, lwork, iwork, liwork, dol, dou, needil, neediu, indwlc, pivmin, scale, wl, wu, vstart, finish, maxcls, ndepth, parity, zoffset, info)
 
integer function iceil(inum, idenom)
 
integer function indxg2p(indxglob, nb, iproc, isrcproc, nprocs)
 
integer function numroc(n, nb, iproc, isrcproc, nprocs)
 
subroutine pchk1mat(ma, mapos0, na, napos0, ia, ja, desca, descapos0, nextra, ex, expos, info)
 
subroutine pchk2mat(ma, mapos0, na, napos0, ia, ja, desca, descapos0, mb, mbpos0, nb, nbpos0, ib, jb, descb, descbpos0, nextra, ex, expos, info)
 
double precision function pdlamch(ictxt, cmach)
 
subroutine pdlared1d(n, ia, ja, desc, bycol, byall, work, lwork)
 
integer function pjlaenv(ictxt, ispec, name, opts, n1, n2, n3, n4)
 
subroutine pmpcol(myproc, nprocs, iil, needil, neediu, pmyils, pmyius, colbrt, frstcl, lastcl)
 
subroutine pmpim2(il, iu, nprocs, pmyils, pmyius)
 
subroutine pxerbla(ictxt, srname, info)
 
subroutine pzelget(scope, top, alpha, a, ia, ja, desca)
 
subroutine pzhentrd(uplo, n, a, ia, ja, desca, d, e, tau, work, lwork, rwork, lrwork, info)
 
subroutine pzlaevswp(n, zin, ldzi, z, iz, jz, descz, nvs, key, rwork, lrwork)
 
subroutine pzunmtr(side, uplo, trans, m, n, a, ia, ja, desca, tau, c, ic, jc, descc, work, lwork, info)