5 
    6      IMPLICIT NONE
    7
    8
    9
   10
   11
   12
   13      CHARACTER          JOBZ, RANGE, UPLO
   14      INTEGER            IA, IL, INFO, IU, IZ, JA, JZ, LIWORK, LWORK, M,
   15     $                   N, NZ
   16      REAL             VL, VU
   17
   18
   19      INTEGER            DESCA( * ), DESCZ( * ), IWORK( * )
   20      REAL               A( * ), W( * ), WORK( * ), Z( * )
   21
   22
   23
   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      INTEGER            CTXT_, M_, N_,
  295     $                   MB_, NB_, RSRC_, CSRC_
  296      parameter( ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
  297     $                   rsrc_ = 7, csrc_ = 8 )
  298      REAL               ZERO
  299      parameter( zero = 0.0e0 )
  300
  301
  302      LOGICAL            ALLEIG, COLBRT, DOBCST, FINISH, FIRST, INDEIG,
  303     $                   LOWER, LQUERY, VALEIG, VSTART, WANTZ
  304      INTEGER            ANB, DOL, DOU, DSTCOL, DSTROW, EIGCNT, FRSTCL,
  305     $                   I, IAROW, ICTXT, IIL, IINDERR, IINDWLC, IINFO,
  306     $                   IIU, IM, INDD, INDD2, INDE, INDE2, INDERR,
  307     $                   INDILU, INDRW, INDTAU, INDWLC, INDWORK, IPIL,
  308     $                   IPIU, IPROC, IZROW, LASTCL, LENGTHI, LENGTHI2,
  309     $                   LIWMIN, LLWORK, LWMIN, LWOPT, MAXCLS, MQ00,
  310     $                   MYCOL, MYIL, MYIU, MYPROC, MYROW, MZ, NB,
  311     $                   NDEPTH, NEEDIL, NEEDIU, NNP, NP00, NPCOL,
  312     $                   NPROCS, NPROW, NPS, NSPLIT, NSYTRD_LWOPT,
  313     $                   OFFSET, PARITY, RLENGTHI, RLENGTHI2, RSTARTI,
  314     $                   SIZE1, SIZE2, SQNPC, SRCCOL, SRCROW, STARTI,
  315     $                   ZOFFSET
  316 
  317      REAL                        PIVMIN, SAFMIN, SCALE, VLL, VUU, WL,
  318     $                            WU
  319
  320
  321      INTEGER            IDUM1( 4 ), IDUM2( 4 )
  322
  323
  324      LOGICAL            LSAME
  325      INTEGER            ICEIL, INDXG2P, NUMROC, PJLAENV
  326      REAL               PSLAMCH
  329
  330
  331      EXTERNAL            blacs_gridinfo, 
chk1mat, igebr2d, igebs2d,
 
  335     $                    sgerv2d, sgesd2d, slarrc, 
slasrt2,
 
  337
  338
  339      INTRINSIC          abs, real, ichar, int, 
max, 
min, mod, sqrt
 
  340
  341
  342
  343 
  344 
  345      info = 0
  346
  347
  348
  349
  350
  351      wantz = 
lsame( jobz, 
'V' )
 
  352      lower = 
lsame( uplo, 
'L' )
 
  353      alleig = 
lsame( range, 
'A' )
 
  354      valeig = 
lsame( range, 
'V' )
 
  355      indeig = 
lsame( range, 
'I' )
 
  356      lquery = ( lwork.EQ.-1 .OR. liwork.EQ.-1 )
  357 
  358
  359
  360
  361
  362
  363      ictxt = desca( ctxt_ )
  364      safmin = 
pslamch( ictxt, 
'Safe minimum' )
 
  365 
  366
  367
  368
  369
  370
  371      indtau = 1
  372      indd = indtau + n
  373      inde = indd + n + 1
  374      indd2 = inde + n + 1
  375      inde2 = indd2 + n
  376      indwork = inde2 + n
  377      llwork = lwork - indwork + 1
  378 
  379
  380
  381
  382
  383
  384      CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
  385 
  386 
  387      nprocs = nprow * npcol
  388      myproc = myrow * npcol + mycol
  389      IF( nprow.EQ.-1 ) THEN
  390         info = -( 800+ctxt_ )
  391      ELSE IF( wantz ) THEN
  392         IF( ictxt.NE.descz( ctxt_ ) ) THEN
  393            info = -( 2100+ctxt_ )
  394         END IF
  395      END IF
  396 
  397
  398
  399
  400
  401
  402      IF ( alleig ) THEN
  403         mz = n
  404      ELSE IF ( indeig ) THEN
  405         mz = iu - il + 1
  406      ELSE
  407
  408         mz = n
  409      END IF
  410
  411      nb =  desca( nb_ )
  412      IF ( wantz ) THEN
  413         np00 = 
numroc( n, nb, 0, 0, nprow )
 
  414         mq00 = 
numroc( mz, nb, 0, 0, npcol )            
 
  415         indrw = indwork + 
max(18*n, np00*mq00 + 2*nb*nb)
 
  416         lwmin = indrw - 1 + (
iceil(mz, nprocs) + 2)*n
 
  417      ELSE
  418         indrw = indwork + 12*n
  419         lwmin = indrw - 1
  420      END IF
  421
  422      lwmin = 
max(3, lwmin)
 
  423      lwopt = lwmin
  424      anb = 
pjlaenv( ictxt, 3, 
'PSSYTTRD', 
'L', 0, 0, 0, 0 )
 
  425      sqnpc = int( sqrt( real( nprocs ) ) )
  426      nps = 
max( 
numroc( n, 1, 0, 0, sqnpc ), 2*anb )
 
  427      nsytrd_lwopt = 2*( anb+1 )*( 4*nps+2 ) + ( nps+4 )*nps
  428      lwopt = 
max( lwopt, 5*n+nsytrd_lwopt )
 
  429
  430      size1 = indrw - indwork
  431 
  432
  433
  434
  435
  436
  437      nnp = 
max( n, nprocs+1, 4 )
 
  438      IF ( wantz ) THEN
  439        liwmin = 12*nnp + 2*n 
  440      ELSE
  441        liwmin = 10*nnp + 2*n
  442      END IF
  443 
  444
  445
  446
  447
  448
  449
  450      indilu = liwmin - 2*nprocs + 1            
  451      size2 = indilu - 2*n 
  452        
  453 
  454
  455
  456
  457
  458
  459      IF( info.EQ.0 ) THEN
  460         CALL chk1mat( n, 4, n, 4, ia, ja, desca, 8, info )
 
  461         IF( wantz )
  462     $      
CALL chk1mat( n, 4, n, 4, iz, jz, descz, 21, info )
 
  463
  464         IF( info.EQ.0 ) THEN
  465            IF( .NOT.( wantz .OR. 
lsame( jobz, 
'N' ) ) ) 
THEN 
  466               info = -1
  467            ELSE IF( .NOT.( alleig .OR. valeig .OR. indeig ) ) THEN
  468               info = -2
  469            ELSE IF( .NOT.( lower .OR. 
lsame( uplo, 
'U' ) ) ) 
THEN 
  470               info = -3
  471            ELSE IF( mod( ia-1, desca( mb_ ) ).NE.0 ) THEN
  472               info = -6
  473            ELSE IF( valeig .AND. n.GT.0 .AND. vu.LE.vl ) THEN
  474               info = -10
  475            ELSE IF( indeig .AND. ( il.LT.1 .OR. il.GT.
max( 1, n ) ) )
 
  476     $                THEN
  477               info = -11
  478            ELSE IF( indeig .AND. ( iu.LT.
min( n, il ) .OR. iu.GT.n ) )
 
  479     $                THEN
  480               info = -12
  481            ELSE IF( lwork.LT.lwmin .AND. .NOT.lquery ) THEN
  482               info = -21
  483            ELSE IF( liwork.LT.liwmin .AND. .NOT.lquery ) THEN
  484               info = -23
  485            ELSE IF( desca( mb_ ).NE.desca( nb_ ) ) THEN
  486               info = -( 800+nb_ )
  487            END IF
  488            IF( wantz ) THEN
  489               iarow = 
indxg2p( 1, desca( nb_ ), myrow, 
 
  490     $                       desca( rsrc_ ), nprow )
  491               izrow = 
indxg2p( 1, desca( nb_ ), myrow, 
 
  492     $                          descz( rsrc_ ), nprow )
  493               IF( iarow.NE.izrow ) THEN
  494                  info = -19
  495               ELSE IF( mod( ia-1, desca( mb_ ) ).NE.
  496     $             mod( iz-1, descz( mb_ ) ) ) THEN
  497                  info = -19
  498               ELSE IF( desca( m_ ).NE.descz( m_ ) ) THEN
  499                  info = -( 2100+m_ )
  500               ELSE IF( desca( n_ ).NE.descz( n_ ) ) THEN
  501                  info = -( 2100+n_ )
  502               ELSE IF( desca( mb_ ).NE.descz( mb_ ) ) THEN
  503                  info = -( 2100+mb_ )
  504               ELSE IF( desca( nb_ ).NE.descz( nb_ ) ) THEN
  505                  info = -( 2100+nb_ )
  506               ELSE IF( desca( rsrc_ ).NE.descz( rsrc_ ) ) THEN
  507                  info = -( 2100+rsrc_ )
  508               ELSE IF( desca( csrc_ ).NE.descz( csrc_ ) ) THEN
  509                  info = -( 2100+csrc_ )
  510               ELSE IF( ictxt.NE.descz( ctxt_ ) ) THEN
  511                  info = -( 2100+ctxt_ )
  512               END IF
  513            END IF
  514         END IF
  515         idum2( 1 ) = 1
  516         IF( lower ) THEN
  517            idum1( 2 ) = ichar( 'L' )
  518         ELSE
  519            idum1( 2 ) = ichar( 'U' )
  520         END IF
  521         idum2( 2 ) = 2
  522         IF( alleig ) THEN
  523            idum1( 3 ) = ichar( 'A' )
  524         ELSE IF( indeig ) THEN
  525            idum1( 3 ) = ichar( 'I' )
  526         ELSE
  527            idum1( 3 ) = ichar( 'V' )
  528         END IF
  529         idum2( 3 ) = 3
  530         IF( lquery ) THEN
  531            idum1( 4 ) = -1
  532         ELSE
  533            idum1( 4 ) = 1
  534         END IF
  535         idum2( 4 ) = 4
  536         IF( wantz ) THEN
  537            idum1( 1 ) = ichar( 'V' )
  538            CALL pchk2mat( n, 4, n, 4, ia, ja, desca, 8, n, 4, n, 4, iz,
 
  539     $                     jz, descz, 21, 4, idum1, idum2, info )
  540         ELSE
  541            idum1( 1 ) = ichar( 'N' )
  542            CALL pchk1mat( n, 4, n, 4, ia, ja, desca, 8, 4, idum1,
 
  543     $                     idum2, info )
  544         END IF
  545         work( 1 ) = real( lwopt )
  546         iwork( 1 ) = liwmin
  547      END IF
  548
  549      IF( info.NE.0 ) THEN
  550         CALL pxerbla( ictxt, 
'PSSYEVR', -info )
 
  551         RETURN
  552      ELSE IF( lquery ) THEN
  553         RETURN
  554      END IF
  555 
  556
  557
  558
  559
  560
  561      IF( n.EQ.0 ) THEN
  562         IF( wantz ) THEN
  563            nz = 0
  564         END IF
  565         m = 0
  566         work( 1 ) = real( lwopt )
  567         iwork( 1 ) = liwmin
  568         RETURN
  569      END IF
  570 
  571      IF( valeig ) THEN
  572         vll = vl
  573         vuu = vu
  574      ELSE
  575         vll = zero
  576         vuu = zero
  577      END IF
  578
  579
  580
  581
  582
  583
  584
  585
  586
  587 
  588 
  589      CALL pssyntrd( uplo, n, a, ia, ja, desca, work( indd ),
 
  590     $               work( inde ), work( indtau ), work( indwork ),
  591     $               llwork, iinfo )
  592 
  593 
  594      IF (iinfo .NE. 0) THEN
  595         CALL pxerbla( ictxt, 
'PSSYNTRD', -iinfo )
 
  596         RETURN
  597      END IF
  598 
  599
  600
  601
  602
  603
  604      offset = 0
  605      IF( ia.EQ.1 .AND. ja.EQ.1 .AND. 
  606     $    desca( rsrc_ ).EQ.0 .AND. desca( csrc_ ).EQ.0 )
  607     $   THEN
  608         CALL pslared1d( n, ia, ja, desca, work( indd ), work( indd2 ),
 
  609     $                   work( indwork ), llwork )
  610
  611         CALL pslared1d( n, ia, ja, desca, work( inde ), work( inde2 ),
 
  612     $                   work( indwork ), llwork )
  613         IF( .NOT.lower )
  614     $      offset = 1
  615      ELSE
  616         DO 10 i = 1, n
  617            CALL pselget( 
'A', 
' ', work( indd2+i-1 ), a, i+ia-1,
 
  618     $                    i+ja-1, desca )
  619   10    CONTINUE
  620         IF( 
lsame( uplo, 
'U' ) ) 
THEN 
  621            DO 20 i = 1, n - 1
  622               CALL pselget( 
'A', 
' ', work( inde2+i-1 ), a, i+ia-1,
 
  623     $                       i+ja, desca )
  624   20       CONTINUE
  625         ELSE
  626            DO 30 i = 1, n - 1
  627               CALL pselget( 
'A', 
' ', work( inde2+i-1 ), a, i+ia,
 
  628     $                       i+ja-1, desca )
  629   30       CONTINUE
  630         END IF
  631      END IF
  632 
  633 
  634 
  635 
  636
  637
  638
  639
  640
  641      IF ( alleig ) THEN 
  642         iil = 1
  643         iiu = n
  644      ELSE IF ( indeig ) THEN
  645         iil = il
  646         iiu = iu
  647      ELSE IF ( valeig ) THEN
  648         CALL slarrc('T', n, vll, vuu, work( indd2 ), 
  649     $    work( inde2 + offset ), safmin, eigcnt, iil, iiu, info)
  650
  651         mz = eigcnt
  652         iil = iil + 1
  653      ENDIF
  654 
  655      IF(mz.EQ.0) THEN
  656         m = 0
  657         IF( wantz ) THEN
  658            nz = 0
  659         END IF
  660         work( 1 ) = real( lwopt )
  661         iwork( 1 ) = liwmin
  662         RETURN
  663      END IF
  664 
  665      myil = 0
  666      myiu = 0
  667      m = 0
  668      im = 0
  669 
  670
  671
  672
  673
  674
  675
  676
  677
  678      CALL pmpim2( iil, iiu, nprocs,
 
  679     $             iwork(indilu), iwork(indilu+nprocs) )
  680
  681
  682
  683      myil = iwork(indilu+myproc)
  684      myiu = iwork(indilu+nprocs+myproc)
  685 
  686 
  687      zoffset = 
max(0, myil - iil - 1) 
 
  688      first = ( myil .EQ. iil )
  689 
  690 
  691
  692
  693
  694
  695
  696      IF(.NOT.wantz) THEN
  697
  698
  699
  700         iinfo = 0
  701         IF ( myil.GT.0 ) THEN
  702            dol = 1
  703            dou = myiu - myil + 1
  704            CALL sstegr2( jobz, 
'I', n,  work( indd2 ),
 
  705     $                  work( inde2+offset ), vll, vuu, myil, myiu,
  706     $                  im, w( 1 ), work( indrw ), n, 
  707     $                  myiu - myil + 1,
  708     $                  iwork( 1 ), work( indwork ), size1, 
  709     $                  iwork( 2*n+1 ), size2, 
  710     $                  dol, dou, zoffset, iinfo )
  711
  712
  713
  714            DO 49 i = 1, im
  715              w( myil-iil+i ) = w( i )
  716 49         CONTINUE
  717
  718
  719         END IF
  720         IF (iinfo .NE. 0) THEN
  721            CALL pxerbla( ictxt, 
'SSTEGR2', -iinfo )
 
  722            RETURN
  723         END IF
  724      ELSEIF ( wantz .AND. nprocs.EQ.1 ) THEN
  725
  726
  727
  728         iinfo = 0
  729         IF ( myil.GT.0 ) THEN
  730            dol = myil - iil + 1
  731            dou = myiu - iil + 1
  732            CALL sstegr2( jobz, 
'I', n,  work( indd2 ),
 
  733     $                  work( inde2+offset ), vll, vuu, iil, iiu,
  734     $                  im, w( 1 ), work( indrw ), n, 
  735     $                  n,
  736     $                  iwork( 1 ), work( indwork ), size1, 
  737     $                  iwork( 2*n+1 ), size2, dol, dou,
  738     $                  zoffset, iinfo )
  739         ENDIF
  740         IF (iinfo .NE. 0) THEN
  741            CALL pxerbla( ictxt, 
'SSTEGR2', -iinfo )
 
  742            RETURN
  743         END IF
  744      ELSEIF ( wantz ) THEN
  745
  746
  747
  748
  749
  750         iinfo = 0
  751
  752         IF ( myil.GT.0 ) THEN
  753            dol = myil - iil + 1
  754            dou = myiu - iil + 1
  755            CALL sstegr2a( jobz, 
'I', n,  work( indd2 ),
 
  756     $                  work( inde2+offset ), vll, vuu, iil, iiu,
  757     $                  im, w( 1 ), work( indrw ), n, 
  758     $                  n, work( indwork ), size1, 
  759     $                  iwork( 2*n+1 ), size2, dol, 
  760     $                  dou, needil, neediu,
  761     $                  inderr, nsplit, pivmin, scale, wl, wu,
  762     $                  iinfo )
  763         ENDIF
  764         IF (iinfo .NE. 0) THEN
  765            CALL pxerbla( ictxt, 
'SSTEGR2A', -iinfo )
 
  766            RETURN
  767         END IF
  768
  769
  770
  771
  772
  773
  774         vstart = .true.
  775         finish = (myil.LE.0)
  776
  777         iinderr = indwork + inderr - 1
  778 
  779
  780
  781
  782
  783
  784
  785
  786
  787
  788
  789
  790         dobcst = .false.
  791         IF(dobcst) THEN
  792
  793
  794            DO 45 i = 2, nprocs
  795               IF (myproc .EQ. (i - 1)) THEN
  796                  dstrow = 0
  797                  dstcol = 0
  798                  starti = dol
  799                  iwork(1) = starti
  800                  IF(myil.GT.0) THEN
  801                     lengthi = myiu - myil + 1
  802                  ELSE
  803                     lengthi = 0
  804                  ENDIF
  805                  iwork(2) = lengthi
  806                  CALL igesd2d( ictxt, 2, 1, iwork, 2, 
  807     $                    dstrow, dstcol )
  808                  IF (( starti.GE.1 ) .AND. ( lengthi.GE.1 )) THEN
  809                     lengthi2 = 2*lengthi
  810
  811                     CALL scopy(lengthi,w( starti ),1,
  812     $                          work( indd ), 1)                    
  813
  814                     CALL scopy(lengthi,work( iinderr+starti-1 ),1,
  815     $                          work( indd+lengthi ), 1)                
  816
  817                     CALL sgesd2d( ictxt, lengthi2, 
  818     $                    1, work( indd ), lengthi2,
  819     $                    dstrow, dstcol )
  820                  END IF
  821               ELSE IF (myproc .EQ. 0) THEN
  822                  srcrow = (i-1) / npcol
  823                  srccol = mod(i-1, npcol)
  824                  CALL igerv2d( ictxt, 2, 1, iwork, 2, 
  825     $                    srcrow, srccol )
  826                  starti = iwork(1)
  827                  lengthi = iwork(2)
  828                  IF (( starti.GE.1 ) .AND. ( lengthi.GE.1 )) THEN
  829                     lengthi2 = 2*lengthi
  830
  831                     CALL sgerv2d( ictxt, lengthi2, 1,
  832     $                 work(indd), lengthi2, srcrow, srccol )
  833
  834                     CALL scopy( lengthi, work(indd), 1,
  835     $                          w( starti ), 1)                    
  836
  837                     CALL scopy(lengthi,work(indd+lengthi),1,
  838     $                          work( iinderr+starti-1 ), 1)     
  839                  END IF
  840               END IF
  841  45        CONTINUE
  842            lengthi = iiu - iil + 1
  843            lengthi2 = lengthi * 2
  844            IF (myproc .EQ. 0) THEN
  845
  846               CALL scopy(lengthi,w ,1, work( indd ), 1)                
  847               CALL scopy(lengthi,work( iinderr ),1,
  848     $                          work( indd+lengthi ), 1)                
  849               CALL sgebs2d( ictxt, 'A', ' ', lengthi2, 1, 
  850     $              work(indd), lengthi2 )
  851            ELSE
  852               srcrow = 0
  853               srccol = 0
  854               CALL sgebr2d( ictxt, 'A', ' ', lengthi2, 1,
  855     $             work(indd), lengthi2, srcrow, srccol )
  856               CALL scopy( lengthi, work(indd), 1, w, 1)
  857               CALL scopy(lengthi,work(indd+lengthi),1,
  858     $                          work( iinderr ), 1)                   
  859            END IF
  860         ELSE
  861
  862
  863
  864
  865            IF( (nprocs.GT.1).AND.(myil.GT.0) ) THEN
  866               CALL pmpcol( myproc, nprocs, iil, needil, neediu, 
 
  867     $                   iwork(indilu), iwork(indilu+nprocs),
  868     $                   colbrt, frstcl, lastcl )
  869            ELSE
  870               colbrt = .false.
  871            ENDIF
  872 
  873            IF(colbrt) THEN
  874
  875
  876               DO 47 iproc = frstcl, lastcl
  877                  IF (myproc .EQ. iproc) THEN
  878                     starti = dol
  879                     iwork(1) = starti
  880                     lengthi = myiu - myil + 1
  881                     iwork(2) = lengthi
  882                     
  883                     IF ((starti.GE.1) .AND. (lengthi.GE.1)) THEN
  884
  885                        CALL scopy(lengthi,w( starti ),1,
  886     $                              work(indd), 1)                    
  887
  888                        CALL scopy(lengthi,
  889     $                          work( iinderr+starti-1 ),1,
  890     $                          work(indd+lengthi), 1)                  
  891                     ENDIF
  892 
  893                     DO 46 i = frstcl, lastcl                      
  894                        IF(i.EQ.myproc) GOTO 46
  895                        dstrow = i/ npcol
  896                        dstcol = mod(i, npcol)
  897                        CALL igesd2d( ictxt, 2, 1, iwork, 2, 
  898     $                             dstrow, dstcol )
  899                        IF ((starti.GE.1) .AND. (lengthi.GE.1)) THEN
  900                           lengthi2 = 2*lengthi
  901
  902                           CALL sgesd2d( ictxt, lengthi2, 
  903     $                          1, work(indd), lengthi2,
  904     $                          dstrow, dstcol )
  905                        END IF
  906  46                 CONTINUE
  907                  ELSE
  908                     srcrow = iproc / npcol
  909                     srccol = mod(iproc, npcol)
  910                     CALL igerv2d( ictxt, 2, 1, iwork, 2, 
  911     $                             srcrow, srccol )
  912                     rstarti = iwork(1)
  913                     rlengthi = iwork(2)
  914                     IF ((rstarti.GE.1 ) .AND. (rlengthi.GE.1 )) THEN
  915                        rlengthi2 = 2*rlengthi
  916                        CALL sgerv2d( ictxt, rlengthi2, 1,
  917     $                      work(inde), rlengthi2,
  918     $                      srcrow, srccol )
  919
  920                        CALL scopy( rlengthi, work(inde), 1,
  921     $                          w( rstarti ), 1)                    
  922
  923                        CALL scopy(rlengthi,work(inde+rlengthi),1,
  924     $                          work( iinderr+rstarti-1 ), 1)           
  925                     END IF
  926                  END IF
  927  47           CONTINUE
  928            ENDIF
  929         ENDIF
  930 
  931
  932
  933
  934
  935
  936
  937
  938 100     CONTINUE
  939         IF ( myil.GT.0 ) THEN
  940            CALL sstegr2b( jobz, n,  work( indd2 ),
 
  941     $                  work( inde2+offset ), 
  942     $                  im, w( 1 ), work( indrw ), n, n,
  943     $                  iwork( 1 ), work( indwork ), size1, 
  944     $                  iwork( 2*n+1 ), size2, dol, 
  945     $                  dou, needil, neediu, indwlc,
  946     $                  pivmin, scale, wl, wu,
  947     $                  vstart, finish, 
  948     $                  maxcls, ndepth, parity, zoffset, iinfo )
  949            iindwlc = indwork + indwlc - 1
  950            IF(.NOT.finish) THEN
  951               IF((needil.LT.dol).OR.(neediu.GT.dou)) THEN
  952                  CALL pmpcol( myproc, nprocs, iil, needil, neediu,
 
  953     $                 iwork(indilu), iwork(indilu+nprocs),
  954     $                   colbrt, frstcl, lastcl )
  955               ELSE
  956                  colbrt = .false.
  957                  frstcl = myproc
  958                  lastcl = myproc
  959               ENDIF
  960
  961
  962
  963
  964               IF(colbrt) THEN
  965                  DO 147 iproc = frstcl, lastcl
  966                     IF (myproc .EQ. iproc) THEN
  967                        starti = dol
  968                        iwork(1) = starti
  969                        IF(myil.GT.0) THEN
  970                           lengthi = myiu - myil + 1
  971                        ELSE
  972                           lengthi = 0
  973                        ENDIF
  974                        iwork(2) = lengthi
  975                        IF ((starti.GE.1).AND.(lengthi.GE.1)) THEN
  976
  977                           CALL scopy(lengthi,
  978     $                          work( iindwlc+starti-1 ),1,
  979     $                          work(indd), 1)                    
  980
  981                           CALL scopy(lengthi,
  982     $                          work( iinderr+starti-1 ),1,
  983     $                          work(indd+lengthi), 1)                  
  984                        ENDIF
  985                     
  986                        DO 146 i = frstcl, lastcl                      
  987                           IF(i.EQ.myproc) GOTO 146
  988                           dstrow = i/ npcol
  989                           dstcol = mod(i, npcol)
  990                           CALL igesd2d( ictxt, 2, 1, iwork, 2, 
  991     $                             dstrow, dstcol )
  992                           IF ((starti.GE.1).AND.(lengthi.GE.1)) THEN
  993                              lengthi2 = 2*lengthi
  994
  995                              CALL sgesd2d( ictxt, lengthi2, 
  996     $                             1, work(indd), lengthi2,
  997     $                             dstrow, dstcol )
  998                           END IF
  999 146                    CONTINUE
 1000                     ELSE
 1001                        srcrow = iproc / npcol
 1002                        srccol = mod(iproc, npcol)
 1003                        CALL igerv2d( ictxt, 2, 1, iwork, 2, 
 1004     $                             srcrow, srccol )
 1005                        rstarti = iwork(1)
 1006                        rlengthi = iwork(2)
 1007                        IF ((rstarti.GE.1).AND.(rlengthi.GE.1)) THEN
 1008                           rlengthi2 = 2*rlengthi
 1009                           CALL sgerv2d( ictxt,rlengthi2, 1,
 1010     $                         work(inde),rlengthi2,
 1011     $                         srcrow, srccol )
 1012
 1013                           CALL scopy(rlengthi, work(inde), 1,
 1014     $                          work( iindwlc+rstarti-1 ), 1)        
 1015
 1016                           CALL scopy(rlengthi,work(inde+rlengthi),1,
 1017     $                          work( iinderr+rstarti-1 ), 1)           
 1018                        END IF
 1019                     END IF
 1020 147              CONTINUE
 1021               ENDIF
 1022               GOTO 100         
 1023            ENDIF
 1024         ENDIF
 1025         IF (iinfo .NE. 0) THEN
 1026            CALL pxerbla( ictxt, 
'SSTEGR2B', -iinfo )
 
 1027            RETURN
 1028         END IF
 1029
 1030      ENDIF
 1031 
 1032
 1033
 1034
 1035
 1036
 1037
 1038
 1039
 1040
 1041
 1042
 1043
 1044
 1045
 1046      DO 50 i = 2, nprocs
 1047         IF (myproc .EQ. (i - 1)) THEN
 1048            dstrow = 0
 1049            dstcol = 0
 1050            starti = myil - iil + 1
 1051            iwork(1) = starti
 1052            IF(myil.GT.0) THEN
 1053               lengthi = myiu - myil + 1
 1054            ELSE
 1055               lengthi = 0
 1056            ENDIF
 1057            iwork(2) = lengthi
 1058            CALL igesd2d( ictxt, 2, 1, iwork, 2, 
 1059     $                    dstrow, dstcol )
 1060            IF ((starti.GE.1).AND.(lengthi.GE.1)) THEN
 1061               CALL sgesd2d( ictxt, lengthi, 
 1062     $              1, w( starti ), lengthi,
 1063     $              dstrow, dstcol )
 1064            ENDIF
 1065         ELSE IF (myproc .EQ. 0) THEN
 1066            srcrow = (i-1) / npcol
 1067            srccol = mod(i-1, npcol)
 1068            CALL igerv2d( ictxt, 2, 1, iwork, 2, 
 1069     $                    srcrow, srccol )
 1070            starti = iwork(1)
 1071            lengthi = iwork(2)
 1072            IF ((starti.GE.1).AND.(lengthi.GE.1)) THEN
 1073               CALL sgerv2d( ictxt, lengthi, 1,
 1074     $                 w( starti ), lengthi, srcrow, srccol )
 1075            ENDIF
 1076         ENDIF
 1077   50 CONTINUE
 1078 
 1079
 1080      m = im
 1081      CALL igsum2d( ictxt, 'A', ' ', 1, 1, m, 1, -1, -1 )
 1082 
 1083
 1084      IF (myproc .EQ. 0) THEN
 1085
 1086         CALL sgebs2d( ictxt, 'A', ' ', m, 1, w, m )
 1087      ELSE
 1088         srcrow = 0
 1089         srccol = 0
 1090         CALL sgebr2d( ictxt, 'A', ' ', m, 1,
 1091     $           w, m, srcrow, srccol )
 1092      END IF
 1093
 1094
 1095
 1096
 1097      DO 160 i = 1, m
 1098         iwork( nprocs+1+i ) = i
 1099  160 CONTINUE
 1100      CALL slasrt2( 
'I', m, w, iwork( nprocs+2 ), iinfo )
 
 1101      IF (iinfo.NE.0) THEN
 1102         CALL pxerbla( ictxt, 
'SLASRT2', -iinfo )
 
 1103         RETURN
 1104      END IF
 1105 
 1106
 1107
 1108
 1109
 1110
 1111      IF ( wantz ) THEN
 1112         DO 170 i = 1, m
 1113            iwork( m+nprocs+1+iwork( nprocs+1+i ) ) = i
 1114  170    CONTINUE
 1115
 1116         iwork( 1 ) = 0
 1117         DO 180 i = 1, nprocs
 1118
 1119
 1120            ipil = iwork(indilu+i-1)
 1121            ipiu = iwork(indilu+nprocs+i-1)
 1122            IF (ipil .EQ. 0) THEN
 1123               iwork( i + 1 ) = iwork( i )
 1124            ELSE
 1125               iwork( i + 1 ) = iwork( i ) + ipiu - ipil + 1
 1126            ENDIF
 1127  180    CONTINUE
 1128 
 1129         IF ( first ) THEN
 1130            CALL pslaevswp(n, work( indrw ), n, z, iz, jz, 
 
 1131     $       descz, iwork( 1 ), iwork( nprocs+m+2 ), work( indwork ), 
 1132     $       indrw - indwork )
 1133         ELSE
 1134            CALL pslaevswp(n, work( indrw + n ), n, z, iz, jz, 
 
 1135     $       descz, iwork( 1 ), iwork( nprocs+m+2 ), work( indwork ), 
 1136     $       indrw - indwork )
 1137         END IF
 1138
 1139         nz = m
 1140
 1141 
 1142
 1143
 1144
 1145
 1146
 1147         IF( nz.GT.0 ) THEN
 1148           CALL psormtr( 
'L', uplo, 
'N', n, nz, a, ia, ja, desca,
 
 1149     $                    work( indtau ), z, iz, jz, descz,
 1150     $                    work( indwork ), size1, iinfo )
 1151         END IF
 1152         IF (iinfo.NE.0) THEN
 1153            CALL pxerbla( ictxt, 
'PSORMTR', -iinfo )
 
 1154            RETURN
 1155         END IF
 1156
 1157 
 1158      END IF
 1159
 1160      work( 1 ) = real( lwopt )
 1161      iwork( 1 ) = liwmin
 1162 
 1163      RETURN
 1164
 1165
 1166
subroutine chk1mat(ma, mapos0, na, napos0, ia, ja, desca, descapos0, info)
 
integer function iceil(inum, idenom)
 
integer function indxg2p(indxglob, nb, iproc, isrcproc, nprocs)
 
integer function numroc(n, nb, iproc, isrcproc, nprocs)
 
real function pslamch(ictxt, cmach)
 
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)
 
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 pselget(scope, top, alpha, a, ia, ja, desca)
 
subroutine pslaevswp(n, zin, ldzi, z, iz, jz, descz, nvs, key, work, lwork)
 
subroutine pslared1d(n, ia, ja, desc, bycol, byall, work, lwork)
 
subroutine psormtr(side, uplo, trans, m, n, a, ia, ja, desca, tau, c, ic, jc, descc, work, lwork, info)
 
subroutine pssyntrd(uplo, n, a, ia, ja, desca, d, e, tau, work, lwork, info)
 
subroutine pxerbla(ictxt, srname, info)
 
subroutine slasrt2(id, n, d, key, info)
 
subroutine sstegr2(jobz, range, n, d, e, vl, vu, il, iu, m, w, z, ldz, nzc, isuppz, work, lwork, iwork, liwork, dol, dou, zoffset, info)
 
subroutine sstegr2a(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 sstegr2b(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)