LAPACK  3.7.0
LAPACK: Linear Algebra PACKage
zdrvhex.f
Go to the documentation of this file.
1 *> \brief \b ZDRVHEX
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 ZDRVHE( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
12 * A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK,
13 * NOUT )
14 *
15 * .. Scalar Arguments ..
16 * LOGICAL TSTERR
17 * INTEGER NMAX, NN, NOUT, NRHS
18 * DOUBLE PRECISION THRESH
19 * ..
20 * .. Array Arguments ..
21 * LOGICAL DOTYPE( * )
22 * INTEGER IWORK( * ), NVAL( * )
23 * DOUBLE PRECISION RWORK( * )
24 * COMPLEX*16 A( * ), AFAC( * ), AINV( * ), B( * ),
25 * $ WORK( * ), X( * ), XACT( * )
26 * ..
27 *
28 *
29 *> \par Purpose:
30 * =============
31 *>
32 *> \verbatim
33 *>
34 *> ZDRVHE tests the driver routines ZHESV, -SVX, and -SVXX.
35 *>
36 *> Note that this file is used only when the XBLAS are available,
37 *> otherwise zdrvhe.f defines this subroutine.
38 *> \endverbatim
39 *
40 * Arguments:
41 * ==========
42 *
43 *> \param[in] DOTYPE
44 *> \verbatim
45 *> DOTYPE is LOGICAL array, dimension (NTYPES)
46 *> The matrix types to be used for testing. Matrices of type j
47 *> (for 1 <= j <= NTYPES) are used for testing if DOTYPE(j) =
48 *> .TRUE.; if DOTYPE(j) = .FALSE., then type j is not used.
49 *> \endverbatim
50 *>
51 *> \param[in] NN
52 *> \verbatim
53 *> NN is INTEGER
54 *> The number of values of N contained in the vector NVAL.
55 *> \endverbatim
56 *>
57 *> \param[in] NVAL
58 *> \verbatim
59 *> NVAL is INTEGER array, dimension (NN)
60 *> The values of the matrix dimension N.
61 *> \endverbatim
62 *>
63 *> \param[in] NRHS
64 *> \verbatim
65 *> NRHS is INTEGER
66 *> The number of right hand side vectors to be generated for
67 *> each linear system.
68 *> \endverbatim
69 *>
70 *> \param[in] THRESH
71 *> \verbatim
72 *> THRESH is DOUBLE PRECISION
73 *> The threshold value for the test ratios. A result is
74 *> included in the output file if RESULT >= THRESH. To have
75 *> every test ratio printed, use THRESH = 0.
76 *> \endverbatim
77 *>
78 *> \param[in] TSTERR
79 *> \verbatim
80 *> TSTERR is LOGICAL
81 *> Flag that indicates whether error exits are to be tested.
82 *> \endverbatim
83 *>
84 *> \param[in] NMAX
85 *> \verbatim
86 *> NMAX is INTEGER
87 *> The maximum value permitted for N, used in dimensioning the
88 *> work arrays.
89 *> \endverbatim
90 *>
91 *> \param[out] A
92 *> \verbatim
93 *> A is COMPLEX*16 array, dimension (NMAX*NMAX)
94 *> \endverbatim
95 *>
96 *> \param[out] AFAC
97 *> \verbatim
98 *> AFAC is COMPLEX*16 array, dimension (NMAX*NMAX)
99 *> \endverbatim
100 *>
101 *> \param[out] AINV
102 *> \verbatim
103 *> AINV is COMPLEX*16 array, dimension (NMAX*NMAX)
104 *> \endverbatim
105 *>
106 *> \param[out] B
107 *> \verbatim
108 *> B is COMPLEX*16 array, dimension (NMAX*NRHS)
109 *> \endverbatim
110 *>
111 *> \param[out] X
112 *> \verbatim
113 *> X is COMPLEX*16 array, dimension (NMAX*NRHS)
114 *> \endverbatim
115 *>
116 *> \param[out] XACT
117 *> \verbatim
118 *> XACT is COMPLEX*16 array, dimension (NMAX*NRHS)
119 *> \endverbatim
120 *>
121 *> \param[out] WORK
122 *> \verbatim
123 *> WORK is COMPLEX*16 array, dimension
124 *> (NMAX*max(2,NRHS))
125 *> \endverbatim
126 *>
127 *> \param[out] RWORK
128 *> \verbatim
129 *> RWORK is DOUBLE PRECISION array, dimension (2*NMAX+2*NRHS)
130 *> \endverbatim
131 *>
132 *> \param[out] IWORK
133 *> \verbatim
134 *> IWORK is INTEGER array, dimension (NMAX)
135 *> \endverbatim
136 *>
137 *> \param[in] NOUT
138 *> \verbatim
139 *> NOUT is INTEGER
140 *> The unit number for output.
141 *> \endverbatim
142 *
143 * Authors:
144 * ========
145 *
146 *> \author Univ. of Tennessee
147 *> \author Univ. of California Berkeley
148 *> \author Univ. of Colorado Denver
149 *> \author NAG Ltd.
150 *
151 *> \date April 2012
152 *
153 *> \ingroup complex16_lin
154 *
155 * =====================================================================
156  SUBROUTINE zdrvhe( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
157  $ a, afac, ainv, b, x, xact, work, rwork, iwork,
158  $ nout )
159 *
160 * -- LAPACK test routine (version 3.7.0) --
161 * -- LAPACK is a software package provided by Univ. of Tennessee, --
162 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
163 * April 2012
164 *
165 * .. Scalar Arguments ..
166  LOGICAL tsterr
167  INTEGER nmax, nn, nout, nrhs
168  DOUBLE PRECISION thresh
169 * ..
170 * .. Array Arguments ..
171  LOGICAL dotype( * )
172  INTEGER iwork( * ), nval( * )
173  DOUBLE PRECISION rwork( * )
174  COMPLEX*16 a( * ), afac( * ), ainv( * ), b( * ),
175  $ work( * ), x( * ), xact( * )
176 * ..
177 *
178 * =====================================================================
179 *
180 * .. Parameters ..
181  DOUBLE PRECISION one, zero
182  parameter ( one = 1.0d+0, zero = 0.0d+0 )
183  INTEGER ntypes, ntests
184  parameter ( ntypes = 10, ntests = 6 )
185  INTEGER nfact
186  parameter ( nfact = 2 )
187 * ..
188 * .. Local Scalars ..
189  LOGICAL zerot
190  CHARACTER dist, equed, fact, TYPE, uplo, xtype
191  CHARACTER*3 path
192  INTEGER i, i1, i2, ifact, imat, in, info, ioff, iuplo,
193  $ izero, j, k, k1, kl, ku, lda, lwork, mode, n,
194  $ nb, nbmin, nerrs, nfail, nimat, nrun, nt,
195  $ n_err_bnds
196  DOUBLE PRECISION ainvnm, anorm, cndnum, rcond, rcondc,
197  $ rpvgrw_svxx
198 * ..
199 * .. Local Arrays ..
200  CHARACTER facts( nfact ), uplos( 2 )
201  INTEGER iseed( 4 ), iseedy( 4 )
202  DOUBLE PRECISION result( ntests ), berr( nrhs ),
203  $ errbnds_n( nrhs, 3 ), errbnds_c( nrhs, 3 )
204 * ..
205 * .. External Functions ..
206  DOUBLE PRECISION dget06, zlanhe
207  EXTERNAL dget06, zlanhe
208 * ..
209 * .. External Subroutines ..
210  EXTERNAL aladhd, alaerh, alasvm, xlaenv, zerrvx, zget04,
213  $ zpot05, zhesvxx
214 * ..
215 * .. Scalars in Common ..
216  LOGICAL lerr, ok
217  CHARACTER*32 srnamt
218  INTEGER infot, nunit
219 * ..
220 * .. Common blocks ..
221  COMMON / infoc / infot, nunit, ok, lerr
222  COMMON / srnamc / srnamt
223 * ..
224 * .. Intrinsic Functions ..
225  INTRINSIC dcmplx, max, min
226 * ..
227 * .. Data statements ..
228  DATA iseedy / 1988, 1989, 1990, 1991 /
229  DATA uplos / 'U', 'L' / , facts / 'F', 'N' /
230 * ..
231 * .. Executable Statements ..
232 *
233 * Initialize constants and the random number seed.
234 *
235  path( 1: 1 ) = 'Z'
236  path( 2: 3 ) = 'HE'
237  nrun = 0
238  nfail = 0
239  nerrs = 0
240  DO 10 i = 1, 4
241  iseed( i ) = iseedy( i )
242  10 CONTINUE
243  lwork = max( 2*nmax, nmax*nrhs )
244 *
245 * Test the error exits
246 *
247  IF( tsterr )
248  $ CALL zerrvx( path, nout )
249  infot = 0
250 *
251 * Set the block size and minimum block size for testing.
252 *
253  nb = 1
254  nbmin = 2
255  CALL xlaenv( 1, nb )
256  CALL xlaenv( 2, nbmin )
257 *
258 * Do for each value of N in NVAL
259 *
260  DO 180 in = 1, nn
261  n = nval( in )
262  lda = max( n, 1 )
263  xtype = 'N'
264  nimat = ntypes
265  IF( n.LE.0 )
266  $ nimat = 1
267 *
268  DO 170 imat = 1, nimat
269 *
270 * Do the tests only if DOTYPE( IMAT ) is true.
271 *
272  IF( .NOT.dotype( imat ) )
273  $ GO TO 170
274 *
275 * Skip types 3, 4, 5, or 6 if the matrix size is too small.
276 *
277  zerot = imat.GE.3 .AND. imat.LE.6
278  IF( zerot .AND. n.LT.imat-2 )
279  $ GO TO 170
280 *
281 * Do first for UPLO = 'U', then for UPLO = 'L'
282 *
283  DO 160 iuplo = 1, 2
284  uplo = uplos( iuplo )
285 *
286 * Set up parameters with ZLATB4 and generate a test matrix
287 * with ZLATMS.
288 *
289  CALL zlatb4( path, imat, n, n, TYPE, kl, ku, anorm, mode,
290  $ cndnum, dist )
291 *
292  srnamt = 'ZLATMS'
293  CALL zlatms( n, n, dist, iseed, TYPE, rwork, mode,
294  $ cndnum, anorm, kl, ku, uplo, a, lda, work,
295  $ info )
296 *
297 * Check error code from ZLATMS.
298 *
299  IF( info.NE.0 ) THEN
300  CALL alaerh( path, 'ZLATMS', info, 0, uplo, n, n, -1,
301  $ -1, -1, imat, nfail, nerrs, nout )
302  GO TO 160
303  END IF
304 *
305 * For types 3-6, zero one or more rows and columns of the
306 * matrix to test that INFO is returned correctly.
307 *
308  IF( zerot ) THEN
309  IF( imat.EQ.3 ) THEN
310  izero = 1
311  ELSE IF( imat.EQ.4 ) THEN
312  izero = n
313  ELSE
314  izero = n / 2 + 1
315  END IF
316 *
317  IF( imat.LT.6 ) THEN
318 *
319 * Set row and column IZERO to zero.
320 *
321  IF( iuplo.EQ.1 ) THEN
322  ioff = ( izero-1 )*lda
323  DO 20 i = 1, izero - 1
324  a( ioff+i ) = zero
325  20 CONTINUE
326  ioff = ioff + izero
327  DO 30 i = izero, n
328  a( ioff ) = zero
329  ioff = ioff + lda
330  30 CONTINUE
331  ELSE
332  ioff = izero
333  DO 40 i = 1, izero - 1
334  a( ioff ) = zero
335  ioff = ioff + lda
336  40 CONTINUE
337  ioff = ioff - izero
338  DO 50 i = izero, n
339  a( ioff+i ) = zero
340  50 CONTINUE
341  END IF
342  ELSE
343  ioff = 0
344  IF( iuplo.EQ.1 ) THEN
345 *
346 * Set the first IZERO rows and columns to zero.
347 *
348  DO 70 j = 1, n
349  i2 = min( j, izero )
350  DO 60 i = 1, i2
351  a( ioff+i ) = zero
352  60 CONTINUE
353  ioff = ioff + lda
354  70 CONTINUE
355  ELSE
356 *
357 * Set the last IZERO rows and columns to zero.
358 *
359  DO 90 j = 1, n
360  i1 = max( j, izero )
361  DO 80 i = i1, n
362  a( ioff+i ) = zero
363  80 CONTINUE
364  ioff = ioff + lda
365  90 CONTINUE
366  END IF
367  END IF
368  ELSE
369  izero = 0
370  END IF
371 *
372 * Set the imaginary part of the diagonals.
373 *
374  CALL zlaipd( n, a, lda+1, 0 )
375 *
376  DO 150 ifact = 1, nfact
377 *
378 * Do first for FACT = 'F', then for other values.
379 *
380  fact = facts( ifact )
381 *
382 * Compute the condition number for comparison with
383 * the value returned by ZHESVX.
384 *
385  IF( zerot ) THEN
386  IF( ifact.EQ.1 )
387  $ GO TO 150
388  rcondc = zero
389 *
390  ELSE IF( ifact.EQ.1 ) THEN
391 *
392 * Compute the 1-norm of A.
393 *
394  anorm = zlanhe( '1', uplo, n, a, lda, rwork )
395 *
396 * Factor the matrix A.
397 *
398  CALL zlacpy( uplo, n, n, a, lda, afac, lda )
399  CALL zhetrf( uplo, n, afac, lda, iwork, work,
400  $ lwork, info )
401 *
402 * Compute inv(A) and take its norm.
403 *
404  CALL zlacpy( uplo, n, n, afac, lda, ainv, lda )
405  lwork = (n+nb+1)*(nb+3)
406  CALL zhetri2( uplo, n, ainv, lda, iwork, work,
407  $ lwork, info )
408  ainvnm = zlanhe( '1', uplo, n, ainv, lda, rwork )
409 *
410 * Compute the 1-norm condition number of A.
411 *
412  IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
413  rcondc = one
414  ELSE
415  rcondc = ( one / anorm ) / ainvnm
416  END IF
417  END IF
418 *
419 * Form an exact solution and set the right hand side.
420 *
421  srnamt = 'ZLARHS'
422  CALL zlarhs( path, xtype, uplo, ' ', n, n, kl, ku,
423  $ nrhs, a, lda, xact, lda, b, lda, iseed,
424  $ info )
425  xtype = 'C'
426 *
427 * --- Test ZHESV ---
428 *
429  IF( ifact.EQ.2 ) THEN
430  CALL zlacpy( uplo, n, n, a, lda, afac, lda )
431  CALL zlacpy( 'Full', n, nrhs, b, lda, x, lda )
432 *
433 * Factor the matrix and solve the system using ZHESV.
434 *
435  srnamt = 'ZHESV '
436  CALL zhesv( uplo, n, nrhs, afac, lda, iwork, x,
437  $ lda, work, lwork, info )
438 *
439 * Adjust the expected value of INFO to account for
440 * pivoting.
441 *
442  k = izero
443  IF( k.GT.0 ) THEN
444  100 CONTINUE
445  IF( iwork( k ).LT.0 ) THEN
446  IF( iwork( k ).NE.-k ) THEN
447  k = -iwork( k )
448  GO TO 100
449  END IF
450  ELSE IF( iwork( k ).NE.k ) THEN
451  k = iwork( k )
452  GO TO 100
453  END IF
454  END IF
455 *
456 * Check error code from ZHESV .
457 *
458  IF( info.NE.k ) THEN
459  CALL alaerh( path, 'ZHESV ', info, k, uplo, n,
460  $ n, -1, -1, nrhs, imat, nfail,
461  $ nerrs, nout )
462  GO TO 120
463  ELSE IF( info.NE.0 ) THEN
464  GO TO 120
465  END IF
466 *
467 * Reconstruct matrix from factors and compute
468 * residual.
469 *
470  CALL zhet01( uplo, n, a, lda, afac, lda, iwork,
471  $ ainv, lda, rwork, result( 1 ) )
472 *
473 * Compute residual of the computed solution.
474 *
475  CALL zlacpy( 'Full', n, nrhs, b, lda, work, lda )
476  CALL zpot02( uplo, n, nrhs, a, lda, x, lda, work,
477  $ lda, rwork, result( 2 ) )
478 *
479 * Check solution from generated exact solution.
480 *
481  CALL zget04( n, nrhs, x, lda, xact, lda, rcondc,
482  $ result( 3 ) )
483  nt = 3
484 *
485 * Print information about the tests that did not pass
486 * the threshold.
487 *
488  DO 110 k = 1, nt
489  IF( result( k ).GE.thresh ) THEN
490  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
491  $ CALL aladhd( nout, path )
492  WRITE( nout, fmt = 9999 )'ZHESV ', uplo, n,
493  $ imat, k, result( k )
494  nfail = nfail + 1
495  END IF
496  110 CONTINUE
497  nrun = nrun + nt
498  120 CONTINUE
499  END IF
500 *
501 * --- Test ZHESVX ---
502 *
503  IF( ifact.EQ.2 )
504  $ CALL zlaset( uplo, n, n, dcmplx( zero ),
505  $ dcmplx( zero ), afac, lda )
506  CALL zlaset( 'Full', n, nrhs, dcmplx( zero ),
507  $ dcmplx( zero ), x, lda )
508 *
509 * Solve the system and compute the condition number and
510 * error bounds using ZHESVX.
511 *
512  srnamt = 'ZHESVX'
513  CALL zhesvx( fact, uplo, n, nrhs, a, lda, afac, lda,
514  $ iwork, b, lda, x, lda, rcond, rwork,
515  $ rwork( nrhs+1 ), work, lwork,
516  $ rwork( 2*nrhs+1 ), info )
517 *
518 * Adjust the expected value of INFO to account for
519 * pivoting.
520 *
521  k = izero
522  IF( k.GT.0 ) THEN
523  130 CONTINUE
524  IF( iwork( k ).LT.0 ) THEN
525  IF( iwork( k ).NE.-k ) THEN
526  k = -iwork( k )
527  GO TO 130
528  END IF
529  ELSE IF( iwork( k ).NE.k ) THEN
530  k = iwork( k )
531  GO TO 130
532  END IF
533  END IF
534 *
535 * Check the error code from ZHESVX.
536 *
537  IF( info.NE.k ) THEN
538  CALL alaerh( path, 'ZHESVX', info, k, fact // uplo,
539  $ n, n, -1, -1, nrhs, imat, nfail,
540  $ nerrs, nout )
541  GO TO 150
542  END IF
543 *
544  IF( info.EQ.0 ) THEN
545  IF( ifact.GE.2 ) THEN
546 *
547 * Reconstruct matrix from factors and compute
548 * residual.
549 *
550  CALL zhet01( uplo, n, a, lda, afac, lda, iwork,
551  $ ainv, lda, rwork( 2*nrhs+1 ),
552  $ result( 1 ) )
553  k1 = 1
554  ELSE
555  k1 = 2
556  END IF
557 *
558 * Compute residual of the computed solution.
559 *
560  CALL zlacpy( 'Full', n, nrhs, b, lda, work, lda )
561  CALL zpot02( uplo, n, nrhs, a, lda, x, lda, work,
562  $ lda, rwork( 2*nrhs+1 ), result( 2 ) )
563 *
564 * Check solution from generated exact solution.
565 *
566  CALL zget04( n, nrhs, x, lda, xact, lda, rcondc,
567  $ result( 3 ) )
568 *
569 * Check the error bounds from iterative refinement.
570 *
571  CALL zpot05( uplo, n, nrhs, a, lda, b, lda, x, lda,
572  $ xact, lda, rwork, rwork( nrhs+1 ),
573  $ result( 4 ) )
574  ELSE
575  k1 = 6
576  END IF
577 *
578 * Compare RCOND from ZHESVX with the computed value
579 * in RCONDC.
580 *
581  result( 6 ) = dget06( rcond, rcondc )
582 *
583 * Print information about the tests that did not pass
584 * the threshold.
585 *
586  DO 140 k = k1, 6
587  IF( result( k ).GE.thresh ) THEN
588  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
589  $ CALL aladhd( nout, path )
590  WRITE( nout, fmt = 9998 )'ZHESVX', fact, uplo,
591  $ n, imat, k, result( k )
592  nfail = nfail + 1
593  END IF
594  140 CONTINUE
595  nrun = nrun + 7 - k1
596 *
597 * --- Test ZHESVXX ---
598 *
599 * Restore the matrices A and B.
600 *
601  IF( ifact.EQ.2 )
602  $ CALL zlaset( uplo, n, n, cmplx( zero ),
603  $ cmplx( zero ), afac, lda )
604  CALL zlaset( 'Full', n, nrhs, cmplx( zero ),
605  $ cmplx( zero ), x, lda )
606 *
607 * Solve the system and compute the condition number
608 * and error bounds using ZHESVXX.
609 *
610  srnamt = 'ZHESVXX'
611  n_err_bnds = 3
612  equed = 'N'
613  CALL zhesvxx( fact, uplo, n, nrhs, a, lda, afac,
614  $ lda, iwork, equed, work( n+1 ), b, lda, x,
615  $ lda, rcond, rpvgrw_svxx, berr, n_err_bnds,
616  $ errbnds_n, errbnds_c, 0, zero, work,
617  $ rwork(2*nrhs+1), info )
618 *
619 * Adjust the expected value of INFO to account for
620 * pivoting.
621 *
622  k = izero
623  IF( k.GT.0 ) THEN
624  135 CONTINUE
625  IF( iwork( k ).LT.0 ) THEN
626  IF( iwork( k ).NE.-k ) THEN
627  k = -iwork( k )
628  GO TO 135
629  END IF
630  ELSE IF( iwork( k ).NE.k ) THEN
631  k = iwork( k )
632  GO TO 135
633  END IF
634  END IF
635 *
636 * Check the error code from ZHESVXX.
637 *
638  IF( info.NE.k .AND. info.LE.n) THEN
639  CALL alaerh( path, 'ZHESVXX', info, k,
640  $ fact // uplo, n, n, -1, -1, nrhs, imat, nfail,
641  $ nerrs, nout )
642  GO TO 150
643  END IF
644 *
645  IF( info.EQ.0 ) THEN
646  IF( ifact.GE.2 ) THEN
647 *
648 * Reconstruct matrix from factors and compute
649 * residual.
650 *
651  CALL zhet01( uplo, n, a, lda, afac, lda, iwork,
652  $ ainv, lda, rwork(2*nrhs+1),
653  $ result( 1 ) )
654  k1 = 1
655  ELSE
656  k1 = 2
657  END IF
658 *
659 * Compute residual of the computed solution.
660 *
661  CALL zlacpy( 'Full', n, nrhs, b, lda, work, lda )
662  CALL zpot02( uplo, n, nrhs, a, lda, x, lda, work,
663  $ lda, rwork( 2*nrhs+1 ), result( 2 ) )
664  result( 2 ) = 0.0
665 *
666 * Check solution from generated exact solution.
667 *
668  CALL zget04( n, nrhs, x, lda, xact, lda, rcondc,
669  $ result( 3 ) )
670 *
671 * Check the error bounds from iterative refinement.
672 *
673  CALL zpot05( uplo, n, nrhs, a, lda, b, lda, x, lda,
674  $ xact, lda, rwork, rwork( nrhs+1 ),
675  $ result( 4 ) )
676  ELSE
677  k1 = 6
678  END IF
679 *
680 * Compare RCOND from ZHESVXX with the computed value
681 * in RCONDC.
682 *
683  result( 6 ) = dget06( rcond, rcondc )
684 *
685 * Print information about the tests that did not pass
686 * the threshold.
687 *
688  DO 85 k = k1, 6
689  IF( result( k ).GE.thresh ) THEN
690  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
691  $ CALL aladhd( nout, path )
692  WRITE( nout, fmt = 9998 )'ZHESVXX',
693  $ fact, uplo, n, imat, k,
694  $ result( k )
695  nfail = nfail + 1
696  END IF
697  85 CONTINUE
698  nrun = nrun + 7 - k1
699 *
700  150 CONTINUE
701 *
702  160 CONTINUE
703  170 CONTINUE
704  180 CONTINUE
705 *
706 * Print a summary of the results.
707 *
708  CALL alasvm( path, nout, nfail, nrun, nerrs )
709 *
710 
711 * Test Error Bounds from ZHESVXX
712 
713  CALL zebchvxx(thresh, path)
714 
715  9999 FORMAT( 1x, a, ', UPLO=''', a1, ''', N =', i5, ', type ', i2,
716  $ ', test ', i2, ', ratio =', g12.5 )
717  9998 FORMAT( 1x, a, ', FACT=''', a1, ''', UPLO=''', a1, ''', N =', i5,
718  $ ', type ', i2, ', test ', i2, ', ratio =', g12.5 )
719  RETURN
720 *
721 * End of ZDRVHE
722 *
723  END
subroutine alasvm(TYPE, NOUT, NFAIL, NRUN, NERRS)
ALASVM
Definition: alasvm.f:75
subroutine zhetri2(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
ZHETRI2
Definition: zhetri2.f:129
subroutine alaerh(PATH, SUBNAM, INFO, INFOE, OPTS, M, N, KL, KU, N5, IMAT, NFAIL, NERRS, NOUT)
ALAERH
Definition: alaerh.f:149
double precision function zlanhe(NORM, UPLO, N, A, LDA, WORK)
ZLANHE returns the value of the 1-norm, or the Frobenius norm, or the infinity norm, or the element of largest absolute value of a complex Hermitian matrix.
Definition: zlanhe.f:126
subroutine zget04(N, NRHS, X, LDX, XACT, LDXACT, RCOND, RESID)
ZGET04
Definition: zget04.f:104
subroutine zpot02(UPLO, N, NRHS, A, LDA, X, LDX, B, LDB, RWORK, RESID)
ZPOT02
Definition: zpot02.f:129
subroutine zlarhs(PATH, XTYPE, UPLO, TRANS, M, N, KL, KU, NRHS, A, LDA, X, LDX, B, LDB, ISEED, INFO)
ZLARHS
Definition: zlarhs.f:211
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
subroutine zhet01(UPLO, N, A, LDA, AFAC, LDAFAC, IPIV, C, LDC, RWORK, RESID)
ZHET01
Definition: zhet01.f:128
subroutine zhesvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, LWORK, RWORK, INFO)
ZHESVX computes the solution to system of linear equations A * X = B for HE matrices ...
Definition: zhesvx.f:287
subroutine xlaenv(ISPEC, NVALUE)
XLAENV
Definition: xlaenv.f:83
subroutine zlatb4(PATH, IMAT, M, N, TYPE, KL, KU, ANORM, MODE, CNDNUM, DIST)
ZLATB4
Definition: zlatb4.f:123
subroutine zlaipd(N, A, INDA, VINDA)
ZLAIPD
Definition: zlaipd.f:85
subroutine zebchvxx(THRESH, PATH)
ZEBCHVXX
Definition: zebchvxx.f:98
subroutine aladhd(IOUNIT, PATH)
ALADHD
Definition: aladhd.f:92
subroutine zlaset(UPLO, M, N, ALPHA, BETA, A, LDA)
ZLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values...
Definition: zlaset.f:108
subroutine zhetrf(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
ZHETRF
Definition: zhetrf.f:179
subroutine zhesvxx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, EQUED, S, B, LDB, X, LDX, RCOND, RPVGRW, BERR, N_ERR_BNDS, ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS, WORK, RWORK, INFO)
ZHESVXX computes the solution to system of linear equations A * X = B for HE matrices ...
Definition: zhesvxx.f:508
double precision function dget06(RCOND, RCONDC)
DGET06
Definition: dget06.f:57
subroutine zerrvx(PATH, NUNIT)
ZERRVX
Definition: zerrvx.f:57
subroutine zdrvhe(DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X, XACT, WORK, RWORK, IWORK, NOUT)
ZDRVHE
Definition: zdrvhe.f:155
subroutine zlatms(M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, KL, KU, PACK, A, LDA, WORK, INFO)
ZLATMS
Definition: zlatms.f:334
subroutine zpot05(UPLO, N, NRHS, A, LDA, B, LDB, X, LDX, XACT, LDXACT, FERR, BERR, RESLTS)
ZPOT05
Definition: zpot05.f:167
subroutine zhesv(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
ZHESV computes the solution to system of linear equations A * X = B for HE matrices ...
Definition: zhesv.f:173