SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
pzlasizegsep.f
Go to the documentation of this file.
1 SUBROUTINE pzlasizegsep( DESCA, IPREPAD, IPOSTPAD, SIZEMQRLEFT,
2 $ SIZEMQRRIGHT, SIZEQRF, SIZETMS, RSIZEQTQ,
3 $ RSIZECHK, SIZEHEEVX, RSIZEHEEVX,
4 $ ISIZEHEEVX, SIZESUBTST, RSIZESUBTST,
5 $ ISIZESUBTST, SIZETST, RSIZETST,
6 $ ISIZETST )
7*
8* -- ScaLAPACK test routine (version 1.7) --
9* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
10* and University of California, Berkeley.
11* October 15, 1999
12*
13* .. Scalar Arguments ..
14 INTEGER IPOSTPAD, IPREPAD, ISIZEHEEVX, ISIZESUBTST,
15 $ ISIZETST, RSIZECHK, RSIZEHEEVX, RSIZEQTQ,
16 $ RSIZESUBTST, RSIZETST, SIZEHEEVX, SIZEMQRLEFT,
17 $ SIZEMQRRIGHT, SIZEQRF, SIZESUBTST, SIZETMS,
18 $ SIZETST
19* ..
20* .. Array Arguments ..
21 INTEGER DESCA( * )
22* ..
23*
24* Purpose
25* PZLASIZEGSEP computes the amount of memory needed by
26* =======
27*
28* PZLASIZEGSEP computes the amount of memory needed by
29* various GSEP test routines, as well as HEGVX itself
30*
31* Arguments
32* =========
33*
34* DESCA (global input) INTEGER array dimension ( DLEN_ )
35* Array descriptor as passed to PZHEGVX
36*
37* SIZEMQRLEFT LWORK for the 1st PZUNMQR call in PZLAGHE
38*
39* SIZEMQRRIGHT LWORK for the 2nd PZUNMQR call in PZLAGHE
40*
41* SIZEQRF LWORK for PZGEQRF in PZLAGHE
42*
43* SIZETMS LWORK for PZLATMS
44*
45* RSIZEQTQ LWORK for PZSEPQTQ (nexer complex)
46*
47* RSIZECHK LWORK for PZGSEPCHK
48*
49* SIZEHEEVX LWORK for PZHEGVX
50*
51* RSIZEHEEVX LRWORK for PZHEGVX
52*
53* ISIZEHEEVX LIWORK for PZHEGVX
54*
55* SIZESUBTST LWORK for PZSUBTST
56*
57* RSIZESUBTST LRWORK for PZSUBTST
58*
59* ISIZESUBTST LIWORK for PZSUBTST
60*
61* SIZETST LWORK for PZTST
62*
63* RSIZETST LRWORK for PZTST
64*
65* ISIZETST LIWORK for PZTST
66*
67* .. Parameters ..
68 INTEGER BLOCK_CYCLIC_2D, DLEN_, DTYPE_, CTXT_, M_, N_,
69 $ MB_, NB_, RSRC_, CSRC_, LLD_
70 PARAMETER ( BLOCK_CYCLIC_2D = 1, dlen_ = 9, dtype_ = 1,
71 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
72 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
73* ..
74* .. Local Scalars ..
75 INTEGER ANB, CSRC_A, IACOL, IAROW, ICOFFA, ICTXT,
76 $ IROFFA, LCM, LCMQ, LDA, MQ0, MYCOL, MYROW, N,
77 $ NB, NEIG, NHEGST_LWOPT, NHETRD_LWOPT, NN, NNP,
78 $ NP, NP0, NPCOL, NPROW, NPS, NQ, NQ0, RSRC_A,
79 $ SIZECHK, SIZEQTQ, SQNPC
80* ..
81* .. External Functions ..
82*
83 INTEGER ICEIL, ILCM, INDXG2P, NUMROC, PJLAENV
84 EXTERNAL ICEIL, ILCM, INDXG2P, NUMROC, PJLAENV
85* ..
86* .. Intrinsic Functions ..
87 INTRINSIC DBLE, INT, MAX, SQRT
88* ..
89* .. External Subroutines ..
90 EXTERNAL blacs_gridinfo
91* ..
92* .. Executable Statements ..
93* This is just to keep ftnchek and toolpack/1 happy
94 IF( block_cyclic_2d*csrc_*ctxt_*dlen_*dtype_*lld_*mb_*m_*nb_*n_*
95 $ rsrc_.LT.0 )RETURN
96*
97 n = desca( m_ )
98 nb = desca( mb_ )
99 rsrc_a = desca( rsrc_ )
100 csrc_a = desca( csrc_ )
101*
102 lda = desca( lld_ )
103 CALL blacs_gridinfo( desca( ctxt_ ), nprow, npcol, myrow, mycol )
104*
105 lcm = ilcm( nprow, npcol )
106 lcmq = lcm / npcol
107 iroffa = 0
108 icoffa = 0
109 iarow = indxg2p( 1, nb, myrow, rsrc_a, nprow )
110 iacol = indxg2p( 1, nb, mycol, csrc_a, npcol )
111 np = numroc( n+iroffa, nb, myrow, iarow, nprow )
112 nq = numroc( n+icoffa, nb, mycol, iacol, npcol )
113 sizemqrleft = max( ( nb*( nb-1 ) ) / 2, ( np+nq )*nb ) + nb*nb
114 sizemqrright = max( ( nb*( nb-1 ) ) / 2,
115 $ ( nq+max( np+numroc( numroc( n+icoffa, nb, 0, 0,
116 $ npcol ), nb, 0, 0, lcmq ), np ) )*nb ) + nb*nb
117 sizeqrf = nb*np + nb*nq + nb*nb
118 sizetms = ( lda+1 )*max( 1, nq ) +
119 $ max( sizemqrleft, sizemqrright, sizeqrf )
120*
121 np0 = numroc( n, desca( mb_ ), 0, 0, nprow )
122 mq0 = numroc( n, desca( nb_ ), 0, 0, npcol )
123 sizeqtq = 0
124 sizechk = 0
125 rsizeqtq = 0
126 rsizechk = numroc( n, desca( nb_ ), mycol, 0, npcol )
127*
128 neig = n
129 nn = max( n, nb, 2 )
130 np0 = numroc( nn, nb, 0, 0, nprow )
131 mq0 = numroc( max( neig, nb, 2 ), nb, 0, 0, npcol )
132 sizeheevx = n + ( np0+mq0+nb )*nb
133 rsizeheevx = 4*n + max( 5*nn, np0*mq0 ) +
134 $ iceil( neig, nprow*npcol )*nn
135 nnp = max( n, nprow*npcol+1, 4 )
136 isizeheevx = 6*nnp
137*
138 ictxt = desca( ctxt_ )
139 anb = pjlaenv( ictxt, 3, 'PZHETTRD', '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*
144 np0 = numroc( n, nb, 0, 0, nprow )
145 nq0 = numroc( n, nb, 0, 0, npcol )
146 nhegst_lwopt = 2*np0*nb + nq0*nb + nb*nb
147 sizeheevx = max( sizeheevx, n+nhetrd_lwopt, nhegst_lwopt )
148*
149 sizesubtst = max( sizetms, sizeqtq, sizechk, sizeheevx ) +
150 $ iprepad + ipostpad
151 rsizesubtst = max( rsizeheevx, rsizeqtq, rsizechk ) + iprepad +
152 $ ipostpad
153 isizesubtst = isizeheevx + iprepad + ipostpad
154*
155*
156* Allow room for A, COPYA and Z and WORK
157*
158 sizetst = 3*( lda*np+iprepad+ipostpad ) + sizesubtst
159*
160* Room for DIAG, WIN, WNEW, GAP and RWORK
161*
162 rsizetst = 4*( n+iprepad+ipostpad ) + rsizesubtst
163*
164* Allow room for IFAIL, ICLUSTR, and IWORK (all in PZHEGVX)
165*
166 isizetst = n + 2*nprow*npcol + 2*( iprepad+ipostpad ) +
167 $ isizesubtst
168*
169 RETURN
170 END
subroutine pzlasizegsep(desca, iprepad, ipostpad, sizemqrleft, sizemqrright, sizeqrf, sizetms, rsizeqtq, rsizechk, sizeheevx, rsizeheevx, isizeheevx, sizesubtst, rsizesubtst, isizesubtst, sizetst, rsizetst, isizetst)
Definition pzlasizegsep.f:7