1 SUBROUTINE CGTT02( TRANS, N, NRHS, DL, D, DU, X, LDX, B, LDB,
2 $ RWORK, RESID )
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 TRANS
10 INTEGER LDB, LDX, N, NRHS
11 REAL RESID
12 * ..
13 * .. Array Arguments ..
14 REAL RWORK( * )
15 COMPLEX B( LDB, * ), D( * ), DL( * ), DU( * ),
16 $ X( LDX, * )
17 * ..
18 *
19 * Purpose
20 * =======
21 *
22 * CGTT02 computes the residual for the solution to a tridiagonal
23 * system of equations:
24 * RESID = norm(B - op(A)*X) / (norm(A) * norm(X) * EPS),
25 * where EPS is the machine epsilon.
26 *
27 * Arguments
28 * =========
29 *
30 * TRANS (input) CHARACTER
31 * Specifies the form of the residual.
32 * = 'N': B - A * X (No transpose)
33 * = 'T': B - A**T * X (Transpose)
34 * = 'C': B - A**H * X (Conjugate transpose)
35 *
36 * N (input) INTEGTER
37 * The order of the matrix A. N >= 0.
38 *
39 * NRHS (input) INTEGER
40 * The number of right hand sides, i.e., the number of columns
41 * of the matrices B and X. NRHS >= 0.
42 *
43 * DL (input) COMPLEX array, dimension (N-1)
44 * The (n-1) sub-diagonal elements of A.
45 *
46 * D (input) COMPLEX array, dimension (N)
47 * The diagonal elements of A.
48 *
49 * DU (input) COMPLEX array, dimension (N-1)
50 * The (n-1) super-diagonal elements of A.
51 *
52 * X (input) COMPLEX array, dimension (LDX,NRHS)
53 * The computed solution vectors X.
54 *
55 * LDX (input) INTEGER
56 * The leading dimension of the array X. LDX >= max(1,N).
57 *
58 * B (input/output) COMPLEX array, dimension (LDB,NRHS)
59 * On entry, the right hand side vectors for the system of
60 * linear equations.
61 * On exit, B is overwritten with the difference B - op(A)*X.
62 *
63 * LDB (input) INTEGER
64 * The leading dimension of the array B. LDB >= max(1,N).
65 *
66 * RWORK (workspace) REAL array, dimension (N)
67 *
68 * RESID (output) REAL
69 * norm(B - op(A)*X) / (norm(A) * norm(X) * EPS)
70 *
71 * =====================================================================
72 *
73 * .. Parameters ..
74 REAL ONE, ZERO
75 PARAMETER ( ONE = 1.0E+0, ZERO = 0.0E+0 )
76 * ..
77 * .. Local Scalars ..
78 INTEGER J
79 REAL ANORM, BNORM, EPS, XNORM
80 * ..
81 * .. External Functions ..
82 LOGICAL LSAME
83 REAL CLANGT, SCASUM, SLAMCH
84 EXTERNAL LSAME, CLANGT, SCASUM, SLAMCH
85 * ..
86 * .. External Subroutines ..
87 EXTERNAL CLAGTM
88 * ..
89 * .. Intrinsic Functions ..
90 INTRINSIC MAX
91 * ..
92 * .. Executable Statements ..
93 *
94 * Quick exit if N = 0 or NRHS = 0
95 *
96 RESID = ZERO
97 IF( N.LE.0 .OR. NRHS.EQ.0 )
98 $ RETURN
99 *
100 * Compute the maximum over the number of right hand sides of
101 * norm(B - op(A)*X) / ( norm(A) * norm(X) * EPS ).
102 *
103 IF( LSAME( TRANS, 'N' ) ) THEN
104 ANORM = CLANGT( '1', N, DL, D, DU )
105 ELSE
106 ANORM = CLANGT( 'I', N, DL, D, DU )
107 END IF
108 *
109 * Exit with RESID = 1/EPS if ANORM = 0.
110 *
111 EPS = SLAMCH( 'Epsilon' )
112 IF( ANORM.LE.ZERO ) THEN
113 RESID = ONE / EPS
114 RETURN
115 END IF
116 *
117 * Compute B - op(A)*X.
118 *
119 CALL CLAGTM( TRANS, N, NRHS, -ONE, DL, D, DU, X, LDX, ONE, B,
120 $ LDB )
121 *
122 DO 10 J = 1, NRHS
123 BNORM = SCASUM( N, B( 1, J ), 1 )
124 XNORM = SCASUM( N, X( 1, J ), 1 )
125 IF( XNORM.LE.ZERO ) THEN
126 RESID = ONE / EPS
127 ELSE
128 RESID = MAX( RESID, ( ( BNORM / ANORM ) / XNORM ) / EPS )
129 END IF
130 10 CONTINUE
131 *
132 RETURN
133 *
134 * End of CGTT02
135 *
136 END
2 $ RWORK, RESID )
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 TRANS
10 INTEGER LDB, LDX, N, NRHS
11 REAL RESID
12 * ..
13 * .. Array Arguments ..
14 REAL RWORK( * )
15 COMPLEX B( LDB, * ), D( * ), DL( * ), DU( * ),
16 $ X( LDX, * )
17 * ..
18 *
19 * Purpose
20 * =======
21 *
22 * CGTT02 computes the residual for the solution to a tridiagonal
23 * system of equations:
24 * RESID = norm(B - op(A)*X) / (norm(A) * norm(X) * EPS),
25 * where EPS is the machine epsilon.
26 *
27 * Arguments
28 * =========
29 *
30 * TRANS (input) CHARACTER
31 * Specifies the form of the residual.
32 * = 'N': B - A * X (No transpose)
33 * = 'T': B - A**T * X (Transpose)
34 * = 'C': B - A**H * X (Conjugate transpose)
35 *
36 * N (input) INTEGTER
37 * The order of the matrix A. N >= 0.
38 *
39 * NRHS (input) INTEGER
40 * The number of right hand sides, i.e., the number of columns
41 * of the matrices B and X. NRHS >= 0.
42 *
43 * DL (input) COMPLEX array, dimension (N-1)
44 * The (n-1) sub-diagonal elements of A.
45 *
46 * D (input) COMPLEX array, dimension (N)
47 * The diagonal elements of A.
48 *
49 * DU (input) COMPLEX array, dimension (N-1)
50 * The (n-1) super-diagonal elements of A.
51 *
52 * X (input) COMPLEX array, dimension (LDX,NRHS)
53 * The computed solution vectors X.
54 *
55 * LDX (input) INTEGER
56 * The leading dimension of the array X. LDX >= max(1,N).
57 *
58 * B (input/output) COMPLEX array, dimension (LDB,NRHS)
59 * On entry, the right hand side vectors for the system of
60 * linear equations.
61 * On exit, B is overwritten with the difference B - op(A)*X.
62 *
63 * LDB (input) INTEGER
64 * The leading dimension of the array B. LDB >= max(1,N).
65 *
66 * RWORK (workspace) REAL array, dimension (N)
67 *
68 * RESID (output) REAL
69 * norm(B - op(A)*X) / (norm(A) * norm(X) * EPS)
70 *
71 * =====================================================================
72 *
73 * .. Parameters ..
74 REAL ONE, ZERO
75 PARAMETER ( ONE = 1.0E+0, ZERO = 0.0E+0 )
76 * ..
77 * .. Local Scalars ..
78 INTEGER J
79 REAL ANORM, BNORM, EPS, XNORM
80 * ..
81 * .. External Functions ..
82 LOGICAL LSAME
83 REAL CLANGT, SCASUM, SLAMCH
84 EXTERNAL LSAME, CLANGT, SCASUM, SLAMCH
85 * ..
86 * .. External Subroutines ..
87 EXTERNAL CLAGTM
88 * ..
89 * .. Intrinsic Functions ..
90 INTRINSIC MAX
91 * ..
92 * .. Executable Statements ..
93 *
94 * Quick exit if N = 0 or NRHS = 0
95 *
96 RESID = ZERO
97 IF( N.LE.0 .OR. NRHS.EQ.0 )
98 $ RETURN
99 *
100 * Compute the maximum over the number of right hand sides of
101 * norm(B - op(A)*X) / ( norm(A) * norm(X) * EPS ).
102 *
103 IF( LSAME( TRANS, 'N' ) ) THEN
104 ANORM = CLANGT( '1', N, DL, D, DU )
105 ELSE
106 ANORM = CLANGT( 'I', N, DL, D, DU )
107 END IF
108 *
109 * Exit with RESID = 1/EPS if ANORM = 0.
110 *
111 EPS = SLAMCH( 'Epsilon' )
112 IF( ANORM.LE.ZERO ) THEN
113 RESID = ONE / EPS
114 RETURN
115 END IF
116 *
117 * Compute B - op(A)*X.
118 *
119 CALL CLAGTM( TRANS, N, NRHS, -ONE, DL, D, DU, X, LDX, ONE, B,
120 $ LDB )
121 *
122 DO 10 J = 1, NRHS
123 BNORM = SCASUM( N, B( 1, J ), 1 )
124 XNORM = SCASUM( N, X( 1, J ), 1 )
125 IF( XNORM.LE.ZERO ) THEN
126 RESID = ONE / EPS
127 ELSE
128 RESID = MAX( RESID, ( ( BNORM / ANORM ) / XNORM ) / EPS )
129 END IF
130 10 CONTINUE
131 *
132 RETURN
133 *
134 * End of CGTT02
135 *
136 END