LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
cchkpt.f
Go to the documentation of this file.
1 *> \brief \b CCHKPT
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 CCHKPT( DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR,
12 * A, D, E, B, X, XACT, WORK, RWORK, NOUT )
13 *
14 * .. Scalar Arguments ..
15 * LOGICAL TSTERR
16 * INTEGER NN, NNS, NOUT
17 * REAL THRESH
18 * ..
19 * .. Array Arguments ..
20 * LOGICAL DOTYPE( * )
21 * INTEGER NSVAL( * ), NVAL( * )
22 * REAL D( * ), RWORK( * )
23 * COMPLEX A( * ), B( * ), E( * ), WORK( * ), X( * ),
24 * $ XACT( * )
25 * ..
26 *
27 *
28 *> \par Purpose:
29 * =============
30 *>
31 *> \verbatim
32 *>
33 *> CCHKPT tests CPTTRF, -TRS, -RFS, and -CON
34 *> \endverbatim
35 *
36 * Arguments:
37 * ==========
38 *
39 *> \param[in] DOTYPE
40 *> \verbatim
41 *> DOTYPE is LOGICAL array, dimension (NTYPES)
42 *> The matrix types to be used for testing. Matrices of type j
43 *> (for 1 <= j <= NTYPES) are used for testing if DOTYPE(j) =
44 *> .TRUE.; if DOTYPE(j) = .FALSE., then type j is not used.
45 *> \endverbatim
46 *>
47 *> \param[in] NN
48 *> \verbatim
49 *> NN is INTEGER
50 *> The number of values of N contained in the vector NVAL.
51 *> \endverbatim
52 *>
53 *> \param[in] NVAL
54 *> \verbatim
55 *> NVAL is INTEGER array, dimension (NN)
56 *> The values of the matrix dimension N.
57 *> \endverbatim
58 *>
59 *> \param[in] NNS
60 *> \verbatim
61 *> NNS is INTEGER
62 *> The number of values of NRHS contained in the vector NSVAL.
63 *> \endverbatim
64 *>
65 *> \param[in] NSVAL
66 *> \verbatim
67 *> NSVAL is INTEGER array, dimension (NNS)
68 *> The values of the number of right hand sides NRHS.
69 *> \endverbatim
70 *>
71 *> \param[in] THRESH
72 *> \verbatim
73 *> THRESH is REAL
74 *> The threshold value for the test ratios. A result is
75 *> included in the output file if RESULT >= THRESH. To have
76 *> every test ratio printed, use THRESH = 0.
77 *> \endverbatim
78 *>
79 *> \param[in] TSTERR
80 *> \verbatim
81 *> TSTERR is LOGICAL
82 *> Flag that indicates whether error exits are to be tested.
83 *> \endverbatim
84 *>
85 *> \param[out] A
86 *> \verbatim
87 *> A is COMPLEX array, dimension (NMAX*2)
88 *> \endverbatim
89 *>
90 *> \param[out] D
91 *> \verbatim
92 *> D is REAL array, dimension (NMAX*2)
93 *> \endverbatim
94 *>
95 *> \param[out] E
96 *> \verbatim
97 *> E is COMPLEX array, dimension (NMAX*2)
98 *> \endverbatim
99 *>
100 *> \param[out] B
101 *> \verbatim
102 *> B is COMPLEX array, dimension (NMAX*NSMAX)
103 *> where NSMAX is the largest entry in NSVAL.
104 *> \endverbatim
105 *>
106 *> \param[out] X
107 *> \verbatim
108 *> X is COMPLEX array, dimension (NMAX*NSMAX)
109 *> \endverbatim
110 *>
111 *> \param[out] XACT
112 *> \verbatim
113 *> XACT is COMPLEX array, dimension (NMAX*NSMAX)
114 *> \endverbatim
115 *>
116 *> \param[out] WORK
117 *> \verbatim
118 *> WORK is COMPLEX array, dimension
119 *> (NMAX*max(3,NSMAX))
120 *> \endverbatim
121 *>
122 *> \param[out] RWORK
123 *> \verbatim
124 *> RWORK is REAL array, dimension
125 *> (max(NMAX,2*NSMAX))
126 *> \endverbatim
127 *>
128 *> \param[in] NOUT
129 *> \verbatim
130 *> NOUT is INTEGER
131 *> The unit number for output.
132 *> \endverbatim
133 *
134 * Authors:
135 * ========
136 *
137 *> \author Univ. of Tennessee
138 *> \author Univ. of California Berkeley
139 *> \author Univ. of Colorado Denver
140 *> \author NAG Ltd.
141 *
142 *> \date November 2011
143 *
144 *> \ingroup complex_lin
145 *
146 * =====================================================================
147  SUBROUTINE cchkpt( DOTYPE, NN, NVAL, NNS, NSVAL, THRESH, TSTERR,
148  $ a, d, e, b, x, xact, work, rwork, nout )
149 *
150 * -- LAPACK test routine (version 3.4.0) --
151 * -- LAPACK is a software package provided by Univ. of Tennessee, --
152 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153 * November 2011
154 *
155 * .. Scalar Arguments ..
156  LOGICAL tsterr
157  INTEGER nn, nns, nout
158  REAL thresh
159 * ..
160 * .. Array Arguments ..
161  LOGICAL dotype( * )
162  INTEGER nsval( * ), nval( * )
163  REAL d( * ), rwork( * )
164  COMPLEX a( * ), b( * ), e( * ), work( * ), x( * ),
165  $ xact( * )
166 * ..
167 *
168 * =====================================================================
169 *
170 * .. Parameters ..
171  REAL one, zero
172  parameter( one = 1.0e+0, zero = 0.0e+0 )
173  INTEGER ntypes
174  parameter( ntypes = 12 )
175  INTEGER ntests
176  parameter( ntests = 7 )
177 * ..
178 * .. Local Scalars ..
179  LOGICAL zerot
180  CHARACTER dist, type, uplo
181  CHARACTER*3 path
182  INTEGER i, ia, imat, in, info, irhs, iuplo, ix, izero,
183  $ j, k, kl, ku, lda, mode, n, nerrs, nfail,
184  $ nimat, nrhs, nrun
185  REAL ainvnm, anorm, cond, dmax, rcond, rcondc
186 * ..
187 * .. Local Arrays ..
188  CHARACTER uplos( 2 )
189  INTEGER iseed( 4 ), iseedy( 4 )
190  REAL result( ntests )
191  COMPLEX z( 3 )
192 * ..
193 * .. External Functions ..
194  INTEGER isamax
195  REAL clanht, scasum, sget06
196  EXTERNAL isamax, clanht, scasum, sget06
197 * ..
198 * .. External Subroutines ..
199  EXTERNAL alaerh, alahd, alasum, ccopy, cerrgt, cget04,
202  $ csscal, scopy, slarnv, sscal
203 * ..
204 * .. Intrinsic Functions ..
205  INTRINSIC abs, max, real
206 * ..
207 * .. Scalars in Common ..
208  LOGICAL lerr, ok
209  CHARACTER*32 srnamt
210  INTEGER infot, nunit
211 * ..
212 * .. Common blocks ..
213  common / infoc / infot, nunit, ok, lerr
214  common / srnamc / srnamt
215 * ..
216 * .. Data statements ..
217  DATA iseedy / 0, 0, 0, 1 / , uplos / 'U', 'L' /
218 * ..
219 * .. Executable Statements ..
220 *
221  path( 1: 1 ) = 'Complex precision'
222  path( 2: 3 ) = 'PT'
223  nrun = 0
224  nfail = 0
225  nerrs = 0
226  DO 10 i = 1, 4
227  iseed( i ) = iseedy( i )
228  10 continue
229 *
230 * Test the error exits
231 *
232  IF( tsterr )
233  $ CALL cerrgt( path, nout )
234  infot = 0
235 *
236  DO 120 in = 1, nn
237 *
238 * Do for each value of N in NVAL.
239 *
240  n = nval( in )
241  lda = max( 1, n )
242  nimat = ntypes
243  IF( n.LE.0 )
244  $ nimat = 1
245 *
246  DO 110 imat = 1, nimat
247 *
248 * Do the tests only if DOTYPE( IMAT ) is true.
249 *
250  IF( n.GT.0 .AND. .NOT.dotype( imat ) )
251  $ go to 110
252 *
253 * Set up parameters with CLATB4.
254 *
255  CALL clatb4( path, imat, n, n, type, kl, ku, anorm, mode,
256  $ cond, dist )
257 *
258  zerot = imat.GE.8 .AND. imat.LE.10
259  IF( imat.LE.6 ) THEN
260 *
261 * Type 1-6: generate a Hermitian tridiagonal matrix of
262 * known condition number in lower triangular band storage.
263 *
264  srnamt = 'CLATMS'
265  CALL clatms( n, n, dist, iseed, type, rwork, mode, cond,
266  $ anorm, kl, ku, 'B', a, 2, work, info )
267 *
268 * Check the error code from CLATMS.
269 *
270  IF( info.NE.0 ) THEN
271  CALL alaerh( path, 'CLATMS', info, 0, ' ', n, n, kl,
272  $ ku, -1, imat, nfail, nerrs, nout )
273  go to 110
274  END IF
275  izero = 0
276 *
277 * Copy the matrix to D and E.
278 *
279  ia = 1
280  DO 20 i = 1, n - 1
281  d( i ) = REAL( A( IA ) )
282  e( i ) = a( ia+1 )
283  ia = ia + 2
284  20 continue
285  IF( n.GT.0 )
286  $ d( n ) = REAL( A( IA ) )
287  ELSE
288 *
289 * Type 7-12: generate a diagonally dominant matrix with
290 * unknown condition number in the vectors D and E.
291 *
292  IF( .NOT.zerot .OR. .NOT.dotype( 7 ) ) THEN
293 *
294 * Let E be complex, D real, with values from [-1,1].
295 *
296  CALL slarnv( 2, iseed, n, d )
297  CALL clarnv( 2, iseed, n-1, e )
298 *
299 * Make the tridiagonal matrix diagonally dominant.
300 *
301  IF( n.EQ.1 ) THEN
302  d( 1 ) = abs( d( 1 ) )
303  ELSE
304  d( 1 ) = abs( d( 1 ) ) + abs( e( 1 ) )
305  d( n ) = abs( d( n ) ) + abs( e( n-1 ) )
306  DO 30 i = 2, n - 1
307  d( i ) = abs( d( i ) ) + abs( e( i ) ) +
308  $ abs( e( i-1 ) )
309  30 continue
310  END IF
311 *
312 * Scale D and E so the maximum element is ANORM.
313 *
314  ix = isamax( n, d, 1 )
315  dmax = d( ix )
316  CALL sscal( n, anorm / dmax, d, 1 )
317  CALL csscal( n-1, anorm / dmax, e, 1 )
318 *
319  ELSE IF( izero.GT.0 ) THEN
320 *
321 * Reuse the last matrix by copying back the zeroed out
322 * elements.
323 *
324  IF( izero.EQ.1 ) THEN
325  d( 1 ) = z( 2 )
326  IF( n.GT.1 )
327  $ e( 1 ) = z( 3 )
328  ELSE IF( izero.EQ.n ) THEN
329  e( n-1 ) = z( 1 )
330  d( n ) = z( 2 )
331  ELSE
332  e( izero-1 ) = z( 1 )
333  d( izero ) = z( 2 )
334  e( izero ) = z( 3 )
335  END IF
336  END IF
337 *
338 * For types 8-10, set one row and column of the matrix to
339 * zero.
340 *
341  izero = 0
342  IF( imat.EQ.8 ) THEN
343  izero = 1
344  z( 2 ) = d( 1 )
345  d( 1 ) = zero
346  IF( n.GT.1 ) THEN
347  z( 3 ) = e( 1 )
348  e( 1 ) = zero
349  END IF
350  ELSE IF( imat.EQ.9 ) THEN
351  izero = n
352  IF( n.GT.1 ) THEN
353  z( 1 ) = e( n-1 )
354  e( n-1 ) = zero
355  END IF
356  z( 2 ) = d( n )
357  d( n ) = zero
358  ELSE IF( imat.EQ.10 ) THEN
359  izero = ( n+1 ) / 2
360  IF( izero.GT.1 ) THEN
361  z( 1 ) = e( izero-1 )
362  z( 3 ) = e( izero )
363  e( izero-1 ) = zero
364  e( izero ) = zero
365  END IF
366  z( 2 ) = d( izero )
367  d( izero ) = zero
368  END IF
369  END IF
370 *
371  CALL scopy( n, d, 1, d( n+1 ), 1 )
372  IF( n.GT.1 )
373  $ CALL ccopy( n-1, e, 1, e( n+1 ), 1 )
374 *
375 *+ TEST 1
376 * Factor A as L*D*L' and compute the ratio
377 * norm(L*D*L' - A) / (n * norm(A) * EPS )
378 *
379  CALL cpttrf( n, d( n+1 ), e( n+1 ), info )
380 *
381 * Check error code from CPTTRF.
382 *
383  IF( info.NE.izero ) THEN
384  CALL alaerh( path, 'CPTTRF', info, izero, ' ', n, n, -1,
385  $ -1, -1, imat, nfail, nerrs, nout )
386  go to 110
387  END IF
388 *
389  IF( info.GT.0 ) THEN
390  rcondc = zero
391  go to 100
392  END IF
393 *
394  CALL cptt01( n, d, e, d( n+1 ), e( n+1 ), work,
395  $ result( 1 ) )
396 *
397 * Print the test ratio if greater than or equal to THRESH.
398 *
399  IF( result( 1 ).GE.thresh ) THEN
400  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
401  $ CALL alahd( nout, path )
402  WRITE( nout, fmt = 9999 )n, imat, 1, result( 1 )
403  nfail = nfail + 1
404  END IF
405  nrun = nrun + 1
406 *
407 * Compute RCONDC = 1 / (norm(A) * norm(inv(A))
408 *
409 * Compute norm(A).
410 *
411  anorm = clanht( '1', n, d, e )
412 *
413 * Use CPTTRS to solve for one column at a time of inv(A),
414 * computing the maximum column sum as we go.
415 *
416  ainvnm = zero
417  DO 50 i = 1, n
418  DO 40 j = 1, n
419  x( j ) = zero
420  40 continue
421  x( i ) = one
422  CALL cpttrs( 'Lower', n, 1, d( n+1 ), e( n+1 ), x, lda,
423  $ info )
424  ainvnm = max( ainvnm, scasum( n, x, 1 ) )
425  50 continue
426  rcondc = one / max( one, anorm*ainvnm )
427 *
428  DO 90 irhs = 1, nns
429  nrhs = nsval( irhs )
430 *
431 * Generate NRHS random solution vectors.
432 *
433  ix = 1
434  DO 60 j = 1, nrhs
435  CALL clarnv( 2, iseed, n, xact( ix ) )
436  ix = ix + lda
437  60 continue
438 *
439  DO 80 iuplo = 1, 2
440 *
441 * Do first for UPLO = 'U', then for UPLO = 'L'.
442 *
443  uplo = uplos( iuplo )
444 *
445 * Set the right hand side.
446 *
447  CALL claptm( uplo, n, nrhs, one, d, e, xact, lda,
448  $ zero, b, lda )
449 *
450 *+ TEST 2
451 * Solve A*x = b and compute the residual.
452 *
453  CALL clacpy( 'Full', n, nrhs, b, lda, x, lda )
454  CALL cpttrs( uplo, n, nrhs, d( n+1 ), e( n+1 ), x,
455  $ lda, info )
456 *
457 * Check error code from CPTTRS.
458 *
459  IF( info.NE.0 )
460  $ CALL alaerh( path, 'CPTTRS', info, 0, uplo, n, n,
461  $ -1, -1, nrhs, imat, nfail, nerrs,
462  $ nout )
463 *
464  CALL clacpy( 'Full', n, nrhs, b, lda, work, lda )
465  CALL cptt02( uplo, n, nrhs, d, e, x, lda, work, lda,
466  $ result( 2 ) )
467 *
468 *+ TEST 3
469 * Check solution from generated exact solution.
470 *
471  CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
472  $ result( 3 ) )
473 *
474 *+ TESTS 4, 5, and 6
475 * Use iterative refinement to improve the solution.
476 *
477  srnamt = 'CPTRFS'
478  CALL cptrfs( uplo, n, nrhs, d, e, d( n+1 ), e( n+1 ),
479  $ b, lda, x, lda, rwork, rwork( nrhs+1 ),
480  $ work, rwork( 2*nrhs+1 ), info )
481 *
482 * Check error code from CPTRFS.
483 *
484  IF( info.NE.0 )
485  $ CALL alaerh( path, 'CPTRFS', info, 0, uplo, n, n,
486  $ -1, -1, nrhs, imat, nfail, nerrs,
487  $ nout )
488 *
489  CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
490  $ result( 4 ) )
491  CALL cptt05( n, nrhs, d, e, b, lda, x, lda, xact, lda,
492  $ rwork, rwork( nrhs+1 ), result( 5 ) )
493 *
494 * Print information about the tests that did not pass the
495 * threshold.
496 *
497  DO 70 k = 2, 6
498  IF( result( k ).GE.thresh ) THEN
499  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
500  $ CALL alahd( nout, path )
501  WRITE( nout, fmt = 9998 )uplo, n, nrhs, imat,
502  $ k, result( k )
503  nfail = nfail + 1
504  END IF
505  70 continue
506  nrun = nrun + 5
507 *
508  80 continue
509  90 continue
510 *
511 *+ TEST 7
512 * Estimate the reciprocal of the condition number of the
513 * matrix.
514 *
515  100 continue
516  srnamt = 'CPTCON'
517  CALL cptcon( n, d( n+1 ), e( n+1 ), anorm, rcond, rwork,
518  $ info )
519 *
520 * Check error code from CPTCON.
521 *
522  IF( info.NE.0 )
523  $ CALL alaerh( path, 'CPTCON', info, 0, ' ', n, n, -1, -1,
524  $ -1, imat, nfail, nerrs, nout )
525 *
526  result( 7 ) = sget06( rcond, rcondc )
527 *
528 * Print the test ratio if greater than or equal to THRESH.
529 *
530  IF( result( 7 ).GE.thresh ) THEN
531  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
532  $ CALL alahd( nout, path )
533  WRITE( nout, fmt = 9999 )n, imat, 7, result( 7 )
534  nfail = nfail + 1
535  END IF
536  nrun = nrun + 1
537  110 continue
538  120 continue
539 *
540 * Print a summary of the results.
541 *
542  CALL alasum( path, nout, nfail, nrun, nerrs )
543 *
544  9999 format( ' N =', i5, ', type ', i2, ', test ', i2, ', ratio = ',
545  $ g12.5 )
546  9998 format( ' UPLO = ''', a1, ''', N =', i5, ', NRHS =', i3,
547  $ ', type ', i2, ', test ', i2, ', ratio = ', g12.5 )
548  return
549 *
550 * End of CCHKPT
551 *
552  END