1      SUBROUTINE PCTZRZRV( M, N, A, IA, JA, DESCA, TAU, WORK )
2*
3*  -- ScaLAPACK routine (version 1.7) --
4*     University of Tennessee, Knoxville, Oak Ridge National Laboratory,
5*     and University of California, Berkeley.
6*     May 28, 2001
7*
8*     .. Scalar Arguments ..
9      INTEGER            IA, JA, M, N
10*     ..
11*     .. Array Arguments ..
12      INTEGER            DESCA( * )
13      COMPLEX            A( * ),  TAU( * ), WORK( * )
14*     ..
15*
16*  Purpose
17*  =======
18*
19*  PCTZRZRV computes sub( A ) = A(IA:IA+M-1,JA:JA+N-1) from T, Z
20*  computed by PCTZRZF.
21*
22*  Notes
23*  =====
24*
25*  Each global data object is described by an associated description
26*  vector.  This vector stores the information required to establish
27*  the mapping between an object element and its corresponding process
28*  and memory location.
29*
30*  Let A be a generic term for any 2D block cyclicly distributed array.
31*  Such a global array has an associated description vector DESCA.
32*  In the following comments, the character _ should be read as
33*  "of the global array".
34*
35*  NOTATION        STORED IN      EXPLANATION
36*  --------------- -------------- --------------------------------------
37*  DTYPE_A(global) DESCA( DTYPE_ )The descriptor type.  In this case,
38*                                 DTYPE_A = 1.
39*  CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
40*                                 the BLACS process grid A is distribu-
41*                                 ted over. The context itself is glo-
42*                                 bal, but the handle (the integer
43*                                 value) may vary.
44*  M_A    (global) DESCA( M_ )    The number of rows in the global
45*                                 array A.
46*  N_A    (global) DESCA( N_ )    The number of columns in the global
47*                                 array A.
48*  MB_A   (global) DESCA( MB_ )   The blocking factor used to distribute
49*                                 the rows of the array.
50*  NB_A   (global) DESCA( NB_ )   The blocking factor used to distribute
51*                                 the columns of the array.
52*  RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
53*                                 row of the array A is distributed.
54*  CSRC_A (global) DESCA( CSRC_ ) The process column over which the
55*                                 first column of the array A is
56*                                 distributed.
57*  LLD_A  (local)  DESCA( LLD_ )  The leading dimension of the local
58*                                 array.  LLD_A >= MAX(1,LOCr(M_A)).
59*
60*  Let K be the number of rows or columns of a distributed matrix,
61*  and assume that its process grid has dimension p x q.
62*  LOCr( K ) denotes the number of elements of K that a process
63*  would receive if K were distributed over the p processes of its
64*  process column.
65*  Similarly, LOCc( K ) denotes the number of elements of K that a
66*  process would receive if K were distributed over the q processes of
67*  its process row.
68*  The values of LOCr() and LOCc() may be determined via a call to the
69*  ScaLAPACK tool function, NUMROC:
70*          LOCr( M ) = NUMROC( M, MB_A, MYROW, RSRC_A, NPROW ),
71*          LOCc( N ) = NUMROC( N, NB_A, MYCOL, CSRC_A, NPCOL ).
72*  An upper bound for these quantities may be computed by:
73*          LOCr( M ) <= ceil( ceil(M/MB_A)/NPROW )*MB_A
74*          LOCc( N ) <= ceil( ceil(N/NB_A)/NPCOL )*NB_A
75*
76*  Arguments
77*  =========
78*
79*  M       (global input) INTEGER
80*          The number of rows to be operated on, i.e. the number of rows
81*          of the distributed submatrix sub( A ). M >= 0.
82*
83*  N       (global input) INTEGER
84*          The number of columns to be operated on, i.e. the number of
85*          columns of the distributed submatrix sub( A ). N >= M >= 0.
86*
87*  A       (local input/local output) COMPLEX pointer into the
88*          local memory to an array of dimension (LLD_A, LOCc(JA+N-1)).
89*          On entry, sub( A ) contains the the factors T and Z computed
90*          by PCTZRZF. On exit, the original matrix is restored.
91*
92*  IA      (global input) INTEGER
93*          The row index in the global array A indicating the first
94*          row of sub( A ).
95*
96*  JA      (global input) INTEGER
97*          The column index in the global array A indicating the
98*          first column of sub( A ).
99*
100*  DESCA   (global and local input) INTEGER array of dimension DLEN_.
101*          The array descriptor for the distributed matrix A.
102*
103*  TAU     (local input) COMPLEX, array, dimension LOCr(M_A).
104*          This array contains the scalar factors TAU of the elementary
105*          reflectors computed by PCTZRZF. TAU is tied to the dis-
106*          tributed matrix A.
107*
108*  WORK    (local workspace) COMPLEX array, dimension (LWORK)
109*          LWORK = MB_A * ( Mp0 + 2*Nq0 + MB_A ), where
110*          Mp0   = NUMROC( M+IROFF, MB_A, MYROW, IAROW, NPROW ) * NB_A,
111*          Nq0   = NUMROC( N+ICOFF, NB_A, MYCOL, IACOL, NPCOL ) * MB_A,
112*          IROFF = MOD( IA-1, MB_A ), ICOFF = MOD( JA-1, NB_A ),
113*          IAROW = INDXG2P( IA, DESCA( MB_ ), MYROW, DESCA( RSRC_ ),
114*                           NPROW ),
115*          IACOL = INDXG2P( JA, DESCA( NB_ ), MYCOL, DESCA( CSRC_ ),
116*                           NPCOL ),
117*          and NUMROC, INDXG2P are ScaLAPACK tool functions.
118*
119*  =====================================================================
120*
121*     .. Parameters ..
122      INTEGER            BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
123     $                   LLD_, MB_, M_, NB_, N_, RSRC_
124      PARAMETER          ( BLOCK_CYCLIC_2D = 1, DLEN_ = 9, DTYPE_ = 1,
125     $                     CTXT_ = 2, M_ = 3, N_ = 4, MB_ = 5, NB_ = 6,
126     $                     RSRC_ = 7, CSRC_ = 8, LLD_ = 9 )
127      COMPLEX            ZERO
128      PARAMETER          ( ZERO = ( 0.0E+0, 0.0E+0 ) )
129*     ..
130*     .. Local Scalars ..
131      CHARACTER          COLBTOP, ROWBTOP
132      INTEGER            I, IACOL, IAROW, IB, ICOFF, ICTXT, IIA, IN,
133     $                   IPT, IPV, IPW, JJA, JM1, JV, L, MYCOL, MYROW,
134     $                   NPCOL, NPROW, NQ
135*     ..
136*     .. Local Arrays ..
137      INTEGER            DESCV( DLEN_ )
138*     ..
139*     .. External Subroutines ..
140      EXTERNAL           BLACS_GRIDINFO, DESCSET, INFOG2L, PCLACPY,
141     $                   PCLARZB, PCLARZT, PCLASET, PB_TOPGET,
142     $                   PB_TOPSET
143*     ..
144*     .. External Functions ..
145      INTEGER            ICEIL, NUMROC
146      EXTERNAL           ICEIL, NUMROC
147*     ..
148*     .. Intrinsic Functions ..
149      INTRINSIC          MAX, MIN, MOD
150*     ..
151*     .. Executable Statements ..
152*
153*     Get grid parameters
154*
155      ICTXT = DESCA( CTXT_ )
156      CALL BLACS_GRIDINFO( ICTXT, NPROW, NPCOL, MYROW, MYCOL )
157*
158*     Quick return if possible
159*
160      IF( N.LT.M )
161     $   RETURN
162*
163      L = N - M
164      JM1 = JA + MIN( M+1, N ) - 1
165      IN = MIN( ICEIL( IA, DESCA( MB_ ) ) * DESCA( MB_ ), IA+M-1 )
166      ICOFF = MOD( JA-1, DESCA( NB_ ) )
167      CALL INFOG2L( IA, JA, DESCA, NPROW, NPCOL, MYROW, MYCOL, IIA, JJA,
168     $              IAROW, IACOL )
169      NQ = NUMROC( N+ICOFF, DESCA( NB_ ), MYCOL, IACOL, NPCOL )
170      IPV = 1
171      IPT = IPV + NQ * DESCA( MB_ )
172      IPW = IPT + DESCA( MB_ ) * DESCA( MB_ )
173      CALL PB_TOPGET( ICTXT, 'Broadcast', 'Rowwise', ROWBTOP )
174      CALL PB_TOPGET( ICTXT, 'Broadcast', 'Columnwise', COLBTOP )
175      CALL PB_TOPSET( ICTXT, 'Broadcast', 'Rowwise', ' ' )
176      CALL PB_TOPSET( ICTXT, 'Broadcast', 'Columnwise', 'I-ring' )
177*
178      CALL DESCSET( DESCV, DESCA( MB_ ), N + ICOFF, DESCA( MB_ ),
179     $              DESCA( NB_ ), IAROW, IACOL, ICTXT, DESCA( MB_ ) )
180*
181*     Handle first block separately
182*
183      IB = IN - IA + 1
184      JV = ICOFF + JM1 - JA + 1
185*
186*     Compute upper triangular matrix T
187*
188      CALL PCLARZT( 'Backward', 'Rowwise', L, IB, A, IA, JM1, DESCA,
189     $              TAU, WORK( IPT ), WORK( IPW ) )
190*
191*     Copy Householder vectors into workspace
192*
193      CALL PCLACPY( 'All', IB, L, A, IA, JM1, DESCA, WORK( IPV ), 1,
194     $              JV, DESCV )
195*
196*     Save temporarily strict lower part of A(IA:IA+IB-1,JA:JA+IB-1)
197*
198      CALL PCLACPY( 'Lower', IB-1, IB-1, A, IA+1, JA, DESCA,
199     $              WORK( IPV ), 1, ICOFF+1, DESCV )
200*
201*     Zeroes the row panel of sub( A ) to get T(IA:IN,JA:JA+N-1)
202*
203      CALL PCLASET( 'All', IB, L, ZERO, ZERO, A, IA, JM1, DESCA )
204      CALL PCLASET( 'Lower', IB-1, IB-1, ZERO, ZERO, A, IA+1, JA,
205     $              DESCA )
206*
207*     Apply block Householder transformation
208*
209      CALL PCLARZB( 'Right', 'Conjugate transpose', 'Backward',
210     $              'Rowwise', IN-IA+1, N, IB, L, WORK( IPV ), 1, JV,
211     $              DESCV, WORK( IPT ), A, IA, JA, DESCA, WORK( IPW ) )
212*
213*     Restore strict lower part of A( IA:IA+IB-1, JA:JA+N-1 )
214*
215      CALL PCLACPY( 'Lower', IB-1, IB-1, WORK( IPV ), 1, ICOFF+1, DESCV,
216     $              A, IA+1, JA, DESCA )
217*
218      DESCV( RSRC_ ) = MOD( DESCV( RSRC_ ) + 1, NPROW )
219*
220*     Loop over the remaining row blocks
221*
222      DO 10 I = IN+1, IA+M-1, DESCA( MB_ )
223         IB = MIN( IA+M-I, DESCA( MB_ ) )
224*
225*        Compute upper triangular matrix T
226*
227         CALL PCLARZT( 'Backward', 'Rowwise', L, IB, A, I, JM1, DESCA,
228     $                 TAU, WORK( IPT ), WORK( IPW ) )
229*
230*        Copy Householder vectors into workspace
231*
232         CALL PCLACPY( 'All', IB, L, A, I, JM1, DESCA, WORK( IPV ), 1,
233     $                 JV, DESCV )
234*
235*        Save temporarily strict lower part of A(I:I+IB-1,J:J+IB-1 )
236*
237         CALL PCLACPY( 'Lower', IB-1, IB-1, A, I+1, JA+I-IA, DESCA,
238     $                 WORK( IPV ), 1, ICOFF+1+I-IA, DESCV )
239*
240*        Zeoes the row panel of sub( A ) to get T(IA:I-1,JA+I-IA:JA+N-1)
241*
242         CALL PCLASET( 'All', IB, L, ZERO, ZERO, A, I, JM1, DESCA )
243         CALL PCLASET( 'Lower', IB-1, IB-1, ZERO, ZERO, A, I+1, JA+I-IA,
244     $                 DESCA )
245*
246*        Apply block Householder transformation
247*
248         CALL PCLARZB( 'Right', 'Conjugate transpose', 'Backward',
249     $                 'Rowwise', I+IB-IA, N-I+IA, IB, L, WORK( IPV ),
250     $                 1, JV, DESCV, WORK( IPT ), A, IA, JA+I-IA, DESCA,
251     $                 WORK( IPW ) )
252*
253         CALL PCLACPY( 'Lower', IB-1, IB-1, WORK( IPV ), 1,
254     $                 ICOFF+1+I-IA, DESCV, A, I+1, JA+I-IA, DESCA )
255*
256         DESCV( RSRC_ ) = MOD( DESCV( RSRC_ ) + 1, NPROW )
257*
258   10 CONTINUE
259*
260      CALL PB_TOPSET( ICTXT, 'Broadcast', 'Rowwise', ROWBTOP )
261      CALL PB_TOPSET( ICTXT, 'Broadcast', 'Columnwise', COLBTOP )
262*
263      RETURN
264*
265*     End of PCTZRZRV
266*
267      END
268