LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine ssptrd ( character  UPLO,
integer  N,
real, dimension( * )  AP,
real, dimension( * )  D,
real, dimension( * )  E,
real, dimension( * )  TAU,
integer  INFO 
)

SSPTRD

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

Purpose:
 SSPTRD reduces a real symmetric matrix A stored in packed form to
 symmetric tridiagonal form T by an orthogonal similarity
 transformation: Q**T * A * Q = T.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          = 'U':  Upper triangle of A is stored;
          = 'L':  Lower triangle of A is stored.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in,out]AP
          AP is REAL array, dimension (N*(N+1)/2)
          On entry, the upper or lower triangle of the symmetric matrix
          A, packed columnwise in a linear array.  The j-th column of A
          is stored in the array AP as follows:
          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
          if UPLO = 'L', AP(i + (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n.
          On exit, if UPLO = 'U', the diagonal and first superdiagonal
          of A are overwritten by the corresponding elements of the
          tridiagonal matrix T, and the elements above the first
          superdiagonal, with the array TAU, represent the orthogonal
          matrix Q as a product of elementary reflectors; if UPLO
          = 'L', the diagonal and first subdiagonal of A are over-
          written by the corresponding elements of the tridiagonal
          matrix T, and the elements below the first subdiagonal, with
          the array TAU, represent the orthogonal matrix Q as a product
          of elementary reflectors. See Further Details.
[out]D
          D is REAL array, dimension (N)
          The diagonal elements of the tridiagonal matrix T:
          D(i) = A(i,i).
[out]E
          E is REAL array, dimension (N-1)
          The off-diagonal elements of the tridiagonal matrix T:
          E(i) = A(i,i+1) if UPLO = 'U', E(i) = A(i+1,i) if UPLO = 'L'.
[out]TAU
          TAU is REAL array, dimension (N-1)
          The scalar factors of the elementary reflectors (see Further
          Details).
[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.
Date
November 2011
Further Details:
  If UPLO = 'U', the matrix Q is represented as a product of elementary
  reflectors

     Q = H(n-1) . . . H(2) H(1).

  Each H(i) has the form

     H(i) = I - tau * v * v**T

  where tau is a real scalar, and v is a real vector with
  v(i+1:n) = 0 and v(i) = 1; v(1:i-1) is stored on exit in AP,
  overwriting A(1:i-1,i+1), and tau is stored in TAU(i).

  If UPLO = 'L', the matrix Q is represented as a product of elementary
  reflectors

     Q = H(1) H(2) . . . H(n-1).

  Each H(i) has the form

     H(i) = I - tau * v * v**T

  where tau is a real scalar, and v is a real vector with
  v(1:i) = 0 and v(i+1) = 1; v(i+2:n) is stored on exit in AP,
  overwriting A(i+2:n,i), and tau is stored in TAU(i).

Definition at line 152 of file ssptrd.f.

152 *
153 * -- LAPACK computational routine (version 3.4.0) --
154 * -- LAPACK is a software package provided by Univ. of Tennessee, --
155 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
156 * November 2011
157 *
158 * .. Scalar Arguments ..
159  CHARACTER uplo
160  INTEGER info, n
161 * ..
162 * .. Array Arguments ..
163  REAL ap( * ), d( * ), e( * ), tau( * )
164 * ..
165 *
166 * =====================================================================
167 *
168 * .. Parameters ..
169  REAL one, zero, half
170  parameter ( one = 1.0, zero = 0.0, half = 1.0 / 2.0 )
171 * ..
172 * .. Local Scalars ..
173  LOGICAL upper
174  INTEGER i, i1, i1i1, ii
175  REAL alpha, taui
176 * ..
177 * .. External Subroutines ..
178  EXTERNAL saxpy, slarfg, sspmv, sspr2, xerbla
179 * ..
180 * .. External Functions ..
181  LOGICAL lsame
182  REAL sdot
183  EXTERNAL lsame, sdot
184 * ..
185 * .. Executable Statements ..
186 *
187 * Test the input parameters
188 *
189  info = 0
190  upper = lsame( uplo, 'U' )
191  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
192  info = -1
193  ELSE IF( n.LT.0 ) THEN
194  info = -2
195  END IF
196  IF( info.NE.0 ) THEN
197  CALL xerbla( 'SSPTRD', -info )
198  RETURN
199  END IF
200 *
201 * Quick return if possible
202 *
203  IF( n.LE.0 )
204  $ RETURN
205 *
206  IF( upper ) THEN
207 *
208 * Reduce the upper triangle of A.
209 * I1 is the index in AP of A(1,I+1).
210 *
211  i1 = n*( n-1 ) / 2 + 1
212  DO 10 i = n - 1, 1, -1
213 *
214 * Generate elementary reflector H(i) = I - tau * v * v**T
215 * to annihilate A(1:i-1,i+1)
216 *
217  CALL slarfg( i, ap( i1+i-1 ), ap( i1 ), 1, taui )
218  e( i ) = ap( i1+i-1 )
219 *
220  IF( taui.NE.zero ) THEN
221 *
222 * Apply H(i) from both sides to A(1:i,1:i)
223 *
224  ap( i1+i-1 ) = one
225 *
226 * Compute y := tau * A * v storing y in TAU(1:i)
227 *
228  CALL sspmv( uplo, i, taui, ap, ap( i1 ), 1, zero, tau,
229  $ 1 )
230 *
231 * Compute w := y - 1/2 * tau * (y**T *v) * v
232 *
233  alpha = -half*taui*sdot( i, tau, 1, ap( i1 ), 1 )
234  CALL saxpy( i, alpha, ap( i1 ), 1, tau, 1 )
235 *
236 * Apply the transformation as a rank-2 update:
237 * A := A - v * w**T - w * v**T
238 *
239  CALL sspr2( uplo, i, -one, ap( i1 ), 1, tau, 1, ap )
240 *
241  ap( i1+i-1 ) = e( i )
242  END IF
243  d( i+1 ) = ap( i1+i )
244  tau( i ) = taui
245  i1 = i1 - i
246  10 CONTINUE
247  d( 1 ) = ap( 1 )
248  ELSE
249 *
250 * Reduce the lower triangle of A. II is the index in AP of
251 * A(i,i) and I1I1 is the index of A(i+1,i+1).
252 *
253  ii = 1
254  DO 20 i = 1, n - 1
255  i1i1 = ii + n - i + 1
256 *
257 * Generate elementary reflector H(i) = I - tau * v * v**T
258 * to annihilate A(i+2:n,i)
259 *
260  CALL slarfg( n-i, ap( ii+1 ), ap( ii+2 ), 1, taui )
261  e( i ) = ap( ii+1 )
262 *
263  IF( taui.NE.zero ) THEN
264 *
265 * Apply H(i) from both sides to A(i+1:n,i+1:n)
266 *
267  ap( ii+1 ) = one
268 *
269 * Compute y := tau * A * v storing y in TAU(i:n-1)
270 *
271  CALL sspmv( uplo, n-i, taui, ap( i1i1 ), ap( ii+1 ), 1,
272  $ zero, tau( i ), 1 )
273 *
274 * Compute w := y - 1/2 * tau * (y**T *v) * v
275 *
276  alpha = -half*taui*sdot( n-i, tau( i ), 1, ap( ii+1 ),
277  $ 1 )
278  CALL saxpy( n-i, alpha, ap( ii+1 ), 1, tau( i ), 1 )
279 *
280 * Apply the transformation as a rank-2 update:
281 * A := A - v * w**T - w * v**T
282 *
283  CALL sspr2( uplo, n-i, -one, ap( ii+1 ), 1, tau( i ), 1,
284  $ ap( i1i1 ) )
285 *
286  ap( ii+1 ) = e( i )
287  END IF
288  d( i ) = ap( ii )
289  tau( i ) = taui
290  ii = i1i1
291  20 CONTINUE
292  d( n ) = ap( ii )
293  END IF
294 *
295  RETURN
296 *
297 * End of SSPTRD
298 *
subroutine sspr2(UPLO, N, ALPHA, X, INCX, Y, INCY, AP)
SSPR2
Definition: sspr2.f:144
subroutine sspmv(UPLO, N, ALPHA, AP, X, INCX, BETA, Y, INCY)
SSPMV
Definition: sspmv.f:149
subroutine slarfg(N, ALPHA, X, INCX, TAU)
SLARFG generates an elementary reflector (Householder matrix).
Definition: slarfg.f:108
real function sdot(N, SX, INCX, SY, INCY)
SDOT
Definition: sdot.f:53
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine saxpy(N, SA, SX, INCX, SY, INCY)
SAXPY
Definition: saxpy.f:54
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: