1 SUBROUTINE ZTRT06( RCOND, RCONDC, UPLO, DIAG, N, A, LDA, RWORK,
2 $ RAT )
3 *
4 * -- LAPACK test routine (version 3.1) --
5 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
6 * November 2006
7 *
8 * .. Scalar Arguments ..
9 CHARACTER DIAG, UPLO
10 INTEGER LDA, N
11 DOUBLE PRECISION RAT, RCOND, RCONDC
12 * ..
13 * .. Array Arguments ..
14 DOUBLE PRECISION RWORK( * )
15 COMPLEX*16 A( LDA, * )
16 * ..
17 *
18 * Purpose
19 * =======
20 *
21 * ZTRT06 computes a test ratio comparing RCOND (the reciprocal
22 * condition number of a triangular matrix A) and RCONDC, the estimate
23 * computed by ZTRCON. Information about the triangular matrix A is
24 * used if one estimate is zero and the other is non-zero to decide if
25 * underflow in the estimate is justified.
26 *
27 * Arguments
28 * =========
29 *
30 * RCOND (input) DOUBLE PRECISION
31 * The estimate of the reciprocal condition number obtained by
32 * forming the explicit inverse of the matrix A and computing
33 * RCOND = 1/( norm(A) * norm(inv(A)) ).
34 *
35 * RCONDC (input) DOUBLE PRECISION
36 * The estimate of the reciprocal condition number computed by
37 * ZTRCON.
38 *
39 * UPLO (input) CHARACTER
40 * Specifies whether the matrix A is upper or lower triangular.
41 * = 'U': Upper triangular
42 * = 'L': Lower triangular
43 *
44 * DIAG (input) CHARACTER
45 * Specifies whether or not the matrix A is unit triangular.
46 * = 'N': Non-unit triangular
47 * = 'U': Unit triangular
48 *
49 * N (input) INTEGER
50 * The order of the matrix A. N >= 0.
51 *
52 * A (input) COMPLEX*16 array, dimension (LDA,N)
53 * The triangular matrix A. If UPLO = 'U', the leading n by n
54 * upper triangular part of the array A contains the upper
55 * triangular matrix, and the strictly lower triangular part of
56 * A is not referenced. If UPLO = 'L', the leading n by n lower
57 * triangular part of the array A contains the lower triangular
58 * matrix, and the strictly upper triangular part of A is not
59 * referenced. If DIAG = 'U', the diagonal elements of A are
60 * also not referenced and are assumed to be 1.
61 *
62 * LDA (input) INTEGER
63 * The leading dimension of the array A. LDA >= max(1,N).
64 *
65 * RWORK (workspace) DOUBLE PRECISION array, dimension (N)
66 *
67 * RAT (output) DOUBLE PRECISION
68 * The test ratio. If both RCOND and RCONDC are nonzero,
69 * RAT = MAX( RCOND, RCONDC )/MIN( RCOND, RCONDC ) - 1.
70 * If RAT = 0, the two estimates are exactly the same.
71 *
72 * =====================================================================
73 *
74 * .. Parameters ..
75 DOUBLE PRECISION ZERO, ONE
76 PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
77 * ..
78 * .. Local Scalars ..
79 DOUBLE PRECISION ANORM, BIGNUM, EPS, RMAX, RMIN
80 * ..
81 * .. External Functions ..
82 DOUBLE PRECISION DLAMCH, ZLANTR
83 EXTERNAL DLAMCH, ZLANTR
84 * ..
85 * .. Intrinsic Functions ..
86 INTRINSIC MAX, MIN
87 * ..
88 * .. Executable Statements ..
89 *
90 EPS = DLAMCH( 'Epsilon' )
91 RMAX = MAX( RCOND, RCONDC )
92 RMIN = MIN( RCOND, RCONDC )
93 *
94 * Do the easy cases first.
95 *
96 IF( RMIN.LT.ZERO ) THEN
97 *
98 * Invalid value for RCOND or RCONDC, return 1/EPS.
99 *
100 RAT = ONE / EPS
101 *
102 ELSE IF( RMIN.GT.ZERO ) THEN
103 *
104 * Both estimates are positive, return RMAX/RMIN - 1.
105 *
106 RAT = RMAX / RMIN - ONE
107 *
108 ELSE IF( RMAX.EQ.ZERO ) THEN
109 *
110 * Both estimates zero.
111 *
112 RAT = ZERO
113 *
114 ELSE
115 *
116 * One estimate is zero, the other is non-zero. If the matrix is
117 * ill-conditioned, return the nonzero estimate multiplied by
118 * 1/EPS; if the matrix is badly scaled, return the nonzero
119 * estimate multiplied by BIGNUM/TMAX, where TMAX is the maximum
120 * element in absolute value in A.
121 *
122 BIGNUM = ONE / DLAMCH( 'Safe minimum' )
123 ANORM = ZLANTR( 'M', UPLO, DIAG, N, N, A, LDA, RWORK )
124 *
125 RAT = RMAX*( MIN( BIGNUM / MAX( ONE, ANORM ), ONE / EPS ) )
126 END IF
127 *
128 RETURN
129 *
130 * End of ZTRT06
131 *
132 END
2 $ RAT )
3 *
4 * -- LAPACK test routine (version 3.1) --
5 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
6 * November 2006
7 *
8 * .. Scalar Arguments ..
9 CHARACTER DIAG, UPLO
10 INTEGER LDA, N
11 DOUBLE PRECISION RAT, RCOND, RCONDC
12 * ..
13 * .. Array Arguments ..
14 DOUBLE PRECISION RWORK( * )
15 COMPLEX*16 A( LDA, * )
16 * ..
17 *
18 * Purpose
19 * =======
20 *
21 * ZTRT06 computes a test ratio comparing RCOND (the reciprocal
22 * condition number of a triangular matrix A) and RCONDC, the estimate
23 * computed by ZTRCON. Information about the triangular matrix A is
24 * used if one estimate is zero and the other is non-zero to decide if
25 * underflow in the estimate is justified.
26 *
27 * Arguments
28 * =========
29 *
30 * RCOND (input) DOUBLE PRECISION
31 * The estimate of the reciprocal condition number obtained by
32 * forming the explicit inverse of the matrix A and computing
33 * RCOND = 1/( norm(A) * norm(inv(A)) ).
34 *
35 * RCONDC (input) DOUBLE PRECISION
36 * The estimate of the reciprocal condition number computed by
37 * ZTRCON.
38 *
39 * UPLO (input) CHARACTER
40 * Specifies whether the matrix A is upper or lower triangular.
41 * = 'U': Upper triangular
42 * = 'L': Lower triangular
43 *
44 * DIAG (input) CHARACTER
45 * Specifies whether or not the matrix A is unit triangular.
46 * = 'N': Non-unit triangular
47 * = 'U': Unit triangular
48 *
49 * N (input) INTEGER
50 * The order of the matrix A. N >= 0.
51 *
52 * A (input) COMPLEX*16 array, dimension (LDA,N)
53 * The triangular matrix A. If UPLO = 'U', the leading n by n
54 * upper triangular part of the array A contains the upper
55 * triangular matrix, and the strictly lower triangular part of
56 * A is not referenced. If UPLO = 'L', the leading n by n lower
57 * triangular part of the array A contains the lower triangular
58 * matrix, and the strictly upper triangular part of A is not
59 * referenced. If DIAG = 'U', the diagonal elements of A are
60 * also not referenced and are assumed to be 1.
61 *
62 * LDA (input) INTEGER
63 * The leading dimension of the array A. LDA >= max(1,N).
64 *
65 * RWORK (workspace) DOUBLE PRECISION array, dimension (N)
66 *
67 * RAT (output) DOUBLE PRECISION
68 * The test ratio. If both RCOND and RCONDC are nonzero,
69 * RAT = MAX( RCOND, RCONDC )/MIN( RCOND, RCONDC ) - 1.
70 * If RAT = 0, the two estimates are exactly the same.
71 *
72 * =====================================================================
73 *
74 * .. Parameters ..
75 DOUBLE PRECISION ZERO, ONE
76 PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
77 * ..
78 * .. Local Scalars ..
79 DOUBLE PRECISION ANORM, BIGNUM, EPS, RMAX, RMIN
80 * ..
81 * .. External Functions ..
82 DOUBLE PRECISION DLAMCH, ZLANTR
83 EXTERNAL DLAMCH, ZLANTR
84 * ..
85 * .. Intrinsic Functions ..
86 INTRINSIC MAX, MIN
87 * ..
88 * .. Executable Statements ..
89 *
90 EPS = DLAMCH( 'Epsilon' )
91 RMAX = MAX( RCOND, RCONDC )
92 RMIN = MIN( RCOND, RCONDC )
93 *
94 * Do the easy cases first.
95 *
96 IF( RMIN.LT.ZERO ) THEN
97 *
98 * Invalid value for RCOND or RCONDC, return 1/EPS.
99 *
100 RAT = ONE / EPS
101 *
102 ELSE IF( RMIN.GT.ZERO ) THEN
103 *
104 * Both estimates are positive, return RMAX/RMIN - 1.
105 *
106 RAT = RMAX / RMIN - ONE
107 *
108 ELSE IF( RMAX.EQ.ZERO ) THEN
109 *
110 * Both estimates zero.
111 *
112 RAT = ZERO
113 *
114 ELSE
115 *
116 * One estimate is zero, the other is non-zero. If the matrix is
117 * ill-conditioned, return the nonzero estimate multiplied by
118 * 1/EPS; if the matrix is badly scaled, return the nonzero
119 * estimate multiplied by BIGNUM/TMAX, where TMAX is the maximum
120 * element in absolute value in A.
121 *
122 BIGNUM = ONE / DLAMCH( 'Safe minimum' )
123 ANORM = ZLANTR( 'M', UPLO, DIAG, N, N, A, LDA, RWORK )
124 *
125 RAT = RMAX*( MIN( BIGNUM / MAX( ONE, ANORM ), ONE / EPS ) )
126 END IF
127 *
128 RETURN
129 *
130 * End of ZTRT06
131 *
132 END