1 SUBROUTINE DORG2L( M, N, K, A, LDA, TAU, WORK, 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, M, N
10 ! .. Array Arguments ..
11 DOUBLE PRECISION A( LDA, * ), TAU( * ), WORK( * )
17 ! DORG2L 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) DOUBLE PRECISION array, dimension (N)
54 ! INFO (output) INTEGER
55 ! = 0: successful exit
56 ! < 0: if INFO = -i, the i-th argument has an illegal value
58 ! =====================================================================
61 DOUBLE PRECISION ONE, ZERO
62 PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
67 ! .. External Subroutines ..
68 ! EXTERNAL DLARF, DSCAL, XERBLA
70 ! .. Intrinsic Functions ..
73 ! .. Executable Statements ..
75 ! Test the input arguments
80 ELSE IF( N.LT.0 .OR. N.GT.M ) THEN
82 ELSE IF( K.LT.0 .OR. K.GT.N ) THEN
84 ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
88 CALL XERBLA( 'DORG2L', -INFO )
92 ! Quick return if possible
97 ! Initialise columns 1:n-k to columns of the unit matrix
109 ! Apply H(i) to A(1:m-k+i,1:n-k+i) from the left
111 A( M-N+II, II ) = ONE
112 CALL DLARF( 'Left', M-N+II, II-1, A( 1, II ), 1, TAU( I ), A, &
114 CALL DSCAL( M-N+II-1, -TAU( I ), A( 1, II ), 1 )
115 A( M-N+II, II ) = ONE - TAU( I )
117 ! Set A(m-k+i+1:m,n-k+i) to zero
119 DO 30 L = M - N + II + 1, M
127 END SUBROUTINE DORG2L