1 SUBROUTINE DORGQL
( M
, N
, K
, A
, LDA
, TAU
, WORK
, LWORK
, INFO
)
3 * -- LAPACK routine
(version
3.1) --
4 * Univ
. of Tennessee
, Univ
. of California Berkeley and NAG Ltd
..
7 * .. Scalar Arguments
..
8 INTEGER INFO
, K
, LDA
, LWORK
, M
, N
10 * .. Array Arguments
..
11 DOUBLE PRECISION A
( LDA
, * ), TAU
( * ), WORK
( * )
17 * DORGQL generates an M
-by
-N
real matrix Q with orthonormal columns
,
18 * which is defined as the last N columns of a product of K elementary
19 * reflectors of order M
21 * Q
= H
(k
) . . . H
(2) H
(1)
23 * as returned by DGEQLF
.
29 * The number of rows of the matrix Q
. M
>= 0.
32 * The number of columns of the matrix Q
. M
>= N
>= 0.
35 * The number of elementary reflectors whose product defines the
36 * matrix Q
. N
>= K
>= 0.
38 * A
(input
/output
) DOUBLE PRECISION array
, dimension (LDA
,N
)
39 * On entry
, the
(n
-k
+i
)-th column must contain the vector which
40 * defines the elementary reflector H
(i
), for i
= 1,2,...,k
, as
41 * returned by DGEQLF in the last k columns of its array
43 * On exit
, the M
-by
-N matrix Q
.
46 * The first
dimension of the array A
. LDA
>= max
(1,M
).
48 * TAU
(input
) DOUBLE PRECISION array
, dimension (K
)
49 * TAU
(i
) must contain the scalar factor of the elementary
50 * reflector H
(i
), as returned by DGEQLF
.
52 * WORK
(workspace
/output
) DOUBLE PRECISION array
, dimension (MAX
(1,LWORK
))
53 * On exit
, if INFO
= 0, WORK
(1) returns the optimal LWORK
.
55 * LWORK
(input
) INTEGER
56 * The
dimension of the array WORK
. LWORK
>= max
(1,N
).
57 * For optimum performance LWORK
>= N*NB
, where NB is the
60 * If LWORK
= -1, then a workspace query is assumed
; the routine
61 * only calculates the optimal size of the WORK array
, returns
62 * this value as the first entry of the WORK array
, and no error
63 * message related
to LWORK is issued by XERBLA
.
65 * INFO
(output
) INTEGER
66 * = 0: successful exit
67 * < 0: if INFO
= -i
, the i
-th argument has an illegal value
69 * =====================================================================
73 PARAMETER ( ZERO
= 0.0D
+0 )
77 INTEGER I
, IB
, IINFO
, IWS
, J
, KK
, L
, LDWORK
, LWKOPT
,
80 * .. External Subroutines
..
81 EXTERNAL DLARFB
, DLARFT
, DORG2L
, XERBLA
83 * .. Intrinsic Functions
..
86 * .. External Functions
..
90 * .. Executable Statements
..
92 * Test the input arguments
95 LQUERY
= ( LWORK
.EQ
.-1 )
98 ELSE IF( N
.LT
.0 .OR
. N
.GT
.M
) THEN
100 ELSE IF( K
.LT
.0 .OR
. K
.GT
.N
) THEN
102 ELSE IF( LDA
.LT
.MAX
( 1, M
) ) THEN
110 NB
= ILAENV
( 1, 'DORGQL', ' ', M
, N
, K
, -1 )
115 IF( LWORK
.LT
.MAX
( 1, N
) .AND
. .NOT
.LQUERY
) THEN
121 CALL XERBLA
( 'DORGQL', -INFO
)
123 ELSE IF( LQUERY
) THEN
127 * Quick
return if possible
136 IF( NB
.GT
.1 .AND
. NB
.LT
.K
) THEN
138 * Determine when
to cross over from blocked
to unblocked code
.
140 NX
= MAX
( 0, ILAENV
( 3, 'DORGQL', ' ', M
, N
, K
, -1 ) )
143 * Determine
if workspace is large enough
for blocked code
.
147 IF( LWORK
.LT
.IWS
) THEN
149 * Not enough workspace
to use optimal NB
: reduce NB and
150 * determine the minimum value of NB
.
153 NBMIN
= MAX
( 2, ILAENV
( 2, 'DORGQL', ' ', M
, N
, K
, -1 ) )
158 IF( NB
.GE
.NBMIN
.AND
. NB
.LT
.K
.AND
. NX
.LT
.K
) THEN
160 * Use blocked code after the first block
.
161 * The last kk columns are handled by the block method
.
163 KK
= MIN
( K
, ( ( K
-NX
+NB
-1 ) / NB
)*NB
)
165 * Set A
(m
-kk
+1:m
,1:n
-kk
) to zero
.
168 DO 10 I
= M
- KK
+ 1, M
176 * Use unblocked code
for the first or only block
.
178 CALL DORG2L
( M
-KK
, N
-KK
, K
-KK
, A
, LDA
, TAU
, WORK
, IINFO
)
184 DO 50 I
= K
- KK
+ 1, K
, NB
185 IB
= MIN
( NB
, K
-I
+1 )
186 IF( N
-K
+I
.GT
.1 ) THEN
188 * Form the triangular factor of the block reflector
189 * H
= H
(i
+ib
-1) . . . H
(i
+1) H
(i
)
191 CALL DLARFT
( 'Backward', 'Columnwise', M
-K
+I
+IB
-1, IB
,
192 $ A
( 1, N
-K
+I
), LDA
, TAU
( I
), WORK
, LDWORK
)
194 * Apply H
to A
(1:m
-k
+i
+ib
-1,1:n
-k
+i
-1) from the left
196 CALL DLARFB
( 'Left', 'No transpose', 'Backward',
197 $
'Columnwise', M
-K
+I
+IB
-1, N
-K
+I
-1, IB
,
198 $ A
( 1, N
-K
+I
), LDA
, WORK
, LDWORK
, A
, LDA
,
199 $ WORK
( IB
+1 ), LDWORK
)
202 * Apply H
to rows
1:m
-k
+i
+ib
-1 of current block
204 CALL DORG2L
( M
-K
+I
+IB
-1, IB
, IB
, A
( 1, N
-K
+I
), LDA
,
205 $ TAU
( I
), WORK
, IINFO
)
207 * Set rows m
-k
+i
+ib
:m of current block
to zero
209 DO 40 J
= N
- K
+ I
, N
- K
+ I
+ IB
- 1
210 DO 30 L
= M
- K
+ I
+ IB
, M