Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

slagtf (3p)

Name

slagtf - agonal matrix and lambda is a scalar, as T-lambda*I = PLU

Synopsis

SUBROUTINE SLAGTF(N, A, LAMBDA, B, C, TOL, D, IN, INFO)

INTEGER N, INFO
INTEGER IN(*)
REAL LAMBDA, TOL
REAL A(*), B(*), C(*), D(*)

SUBROUTINE SLAGTF_64(N, A, LAMBDA, B, C, TOL, D, IN, INFO)

INTEGER*8 N, INFO
INTEGER*8 IN(*)
REAL LAMBDA, TOL
REAL A(*), B(*), C(*), D(*)




F95 INTERFACE
SUBROUTINE LAGTF(N, A, LAMBDA, B, C, TOL, D, IN, INFO)

INTEGER :: N, INFO
INTEGER, DIMENSION(:) :: IN
REAL :: LAMBDA, TOL
REAL, DIMENSION(:) :: A, B, C, D

SUBROUTINE LAGTF_64(N, A, LAMBDA, B, C, TOL, D, IN, INFO)

INTEGER(8) :: N, INFO
INTEGER(8), DIMENSION(:) :: IN
REAL :: LAMBDA, TOL
REAL, DIMENSION(:) :: A, B, C, D




C INTERFACE
#include <sunperf.h>

void slagtf(int n, float *a, float lambda, float *b,  float  *c,  float
tol, float *d, int *in, int *info);

void  slagtf_64(long  n,  float  *a,  float lambda, float *b, float *c,
float tol, float *d, long *in, long *info);

Description

Oracle Solaris Studio Performance Library                           slagtf(3P)



NAME
       slagtf - factorize the matrix (T-lambda*I), where T is an n by n tridi-
       agonal matrix and lambda is a scalar, as T-lambda*I = PLU


SYNOPSIS
       SUBROUTINE SLAGTF(N, A, LAMBDA, B, C, TOL, D, IN, INFO)

       INTEGER N, INFO
       INTEGER IN(*)
       REAL LAMBDA, TOL
       REAL A(*), B(*), C(*), D(*)

       SUBROUTINE SLAGTF_64(N, A, LAMBDA, B, C, TOL, D, IN, INFO)

       INTEGER*8 N, INFO
       INTEGER*8 IN(*)
       REAL LAMBDA, TOL
       REAL A(*), B(*), C(*), D(*)




   F95 INTERFACE
       SUBROUTINE LAGTF(N, A, LAMBDA, B, C, TOL, D, IN, INFO)

       INTEGER :: N, INFO
       INTEGER, DIMENSION(:) :: IN
       REAL :: LAMBDA, TOL
       REAL, DIMENSION(:) :: A, B, C, D

       SUBROUTINE LAGTF_64(N, A, LAMBDA, B, C, TOL, D, IN, INFO)

       INTEGER(8) :: N, INFO
       INTEGER(8), DIMENSION(:) :: IN
       REAL :: LAMBDA, TOL
       REAL, DIMENSION(:) :: A, B, C, D




   C INTERFACE
       #include <sunperf.h>

       void slagtf(int n, float *a, float lambda, float *b,  float  *c,  float
                 tol, float *d, int *in, int *info);

       void  slagtf_64(long  n,  float  *a,  float lambda, float *b, float *c,
                 float tol, float *d, long *in, long *info);



PURPOSE
       slagtf factorizes the matrix (T - lambda*I), where  T  is  an  n  by  n
       tridiagonal  matrix and lambda is a scalar, as where P is a permutation
       matrix, L is a unit lower tridiagonal matrix with at most one  non-zero
       sub-diagonal  elements  per  column and U is an upper triangular matrix
       with at most two non-zero super-diagonal elements per column.

       The factorization is obtained by Gaussian elimination with partial piv-
       oting and implicit row scaling.

       The  parameter  LAMBDA is included in the routine so that SLAGTF may be
       used, in conjunction with  SLAGTS,  to  obtain  eigenvectors  of  T  by
       inverse iteration.


ARGUMENTS
       N (input) The order of the matrix T.


       A (input/output)
                 On entry, A must contain the diagonal elements of T.

                 On  exit,  A is overwritten by the n diagonal elements of the
                 upper triangular matrix U of the factorization of T.


       LAMBDA (input)
                 On entry, the scalar lambda.


       B (input/output)
                 On entry, B must contain the (n-1) super-diagonal elements of
                 T.

                 On  exit,  B  is overwritten by the (n-1) super-diagonal ele-
                 ments of the matrix U of the factorization of T.


       C (input/output)
                 On entry, C must contain the (n-1) sub-diagonal  elements  of
                 T.

                 On  exit, C is overwritten by the (n-1) sub-diagonal elements
                 of the matrix L of the factorization of T.


       TOL (input/output)
                 On entry, a relative tolerance used to  indicate  whether  or
                 not  the matrix (T - lambda*I) is nearly singular. TOL should
                 normally be chose as approximately the largest relative error
                 in  the  elements of T. For example, if the elements of T are
                 correct to about 4 significant figures, then  TOL  should  be
                 set to about 5*10**(-4). If TOL is supplied as less than eps,
                 where eps is the relative machine precision, then  the  value
                 eps is used in place of TOL.


       D (output)
                 On  exit, D is overwritten by the (n-2) second super-diagonal
                 elements of the matrix U of the factorization of T.


       IN (output)
                 On exit, IN contains details of the permutation matrix P.  If
                 an  interchange  occurred at the kth step of the elimination,
                 then IN(k) = 1,  otherwise  IN(k)  =  0.  The  element  IN(n)
                 returns the smallest positive integer j such that

                 abs( u(j,j) ).le. norm( (T - lambda*I)(j) )*TOL,

                 where  norm( A(j) ) denotes the sum of the absolute values of
                 the jth row of the matrix A. If no such j exists  then  IN(n)
                 is returned as zero. If IN(n) is returned as positive, then a
                 diagonal  element  of  U  is  small,  indicating  that  (T  -
                 lambda*I) is singular or nearly singular,


       INFO (output)
                 = 0   : successful exit




                                  7 Nov 2015                        slagtf(3P)