3d1f8690b63b4b41c1738f2745721856097a358f
[platform/upstream/lapack.git] / TESTING / LIN / dgbt02.f
1 *> \brief \b DGBT02
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 DGBT02( TRANS, M, N, KL, KU, NRHS, A, LDA, X, LDX, B,
12 *                          LDB, RESID )
13
14 *       .. Scalar Arguments ..
15 *       CHARACTER          TRANS
16 *       INTEGER            KL, KU, LDA, LDB, LDX, M, N, NRHS
17 *       DOUBLE PRECISION   RESID
18 *       ..
19 *       .. Array Arguments ..
20 *       DOUBLE PRECISION   A( LDA, * ), B( LDB, * ), X( LDX, * )
21 *       ..
22 *  
23 *
24 *> \par Purpose:
25 *  =============
26 *>
27 *> \verbatim
28 *>
29 *> DGBT02 computes the residual for a solution of a banded system of
30 *> equations  A*x = b  or  A'*x = b:
31 *>    RESID = norm( B - A*X ) / ( norm(A) * norm(X) * EPS).
32 *> where EPS is the machine precision.
33 *> \endverbatim
34 *
35 *  Arguments:
36 *  ==========
37 *
38 *> \param[in] TRANS
39 *> \verbatim
40 *>          TRANS is CHARACTER*1
41 *>          Specifies the form of the system of equations:
42 *>          = 'N':  A *x = b
43 *>          = 'T':  A'*x = b, where A' is the transpose of A
44 *>          = 'C':  A'*x = b, where A' is the transpose of A
45 *> \endverbatim
46 *>
47 *> \param[in] M
48 *> \verbatim
49 *>          M is INTEGER
50 *>          The number of rows of the matrix A.  M >= 0.
51 *> \endverbatim
52 *>
53 *> \param[in] N
54 *> \verbatim
55 *>          N is INTEGER
56 *>          The number of columns of the matrix A.  N >= 0.
57 *> \endverbatim
58 *>
59 *> \param[in] KL
60 *> \verbatim
61 *>          KL is INTEGER
62 *>          The number of subdiagonals within the band of A.  KL >= 0.
63 *> \endverbatim
64 *>
65 *> \param[in] KU
66 *> \verbatim
67 *>          KU is INTEGER
68 *>          The number of superdiagonals within the band of A.  KU >= 0.
69 *> \endverbatim
70 *>
71 *> \param[in] NRHS
72 *> \verbatim
73 *>          NRHS is INTEGER
74 *>          The number of columns of B.  NRHS >= 0.
75 *> \endverbatim
76 *>
77 *> \param[in] A
78 *> \verbatim
79 *>          A is DOUBLE PRECISION array, dimension (LDA,N)
80 *>          The original matrix A in band storage, stored in rows 1 to
81 *>          KL+KU+1.
82 *> \endverbatim
83 *>
84 *> \param[in] LDA
85 *> \verbatim
86 *>          LDA is INTEGER
87 *>          The leading dimension of the array A.  LDA >= max(1,KL+KU+1).
88 *> \endverbatim
89 *>
90 *> \param[in] X
91 *> \verbatim
92 *>          X is DOUBLE PRECISION array, dimension (LDX,NRHS)
93 *>          The computed solution vectors for the system of linear
94 *>          equations.
95 *> \endverbatim
96 *>
97 *> \param[in] LDX
98 *> \verbatim
99 *>          LDX is INTEGER
100 *>          The leading dimension of the array X.  If TRANS = 'N',
101 *>          LDX >= max(1,N); if TRANS = 'T' or 'C', LDX >= max(1,M).
102 *> \endverbatim
103 *>
104 *> \param[in,out] B
105 *> \verbatim
106 *>          B is DOUBLE PRECISION array, dimension (LDB,NRHS)
107 *>          On entry, the right hand side vectors for the system of
108 *>          linear equations.
109 *>          On exit, B is overwritten with the difference B - A*X.
110 *> \endverbatim
111 *>
112 *> \param[in] LDB
113 *> \verbatim
114 *>          LDB is INTEGER
115 *>          The leading dimension of the array B.  IF TRANS = 'N',
116 *>          LDB >= max(1,M); if TRANS = 'T' or 'C', LDB >= max(1,N).
117 *> \endverbatim
118 *>
119 *> \param[out] RESID
120 *> \verbatim
121 *>          RESID is DOUBLE PRECISION
122 *>          The maximum over the number of right hand sides of
123 *>          norm(B - A*X) / ( norm(A) * norm(X) * EPS ).
124 *> \endverbatim
125 *
126 *  Authors:
127 *  ========
128 *
129 *> \author Univ. of Tennessee 
130 *> \author Univ. of California Berkeley 
131 *> \author Univ. of Colorado Denver 
132 *> \author NAG Ltd. 
133 *
134 *> \date November 2011
135 *
136 *> \ingroup double_lin
137 *
138 *  =====================================================================
139       SUBROUTINE DGBT02( TRANS, M, N, KL, KU, NRHS, A, LDA, X, LDX, B,
140      $                   LDB, RESID )
141 *
142 *  -- LAPACK test routine (version 3.4.0) --
143 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
144 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
145 *     November 2011
146 *
147 *     .. Scalar Arguments ..
148       CHARACTER          TRANS
149       INTEGER            KL, KU, LDA, LDB, LDX, M, N, NRHS
150       DOUBLE PRECISION   RESID
151 *     ..
152 *     .. Array Arguments ..
153       DOUBLE PRECISION   A( LDA, * ), B( LDB, * ), X( LDX, * )
154 *     ..
155 *
156 *  =====================================================================
157 *
158 *     .. Parameters ..
159       DOUBLE PRECISION   ZERO, ONE
160       PARAMETER          ( ZERO = 0.0D+0, ONE = 1.0D+0 )
161 *     ..
162 *     .. Local Scalars ..
163       INTEGER            I1, I2, J, KD, N1
164       DOUBLE PRECISION   ANORM, BNORM, EPS, XNORM
165 *     ..
166 *     .. External Functions ..
167       LOGICAL            LSAME
168       DOUBLE PRECISION   DASUM, DLAMCH
169       EXTERNAL           LSAME, DASUM, DLAMCH
170 *     ..
171 *     .. External Subroutines ..
172       EXTERNAL           DGBMV
173 *     ..
174 *     .. Intrinsic Functions ..
175       INTRINSIC          MAX, MIN
176 *     ..
177 *     .. Executable Statements ..
178 *
179 *     Quick return if N = 0 pr NRHS = 0
180 *
181       IF( M.LE.0 .OR. N.LE.0 .OR. NRHS.LE.0 ) THEN
182          RESID = ZERO
183          RETURN
184       END IF
185 *
186 *     Exit with RESID = 1/EPS if ANORM = 0.
187 *
188       EPS = DLAMCH( 'Epsilon' )
189       KD = KU + 1
190       ANORM = ZERO
191       DO 10 J = 1, N
192          I1 = MAX( KD+1-J, 1 )
193          I2 = MIN( KD+M-J, KL+KD )
194          ANORM = MAX( ANORM, DASUM( I2-I1+1, A( I1, J ), 1 ) )
195    10 CONTINUE
196       IF( ANORM.LE.ZERO ) THEN
197          RESID = ONE / EPS
198          RETURN
199       END IF
200 *
201       IF( LSAME( TRANS, 'T' ) .OR. LSAME( TRANS, 'C' ) ) THEN
202          N1 = N
203       ELSE
204          N1 = M
205       END IF
206 *
207 *     Compute  B - A*X (or  B - A'*X )
208 *
209       DO 20 J = 1, NRHS
210          CALL DGBMV( TRANS, M, N, KL, KU, -ONE, A, LDA, X( 1, J ), 1,
211      $               ONE, B( 1, J ), 1 )
212    20 CONTINUE
213 *
214 *     Compute the maximum over the number of right hand sides of
215 *        norm(B - A*X) / ( norm(A) * norm(X) * EPS ).
216 *
217       RESID = ZERO
218       DO 30 J = 1, NRHS
219          BNORM = DASUM( N1, B( 1, J ), 1 )
220          XNORM = DASUM( N1, X( 1, J ), 1 )
221          IF( XNORM.LE.ZERO ) THEN
222             RESID = ONE / EPS
223          ELSE
224             RESID = MAX( RESID, ( ( BNORM / ANORM ) / XNORM ) / EPS )
225          END IF
226    30 CONTINUE
227 *
228       RETURN
229 *
230 *     End of DGBT02
231 *
232       END