6
7
8
9
10
11
12 IMPLICIT NONE
13
14
15 INTEGER IPOSTPAD, IPREPAD, ISIZESUBTST, ISIZESYEVR,
16 $ ISIZETST, SIZECHK, SIZEMQRLEFT, SIZEMQRRIGHT,
17 $ SIZEQRF, SIZEQTQ, SIZESUBTST, SIZESYEVR,
18 $ SIZETMS, SIZETST
19
20
21 INTEGER DESCA( * )
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61 INTEGER CTXT_, M_,
62 $ MB_, NB_, RSRC_, CSRC_, LLD_
63 parameter(
64 $ ctxt_ = 2, m_ = 3, mb_ = 5, nb_ = 6,
65 $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
66
67
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
73 INTEGER ICEIL, ILCM, INDXG2P, NUMROC
75
76
77 EXTERNAL blacs_gridinfo
78
79
81
82
83
84 n = desca( m_ )
85 nb = desca( mb_ )
86 rsrc_a = desca( rsrc_ )
87 csrc_a = desca( csrc_ )
88
89 lda = desca( lld_ )
90 CALL blacs_gridinfo( desca( ctxt_ ), nprow, npcol, myrow, mycol )
91
92 lcm =
ilcm( nprow, npcol )
93 lcmq = lcm / npcol
94 iroffa = 0
95 icoffa = 0
96 iarow =
indxg2p( 1, nb, myrow, rsrc_a, nprow )
97 iacol =
indxg2p( 1, nb, mycol, csrc_a, npcol )
98 np =
numroc( n+iroffa, nb, myrow, iarow, nprow )
99 nq =
numroc( n+icoffa, nb, mycol, iacol, npcol )
100 sizemqrleft =
max( ( nb*( nb-1 ) ) / 2, ( np+nq )*nb ) + nb*nb
101 sizemqrright =
max( ( nb*( nb-1 ) ) / 2,
103 $ npcol ), nb, 0, 0, lcmq ), np ) )*nb ) + nb*nb
104 sizeqrf = nb*np + nb*nq + nb*nb
105 sizetms = ( lda+1 )*
max( 1, nq ) +
106 $
max( sizemqrleft, sizemqrright, sizeqrf )
107
108 np0 =
numroc( n, desca( mb_ ), 0, 0, nprow )
109 mq0 =
numroc( n, desca( nb_ ), 0, 0, npcol )
110 sizeqtq = 2 +
max( desca( mb_ ), 2 )*( 2*np0+mq0 )
111 sizechk =
numroc( n, desca( nb_ ), mycol, 0, npcol )
112
113 neig = n
114 nn =
max( n, nb, 2 ) + 1
115 np0 =
numroc( nn, nb, 0, 0, nprow )
116 mq0 =
numroc(
max( neig, nb, 2 ), nb, 0, 0, npcol )
117 nnp =
max( n, nprow*npcol+1, 4 )
118
119
120 sizesyevr = 1 + 5*n +
max( 18*nn, np0*mq0+2*nb*nb ) +
121 $ (2 +
iceil( neig, nprow*npcol ))*nn
122 sizesyevr =
max(3, sizesyevr)
123
124 isizesyevr = 12*nnp + 2*n
125
126 sizesubtst =
max( sizetms, sizeqtq, sizechk, sizesyevr ) +
127 $ iprepad + ipostpad
128 isizesubtst = isizesyevr + iprepad + ipostpad
129
130
131
132 sizetst = 3*( lda*np+iprepad+ipostpad ) +
133 $ 4*( n+iprepad+ipostpad ) + sizesubtst
134
135
136
137
138 isizetst = n + 2*nprow*npcol + 2*( iprepad+ipostpad ) +
139 $ isizesubtst
140
141
142 RETURN
integer function iceil(inum, idenom)
integer function ilcm(m, n)
integer function indxg2p(indxglob, nb, iproc, isrcproc, nprocs)
integer function numroc(n, nb, iproc, isrcproc, nprocs)