1 SUBROUTINE ZUNG2R
( M
, N
, K
, A
, LDA
, TAU
, WORK
, INFO
)
3 * -- LAPACK routine
(version
3.1) --
4 * Univ
. of Tennessee
, Univ
. of California Berkeley and NAG Ltd
..
7 * .. Scalar Arguments
..
8 INTEGER INFO
, K
, LDA
, M
, N
10 * .. Array Arguments
..
11 COMPLEX*16 A
( LDA
, * ), TAU
( * ), WORK
( * )
17 * ZUNG2R generates an m by n
complex matrix Q with orthonormal columns
,
18 * which is defined as the first n columns of a product of k elementary
19 * reflectors of order m
21 * Q
= H
(1) H
(2) . . . H
(k
)
23 * as returned by ZGEQRF
.
29 * The number of rows of the matrix Q
. M
>= 0.
32 * The number of columns of the matrix Q
. M
>= N
>= 0.
35 * The number of elementary reflectors whose product defines the
36 * matrix Q
. N
>= K
>= 0.
38 * A
(input
/output
) COMPLEX*16 array
, dimension (LDA
,N
)
39 * On entry
, the i
-th column must contain the vector which
40 * defines the elementary reflector H
(i
), for i
= 1,2,...,k
, as
41 * returned by ZGEQRF in the first k columns of its array
43 * On exit
, the m by n matrix Q
.
46 * The first
dimension of the array A
. LDA
>= max
(1,M
).
48 * TAU
(input
) COMPLEX*16 array
, dimension (K
)
49 * TAU
(i
) must contain the scalar factor of the elementary
50 * reflector H
(i
), as returned by ZGEQRF
.
52 * WORK
(workspace
) COMPLEX*16 array
, dimension (N
)
54 * INFO
(output
) INTEGER
55 * = 0: successful exit
56 * < 0: if INFO
= -i
, the i
-th argument has an illegal value
58 * =====================================================================
62 PARAMETER ( ONE
= ( 1.0D
+0, 0.0D
+0 ),
63 $ ZERO
= ( 0.0D
+0, 0.0D
+0 ) )
68 * .. External Subroutines
..
69 EXTERNAL XERBLA
, ZLARF
, ZSCAL
71 * .. Intrinsic Functions
..
74 * .. Executable Statements
..
76 * Test the input arguments
81 ELSE IF( N
.LT
.0 .OR
. N
.GT
.M
) THEN
83 ELSE IF( K
.LT
.0 .OR
. K
.GT
.N
) THEN
85 ELSE IF( LDA
.LT
.MAX
( 1, M
) ) THEN
89 CALL XERBLA
( 'ZUNG2R', -INFO
)
93 * Quick
return if possible
98 * Initialise columns k
+1:n
to columns of the unit matrix
109 * Apply H
(i
) to A
(i
:m
,i
:n
) from the left
113 CALL ZLARF
( 'Left', M
-I
+1, N
-I
, A
( I
, I
), 1, TAU
( I
),
114 $ A
( I
, I
+1 ), LDA
, WORK
)
117 $
CALL ZSCAL
( M
-I
, -TAU
( I
), A
( I
+1, I
), 1 )
118 A
( I
, I
) = ONE
- TAU
( I
)
120 * Set A
(1:i
-1,i
) to zero