LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dorgl2.f
Go to the documentation of this file.
1*> \brief \b DORGL2
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DORGL2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dorgl2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dorgl2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dorgl2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DORGL2( M, N, K, A, LDA, TAU, WORK, INFO )
20*
21* .. Scalar Arguments ..
22* INTEGER INFO, K, LDA, M, N
23* ..
24* .. Array Arguments ..
25* DOUBLE PRECISION A( LDA, * ), TAU( * ), WORK( * )
26* ..
27*
28*
29*> \par Purpose:
30* =============
31*>
32*> \verbatim
33*>
34*> DORGL2 generates an m by n real matrix Q with orthonormal rows,
35*> which is defined as the first m rows of a product of k elementary
36*> reflectors of order n
37*>
38*> Q = H(k) . . . H(2) H(1)
39*>
40*> as returned by DGELQF.
41*> \endverbatim
42*
43* Arguments:
44* ==========
45*
46*> \param[in] M
47*> \verbatim
48*> M is INTEGER
49*> The number of rows of the matrix Q. M >= 0.
50*> \endverbatim
51*>
52*> \param[in] N
53*> \verbatim
54*> N is INTEGER
55*> The number of columns of the matrix Q. N >= M.
56*> \endverbatim
57*>
58*> \param[in] K
59*> \verbatim
60*> K is INTEGER
61*> The number of elementary reflectors whose product defines the
62*> matrix Q. M >= K >= 0.
63*> \endverbatim
64*>
65*> \param[in,out] A
66*> \verbatim
67*> A is DOUBLE PRECISION array, dimension (LDA,N)
68*> On entry, the i-th row must contain the vector which defines
69*> the elementary reflector H(i), for i = 1,2,...,k, as returned
70*> by DGELQF in the first k rows of its array argument A.
71*> On exit, the m-by-n matrix Q.
72*> \endverbatim
73*>
74*> \param[in] LDA
75*> \verbatim
76*> LDA is INTEGER
77*> The first dimension of the array A. LDA >= max(1,M).
78*> \endverbatim
79*>
80*> \param[in] TAU
81*> \verbatim
82*> TAU is DOUBLE PRECISION array, dimension (K)
83*> TAU(i) must contain the scalar factor of the elementary
84*> reflector H(i), as returned by DGELQF.
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 has 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*> \ingroup ungl2
108*
109* =====================================================================
110 SUBROUTINE dorgl2( M, N, K, A, LDA, TAU, WORK, INFO )
111*
112* -- LAPACK computational routine --
113* -- LAPACK is a software package provided by Univ. of Tennessee, --
114* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
115*
116* .. Scalar Arguments ..
117 INTEGER INFO, K, LDA, M, N
118* ..
119* .. Array Arguments ..
120 DOUBLE PRECISION A( LDA, * ), TAU( * ), WORK( * )
121* ..
122*
123* =====================================================================
124*
125* .. Parameters ..
126 DOUBLE PRECISION ONE, ZERO
127 parameter( one = 1.0d+0, zero = 0.0d+0 )
128* ..
129* .. Local Scalars ..
130 INTEGER I, J, L
131* ..
132* .. External Subroutines ..
133 EXTERNAL dlarf1f, dscal, xerbla
134* ..
135* .. Intrinsic Functions ..
136 INTRINSIC max
137* ..
138* .. Executable Statements ..
139*
140* Test the input arguments
141*
142 info = 0
143 IF( m.LT.0 ) THEN
144 info = -1
145 ELSE IF( n.LT.m ) THEN
146 info = -2
147 ELSE IF( k.LT.0 .OR. k.GT.m ) THEN
148 info = -3
149 ELSE IF( lda.LT.max( 1, m ) ) THEN
150 info = -5
151 END IF
152 IF( info.NE.0 ) THEN
153 CALL xerbla( 'DORGL2', -info )
154 RETURN
155 END IF
156*
157* Quick return if possible
158*
159 IF( m.LE.0 )
160 $ RETURN
161*
162 IF( k.LT.m ) THEN
163*
164* Initialise rows k+1:m to rows of the unit matrix
165*
166 DO 20 j = 1, n
167 DO 10 l = k + 1, m
168 a( l, j ) = zero
169 10 CONTINUE
170 IF( j.GT.k .AND. j.LE.m )
171 $ a( j, j ) = one
172 20 CONTINUE
173 END IF
174*
175 DO 40 i = k, 1, -1
176*
177* Apply H(i) to A(i:m,i:n) from the right
178*
179 IF( i.LT.n ) THEN
180 IF( i.LT.m ) THEN
181 CALL dlarf1f( 'Right', m-i, n-i+1, a( i, i ), lda,
182 $ tau( i ), a( i+1, i ), lda, work )
183 END IF
184 CALL dscal( n-i, -tau( i ), a( i, i+1 ), lda )
185 END IF
186 a( i, i ) = one - tau( i )
187*
188* Set A(i,1:i-1) to zero
189*
190 DO 30 l = 1, i - 1
191 a( i, l ) = zero
192 30 CONTINUE
193 40 CONTINUE
194 RETURN
195*
196* End of DORGL2
197*
198 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dlarf1f(side, m, n, v, incv, tau, c, ldc, work)
DLARF1F applies an elementary reflector to a general rectangular
Definition dlarf1f.f:157
subroutine dscal(n, da, dx, incx)
DSCAL
Definition dscal.f:79
subroutine dorgl2(m, n, k, a, lda, tau, work, info)
DORGL2
Definition dorgl2.f:111