SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
pdlasizesyev.f
Go to the documentation of this file.
1*
2*
3 SUBROUTINE pdlasizesyev( JOBZ, N, DESCA, MINSIZE )
4*
5*
6* -- ScaLAPACK routine (version 1.7) --
7* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
8* and University of California, Berkeley.
9* May 1, 1997
10*
11* .. Scalar Arguments ..
12 CHARACTER JOBZ
13 INTEGER MINSIZE, N
14* ..
15* .. Array Arguments ..
16 INTEGER DESCA( * )
17* ..
18*
19* Purpose
20* =======
21*
22* PDLASIZESYEV computes the amount of memory needed by PDSYEV
23* to calculate:
24* 1) Eigenvectors and eigenvalues if JOBZ = 'V'
25* 2) Eigenvalues only if JOBZ = 'N'
26*
27* Arguments
28* =========
29*
30* NP = the number of rows local to a given process.
31* NQ = the number of columns local to a given process.
32*
33* JOBZ (global input) CHARACTER*1
34* Specifies whether or not to compute the eigenvectors:
35* = 'N': Compute eigenvalues only.
36* = 'V': Compute eigenvalues and eigenvectors.
37*
38* N (global input) INTEGER
39* Size of the matrix to be tested. (global size)
40*
41* DESCA (global input) INTEGER array dimension ( DLEN_ )
42*
43* MINSIZE (global output) INTEGER
44* Workspace required for PDSYEV to:
45* 1) Eigenvectors and eigenvalues if JOBZ = 'V'
46* 2) Eigenvalues only if JOBZ = 'N'
47*
48*
49* .. Parameters ..
50 INTEGER BLOCK_CYCLIC_2D, DLEN_, DTYPE_, CTXT_, M_, N_,
51 $ MB_, NB_, RSRC_, CSRC_, LLD_
52 parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
53 $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
54 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
55* ..
56* .. Local Scalars ..
57 LOGICAL WANTZ
58 INTEGER CONTEXTC, CSRC_A, IACOL, IAROW, ICOFFA, IROFFA,
59 $ LCM, LCMQ, LDC, MQ0, MYCOL, MYPCOLC, MYPROWC,
60 $ MYROW, NB, NN, NP, NP0, NPCOL, NPCOLC, NPROCS,
61 $ NPROW, NPROWC, NQ, NRC, QRMEM, RSRC_A,
62 $ SIZEMQRLEFT, SIZEMQRRIGHT
63* ..
64* .. External Functions ..
65*
66*
67 LOGICAL LSAME
68 INTEGER ILCM, INDXG2P, NUMROC, SL_GRIDRESHAPE
69 EXTERNAL ilcm, indxg2p, lsame, numroc, sl_gridreshape
70* ..
71* .. External Subroutines ..
72 EXTERNAL blacs_gridinfo, blacs_gridexit
73* ..
74* .. Intrinsic Functions ..
75 INTRINSIC max
76* ..
77* .. Executable Statements ..
78* This is just to keep ftnchek happy
79 IF( block_cyclic_2d*csrc_*ctxt_*dlen_*dtype_*lld_*mb_*m_*nb_*n_*
80 $ rsrc_.LT.0 )RETURN
81*
82 CALL blacs_gridinfo( desca( ctxt_ ), nprow, npcol, myrow, mycol )
83 nb = desca( mb_ )
84 n = desca( m_ )
85 rsrc_a = desca( rsrc_ )
86 csrc_a = desca( csrc_ )
87 lcm = ilcm( nprow, npcol )
88 lcmq = lcm / npcol
89 iroffa = 0
90 icoffa = 0
91 iarow = indxg2p( 1, nb, myrow, rsrc_a, nprow )
92 iacol = indxg2p( 1, nb, mycol, csrc_a, npcol )
93 np = numroc( n+iroffa, nb, myrow, iarow, nprow )
94 nq = numroc( n+icoffa, nb, mycol, iacol, npcol )
95 sizemqrleft = max( ( nb*( nb-1 ) ) / 2, ( np+nq )*nb ) + nb*nb
96 sizemqrright = max( ( nb*( nb-1 ) ) / 2,
97 $ ( nq+max( np+numroc( numroc( n+icoffa, nb, 0, 0,
98 $ npcol ), nb, 0, 0, lcmq ), np ) )*nb ) + nb*nb
99 nn = max( n, nb, 2 )
100 np0 = numroc( nn, nb, 0, 0, nprow )
101 mq0 = numroc( nn, nb, 0, 0, npcol )
102 nprocs = nprow*npcol
103 wantz = lsame( jobz, 'V' )
104 ldc = 0
105*
106* Create the new context that is used in PDSYEV
107*
108 IF( wantz ) THEN
109 contextc = sl_gridreshape( desca( ctxt_ ), 0, 1, 1, nprocs, 1 )
110 CALL blacs_gridinfo( contextc, nprowc, npcolc, myprowc,
111 $ mypcolc )
112 nrc = numroc( n, nb, myprowc, 0, nprocs)
113 ldc = max( 1, nrc )
114 CALL blacs_gridexit( contextc )
115 END IF
116
117*
118* Compute the total amount of space needed
119*
120 IF( wantz ) THEN
121 qrmem = 5*n + max( 2*np0 +mq0 + nb*nn, 2*nn-2 ) + n*ldc
122 minsize = max( sizemqrleft, sizemqrright, qrmem )
123 ELSE
124 minsize = 5*n + 2*np0 +mq0 + nb*nn
125 END IF
126*
127 RETURN
128*
129* End of PDLASIZESYEV
130*
131 END
#define max(A, B)
Definition pcgemr.c:180
subroutine pdlasizesyev(jobz, n, desca, minsize)
Definition pdlasizesyev.f:4