Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dsbtrd (3p)

Name

dsbtrd - reduce a real symmetric band matrix A to symmetric tridiagonal form T by an orthogonal similarity transformation

Synopsis

SUBROUTINE DSBTRD(VECT, UPLO, N, KD, AB, LDAB, D, E, Q, LDQ, WORK,
INFO)

CHARACTER*1 VECT, UPLO
INTEGER N, KD, LDAB, LDQ, INFO
DOUBLE PRECISION AB(LDAB,*), D(*), E(*), Q(LDQ,*), WORK(*)

SUBROUTINE DSBTRD_64(VECT, UPLO, N, KD, AB, LDAB, D, E, Q, LDQ, WORK,
INFO)

CHARACTER*1 VECT, UPLO
INTEGER*8 N, KD, LDAB, LDQ, INFO
DOUBLE PRECISION AB(LDAB,*), D(*), E(*), Q(LDQ,*), WORK(*)




F95 INTERFACE
SUBROUTINE SBTRD(VECT, UPLO, N, KD, AB, LDAB, D, E, Q, LDQ,
WORK, INFO)

CHARACTER(LEN=1) :: VECT, UPLO
INTEGER :: N, KD, LDAB, LDQ, INFO
REAL(8), DIMENSION(:) :: D, E, WORK
REAL(8), DIMENSION(:,:) :: AB, Q

SUBROUTINE SBTRD_64(VECT, UPLO, N, KD, AB, LDAB, D, E, Q, LDQ,
WORK, INFO)

CHARACTER(LEN=1) :: VECT, UPLO
INTEGER(8) :: N, KD, LDAB, LDQ, INFO
REAL(8), DIMENSION(:) :: D, E, WORK
REAL(8), DIMENSION(:,:) :: AB, Q




C INTERFACE
#include <sunperf.h>

void dsbtrd(char vect, char uplo, int n, int kd, double *ab, int  ldab,
double *d, double *e, double *q, int ldq, int *info);

void  dsbtrd_64(char vect, char uplo, long n, long kd, double *ab, long
ldab, double *d, double *e, double *q, long ldq, long *info);

Description

Oracle Solaris Studio Performance Library                           dsbtrd(3P)



NAME
       dsbtrd - reduce a real symmetric band matrix A to symmetric tridiagonal
       form T by an orthogonal similarity transformation


SYNOPSIS
       SUBROUTINE DSBTRD(VECT, UPLO, N, KD, AB, LDAB, D, E, Q, LDQ, WORK,
             INFO)

       CHARACTER*1 VECT, UPLO
       INTEGER N, KD, LDAB, LDQ, INFO
       DOUBLE PRECISION AB(LDAB,*), D(*), E(*), Q(LDQ,*), WORK(*)

       SUBROUTINE DSBTRD_64(VECT, UPLO, N, KD, AB, LDAB, D, E, Q, LDQ, WORK,
             INFO)

       CHARACTER*1 VECT, UPLO
       INTEGER*8 N, KD, LDAB, LDQ, INFO
       DOUBLE PRECISION AB(LDAB,*), D(*), E(*), Q(LDQ,*), WORK(*)




   F95 INTERFACE
       SUBROUTINE SBTRD(VECT, UPLO, N, KD, AB, LDAB, D, E, Q, LDQ,
              WORK, INFO)

       CHARACTER(LEN=1) :: VECT, UPLO
       INTEGER :: N, KD, LDAB, LDQ, INFO
       REAL(8), DIMENSION(:) :: D, E, WORK
       REAL(8), DIMENSION(:,:) :: AB, Q

       SUBROUTINE SBTRD_64(VECT, UPLO, N, KD, AB, LDAB, D, E, Q, LDQ,
              WORK, INFO)

       CHARACTER(LEN=1) :: VECT, UPLO
       INTEGER(8) :: N, KD, LDAB, LDQ, INFO
       REAL(8), DIMENSION(:) :: D, E, WORK
       REAL(8), DIMENSION(:,:) :: AB, Q




   C INTERFACE
       #include <sunperf.h>

       void dsbtrd(char vect, char uplo, int n, int kd, double *ab, int  ldab,
                 double *d, double *e, double *q, int ldq, int *info);

       void  dsbtrd_64(char vect, char uplo, long n, long kd, double *ab, long
                 ldab, double *d, double *e, double *q, long ldq, long *info);



PURPOSE
       dsbtrd  reduces a real symmetric band matrix A to symmetric tridiagonal
       form T by an orthogonal similarity transformation: Q**T * A * Q = T.


ARGUMENTS
       VECT (input)
                 = 'N':  do not form Q;
                 = 'V':  form Q;
                 = 'U':  update a matrix X, by forming X*Q.


       UPLO (input)
                 = 'U':  Upper triangle of A is stored;
                 = 'L':  Lower triangle of A is stored.


       N (input) The order of the matrix A.  N >= 0.


       KD (input)
                 The number of superdiagonals of the matrix A if UPLO  =  'U',
                 or the number of subdiagonals if UPLO = 'L'.  KD >= 0.


       AB (input/output)
                 On  entry,  the upper or lower triangle of the symmetric band
                 matrix A, stored in the first KD+1 rows of the array.  The j-
                 th  column  of A is stored in the j-th column of the array AB
                 as follows: if  UPLO  =  'U',  AB(kd+1+i-j,j)  =  A(i,j)  for
                 max(1,j-kd)<=i<=j; if UPLO = 'L', AB(1+i-j,j)    = A(i,j) for
                 j<=i<=min(n,j+kd).  On exit, the diagonal elements of AB  are
                 overwritten  by  the  diagonal  elements  of  the tridiagonal
                 matrix T; if KD > 0, the elements on the first  superdiagonal
                 (if  UPLO = 'U') or the first subdiagonal (if UPLO = 'L') are
                 overwritten by the off-diagonal elements of T; the rest of AB
                 is overwritten by values generated during the reduction.


       LDAB (input)
                 The leading dimension of the array AB.  LDAB >= KD+1.


       D (output)
                 The diagonal elements of the tridiagonal matrix T.


       E (output)
                 The off-diagonal elements of the tridiagonal matrix T: E(i) =
                 T(i,i+1) if UPLO = 'U'; E(i) = T(i+1,i) if UPLO = 'L'.


       Q (input/output)
                 On entry, if VECT = 'U', then Q must contain an N-by-N matrix
                 X; if VECT = 'N' or 'V', then Q need not be set.

                 On  exit:  if  VECT  =  'V', Q contains the N-by-N orthogonal
                 matrix Q; if VECT = 'U', Q contains the product X*Q; if  VECT
                 = 'N', the array Q is not referenced.


       LDQ (input)
                 The leading dimension of the array Q.  LDQ >= 1, and LDQ >= N
                 if VECT = 'V' or 'U'.


       WORK (workspace)
                 dimension(N)

       INFO (output)
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value

FURTHER DETAILS
       Modified by Linda Kaufman, Bell Labs.




                                  7 Nov 2015                        dsbtrd(3P)