SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ pzlasizesepr()

subroutine pzlasizesepr ( integer, dimension( * )  desca,
integer  iprepad,
integer  ipostpad,
integer  sizemqrleft,
integer  sizemqrright,
integer  sizeqrf,
integer  sizetms,
integer  sizeqtq,
integer  sizechk,
integer  sizeheevr,
integer  rsizeheevr,
integer  isizeheevr,
integer  sizesubtst,
integer  rsizesubtst,
integer  isizesubtst,
integer  sizetst,
integer  rsizetst,
integer  isizetst 
)

Definition at line 1 of file pzlasizesepr.f.

7*
8* -- ScaLAPACK routine (@(MODE)version *TBA*) --
9* University of California, Berkeley and
10* University of Tennessee, Knoxville.
11* October 21, 2006
12*
13 IMPLICIT NONE
14*
15* .. Scalar Arguments ..
16 INTEGER IPOSTPAD, IPREPAD, ISIZEHEEVR, ISIZESUBTST,
17 $ ISIZETST, RSIZEHEEVR, RSIZESUBTST, RSIZETST,
18 $ SIZECHK, SIZEHEEVR, SIZEMQRLEFT, SIZEMQRRIGHT,
19 $ SIZEQRF, SIZEQTQ, SIZESUBTST, SIZETMS, SIZETST
20* ..
21* .. Array Arguments ..
22 INTEGER DESCA( * )
23*
24* Purpose
25* =======
26*
27* PZLASIZESEPR computes the amount of memory needed by
28* various SEPR test routines, as well as PZHEEVR itself.
29*
30* Arguments
31* =========
32*
33* DESCA (global input) INTEGER array dimension ( DLEN_ )
34* Array descriptor for dense matrix.
35*
36* SIZEMQRLEFT LWORK for the 1st PZUNMQR call in PZLAGHE
37*
38* SIZEMQRRIGHT LWORK for the 2nd PZUNMQR call in PZLAGHE
39*
40* SIZEQRF LWORK for PZGEQRF in PZLAGHE
41*
42* SIZETMS LWORK for PZLATMS
43*
44* SIZEQTQ LWORK for PZSEPQTQ
45*
46* SIZECHK LWORK for PZSEPCHK
47*
48* SIZEHEEVR LWORK for PZHEEVR
49*
50* RSIZEHEEVR LRWORK for PZHEEVR
51*
52* ISIZEHEEVR LIWORK for PZHEEVR
53*
54* SIZESUBTST LWORK for PZSEPRSUBTST
55*
56* RSIZESUBTST LRWORK for PZSEPRSUBTST
57*
58* ISIZESUBTST LIWORK for PZSEPRSUBTST
59*
60* SIZETST LWORK for PZSEPRTST
61*
62* RSIZETST LRWORK for PZSEPRTST
63*
64* ISIZETST LIWORK for PZSEPRTST
65*
66*
67* .. Parameters ..
68 INTEGER CTXT_, M_,
69 $ MB_, NB_, RSRC_, CSRC_, LLD_
70 parameter(
71 $ ctxt_ = 2, m_ = 3, mb_ = 5, nb_ = 6,
72 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
73* ..
74* .. Local Scalars ..
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
79* ..
80* .. External Functions ..
81 INTEGER ICEIL, ILCM, INDXG2P, NUMROC
82 EXTERNAL iceil, ilcm, indxg2p, numroc
83 INTEGER PJLAENV
84 EXTERNAL pjlaenv
85*
86* .. External Subroutines ..
87 EXTERNAL blacs_gridinfo
88* ..
89* .. Intrinsic Functions ..
90 INTRINSIC dble, int, max, sqrt
91* ..
92* .. Executable Statements ..
93*
94 n = desca( m_ )
95 nb = desca( mb_ )
96 rsrc_a = desca( rsrc_ )
97 csrc_a = desca( csrc_ )
98*
99 lda = desca( lld_ )
100 CALL blacs_gridinfo( desca( ctxt_ ), nprow, npcol, myrow, mycol )
101*
102 lcm = ilcm( nprow, npcol )
103 lcmq = lcm / npcol
104 iroffa = 0
105 icoffa = 0
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 )
117*
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 )
122*
123 neig = n
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 )
128*
129*
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)
135*
136 isizeheevr = 12*nnp + 2*n
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 sizeheevr = max( sizeheevr, n + nhetrd_lwopt )
144*
145 sizesubtst = max( sizetms, sizeheevr ) +
146 $ iprepad + ipostpad
147 rsizesubtst = max( sizeqtq, sizechk, rsizeheevr ) +
148 $ iprepad + ipostpad
149 isizesubtst = isizeheevr + iprepad + ipostpad
150*
151* Allow room for A, COPYA, Z, WORK
152*
153 sizetst = 3*( lda*np+iprepad+ipostpad ) + sizesubtst
154*
155* Allow room for DIAG, WIN, WNEW, GAP, RWORK
156*
157 rsizetst = 4*( n+iprepad+ipostpad ) + rsizesubtst
158*
159* Allow room for IFAIL, ICLUSTR, and IWORK
160* (only needed for PZHEEVX)
161*
162 isizetst = n + 2*nprow*npcol + 2*( iprepad+ipostpad ) +
163 $ isizesubtst
164*
165*
166 RETURN
integer function iceil(inum, idenom)
Definition iceil.f:2
integer function ilcm(m, n)
Definition ilcm.f:2
integer function indxg2p(indxglob, nb, iproc, isrcproc, nprocs)
Definition indxg2p.f:2
integer function numroc(n, nb, iproc, isrcproc, nprocs)
Definition numroc.f:2
#define max(A, B)
Definition pcgemr.c:180
integer function pjlaenv(ictxt, ispec, name, opts, n1, n2, n3, n4)
Definition pjlaenv.f:3
Here is the caller graph for this function: