2329
|
1 SUBROUTINE ZGELQ2( M, N, 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 |
|
6 * September 30, 1994 |
|
7 * |
|
8 * .. Scalar Arguments .. |
|
9 INTEGER INFO, LDA, M, N |
|
10 * .. |
|
11 * .. Array Arguments .. |
|
12 COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * ) |
|
13 * .. |
|
14 * |
|
15 * Purpose |
|
16 * ======= |
|
17 * |
|
18 * ZGELQ2 computes an LQ factorization of a complex m by n matrix A: |
|
19 * A = L * Q. |
|
20 * |
|
21 * Arguments |
|
22 * ========= |
|
23 * |
|
24 * M (input) INTEGER |
|
25 * The number of rows of the matrix A. M >= 0. |
|
26 * |
|
27 * N (input) INTEGER |
|
28 * The number of columns of the matrix A. N >= 0. |
|
29 * |
|
30 * A (input/output) COMPLEX*16 array, dimension (LDA,N) |
|
31 * On entry, the m by n matrix A. |
|
32 * On exit, the elements on and below the diagonal of the array |
|
33 * contain the m by min(m,n) lower trapezoidal matrix L (L is |
|
34 * lower triangular if m <= n); the elements above the diagonal, |
|
35 * with the array TAU, represent the unitary matrix Q as a |
|
36 * product of elementary reflectors (see Further Details). |
|
37 * |
|
38 * LDA (input) INTEGER |
|
39 * The leading dimension of the array A. LDA >= max(1,M). |
|
40 * |
|
41 * TAU (output) COMPLEX*16 array, dimension (min(M,N)) |
|
42 * The scalar factors of the elementary reflectors (see Further |
|
43 * Details). |
|
44 * |
|
45 * WORK (workspace) COMPLEX*16 array, dimension (M) |
|
46 * |
|
47 * INFO (output) INTEGER |
|
48 * = 0: successful exit |
|
49 * < 0: if INFO = -i, the i-th argument had an illegal value |
|
50 * |
|
51 * Further Details |
|
52 * =============== |
|
53 * |
|
54 * The matrix Q is represented as a product of elementary reflectors |
|
55 * |
|
56 * Q = H(k)' . . . H(2)' H(1)', where k = min(m,n). |
|
57 * |
|
58 * Each H(i) has the form |
|
59 * |
|
60 * H(i) = I - tau * v * v' |
|
61 * |
|
62 * where tau is a complex scalar, and v is a complex vector with |
|
63 * v(1:i-1) = 0 and v(i) = 1; conjg(v(i+1:n)) is stored on exit in |
|
64 * A(i,i+1:n), and tau in TAU(i). |
|
65 * |
|
66 * ===================================================================== |
|
67 * |
|
68 * .. Parameters .. |
|
69 COMPLEX*16 ONE |
|
70 PARAMETER ( ONE = ( 1.0D+0, 0.0D+0 ) ) |
|
71 * .. |
|
72 * .. Local Scalars .. |
|
73 INTEGER I, K |
|
74 COMPLEX*16 ALPHA |
|
75 * .. |
|
76 * .. External Subroutines .. |
|
77 EXTERNAL XERBLA, ZLACGV, ZLARF, ZLARFG |
|
78 * .. |
|
79 * .. Intrinsic Functions .. |
|
80 INTRINSIC MAX, MIN |
|
81 * .. |
|
82 * .. Executable Statements .. |
|
83 * |
|
84 * Test the input arguments |
|
85 * |
|
86 INFO = 0 |
|
87 IF( M.LT.0 ) THEN |
|
88 INFO = -1 |
|
89 ELSE IF( N.LT.0 ) THEN |
|
90 INFO = -2 |
|
91 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN |
|
92 INFO = -4 |
|
93 END IF |
|
94 IF( INFO.NE.0 ) THEN |
|
95 CALL XERBLA( 'ZGELQ2', -INFO ) |
|
96 RETURN |
|
97 END IF |
|
98 * |
|
99 K = MIN( M, N ) |
|
100 * |
|
101 DO 10 I = 1, K |
|
102 * |
|
103 * Generate elementary reflector H(i) to annihilate A(i,i+1:n) |
|
104 * |
|
105 CALL ZLACGV( N-I+1, A( I, I ), LDA ) |
|
106 ALPHA = A( I, I ) |
|
107 CALL ZLARFG( N-I+1, ALPHA, A( I, MIN( I+1, N ) ), LDA, |
|
108 $ TAU( I ) ) |
|
109 IF( I.LT.M ) THEN |
|
110 * |
|
111 * Apply H(i) to A(i+1:m,i:n) from the right |
|
112 * |
|
113 A( I, I ) = ONE |
|
114 CALL ZLARF( 'Right', M-I, N-I+1, A( I, I ), LDA, TAU( I ), |
|
115 $ A( I+1, I ), LDA, WORK ) |
|
116 END IF |
|
117 A( I, I ) = ALPHA |
|
118 CALL ZLACGV( N-I+1, A( I, I ), LDA ) |
|
119 10 CONTINUE |
|
120 RETURN |
|
121 * |
|
122 * End of ZGELQ2 |
|
123 * |
|
124 END |