Previous Next Contents Generated Index Doc Set Home



Solution to a Linear System in a Triangular Matrix

The subroutines described in this section solve the linear system Ax = b for a triangular matrix A and vectors b and x.

Calling Sequence

CALL DTRSL 
(DA, LDA, N, DB, JOB, INFO)
CALL STRSL 
(SA, LDA, N, SB, JOB, INFO)
CALL ZTRSL 
(ZA, LDA, N, ZB, JOB, INFO)
CALL CTRSL 
(CA, LDA, N, CB, JOB, INFO)






void dtrsl 
(double *da, int lda, int n, double *db, int job, int 
*info)
void strsl 
(float *sa, int lda, int n, float *sb, int job, int 
*info)
void ztrsl 
(doublecomplex *za, int lda, int n, doublecomplex *zb, 
int job, int *info)
void ctrsl 
(complex *ca, int lda, int n, complex *cb, int job, int 
*info)

Arguments

xA

Matrix A.

LDA

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

N

Order of the matrix A. N 0.

xB

On entry, the right-hand side vector b.
On exit, the solution vector x.

JOB

Determines which operation the subroutine will perform:

00

solve Ax = b, A lower triangular

01

solve Ax = b, A upper triangular

10

solve AHx = b, A lower triangular

11

solve AHx = b, A upper triangular

Note that ATx = AHx for real matrices.

INFO

On exit:

INFO = 0

Subroutine completed normally.

INFO > 0

Returns the index of the first zero diagonal element of A.

Sample Program

 
      PROGRAM TEST
      IMPLICIT NONE
C
      INTEGER           LDA, LOTRAN, N
      PARAMETER        (LOTRAN = 10)
      PARAMETER        (N = 5)
      PARAMETER        (LDA = N)
C
      DOUBLE PRECISION  A(LDA,N), B(N)
      INTEGER           ICOL, INFO, IROW, JOB
C
      EXTERNAL          DTRSL
C
C     Initialize the array A to store the 5x5 triangular matrix A
C     shown below.
C
C         1                    5
C         1  1                 4
C     A = 1  1  1          b = 3
C         1  1  1  1           2
C         1  1  1  1  1        1
C
      DATA A / 5*1.0D0, 8D8, 4*1.0D0, 2*8D8, 3*1.0D0, 3*8D8,
     $         2*1.0D0, 4*8D8, 1.0D0 /
      DATA B / 5.0D0, 4.0D0, 3.0D0, 2.0D0, 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)
      PRINT 1030
      PRINT 1040, B
C
C     Solve the matrix in banded form.
C
      JOB = LOTRAN
      CALL DTRSL (A, LDA, N, B, JOB, INFO)
      IF (INFO .EQ. 0) THEN
        PRINT 1050
        PRINT 1040, B
      ELSE
        PRINT 1060, 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, 'b:')
 1040 FORMAT (3X, F4.1)
 1050 FORMAT (/1X, 'A''**(-1) * b:')
 1060 FORMAT (1X, 'A appears singular at ', I2)
C
      END
 

Sample Output

 
 A in full form:
    1.0
    1.0    1.0
    1.0    1.0    1.0
    1.0    1.0    1.0    1.0
    1.0    1.0    1.0    1.0    1.0



 A in triangular form: (* in unused elements)
    1.0   ****   ****   ****   ****
    1.0    1.0   ****   ****   ****
    1.0    1.0    1.0   ****   ****
    1.0    1.0    1.0    1.0   ****
    1.0    1.0    1.0    1.0    1.0



 b:
    5.0
    4.0
    3.0
    2.0
    1.0



 A'**(-1) * b:
    1.0
    1.0
    1.0
    1.0
    1.0








Previous Next Contents Generated Index Doc Set Home