Previous Next Contents Generated Index Doc Set Home



Determinant and Inverse of a Triangular Matrix

The subroutines described in this section compute the determinant and inverse of a triangular matrix A.

Calling Sequence

CALL DTRDI 
(DA, LDA, N, DDET, JOB, INFO)
CALL STRDI 
(SA, LDA, N, SDET, JOB, INFO)
CALL ZTRDI 
(ZA, LDA, N, ZDET, JOB, INFO)
CALL CTRDI 
(CA, LDA, N, CDET, JOB, INFO)






void dtrdi 
(double *da, int lda, int n, double *ddet, int job, int 
*info)
void strdi 
(float *sa, int lda, int n, float *sdet, int job, int 
*info)
void ztrdi 
(doublecomplex *za, int lda, int n, doublecomplex 
*zdet, int job, int *info)
void ctrdi 
(complex *ca, int lda, int n, complex *cdet, int job, 
int *info)

Arguments

xA

On entry, the matrix A.
On exit, the inverse of the original matrix A if the inverse was requested, otherwise unchanged.

LDA

Leading dimension of the array A as specified in a dimension or type statement. LDA max(1,N).

N

Order of the original matrix A. N 0.

xDET

On exit, the determinant of the matrix A. The determinant is stored as b × 10expon where b is stored in DET(1) and expon is stored in DET(2). 1.0 |DET(1)| < 10.0 or DET(1) = 0.0.

JOB

Determines which operation the subroutine will perform:

010

no determinant, inverse of lower triangular A

011

no determinant, inverse of upper triangular A

100

determinant, no inverse

110

determinant, inverse of lower triangular A

111

determinant, inverse of upper triangular A

INFO

On exit:

INFO = 0

Subroutine completed normally.

INFO > 0

Contains the index of a zero element of A if the inverse is requested and A is singular.

Sample Program




      PROGRAM TEST
      IMPLICIT NONE
C
      INTEGER           INDTLO, LDA, N
      PARAMETER        (INDTLO = 110)
      PARAMETER        (N = 5)
      PARAMETER        (LDA = N)
C
      DOUBLE PRECISION  A(LDA,N), DET(2)
      INTEGER           ICOL, INFO, IROW, JOB
C
      EXTERNAL          DTRDI
C
C     Initialize the array A to store the 5x5 triangular matrix A
C     shown below.
C
C         1
C         1  -1
C     A = 1  -2  1
C         1  -3  3  -1
C         1  -4  6  -4  1
C
      DATA A / 5*1.0D0, 8D8, -1.0D0, -2.0D0, -3.0D0, -4.0D0,
     $         2*8D8, 1.0D0, 3.0D0, 6.0D0, 3*8D8, -1.0D0,
     $         -4.0D0, 4*8D8, 1.0D0 /
C
C     Print the initial values of the arrays.
C
      PRINT 1000
      DO 100, IROW = 1, N
        PRINT 1010, (A(IROW,ICOL), ICOL = 1, IROW)
  100 CONTINUE
      PRINT 1020
      PRINT 1010, ((A(IROW,ICOL), ICOL = 1, N), IROW = 1, LDA)
C
C     Factor the matrix in banded form.
C
      JOB = INDTLO
      CALL DTRDI (A, LDA, N, DET, JOB, INFO)
      IF (INFO .EQ. 0) THEN
        PRINT 1030, DET(1) * (10.0 ** DET(2))
        PRINT 1040
        DO 110, IROW = 1, N
          PRINT 1010, (A(IROW,ICOL), ICOL = 1, IROW)
  110   CONTINUE
      ELSE
        PRINT 1050, INFO
      END IF
C
 1000 FORMAT (1X, `A in full form:')
 1010 FORMAT (5(3X, F4.1))
 1020 FORMAT (/1X, `A in triangular form: (* in unused elements)')
 1030 FORMAT (/1X, `det(A) = `, F4.1)
 1040 FORMAT (/1X, `A**(-1):')
 1050 FORMAT (1X, `A appears singular at `, I2)
C
      END



Sample Output

 
 A in full form:
    1.0
    1.0   -1.0
    1.0   -2.0    1.0
    1.0   -3.0    3.0   -1.0
    1.0   -4.0    6.0   -4.0    1.0



 A in triangular form: (* in unused elements)
    1.0   ****   ****   ****   ****
    1.0   -1.0   ****   ****   ****
    1.0   -2.0    1.0   ****   ****
    1.0   -3.0    3.0   -1.0   ****
    1.0   -4.0    6.0   -4.0    1.0



 det(A) =  1.0



 A**(-1):
    1.0
    1.0   -1.0
    1.0   -2.0    1.0
    1.0   -3.0    3.0   -1.0
    1.0   -4.0    6.0   -4.0    1.0






Previous Next Contents Generated Index Doc Set Home