LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
ddrvpo.f
Go to the documentation of this file.
1 *> \brief \b DDRVPO
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 DDRVPO( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
12 * A, AFAC, ASAV, B, BSAV, X, XACT, S, WORK,
13 * RWORK, IWORK, 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 A( * ), AFAC( * ), ASAV( * ), B( * ),
24 * $ BSAV( * ), RWORK( * ), S( * ), WORK( * ),
25 * $ X( * ), XACT( * )
26 * ..
27 *
28 *
29 *> \par Purpose:
30 * =============
31 *>
32 *> \verbatim
33 *>
34 *> DDRVPO tests the driver routines DPOSV and -SVX.
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] NRHS
61 *> \verbatim
62 *> NRHS is INTEGER
63 *> The number of right hand side vectors to be generated for
64 *> each linear system.
65 *> \endverbatim
66 *>
67 *> \param[in] THRESH
68 *> \verbatim
69 *> THRESH is DOUBLE PRECISION
70 *> The threshold value for the test ratios. A result is
71 *> included in the output file if RESULT >= THRESH. To have
72 *> every test ratio printed, use THRESH = 0.
73 *> \endverbatim
74 *>
75 *> \param[in] TSTERR
76 *> \verbatim
77 *> TSTERR is LOGICAL
78 *> Flag that indicates whether error exits are to be tested.
79 *> \endverbatim
80 *>
81 *> \param[in] NMAX
82 *> \verbatim
83 *> NMAX is INTEGER
84 *> The maximum value permitted for N, used in dimensioning the
85 *> work arrays.
86 *> \endverbatim
87 *>
88 *> \param[out] A
89 *> \verbatim
90 *> A is DOUBLE PRECISION array, dimension (NMAX*NMAX)
91 *> \endverbatim
92 *>
93 *> \param[out] AFAC
94 *> \verbatim
95 *> AFAC is DOUBLE PRECISION array, dimension (NMAX*NMAX)
96 *> \endverbatim
97 *>
98 *> \param[out] ASAV
99 *> \verbatim
100 *> ASAV is DOUBLE PRECISION array, dimension (NMAX*NMAX)
101 *> \endverbatim
102 *>
103 *> \param[out] B
104 *> \verbatim
105 *> B is DOUBLE PRECISION array, dimension (NMAX*NRHS)
106 *> \endverbatim
107 *>
108 *> \param[out] BSAV
109 *> \verbatim
110 *> BSAV is DOUBLE PRECISION array, dimension (NMAX*NRHS)
111 *> \endverbatim
112 *>
113 *> \param[out] X
114 *> \verbatim
115 *> X is DOUBLE PRECISION array, dimension (NMAX*NRHS)
116 *> \endverbatim
117 *>
118 *> \param[out] XACT
119 *> \verbatim
120 *> XACT is DOUBLE PRECISION array, dimension (NMAX*NRHS)
121 *> \endverbatim
122 *>
123 *> \param[out] S
124 *> \verbatim
125 *> S is DOUBLE PRECISION array, dimension (NMAX)
126 *> \endverbatim
127 *>
128 *> \param[out] WORK
129 *> \verbatim
130 *> WORK is DOUBLE PRECISION array, dimension
131 *> (NMAX*max(3,NRHS))
132 *> \endverbatim
133 *>
134 *> \param[out] RWORK
135 *> \verbatim
136 *> RWORK is DOUBLE PRECISION array, dimension (NMAX+2*NRHS)
137 *> \endverbatim
138 *>
139 *> \param[out] IWORK
140 *> \verbatim
141 *> IWORK is INTEGER array, dimension (NMAX)
142 *> \endverbatim
143 *>
144 *> \param[in] NOUT
145 *> \verbatim
146 *> NOUT is INTEGER
147 *> The unit number for output.
148 *> \endverbatim
149 *
150 * Authors:
151 * ========
152 *
153 *> \author Univ. of Tennessee
154 *> \author Univ. of California Berkeley
155 *> \author Univ. of Colorado Denver
156 *> \author NAG Ltd.
157 *
158 *> \date November 2011
159 *
160 *> \ingroup double_lin
161 *
162 * =====================================================================
163  SUBROUTINE ddrvpo( DOTYPE, NN, NVAL, NRHS, THRESH, TSTERR, NMAX,
164  $ a, afac, asav, b, bsav, x, xact, s, work,
165  $ rwork, iwork, nout )
166 *
167 * -- LAPACK test routine (version 3.4.0) --
168 * -- LAPACK is a software package provided by Univ. of Tennessee, --
169 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
170 * November 2011
171 *
172 * .. Scalar Arguments ..
173  LOGICAL tsterr
174  INTEGER nmax, nn, nout, nrhs
175  DOUBLE PRECISION thresh
176 * ..
177 * .. Array Arguments ..
178  LOGICAL dotype( * )
179  INTEGER iwork( * ), nval( * )
180  DOUBLE PRECISION a( * ), afac( * ), asav( * ), b( * ),
181  $ bsav( * ), rwork( * ), s( * ), work( * ),
182  $ x( * ), xact( * )
183 * ..
184 *
185 * =====================================================================
186 *
187 * .. Parameters ..
188  DOUBLE PRECISION one, zero
189  parameter( one = 1.0d+0, zero = 0.0d+0 )
190  INTEGER ntypes
191  parameter( ntypes = 9 )
192  INTEGER ntests
193  parameter( ntests = 6 )
194 * ..
195 * .. Local Scalars ..
196  LOGICAL equil, nofact, prefac, zerot
197  CHARACTER dist, equed, fact, type, uplo, xtype
198  CHARACTER*3 path
199  INTEGER i, iequed, ifact, imat, in, info, ioff, iuplo,
200  $ izero, k, k1, kl, ku, lda, mode, n, nb, nbmin,
201  $ nerrs, nfact, nfail, nimat, nrun, nt
202  DOUBLE PRECISION ainvnm, amax, anorm, cndnum, rcond, rcondc,
203  $ roldc, scond
204 * ..
205 * .. Local Arrays ..
206  CHARACTER equeds( 2 ), facts( 3 ), uplos( 2 )
207  INTEGER iseed( 4 ), iseedy( 4 )
208  DOUBLE PRECISION result( ntests )
209 * ..
210 * .. External Functions ..
211  LOGICAL lsame
212  DOUBLE PRECISION dget06, dlansy
213  EXTERNAL lsame, dget06, dlansy
214 * ..
215 * .. External Subroutines ..
216  EXTERNAL aladhd, alaerh, alasvm, derrvx, dget04, dlacpy,
219  $ dpotri, xlaenv
220 * ..
221 * .. Intrinsic Functions ..
222  INTRINSIC max
223 * ..
224 * .. Scalars in Common ..
225  LOGICAL lerr, ok
226  CHARACTER*32 srnamt
227  INTEGER infot, nunit
228 * ..
229 * .. Common blocks ..
230  common / infoc / infot, nunit, ok, lerr
231  common / srnamc / srnamt
232 * ..
233 * .. Data statements ..
234  DATA iseedy / 1988, 1989, 1990, 1991 /
235  DATA uplos / 'U', 'L' /
236  DATA facts / 'F', 'N', 'E' /
237  DATA equeds / 'N', 'Y' /
238 * ..
239 * .. Executable Statements ..
240 *
241 * Initialize constants and the random number seed.
242 *
243  path( 1: 1 ) = 'Double 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 derrvx( path, nout )
256  infot = 0
257 *
258 * Set the block size and minimum block size for testing.
259 *
260  nb = 1
261  nbmin = 2
262  CALL xlaenv( 1, nb )
263  CALL xlaenv( 2, nbmin )
264 *
265 * Do for each value of N in NVAL
266 *
267  DO 130 in = 1, nn
268  n = nval( in )
269  lda = max( n, 1 )
270  xtype = 'N'
271  nimat = ntypes
272  IF( n.LE.0 )
273  $ nimat = 1
274 *
275  DO 120 imat = 1, nimat
276 *
277 * Do the tests only if DOTYPE( IMAT ) is true.
278 *
279  IF( .NOT.dotype( imat ) )
280  $ go to 120
281 *
282 * Skip types 3, 4, or 5 if the matrix size is too small.
283 *
284  zerot = imat.GE.3 .AND. imat.LE.5
285  IF( zerot .AND. n.LT.imat-2 )
286  $ go to 120
287 *
288 * Do first for UPLO = 'U', then for UPLO = 'L'
289 *
290  DO 110 iuplo = 1, 2
291  uplo = uplos( iuplo )
292 *
293 * Set up parameters with DLATB4 and generate a test matrix
294 * with DLATMS.
295 *
296  CALL dlatb4( path, imat, n, n, type, kl, ku, anorm, mode,
297  $ cndnum, dist )
298 *
299  srnamt = 'DLATMS'
300  CALL dlatms( n, n, dist, iseed, type, rwork, mode,
301  $ cndnum, anorm, kl, ku, uplo, a, lda, work,
302  $ info )
303 *
304 * Check error code from DLATMS.
305 *
306  IF( info.NE.0 ) THEN
307  CALL alaerh( path, 'DLATMS', info, 0, uplo, n, n, -1,
308  $ -1, -1, imat, nfail, nerrs, nout )
309  go to 110
310  END IF
311 *
312 * For types 3-5, zero one row and column of the matrix to
313 * test that INFO is returned correctly.
314 *
315  IF( zerot ) THEN
316  IF( imat.EQ.3 ) THEN
317  izero = 1
318  ELSE IF( imat.EQ.4 ) THEN
319  izero = n
320  ELSE
321  izero = n / 2 + 1
322  END IF
323  ioff = ( izero-1 )*lda
324 *
325 * Set row and column IZERO of A to 0.
326 *
327  IF( iuplo.EQ.1 ) THEN
328  DO 20 i = 1, izero - 1
329  a( ioff+i ) = zero
330  20 continue
331  ioff = ioff + izero
332  DO 30 i = izero, n
333  a( ioff ) = zero
334  ioff = ioff + lda
335  30 continue
336  ELSE
337  ioff = izero
338  DO 40 i = 1, izero - 1
339  a( ioff ) = zero
340  ioff = ioff + lda
341  40 continue
342  ioff = ioff - izero
343  DO 50 i = izero, n
344  a( ioff+i ) = zero
345  50 continue
346  END IF
347  ELSE
348  izero = 0
349  END IF
350 *
351 * Save a copy of the matrix A in ASAV.
352 *
353  CALL dlacpy( uplo, n, n, a, lda, asav, lda )
354 *
355  DO 100 iequed = 1, 2
356  equed = equeds( iequed )
357  IF( iequed.EQ.1 ) THEN
358  nfact = 3
359  ELSE
360  nfact = 1
361  END IF
362 *
363  DO 90 ifact = 1, nfact
364  fact = facts( ifact )
365  prefac = lsame( fact, 'F' )
366  nofact = lsame( fact, 'N' )
367  equil = lsame( fact, 'E' )
368 *
369  IF( zerot ) THEN
370  IF( prefac )
371  $ go to 90
372  rcondc = zero
373 *
374  ELSE IF( .NOT.lsame( fact, 'N' ) ) THEN
375 *
376 * Compute the condition number for comparison with
377 * the value returned by DPOSVX (FACT = 'N' reuses
378 * the condition number from the previous iteration
379 * with FACT = 'F').
380 *
381  CALL dlacpy( uplo, n, n, asav, lda, afac, lda )
382  IF( equil .OR. iequed.GT.1 ) THEN
383 *
384 * Compute row and column scale factors to
385 * equilibrate the matrix A.
386 *
387  CALL dpoequ( n, afac, lda, s, scond, amax,
388  $ info )
389  IF( info.EQ.0 .AND. n.GT.0 ) THEN
390  IF( iequed.GT.1 )
391  $ scond = zero
392 *
393 * Equilibrate the matrix.
394 *
395  CALL dlaqsy( uplo, n, afac, lda, s, scond,
396  $ amax, equed )
397  END IF
398  END IF
399 *
400 * Save the condition number of the
401 * non-equilibrated system for use in DGET04.
402 *
403  IF( equil )
404  $ roldc = rcondc
405 *
406 * Compute the 1-norm of A.
407 *
408  anorm = dlansy( '1', uplo, n, afac, lda, rwork )
409 *
410 * Factor the matrix A.
411 *
412  CALL dpotrf( uplo, n, afac, lda, info )
413 *
414 * Form the inverse of A.
415 *
416  CALL dlacpy( uplo, n, n, afac, lda, a, lda )
417  CALL dpotri( uplo, n, a, lda, info )
418 *
419 * Compute the 1-norm condition number of A.
420 *
421  ainvnm = dlansy( '1', uplo, n, a, lda, rwork )
422  IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
423  rcondc = one
424  ELSE
425  rcondc = ( one / anorm ) / ainvnm
426  END IF
427  END IF
428 *
429 * Restore the matrix A.
430 *
431  CALL dlacpy( uplo, n, n, asav, lda, a, lda )
432 *
433 * Form an exact solution and set the right hand side.
434 *
435  srnamt = 'DLARHS'
436  CALL dlarhs( path, xtype, uplo, ' ', n, n, kl, ku,
437  $ nrhs, a, lda, xact, lda, b, lda,
438  $ iseed, info )
439  xtype = 'C'
440  CALL dlacpy( 'Full', n, nrhs, b, lda, bsav, lda )
441 *
442  IF( nofact ) THEN
443 *
444 * --- Test DPOSV ---
445 *
446 * Compute the L*L' or U'*U factorization of the
447 * matrix and solve the system.
448 *
449  CALL dlacpy( uplo, n, n, a, lda, afac, lda )
450  CALL dlacpy( 'Full', n, nrhs, b, lda, x, lda )
451 *
452  srnamt = 'DPOSV '
453  CALL dposv( uplo, n, nrhs, afac, lda, x, lda,
454  $ info )
455 *
456 * Check error code from DPOSV .
457 *
458  IF( info.NE.izero ) THEN
459  CALL alaerh( path, 'DPOSV ', info, izero,
460  $ uplo, n, n, -1, -1, nrhs, imat,
461  $ nfail, nerrs, nout )
462  go to 70
463  ELSE IF( info.NE.0 ) THEN
464  go to 70
465  END IF
466 *
467 * Reconstruct matrix from factors and compute
468 * residual.
469 *
470  CALL dpot01( uplo, n, a, lda, afac, lda, rwork,
471  $ result( 1 ) )
472 *
473 * Compute residual of the computed solution.
474 *
475  CALL dlacpy( 'Full', n, nrhs, b, lda, work,
476  $ lda )
477  CALL dpot02( uplo, n, nrhs, a, lda, x, lda,
478  $ work, lda, rwork, result( 2 ) )
479 *
480 * Check solution from generated exact solution.
481 *
482  CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
483  $ result( 3 ) )
484  nt = 3
485 *
486 * Print information about the tests that did not
487 * pass the threshold.
488 *
489  DO 60 k = 1, nt
490  IF( result( k ).GE.thresh ) THEN
491  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
492  $ CALL aladhd( nout, path )
493  WRITE( nout, fmt = 9999 )'DPOSV ', uplo,
494  $ n, imat, k, result( k )
495  nfail = nfail + 1
496  END IF
497  60 continue
498  nrun = nrun + nt
499  70 continue
500  END IF
501 *
502 * --- Test DPOSVX ---
503 *
504  IF( .NOT.prefac )
505  $ CALL dlaset( uplo, n, n, zero, zero, afac, lda )
506  CALL dlaset( 'Full', n, nrhs, zero, zero, x, lda )
507  IF( iequed.GT.1 .AND. n.GT.0 ) THEN
508 *
509 * Equilibrate the matrix if FACT='F' and
510 * EQUED='Y'.
511 *
512  CALL dlaqsy( uplo, n, a, lda, s, scond, amax,
513  $ equed )
514  END IF
515 *
516 * Solve the system and compute the condition number
517 * and error bounds using DPOSVX.
518 *
519  srnamt = 'DPOSVX'
520  CALL dposvx( fact, uplo, n, nrhs, a, lda, afac,
521  $ lda, equed, s, b, lda, x, lda, rcond,
522  $ rwork, rwork( nrhs+1 ), work, iwork,
523  $ info )
524 *
525 * Check the error code from DPOSVX.
526 *
527  IF( info.NE.izero ) THEN
528  CALL alaerh( path, 'DPOSVX', info, izero,
529  $ fact // uplo, n, n, -1, -1, nrhs,
530  $ imat, nfail, nerrs, nout )
531  go to 90
532  END IF
533 *
534  IF( info.EQ.0 ) THEN
535  IF( .NOT.prefac ) THEN
536 *
537 * Reconstruct matrix from factors and compute
538 * residual.
539 *
540  CALL dpot01( uplo, n, a, lda, afac, lda,
541  $ rwork( 2*nrhs+1 ), result( 1 ) )
542  k1 = 1
543  ELSE
544  k1 = 2
545  END IF
546 *
547 * Compute residual of the computed solution.
548 *
549  CALL dlacpy( 'Full', n, nrhs, bsav, lda, work,
550  $ lda )
551  CALL dpot02( uplo, n, nrhs, asav, lda, x, lda,
552  $ work, lda, rwork( 2*nrhs+1 ),
553  $ result( 2 ) )
554 *
555 * Check solution from generated exact solution.
556 *
557  IF( nofact .OR. ( prefac .AND. lsame( equed,
558  $ 'N' ) ) ) THEN
559  CALL dget04( n, nrhs, x, lda, xact, lda,
560  $ rcondc, result( 3 ) )
561  ELSE
562  CALL dget04( n, nrhs, x, lda, xact, lda,
563  $ roldc, result( 3 ) )
564  END IF
565 *
566 * Check the error bounds from iterative
567 * refinement.
568 *
569  CALL dpot05( uplo, n, nrhs, asav, lda, b, lda,
570  $ x, lda, xact, lda, rwork,
571  $ rwork( nrhs+1 ), result( 4 ) )
572  ELSE
573  k1 = 6
574  END IF
575 *
576 * Compare RCOND from DPOSVX with the computed value
577 * in RCONDC.
578 *
579  result( 6 ) = dget06( rcond, rcondc )
580 *
581 * Print information about the tests that did not pass
582 * the threshold.
583 *
584  DO 80 k = k1, 6
585  IF( result( k ).GE.thresh ) THEN
586  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
587  $ CALL aladhd( nout, path )
588  IF( prefac ) THEN
589  WRITE( nout, fmt = 9997 )'DPOSVX', fact,
590  $ uplo, n, equed, imat, k, result( k )
591  ELSE
592  WRITE( nout, fmt = 9998 )'DPOSVX', fact,
593  $ uplo, n, imat, k, result( k )
594  END IF
595  nfail = nfail + 1
596  END IF
597  80 continue
598  nrun = nrun + 7 - k1
599  90 continue
600  100 continue
601  110 continue
602  120 continue
603  130 continue
604 *
605 * Print a summary of the results.
606 *
607  CALL alasvm( path, nout, nfail, nrun, nerrs )
608 *
609  9999 format( 1x, a, ', UPLO=''', a1, ''', N =', i5, ', type ', i1,
610  $ ', test(', i1, ')=', g12.5 )
611  9998 format( 1x, a, ', FACT=''', a1, ''', UPLO=''', a1, ''', N=', i5,
612  $ ', type ', i1, ', test(', i1, ')=', g12.5 )
613  9997 format( 1x, a, ', FACT=''', a1, ''', UPLO=''', a1, ''', N=', i5,
614  $ ', EQUED=''', a1, ''', type ', i1, ', test(', i1, ') =',
615  $ g12.5 )
616  return
617 *
618 * End of DDRVPO
619 *
620  END