2329
|
1 SUBROUTINE ZUNGL2( M, N, K, A, LDA, TAU, WORK, INFO ) |
|
2 * |
3333
|
3 * -- LAPACK routine (version 3.0) -- |
2329
|
4 * Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd., |
|
5 * Courant Institute, Argonne National Lab, and Rice University |
3333
|
6 * June 30, 1999 |
2329
|
7 * |
|
8 * .. Scalar Arguments .. |
|
9 INTEGER INFO, K, LDA, M, N |
|
10 * .. |
|
11 * .. Array Arguments .. |
|
12 COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * ) |
|
13 * .. |
|
14 * |
|
15 * Purpose |
|
16 * ======= |
|
17 * |
|
18 * ZUNGL2 generates an m-by-n complex matrix Q with orthonormal rows, |
|
19 * which is defined as the first m rows of a product of k elementary |
|
20 * reflectors of order n |
|
21 * |
|
22 * Q = H(k)' . . . H(2)' H(1)' |
|
23 * |
|
24 * as returned by ZGELQF. |
|
25 * |
|
26 * Arguments |
|
27 * ========= |
|
28 * |
|
29 * M (input) INTEGER |
|
30 * The number of rows of the matrix Q. M >= 0. |
|
31 * |
|
32 * N (input) INTEGER |
|
33 * The number of columns of the matrix Q. N >= M. |
|
34 * |
|
35 * K (input) INTEGER |
|
36 * The number of elementary reflectors whose product defines the |
|
37 * matrix Q. M >= K >= 0. |
|
38 * |
|
39 * A (input/output) COMPLEX*16 array, dimension (LDA,N) |
|
40 * On entry, the i-th row must contain the vector which defines |
|
41 * the elementary reflector H(i), for i = 1,2,...,k, as returned |
|
42 * by ZGELQF in the first k rows of its array argument A. |
|
43 * On exit, the m by n matrix Q. |
|
44 * |
|
45 * LDA (input) INTEGER |
|
46 * The first dimension of the array A. LDA >= max(1,M). |
|
47 * |
|
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 ZGELQF. |
|
51 * |
|
52 * WORK (workspace) COMPLEX*16 array, dimension (M) |
|
53 * |
|
54 * INFO (output) INTEGER |
|
55 * = 0: successful exit |
|
56 * < 0: if INFO = -i, the i-th argument has an illegal value |
|
57 * |
|
58 * ===================================================================== |
|
59 * |
|
60 * .. Parameters .. |
|
61 COMPLEX*16 ONE, ZERO |
|
62 PARAMETER ( ONE = ( 1.0D+0, 0.0D+0 ), |
|
63 $ ZERO = ( 0.0D+0, 0.0D+0 ) ) |
|
64 * .. |
|
65 * .. Local Scalars .. |
|
66 INTEGER I, J, L |
|
67 * .. |
|
68 * .. External Subroutines .. |
|
69 EXTERNAL XERBLA, ZLACGV, ZLARF, ZSCAL |
|
70 * .. |
|
71 * .. Intrinsic Functions .. |
|
72 INTRINSIC DCONJG, MAX |
|
73 * .. |
|
74 * .. Executable Statements .. |
|
75 * |
|
76 * Test the input arguments |
|
77 * |
|
78 INFO = 0 |
|
79 IF( M.LT.0 ) THEN |
|
80 INFO = -1 |
|
81 ELSE IF( N.LT.M ) THEN |
|
82 INFO = -2 |
|
83 ELSE IF( K.LT.0 .OR. K.GT.M ) THEN |
|
84 INFO = -3 |
|
85 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN |
|
86 INFO = -5 |
|
87 END IF |
|
88 IF( INFO.NE.0 ) THEN |
|
89 CALL XERBLA( 'ZUNGL2', -INFO ) |
|
90 RETURN |
|
91 END IF |
|
92 * |
|
93 * Quick return if possible |
|
94 * |
|
95 IF( M.LE.0 ) |
|
96 $ RETURN |
|
97 * |
|
98 IF( K.LT.M ) THEN |
|
99 * |
|
100 * Initialise rows k+1:m to rows of the unit matrix |
|
101 * |
|
102 DO 20 J = 1, N |
|
103 DO 10 L = K + 1, M |
|
104 A( L, J ) = ZERO |
|
105 10 CONTINUE |
|
106 IF( J.GT.K .AND. J.LE.M ) |
|
107 $ A( J, J ) = ONE |
|
108 20 CONTINUE |
|
109 END IF |
|
110 * |
|
111 DO 40 I = K, 1, -1 |
|
112 * |
|
113 * Apply H(i)' to A(i:m,i:n) from the right |
|
114 * |
|
115 IF( I.LT.N ) THEN |
|
116 CALL ZLACGV( N-I, A( I, I+1 ), LDA ) |
|
117 IF( I.LT.M ) THEN |
|
118 A( I, I ) = ONE |
|
119 CALL ZLARF( 'Right', M-I, N-I+1, A( I, I ), LDA, |
|
120 $ DCONJG( TAU( I ) ), A( I+1, I ), LDA, WORK ) |
|
121 END IF |
|
122 CALL ZSCAL( N-I, -TAU( I ), A( I, I+1 ), LDA ) |
|
123 CALL ZLACGV( N-I, A( I, I+1 ), LDA ) |
|
124 END IF |
|
125 A( I, I ) = ONE - DCONJG( TAU( I ) ) |
|
126 * |
3333
|
127 * Set A(i,1:i-1) to zero |
2329
|
128 * |
|
129 DO 30 L = 1, I - 1 |
|
130 A( I, L ) = ZERO |
|
131 30 CONTINUE |
|
132 40 CONTINUE |
|
133 RETURN |
|
134 * |
|
135 * End of ZUNGL2 |
|
136 * |
|
137 END |