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