LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
cchkpo.f
Go to the documentation of this file.
1 *> \brief \b CCHKPO
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 CCHKPO( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
12 * THRESH, TSTERR, NMAX, A, AFAC, AINV, B, X,
13 * XACT, WORK, RWORK, NOUT )
14 *
15 * .. Scalar Arguments ..
16 * LOGICAL TSTERR
17 * INTEGER NMAX, NN, NNB, NNS, NOUT
18 * REAL THRESH
19 * ..
20 * .. Array Arguments ..
21 * LOGICAL DOTYPE( * )
22 * INTEGER NBVAL( * ), NSVAL( * ), NVAL( * )
23 * REAL RWORK( * )
24 * COMPLEX A( * ), AFAC( * ), AINV( * ), B( * ),
25 * $ WORK( * ), X( * ), XACT( * )
26 * ..
27 *
28 *
29 *> \par Purpose:
30 * =============
31 *>
32 *> \verbatim
33 *>
34 *> CCHKPO tests CPOTRF, -TRI, -TRS, -RFS, and -CON
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 dimension N.
58 *> \endverbatim
59 *>
60 *> \param[in] NNB
61 *> \verbatim
62 *> NNB is INTEGER
63 *> The number of values of NB contained in the vector NBVAL.
64 *> \endverbatim
65 *>
66 *> \param[in] NBVAL
67 *> \verbatim
68 *> NBVAL is INTEGER array, dimension (NBVAL)
69 *> The values of the blocksize NB.
70 *> \endverbatim
71 *>
72 *> \param[in] NNS
73 *> \verbatim
74 *> NNS is INTEGER
75 *> The number of values of NRHS contained in the vector NSVAL.
76 *> \endverbatim
77 *>
78 *> \param[in] NSVAL
79 *> \verbatim
80 *> NSVAL is INTEGER array, dimension (NNS)
81 *> The values of the number of right hand sides NRHS.
82 *> \endverbatim
83 *>
84 *> \param[in] THRESH
85 *> \verbatim
86 *> THRESH is REAL
87 *> The threshold value for the test ratios. A result is
88 *> included in the output file if RESULT >= THRESH. To have
89 *> every test ratio printed, use THRESH = 0.
90 *> \endverbatim
91 *>
92 *> \param[in] TSTERR
93 *> \verbatim
94 *> TSTERR is LOGICAL
95 *> Flag that indicates whether error exits are to be tested.
96 *> \endverbatim
97 *>
98 *> \param[in] NMAX
99 *> \verbatim
100 *> NMAX is INTEGER
101 *> The maximum value permitted for N, used in dimensioning the
102 *> work arrays.
103 *> \endverbatim
104 *>
105 *> \param[out] A
106 *> \verbatim
107 *> A is COMPLEX array, dimension (NMAX*NMAX)
108 *> \endverbatim
109 *>
110 *> \param[out] AFAC
111 *> \verbatim
112 *> AFAC is COMPLEX array, dimension (NMAX*NMAX)
113 *> \endverbatim
114 *>
115 *> \param[out] AINV
116 *> \verbatim
117 *> AINV is COMPLEX array, dimension (NMAX*NMAX)
118 *> \endverbatim
119 *>
120 *> \param[out] B
121 *> \verbatim
122 *> B is COMPLEX array, dimension (NMAX*NSMAX)
123 *> where NSMAX is the largest entry in NSVAL.
124 *> \endverbatim
125 *>
126 *> \param[out] X
127 *> \verbatim
128 *> X is COMPLEX array, dimension (NMAX*NSMAX)
129 *> \endverbatim
130 *>
131 *> \param[out] XACT
132 *> \verbatim
133 *> XACT is COMPLEX array, dimension (NMAX*NSMAX)
134 *> \endverbatim
135 *>
136 *> \param[out] WORK
137 *> \verbatim
138 *> WORK is COMPLEX array, dimension
139 *> (NMAX*max(3,NSMAX))
140 *> \endverbatim
141 *>
142 *> \param[out] RWORK
143 *> \verbatim
144 *> RWORK is REAL array, dimension
145 *> (NMAX+2*NSMAX)
146 *> \endverbatim
147 *>
148 *> \param[in] NOUT
149 *> \verbatim
150 *> NOUT is INTEGER
151 *> The unit number for output.
152 *> \endverbatim
153 *
154 * Authors:
155 * ========
156 *
157 *> \author Univ. of Tennessee
158 *> \author Univ. of California Berkeley
159 *> \author Univ. of Colorado Denver
160 *> \author NAG Ltd.
161 *
162 *> \date November 2011
163 *
164 *> \ingroup complex_lin
165 *
166 * =====================================================================
167  SUBROUTINE cchkpo( DOTYPE, NN, NVAL, NNB, NBVAL, NNS, NSVAL,
168  $ thresh, tsterr, nmax, a, afac, ainv, b, x,
169  $ xact, work, rwork, nout )
170 *
171 * -- LAPACK test routine (version 3.4.0) --
172 * -- LAPACK is a software package provided by Univ. of Tennessee, --
173 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
174 * November 2011
175 *
176 * .. Scalar Arguments ..
177  LOGICAL tsterr
178  INTEGER nmax, nn, nnb, nns, nout
179  REAL thresh
180 * ..
181 * .. Array Arguments ..
182  LOGICAL dotype( * )
183  INTEGER nbval( * ), nsval( * ), nval( * )
184  REAL rwork( * )
185  COMPLEX a( * ), afac( * ), ainv( * ), b( * ),
186  $ work( * ), x( * ), xact( * )
187 * ..
188 *
189 * =====================================================================
190 *
191 * .. Parameters ..
192  COMPLEX czero
193  parameter( czero = ( 0.0e+0, 0.0e+0 ) )
194  INTEGER ntypes
195  parameter( ntypes = 9 )
196  INTEGER ntests
197  parameter( ntests = 8 )
198 * ..
199 * .. Local Scalars ..
200  LOGICAL zerot
201  CHARACTER dist, type, uplo, xtype
202  CHARACTER*3 path
203  INTEGER i, imat, in, inb, info, ioff, irhs, iuplo,
204  $ izero, k, kl, ku, lda, mode, n, nb, nerrs,
205  $ nfail, nimat, nrhs, nrun
206  REAL anorm, cndnum, rcond, rcondc
207 * ..
208 * .. Local Arrays ..
209  CHARACTER uplos( 2 )
210  INTEGER iseed( 4 ), iseedy( 4 )
211  REAL result( ntests )
212 * ..
213 * .. External Functions ..
214  REAL clanhe, sget06
215  EXTERNAL clanhe, sget06
216 * ..
217 * .. External Subroutines ..
218  EXTERNAL alaerh, alahd, alasum, cerrpo, cget04, clacpy,
221  $ cpotrs, xlaenv
222 * ..
223 * .. Scalars in Common ..
224  LOGICAL lerr, ok
225  CHARACTER*32 srnamt
226  INTEGER infot, nunit
227 * ..
228 * .. Common blocks ..
229  common / infoc / infot, nunit, ok, lerr
230  common / srnamc / srnamt
231 * ..
232 * .. Intrinsic Functions ..
233  INTRINSIC max
234 * ..
235 * .. Data statements ..
236  DATA iseedy / 1988, 1989, 1990, 1991 /
237  DATA uplos / 'U', 'L' /
238 * ..
239 * .. Executable Statements ..
240 *
241 * Initialize constants and the random number seed.
242 *
243  path( 1: 1 ) = 'Complex precision'
244  path( 2: 3 ) = 'PO'
245  nrun = 0
246  nfail = 0
247  nerrs = 0
248  DO 10 i = 1, 4
249  iseed( i ) = iseedy( i )
250  10 continue
251 *
252 * Test the error exits
253 *
254  IF( tsterr )
255  $ CALL cerrpo( path, nout )
256  infot = 0
257 *
258 * Do for each value of N in NVAL
259 *
260  DO 120 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  izero = 0
269  DO 110 imat = 1, nimat
270 *
271 * Do the tests only if DOTYPE( IMAT ) is true.
272 *
273  IF( .NOT.dotype( imat ) )
274  $ go to 110
275 *
276 * Skip types 3, 4, or 5 if the matrix size is too small.
277 *
278  zerot = imat.GE.3 .AND. imat.LE.5
279  IF( zerot .AND. n.LT.imat-2 )
280  $ go to 110
281 *
282 * Do first for UPLO = 'U', then for UPLO = 'L'
283 *
284  DO 100 iuplo = 1, 2
285  uplo = uplos( iuplo )
286 *
287 * Set up parameters with CLATB4 and generate a test matrix
288 * with CLATMS.
289 *
290  CALL clatb4( path, imat, n, n, type, kl, ku, anorm, mode,
291  $ cndnum, dist )
292 *
293  srnamt = 'CLATMS'
294  CALL clatms( n, n, dist, iseed, type, rwork, mode,
295  $ cndnum, anorm, kl, ku, uplo, a, lda, work,
296  $ info )
297 *
298 * Check error code from CLATMS.
299 *
300  IF( info.NE.0 ) THEN
301  CALL alaerh( path, 'CLATMS', info, 0, uplo, n, n, -1,
302  $ -1, -1, imat, nfail, nerrs, nout )
303  go to 100
304  END IF
305 *
306 * For types 3-5, zero one row and column of the matrix to
307 * test that INFO is returned correctly.
308 *
309  IF( zerot ) THEN
310  IF( imat.EQ.3 ) THEN
311  izero = 1
312  ELSE IF( imat.EQ.4 ) THEN
313  izero = n
314  ELSE
315  izero = n / 2 + 1
316  END IF
317  ioff = ( izero-1 )*lda
318 *
319 * Set row and column IZERO of A to 0.
320 *
321  IF( iuplo.EQ.1 ) THEN
322  DO 20 i = 1, izero - 1
323  a( ioff+i ) = czero
324  20 continue
325  ioff = ioff + izero
326  DO 30 i = izero, n
327  a( ioff ) = czero
328  ioff = ioff + lda
329  30 continue
330  ELSE
331  ioff = izero
332  DO 40 i = 1, izero - 1
333  a( ioff ) = czero
334  ioff = ioff + lda
335  40 continue
336  ioff = ioff - izero
337  DO 50 i = izero, n
338  a( ioff+i ) = czero
339  50 continue
340  END IF
341  ELSE
342  izero = 0
343  END IF
344 *
345 * Set the imaginary part of the diagonals.
346 *
347  CALL claipd( n, a, lda+1, 0 )
348 *
349 * Do for each value of NB in NBVAL
350 *
351  DO 90 inb = 1, nnb
352  nb = nbval( inb )
353  CALL xlaenv( 1, nb )
354 *
355 * Compute the L*L' or U'*U factorization of the matrix.
356 *
357  CALL clacpy( uplo, n, n, a, lda, afac, lda )
358  srnamt = 'CPOTRF'
359  CALL cpotrf( uplo, n, afac, lda, info )
360 *
361 * Check error code from CPOTRF.
362 *
363  IF( info.NE.izero ) THEN
364  CALL alaerh( path, 'CPOTRF', info, izero, uplo, n,
365  $ n, -1, -1, nb, imat, nfail, nerrs,
366  $ nout )
367  go to 90
368  END IF
369 *
370 * Skip the tests if INFO is not 0.
371 *
372  IF( info.NE.0 )
373  $ go to 90
374 *
375 *+ TEST 1
376 * Reconstruct matrix from factors and compute residual.
377 *
378  CALL clacpy( uplo, n, n, afac, lda, ainv, lda )
379  CALL cpot01( uplo, n, a, lda, ainv, lda, rwork,
380  $ result( 1 ) )
381 *
382 *+ TEST 2
383 * Form the inverse and compute the residual.
384 *
385  CALL clacpy( uplo, n, n, afac, lda, ainv, lda )
386  srnamt = 'CPOTRI'
387  CALL cpotri( uplo, n, ainv, lda, info )
388 *
389 * Check error code from CPOTRI.
390 *
391  IF( info.NE.0 )
392  $ CALL alaerh( path, 'CPOTRI', info, 0, uplo, n, n,
393  $ -1, -1, -1, imat, nfail, nerrs, nout )
394 *
395  CALL cpot03( uplo, n, a, lda, ainv, lda, work, lda,
396  $ rwork, rcondc, result( 2 ) )
397 *
398 * Print information about the tests that did not pass
399 * the threshold.
400 *
401  DO 60 k = 1, 2
402  IF( result( k ).GE.thresh ) THEN
403  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
404  $ CALL alahd( nout, path )
405  WRITE( nout, fmt = 9999 )uplo, n, nb, imat, k,
406  $ result( k )
407  nfail = nfail + 1
408  END IF
409  60 continue
410  nrun = nrun + 2
411 *
412 * Skip the rest of the tests unless this is the first
413 * blocksize.
414 *
415  IF( inb.NE.1 )
416  $ go to 90
417 *
418  DO 80 irhs = 1, nns
419  nrhs = nsval( irhs )
420 *
421 *+ TEST 3
422 * Solve and compute residual for A * X = B .
423 *
424  srnamt = 'CLARHS'
425  CALL clarhs( path, xtype, uplo, ' ', n, n, kl, ku,
426  $ nrhs, a, lda, xact, lda, b, lda,
427  $ iseed, info )
428  CALL clacpy( 'Full', n, nrhs, b, lda, x, lda )
429 *
430  srnamt = 'CPOTRS'
431  CALL cpotrs( uplo, n, nrhs, afac, lda, x, lda,
432  $ info )
433 *
434 * Check error code from CPOTRS.
435 *
436  IF( info.NE.0 )
437  $ CALL alaerh( path, 'CPOTRS', info, 0, uplo, n,
438  $ n, -1, -1, nrhs, imat, nfail,
439  $ nerrs, nout )
440 *
441  CALL clacpy( 'Full', n, nrhs, b, lda, work, lda )
442  CALL cpot02( uplo, n, nrhs, a, lda, x, lda, work,
443  $ lda, rwork, result( 3 ) )
444 *
445 *+ TEST 4
446 * Check solution from generated exact solution.
447 *
448  CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
449  $ result( 4 ) )
450 *
451 *+ TESTS 5, 6, and 7
452 * Use iterative refinement to improve the solution.
453 *
454  srnamt = 'CPORFS'
455  CALL cporfs( uplo, n, nrhs, a, lda, afac, lda, b,
456  $ lda, x, lda, rwork, rwork( nrhs+1 ),
457  $ work, rwork( 2*nrhs+1 ), info )
458 *
459 * Check error code from CPORFS.
460 *
461  IF( info.NE.0 )
462  $ CALL alaerh( path, 'CPORFS', info, 0, uplo, n,
463  $ n, -1, -1, nrhs, imat, nfail,
464  $ nerrs, nout )
465 *
466  CALL cget04( n, nrhs, x, lda, xact, lda, rcondc,
467  $ result( 5 ) )
468  CALL cpot05( uplo, n, nrhs, a, lda, b, lda, x, lda,
469  $ xact, lda, rwork, rwork( nrhs+1 ),
470  $ result( 6 ) )
471 *
472 * Print information about the tests that did not pass
473 * the threshold.
474 *
475  DO 70 k = 3, 7
476  IF( result( k ).GE.thresh ) THEN
477  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
478  $ CALL alahd( nout, path )
479  WRITE( nout, fmt = 9998 )uplo, n, nrhs,
480  $ imat, k, result( k )
481  nfail = nfail + 1
482  END IF
483  70 continue
484  nrun = nrun + 5
485  80 continue
486 *
487 *+ TEST 8
488 * Get an estimate of RCOND = 1/CNDNUM.
489 *
490  anorm = clanhe( '1', uplo, n, a, lda, rwork )
491  srnamt = 'CPOCON'
492  CALL cpocon( uplo, n, afac, lda, anorm, rcond, work,
493  $ rwork, info )
494 *
495 * Check error code from CPOCON.
496 *
497  IF( info.NE.0 )
498  $ CALL alaerh( path, 'CPOCON', info, 0, uplo, n, n,
499  $ -1, -1, -1, imat, nfail, nerrs, nout )
500 *
501  result( 8 ) = sget06( rcond, rcondc )
502 *
503 * Print the test ratio if it is .GE. THRESH.
504 *
505  IF( result( 8 ).GE.thresh ) THEN
506  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
507  $ CALL alahd( nout, path )
508  WRITE( nout, fmt = 9997 )uplo, n, imat, 8,
509  $ result( 8 )
510  nfail = nfail + 1
511  END IF
512  nrun = nrun + 1
513  90 continue
514  100 continue
515  110 continue
516  120 continue
517 *
518 * Print a summary of the results.
519 *
520  CALL alasum( path, nout, nfail, nrun, nerrs )
521 *
522  9999 format( ' UPLO = ''', a1, ''', N =', i5, ', NB =', i4, ', type ',
523  $ i2, ', test ', i2, ', ratio =', g12.5 )
524  9998 format( ' UPLO = ''', a1, ''', N =', i5, ', NRHS=', i3, ', type ',
525  $ i2, ', test(', i2, ') =', g12.5 )
526  9997 format( ' UPLO = ''', a1, ''', N =', i5, ',', 10x, ' type ', i2,
527  $ ', test(', i2, ') =', g12.5 )
528  return
529 *
530 * End of CCHKPO
531 *
532  END