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*>    norm(R**H * op(A)) / ( norm(A) * alpha * max(M,N,NRHS) * EPS ),
32*>
33*> where R = B - op(A)*X, op(A) is A or A**H, depending on TRANS, EPS
34*> is the machine epsilon, and
35*>
36*>    alpha = norm(B) if IRESID = 1 (zero-residual problem)
37*>    alpha = norm(R) if IRESID = 2 (otherwise).
38*>
39*> The norm used is the 1-norm.
40*> \endverbatim
41*
42*  Arguments:
43*  ==========
44*
45*> \param[in] TRANS
46*> \verbatim
47*>          TRANS is CHARACTER*1
48*>          Specifies whether or not the transpose of A is used.
49*>          = 'N':  No transpose, op(A) = A.
50*>          = 'C':  Conjugate transpose, op(A) = A**H.
51*> \endverbatim
52*>
53*> \param[in] IRESID
54*> \verbatim
55*>          IRESID is INTEGER
56*>          IRESID = 1 indicates zero-residual problem.
57*>          IRESID = 2 indicates non-zero residual.
58*> \endverbatim
59*>
60*> \param[in] M
61*> \verbatim
62*>          M is INTEGER
63*>          The number of rows of the matrix A.
64*>          If TRANS = 'N', the number of rows of the matrix B.
65*>          If TRANS = 'C', the number of rows of the matrix X.
66*> \endverbatim
67*>
68*> \param[in] N
69*> \verbatim
70*>          N is INTEGER
71*>          The number of columns of the matrix  A.
72*>          If TRANS = 'N', the number of rows of the matrix X.
73*>          If TRANS = 'C', the number of rows of the matrix B.
74*> \endverbatim
75*>
76*> \param[in] NRHS
77*> \verbatim
78*>          NRHS is INTEGER
79*>          The number of columns of the matrices X and B.
80*> \endverbatim
81*>
82*> \param[in] A
83*> \verbatim
84*>          A is COMPLEX*16 array, dimension (LDA,N)
85*>          The m-by-n matrix A.
86*> \endverbatim
87*>
88*> \param[in] LDA
89*> \verbatim
90*>          LDA is INTEGER
91*>          The leading dimension of the array A. LDA >= M.
92*> \endverbatim
93*>
94*> \param[in] X
95*> \verbatim
96*>          X is COMPLEX*16 array, dimension (LDX,NRHS)
97*>          If TRANS = 'N', the n-by-nrhs matrix X.
98*>          If TRANS = 'C', the m-by-nrhs matrix X.
99*> \endverbatim
100*>
101*> \param[in] LDX
102*> \verbatim
103*>          LDX is INTEGER
104*>          The leading dimension of the array X.
105*>          If TRANS = 'N', LDX >= N.
106*>          If TRANS = 'C', LDX >= M.
107*> \endverbatim
108*>
109*> \param[in] B
110*> \verbatim
111*>          B is COMPLEX*16 array, dimension (LDB,NRHS)
112*>          If TRANS = 'N', the m-by-nrhs matrix B.
113*>          If TRANS = 'C', the n-by-nrhs matrix B.
114*> \endverbatim
115*>
116*> \param[in] LDB
117*> \verbatim
118*>          LDB is INTEGER
119*>          The leading dimension of the array B.
120*>          If TRANS = 'N', LDB >= M.
121*>          If TRANS = 'C', LDB >= N.
122*> \endverbatim
123*>
124*> \param[out] C
125*> \verbatim
126*>          C is COMPLEX*16 array, dimension (LDB,NRHS)
127*> \endverbatim
128*>
129*> \param[out] WORK
130*> \verbatim
131*>          WORK is COMPLEX*16 array, dimension (LWORK)
132*> \endverbatim
133*>
134*> \param[in] LWORK
135*> \verbatim
136*>          LWORK is INTEGER
137*>          The length of the array WORK.  LWORK >= NRHS*(M+N).
138*> \endverbatim
139*
140*  Authors:
141*  ========
142*
143*> \author Univ. of Tennessee
144*> \author Univ. of California Berkeley
145*> \author Univ. of Colorado Denver
146*> \author NAG Ltd.
147*
148*> \ingroup complex16_lin
149*
150*  =====================================================================
151      DOUBLE PRECISION FUNCTION ZQRT17( TRANS, IRESID, M, N, NRHS, A,
152     $                 LDA, X, LDX, B, LDB, C, WORK, LWORK )
153*
154*  -- LAPACK test routine --
155*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
156*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
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   ERR, NORMA, NORMB, NORMRS, SMLNUM
176*     ..
177*     .. Local Arrays ..
178      DOUBLE PRECISION   RWORK( 1 )
179*     ..
180*     .. External Functions ..
181      LOGICAL            LSAME
182      DOUBLE PRECISION   DLAMCH, ZLANGE
183      EXTERNAL           LSAME, DLAMCH, ZLANGE
184*     ..
185*     .. External Subroutines ..
186      EXTERNAL           XERBLA, ZGEMM, ZLACPY, ZLASCL
187*     ..
188*     .. Intrinsic Functions ..
189      INTRINSIC          DBLE, DCMPLX, MAX
190*     ..
191*     .. Executable Statements ..
192*
193      ZQRT17 = ZERO
194*
195      IF( LSAME( TRANS, 'N' ) ) THEN
196         NROWS = M
197         NCOLS = N
198      ELSE IF( LSAME( TRANS, 'C' ) ) THEN
199         NROWS = N
200         NCOLS = M
201      ELSE
202         CALL XERBLA( 'ZQRT17', 1 )
203         RETURN
204      END IF
205*
206      IF( LWORK.LT.NCOLS*NRHS ) THEN
207         CALL XERBLA( 'ZQRT17', 13 )
208         RETURN
209      END IF
210*
211      IF( M.LE.0 .OR. N.LE.0 .OR. NRHS.LE.0 )
212     $   RETURN
213*
214      NORMA = ZLANGE( 'One-norm', M, N, A, LDA, RWORK )
215      SMLNUM = DLAMCH( 'Safe minimum' ) / DLAMCH( 'Precision' )
216      ISCL = 0
217*
218*     compute residual and scale it
219*
220      CALL ZLACPY( 'All', NROWS, NRHS, B, LDB, C, LDB )
221      CALL ZGEMM( TRANS, 'No transpose', NROWS, NRHS, NCOLS,
222     $            DCMPLX( -ONE ), A, LDA, X, LDX, DCMPLX( ONE ), C,
223     $            LDB )
224      NORMRS = ZLANGE( 'Max', NROWS, NRHS, C, LDB, RWORK )
225      IF( NORMRS.GT.SMLNUM ) THEN
226         ISCL = 1
227         CALL ZLASCL( 'General', 0, 0, NORMRS, ONE, NROWS, NRHS, C, LDB,
228     $                INFO )
229      END IF
230*
231*     compute R**H * op(A)
232*
233      CALL ZGEMM( 'Conjugate transpose', TRANS, NRHS, NCOLS, NROWS,
234     $            DCMPLX( ONE ), C, LDB, A, LDA, DCMPLX( ZERO ), WORK,
235     $            NRHS )
236*
237*     compute and properly scale error
238*
239      ERR = ZLANGE( 'One-norm', NRHS, NCOLS, WORK, NRHS, RWORK )
240      IF( NORMA.NE.ZERO )
241     $   ERR = ERR / NORMA
242*
243      IF( ISCL.EQ.1 )
244     $   ERR = ERR*NORMRS
245*
246      IF( IRESID.EQ.1 ) THEN
247         NORMB = ZLANGE( 'One-norm', NROWS, NRHS, B, LDB, RWORK )
248         IF( NORMB.NE.ZERO )
249     $      ERR = ERR / NORMB
250      ELSE
251         IF( NORMRS.NE.ZERO )
252     $      ERR = ERR / NORMRS
253      END IF
254*
255      ZQRT17 = ERR / ( DLAMCH( 'Epsilon' )*DBLE( MAX( M, N, NRHS ) ) )
256      RETURN
257*
258*     End of ZQRT17
259*
260      END
261