REAL routines for triangular, packed storage matrix

stpcon

USAGE:
  rcond, info = NumRu::Lapack.stpcon( norm, uplo, diag, ap, [:usage => usage, :help => help])


FORTRAN MANUAL
      SUBROUTINE STPCON( NORM, UPLO, DIAG, N, AP, RCOND, WORK, IWORK, INFO )

*  Purpose
*  =======
*
*  STPCON estimates the reciprocal of the condition number of a packed
*  triangular matrix A, in either the 1-norm or the infinity-norm.
*
*  The norm of A is computed and an estimate is obtained for
*  norm(inv(A)), then the reciprocal of the condition number is
*  computed as
*     RCOND = 1 / ( norm(A) * norm(inv(A)) ).
*

*  Arguments
*  =========
*
*  NORM    (input) CHARACTER*1
*          Specifies whether the 1-norm condition number or the
*          infinity-norm condition number is required:
*          = '1' or 'O':  1-norm;
*          = 'I':         Infinity-norm.
*
*  UPLO    (input) CHARACTER*1
*          = 'U':  A is upper triangular;
*          = 'L':  A is lower triangular.
*
*  DIAG    (input) CHARACTER*1
*          = 'N':  A is non-unit triangular;
*          = 'U':  A is unit triangular.
*
*  N       (input) INTEGER
*          The order of the matrix A.  N >= 0.
*
*  AP      (input) REAL array, dimension (N*(N+1)/2)
*          The upper or lower triangular matrix A, packed columnwise in
*          a linear array.  The j-th column of A is stored in the array
*          AP as follows:
*          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
*          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
*          If DIAG = 'U', the diagonal elements of A are not referenced
*          and are assumed to be 1.
*
*  RCOND   (output) REAL
*          The reciprocal of the condition number of the matrix A,
*          computed as RCOND = 1/(norm(A) * norm(inv(A))).
*
*  WORK    (workspace) REAL array, dimension (3*N)
*
*  IWORK   (workspace) INTEGER array, dimension (N)
*
*  INFO    (output) INTEGER
*          = 0:  successful exit
*          < 0:  if INFO = -i, the i-th argument had an illegal value
*

*  =====================================================================
*


    
go to the page top

stprfs

USAGE:
  ferr, berr, info = NumRu::Lapack.stprfs( uplo, trans, diag, ap, b, x, [:usage => usage, :help => help])


FORTRAN MANUAL
      SUBROUTINE STPRFS( UPLO, TRANS, DIAG, N, NRHS, AP, B, LDB, X, LDX, FERR, BERR, WORK, IWORK, INFO )

*  Purpose
*  =======
*
*  STPRFS provides error bounds and backward error estimates for the
*  solution to a system of linear equations with a triangular packed
*  coefficient matrix.
*
*  The solution matrix X must be computed by STPTRS or some other
*  means before entering this routine.  STPRFS does not do iterative
*  refinement because doing so cannot improve the backward error.
*

*  Arguments
*  =========
*
*  UPLO    (input) CHARACTER*1
*          = 'U':  A is upper triangular;
*          = 'L':  A is lower triangular.
*
*  TRANS   (input) CHARACTER*1
*          Specifies the form of the system of equations:
*          = 'N':  A * X = B  (No transpose)
*          = 'T':  A**T * X = B  (Transpose)
*          = 'C':  A**H * X = B  (Conjugate transpose = Transpose)
*
*  DIAG    (input) CHARACTER*1
*          = 'N':  A is non-unit triangular;
*          = 'U':  A is unit triangular.
*
*  N       (input) INTEGER
*          The order of the matrix A.  N >= 0.
*
*  NRHS    (input) INTEGER
*          The number of right hand sides, i.e., the number of columns
*          of the matrices B and X.  NRHS >= 0.
*
*  AP      (input) REAL array, dimension (N*(N+1)/2)
*          The upper or lower triangular matrix A, packed columnwise in
*          a linear array.  The j-th column of A is stored in the array
*          AP as follows:
*          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
*          if UPLO = 'L', AP(i + (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n.
*          If DIAG = 'U', the diagonal elements of A are not referenced
*          and are assumed to be 1.
*
*  B       (input) REAL array, dimension (LDB,NRHS)
*          The right hand side matrix B.
*
*  LDB     (input) INTEGER
*          The leading dimension of the array B.  LDB >= max(1,N).
*
*  X       (input) REAL array, dimension (LDX,NRHS)
*          The solution matrix X.
*
*  LDX     (input) INTEGER
*          The leading dimension of the array X.  LDX >= max(1,N).
*
*  FERR    (output) REAL array, dimension (NRHS)
*          The estimated forward error bound for each solution vector
*          X(j) (the j-th column of the solution matrix X).
*          If XTRUE is the true solution corresponding to X(j), FERR(j)
*          is an estimated upper bound for the magnitude of the largest
*          element in (X(j) - XTRUE) divided by the magnitude of the
*          largest element in X(j).  The estimate is as reliable as
*          the estimate for RCOND, and is almost always a slight
*          overestimate of the true error.
*
*  BERR    (output) REAL array, dimension (NRHS)
*          The componentwise relative backward error of each solution
*          vector X(j) (i.e., the smallest relative change in
*          any element of A or B that makes X(j) an exact solution).
*
*  WORK    (workspace) REAL array, dimension (3*N)
*
*  IWORK   (workspace) INTEGER array, dimension (N)
*
*  INFO    (output) INTEGER
*          = 0:  successful exit
*          < 0:  if INFO = -i, the i-th argument had an illegal value
*

*  =====================================================================
*


    
go to the page top

stptri

USAGE:
  info, ap = NumRu::Lapack.stptri( uplo, diag, n, ap, [:usage => usage, :help => help])


FORTRAN MANUAL
      SUBROUTINE STPTRI( UPLO, DIAG, N, AP, INFO )

*  Purpose
*  =======
*
*  STPTRI computes the inverse of a real upper or lower triangular
*  matrix A stored in packed format.
*

*  Arguments
*  =========
*
*  UPLO    (input) CHARACTER*1
*          = 'U':  A is upper triangular;
*          = 'L':  A is lower triangular.
*
*  DIAG    (input) CHARACTER*1
*          = 'N':  A is non-unit triangular;
*          = 'U':  A is unit triangular.
*
*  N       (input) INTEGER
*          The order of the matrix A.  N >= 0.
*
*  AP      (input/output) REAL array, dimension (N*(N+1)/2)
*          On entry, the upper or lower triangular matrix A, stored
*          columnwise in a linear array.  The j-th column of A is stored
*          in the array AP as follows:
*          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
*          if UPLO = 'L', AP(i + (j-1)*((2*n-j)/2) = A(i,j) for j<=i<=n.
*          See below for further details.
*          On exit, the (triangular) inverse of the original matrix, in
*          the same packed storage format.
*
*  INFO    (output) INTEGER
*          = 0:  successful exit
*          < 0:  if INFO = -i, the i-th argument had an illegal value
*          > 0:  if INFO = i, A(i,i) is exactly zero.  The triangular
*                matrix is singular and its inverse can not be computed.
*

*  Further Details
*  ===============
*
*  A triangular matrix A can be transferred to packed storage using one
*  of the following program segments:
*
*  UPLO = 'U':                      UPLO = 'L':
*
*        JC = 1                           JC = 1
*        DO 2 J = 1, N                    DO 2 J = 1, N
*           DO 1 I = 1, J                    DO 1 I = J, N
*              AP(JC+I-1) = A(I,J)              AP(JC+I-J) = A(I,J)
*      1    CONTINUE                    1    CONTINUE
*           JC = JC + J                      JC = JC + N - J + 1
*      2 CONTINUE                       2 CONTINUE
*
*  =====================================================================
*


    
go to the page top

stptrs

USAGE:
  info, b = NumRu::Lapack.stptrs( uplo, trans, diag, n, ap, b, [:usage => usage, :help => help])


FORTRAN MANUAL
      SUBROUTINE STPTRS( UPLO, TRANS, DIAG, N, NRHS, AP, B, LDB, INFO )

*  Purpose
*  =======
*
*  STPTRS solves a triangular system of the form
*
*     A * X = B  or  A**T * X = B,
*
*  where A is a triangular matrix of order N stored in packed format,
*  and B is an N-by-NRHS matrix.  A check is made to verify that A is
*  nonsingular.
*

*  Arguments
*  =========
*
*  UPLO    (input) CHARACTER*1
*          = 'U':  A is upper triangular;
*          = 'L':  A is lower triangular.
*
*  TRANS   (input) CHARACTER*1
*          Specifies the form of the system of equations:
*          = 'N':  A * X = B  (No transpose)
*          = 'T':  A**T * X = B  (Transpose)
*          = 'C':  A**H * X = B  (Conjugate transpose = Transpose)
*
*  DIAG    (input) CHARACTER*1
*          = 'N':  A is non-unit triangular;
*          = 'U':  A is unit triangular.
*
*  N       (input) INTEGER
*          The order of the matrix A.  N >= 0.
*
*  NRHS    (input) INTEGER
*          The number of right hand sides, i.e., the number of columns
*          of the matrix B.  NRHS >= 0.
*
*  AP      (input) REAL array, dimension (N*(N+1)/2)
*          The upper or lower triangular matrix A, packed columnwise in
*          a linear array.  The j-th column of A is stored in the array
*          AP as follows:
*          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
*          if UPLO = 'L', AP(i + (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n.
*
*  B       (input/output) REAL array, dimension (LDB,NRHS)
*          On entry, the right hand side matrix B.
*          On exit, if INFO = 0, the solution matrix X.
*
*  LDB     (input) INTEGER
*          The leading dimension of the array B.  LDB >= max(1,N).
*
*  INFO    (output) INTEGER
*          = 0:  successful exit
*          < 0:  if INFO = -i, the i-th argument had an illegal value
*          > 0:  if INFO = i, the i-th diagonal element of A is zero,
*                indicating that the matrix is singular and the
*                solutions X have not been computed.
*

*  =====================================================================
*


    
go to the page top

stpttf

USAGE:
  arf, info = NumRu::Lapack.stpttf( transr, uplo, n, ap, [:usage => usage, :help => help])


FORTRAN MANUAL
      SUBROUTINE STPTTF( TRANSR, UPLO, N, AP, ARF, INFO )

*  Purpose
*  =======
*
*  STPTTF copies a triangular matrix A from standard packed format (TP)
*  to rectangular full packed format (TF).
*

*  Arguments
*  =========
*
*  TRANSR   (input) CHARACTER*1
*          = 'N':  ARF in Normal format is wanted;
*          = 'T':  ARF in Conjugate-transpose format is wanted.
*
*  UPLO    (input) CHARACTER*1
*          = 'U':  A is upper triangular;
*          = 'L':  A is lower triangular.
*
*  N       (input) INTEGER
*          The order of the matrix A.  N >= 0.
*
*  AP      (input) REAL array, dimension ( N*(N+1)/2 ),
*          On entry, the upper or lower triangular matrix A, packed
*          columnwise in a linear array. The j-th column of A is stored
*          in the array AP as follows:
*          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
*          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
*
*  ARF     (output) REAL array, dimension ( N*(N+1)/2 ),
*          On exit, the upper or lower triangular matrix A stored in
*          RFP format. For a further discussion see Notes below.
*
*  INFO    (output) INTEGER
*          = 0:  successful exit
*          < 0:  if INFO = -i, the i-th argument had an illegal value
*

*  Further Details
*  ===============
*
*  We first consider Rectangular Full Packed (RFP) Format when N is
*  even. We give an example where N = 6.
*
*      AP is Upper             AP is Lower
*
*   00 01 02 03 04 05       00
*      11 12 13 14 15       10 11
*         22 23 24 25       20 21 22
*            33 34 35       30 31 32 33
*               44 45       40 41 42 43 44
*                  55       50 51 52 53 54 55
*
*
*  Let TRANSR = 'N'. RFP holds AP as follows:
*  For UPLO = 'U' the upper trapezoid A(0:5,0:2) consists of the last
*  three columns of AP upper. The lower triangle A(4:6,0:2) consists of
*  the transpose of the first three columns of AP upper.
*  For UPLO = 'L' the lower trapezoid A(1:6,0:2) consists of the first
*  three columns of AP lower. The upper triangle A(0:2,0:2) consists of
*  the transpose of the last three columns of AP lower.
*  This covers the case N even and TRANSR = 'N'.
*
*         RFP A                   RFP A
*
*        03 04 05                33 43 53
*        13 14 15                00 44 54
*        23 24 25                10 11 55
*        33 34 35                20 21 22
*        00 44 45                30 31 32
*        01 11 55                40 41 42
*        02 12 22                50 51 52
*
*  Now let TRANSR = 'T'. RFP A in both UPLO cases is just the
*  transpose of RFP A above. One therefore gets:
*
*
*           RFP A                   RFP A
*
*     03 13 23 33 00 01 02    33 00 10 20 30 40 50
*     04 14 24 34 44 11 12    43 44 11 21 31 41 51
*     05 15 25 35 45 55 22    53 54 55 22 32 42 52
*
*
*  We then consider Rectangular Full Packed (RFP) Format when N is
*  odd. We give an example where N = 5.
*
*     AP is Upper                 AP is Lower
*
*   00 01 02 03 04              00
*      11 12 13 14              10 11
*         22 23 24              20 21 22
*            33 34              30 31 32 33
*               44              40 41 42 43 44
*
*
*  Let TRANSR = 'N'. RFP holds AP as follows:
*  For UPLO = 'U' the upper trapezoid A(0:4,0:2) consists of the last
*  three columns of AP upper. The lower triangle A(3:4,0:1) consists of
*  the transpose of the first two columns of AP upper.
*  For UPLO = 'L' the lower trapezoid A(0:4,0:2) consists of the first
*  three columns of AP lower. The upper triangle A(0:1,1:2) consists of
*  the transpose of the last two columns of AP lower.
*  This covers the case N odd and TRANSR = 'N'.
*
*         RFP A                   RFP A
*
*        02 03 04                00 33 43
*        12 13 14                10 11 44
*        22 23 24                20 21 22
*        00 33 34                30 31 32
*        01 11 44                40 41 42
*
*  Now let TRANSR = 'T'. RFP A in both UPLO cases is just the
*  transpose of RFP A above. One therefore gets:
*
*           RFP A                   RFP A
*
*     02 12 22 00 01             00 10 20 30 40 50
*     03 13 23 33 11             33 11 21 31 41 51
*     04 14 24 34 44             43 44 22 32 42 52
*
*  =====================================================================
*


    
go to the page top

stpttr

USAGE:
  a, info = NumRu::Lapack.stpttr( uplo, ap, [:usage => usage, :help => help])


FORTRAN MANUAL
      SUBROUTINE STPTTR( UPLO, N, AP, A, LDA, INFO )

*  Purpose
*  =======
*
*  STPTTR copies a triangular matrix A from standard packed format (TP)
*  to standard full format (TR).
*

*  Arguments
*  =========
*
*  UPLO    (input) CHARACTER*1
*          = 'U':  A is upper triangular.
*          = 'L':  A is lower triangular.
*
*  N       (input) INTEGER
*          The order of the matrix A. N >= 0.
*
*  AP      (input) REAL array, dimension ( N*(N+1)/2 ),
*          On entry, the upper or lower triangular matrix A, packed
*          columnwise in a linear array. The j-th column of A is stored
*          in the array AP as follows:
*          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
*          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
*
*  A       (output) REAL array, dimension ( LDA, N )
*          On exit, the triangular matrix A.  If UPLO = 'U', the leading
*          N-by-N upper triangular part of A contains the upper
*          triangular part of the matrix A, and the strictly lower
*          triangular part of A is not referenced.  If UPLO = 'L', the
*          leading N-by-N lower triangular part of A contains the lower
*          triangular part of the matrix A, and the strictly upper
*          triangular part of A is not referenced.
*
*  LDA     (input) INTEGER
*          The leading dimension of the array A.  LDA >= max(1,N).
*
*  INFO    (output) INTEGER
*          = 0:  successful exit
*          < 0:  if INFO = -i, the i-th argument had an illegal value
*

*  =====================================================================
*


    
go to the page top
back to matrix types
back to data types