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

◆ sopgtr()

subroutine sopgtr ( character uplo,
integer n,
real, dimension( * ) ap,
real, dimension( * ) tau,
real, dimension( ldq, * ) q,
integer ldq,
real, dimension( * ) work,
integer info )

SOPGTR

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

Purpose:
!>
!> SOPGTR generates a real orthogonal matrix Q which is defined as the
!> product of n-1 elementary reflectors H(i) of order n, as returned by
!> SSPTRD using packed storage:
!>
!> 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 triangular packed storage used in previous
!>                 call to SSPTRD;
!>          = 'L': Lower triangular packed storage used in previous
!>                 call to SSPTRD.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix Q. N >= 0.
!> 
[in]AP
!>          AP is REAL array, dimension (N*(N+1)/2)
!>          The vectors which define the elementary reflectors, as
!>          returned by SSPTRD.
!> 
[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 SSPTRD.
!> 
[out]Q
!>          Q is REAL array, dimension (LDQ,N)
!>          The N-by-N orthogonal matrix Q.
!> 
[in]LDQ
!>          LDQ is INTEGER
!>          The leading dimension of the array Q. LDQ >= max(1,N).
!> 
[out]WORK
!>          WORK is REAL array, dimension (N-1)
!> 
[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 111 of file sopgtr.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 CHARACTER UPLO
119 INTEGER INFO, LDQ, N
120* ..
121* .. Array Arguments ..
122 REAL AP( * ), Q( LDQ, * ), TAU( * ), WORK( * )
123* ..
124*
125* =====================================================================
126*
127* .. Parameters ..
128 REAL ZERO, ONE
129 parameter( zero = 0.0e+0, one = 1.0e+0 )
130* ..
131* .. Local Scalars ..
132 LOGICAL UPPER
133 INTEGER I, IINFO, IJ, J
134* ..
135* .. External Functions ..
136 LOGICAL LSAME
137 EXTERNAL lsame
138* ..
139* .. External Subroutines ..
140 EXTERNAL sorg2l, sorg2r, xerbla
141* ..
142* .. Intrinsic Functions ..
143 INTRINSIC max
144* ..
145* .. Executable Statements ..
146*
147* Test the input arguments
148*
149 info = 0
150 upper = lsame( uplo, 'U' )
151 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
152 info = -1
153 ELSE IF( n.LT.0 ) THEN
154 info = -2
155 ELSE IF( ldq.LT.max( 1, n ) ) THEN
156 info = -6
157 END IF
158 IF( info.NE.0 ) THEN
159 CALL xerbla( 'SOPGTR', -info )
160 RETURN
161 END IF
162*
163* Quick return if possible
164*
165 IF( n.EQ.0 )
166 $ RETURN
167*
168 IF( upper ) THEN
169*
170* Q was determined by a call to SSPTRD with UPLO = 'U'
171*
172* Unpack the vectors which define the elementary reflectors and
173* set the last row and column of Q equal to those of the unit
174* matrix
175*
176 ij = 2
177 DO 20 j = 1, n - 1
178 DO 10 i = 1, j - 1
179 q( i, j ) = ap( ij )
180 ij = ij + 1
181 10 CONTINUE
182 ij = ij + 2
183 q( n, j ) = zero
184 20 CONTINUE
185 DO 30 i = 1, n - 1
186 q( i, n ) = zero
187 30 CONTINUE
188 q( n, n ) = one
189*
190* Generate Q(1:n-1,1:n-1)
191*
192 CALL sorg2l( n-1, n-1, n-1, q, ldq, tau, work, iinfo )
193*
194 ELSE
195*
196* Q was determined by a call to SSPTRD with UPLO = 'L'.
197*
198* Unpack the vectors which define the elementary reflectors and
199* set the first row and column of Q equal to those of the unit
200* matrix
201*
202 q( 1, 1 ) = one
203 DO 40 i = 2, n
204 q( i, 1 ) = zero
205 40 CONTINUE
206 ij = 3
207 DO 60 j = 2, n
208 q( 1, j ) = zero
209 DO 50 i = j + 1, n
210 q( i, j ) = ap( ij )
211 ij = ij + 1
212 50 CONTINUE
213 ij = ij + 2
214 60 CONTINUE
215 IF( n.GT.1 ) THEN
216*
217* Generate Q(2:n,2:n)
218*
219 CALL sorg2r( n-1, n-1, n-1, q( 2, 2 ), ldq, tau, work,
220 $ iinfo )
221 END IF
222 END IF
223 RETURN
224*
225* End of SOPGTR
226*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine sorg2l(m, n, k, a, lda, tau, work, info)
SORG2L generates all or part of the orthogonal matrix Q from a QL factorization determined by sgeqlf ...
Definition sorg2l.f:112
subroutine sorg2r(m, n, k, a, lda, tau, work, info)
SORG2R generates all or part of the orthogonal matrix Q from a QR factorization determined by sgeqrf ...
Definition sorg2r.f:112
Here is the call graph for this function:
Here is the caller graph for this function: