Contents


NAME

     dtrtri - compute the inverse of a real upper or  lower  tri-
     angular matrix A

SYNOPSIS

     SUBROUTINE DTRTRI(UPLO, DIAG, N, A, LDA, INFO)

     CHARACTER * 1 UPLO, DIAG
     INTEGER N, LDA, INFO
     DOUBLE PRECISION A(LDA,*)

     SUBROUTINE DTRTRI_64(UPLO, DIAG, N, A, LDA, INFO)

     CHARACTER * 1 UPLO, DIAG
     INTEGER*8 N, LDA, INFO
     DOUBLE PRECISION A(LDA,*)

  F95 INTERFACE
     SUBROUTINE TRTRI(UPLO, DIAG, N, A, [LDA], [INFO])

     CHARACTER(LEN=1) :: UPLO, DIAG
     INTEGER :: N, LDA, INFO
     REAL(8), DIMENSION(:,:) :: A

     SUBROUTINE TRTRI_64(UPLO, DIAG, N, A, [LDA], [INFO])

     CHARACTER(LEN=1) :: UPLO, DIAG
     INTEGER(8) :: N, LDA, INFO
     REAL(8), DIMENSION(:,:) :: A

  C INTERFACE
     #include <sunperf.h>

     void dtrtri(char uplo, char diag, int n, double *a, int lda,
               int *info);

     void dtrtri_64(char uplo, char diag, long n, double *a, long
               lda, long *info);

PURPOSE

     dtrtri computes the inverse of a real upper  or  lower  tri-
     angular matrix A.

     This is the Level 3 BLAS version of the algorithm.

ARGUMENTS

     UPLO (input)
               = 'U':  A is upper triangular;
               = 'L':  A is lower triangular.

     DIAG (input)
               = 'N':  A is non-unit triangular;
               = 'U':  A is unit triangular.

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

     A (input/output)
               On entry, the triangular matrix A.  If UPLO = 'U',
               the  leading  N-by-N  upper triangular part of the
               array A contains the upper triangular matrix,  and
               the  strictly  lower  triangular  part of A is not
               referenced.  If UPLO =  'L',  the  leading  N-by-N
               lower  triangular part of the array A contains the
               lower triangular matrix, and  the  strictly  upper
               triangular part of A is not referenced.  If DIAG =
               'U', the diagonal  elements  of  A  are  also  not
               referenced  and are assumed to be 1.  On exit, the
               (triangular) inverse of the  original  matrix,  in
               the same storage format.

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

     INFO (output)
               = 0: successful exit
               < 0: if INFO = -i, the i-th argument had an  ille-
               gal value
               > 0: if INFO = i, A(i,i)  is  exactly  zero.   The
               triangular  matrix is singular and its inverse can
               not be computed.