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

◆ dorgtr()

subroutine dorgtr ( character uplo,
integer n,
double precision, dimension( lda, * ) a,
integer lda,
double precision, dimension( * ) tau,
double precision, dimension( * ) work,
integer lwork,
integer info )

DORGTR

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

Purpose:
!>
!> DORGTR generates a real orthogonal matrix Q which is defined as the
!> product of n-1 elementary reflectors of order N, as returned by
!> DSYTRD:
!>
!> 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 DSYTRD;
!>          = 'L': Lower triangle of A contains elementary reflectors
!>                 from DSYTRD.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix Q. N >= 0.
!> 
[in,out]A
!>          A is DOUBLE PRECISION array, dimension (LDA,N)
!>          On entry, the vectors which define the elementary reflectors,
!>          as returned by DSYTRD.
!>          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 DOUBLE PRECISION array, dimension (N-1)
!>          TAU(i) must contain the scalar factor of the elementary
!>          reflector H(i), as returned by DSYTRD.
!> 
[out]WORK
!>          WORK is DOUBLE PRECISION 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 dorgtr.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 DOUBLE PRECISION A( LDA, * ), TAU( * ), WORK( * )
132* ..
133*
134* =====================================================================
135*
136* .. Parameters ..
137 DOUBLE PRECISION ZERO, ONE
138 parameter( zero = 0.0d+0, one = 1.0d+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 EXTERNAL lsame, ilaenv
148* ..
149* .. External Subroutines ..
150 EXTERNAL dorgql, dorgqr, xerbla
151* ..
152* .. Intrinsic Functions ..
153 INTRINSIC max
154* ..
155* .. Executable Statements ..
156*
157* Test the input arguments
158*
159 info = 0
160 lquery = ( lwork.EQ.-1 )
161 upper = lsame( uplo, 'U' )
162 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
163 info = -1
164 ELSE IF( n.LT.0 ) THEN
165 info = -2
166 ELSE IF( lda.LT.max( 1, n ) ) THEN
167 info = -4
168 ELSE IF( lwork.LT.max( 1, n-1 ) .AND. .NOT.lquery ) THEN
169 info = -7
170 END IF
171*
172 IF( info.EQ.0 ) THEN
173 IF( upper ) THEN
174 nb = ilaenv( 1, 'DORGQL', ' ', n-1, n-1, n-1, -1 )
175 ELSE
176 nb = ilaenv( 1, 'DORGQR', ' ', n-1, n-1, n-1, -1 )
177 END IF
178 lwkopt = max( 1, n-1 )*nb
179 work( 1 ) = lwkopt
180 END IF
181*
182 IF( info.NE.0 ) THEN
183 CALL xerbla( 'DORGTR', -info )
184 RETURN
185 ELSE IF( lquery ) THEN
186 RETURN
187 END IF
188*
189* Quick return if possible
190*
191 IF( n.EQ.0 ) THEN
192 work( 1 ) = 1
193 RETURN
194 END IF
195*
196 IF( upper ) THEN
197*
198* Q was determined by a call to DSYTRD with UPLO = 'U'
199*
200* Shift the vectors which define the elementary reflectors one
201* column to the left, and set the last row and column of Q to
202* those of the unit matrix
203*
204 DO 20 j = 1, n - 1
205 DO 10 i = 1, j - 1
206 a( i, j ) = a( i, j+1 )
207 10 CONTINUE
208 a( n, j ) = zero
209 20 CONTINUE
210 DO 30 i = 1, n - 1
211 a( i, n ) = zero
212 30 CONTINUE
213 a( n, n ) = one
214*
215* Generate Q(1:n-1,1:n-1)
216*
217 CALL dorgql( n-1, n-1, n-1, a, lda, tau, work, lwork,
218 $ iinfo )
219*
220 ELSE
221*
222* Q was determined by a call to DSYTRD with UPLO = 'L'.
223*
224* Shift the vectors which define the elementary reflectors one
225* column to the right, and set the first row and column of Q to
226* those of the unit matrix
227*
228 DO 50 j = n, 2, -1
229 a( 1, j ) = zero
230 DO 40 i = j + 1, n
231 a( i, j ) = a( i, j-1 )
232 40 CONTINUE
233 50 CONTINUE
234 a( 1, 1 ) = one
235 DO 60 i = 2, n
236 a( i, 1 ) = zero
237 60 CONTINUE
238 IF( n.GT.1 ) THEN
239*
240* Generate Q(2:n,2:n)
241*
242 CALL dorgqr( n-1, n-1, n-1, a( 2, 2 ), lda, tau, work,
243 $ lwork, iinfo )
244 END IF
245 END IF
246 work( 1 ) = lwkopt
247 RETURN
248*
249* End of DORGTR
250*
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
subroutine dorgql(m, n, k, a, lda, tau, work, lwork, info)
DORGQL
Definition dorgql.f:126
subroutine dorgqr(m, n, k, a, lda, tau, work, lwork, info)
DORGQR
Definition dorgqr.f:126
Here is the call graph for this function:
Here is the caller graph for this function: