LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zqrt17.f
Go to the documentation of this file.
1 *> \brief \b ZQRT17
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * DOUBLE PRECISION FUNCTION ZQRT17( TRANS, IRESID, M, N, NRHS, A,
12 * LDA, X, LDX, B, LDB, C, WORK, LWORK )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER TRANS
16 * INTEGER IRESID, LDA, LDB, LDX, LWORK, M, N, NRHS
17 * ..
18 * .. Array Arguments ..
19 * COMPLEX*16 A( LDA, * ), B( LDB, * ), C( LDB, * ),
20 * $ WORK( LWORK ), X( LDX, * )
21 * ..
22 *
23 *
24 *> \par Purpose:
25 * =============
26 *>
27 *> \verbatim
28 *>
29 *> ZQRT17 computes the ratio
30 *>
31 *> || R'*op(A) ||/(||A||*alpha*max(M,N,NRHS)*eps)
32 *>
33 *> where R = op(A)*X - B, op(A) is A or A', and
34 *>
35 *> alpha = ||B|| if IRESID = 1 (zero-residual problem)
36 *> alpha = ||R|| if IRESID = 2 (otherwise).
37 *> \endverbatim
38 *
39 * Arguments:
40 * ==========
41 *
42 *> \param[in] TRANS
43 *> \verbatim
44 *> TRANS is CHARACTER*1
45 *> Specifies whether or not the transpose of A is used.
46 *> = 'N': No transpose, op(A) = A.
47 *> = 'C': Conjugate transpose, op(A) = A'.
48 *> \endverbatim
49 *>
50 *> \param[in] IRESID
51 *> \verbatim
52 *> IRESID is INTEGER
53 *> IRESID = 1 indicates zero-residual problem.
54 *> IRESID = 2 indicates non-zero residual.
55 *> \endverbatim
56 *>
57 *> \param[in] M
58 *> \verbatim
59 *> M is INTEGER
60 *> The number of rows of the matrix A.
61 *> If TRANS = 'N', the number of rows of the matrix B.
62 *> If TRANS = 'C', the number of rows of the matrix X.
63 *> \endverbatim
64 *>
65 *> \param[in] N
66 *> \verbatim
67 *> N is INTEGER
68 *> The number of columns of the matrix A.
69 *> If TRANS = 'N', the number of rows of the matrix X.
70 *> If TRANS = 'C', the number of rows of the matrix B.
71 *> \endverbatim
72 *>
73 *> \param[in] NRHS
74 *> \verbatim
75 *> NRHS is INTEGER
76 *> The number of columns of the matrices X and B.
77 *> \endverbatim
78 *>
79 *> \param[in] A
80 *> \verbatim
81 *> A is COMPLEX*16 array, dimension (LDA,N)
82 *> The m-by-n matrix A.
83 *> \endverbatim
84 *>
85 *> \param[in] LDA
86 *> \verbatim
87 *> LDA is INTEGER
88 *> The leading dimension of the array A. LDA >= M.
89 *> \endverbatim
90 *>
91 *> \param[in] X
92 *> \verbatim
93 *> X is COMPLEX*16 array, dimension (LDX,NRHS)
94 *> If TRANS = 'N', the n-by-nrhs matrix X.
95 *> If TRANS = 'C', the m-by-nrhs matrix X.
96 *> \endverbatim
97 *>
98 *> \param[in] LDX
99 *> \verbatim
100 *> LDX is INTEGER
101 *> The leading dimension of the array X.
102 *> If TRANS = 'N', LDX >= N.
103 *> If TRANS = 'C', LDX >= M.
104 *> \endverbatim
105 *>
106 *> \param[in] B
107 *> \verbatim
108 *> B is COMPLEX*16 array, dimension (LDB,NRHS)
109 *> If TRANS = 'N', the m-by-nrhs matrix B.
110 *> If TRANS = 'C', the n-by-nrhs matrix B.
111 *> \endverbatim
112 *>
113 *> \param[in] LDB
114 *> \verbatim
115 *> LDB is INTEGER
116 *> The leading dimension of the array B.
117 *> If TRANS = 'N', LDB >= M.
118 *> If TRANS = 'C', LDB >= N.
119 *> \endverbatim
120 *>
121 *> \param[out] C
122 *> \verbatim
123 *> C is COMPLEX*16 array, dimension (LDB,NRHS)
124 *> \endverbatim
125 *>
126 *> \param[out] WORK
127 *> \verbatim
128 *> WORK is COMPLEX*16 array, dimension (LWORK)
129 *> \endverbatim
130 *>
131 *> \param[in] LWORK
132 *> \verbatim
133 *> LWORK is INTEGER
134 *> The length of the array WORK. LWORK >= NRHS*(M+N).
135 *> \endverbatim
136 *
137 * Authors:
138 * ========
139 *
140 *> \author Univ. of Tennessee
141 *> \author Univ. of California Berkeley
142 *> \author Univ. of Colorado Denver
143 *> \author NAG Ltd.
144 *
145 *> \date November 2011
146 *
147 *> \ingroup complex16_lin
148 *
149 * =====================================================================
150  DOUBLE PRECISION FUNCTION zqrt17( TRANS, IRESID, M, N, NRHS, A,
151  $ lda, x, ldx, b, ldb, c, work, lwork )
152 *
153 * -- LAPACK test routine (version 3.4.0) --
154 * -- LAPACK is a software package provided by Univ. of Tennessee, --
155 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
156 * November 2011
157 *
158 * .. Scalar Arguments ..
159  CHARACTER trans
160  INTEGER iresid, lda, ldb, ldx, lwork, m, n, nrhs
161 * ..
162 * .. Array Arguments ..
163  COMPLEX*16 a( lda, * ), b( ldb, * ), c( ldb, * ),
164  $ work( lwork ), x( ldx, * )
165 * ..
166 *
167 * =====================================================================
168 *
169 * .. Parameters ..
170  DOUBLE PRECISION zero, one
171  parameter( zero = 0.0d0, one = 1.0d0 )
172 * ..
173 * .. Local Scalars ..
174  INTEGER info, iscl, ncols, nrows
175  DOUBLE PRECISION bignum, err, norma, normb, normrs, normx,
176  $ smlnum
177 * ..
178 * .. Local Arrays ..
179  DOUBLE PRECISION rwork( 1 )
180 * ..
181 * .. External Functions ..
182  LOGICAL lsame
183  DOUBLE PRECISION dlamch, zlange
184  EXTERNAL lsame, dlamch, zlange
185 * ..
186 * .. External Subroutines ..
187  EXTERNAL xerbla, zgemm, zlacpy, zlascl
188 * ..
189 * .. Intrinsic Functions ..
190  INTRINSIC dble, dcmplx, max
191 * ..
192 * .. Executable Statements ..
193 *
194  zqrt17 = zero
195 *
196  IF( lsame( trans, 'N' ) ) THEN
197  nrows = m
198  ncols = n
199  ELSE IF( lsame( trans, 'C' ) ) THEN
200  nrows = n
201  ncols = m
202  ELSE
203  CALL xerbla( 'ZQRT17', 1 )
204  return
205  END IF
206 *
207  IF( lwork.LT.ncols*nrhs ) THEN
208  CALL xerbla( 'ZQRT17', 13 )
209  return
210  END IF
211 *
212  IF( m.LE.0 .OR. n.LE.0 .OR. nrhs.LE.0 )
213  $ return
214 *
215  norma = zlange( 'One-norm', m, n, a, lda, rwork )
216  smlnum = dlamch( 'Safe minimum' ) / dlamch( 'Precision' )
217  bignum = one / smlnum
218  iscl = 0
219 *
220 * compute residual and scale it
221 *
222  CALL zlacpy( 'All', nrows, nrhs, b, ldb, c, ldb )
223  CALL zgemm( trans, 'No transpose', nrows, nrhs, ncols,
224  $ dcmplx( -one ), a, lda, x, ldx, dcmplx( one ), c,
225  $ ldb )
226  normrs = zlange( 'Max', nrows, nrhs, c, ldb, rwork )
227  IF( normrs.GT.smlnum ) THEN
228  iscl = 1
229  CALL zlascl( 'General', 0, 0, normrs, one, nrows, nrhs, c, ldb,
230  $ info )
231  END IF
232 *
233 * compute R'*A
234 *
235  CALL zgemm( 'Conjugate transpose', trans, nrhs, ncols, nrows,
236  $ dcmplx( one ), c, ldb, a, lda, dcmplx( zero ), work,
237  $ nrhs )
238 *
239 * compute and properly scale error
240 *
241  err = zlange( 'One-norm', nrhs, ncols, work, nrhs, rwork )
242  IF( norma.NE.zero )
243  $ err = err / norma
244 *
245  IF( iscl.EQ.1 )
246  $ err = err*normrs
247 *
248  IF( iresid.EQ.1 ) THEN
249  normb = zlange( 'One-norm', nrows, nrhs, b, ldb, rwork )
250  IF( normb.NE.zero )
251  $ err = err / normb
252  ELSE
253  normx = zlange( 'One-norm', ncols, nrhs, x, ldx, rwork )
254  IF( normx.NE.zero )
255  $ err = err / normx
256  END IF
257 *
258  zqrt17 = err / ( dlamch( 'Epsilon' )*dble( max( m, n, nrhs ) ) )
259  return
260 *
261 * End of ZQRT17
262 *
263  END