LAPACK 3.3.0

dtbt03.f

Go to the documentation of this file.
00001       SUBROUTINE DTBT03( UPLO, TRANS, DIAG, N, KD, NRHS, AB, LDAB,
00002      $                   SCALE, CNORM, TSCAL, X, LDX, B, LDB, WORK,
00003      $                   RESID )
00004 *
00005 *  -- LAPACK test routine (version 3.1) --
00006 *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
00007 *     November 2006
00008 *
00009 *     .. Scalar Arguments ..
00010       CHARACTER          DIAG, TRANS, UPLO
00011       INTEGER            KD, LDAB, LDB, LDX, N, NRHS
00012       DOUBLE PRECISION   RESID, SCALE, TSCAL
00013 *     ..
00014 *     .. Array Arguments ..
00015       DOUBLE PRECISION   AB( LDAB, * ), B( LDB, * ), CNORM( * ),
00016      $                   WORK( * ), X( LDX, * )
00017 *     ..
00018 *
00019 *  Purpose
00020 *  =======
00021 *
00022 *  DTBT03 computes the residual for the solution to a scaled triangular
00023 *  system of equations  A*x = s*b  or  A'*x = s*b  when A is a
00024 *  triangular band matrix. Here A' is the transpose of A, s is a scalar,
00025 *  and x and b are N by NRHS matrices.  The test ratio is the maximum
00026 *  over the number of right hand sides of
00027 *     norm(s*b - op(A)*x) / ( norm(op(A)) * norm(x) * EPS ),
00028 *  where op(A) denotes A or A' and EPS is the machine epsilon.
00029 *
00030 *  Arguments
00031 *  =========
00032 *
00033 *  UPLO    (input) CHARACTER*1
00034 *          Specifies whether the matrix A is upper or lower triangular.
00035 *          = 'U':  Upper triangular
00036 *          = 'L':  Lower triangular
00037 *
00038 *  TRANS   (input) CHARACTER*1
00039 *          Specifies the operation applied to A.
00040 *          = 'N':  A *x = b  (No transpose)
00041 *          = 'T':  A'*x = b  (Transpose)
00042 *          = 'C':  A'*x = b  (Conjugate transpose = Transpose)
00043 *
00044 *  DIAG    (input) CHARACTER*1
00045 *          Specifies whether or not the matrix A is unit triangular.
00046 *          = 'N':  Non-unit triangular
00047 *          = 'U':  Unit triangular
00048 *
00049 *  N       (input) INTEGER
00050 *          The order of the matrix A.  N >= 0.
00051 *
00052 *  KD      (input) INTEGER
00053 *          The number of superdiagonals or subdiagonals of the
00054 *          triangular band matrix A.  KD >= 0.
00055 *
00056 *  NRHS    (input) INTEGER
00057 *          The number of right hand sides, i.e., the number of columns
00058 *          of the matrices X and B.  NRHS >= 0.
00059 *
00060 *  AB      (input) DOUBLE PRECISION array, dimension (LDAB,N)
00061 *          The upper or lower triangular band matrix A, stored in the
00062 *          first kd+1 rows of the array. The j-th column of A is stored
00063 *          in the j-th column of the array AB as follows:
00064 *          if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
00065 *          if UPLO = 'L', AB(1+i-j,j)    = A(i,j) for j<=i<=min(n,j+kd).
00066 *
00067 *  LDAB    (input) INTEGER
00068 *          The leading dimension of the array AB.  LDAB >= KD+1.
00069 *
00070 *  SCALE   (input) DOUBLE PRECISION
00071 *          The scaling factor s used in solving the triangular system.
00072 *
00073 *  CNORM   (input) DOUBLE PRECISION array, dimension (N)
00074 *          The 1-norms of the columns of A, not counting the diagonal.
00075 *
00076 *  TSCAL   (input) DOUBLE PRECISION
00077 *          The scaling factor used in computing the 1-norms in CNORM.
00078 *          CNORM actually contains the column norms of TSCAL*A.
00079 *
00080 *  X       (input) DOUBLE PRECISION array, dimension (LDX,NRHS)
00081 *          The computed solution vectors for the system of linear
00082 *          equations.
00083 *
00084 *  LDX     (input) INTEGER
00085 *          The leading dimension of the array X.  LDX >= max(1,N).
00086 *
00087 *  B       (input) DOUBLE PRECISION array, dimension (LDB,NRHS)
00088 *          The right hand side vectors for the system of linear
00089 *          equations.
00090 *
00091 *  LDB     (input) INTEGER
00092 *          The leading dimension of the array B.  LDB >= max(1,N).
00093 *
00094 *  WORK    (workspace) DOUBLE PRECISION array, dimension (N)
00095 *
00096 *  RESID   (output) DOUBLE PRECISION
00097 *          The maximum over the number of right hand sides of
00098 *          norm(op(A)*x - s*b) / ( norm(op(A)) * norm(x) * EPS ).
00099 *
00100 *  =====================================================================
00101 *
00102 *     .. Parameters ..
00103       DOUBLE PRECISION   ONE, ZERO
00104       PARAMETER          ( ONE = 1.0D+0, ZERO = 0.0D+0 )
00105 *     ..
00106 *     .. Local Scalars ..
00107       INTEGER            IX, J
00108       DOUBLE PRECISION   BIGNUM, EPS, ERR, SMLNUM, TNORM, XNORM, XSCAL
00109 *     ..
00110 *     .. External Functions ..
00111       LOGICAL            LSAME
00112       INTEGER            IDAMAX
00113       DOUBLE PRECISION   DLAMCH
00114       EXTERNAL           LSAME, IDAMAX, DLAMCH
00115 *     ..
00116 *     .. External Subroutines ..
00117       EXTERNAL           DAXPY, DCOPY, DLABAD, DSCAL, DTBMV
00118 *     ..
00119 *     .. Intrinsic Functions ..
00120       INTRINSIC          ABS, DBLE, MAX
00121 *     ..
00122 *     .. Executable Statements ..
00123 *
00124 *     Quick exit if N = 0
00125 *
00126       IF( N.LE.0 .OR. NRHS.LE.0 ) THEN
00127          RESID = ZERO
00128          RETURN
00129       END IF
00130       EPS = DLAMCH( 'Epsilon' )
00131       SMLNUM = DLAMCH( 'Safe minimum' )
00132       BIGNUM = ONE / SMLNUM
00133       CALL DLABAD( SMLNUM, BIGNUM )
00134 *
00135 *     Compute the norm of the triangular matrix A using the column
00136 *     norms already computed by DLATBS.
00137 *
00138       TNORM = ZERO
00139       IF( LSAME( DIAG, 'N' ) ) THEN
00140          IF( LSAME( UPLO, 'U' ) ) THEN
00141             DO 10 J = 1, N
00142                TNORM = MAX( TNORM, TSCAL*ABS( AB( KD+1, J ) )+
00143      $                 CNORM( J ) )
00144    10       CONTINUE
00145          ELSE
00146             DO 20 J = 1, N
00147                TNORM = MAX( TNORM, TSCAL*ABS( AB( 1, J ) )+CNORM( J ) )
00148    20       CONTINUE
00149          END IF
00150       ELSE
00151          DO 30 J = 1, N
00152             TNORM = MAX( TNORM, TSCAL+CNORM( J ) )
00153    30    CONTINUE
00154       END IF
00155 *
00156 *     Compute the maximum over the number of right hand sides of
00157 *        norm(op(A)*x - s*b) / ( norm(op(A)) * norm(x) * EPS ).
00158 *
00159       RESID = ZERO
00160       DO 40 J = 1, NRHS
00161          CALL DCOPY( N, X( 1, J ), 1, WORK, 1 )
00162          IX = IDAMAX( N, WORK, 1 )
00163          XNORM = MAX( ONE, ABS( X( IX, J ) ) )
00164          XSCAL = ( ONE / XNORM ) / DBLE( KD+1 )
00165          CALL DSCAL( N, XSCAL, WORK, 1 )
00166          CALL DTBMV( UPLO, TRANS, DIAG, N, KD, AB, LDAB, WORK, 1 )
00167          CALL DAXPY( N, -SCALE*XSCAL, B( 1, J ), 1, WORK, 1 )
00168          IX = IDAMAX( N, WORK, 1 )
00169          ERR = TSCAL*ABS( WORK( IX ) )
00170          IX = IDAMAX( N, X( 1, J ), 1 )
00171          XNORM = ABS( X( IX, J ) )
00172          IF( ERR*SMLNUM.LE.XNORM ) THEN
00173             IF( XNORM.GT.ZERO )
00174      $         ERR = ERR / XNORM
00175          ELSE
00176             IF( ERR.GT.ZERO )
00177      $         ERR = ONE / EPS
00178          END IF
00179          IF( ERR*SMLNUM.LE.TNORM ) THEN
00180             IF( TNORM.GT.ZERO )
00181      $         ERR = ERR / TNORM
00182          ELSE
00183             IF( ERR.GT.ZERO )
00184      $         ERR = ONE / EPS
00185          END IF
00186          RESID = MAX( RESID, ERR )
00187    40 CONTINUE
00188 *
00189       RETURN
00190 *
00191 *     End of DTBT03
00192 *
00193       END
 All Files Functions