LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cgeql2.f
Go to the documentation of this file.
1 *> \brief \b CGEQL2 computes the QL factorization of a general rectangular matrix using an unblocked algorithm.
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CGEQL2 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cgeql2.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cgeql2.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cgeql2.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CGEQL2( M, N, A, LDA, TAU, WORK, INFO )
22 *
23 * .. Scalar Arguments ..
24 * INTEGER INFO, LDA, M, N
25 * ..
26 * .. Array Arguments ..
27 * COMPLEX A( LDA, * ), TAU( * ), WORK( * )
28 * ..
29 *
30 *
31 *> \par Purpose:
32 * =============
33 *>
34 *> \verbatim
35 *>
36 *> CGEQL2 computes a QL factorization of a complex m by n matrix A:
37 *> A = Q * L.
38 *> \endverbatim
39 *
40 * Arguments:
41 * ==========
42 *
43 *> \param[in] M
44 *> \verbatim
45 *> M is INTEGER
46 *> The number of rows of the matrix A. M >= 0.
47 *> \endverbatim
48 *>
49 *> \param[in] N
50 *> \verbatim
51 *> N is INTEGER
52 *> The number of columns of the matrix A. N >= 0.
53 *> \endverbatim
54 *>
55 *> \param[in,out] A
56 *> \verbatim
57 *> A is COMPLEX array, dimension (LDA,N)
58 *> On entry, the m by n matrix A.
59 *> On exit, if m >= n, the lower triangle of the subarray
60 *> A(m-n+1:m,1:n) contains the n by n lower triangular matrix L;
61 *> if m <= n, the elements on and below the (n-m)-th
62 *> superdiagonal contain the m by n lower trapezoidal matrix L;
63 *> the remaining elements, with the array TAU, represent the
64 *> unitary matrix Q as a product of elementary reflectors
65 *> (see Further Details).
66 *> \endverbatim
67 *>
68 *> \param[in] LDA
69 *> \verbatim
70 *> LDA is INTEGER
71 *> The leading dimension of the array A. LDA >= max(1,M).
72 *> \endverbatim
73 *>
74 *> \param[out] TAU
75 *> \verbatim
76 *> TAU is COMPLEX array, dimension (min(M,N))
77 *> The scalar factors of the elementary reflectors (see Further
78 *> Details).
79 *> \endverbatim
80 *>
81 *> \param[out] WORK
82 *> \verbatim
83 *> WORK is COMPLEX array, dimension (N)
84 *> \endverbatim
85 *>
86 *> \param[out] INFO
87 *> \verbatim
88 *> INFO is INTEGER
89 *> = 0: successful exit
90 *> < 0: if INFO = -i, the i-th argument had an illegal value
91 *> \endverbatim
92 *
93 * Authors:
94 * ========
95 *
96 *> \author Univ. of Tennessee
97 *> \author Univ. of California Berkeley
98 *> \author Univ. of Colorado Denver
99 *> \author NAG Ltd.
100 *
101 *> \date September 2012
102 *
103 *> \ingroup complexGEcomputational
104 *
105 *> \par Further Details:
106 * =====================
107 *>
108 *> \verbatim
109 *>
110 *> The matrix Q is represented as a product of elementary reflectors
111 *>
112 *> Q = H(k) . . . H(2) H(1), where k = min(m,n).
113 *>
114 *> Each H(i) has the form
115 *>
116 *> H(i) = I - tau * v * v**H
117 *>
118 *> where tau is a complex scalar, and v is a complex vector with
119 *> v(m-k+i+1:m) = 0 and v(m-k+i) = 1; v(1:m-k+i-1) is stored on exit in
120 *> A(1:m-k+i-1,n-k+i), and tau in TAU(i).
121 *> \endverbatim
122 *>
123 * =====================================================================
124  SUBROUTINE cgeql2( M, N, A, LDA, TAU, WORK, INFO )
125 *
126 * -- LAPACK computational routine (version 3.4.2) --
127 * -- LAPACK is a software package provided by Univ. of Tennessee, --
128 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
129 * September 2012
130 *
131 * .. Scalar Arguments ..
132  INTEGER INFO, LDA, M, N
133 * ..
134 * .. Array Arguments ..
135  COMPLEX A( lda, * ), TAU( * ), WORK( * )
136 * ..
137 *
138 * =====================================================================
139 *
140 * .. Parameters ..
141  COMPLEX ONE
142  parameter ( one = ( 1.0e+0, 0.0e+0 ) )
143 * ..
144 * .. Local Scalars ..
145  INTEGER I, K
146  COMPLEX ALPHA
147 * ..
148 * .. External Subroutines ..
149  EXTERNAL clarf, clarfg, xerbla
150 * ..
151 * .. Intrinsic Functions ..
152  INTRINSIC conjg, max, min
153 * ..
154 * .. Executable Statements ..
155 *
156 * Test the input arguments
157 *
158  info = 0
159  IF( m.LT.0 ) THEN
160  info = -1
161  ELSE IF( n.LT.0 ) THEN
162  info = -2
163  ELSE IF( lda.LT.max( 1, m ) ) THEN
164  info = -4
165  END IF
166  IF( info.NE.0 ) THEN
167  CALL xerbla( 'CGEQL2', -info )
168  RETURN
169  END IF
170 *
171  k = min( m, n )
172 *
173  DO 10 i = k, 1, -1
174 *
175 * Generate elementary reflector H(i) to annihilate
176 * A(1:m-k+i-1,n-k+i)
177 *
178  alpha = a( m-k+i, n-k+i )
179  CALL clarfg( m-k+i, alpha, a( 1, n-k+i ), 1, tau( i ) )
180 *
181 * Apply H(i)**H to A(1:m-k+i,1:n-k+i-1) from the left
182 *
183  a( m-k+i, n-k+i ) = one
184  CALL clarf( 'Left', m-k+i, n-k+i-1, a( 1, n-k+i ), 1,
185  $ conjg( tau( i ) ), a, lda, work )
186  a( m-k+i, n-k+i ) = alpha
187  10 CONTINUE
188  RETURN
189 *
190 * End of CGEQL2
191 *
192  END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine clarf(SIDE, M, N, V, INCV, TAU, C, LDC, WORK)
CLARF applies an elementary reflector to a general rectangular matrix.
Definition: clarf.f:130
subroutine cgeql2(M, N, A, LDA, TAU, WORK, INFO)
CGEQL2 computes the QL factorization of a general rectangular matrix using an unblocked algorithm...
Definition: cgeql2.f:125
subroutine clarfg(N, ALPHA, X, INCX, TAU)
CLARFG generates an elementary reflector (Householder matrix).
Definition: clarfg.f:108