1      SUBROUTINE PCUNMHR( SIDE, TRANS, M, N, ILO, IHI, A, IA, JA, DESCA,
2     $                    TAU, C, IC, JC, DESCC, WORK, LWORK, INFO )
3*
4*  -- ScaLAPACK routine (version 1.7) --
5*     University of Tennessee, Knoxville, Oak Ridge National Laboratory,
6*     and University of California, Berkeley.
7*     May 1, 1997
8*
9*     .. Scalar Arguments ..
10      CHARACTER          SIDE, TRANS
11      INTEGER            IA, IC, IHI, ILO, INFO, JA, JC, LWORK, M, N
12*     ..
13*     .. Array Arguments ..
14      INTEGER            DESCA( * ), DESCC( * )
15      COMPLEX            A( * ), C( * ), TAU( * ), WORK( * )
16*     ..
17*
18*  Purpose
19*  =======
20*
21*  PCUNMHR overwrites the general complex M-by-N distributed matrix
22*  sub( C ) = C(IC:IC+M-1,JC:JC+N-1) with
23*
24*                       SIDE = 'L'           SIDE = 'R'
25*  TRANS = 'N':      Q * sub( C )          sub( C ) * Q
26*  TRANS = 'C':      Q**H * sub( C )       sub( C ) * Q**H
27*
28*  where Q is a complex unitary distributed matrix of order nq, with
29*  nq = m if SIDE = 'L' and nq = n if SIDE = 'R'. Q is defined as the
30*  product of IHI-ILO elementary reflectors, as returned by PCGEHRD:
31*
32*  Q = H(ilo) H(ilo+1) . . . H(ihi-1).
33*
34*  Notes
35*  =====
36*
37*  Each global data object is described by an associated description
38*  vector.  This vector stores the information required to establish
39*  the mapping between an object element and its corresponding process
40*  and memory location.
41*
42*  Let A be a generic term for any 2D block cyclicly distributed array.
43*  Such a global array has an associated description vector DESCA.
44*  In the following comments, the character _ should be read as
45*  "of the global array".
46*
47*  NOTATION        STORED IN      EXPLANATION
48*  --------------- -------------- --------------------------------------
49*  DTYPE_A(global) DESCA( DTYPE_ )The descriptor type.  In this case,
50*                                 DTYPE_A = 1.
51*  CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
52*                                 the BLACS process grid A is distribu-
53*                                 ted over. The context itself is glo-
54*                                 bal, but the handle (the integer
55*                                 value) may vary.
56*  M_A    (global) DESCA( M_ )    The number of rows in the global
57*                                 array A.
58*  N_A    (global) DESCA( N_ )    The number of columns in the global
59*                                 array A.
60*  MB_A   (global) DESCA( MB_ )   The blocking factor used to distribute
61*                                 the rows of the array.
62*  NB_A   (global) DESCA( NB_ )   The blocking factor used to distribute
63*                                 the columns of the array.
64*  RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
65*                                 row of the array A is distributed.
66*  CSRC_A (global) DESCA( CSRC_ ) The process column over which the
67*                                 first column of the array A is
68*                                 distributed.
69*  LLD_A  (local)  DESCA( LLD_ )  The leading dimension of the local
70*                                 array.  LLD_A >= MAX(1,LOCr(M_A)).
71*
72*  Let K be the number of rows or columns of a distributed matrix,
73*  and assume that its process grid has dimension p x q.
74*  LOCr( K ) denotes the number of elements of K that a process
75*  would receive if K were distributed over the p processes of its
76*  process column.
77*  Similarly, LOCc( K ) denotes the number of elements of K that a
78*  process would receive if K were distributed over the q processes of
79*  its process row.
80*  The values of LOCr() and LOCc() may be determined via a call to the
81*  ScaLAPACK tool function, NUMROC:
82*          LOCr( M ) = NUMROC( M, MB_A, MYROW, RSRC_A, NPROW ),
83*          LOCc( N ) = NUMROC( N, NB_A, MYCOL, CSRC_A, NPCOL ).
84*  An upper bound for these quantities may be computed by:
85*          LOCr( M ) <= ceil( ceil(M/MB_A)/NPROW )*MB_A
86*          LOCc( N ) <= ceil( ceil(N/NB_A)/NPCOL )*NB_A
87*
88*  Arguments
89*  =========
90*
91*  SIDE    (global input) CHARACTER
92*          = 'L': apply Q or Q**H from the Left;
93*          = 'R': apply Q or Q**H from the Right.
94*
95*  TRANS   (global input) CHARACTER
96*          = 'N':  No transpose, apply Q;
97*          = 'C':  Conjugate transpose, apply Q**H.
98*
99*  M       (global input) INTEGER
100*          The number of rows to be operated on i.e the number of rows
101*          of the distributed submatrix sub( C ). M >= 0.
102*
103*  N       (global input) INTEGER
104*          The number of columns to be operated on i.e the number of
105*          columns of the distributed submatrix sub( C ). N >= 0.
106*
107*  ILO     (global input) INTEGER
108*  IHI     (global input) INTEGER
109*          ILO and IHI must have the same values as in the previous call
110*          of PCGEHRD. Q is equal to the unit matrix except in the
111*          distributed submatrix Q(ia+ilo:ia+ihi-1,ia+ilo:ja+ihi-1).
112*          If SIDE = 'L', 1 <= ILO <= IHI <= max(1,M);
113*          if SIDE = 'R', 1 <= ILO <= IHI <= max(1,N);
114*          ILO and IHI are relative indexes.
115*
116*  A       (local input) COMPLEX pointer into the local memory
117*          to an array of dimension (LLD_A,LOCc(JA+M-1)) if SIDE='L',
118*          and (LLD_A,LOCc(JA+N-1)) if SIDE = 'R'. The vectors which
119*          define the elementary reflectors, as returned by PCGEHRD.
120*
121*  IA      (global input) INTEGER
122*          The row index in the global array A indicating the first
123*          row of sub( A ).
124*
125*  JA      (global input) INTEGER
126*          The column index in the global array A indicating the
127*          first column of sub( A ).
128*
129*  DESCA   (global and local input) INTEGER array of dimension DLEN_.
130*          The array descriptor for the distributed matrix A.
131*
132*  TAU     (local input) COMPLEX, array, dimension LOCc(JA+M-2)
133*          if SIDE = 'L', and LOCc(JA+N-2) if SIDE = 'R'. This array
134*          contains the scalar factors TAU(j) of the elementary
135*          reflectors H(j) as returned by PCGEHRD. TAU is tied to
136*          the distributed matrix A.
137*
138*  C       (local input/local output) COMPLEX pointer into the
139*          local memory to an array of dimension (LLD_C,LOCc(JC+N-1)).
140*          On entry, the local pieces of the distributed matrix sub(C).
141*          On exit, sub( C ) is overwritten by Q*sub( C ) or Q'*sub( C )
142*          or sub( C )*Q' or sub( C )*Q.
143*
144*  IC      (global input) INTEGER
145*          The row index in the global array C indicating the first
146*          row of sub( C ).
147*
148*  JC      (global input) INTEGER
149*          The column index in the global array C indicating the
150*          first column of sub( C ).
151*
152*  DESCC   (global and local input) INTEGER array of dimension DLEN_.
153*          The array descriptor for the distributed matrix C.
154*
155*  WORK    (local workspace/local output) COMPLEX array,
156*                                                     dimension (LWORK)
157*          On exit, WORK(1) returns the minimal and optimal LWORK.
158*
159*  LWORK   (local or global input) INTEGER
160*          The dimension of the array WORK.
161*          LWORK is local input and must be at least
162*
163*          IAA = IA + ILO; JAA = JA+ILO-1;
164*          If SIDE = 'L',
165*            MI = IHI-ILO; NI = N; ICC = IC + ILO; JCC = JC;
166*            LWORK >= MAX( (NB_A*(NB_A-1))/2, (NqC0 + MpC0)*NB_A ) +
167*                     NB_A * NB_A
168*          else if SIDE = 'R',
169*            MI = M; NI = IHI-ILO; ICC = IC; JCC = JC + ILO;
170*            LWORK >= MAX( (NB_A*(NB_A-1))/2, ( NqC0 + MAX( NpA0 +
171*                     NUMROC( NUMROC( NI+ICOFFC, NB_A, 0, 0, NPCOL ),
172*                             NB_A, 0, 0, LCMQ ), MpC0 ) )*NB_A ) +
173*                     NB_A * NB_A
174*          end if
175*
176*          where LCMQ = LCM / NPCOL with LCM = ICLM( NPROW, NPCOL ),
177*
178*          IROFFA = MOD( IAA-1, MB_A ), ICOFFA = MOD( JAA-1, NB_A ),
179*          IAROW = INDXG2P( IAA, MB_A, MYROW, RSRC_A, NPROW ),
180*          NpA0 = NUMROC( NI+IROFFA, MB_A, MYROW, IAROW, NPROW ),
181*
182*          IROFFC = MOD( ICC-1, MB_C ), ICOFFC = MOD( JCC-1, NB_C ),
183*          ICROW = INDXG2P( ICC, MB_C, MYROW, RSRC_C, NPROW ),
184*          ICCOL = INDXG2P( JCC, NB_C, MYCOL, CSRC_C, NPCOL ),
185*          MpC0 = NUMROC( MI+IROFFC, MB_C, MYROW, ICROW, NPROW ),
186*          NqC0 = NUMROC( NI+ICOFFC, NB_C, MYCOL, ICCOL, NPCOL ),
187*
188*          ILCM, INDXG2P and NUMROC are ScaLAPACK tool functions;
189*          MYROW, MYCOL, NPROW and NPCOL can be determined by calling
190*          the subroutine BLACS_GRIDINFO.
191*
192*          If LWORK = -1, then LWORK is global input and a workspace
193*          query is assumed; the routine only calculates the minimum
194*          and optimal size for all work arrays. Each of these
195*          values is returned in the first entry of the corresponding
196*          work array, and no error message is issued by PXERBLA.
197*
198*
199*  INFO    (global output) INTEGER
200*          = 0:  successful exit
201*          < 0:  If the i-th argument is an array and the j-entry had
202*                an illegal value, then INFO = -(i*100+j), if the i-th
203*                argument is a scalar and had an illegal value, then
204*                INFO = -i.
205*
206*  Alignment requirements
207*  ======================
208*
209*  The distributed submatrices A(IA:*, JA:*) and C(IC:IC+M-1,JC:JC+N-1)
210*  must verify some alignment properties, namely the following
211*  expressions should be true:
212*
213*  If SIDE = 'L',
214*    ( MB_A.EQ.MB_C .AND. IROFFA.EQ.IROFFC .AND. IAROW.EQ.ICROW )
215*  If SIDE = 'R',
216*    ( MB_A.EQ.NB_C .AND. IROFFA.EQ.ICOFFC )
217*
218*  =====================================================================
219*
220*     .. Parameters ..
221      INTEGER            BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
222     $                   LLD_, MB_, M_, NB_, N_, RSRC_
223      PARAMETER          ( BLOCK_CYCLIC_2D = 1, DLEN_ = 9, DTYPE_ = 1,
224     $                     CTXT_ = 2, M_ = 3, N_ = 4, MB_ = 5, NB_ = 6,
225     $                     RSRC_ = 7, CSRC_ = 8, LLD_ = 9 )
226*     ..
227*     .. Local Scalars ..
228      LOGICAL            LEFT, LQUERY, NOTRAN
229      INTEGER            IAA, IAROW, ICC, ICCOL, ICOFFC, ICROW, ICTXT,
230     $                   IINFO, IROFFA, IROFFC, JAA, JCC, LCM, LCMQ,
231     $                   LWMIN, MI, MPC0, MYCOL, MYROW, NH, NI, NPA0,
232     $                   NPCOL, NPROW, NQ, NQC0
233*     ..
234*     .. Local Arrays ..
235      INTEGER            IDUM1( 5 ), IDUM2( 5 )
236*     ..
237*     .. External Subroutines ..
238      EXTERNAL           BLACS_GRIDINFO, CHK1MAT, PCHK2MAT, PCUNMQR,
239     $                   PXERBLA
240*     ..
241*     .. External Functions ..
242      LOGICAL            LSAME
243      INTEGER            ILCM, INDXG2P, NUMROC
244      EXTERNAL           ILCM, INDXG2P, LSAME, NUMROC
245*     ..
246*     .. Intrinsic Functions ..
247      INTRINSIC          CMPLX, ICHAR, MAX, MIN, MOD, REAL
248*     ..
249*     .. Executable Statements ..
250*
251*     Get grid parameters
252*
253      ICTXT = DESCA( CTXT_ )
254      CALL BLACS_GRIDINFO( ICTXT, NPROW, NPCOL, MYROW, MYCOL )
255*
256*     Test the input parameters
257*
258      INFO = 0
259      NH = IHI - ILO
260      IF( NPROW.EQ.-1 ) THEN
261         INFO = -(1000+CTXT_)
262      ELSE
263         LEFT = LSAME( SIDE, 'L' )
264         NOTRAN = LSAME( TRANS, 'N' )
265         IAA = IA + ILO
266         JAA = JA + ILO - 1
267*
268*        NQ is the order of Q
269*
270         IF( LEFT ) THEN
271            NQ = M
272            MI = NH
273            NI = N
274            ICC = IC + ILO
275            JCC = JC
276            CALL CHK1MAT( M, 3, M, 3, IA, JA, DESCA, 10, INFO )
277         ELSE
278            NQ = N
279            MI = M
280            NI = NH
281            ICC = IC
282            JCC = JC + ILO
283            CALL CHK1MAT( N, 4, N, 4, IA, JA, DESCA, 10, INFO )
284         END IF
285         CALL CHK1MAT( M, 3, N, 4, IC, JC, DESCC, 15, INFO )
286         IF( INFO.EQ.0 ) THEN
287            IROFFA = MOD( IAA-1, DESCA( MB_ ) )
288            IROFFC = MOD( ICC-1, DESCC( MB_ ) )
289            ICOFFC = MOD( JCC-1, DESCC( NB_ ) )
290            IAROW = INDXG2P( IAA, DESCA( MB_ ), MYROW, DESCA( RSRC_ ),
291     $                       NPROW )
292            ICROW = INDXG2P( ICC, DESCC( MB_ ), MYROW, DESCC( RSRC_ ),
293     $                       NPROW )
294            ICCOL = INDXG2P( JCC, DESCC( NB_ ), MYCOL, DESCC( CSRC_ ),
295     $                       NPCOL )
296            MPC0 = NUMROC( MI+IROFFC, DESCC( MB_ ), MYROW, ICROW,
297     $                     NPROW )
298            NQC0 = NUMROC( NI+ICOFFC, DESCC( NB_ ), MYCOL, ICCOL,
299     $                     NPCOL )
300*
301            IF( LEFT ) THEN
302               LWMIN = MAX( ( DESCA( NB_ ) * ( DESCA( NB_ ) - 1 ) ) / 2,
303     $                      ( MPC0 + NQC0 ) * DESCA( NB_ ) ) +
304     $                 DESCA( NB_ ) * DESCA( NB_ )
305            ELSE
306               NPA0 = NUMROC( NI+IROFFA, DESCA( MB_ ), MYROW, IAROW,
307     $                        NPROW )
308               LCM = ILCM( NPROW, NPCOL )
309               LCMQ = LCM / NPCOL
310               LWMIN =  MAX( ( DESCA( NB_ ) * ( DESCA( NB_ ) - 1 ) )
311     $                  / 2, ( NQC0 + MAX( NPA0 + NUMROC( NUMROC(
312     $                  NI+ICOFFC, DESCA( NB_ ), 0, 0, NPCOL ),
313     $                  DESCA( NB_ ), 0, 0, LCMQ ), MPC0 ) ) *
314     $                  DESCA( NB_ ) ) + DESCA( NB_ ) * DESCA( NB_ )
315            END IF
316*
317            WORK( 1 ) = CMPLX( REAL( LWMIN ) )
318            LQUERY = ( LWORK.EQ.-1 )
319            IF( .NOT.LEFT .AND. .NOT.LSAME( SIDE, 'R' ) ) THEN
320               INFO = -1
321            ELSE IF( .NOT.NOTRAN .AND. .NOT.LSAME( TRANS, 'C' ) ) THEN
322               INFO = -2
323            ELSE IF( ILO.LT.1 .OR. ILO.GT.MAX( 1, NQ ) ) THEN
324               INFO = -5
325            ELSE IF( IHI.LT.MIN( ILO, NQ ) .OR. IHI.GT.NQ ) THEN
326               INFO = -6
327            ELSE IF( .NOT.LEFT .AND. DESCA( MB_ ).NE.DESCC( NB_ ) ) THEN
328               INFO = -(1000+NB_)
329            ELSE IF( LEFT .AND. IROFFA.NE.IROFFC ) THEN
330               INFO = -13
331            ELSE IF( LEFT .AND. IAROW.NE.ICROW ) THEN
332               INFO = -13
333            ELSE IF( .NOT.LEFT .AND. IROFFA.NE.ICOFFC ) THEN
334               INFO = -14
335            ELSE IF( LEFT .AND. DESCA( MB_ ).NE.DESCC( MB_ ) ) THEN
336               INFO = -(1500+MB_)
337            ELSE IF( ICTXT.NE.DESCC( CTXT_ ) ) THEN
338               INFO = -(1500+CTXT_)
339            ELSE IF( LWORK.LT.LWMIN .AND. .NOT.LQUERY ) THEN
340               INFO = -17
341            END IF
342         END IF
343*
344         IF( LEFT ) THEN
345            IDUM1( 1 ) = ICHAR( 'L' )
346         ELSE
347            IDUM1( 1 ) = ICHAR( 'R' )
348         END IF
349         IDUM2( 1 ) = 1
350         IF( NOTRAN ) THEN
351            IDUM1( 2 ) = ICHAR( 'N' )
352         ELSE
353            IDUM1( 2 ) = ICHAR( 'C' )
354         END IF
355         IDUM2( 2 ) = 2
356         IDUM1( 3 ) = ILO
357         IDUM2( 3 ) = 5
358         IDUM1( 4 ) = IHI
359         IDUM2( 4 ) = 6
360         IF( LWORK.EQ.-1 ) THEN
361            IDUM1( 5 ) = -1
362         ELSE
363            IDUM1( 5 ) = 1
364         END IF
365         IDUM2( 5 ) = 17
366         IF( LEFT ) THEN
367            CALL PCHK2MAT( M, 3, M, 3, IA, JA, DESCA, 10, M, 3, N, 4,
368     $                     IC, JC, DESCC, 15, 5, IDUM1, IDUM2, INFO )
369         ELSE
370            CALL PCHK2MAT( N, 4, N, 4, IA, JA, DESCA, 10, M, 3, N, 4,
371     $                     IC, JC, DESCC, 15, 5, IDUM1, IDUM2, INFO )
372         END IF
373      END IF
374*
375      IF( INFO.NE.0 ) THEN
376         CALL PXERBLA( ICTXT, 'PCUNMHR', -INFO )
377         RETURN
378      ELSE IF( LQUERY ) THEN
379         RETURN
380      END IF
381*
382*     Quick return if possible
383*
384      IF( M.EQ.0 .OR. N.EQ.0 .OR. NH.EQ.0 )
385     $   RETURN
386*
387      CALL PCUNMQR( SIDE, TRANS, MI, NI, NH, A, IAA, JAA, DESCA, TAU,
388     $              C, ICC, JCC, DESCC, WORK, LWORK, IINFO )
389*
390      WORK( 1 ) = CMPLX( REAL( LWMIN ) )
391*
392      RETURN
393*
394*     End of PCUNMHR
395*
396      END
397