Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

spstrf (3p)

Name

spstrf - compute the Cholesky factorization with complete pivoting of a real symmetric positive semidefinite matrix A

Synopsis

SUBROUTINE SPSTRF(UPLO, N, A, LDA, PIV, RANK, TOL, WORK, INFO)


REAL TOL

INTEGER INFO, LDA, N, RANK

CHARACTER*1 UPLO

REAL A(LDA,*), WORK(2*N)

INTEGER PIV(N)


SUBROUTINE SPSTRF_64(UPLO, N, A, LDA, PIV, RANK, TOL, WORK, INFO)


REAL TOL

INTEGER*8 INFO, LDA, N, RANK

CHARACTER*1 UPLO

REAL A(LDA,*), WORK(2*N)

INTEGER*8 PIV(N)


F95 INTERFACE
SUBROUTINE PSTRF(UPLO, N, A, LDA, PIV, RANK, TOL, WORK, INFO)


REAL, DIMENSION(:,:) :: A

INTEGER :: N, LDA, RANK, INFO

CHARACTER(LEN=1) :: UPLO

INTEGER, DIMENSION(:) :: PIV

REAL, DIMENSION(:) :: WORK

REAL :: TOL


SUBROUTINE PSTRF_64(UPLO, N, A, LDA, PIV, RANK, TOL, WORK, INFO)


REAL, DIMENSION(:,:) :: A

INTEGER(8) :: N, LDA, RANK, INFO

CHARACTER(LEN=1) :: UPLO

INTEGER(8), DIMENSION(:) :: PIV

REAL, DIMENSION(:) :: WORK

REAL :: TOL


C INTERFACE
#include <sunperf.h>

void spstrf (char uplo, int n, float *a, int lda, int *piv, int  *rank,
float tol, int *info);


void  spstrf_64 (char uplo, long n, float *a, long lda, long *piv, long
*rank, float tol, long *info);

Description

Oracle Solaris Studio Performance Library                           spstrf(3P)



NAME
       spstrf - compute the Cholesky factorization with complete pivoting of a
       real symmetric positive semidefinite matrix A


SYNOPSIS
       SUBROUTINE SPSTRF(UPLO, N, A, LDA, PIV, RANK, TOL, WORK, INFO)


       REAL TOL

       INTEGER INFO, LDA, N, RANK

       CHARACTER*1 UPLO

       REAL A(LDA,*), WORK(2*N)

       INTEGER PIV(N)


       SUBROUTINE SPSTRF_64(UPLO, N, A, LDA, PIV, RANK, TOL, WORK, INFO)


       REAL TOL

       INTEGER*8 INFO, LDA, N, RANK

       CHARACTER*1 UPLO

       REAL A(LDA,*), WORK(2*N)

       INTEGER*8 PIV(N)


   F95 INTERFACE
       SUBROUTINE PSTRF(UPLO, N, A, LDA, PIV, RANK, TOL, WORK, INFO)


       REAL, DIMENSION(:,:) :: A

       INTEGER :: N, LDA, RANK, INFO

       CHARACTER(LEN=1) :: UPLO

       INTEGER, DIMENSION(:) :: PIV

       REAL, DIMENSION(:) :: WORK

       REAL :: TOL


       SUBROUTINE PSTRF_64(UPLO, N, A, LDA, PIV, RANK, TOL, WORK, INFO)


       REAL, DIMENSION(:,:) :: A

       INTEGER(8) :: N, LDA, RANK, INFO

       CHARACTER(LEN=1) :: UPLO

       INTEGER(8), DIMENSION(:) :: PIV

       REAL, DIMENSION(:) :: WORK

       REAL :: TOL


   C INTERFACE
       #include <sunperf.h>

       void spstrf (char uplo, int n, float *a, int lda, int *piv, int  *rank,
                 float tol, int *info);


       void  spstrf_64 (char uplo, long n, float *a, long lda, long *piv, long
                 *rank, float tol, long *info);


PURPOSE
       spstrf computes the Cholesky factorization with complete pivoting of  a
       real symmetric positive semidefinite matrix A.

       The  factorization  has  the  form P**T * A * P = U**T * U ,  if UPLO =
       'U', P**T * A * P = L  * L**T,  if UPLO = 'L', where U is an upper tri-
       angular  matrix  and  L  is lower triangular, and P is stored as vector
       PIV.

       This algorithm does not attempt to check that A is  positive  semidefi-
       nite. This version of the algorithm calls level 3 BLAS.


ARGUMENTS
       UPLO (input)
                 UPLO is CHARACTER*1
                 Specifies  whether  the upper or lower triangular part of the
                 symmetric matrix A is stored.
                 = 'U':  Upper triangular
                 = 'L':  Lower triangular


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


       A (input/output)
                 A is REAL array, dimension (LDA,N)
                 On entry, the symmetric matrix A. If UPLO = 'U', the  leading
                 n by n upper triangular part of A contains the upper triangu-
                 lar part of the matrix A, and the strictly  lower  triangular
                 part  of A is not referenced. If UPLO = 'L', the leading n by
                 n lower triangular part of A contains  the  lower  triangular
                 part  of the matrix A, and the strictly upper triangular part
                 of A is not referenced.
                 On exit, if INFO = 0, the factor U or  L  from  the  Cholesky
                 factorization as above.


       LDA (input)
                 LDA is INTEGER
                 The leading dimension of the array A.
                 LDA >= max(1,N).


       PIV (output)
                 PIV is INTEGER array, dimension (N)
                 PIV  is such that the nonzero entries are P( PIV(K), K ) = 1.


       RANK (output)
                 RANK is INTEGER
                 The rank of A given by the number of steps the algorithm com-
                 pleted.


       TOL (input)
                 TOL is REAL
                 User  defined  tolerance.  If TOL < 0, then N*U*MAX( A(K,K) )
                 will be used. The algorithm terminates at the (K-1)st step if
                 the pivot <= TOL.


       WORK (output)
                 WORK is REAL array, dimension (2*N)
                 Work space.


       INFO (output)
                 INFO is INTEGER
                 < 0: If INFO = -K, the K-th argument had an illegal value,
                 = 0: algorithm completed successfully, and
                 > 0: the matrix A is either rank deficient with computed rank
                 as returned in RANK, or is  indefinite.   See  Section  7  of
                 LAPACK Working Note #161 for further information.



                                  7 Nov 2015                        spstrf(3P)