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