LAPACK 3.12.0
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 113 of file sopgtr.f.

114*
115* -- LAPACK computational routine --
116* -- LAPACK is a software package provided by Univ. of Tennessee, --
117* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
118*
119* .. Scalar Arguments ..
120 CHARACTER UPLO
121 INTEGER INFO, LDQ, N
122* ..
123* .. Array Arguments ..
124 REAL AP( * ), Q( LDQ, * ), TAU( * ), WORK( * )
125* ..
126*
127* =====================================================================
128*
129* .. Parameters ..
130 REAL ZERO, ONE
131 parameter( zero = 0.0e+0, one = 1.0e+0 )
132* ..
133* .. Local Scalars ..
134 LOGICAL UPPER
135 INTEGER I, IINFO, IJ, J
136* ..
137* .. External Functions ..
138 LOGICAL LSAME
139 EXTERNAL lsame
140* ..
141* .. External Subroutines ..
142 EXTERNAL sorg2l, sorg2r, xerbla
143* ..
144* .. Intrinsic Functions ..
145 INTRINSIC max
146* ..
147* .. Executable Statements ..
148*
149* Test the input arguments
150*
151 info = 0
152 upper = lsame( uplo, 'U' )
153 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
154 info = -1
155 ELSE IF( n.LT.0 ) THEN
156 info = -2
157 ELSE IF( ldq.LT.max( 1, n ) ) THEN
158 info = -6
159 END IF
160 IF( info.NE.0 ) THEN
161 CALL xerbla( 'SOPGTR', -info )
162 RETURN
163 END IF
164*
165* Quick return if possible
166*
167 IF( n.EQ.0 )
168 $ RETURN
169*
170 IF( upper ) THEN
171*
172* Q was determined by a call to SSPTRD with UPLO = 'U'
173*
174* Unpack the vectors which define the elementary reflectors and
175* set the last row and column of Q equal to those of the unit
176* matrix
177*
178 ij = 2
179 DO 20 j = 1, n - 1
180 DO 10 i = 1, j - 1
181 q( i, j ) = ap( ij )
182 ij = ij + 1
183 10 CONTINUE
184 ij = ij + 2
185 q( n, j ) = zero
186 20 CONTINUE
187 DO 30 i = 1, n - 1
188 q( i, n ) = zero
189 30 CONTINUE
190 q( n, n ) = one
191*
192* Generate Q(1:n-1,1:n-1)
193*
194 CALL sorg2l( n-1, n-1, n-1, q, ldq, tau, work, iinfo )
195*
196 ELSE
197*
198* Q was determined by a call to SSPTRD with UPLO = 'L'.
199*
200* Unpack the vectors which define the elementary reflectors and
201* set the first row and column of Q equal to those of the unit
202* matrix
203*
204 q( 1, 1 ) = one
205 DO 40 i = 2, n
206 q( i, 1 ) = zero
207 40 CONTINUE
208 ij = 3
209 DO 60 j = 2, n
210 q( 1, j ) = zero
211 DO 50 i = j + 1, n
212 q( i, j ) = ap( ij )
213 ij = ij + 1
214 50 CONTINUE
215 ij = ij + 2
216 60 CONTINUE
217 IF( n.GT.1 ) THEN
218*
219* Generate Q(2:n,2:n)
220*
221 CALL sorg2r( n-1, n-1, n-1, q( 2, 2 ), ldq, tau, work,
222 $ iinfo )
223 END IF
224 END IF
225 RETURN
226*
227* End of SOPGTR
228*
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:114
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:114
Here is the call graph for this function:
Here is the caller graph for this function: