ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
pdlasizesep.f
Go to the documentation of this file.
1 *
2 *
3  SUBROUTINE pdlasizesep( DESCA, IPREPAD, IPOSTPAD, SIZEMQRLEFT,
4  $ SIZEMQRRIGHT, SIZEQRF, SIZETMS, SIZEQTQ,
5  $ SIZECHK, SIZESYEVX, ISIZESYEVX,
6  $ SIZESUBTST, ISIZESUBTST, SIZETST,
7  $ ISIZETST )
8 *
9 * -- ScaLAPACK routine (version 1.7) --
10 * University of Tennessee, Knoxville, Oak Ridge National Laboratory,
11 * and University of California, Berkeley.
12 * May 1, 1997
13 *
14 * .. Scalar Arguments ..
15  INTEGER IPOSTPAD, IPREPAD, ISIZESUBTST, ISIZESYEVX,
16  $ ISIZETST, SIZECHK, SIZEMQRLEFT, SIZEMQRRIGHT,
17  $ SIZEQRF, SIZEQTQ, SIZESUBTST, SIZESYEVX,
18  $ SIZETMS, SIZETST
19 * ..
20 * .. Array Arguments ..
21  INTEGER DESCA( * )
22 * ..
23 *
24 * Purpose
25 * =======
26 *
27 * PDLASIZESEP computes the amount of memory needed by
28 * various SEP test routines, as well as SYEVX itself
29 *
30 * Arguments
31 * =========
32 *
33 * DESCA (global input) INTEGER array dimension ( DLEN_ )
34 * Array descriptor as passed to PDSYEVX
35 *
36 * SIZEMQRLEFT LWORK for the 1st PDORMQR call in PDLAGSY
37 *
38 * SIZEMQRRIGHT LWORK for the 2nd PDORMQR call in PDLAGSY
39 *
40 * SIZEQRF LWORK for PDGEQRF in PDLAGSY
41 *
42 * SIZETMS LWORK for PDLATMS
43 *
44 * SIZEQTQ LWORK for PDSEPQTQ (nexer complex)
45 *
46 * SIZECHK LWORK for PDSEPCHK
47 *
48 * SIZESYEVX LWORK for PDSYEVX
49 *
50 * ISIZESYEVX LIWORK for PDSYEVX
51 *
52 * SIZESUBTST LWORK for PDSUBTST
53 *
54 * ISIZESUBTST LIWORK for PDSUBTST
55 *
56 * SIZETST LWORK for PDTST
57 *
58 * ISIZETST LIWORK for PDTST
59 *
60 * .. Parameters ..
61  INTEGER BLOCK_CYCLIC_2D, DLEN_, DTYPE_, CTXT_, M_, N_,
62  $ MB_, NB_, RSRC_, CSRC_, LLD_
63  PARAMETER ( BLOCK_CYCLIC_2D = 1, dlen_ = 9, dtype_ = 1,
64  $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
65  $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
66 * ..
67 * .. Local Scalars ..
68  INTEGER CSRC_A, IACOL, IAROW, ICOFFA, IROFFA, LCM,
69  $ LCMQ, LDA, MQ0, MYCOL, MYROW, N, NB, NEIG, NN,
70  $ NNP, NP, NP0, NPCOL, NPROW, NQ, RSRC_A
71 * ..
72 * .. External Functions ..
73  INTEGER ICEIL, ILCM, INDXG2P, NUMROC
74  EXTERNAL ICEIL, ILCM, INDXG2P, NUMROC
75 * ..
76 ** .. Executable Statements ..
77 * This is just to keep ftnchek happy
78 * .. External Subroutines ..
79  EXTERNAL blacs_gridinfo
80 * ..
81 * .. Intrinsic Functions ..
82  INTRINSIC max
83 * ..
84 * .. Executable Statements ..
85  IF( block_cyclic_2d*csrc_*ctxt_*dlen_*dtype_*lld_*mb_*m_*nb_*n_*
86  $ rsrc_.LT.0 )RETURN
87 *
88  n = desca( m_ )
89  nb = desca( mb_ )
90  rsrc_a = desca( rsrc_ )
91  csrc_a = desca( csrc_ )
92 *
93  lda = desca( lld_ )
94  CALL blacs_gridinfo( desca( ctxt_ ), nprow, npcol, myrow, mycol )
95 *
96  lcm = ilcm( nprow, npcol )
97  lcmq = lcm / npcol
98  iroffa = 0
99  icoffa = 0
100  iarow = indxg2p( 1, nb, myrow, rsrc_a, nprow )
101  iacol = indxg2p( 1, nb, mycol, csrc_a, npcol )
102  np = numroc( n+iroffa, nb, myrow, iarow, nprow )
103  nq = numroc( n+icoffa, nb, mycol, iacol, npcol )
104  sizemqrleft = max( ( nb*( nb-1 ) ) / 2, ( np+nq )*nb ) + nb*nb
105  sizemqrright = max( ( nb*( nb-1 ) ) / 2,
106  $ ( nq+max( np+numroc( numroc( n+icoffa, nb, 0, 0,
107  $ npcol ), nb, 0, 0, lcmq ), np ) )*nb ) + nb*nb
108  sizeqrf = nb*np + nb*nq + nb*nb
109  sizetms = ( lda+1 )*max( 1, nq ) +
110  $ max( sizemqrleft, sizemqrright, sizeqrf )
111 *
112  np0 = numroc( n, desca( mb_ ), 0, 0, nprow )
113  mq0 = numroc( n, desca( nb_ ), 0, 0, npcol )
114  sizeqtq = 2 + max( desca( mb_ ), 2 )*( 2*np0+mq0 )
115  sizechk = numroc( n, desca( nb_ ), mycol, 0, npcol )
116 *
117  neig = n
118  nn = max( n, nb, 2 )
119  np0 = numroc( nn, nb, 0, 0, nprow )
120  mq0 = numroc( max( neig, nb, 2 ), nb, 0, 0, npcol )
121  sizesyevx = 5*n + max( 5*nn, np0*mq0+2*nb*nb ) +
122  $ iceil( neig, nprow*npcol )*nn
123  nnp = max( n, nprow*npcol+1, 4 )
124  isizesyevx = 6*nnp
125 *
126  sizesubtst = max( sizetms, sizeqtq, sizechk, sizesyevx ) +
127  $ iprepad + ipostpad
128  isizesubtst = isizesyevx + iprepad + ipostpad
129 *
130 *
131 * Allow room for A, COPYA and Z and DIAG, WIN, WNEW, GAP, WORK
132 *
133  sizetst = 3*( lda*np+iprepad+ipostpad ) +
134  $ 4*( n+iprepad+ipostpad ) + sizesubtst
135 *
136 * Allow room for IFAIL, ICLUSTR, and IWORK (all in PDSYEVX)
137 *
138  isizetst = n + 2*nprow*npcol + 2*( iprepad+ipostpad ) +
139  $ isizesubtst
140 *
141  RETURN
142  END
max
#define max(A, B)
Definition: pcgemr.c:180
pdlasizesep
subroutine pdlasizesep(DESCA, IPREPAD, IPOSTPAD, SIZEMQRLEFT, SIZEMQRRIGHT, SIZEQRF, SIZETMS, SIZEQTQ, SIZECHK, SIZESYEVX, ISIZESYEVX, SIZESUBTST, ISIZESUBTST, SIZETST, ISIZETST)
Definition: pdlasizesep.f:8