LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine cgtt01 ( integer  N,
complex, dimension( * )  DL,
complex, dimension( * )  D,
complex, dimension( * )  DU,
complex, dimension( * )  DLF,
complex, dimension( * )  DF,
complex, dimension( * )  DUF,
complex, dimension( * )  DU2,
integer, dimension( * )  IPIV,
complex, dimension( ldwork, * )  WORK,
integer  LDWORK,
real, dimension( * )  RWORK,
real  RESID 
)

CGTT01

Purpose:
 CGTT01 reconstructs a tridiagonal matrix A from its LU factorization
 and computes the residual
    norm(L*U - A) / ( norm(A) * EPS ),
 where EPS is the machine epsilon.
Parameters
[in]N
          N is INTEGTER
          The order of the matrix A.  N >= 0.
[in]DL
          DL is COMPLEX array, dimension (N-1)
          The (n-1) sub-diagonal elements of A.
[in]D
          D is COMPLEX array, dimension (N)
          The diagonal elements of A.
[in]DU
          DU is COMPLEX array, dimension (N-1)
          The (n-1) super-diagonal elements of A.
[in]DLF
          DLF is COMPLEX array, dimension (N-1)
          The (n-1) multipliers that define the matrix L from the
          LU factorization of A.
[in]DF
          DF is COMPLEX array, dimension (N)
          The n diagonal elements of the upper triangular matrix U from
          the LU factorization of A.
[in]DUF
          DUF is COMPLEX array, dimension (N-1)
          The (n-1) elements of the first super-diagonal of U.
[in]DU2
          DU2 is COMPLEX array, dimension (N-2)
          The (n-2) elements of the second super-diagonal of U.
[in]IPIV
          IPIV is INTEGER array, dimension (N)
          The pivot indices; for 1 <= i <= n, row i of the matrix was
          interchanged with row IPIV(i).  IPIV(i) will always be either
          i or i+1; IPIV(i) = i indicates a row interchange was not
          required.
[out]WORK
          WORK is COMPLEX array, dimension (LDWORK,N)
[in]LDWORK
          LDWORK is INTEGER
          The leading dimension of the array WORK.  LDWORK >= max(1,N).
[out]RWORK
          RWORK is REAL array, dimension (N)
[out]RESID
          RESID is REAL
          The scaled residual:  norm(L*U - A) / (norm(A) * EPS)
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 136 of file cgtt01.f.

136 *
137 * -- LAPACK test routine (version 3.4.0) --
138 * -- LAPACK is a software package provided by Univ. of Tennessee, --
139 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
140 * November 2011
141 *
142 * .. Scalar Arguments ..
143  INTEGER ldwork, n
144  REAL resid
145 * ..
146 * .. Array Arguments ..
147  INTEGER ipiv( * )
148  REAL rwork( * )
149  COMPLEX d( * ), df( * ), dl( * ), dlf( * ), du( * ),
150  $ du2( * ), duf( * ), work( ldwork, * )
151 * ..
152 *
153 * =====================================================================
154 *
155 * .. Parameters ..
156  REAL one, zero
157  parameter ( one = 1.0e+0, zero = 0.0e+0 )
158 * ..
159 * .. Local Scalars ..
160  INTEGER i, ip, j, lastj
161  REAL anorm, eps
162  COMPLEX li
163 * ..
164 * .. External Functions ..
165  REAL clangt, clanhs, slamch
166  EXTERNAL clangt, clanhs, slamch
167 * ..
168 * .. Intrinsic Functions ..
169  INTRINSIC min
170 * ..
171 * .. External Subroutines ..
172  EXTERNAL caxpy, cswap
173 * ..
174 * .. Executable Statements ..
175 *
176 * Quick return if possible
177 *
178  IF( n.LE.0 ) THEN
179  resid = zero
180  RETURN
181  END IF
182 *
183  eps = slamch( 'Epsilon' )
184 *
185 * Copy the matrix U to WORK.
186 *
187  DO 20 j = 1, n
188  DO 10 i = 1, n
189  work( i, j ) = zero
190  10 CONTINUE
191  20 CONTINUE
192  DO 30 i = 1, n
193  IF( i.EQ.1 ) THEN
194  work( i, i ) = df( i )
195  IF( n.GE.2 )
196  $ work( i, i+1 ) = duf( i )
197  IF( n.GE.3 )
198  $ work( i, i+2 ) = du2( i )
199  ELSE IF( i.EQ.n ) THEN
200  work( i, i ) = df( i )
201  ELSE
202  work( i, i ) = df( i )
203  work( i, i+1 ) = duf( i )
204  IF( i.LT.n-1 )
205  $ work( i, i+2 ) = du2( i )
206  END IF
207  30 CONTINUE
208 *
209 * Multiply on the left by L.
210 *
211  lastj = n
212  DO 40 i = n - 1, 1, -1
213  li = dlf( i )
214  CALL caxpy( lastj-i+1, li, work( i, i ), ldwork,
215  $ work( i+1, i ), ldwork )
216  ip = ipiv( i )
217  IF( ip.EQ.i ) THEN
218  lastj = min( i+2, n )
219  ELSE
220  CALL cswap( lastj-i+1, work( i, i ), ldwork, work( i+1, i ),
221  $ ldwork )
222  END IF
223  40 CONTINUE
224 *
225 * Subtract the matrix A.
226 *
227  work( 1, 1 ) = work( 1, 1 ) - d( 1 )
228  IF( n.GT.1 ) THEN
229  work( 1, 2 ) = work( 1, 2 ) - du( 1 )
230  work( n, n-1 ) = work( n, n-1 ) - dl( n-1 )
231  work( n, n ) = work( n, n ) - d( n )
232  DO 50 i = 2, n - 1
233  work( i, i-1 ) = work( i, i-1 ) - dl( i-1 )
234  work( i, i ) = work( i, i ) - d( i )
235  work( i, i+1 ) = work( i, i+1 ) - du( i )
236  50 CONTINUE
237  END IF
238 *
239 * Compute the 1-norm of the tridiagonal matrix A.
240 *
241  anorm = clangt( '1', n, dl, d, du )
242 *
243 * Compute the 1-norm of WORK, which is only guaranteed to be
244 * upper Hessenberg.
245 *
246  resid = clanhs( '1', n, work, ldwork, rwork )
247 *
248 * Compute norm(L*U - A) / (norm(A) * EPS)
249 *
250  IF( anorm.LE.zero ) THEN
251  IF( resid.NE.zero )
252  $ resid = one / eps
253  ELSE
254  resid = ( resid / anorm ) / eps
255  END IF
256 *
257  RETURN
258 *
259 * End of CGTT01
260 *
real function clanhs(NORM, N, A, LDA, WORK)
CLANHS returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition: clanhs.f:111
real function clangt(NORM, N, DL, D, DU)
CLANGT returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition: clangt.f:108
subroutine cswap(N, CX, INCX, CY, INCY)
CSWAP
Definition: cswap.f:52
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69
subroutine caxpy(N, CA, CX, INCX, CY, INCY)
CAXPY
Definition: caxpy.f:53

Here is the call graph for this function:

Here is the caller graph for this function: