Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

sgetri (3p)

Name

sgetri - compute the inverse of a matrix using the LU factorization computed by SGETRF

Synopsis

SUBROUTINE SGETRI(N, A, LDA, IPIVOT, WORK, LDWORK, INFO)

INTEGER N, LDA, LDWORK, INFO
INTEGER IPIVOT(*)
REAL A(LDA,*), WORK(*)

SUBROUTINE SGETRI_64(N, A, LDA, IPIVOT, WORK, LDWORK, INFO)

INTEGER*8 N, LDA, LDWORK, INFO
INTEGER*8 IPIVOT(*)
REAL A(LDA,*), WORK(*)




F95 INTERFACE
SUBROUTINE GETRI(N, A, LDA, IPIVOT, WORK, LDWORK, INFO)

INTEGER :: N, LDA, LDWORK, INFO
INTEGER, DIMENSION(:) :: IPIVOT
REAL, DIMENSION(:) :: WORK
REAL, DIMENSION(:,:) :: A

SUBROUTINE GETRI_64(N, A, LDA, IPIVOT, WORK, LDWORK, INFO)

INTEGER(8) :: N, LDA, LDWORK, INFO
INTEGER(8), DIMENSION(:) :: IPIVOT
REAL, DIMENSION(:) :: WORK
REAL, DIMENSION(:,:) :: A




C INTERFACE
#include <sunperf.h>

void sgetri(int n, float *a, int lda, int *ipivot, int *info);

void sgetri_64(long n, float *a, long lda, long *ipivot, long *info);

Description

Oracle Solaris Studio Performance Library                           sgetri(3P)



NAME
       sgetri  -  compute  the  inverse of a matrix using the LU factorization
       computed by SGETRF


SYNOPSIS
       SUBROUTINE SGETRI(N, A, LDA, IPIVOT, WORK, LDWORK, INFO)

       INTEGER N, LDA, LDWORK, INFO
       INTEGER IPIVOT(*)
       REAL A(LDA,*), WORK(*)

       SUBROUTINE SGETRI_64(N, A, LDA, IPIVOT, WORK, LDWORK, INFO)

       INTEGER*8 N, LDA, LDWORK, INFO
       INTEGER*8 IPIVOT(*)
       REAL A(LDA,*), WORK(*)




   F95 INTERFACE
       SUBROUTINE GETRI(N, A, LDA, IPIVOT, WORK, LDWORK, INFO)

       INTEGER :: N, LDA, LDWORK, INFO
       INTEGER, DIMENSION(:) :: IPIVOT
       REAL, DIMENSION(:) :: WORK
       REAL, DIMENSION(:,:) :: A

       SUBROUTINE GETRI_64(N, A, LDA, IPIVOT, WORK, LDWORK, INFO)

       INTEGER(8) :: N, LDA, LDWORK, INFO
       INTEGER(8), DIMENSION(:) :: IPIVOT
       REAL, DIMENSION(:) :: WORK
       REAL, DIMENSION(:,:) :: A




   C INTERFACE
       #include <sunperf.h>

       void sgetri(int n, float *a, int lda, int *ipivot, int *info);

       void sgetri_64(long n, float *a, long lda, long *ipivot, long *info);



PURPOSE
       sgetri computes the inverse of a matrix using the LU factorization com-
       puted by SGETRF.

       This  method  inverts  U and then computes inv(A) by solving the system
       inv(A)*L = inv(U) for inv(A).


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


       A (input/output)
                 On entry, the factors L and U  from  the  factorization  A  =
                 P*L*U  as  computed  by  SGETRF.   On  exit, if INFO = 0, the
                 inverse of the original matrix A.


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


       IPIVOT (input)
                 The pivot indices from SGETRF; for  1<=i<=N,  row  i  of  the
                 matrix was interchanged with row IPIVOT(i).


       WORK (workspace)
                 On  exit, if INFO=0, then WORK(1) returns the optimal LDWORK.


       LDWORK (input)
                 The dimension of the array WORK.  LDWORK  >=  max(1,N).   For
                 optimal  performance  LDWORK >= N*NB, where NB is the optimal
                 blocksize returned by ILAENV.

                 If LDWORK = -1, then a workspace query is assumed;  the  rou-
                 tine  only  calculates  the  optimal  size of the WORK array,
                 returns this value as the first entry of the WORK array,  and
                 no error message related to LDWORK is issued by XERBLA.


       INFO (output)
                 = 0:  successful exit
                 < 0:  if INFO = -i, the i-th argument had an illegal value
                 > 0:  if INFO = i, U(i,i) is exactly zero; the matrix is sin-
                 gular and its inverse could not be computed.




                                  7 Nov 2015                        sgetri(3P)