LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ sorgr2()

subroutine sorgr2 ( integer m,
integer n,
integer k,
real, dimension( lda, * ) a,
integer lda,
real, dimension( * ) tau,
real, dimension( * ) work,
integer info )

SORGR2 generates all or part of the orthogonal matrix Q from an RQ factorization determined by sgerqf (unblocked algorithm).

Download SORGR2 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> SORGR2 generates an m by n real matrix Q with orthonormal rows,
!> which is defined as the last m rows of a product of k elementary
!> reflectors of order n
!>
!>       Q  =  H(1) H(2) . . . H(k)
!>
!> as returned by SGERQF.
!> 
Parameters
[in]M
!>          M is INTEGER
!>          The number of rows of the matrix Q. M >= 0.
!> 
[in]N
!>          N is INTEGER
!>          The number of columns of the matrix Q. N >= M.
!> 
[in]K
!>          K is INTEGER
!>          The number of elementary reflectors whose product defines the
!>          matrix Q. M >= K >= 0.
!> 
[in,out]A
!>          A is REAL array, dimension (LDA,N)
!>          On entry, the (m-k+i)-th row must contain the vector which
!>          defines the elementary reflector H(i), for i = 1,2,...,k, as
!>          returned by SGERQF in the last k rows of its array argument
!>          A.
!>          On exit, the m by n matrix Q.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The first dimension of the array A. LDA >= max(1,M).
!> 
[in]TAU
!>          TAU is REAL array, dimension (K)
!>          TAU(i) must contain the scalar factor of the elementary
!>          reflector H(i), as returned by SGERQF.
!> 
[out]WORK
!>          WORK is REAL array, dimension (M)
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0: successful exit
!>          < 0: if INFO = -i, the i-th argument has an illegal value
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 111 of file sorgr2.f.

112*
113* -- LAPACK computational routine --
114* -- LAPACK is a software package provided by Univ. of Tennessee, --
115* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
116*
117* .. Scalar Arguments ..
118 INTEGER INFO, K, LDA, M, N
119* ..
120* .. Array Arguments ..
121 REAL A( LDA, * ), TAU( * ), WORK( * )
122* ..
123*
124* =====================================================================
125*
126* .. Parameters ..
127 REAL ONE, ZERO
128 parameter( one = 1.0e+0, zero = 0.0e+0 )
129* ..
130* .. Local Scalars ..
131 INTEGER I, II, J, L
132* ..
133* .. External Subroutines ..
134 EXTERNAL slarf1l, sscal, xerbla
135* ..
136* .. Intrinsic Functions ..
137 INTRINSIC max
138* ..
139* .. Executable Statements ..
140*
141* Test the input arguments
142*
143 info = 0
144 IF( m.LT.0 ) THEN
145 info = -1
146 ELSE IF( n.LT.m ) THEN
147 info = -2
148 ELSE IF( k.LT.0 .OR. k.GT.m ) THEN
149 info = -3
150 ELSE IF( lda.LT.max( 1, m ) ) THEN
151 info = -5
152 END IF
153 IF( info.NE.0 ) THEN
154 CALL xerbla( 'SORGR2', -info )
155 RETURN
156 END IF
157*
158* Quick return if possible
159*
160 IF( m.LE.0 )
161 $ RETURN
162*
163 IF( k.LT.m ) THEN
164*
165* Initialise rows 1:m-k to rows of the unit matrix
166*
167 DO 20 j = 1, n
168 DO 10 l = 1, m - k
169 a( l, j ) = zero
170 10 CONTINUE
171 IF( j.GT.n-m .AND. j.LE.n-k )
172 $ a( m-n+j, j ) = one
173 20 CONTINUE
174 END IF
175*
176 DO 40 i = 1, k
177 ii = m - k + i
178*
179* Apply H(i) to A(1:m-k+i,1:n-k+i) from the right
180*
181 a( ii, n-m+ii ) = one
182 CALL slarf1l( 'Right', ii-1, n-m+ii, a( ii, 1 ), lda,
183 $ tau( i ), a, lda, work )
184 CALL sscal( n-m+ii-1, -tau( i ), a( ii, 1 ), lda )
185 a( ii, n-m+ii ) = one - tau( i )
186*
187* Set A(m-k+i,n-k+i+1:n) to zero
188*
189 DO 30 l = n - m + ii + 1, n
190 a( ii, l ) = zero
191 30 CONTINUE
192 40 CONTINUE
193 RETURN
194*
195* End of SORGR2
196*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79
subroutine slarf1l(side, m, n, v, incv, tau, c, ldc, work)
SLARF1L applies an elementary reflector to a general rectangular
Definition slarf1l.f:125
Here is the call graph for this function:
Here is the caller graph for this function: