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