Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sla_syrcond (3p)

Name

sla_syrcond - estimate the Skeel condition number for a symmetric indefinite matrix

Synopsis

REAL FUNCTION SLA_SYRCOND(UPLO, N, A, LDA, AF, LDAF,  IPIV,  CMODE,  C,
INFO, WORK, IWORK)


CHARACTER*1 UPLO

INTEGER N, LDA, LDAF, INFO, CMODE

INTEGER IWORK(*), IPIV(*)

REAL A(LDA,*), AF(LDAF,*), WORK(*), C(*)


REAL FUNCTION SLA_SYRCOND_64(UPLO, N, A, LDA, AF, LDAF, IPIV, CMODE, C,
INFO, WORK, IWORK)


CHARACTER*1 UPLO

INTEGER*8 N, LDA, LDAF, INFO, CMODE

INTEGER*8 IWORK(*), IPIV(*)

REAL A(LDA,*), AF(LDAF,*), WORK(*), C(*)


F95 INTERFACE
REAL FUNCTION LA_SYRCOND(UPLO, N, A, LDA, AF,  LDAF,  IPIV,  CMODE,  C,
INFO, WORK, IWORK )


REAL, DIMENSION(:,:) :: A, AF

INTEGER :: N, LDA, LDAF, CMODE, INFO

CHARACTER(LEN=1) :: UPLO

INTEGER, DIMENSION(:) :: IWORK

REAL, DIMENSION(:) :: C, WORK


REAL FUNCTION LA_SYRCOND_64( UPLO, N, A, LDA, AF, LDAF, IPIV, CMODE, C,
INFO, WORK, IWORK)


REAL, DIMENSION(:,:) :: A, AF

INTEGER(8) :: N, LDA, LDAF, CMODE, INFO

CHARACTER(LEN=1) :: UPLO

INTEGER(8), DIMENSION(:) :: IWORK

REAL, DIMENSION(:) :: C, WORK


C INTERFACE
#include <sunperf.h>

float sla_syrcond (char uplo, int n, float *a, int lda, float *af,  int
ldaf, int cmode, float *c, int *info);

float sla_syrcond_64 (char uplo, long n, float *a, long lda, float *af,
long ldaf, long cmode, float *c, long *info);

Description

Oracle Solaris Studio Performance Library                      sla_syrcond(3P)



NAME
       sla_syrcond  -  estimate  the  Skeel  condition  number for a symmetric
       indefinite matrix


SYNOPSIS
       REAL FUNCTION SLA_SYRCOND(UPLO, N, A, LDA, AF, LDAF,  IPIV,  CMODE,  C,
                 INFO, WORK, IWORK)


       CHARACTER*1 UPLO

       INTEGER N, LDA, LDAF, INFO, CMODE

       INTEGER IWORK(*), IPIV(*)

       REAL A(LDA,*), AF(LDAF,*), WORK(*), C(*)


       REAL FUNCTION SLA_SYRCOND_64(UPLO, N, A, LDA, AF, LDAF, IPIV, CMODE, C,
                 INFO, WORK, IWORK)


       CHARACTER*1 UPLO

       INTEGER*8 N, LDA, LDAF, INFO, CMODE

       INTEGER*8 IWORK(*), IPIV(*)

       REAL A(LDA,*), AF(LDAF,*), WORK(*), C(*)


   F95 INTERFACE
       REAL FUNCTION LA_SYRCOND(UPLO, N, A, LDA, AF,  LDAF,  IPIV,  CMODE,  C,
                 INFO, WORK, IWORK )


       REAL, DIMENSION(:,:) :: A, AF

       INTEGER :: N, LDA, LDAF, CMODE, INFO

       CHARACTER(LEN=1) :: UPLO

       INTEGER, DIMENSION(:) :: IWORK

       REAL, DIMENSION(:) :: C, WORK


       REAL FUNCTION LA_SYRCOND_64( UPLO, N, A, LDA, AF, LDAF, IPIV, CMODE, C,
                 INFO, WORK, IWORK)


       REAL, DIMENSION(:,:) :: A, AF

       INTEGER(8) :: N, LDA, LDAF, CMODE, INFO

       CHARACTER(LEN=1) :: UPLO

       INTEGER(8), DIMENSION(:) :: IWORK

       REAL, DIMENSION(:) :: C, WORK


   C INTERFACE
       #include <sunperf.h>

       float sla_syrcond (char uplo, int n, float *a, int lda, float *af,  int
                 ldaf, int cmode, float *c, int *info);

       float sla_syrcond_64 (char uplo, long n, float *a, long lda, float *af,
                 long ldaf, long cmode, float *c, long *info);


PURPOSE
       sla_syrcond estimates the Skeel condition number  of   op(A)  *  op2(C)
       where  op2  is  determined by CMODE as follows CMODE =  1    op2(C) = C
       CMODE =  0    op2(C) = I CMODE = -1    op2(C) = inv(C) The Skeel condi-
       tion  number  cond(A) = norminf( |inv(A)||A| ) is computed by computing
       scaling factors R such that diag(R)*A*op2(C) is  row  equilibrated  and
       computing the standard infinity-norm condition number.


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


       N (input)
                 N is INTEGER
                 The number of linear equations, i.e., the order of the matrix
                 A. N >= 0.


       A (input)
                 A is REAL array, dimension (LDA,N)
                 On entry, the N-by-N matrix A.


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


       AF (input)
                 AF is REAL array, dimension (LDAF,N)
                 The block diagonal matrix  D  and  the  multipliers  used  to
                 obtain the factor U or L as computed by SSYTRF.


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


       IPIV (input)
                 IPIV is INTEGER array, dimension (N)
                 Details  of  the interchanges and the block structure of D as
                 determined by SSYTRF.


       CMODE (input)
                 CMODE is INTEGER
                 Determines op2(C) in the formula op(A) * op2(C) as follows:
                 CMODE =  1    op2(C) = C
                 CMODE =  0    op2(C) = I
                 CMODE = -1    op2(C) = inv(C)


       C (input)
                 C is REAL array, dimension (N)
                 The vector C in the formula op(A) * op2(C).


       INFO (output)
                 INFO is INTEGER
                 = 0:  Successful exit.
                 i > 0:  The ith argument is invalid.


       WORK (input)
                 WORK is REAL array, dimension (3*N).
                 Workspace.


       IWORK (input)
                 IWORK is INTEGER array, dimension (N).
                 Workspace.




                                  7 Nov 2015                   sla_syrcond(3P)