LAPACK 3.3.1
Linear Algebra PACKage

sgtt01.f

Go to the documentation of this file.
00001       SUBROUTINE SGTT01( N, DL, D, DU, DLF, DF, DUF, DU2, IPIV, WORK,
00002      $                   LDWORK, RWORK, RESID )
00003 *
00004 *  -- LAPACK test routine (version 3.1) --
00005 *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
00006 *     November 2006
00007 *
00008 *     .. Scalar Arguments ..
00009       INTEGER            LDWORK, N
00010       REAL               RESID
00011 *     ..
00012 *     .. Array Arguments ..
00013       INTEGER            IPIV( * )
00014       REAL               D( * ), DF( * ), DL( * ), DLF( * ), DU( * ),
00015      $                   DU2( * ), DUF( * ), RWORK( * ),
00016      $                   WORK( LDWORK, * )
00017 *     ..
00018 *
00019 *  Purpose
00020 *  =======
00021 *
00022 *  SGTT01 reconstructs a tridiagonal matrix A from its LU factorization
00023 *  and computes the residual
00024 *     norm(L*U - A) / ( norm(A) * EPS ),
00025 *  where EPS is the machine epsilon.
00026 *
00027 *  Arguments
00028 *  =========
00029 *
00030 *  N       (input) INTEGTER
00031 *          The order of the matrix A.  N >= 0.
00032 *
00033 *  DL      (input) REAL array, dimension (N-1)
00034 *          The (n-1) sub-diagonal elements of A.
00035 *
00036 *  D       (input) REAL array, dimension (N)
00037 *          The diagonal elements of A.
00038 *
00039 *  DU      (input) REAL array, dimension (N-1)
00040 *          The (n-1) super-diagonal elements of A.
00041 *
00042 *  DLF     (input) REAL array, dimension (N-1)
00043 *          The (n-1) multipliers that define the matrix L from the
00044 *          LU factorization of A.
00045 *
00046 *  DF      (input) REAL array, dimension (N)
00047 *          The n diagonal elements of the upper triangular matrix U from
00048 *          the LU factorization of A.
00049 *
00050 *  DUF     (input) REAL array, dimension (N-1)
00051 *          The (n-1) elements of the first super-diagonal of U.
00052 *
00053 *  DU2F    (input) REAL array, dimension (N-2)
00054 *          The (n-2) elements of the second super-diagonal of U.
00055 *
00056 *  IPIV    (input) INTEGER array, dimension (N)
00057 *          The pivot indices; for 1 <= i <= n, row i of the matrix was
00058 *          interchanged with row IPIV(i).  IPIV(i) will always be either
00059 *          i or i+1; IPIV(i) = i indicates a row interchange was not
00060 *          required.
00061 *
00062 *  WORK    (workspace) REAL array, dimension (LDWORK,N)
00063 *
00064 *  LDWORK  (input) INTEGER
00065 *          The leading dimension of the array WORK.  LDWORK >= max(1,N).
00066 *
00067 *  RWORK   (workspace) REAL array, dimension (N)
00068 *
00069 *  RESID   (output) REAL
00070 *          The scaled residual:  norm(L*U - A) / (norm(A) * EPS)
00071 *
00072 *  =====================================================================
00073 *
00074 *     .. Parameters ..
00075       REAL               ONE, ZERO
00076       PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
00077 *     ..
00078 *     .. Local Scalars ..
00079       INTEGER            I, IP, J, LASTJ
00080       REAL               ANORM, EPS, LI
00081 *     ..
00082 *     .. External Functions ..
00083       REAL               SLAMCH, SLANGT, SLANHS
00084       EXTERNAL           SLAMCH, SLANGT, SLANHS
00085 *     ..
00086 *     .. Intrinsic Functions ..
00087       INTRINSIC          MIN
00088 *     ..
00089 *     .. External Subroutines ..
00090       EXTERNAL           SAXPY, SSWAP
00091 *     ..
00092 *     .. Executable Statements ..
00093 *
00094 *     Quick return if possible
00095 *
00096       IF( N.LE.0 ) THEN
00097          RESID = ZERO
00098          RETURN
00099       END IF
00100 *
00101       EPS = SLAMCH( 'Epsilon' )
00102 *
00103 *     Copy the matrix U to WORK.
00104 *
00105       DO 20 J = 1, N
00106          DO 10 I = 1, N
00107             WORK( I, J ) = ZERO
00108    10    CONTINUE
00109    20 CONTINUE
00110       DO 30 I = 1, N
00111          IF( I.EQ.1 ) THEN
00112             WORK( I, I ) = DF( I )
00113             IF( N.GE.2 )
00114      $         WORK( I, I+1 ) = DUF( I )
00115             IF( N.GE.3 )
00116      $         WORK( I, I+2 ) = DU2( I )
00117          ELSE IF( I.EQ.N ) THEN
00118             WORK( I, I ) = DF( I )
00119          ELSE
00120             WORK( I, I ) = DF( I )
00121             WORK( I, I+1 ) = DUF( I )
00122             IF( I.LT.N-1 )
00123      $         WORK( I, I+2 ) = DU2( I )
00124          END IF
00125    30 CONTINUE
00126 *
00127 *     Multiply on the left by L.
00128 *
00129       LASTJ = N
00130       DO 40 I = N - 1, 1, -1
00131          LI = DLF( I )
00132          CALL SAXPY( LASTJ-I+1, LI, WORK( I, I ), LDWORK,
00133      $               WORK( I+1, I ), LDWORK )
00134          IP = IPIV( I )
00135          IF( IP.EQ.I ) THEN
00136             LASTJ = MIN( I+2, N )
00137          ELSE
00138             CALL SSWAP( LASTJ-I+1, WORK( I, I ), LDWORK, WORK( I+1, I ),
00139      $                  LDWORK )
00140          END IF
00141    40 CONTINUE
00142 *
00143 *     Subtract the matrix A.
00144 *
00145       WORK( 1, 1 ) = WORK( 1, 1 ) - D( 1 )
00146       IF( N.GT.1 ) THEN
00147          WORK( 1, 2 ) = WORK( 1, 2 ) - DU( 1 )
00148          WORK( N, N-1 ) = WORK( N, N-1 ) - DL( N-1 )
00149          WORK( N, N ) = WORK( N, N ) - D( N )
00150          DO 50 I = 2, N - 1
00151             WORK( I, I-1 ) = WORK( I, I-1 ) - DL( I-1 )
00152             WORK( I, I ) = WORK( I, I ) - D( I )
00153             WORK( I, I+1 ) = WORK( I, I+1 ) - DU( I )
00154    50    CONTINUE
00155       END IF
00156 *
00157 *     Compute the 1-norm of the tridiagonal matrix A.
00158 *
00159       ANORM = SLANGT( '1', N, DL, D, DU )
00160 *
00161 *     Compute the 1-norm of WORK, which is only guaranteed to be
00162 *     upper Hessenberg.
00163 *
00164       RESID = SLANHS( '1', N, WORK, LDWORK, RWORK )
00165 *
00166 *     Compute norm(L*U - A) / (norm(A) * EPS)
00167 *
00168       IF( ANORM.LE.ZERO ) THEN
00169          IF( RESID.NE.ZERO )
00170      $      RESID = ONE / EPS
00171       ELSE
00172          RESID = ( RESID / ANORM ) / EPS
00173       END IF
00174 *
00175       RETURN
00176 *
00177 *     End of SGTT01
00178 *
00179       END
 All Files Functions