LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
dtbt06.f
Go to the documentation of this file.
1 *> \brief \b DTBT06
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 DTBT06( RCOND, RCONDC, UPLO, DIAG, N, KD, AB, LDAB,
12 * WORK, RAT )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER DIAG, UPLO
16 * INTEGER KD, LDAB, N
17 * DOUBLE PRECISION RAT, RCOND, RCONDC
18 * ..
19 * .. Array Arguments ..
20 * DOUBLE PRECISION AB( LDAB, * ), WORK( * )
21 * ..
22 *
23 *
24 *> \par Purpose:
25 * =============
26 *>
27 *> \verbatim
28 *>
29 *> DTBT06 computes a test ratio comparing RCOND (the reciprocal
30 *> condition number of a triangular matrix A) and RCONDC, the estimate
31 *> computed by DTBCON. Information about the triangular matrix A is
32 *> used if one estimate is zero and the other is non-zero to decide if
33 *> underflow in the estimate is justified.
34 *> \endverbatim
35 *
36 * Arguments:
37 * ==========
38 *
39 *> \param[in] RCOND
40 *> \verbatim
41 *> RCOND is DOUBLE PRECISION
42 *> The estimate of the reciprocal condition number obtained by
43 *> forming the explicit inverse of the matrix A and computing
44 *> RCOND = 1/( norm(A) * norm(inv(A)) ).
45 *> \endverbatim
46 *>
47 *> \param[in] RCONDC
48 *> \verbatim
49 *> RCONDC is DOUBLE PRECISION
50 *> The estimate of the reciprocal condition number computed by
51 *> DTBCON.
52 *> \endverbatim
53 *>
54 *> \param[in] UPLO
55 *> \verbatim
56 *> UPLO is CHARACTER
57 *> Specifies whether the matrix A is upper or lower triangular.
58 *> = 'U': Upper triangular
59 *> = 'L': Lower triangular
60 *> \endverbatim
61 *>
62 *> \param[in] DIAG
63 *> \verbatim
64 *> DIAG is CHARACTER
65 *> Specifies whether or not the matrix A is unit triangular.
66 *> = 'N': Non-unit triangular
67 *> = 'U': Unit triangular
68 *> \endverbatim
69 *>
70 *> \param[in] N
71 *> \verbatim
72 *> N is INTEGER
73 *> The order of the matrix A. N >= 0.
74 *> \endverbatim
75 *>
76 *> \param[in] KD
77 *> \verbatim
78 *> KD is INTEGER
79 *> The number of superdiagonals or subdiagonals of the
80 *> triangular band matrix A. KD >= 0.
81 *> \endverbatim
82 *>
83 *> \param[in] AB
84 *> \verbatim
85 *> AB is DOUBLE PRECISION array, dimension (LDAB,N)
86 *> The upper or lower triangular band matrix A, stored in the
87 *> first kd+1 rows of the array. The j-th column of A is stored
88 *> in the j-th column of the array AB as follows:
89 *> if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
90 *> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+kd).
91 *> \endverbatim
92 *>
93 *> \param[in] LDAB
94 *> \verbatim
95 *> LDAB is INTEGER
96 *> The leading dimension of the array AB. LDAB >= KD+1.
97 *> \endverbatim
98 *>
99 *> \param[out] WORK
100 *> \verbatim
101 *> WORK is DOUBLE PRECISION array, dimension (N)
102 *> \endverbatim
103 *>
104 *> \param[out] RAT
105 *> \verbatim
106 *> RAT is DOUBLE PRECISION
107 *> The test ratio. If both RCOND and RCONDC are nonzero,
108 *> RAT = MAX( RCOND, RCONDC )/MIN( RCOND, RCONDC ) - 1.
109 *> If RAT = 0, the two estimates are exactly the same.
110 *> \endverbatim
111 *
112 * Authors:
113 * ========
114 *
115 *> \author Univ. of Tennessee
116 *> \author Univ. of California Berkeley
117 *> \author Univ. of Colorado Denver
118 *> \author NAG Ltd.
119 *
120 *> \date November 2011
121 *
122 *> \ingroup double_lin
123 *
124 * =====================================================================
125  SUBROUTINE dtbt06( RCOND, RCONDC, UPLO, DIAG, N, KD, AB, LDAB,
126  $ work, rat )
127 *
128 * -- LAPACK test routine (version 3.4.0) --
129 * -- LAPACK is a software package provided by Univ. of Tennessee, --
130 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
131 * November 2011
132 *
133 * .. Scalar Arguments ..
134  CHARACTER DIAG, UPLO
135  INTEGER KD, LDAB, N
136  DOUBLE PRECISION RAT, RCOND, RCONDC
137 * ..
138 * .. Array Arguments ..
139  DOUBLE PRECISION AB( ldab, * ), WORK( * )
140 * ..
141 *
142 * =====================================================================
143 *
144 * .. Parameters ..
145  DOUBLE PRECISION ZERO, ONE
146  parameter ( zero = 0.0d+0, one = 1.0d+0 )
147 * ..
148 * .. Local Scalars ..
149  DOUBLE PRECISION ANORM, BIGNUM, EPS, RMAX, RMIN, SMLNUM
150 * ..
151 * .. External Functions ..
152  DOUBLE PRECISION DLAMCH, DLANTB
153  EXTERNAL dlamch, dlantb
154 * ..
155 * .. Intrinsic Functions ..
156  INTRINSIC max, min
157 * ..
158 * .. External Subroutines ..
159  EXTERNAL dlabad
160 * ..
161 * .. Executable Statements ..
162 *
163  eps = dlamch( 'Epsilon' )
164  rmax = max( rcond, rcondc )
165  rmin = min( rcond, rcondc )
166 *
167 * Do the easy cases first.
168 *
169  IF( rmin.LT.zero ) THEN
170 *
171 * Invalid value for RCOND or RCONDC, return 1/EPS.
172 *
173  rat = one / eps
174 *
175  ELSE IF( rmin.GT.zero ) THEN
176 *
177 * Both estimates are positive, return RMAX/RMIN - 1.
178 *
179  rat = rmax / rmin - one
180 *
181  ELSE IF( rmax.EQ.zero ) THEN
182 *
183 * Both estimates zero.
184 *
185  rat = zero
186 *
187  ELSE
188 *
189 * One estimate is zero, the other is non-zero. If the matrix is
190 * ill-conditioned, return the nonzero estimate multiplied by
191 * 1/EPS; if the matrix is badly scaled, return the nonzero
192 * estimate multiplied by BIGNUM/TMAX, where TMAX is the maximum
193 * element in absolute value in A.
194 *
195  smlnum = dlamch( 'Safe minimum' )
196  bignum = one / smlnum
197  CALL dlabad( smlnum, bignum )
198  anorm = dlantb( 'M', uplo, diag, n, kd, ab, ldab, work )
199 *
200  rat = rmax*( min( bignum / max( one, anorm ), one / eps ) )
201  END IF
202 *
203  RETURN
204 *
205 * End of DTBT06
206 *
207  END
subroutine dlabad(SMALL, LARGE)
DLABAD
Definition: dlabad.f:76
subroutine dtbt06(RCOND, RCONDC, UPLO, DIAG, N, KD, AB, LDAB, WORK, RAT)
DTBT06
Definition: dtbt06.f:127