LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cptt01.f
Go to the documentation of this file.
1 *> \brief \b CPTT01
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE CPTT01( N, D, E, DF, EF, WORK, RESID )
12 *
13 * .. Scalar Arguments ..
14 * INTEGER N
15 * REAL RESID
16 * ..
17 * .. Array Arguments ..
18 * REAL D( * ), DF( * )
19 * COMPLEX E( * ), EF( * ), WORK( * )
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> CPTT01 reconstructs a tridiagonal matrix A from its L*D*L'
29 *> factorization and computes the residual
30 *> norm(L*D*L' - A) / ( n * norm(A) * EPS ),
31 *> where EPS is the machine epsilon.
32 *> \endverbatim
33 *
34 * Arguments:
35 * ==========
36 *
37 *> \param[in] N
38 *> \verbatim
39 *> N is INTEGTER
40 *> The order of the matrix A.
41 *> \endverbatim
42 *>
43 *> \param[in] D
44 *> \verbatim
45 *> D is REAL array, dimension (N)
46 *> The n diagonal elements of the tridiagonal matrix A.
47 *> \endverbatim
48 *>
49 *> \param[in] E
50 *> \verbatim
51 *> E is COMPLEX array, dimension (N-1)
52 *> The (n-1) subdiagonal elements of the tridiagonal matrix A.
53 *> \endverbatim
54 *>
55 *> \param[in] DF
56 *> \verbatim
57 *> DF is REAL array, dimension (N)
58 *> The n diagonal elements of the factor L from the L*D*L'
59 *> factorization of A.
60 *> \endverbatim
61 *>
62 *> \param[in] EF
63 *> \verbatim
64 *> EF is COMPLEX array, dimension (N-1)
65 *> The (n-1) subdiagonal elements of the factor L from the
66 *> L*D*L' factorization of A.
67 *> \endverbatim
68 *>
69 *> \param[out] WORK
70 *> \verbatim
71 *> WORK is COMPLEX array, dimension (2*N)
72 *> \endverbatim
73 *>
74 *> \param[out] RESID
75 *> \verbatim
76 *> RESID is REAL
77 *> norm(L*D*L' - A) / (n * norm(A) * EPS)
78 *> \endverbatim
79 *
80 * Authors:
81 * ========
82 *
83 *> \author Univ. of Tennessee
84 *> \author Univ. of California Berkeley
85 *> \author Univ. of Colorado Denver
86 *> \author NAG Ltd.
87 *
88 *> \date November 2011
89 *
90 *> \ingroup complex_lin
91 *
92 * =====================================================================
93  SUBROUTINE cptt01( N, D, E, DF, EF, WORK, RESID )
94 *
95 * -- LAPACK test routine (version 3.4.0) --
96 * -- LAPACK is a software package provided by Univ. of Tennessee, --
97 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
98 * November 2011
99 *
100 * .. Scalar Arguments ..
101  INTEGER N
102  REAL RESID
103 * ..
104 * .. Array Arguments ..
105  REAL D( * ), DF( * )
106  COMPLEX E( * ), EF( * ), WORK( * )
107 * ..
108 *
109 * =====================================================================
110 *
111 * .. Parameters ..
112  REAL ONE, ZERO
113  parameter ( one = 1.0e+0, zero = 0.0e+0 )
114 * ..
115 * .. Local Scalars ..
116  INTEGER I
117  REAL ANORM, EPS
118  COMPLEX DE
119 * ..
120 * .. External Functions ..
121  REAL SLAMCH
122  EXTERNAL slamch
123 * ..
124 * .. Intrinsic Functions ..
125  INTRINSIC abs, conjg, max, real
126 * ..
127 * .. Executable Statements ..
128 *
129 * Quick return if possible
130 *
131  IF( n.LE.0 ) THEN
132  resid = zero
133  RETURN
134  END IF
135 *
136  eps = slamch( 'Epsilon' )
137 *
138 * Construct the difference L*D*L' - A.
139 *
140  work( 1 ) = df( 1 ) - d( 1 )
141  DO 10 i = 1, n - 1
142  de = df( i )*ef( i )
143  work( n+i ) = de - e( i )
144  work( 1+i ) = de*conjg( ef( i ) ) + df( i+1 ) - d( i+1 )
145  10 CONTINUE
146 *
147 * Compute the 1-norms of the tridiagonal matrices A and WORK.
148 *
149  IF( n.EQ.1 ) THEN
150  anorm = d( 1 )
151  resid = abs( work( 1 ) )
152  ELSE
153  anorm = max( d( 1 )+abs( e( 1 ) ), d( n )+abs( e( n-1 ) ) )
154  resid = max( abs( work( 1 ) )+abs( work( n+1 ) ),
155  $ abs( work( n ) )+abs( work( 2*n-1 ) ) )
156  DO 20 i = 2, n - 1
157  anorm = max( anorm, d( i )+abs( e( i ) )+abs( e( i-1 ) ) )
158  resid = max( resid, abs( work( i ) )+abs( work( n+i-1 ) )+
159  $ abs( work( n+i ) ) )
160  20 CONTINUE
161  END IF
162 *
163 * Compute norm(L*D*L' - A) / (n * norm(A) * EPS)
164 *
165  IF( anorm.LE.zero ) THEN
166  IF( resid.NE.zero )
167  $ resid = one / eps
168  ELSE
169  resid = ( ( resid / REAL( N ) ) / anorm ) / eps
170  END IF
171 *
172  RETURN
173 *
174 * End of CPTT01
175 *
176  END
subroutine cptt01(N, D, E, DF, EF, WORK, RESID)
CPTT01
Definition: cptt01.f:94