1 SUBROUTINE pclasizesepr( DESCA, IPREPAD, IPOSTPAD, SIZEMQRLEFT,
2 $ SIZEMQRRIGHT, SIZEQRF, SIZETMS, SIZEQTQ,
3 $ SIZECHK, SIZEHEEVR, RSIZEHEEVR,
4 $ ISIZEHEEVR, SIZESUBTST, RSIZESUBTST,
5 $ ISIZESUBTST, SIZETST, RSIZETST,
16 INTEGER IPOSTPAD, IPREPAD, ISIZEHEEVR, ISIZESUBTST,
17 $ ISIZETST, RSIZEHEEVR, RSIZESUBTST, RSIZETST,
18 $ sizechk, sizeheevr, sizemqrleft, sizemqrright,
19 $ sizeqrf, sizeqtq, sizesubtst, sizetms, sizetst
69 $ MB_, NB_, RSRC_, CSRC_, LLD_
71 $ CTXT_ = 2, m_ = 3, mb_ = 5, nb_ = 6,
72 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
75 INTEGER CSRC_A, IACOL, IAROW, ICOFFA, IROFFA, LCM,
76 $ LCMQ, LDA, MQ0, MYCOL, MYROW, N, NB, NEIG, NN,
77 $ NNP, NP, NP0, NPCOL, NPROW, NQ, RSRC_A
78 INTEGER ANB, ICTXT, NHETRD_LWOPT, NPS, SQNPC
81 INTEGER ICEIL, ILCM, INDXG2P, NUMROC
82 EXTERNAL ICEIL, ILCM, INDXG2P, NUMROC
87 EXTERNAL blacs_gridinfo
90 INTRINSIC dble, int,
max, sqrt
96 rsrc_a = desca( rsrc_ )
97 csrc_a = desca( csrc_ )
100 CALL blacs_gridinfo( desca( ctxt_ ), nprow, npcol, myrow, mycol )
102 lcm = ilcm( nprow, npcol )
106 iarow = indxg2p( 1, nb, myrow, rsrc_a, nprow )
107 iacol = indxg2p( 1, nb, mycol, csrc_a, npcol )
108 np = numroc( n+iroffa, nb, myrow, iarow, nprow )
109 nq = numroc( n+icoffa, nb, mycol, iacol, npcol )
110 sizemqrleft =
max( ( nb*( nb-1 ) ) / 2, ( np+nq )*nb ) + nb*nb
111 sizemqrright =
max( ( nb*( nb-1 ) ) / 2,
112 $ ( nq+
max( np+numroc( numroc( n+icoffa, nb, 0, 0,
113 $ npcol ), nb, 0, 0, lcmq ), np ) )*nb ) + nb*nb
114 sizeqrf = nb*np + nb*nq + nb*nb
115 sizetms = ( lda+1 )*
max( 1, nq ) +
116 $
max( sizemqrleft, sizemqrright, sizeqrf )
118 np0 = numroc( n, desca( mb_ ), 0, 0, nprow )
119 mq0 = numroc( n, desca( nb_ ), 0, 0, npcol )
120 sizeqtq = 2 +
max( desca( mb_ ), 2 )*( 2*np0+mq0 )
121 sizechk = numroc( n, desca( nb_ ), mycol, 0, npcol )
124 nn =
max( n, nb, 2 ) + 1
125 np0 = numroc( nn, nb, 0, 0, nprow )
126 mq0 = numroc(
max( neig, nb, 2 ), nb, 0, 0, npcol )
127 nnp =
max( n, nprow*npcol+1, 4 )
130 sizeheevr = 1+n + ( np0+mq0+nb )*nb
131 sizeheevr =
max(3, sizeheevr)
132 rsizeheevr = 1 + 5*n +
max( 18*nn, np0*mq0+2*nb*nb ) +
133 $ (2 + iceil( neig, nprow*npcol ))*nn
134 rsizeheevr =
max(3, rsizeheevr)
136 isizeheevr = 12*nnp + 2*n
138 ictxt = desca( ctxt_ )
139 anb = pjlaenv( ictxt, 3,
'PCHETTRD',
'L', 0, 0, 0, 0 )
140 sqnpc = int( sqrt( dble( nprow*npcol ) ) )
141 nps =
max( numroc( n, 1, 0, 0, sqnpc ), 2*anb )
142 nhetrd_lwopt = 2*( anb+1 )*( 4*nps+2 ) + ( nps+2 )*nps
143 sizeheevr =
max( sizeheevr, n + nhetrd_lwopt )
145 sizesubtst =
max( sizetms, sizeheevr ) +
147 rsizesubtst =
max( sizeqtq, sizechk, rsizeheevr ) +
149 isizesubtst = isizeheevr + iprepad + ipostpad
153 sizetst = 3*( lda*np+iprepad+ipostpad ) + sizesubtst
157 rsizetst = 4*( n+iprepad+ipostpad ) + rsizesubtst
162 isizetst = n + 2*nprow*npcol + 2*( iprepad+ipostpad ) +