Contents
     dtpsv - solve one of the systems of equations A*x  =  b,  or
     A'*x = b
     SUBROUTINE DTPSV(UPLO, TRANSA, DIAG, N, A, Y, INCY)
     CHARACTER * 1 UPLO, TRANSA, DIAG
     INTEGER N, INCY
     DOUBLE PRECISION A(*), Y(*)
     SUBROUTINE DTPSV_64(UPLO, TRANSA, DIAG, N, A, Y, INCY)
     CHARACTER * 1 UPLO, TRANSA, DIAG
     INTEGER*8 N, INCY
     DOUBLE PRECISION A(*), Y(*)
  F95 INTERFACE
     SUBROUTINE TPSV(UPLO, [TRANSA], DIAG, [N], A, Y, [INCY])
     CHARACTER(LEN=1) :: UPLO, TRANSA, DIAG
     INTEGER :: N, INCY
     REAL(8), DIMENSION(:) :: A, Y
     SUBROUTINE TPSV_64(UPLO, [TRANSA], DIAG, [N], A, Y, [INCY])
     CHARACTER(LEN=1) :: UPLO, TRANSA, DIAG
     INTEGER(8) :: N, INCY
     REAL(8), DIMENSION(:) :: A, Y
  C INTERFACE
     #include <sunperf.h>
     void dtpsv(char uplo, char transa, char diag, int n,  double
               *a, double *y, int incy);
     void dtpsv_64(char uplo, char transa,  char  diag,  long  n,
               double *a, double *y, long incy);
     dtpsv solves one of the systems of equations  A*x  =  b,  or
     A'*x  = b, where b and x are n element vectors and A is an n
     by n unit, or non-unit, upper or  lower  triangular  matrix,
     supplied in packed form.
     No test for singularity or near-singularity is  included  in
     this  routine.  Such  tests must be performed before calling
     this routine.
     UPLO (input)
               On entry, UPLO specifies whether the matrix is  an
               upper or lower triangular matrix as follows:
               UPLO = 'U' or  'u'    A  is  an  upper  triangular
               matrix.
               UPLO = 'L'  or  'l'    A  is  a  lower  triangular
               matrix.
               Unchanged on exit.
     TRANSA (input)
               On entry, TRANSA specifies  the  equations  to  be
               solved as follows:
               TRANSA = 'N' or 'n'   A*x = b.
               TRANSA = 'T' or 't'   A'*x = b.
               TRANSA = 'C' or 'c'   A'*x = b.
               Unchanged on exit.
               TRANSA is defaulted to 'N' for F95 INTERFACE.
     DIAG (input)
               On entry, DIAG specifies whether or not A is  unit
               triangular as follows:
               DIAG = 'U' or 'u'   A is assumed to be  unit  tri-
               angular.
               DIAG = 'N' or 'n'   A is not assumed  to  be  unit
               triangular.
               Unchanged on exit.
     N (input)
               On entry, N specifies the order of the  matrix  A.
               N >= 0.  Unchanged on exit.
     A (input)
               ( ( n*( n + 1 ) )/2 ).  Before entry with  UPLO  =
               'U'  or  'u',  the  array A must contain the upper
               triangular matrix packed sequentially,  column  by
               column,  so that A( 1 ) contains a( 1, 1 ), A( 2 )
               and A( 3 ) contain a( 1, 2 ) and a( 2, 2 ) respec-
               tively,  and  so on.  Before entry with UPLO = 'L'
               or 'l', the array A must contain  the  lower  tri-
               angular  matrix  packed  sequentially,  column  by
               column, so that A( 1 ) contains a( 1, 1 ), A( 2  )
               and A( 3 ) contain a( 2, 1 ) and a( 3, 1 ) respec-
               tively, and so on.  Note that when  DIAG = 'U'  or
               'u',  the  diagonal  elements  of A are not refer-
               enced, but are assumed to be unity.  Unchanged  on
               exit.
     Y (input/output)
               ( 1 + ( n - 1 )*abs( INCY ) ).  Before entry,  the
               incremented  array  Y  must  contain the n element
               right-hand side vector b. On exit, Y is  overwrit-
               ten with the solution vector x.
     INCY (input)
               On entry, INCY specifies  the  increment  for  the
               elements of Y. INCY <> 0.  Unchanged on exit.