LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
double precision function zqrt17 ( character  TRANS,
integer  IRESID,
integer  M,
integer  N,
integer  NRHS,
complex*16, dimension( lda, * )  A,
integer  LDA,
complex*16, dimension( ldx, * )  X,
integer  LDX,
complex*16, dimension( ldb, * )  B,
integer  LDB,
complex*16, dimension( ldb, * )  C,
complex*16, dimension( lwork )  WORK,
integer  LWORK 
)

ZQRT17

Purpose:
 ZQRT17 computes the ratio

    || R'*op(A) ||/(||A||*alpha*max(M,N,NRHS)*eps)

 where R = op(A)*X - B, op(A) is A or A', and

    alpha = ||B|| if IRESID = 1 (zero-residual problem)
    alpha = ||R|| if IRESID = 2 (otherwise).
Parameters
[in]TRANS
          TRANS is CHARACTER*1
          Specifies whether or not the transpose of A is used.
          = 'N':  No transpose, op(A) = A.
          = 'C':  Conjugate transpose, op(A) = A'.
[in]IRESID
          IRESID is INTEGER
          IRESID = 1 indicates zero-residual problem.
          IRESID = 2 indicates non-zero residual.
[in]M
          M is INTEGER
          The number of rows of the matrix A.
          If TRANS = 'N', the number of rows of the matrix B.
          If TRANS = 'C', the number of rows of the matrix X.
[in]N
          N is INTEGER
          The number of columns of the matrix  A.
          If TRANS = 'N', the number of rows of the matrix X.
          If TRANS = 'C', the number of rows of the matrix B.
[in]NRHS
          NRHS is INTEGER
          The number of columns of the matrices X and B.
[in]A
          A is COMPLEX*16 array, dimension (LDA,N)
          The m-by-n matrix A.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A. LDA >= M.
[in]X
          X is COMPLEX*16 array, dimension (LDX,NRHS)
          If TRANS = 'N', the n-by-nrhs matrix X.
          If TRANS = 'C', the m-by-nrhs matrix X.
[in]LDX
          LDX is INTEGER
          The leading dimension of the array X.
          If TRANS = 'N', LDX >= N.
          If TRANS = 'C', LDX >= M.
[in]B
          B is COMPLEX*16 array, dimension (LDB,NRHS)
          If TRANS = 'N', the m-by-nrhs matrix B.
          If TRANS = 'C', the n-by-nrhs matrix B.
[in]LDB
          LDB is INTEGER
          The leading dimension of the array B.
          If TRANS = 'N', LDB >= M.
          If TRANS = 'C', LDB >= N.
[out]C
          C is COMPLEX*16 array, dimension (LDB,NRHS)
[out]WORK
          WORK is COMPLEX*16 array, dimension (LWORK)
[in]LWORK
          LWORK is INTEGER
          The length of the array WORK.  LWORK >= NRHS*(M+N).
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2015

Definition at line 152 of file zqrt17.f.

152 *
153 * -- LAPACK test routine (version 3.6.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 2015
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  IF( normrs.NE.zero )
254  $ err = err / normrs
255  END IF
256 *
257  zqrt17 = err / ( dlamch( 'Epsilon' )*dble( max( m, n, nrhs ) ) )
258  RETURN
259 *
260 * End of ZQRT17
261 *
subroutine zlacpy(UPLO, M, N, A, LDA, B, LDB)
ZLACPY copies all or part of one two-dimensional array to another.
Definition: zlacpy.f:105
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
subroutine zgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
ZGEMM
Definition: zgemm.f:189
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
double precision function zlange(NORM, M, N, A, LDA, WORK)
ZLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition: zlange.f:117
subroutine zlascl(TYPE, KL, KU, CFROM, CTO, M, N, A, LDA, INFO)
ZLASCL multiplies a general rectangular matrix by a real scalar defined as cto/cfrom.
Definition: zlascl.f:145
double precision function zqrt17(TRANS, IRESID, M, N, NRHS, A, LDA, X, LDX, B, LDB, C, WORK, LWORK)
ZQRT17
Definition: zqrt17.f:152
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function: