LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
sopgtr.f
Go to the documentation of this file.
1*> \brief \b SOPGTR
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SOPGTR + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/sopgtr.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/sopgtr.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/sopgtr.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SOPGTR( UPLO, N, AP, TAU, Q, LDQ, WORK, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, LDQ, N
24* ..
25* .. Array Arguments ..
26* REAL AP( * ), Q( LDQ, * ), TAU( * ), WORK( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> SOPGTR generates a real orthogonal matrix Q which is defined as the
36*> product of n-1 elementary reflectors H(i) of order n, as returned by
37*> SSPTRD using packed storage:
38*>
39*> if UPLO = 'U', Q = H(n-1) . . . H(2) H(1),
40*>
41*> if UPLO = 'L', Q = H(1) H(2) . . . H(n-1).
42*> \endverbatim
43*
44* Arguments:
45* ==========
46*
47*> \param[in] UPLO
48*> \verbatim
49*> UPLO is CHARACTER*1
50*> = 'U': Upper triangular packed storage used in previous
51*> call to SSPTRD;
52*> = 'L': Lower triangular packed storage used in previous
53*> call to SSPTRD.
54*> \endverbatim
55*>
56*> \param[in] N
57*> \verbatim
58*> N is INTEGER
59*> The order of the matrix Q. N >= 0.
60*> \endverbatim
61*>
62*> \param[in] AP
63*> \verbatim
64*> AP is REAL array, dimension (N*(N+1)/2)
65*> The vectors which define the elementary reflectors, as
66*> returned by SSPTRD.
67*> \endverbatim
68*>
69*> \param[in] TAU
70*> \verbatim
71*> TAU is REAL array, dimension (N-1)
72*> TAU(i) must contain the scalar factor of the elementary
73*> reflector H(i), as returned by SSPTRD.
74*> \endverbatim
75*>
76*> \param[out] Q
77*> \verbatim
78*> Q is REAL array, dimension (LDQ,N)
79*> The N-by-N orthogonal matrix Q.
80*> \endverbatim
81*>
82*> \param[in] LDQ
83*> \verbatim
84*> LDQ is INTEGER
85*> The leading dimension of the array Q. LDQ >= max(1,N).
86*> \endverbatim
87*>
88*> \param[out] WORK
89*> \verbatim
90*> WORK is REAL array, dimension (N-1)
91*> \endverbatim
92*>
93*> \param[out] INFO
94*> \verbatim
95*> INFO is INTEGER
96*> = 0: successful exit
97*> < 0: if INFO = -i, the i-th argument had an illegal value
98*> \endverbatim
99*
100* Authors:
101* ========
102*
103*> \author Univ. of Tennessee
104*> \author Univ. of California Berkeley
105*> \author Univ. of Colorado Denver
106*> \author NAG Ltd.
107*
108*> \ingroup upgtr
109*
110* =====================================================================
111 SUBROUTINE sopgtr( UPLO, N, AP, TAU, Q, LDQ, WORK, INFO )
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*
227 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
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
subroutine sopgtr(uplo, n, ap, tau, q, ldq, work, info)
SOPGTR
Definition sopgtr.f:112