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

◆ sorgtr()

subroutine sorgtr ( character uplo,
integer n,
real, dimension( lda, * ) a,
integer lda,
real, dimension( * ) tau,
real, dimension( * ) work,
integer lwork,
integer info )

SORGTR

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

Purpose:
!>
!> SORGTR generates a real orthogonal matrix Q which is defined as the
!> product of n-1 elementary reflectors of order N, as returned by
!> SSYTRD:
!>
!> if UPLO = 'U', Q = H(n-1) . . . H(2) H(1),
!>
!> if UPLO = 'L', Q = H(1) H(2) . . . H(n-1).
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          = 'U': Upper triangle of A contains elementary reflectors
!>                 from SSYTRD;
!>          = 'L': Lower triangle of A contains elementary reflectors
!>                 from SSYTRD.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix Q. N >= 0.
!> 
[in,out]A
!>          A is REAL array, dimension (LDA,N)
!>          On entry, the vectors which define the elementary reflectors,
!>          as returned by SSYTRD.
!>          On exit, the N-by-N orthogonal matrix Q.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A. LDA >= max(1,N).
!> 
[in]TAU
!>          TAU is REAL array, dimension (N-1)
!>          TAU(i) must contain the scalar factor of the elementary
!>          reflector H(i), as returned by SSYTRD.
!> 
[out]WORK
!>          WORK is REAL array, dimension (MAX(1,LWORK))
!>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
!> 
[in]LWORK
!>          LWORK is INTEGER
!>          The dimension of the array WORK. LWORK >= max(1,N-1).
!>          For optimum performance LWORK >= (N-1)*NB, where NB is
!>          the optimal blocksize.
!>
!>          If LWORK = -1, then a workspace query is assumed; the routine
!>          only calculates the optimal size of the WORK array, returns
!>          this value as the first entry of the WORK array, and no error
!>          message related to LWORK is issued by XERBLA.
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0:  successful exit
!>          < 0:  if INFO = -i, the i-th argument had an illegal value
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 120 of file sorgtr.f.

121*
122* -- LAPACK computational routine --
123* -- LAPACK is a software package provided by Univ. of Tennessee, --
124* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
125*
126* .. Scalar Arguments ..
127 CHARACTER UPLO
128 INTEGER INFO, LDA, LWORK, N
129* ..
130* .. Array Arguments ..
131 REAL A( LDA, * ), TAU( * ), WORK( * )
132* ..
133*
134* =====================================================================
135*
136* .. Parameters ..
137 REAL ZERO, ONE
138 parameter( zero = 0.0e+0, one = 1.0e+0 )
139* ..
140* .. Local Scalars ..
141 LOGICAL LQUERY, UPPER
142 INTEGER I, IINFO, J, LWKOPT, NB
143* ..
144* .. External Functions ..
145 LOGICAL LSAME
146 INTEGER ILAENV
147 REAL SROUNDUP_LWORK
148 EXTERNAL ilaenv, lsame, sroundup_lwork
149* ..
150* .. External Subroutines ..
151 EXTERNAL sorgql, sorgqr, xerbla
152* ..
153* .. Intrinsic Functions ..
154 INTRINSIC max
155* ..
156* .. Executable Statements ..
157*
158* Test the input arguments
159*
160 info = 0
161 lquery = ( lwork.EQ.-1 )
162 upper = lsame( uplo, 'U' )
163 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
164 info = -1
165 ELSE IF( n.LT.0 ) THEN
166 info = -2
167 ELSE IF( lda.LT.max( 1, n ) ) THEN
168 info = -4
169 ELSE IF( lwork.LT.max( 1, n-1 ) .AND. .NOT.lquery ) THEN
170 info = -7
171 END IF
172*
173 IF( info.EQ.0 ) THEN
174 IF ( upper ) THEN
175 nb = ilaenv( 1, 'SORGQL', ' ', n-1, n-1, n-1, -1 )
176 ELSE
177 nb = ilaenv( 1, 'SORGQR', ' ', n-1, n-1, n-1, -1 )
178 END IF
179 lwkopt = max( 1, n-1 )*nb
180 work( 1 ) = sroundup_lwork(lwkopt)
181 END IF
182*
183 IF( info.NE.0 ) THEN
184 CALL xerbla( 'SORGTR', -info )
185 RETURN
186 ELSE IF( lquery ) THEN
187 RETURN
188 END IF
189*
190* Quick return if possible
191*
192 IF( n.EQ.0 ) THEN
193 work( 1 ) = 1
194 RETURN
195 END IF
196*
197 IF( upper ) THEN
198*
199* Q was determined by a call to SSYTRD with UPLO = 'U'
200*
201* Shift the vectors which define the elementary reflectors one
202* column to the left, and set the last row and column of Q to
203* those of the unit matrix
204*
205 DO 20 j = 1, n - 1
206 DO 10 i = 1, j - 1
207 a( i, j ) = a( i, j+1 )
208 10 CONTINUE
209 a( n, j ) = zero
210 20 CONTINUE
211 DO 30 i = 1, n - 1
212 a( i, n ) = zero
213 30 CONTINUE
214 a( n, n ) = one
215*
216* Generate Q(1:n-1,1:n-1)
217*
218 CALL sorgql( n-1, n-1, n-1, a, lda, tau, work, lwork,
219 $ iinfo )
220*
221 ELSE
222*
223* Q was determined by a call to SSYTRD with UPLO = 'L'.
224*
225* Shift the vectors which define the elementary reflectors one
226* column to the right, and set the first row and column of Q to
227* those of the unit matrix
228*
229 DO 50 j = n, 2, -1
230 a( 1, j ) = zero
231 DO 40 i = j + 1, n
232 a( i, j ) = a( i, j-1 )
233 40 CONTINUE
234 50 CONTINUE
235 a( 1, 1 ) = one
236 DO 60 i = 2, n
237 a( i, 1 ) = zero
238 60 CONTINUE
239 IF( n.GT.1 ) THEN
240*
241* Generate Q(2:n,2:n)
242*
243 CALL sorgqr( n-1, n-1, n-1, a( 2, 2 ), lda, tau, work,
244 $ lwork, iinfo )
245 END IF
246 END IF
247 work( 1 ) = sroundup_lwork(lwkopt)
248 RETURN
249*
250* End of SORGTR
251*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:160
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
real function sroundup_lwork(lwork)
SROUNDUP_LWORK
subroutine sorgql(m, n, k, a, lda, tau, work, lwork, info)
SORGQL
Definition sorgql.f:126
subroutine sorgqr(m, n, k, a, lda, tau, work, lwork, info)
SORGQR
Definition sorgqr.f:126
Here is the call graph for this function:
Here is the caller graph for this function: