LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zchktp.f
Go to the documentation of this file.
1 *> \brief \b ZCHKTP
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 ZCHKTP( DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR,
12 * NMAX, AP, AINVP, B, X, XACT, WORK, RWORK,
13 * NOUT )
14 *
15 * .. Scalar Arguments ..
16 * LOGICAL TSTERR
17 * INTEGER NMAX, NN, NNS, NOUT
18 * DOUBLE PRECISION THRESH
19 * ..
20 * .. Array Arguments ..
21 * LOGICAL DOTYPE( * )
22 * INTEGER NSVAL( * ), NVAL( * )
23 * DOUBLE PRECISION RWORK( * )
24 * COMPLEX*16 AINVP( * ), AP( * ), B( * ), WORK( * ), X( * ),
25 * $ XACT( * )
26 * ..
27 *
28 *
29 *> \par Purpose:
30 * =============
31 *>
32 *> \verbatim
33 *>
34 *> ZCHKTP tests ZTPTRI, -TRS, -RFS, and -CON, and ZLATPS
35 *> \endverbatim
36 *
37 * Arguments:
38 * ==========
39 *
40 *> \param[in] DOTYPE
41 *> \verbatim
42 *> DOTYPE is LOGICAL array, dimension (NTYPES)
43 *> The matrix types to be used for testing. Matrices of type j
44 *> (for 1 <= j <= NTYPES) are used for testing if DOTYPE(j) =
45 *> .TRUE.; if DOTYPE(j) = .FALSE., then type j is not used.
46 *> \endverbatim
47 *>
48 *> \param[in] NN
49 *> \verbatim
50 *> NN is INTEGER
51 *> The number of values of N contained in the vector NVAL.
52 *> \endverbatim
53 *>
54 *> \param[in] NVAL
55 *> \verbatim
56 *> NVAL is INTEGER array, dimension (NN)
57 *> The values of the matrix column dimension N.
58 *> \endverbatim
59 *>
60 *> \param[in] NNS
61 *> \verbatim
62 *> NNS is INTEGER
63 *> The number of values of NRHS contained in the vector NSVAL.
64 *> \endverbatim
65 *>
66 *> \param[in] NSVAL
67 *> \verbatim
68 *> NSVAL is INTEGER array, dimension (NNS)
69 *> The values of the number of right hand sides NRHS.
70 *> \endverbatim
71 *>
72 *> \param[in] THRESH
73 *> \verbatim
74 *> THRESH is DOUBLE PRECISION
75 *> The threshold value for the test ratios. A result is
76 *> included in the output file if RESULT >= THRESH. To have
77 *> every test ratio printed, use THRESH = 0.
78 *> \endverbatim
79 *>
80 *> \param[in] TSTERR
81 *> \verbatim
82 *> TSTERR is LOGICAL
83 *> Flag that indicates whether error exits are to be tested.
84 *> \endverbatim
85 *>
86 *> \param[in] NMAX
87 *> \verbatim
88 *> NMAX is INTEGER
89 *> The leading dimension of the work arrays. NMAX >= the
90 *> maximumm value of N in NVAL.
91 *> \endverbatim
92 *>
93 *> \param[out] AP
94 *> \verbatim
95 *> AP is COMPLEX*16 array, dimension (NMAX*(NMAX+1)/2)
96 *> \endverbatim
97 *>
98 *> \param[out] AINVP
99 *> \verbatim
100 *> AINVP is COMPLEX*16 array, dimension (NMAX*(NMAX+1)/2)
101 *> \endverbatim
102 *>
103 *> \param[out] B
104 *> \verbatim
105 *> B is COMPLEX*16 array, dimension (NMAX*NSMAX)
106 *> where NSMAX is the largest entry in NSVAL.
107 *> \endverbatim
108 *>
109 *> \param[out] X
110 *> \verbatim
111 *> X is COMPLEX*16 array, dimension (NMAX*NSMAX)
112 *> \endverbatim
113 *>
114 *> \param[out] XACT
115 *> \verbatim
116 *> XACT is COMPLEX*16 array, dimension (NMAX*NSMAX)
117 *> \endverbatim
118 *>
119 *> \param[out] WORK
120 *> \verbatim
121 *> WORK is COMPLEX*16 array, dimension
122 *> (NMAX*max(3,NSMAX))
123 *> \endverbatim
124 *>
125 *> \param[out] RWORK
126 *> \verbatim
127 *> RWORK is DOUBLE PRECISION array, dimension
128 *> (max(NMAX,2*NSMAX))
129 *> \endverbatim
130 *>
131 *> \param[in] NOUT
132 *> \verbatim
133 *> NOUT is INTEGER
134 *> The unit number for output.
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  SUBROUTINE zchktp( DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR,
151  $ nmax, ap, ainvp, b, x, xact, work, rwork,
152  $ nout )
153 *
154 * -- LAPACK test routine (version 3.4.0) --
155 * -- LAPACK is a software package provided by Univ. of Tennessee, --
156 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
157 * November 2011
158 *
159 * .. Scalar Arguments ..
160  LOGICAL tsterr
161  INTEGER nmax, nn, nns, nout
162  DOUBLE PRECISION thresh
163 * ..
164 * .. Array Arguments ..
165  LOGICAL dotype( * )
166  INTEGER nsval( * ), nval( * )
167  DOUBLE PRECISION rwork( * )
168  COMPLEX*16 ainvp( * ), ap( * ), b( * ), work( * ), x( * ),
169  $ xact( * )
170 * ..
171 *
172 * =====================================================================
173 *
174 * .. Parameters ..
175  INTEGER ntype1, ntypes
176  parameter( ntype1 = 10, ntypes = 18 )
177  INTEGER ntests
178  parameter( ntests = 9 )
179  INTEGER ntran
180  parameter( ntran = 3 )
181  DOUBLE PRECISION one, zero
182  parameter( one = 1.0d+0, zero = 0.0d+0 )
183 * ..
184 * .. Local Scalars ..
185  CHARACTER diag, norm, trans, uplo, xtype
186  CHARACTER*3 path
187  INTEGER i, idiag, imat, in, info, irhs, itran, iuplo,
188  $ k, lap, lda, n, nerrs, nfail, nrhs, nrun
189  DOUBLE PRECISION ainvnm, anorm, rcond, rcondc, rcondi, rcondo,
190  $ scale
191 * ..
192 * .. Local Arrays ..
193  CHARACTER transs( ntran ), uplos( 2 )
194  INTEGER iseed( 4 ), iseedy( 4 )
195  DOUBLE PRECISION result( ntests )
196 * ..
197 * .. External Functions ..
198  LOGICAL lsame
199  DOUBLE PRECISION zlantp
200  EXTERNAL lsame, zlantp
201 * ..
202 * .. External Subroutines ..
203  EXTERNAL alaerh, alahd, alasum, zcopy, zerrtr, zget04,
206  $ ztptrs
207 * ..
208 * .. Scalars in Common ..
209  LOGICAL lerr, ok
210  CHARACTER*32 srnamt
211  INTEGER infot, iounit
212 * ..
213 * .. Common blocks ..
214  common / infoc / infot, iounit, ok, lerr
215  common / srnamc / srnamt
216 * ..
217 * .. Intrinsic Functions ..
218  INTRINSIC max
219 * ..
220 * .. Data statements ..
221  DATA iseedy / 1988, 1989, 1990, 1991 /
222  DATA uplos / 'U', 'L' / , transs / 'N', 'T', 'C' /
223 * ..
224 * .. Executable Statements ..
225 *
226 * Initialize constants and the random number seed.
227 *
228  path( 1: 1 ) = 'Zomplex precision'
229  path( 2: 3 ) = 'TP'
230  nrun = 0
231  nfail = 0
232  nerrs = 0
233  DO 10 i = 1, 4
234  iseed( i ) = iseedy( i )
235  10 continue
236 *
237 * Test the error exits
238 *
239  IF( tsterr )
240  $ CALL zerrtr( path, nout )
241  infot = 0
242 *
243  DO 110 in = 1, nn
244 *
245 * Do for each value of N in NVAL
246 *
247  n = nval( in )
248  lda = max( 1, n )
249  lap = lda*( lda+1 ) / 2
250  xtype = 'N'
251 *
252  DO 70 imat = 1, ntype1
253 *
254 * Do the tests only if DOTYPE( IMAT ) is true.
255 *
256  IF( .NOT.dotype( imat ) )
257  $ go to 70
258 *
259  DO 60 iuplo = 1, 2
260 *
261 * Do first for UPLO = 'U', then for UPLO = 'L'
262 *
263  uplo = uplos( iuplo )
264 *
265 * Call ZLATTP to generate a triangular test matrix.
266 *
267  srnamt = 'ZLATTP'
268  CALL zlattp( imat, uplo, 'No transpose', diag, iseed, n,
269  $ ap, x, work, rwork, info )
270 *
271 * Set IDIAG = 1 for non-unit matrices, 2 for unit.
272 *
273  IF( lsame( diag, 'N' ) ) THEN
274  idiag = 1
275  ELSE
276  idiag = 2
277  END IF
278 *
279 *+ TEST 1
280 * Form the inverse of A.
281 *
282  IF( n.GT.0 )
283  $ CALL zcopy( lap, ap, 1, ainvp, 1 )
284  srnamt = 'ZTPTRI'
285  CALL ztptri( uplo, diag, n, ainvp, info )
286 *
287 * Check error code from ZTPTRI.
288 *
289  IF( info.NE.0 )
290  $ CALL alaerh( path, 'ZTPTRI', info, 0, uplo // diag, n,
291  $ n, -1, -1, -1, imat, nfail, nerrs, nout )
292 *
293 * Compute the infinity-norm condition number of A.
294 *
295  anorm = zlantp( 'I', uplo, diag, n, ap, rwork )
296  ainvnm = zlantp( 'I', uplo, diag, n, ainvp, rwork )
297  IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
298  rcondi = one
299  ELSE
300  rcondi = ( one / anorm ) / ainvnm
301  END IF
302 *
303 * Compute the residual for the triangular matrix times its
304 * inverse. Also compute the 1-norm condition number of A.
305 *
306  CALL ztpt01( uplo, diag, n, ap, ainvp, rcondo, rwork,
307  $ result( 1 ) )
308 *
309 * Print the test ratio if it is .GE. THRESH.
310 *
311  IF( result( 1 ).GE.thresh ) THEN
312  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
313  $ CALL alahd( nout, path )
314  WRITE( nout, fmt = 9999 )uplo, diag, n, imat, 1,
315  $ result( 1 )
316  nfail = nfail + 1
317  END IF
318  nrun = nrun + 1
319 *
320  DO 40 irhs = 1, nns
321  nrhs = nsval( irhs )
322  xtype = 'N'
323 *
324  DO 30 itran = 1, ntran
325 *
326 * Do for op(A) = A, A**T, or A**H.
327 *
328  trans = transs( itran )
329  IF( itran.EQ.1 ) THEN
330  norm = 'O'
331  rcondc = rcondo
332  ELSE
333  norm = 'I'
334  rcondc = rcondi
335  END IF
336 *
337 *+ TEST 2
338 * Solve and compute residual for op(A)*x = b.
339 *
340  srnamt = 'ZLARHS'
341  CALL zlarhs( path, xtype, uplo, trans, n, n, 0,
342  $ idiag, nrhs, ap, lap, xact, lda, b,
343  $ lda, iseed, info )
344  xtype = 'C'
345  CALL zlacpy( 'Full', n, nrhs, b, lda, x, lda )
346 *
347  srnamt = 'ZTPTRS'
348  CALL ztptrs( uplo, trans, diag, n, nrhs, ap, x,
349  $ lda, info )
350 *
351 * Check error code from ZTPTRS.
352 *
353  IF( info.NE.0 )
354  $ CALL alaerh( path, 'ZTPTRS', info, 0,
355  $ uplo // trans // diag, n, n, -1,
356  $ -1, -1, imat, nfail, nerrs, nout )
357 *
358  CALL ztpt02( uplo, trans, diag, n, nrhs, ap, x,
359  $ lda, b, lda, work, rwork,
360  $ result( 2 ) )
361 *
362 *+ TEST 3
363 * Check solution from generated exact solution.
364 *
365  CALL zget04( n, nrhs, x, lda, xact, lda, rcondc,
366  $ result( 3 ) )
367 *
368 *+ TESTS 4, 5, and 6
369 * Use iterative refinement to improve the solution and
370 * compute error bounds.
371 *
372  srnamt = 'ZTPRFS'
373  CALL ztprfs( uplo, trans, diag, n, nrhs, ap, b,
374  $ lda, x, lda, rwork, rwork( nrhs+1 ),
375  $ work, rwork( 2*nrhs+1 ), info )
376 *
377 * Check error code from ZTPRFS.
378 *
379  IF( info.NE.0 )
380  $ CALL alaerh( path, 'ZTPRFS', info, 0,
381  $ uplo // trans // diag, n, n, -1,
382  $ -1, nrhs, imat, nfail, nerrs,
383  $ nout )
384 *
385  CALL zget04( n, nrhs, x, lda, xact, lda, rcondc,
386  $ result( 4 ) )
387  CALL ztpt05( uplo, trans, diag, n, nrhs, ap, b,
388  $ lda, x, lda, xact, lda, rwork,
389  $ rwork( nrhs+1 ), result( 5 ) )
390 *
391 * Print information about the tests that did not pass
392 * the threshold.
393 *
394  DO 20 k = 2, 6
395  IF( result( k ).GE.thresh ) THEN
396  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
397  $ CALL alahd( nout, path )
398  WRITE( nout, fmt = 9998 )uplo, trans, diag,
399  $ n, nrhs, imat, k, result( k )
400  nfail = nfail + 1
401  END IF
402  20 continue
403  nrun = nrun + 5
404  30 continue
405  40 continue
406 *
407 *+ TEST 7
408 * Get an estimate of RCOND = 1/CNDNUM.
409 *
410  DO 50 itran = 1, 2
411  IF( itran.EQ.1 ) THEN
412  norm = 'O'
413  rcondc = rcondo
414  ELSE
415  norm = 'I'
416  rcondc = rcondi
417  END IF
418  srnamt = 'ZTPCON'
419  CALL ztpcon( norm, uplo, diag, n, ap, rcond, work,
420  $ rwork, info )
421 *
422 * Check error code from ZTPCON.
423 *
424  IF( info.NE.0 )
425  $ CALL alaerh( path, 'ZTPCON', info, 0,
426  $ norm // uplo // diag, n, n, -1, -1,
427  $ -1, imat, nfail, nerrs, nout )
428 *
429  CALL ztpt06( rcond, rcondc, uplo, diag, n, ap, rwork,
430  $ result( 7 ) )
431 *
432 * Print the test ratio if it is .GE. THRESH.
433 *
434  IF( result( 7 ).GE.thresh ) THEN
435  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
436  $ CALL alahd( nout, path )
437  WRITE( nout, fmt = 9997 ) 'ZTPCON', norm, uplo,
438  $ diag, n, imat, 7, result( 7 )
439  nfail = nfail + 1
440  END IF
441  nrun = nrun + 1
442  50 continue
443  60 continue
444  70 continue
445 *
446 * Use pathological test matrices to test ZLATPS.
447 *
448  DO 100 imat = ntype1 + 1, ntypes
449 *
450 * Do the tests only if DOTYPE( IMAT ) is true.
451 *
452  IF( .NOT.dotype( imat ) )
453  $ go to 100
454 *
455  DO 90 iuplo = 1, 2
456 *
457 * Do first for UPLO = 'U', then for UPLO = 'L'
458 *
459  uplo = uplos( iuplo )
460  DO 80 itran = 1, ntran
461 *
462 * Do for op(A) = A, A**T, or A**H.
463 *
464  trans = transs( itran )
465 *
466 * Call ZLATTP to generate a triangular test matrix.
467 *
468  srnamt = 'ZLATTP'
469  CALL zlattp( imat, uplo, trans, diag, iseed, n, ap, x,
470  $ work, rwork, info )
471 *
472 *+ TEST 8
473 * Solve the system op(A)*x = b.
474 *
475  srnamt = 'ZLATPS'
476  CALL zcopy( n, x, 1, b, 1 )
477  CALL zlatps( uplo, trans, diag, 'N', n, ap, b, scale,
478  $ rwork, info )
479 *
480 * Check error code from ZLATPS.
481 *
482  IF( info.NE.0 )
483  $ CALL alaerh( path, 'ZLATPS', info, 0,
484  $ uplo // trans // diag // 'N', n, n,
485  $ -1, -1, -1, imat, nfail, nerrs, nout )
486 *
487  CALL ztpt03( uplo, trans, diag, n, 1, ap, scale,
488  $ rwork, one, b, lda, x, lda, work,
489  $ result( 8 ) )
490 *
491 *+ TEST 9
492 * Solve op(A)*x = b again with NORMIN = 'Y'.
493 *
494  CALL zcopy( n, x, 1, b( n+1 ), 1 )
495  CALL zlatps( uplo, trans, diag, 'Y', n, ap, b( n+1 ),
496  $ scale, rwork, info )
497 *
498 * Check error code from ZLATPS.
499 *
500  IF( info.NE.0 )
501  $ CALL alaerh( path, 'ZLATPS', info, 0,
502  $ uplo // trans // diag // 'Y', n, n,
503  $ -1, -1, -1, imat, nfail, nerrs, nout )
504 *
505  CALL ztpt03( uplo, trans, diag, n, 1, ap, scale,
506  $ rwork, one, b( n+1 ), lda, x, lda, work,
507  $ result( 9 ) )
508 *
509 * Print information about the tests that did not pass
510 * the threshold.
511 *
512  IF( result( 8 ).GE.thresh ) THEN
513  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
514  $ CALL alahd( nout, path )
515  WRITE( nout, fmt = 9996 )'ZLATPS', uplo, trans,
516  $ diag, 'N', n, imat, 8, result( 8 )
517  nfail = nfail + 1
518  END IF
519  IF( result( 9 ).GE.thresh ) THEN
520  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
521  $ CALL alahd( nout, path )
522  WRITE( nout, fmt = 9996 )'ZLATPS', uplo, trans,
523  $ diag, 'Y', n, imat, 9, result( 9 )
524  nfail = nfail + 1
525  END IF
526  nrun = nrun + 2
527  80 continue
528  90 continue
529  100 continue
530  110 continue
531 *
532 * Print a summary of the results.
533 *
534  CALL alasum( path, nout, nfail, nrun, nerrs )
535 *
536  9999 format( ' UPLO=''', a1, ''', DIAG=''', a1, ''', N=', i5,
537  $ ', type ', i2, ', test(', i2, ')= ', g12.5 )
538  9998 format( ' UPLO=''', a1, ''', TRANS=''', a1, ''', DIAG=''', a1,
539  $ ''', N=', i5, ''', NRHS=', i5, ', type ', i2, ', test(',
540  $ i2, ')= ', g12.5 )
541  9997 format( 1x, a, '( ''', a1, ''', ''', a1, ''', ''', a1, ''',',
542  $ i5, ', ... ), type ', i2, ', test(', i2, ')=', g12.5 )
543  9996 format( 1x, a, '( ''', a1, ''', ''', a1, ''', ''', a1, ''', ''',
544  $ a1, ''',', i5, ', ... ), type ', i2, ', test(', i2, ')=',
545  $ g12.5 )
546  return
547 *
548 * End of ZCHKTP
549 *
550  END