LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
sdrvrfp.f
Go to the documentation of this file.
1 *> \brief \b SDRVRFP
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 SDRVRFP( NOUT, NN, NVAL, NNS, NSVAL, NNT, NTVAL,
12 * + THRESH, A, ASAV, AFAC, AINV, B,
13 * + BSAV, XACT, X, ARF, ARFINV,
14 * + S_WORK_SLATMS, S_WORK_SPOT01, S_TEMP_SPOT02,
15 * + S_TEMP_SPOT03, S_WORK_SLANSY,
16 * + S_WORK_SPOT02, S_WORK_SPOT03 )
17 *
18 * .. Scalar Arguments ..
19 * INTEGER NN, NNS, NNT, NOUT
20 * REAL THRESH
21 * ..
22 * .. Array Arguments ..
23 * INTEGER NVAL( NN ), NSVAL( NNS ), NTVAL( NNT )
24 * REAL A( * )
25 * REAL AINV( * )
26 * REAL ASAV( * )
27 * REAL B( * )
28 * REAL BSAV( * )
29 * REAL AFAC( * )
30 * REAL ARF( * )
31 * REAL ARFINV( * )
32 * REAL XACT( * )
33 * REAL X( * )
34 * REAL S_WORK_SLATMS( * )
35 * REAL S_WORK_SPOT01( * )
36 * REAL S_TEMP_SPOT02( * )
37 * REAL S_TEMP_SPOT03( * )
38 * REAL S_WORK_SLANSY( * )
39 * REAL S_WORK_SPOT02( * )
40 * REAL S_WORK_SPOT03( * )
41 * ..
42 *
43 *
44 *> \par Purpose:
45 * =============
46 *>
47 *> \verbatim
48 *>
49 *> SDRVRFP tests the LAPACK RFP routines:
50 *> SPFTRF, SPFTRS, and SPFTRI.
51 *>
52 *> This testing routine follow the same tests as DDRVPO (test for the full
53 *> format Symmetric Positive Definite solver).
54 *>
55 *> The tests are performed in Full Format, convertion back and forth from
56 *> full format to RFP format are performed using the routines STRTTF and
57 *> STFTTR.
58 *>
59 *> First, a specific matrix A of size N is created. There is nine types of
60 *> different matrixes possible.
61 *> 1. Diagonal 6. Random, CNDNUM = sqrt(0.1/EPS)
62 *> 2. Random, CNDNUM = 2 7. Random, CNDNUM = 0.1/EPS
63 *> *3. First row and column zero 8. Scaled near underflow
64 *> *4. Last row and column zero 9. Scaled near overflow
65 *> *5. Middle row and column zero
66 *> (* - tests error exits from SPFTRF, no test ratios are computed)
67 *> A solution XACT of size N-by-NRHS is created and the associated right
68 *> hand side B as well. Then SPFTRF is called to compute L (or U), the
69 *> Cholesky factor of A. Then L (or U) is used to solve the linear system
70 *> of equations AX = B. This gives X. Then L (or U) is used to compute the
71 *> inverse of A, AINV. The following four tests are then performed:
72 *> (1) norm( L*L' - A ) / ( N * norm(A) * EPS ) or
73 *> norm( U'*U - A ) / ( N * norm(A) * EPS ),
74 *> (2) norm(B - A*X) / ( norm(A) * norm(X) * EPS ),
75 *> (3) norm( I - A*AINV ) / ( N * norm(A) * norm(AINV) * EPS ),
76 *> (4) ( norm(X-XACT) * RCOND ) / ( norm(XACT) * EPS ),
77 *> where EPS is the machine precision, RCOND the condition number of A, and
78 *> norm( . ) the 1-norm for (1,2,3) and the inf-norm for (4).
79 *> Errors occur when INFO parameter is not as expected. Failures occur when
80 *> a test ratios is greater than THRES.
81 *> \endverbatim
82 *
83 * Arguments:
84 * ==========
85 *
86 *> \param[in] NOUT
87 *> \verbatim
88 *> NOUT is INTEGER
89 *> The unit number for output.
90 *> \endverbatim
91 *>
92 *> \param[in] NN
93 *> \verbatim
94 *> NN is INTEGER
95 *> The number of values of N contained in the vector NVAL.
96 *> \endverbatim
97 *>
98 *> \param[in] NVAL
99 *> \verbatim
100 *> NVAL is INTEGER array, dimension (NN)
101 *> The values of the matrix dimension N.
102 *> \endverbatim
103 *>
104 *> \param[in] NNS
105 *> \verbatim
106 *> NNS is INTEGER
107 *> The number of values of NRHS contained in the vector NSVAL.
108 *> \endverbatim
109 *>
110 *> \param[in] NSVAL
111 *> \verbatim
112 *> NSVAL is INTEGER array, dimension (NNS)
113 *> The values of the number of right-hand sides NRHS.
114 *> \endverbatim
115 *>
116 *> \param[in] NNT
117 *> \verbatim
118 *> NNT is INTEGER
119 *> The number of values of MATRIX TYPE contained in the vector NTVAL.
120 *> \endverbatim
121 *>
122 *> \param[in] NTVAL
123 *> \verbatim
124 *> NTVAL is INTEGER array, dimension (NNT)
125 *> The values of matrix type (between 0 and 9 for PO/PP/PF matrices).
126 *> \endverbatim
127 *>
128 *> \param[in] THRESH
129 *> \verbatim
130 *> THRESH is REAL
131 *> The threshold value for the test ratios. A result is
132 *> included in the output file if RESULT >= THRESH. To have
133 *> every test ratio printed, use THRESH = 0.
134 *> \endverbatim
135 *>
136 *> \param[out] A
137 *> \verbatim
138 *> A is REAL array, dimension (NMAX*NMAX)
139 *> \endverbatim
140 *>
141 *> \param[out] ASAV
142 *> \verbatim
143 *> ASAV is REAL array, dimension (NMAX*NMAX)
144 *> \endverbatim
145 *>
146 *> \param[out] AFAC
147 *> \verbatim
148 *> AFAC is REAL array, dimension (NMAX*NMAX)
149 *> \endverbatim
150 *>
151 *> \param[out] AINV
152 *> \verbatim
153 *> AINV is REAL array, dimension (NMAX*NMAX)
154 *> \endverbatim
155 *>
156 *> \param[out] B
157 *> \verbatim
158 *> B is REAL array, dimension (NMAX*MAXRHS)
159 *> \endverbatim
160 *>
161 *> \param[out] BSAV
162 *> \verbatim
163 *> BSAV is REAL array, dimension (NMAX*MAXRHS)
164 *> \endverbatim
165 *>
166 *> \param[out] XACT
167 *> \verbatim
168 *> XACT is REAL array, dimension (NMAX*MAXRHS)
169 *> \endverbatim
170 *>
171 *> \param[out] X
172 *> \verbatim
173 *> X is REAL array, dimension (NMAX*MAXRHS)
174 *> \endverbatim
175 *>
176 *> \param[out] ARF
177 *> \verbatim
178 *> ARF is REAL array, dimension ((NMAX*(NMAX+1))/2)
179 *> \endverbatim
180 *>
181 *> \param[out] ARFINV
182 *> \verbatim
183 *> ARFINV is REAL array, dimension ((NMAX*(NMAX+1))/2)
184 *> \endverbatim
185 *>
186 *> \param[out] S_WORK_SLATMS
187 *> \verbatim
188 *> S_WORK_SLATMS is REAL array, dimension ( 3*NMAX )
189 *> \endverbatim
190 *>
191 *> \param[out] S_WORK_SPOT01
192 *> \verbatim
193 *> S_WORK_SPOT01 is REAL array, dimension ( NMAX )
194 *> \endverbatim
195 *>
196 *> \param[out] S_TEMP_SPOT02
197 *> \verbatim
198 *> S_TEMP_SPOT02 is REAL array, dimension ( NMAX*MAXRHS )
199 *> \endverbatim
200 *>
201 *> \param[out] S_TEMP_SPOT03
202 *> \verbatim
203 *> S_TEMP_SPOT03 is REAL array, dimension ( NMAX*NMAX )
204 *> \endverbatim
205 *>
206 *> \param[out] S_WORK_SLATMS
207 *> \verbatim
208 *> S_WORK_SLATMS is REAL array, dimension ( NMAX )
209 *> \endverbatim
210 *>
211 *> \param[out] S_WORK_SLANSY
212 *> \verbatim
213 *> S_WORK_SLANSY is REAL array, dimension ( NMAX )
214 *> \endverbatim
215 *>
216 *> \param[out] S_WORK_SPOT02
217 *> \verbatim
218 *> S_WORK_SPOT02 is REAL array, dimension ( NMAX )
219 *> \endverbatim
220 *>
221 *> \param[out] S_WORK_SPOT03
222 *> \verbatim
223 *> S_WORK_SPOT03 is REAL array, dimension ( NMAX )
224 *> \endverbatim
225 *
226 * Authors:
227 * ========
228 *
229 *> \author Univ. of Tennessee
230 *> \author Univ. of California Berkeley
231 *> \author Univ. of Colorado Denver
232 *> \author NAG Ltd.
233 *
234 *> \date November 2011
235 *
236 *> \ingroup single_lin
237 *
238 * =====================================================================
239  SUBROUTINE sdrvrfp( NOUT, NN, NVAL, NNS, NSVAL, NNT, NTVAL,
240  + thresh, a, asav, afac, ainv, b,
241  + bsav, xact, x, arf, arfinv,
242  + s_work_slatms, s_work_spot01, s_temp_spot02,
243  + s_temp_spot03, s_work_slansy,
244  + s_work_spot02, s_work_spot03 )
245 *
246 * -- LAPACK test routine (version 3.4.0) --
247 * -- LAPACK is a software package provided by Univ. of Tennessee, --
248 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
249 * November 2011
250 *
251 * .. Scalar Arguments ..
252  INTEGER nn, nns, nnt, nout
253  REAL thresh
254 * ..
255 * .. Array Arguments ..
256  INTEGER nval( nn ), nsval( nns ), ntval( nnt )
257  REAL a( * )
258  REAL ainv( * )
259  REAL asav( * )
260  REAL b( * )
261  REAL bsav( * )
262  REAL afac( * )
263  REAL arf( * )
264  REAL arfinv( * )
265  REAL xact( * )
266  REAL x( * )
267  REAL s_work_slatms( * )
268  REAL s_work_spot01( * )
269  REAL s_temp_spot02( * )
270  REAL s_temp_spot03( * )
271  REAL s_work_slansy( * )
272  REAL s_work_spot02( * )
273  REAL s_work_spot03( * )
274 * ..
275 *
276 * =====================================================================
277 *
278 * .. Parameters ..
279  REAL one, zero
280  parameter( one = 1.0e+0, zero = 0.0e+0 )
281  INTEGER ntests
282  parameter( ntests = 4 )
283 * ..
284 * .. Local Scalars ..
285  LOGICAL zerot
286  INTEGER i, info, iuplo, lda, ldb, imat, nerrs, nfail,
287  + nrhs, nrun, izero, ioff, k, nt, n, iform, iin,
288  + iit, iis
289  CHARACTER dist, ctype, uplo, cform
290  INTEGER kl, ku, mode
291  REAL anorm, ainvnm, cndnum, rcondc
292 * ..
293 * .. Local Arrays ..
294  CHARACTER uplos( 2 ), forms( 2 )
295  INTEGER iseed( 4 ), iseedy( 4 )
296  REAL result( ntests )
297 * ..
298 * .. External Functions ..
299  REAL slansy
300  EXTERNAL slansy
301 * ..
302 * .. External Subroutines ..
303  EXTERNAL aladhd, alaerh, alasvm, sget04, stfttr, slacpy,
306 * ..
307 * .. Scalars in Common ..
308  CHARACTER*32 srnamt
309 * ..
310 * .. Common blocks ..
311  common / srnamc / srnamt
312 * ..
313 * .. Data statements ..
314  DATA iseedy / 1988, 1989, 1990, 1991 /
315  DATA uplos / 'U', 'L' /
316  DATA forms / 'N', 'T' /
317 * ..
318 * .. Executable Statements ..
319 *
320 * Initialize constants and the random number seed.
321 *
322  nrun = 0
323  nfail = 0
324  nerrs = 0
325  DO 10 i = 1, 4
326  iseed( i ) = iseedy( i )
327  10 continue
328 *
329  DO 130 iin = 1, nn
330 *
331  n = nval( iin )
332  lda = max( n, 1 )
333  ldb = max( n, 1 )
334 *
335  DO 980 iis = 1, nns
336 *
337  nrhs = nsval( iis )
338 *
339  DO 120 iit = 1, nnt
340 *
341  imat = ntval( iit )
342 *
343 * If N.EQ.0, only consider the first type
344 *
345  IF( n.EQ.0 .AND. iit.GT.1 ) go to 120
346 *
347 * Skip types 3, 4, or 5 if the matrix size is too small.
348 *
349  IF( imat.EQ.4 .AND. n.LE.1 ) go to 120
350  IF( imat.EQ.5 .AND. n.LE.2 ) go to 120
351 *
352 * Do first for UPLO = 'U', then for UPLO = 'L'
353 *
354  DO 110 iuplo = 1, 2
355  uplo = uplos( iuplo )
356 *
357 * Do first for CFORM = 'N', then for CFORM = 'C'
358 *
359  DO 100 iform = 1, 2
360  cform = forms( iform )
361 *
362 * Set up parameters with SLATB4 and generate a test
363 * matrix with SLATMS.
364 *
365  CALL slatb4( 'SPO', imat, n, n, ctype, kl, ku,
366  + anorm, mode, cndnum, dist )
367 *
368  srnamt = 'SLATMS'
369  CALL slatms( n, n, dist, iseed, ctype,
370  + s_work_slatms,
371  + mode, cndnum, anorm, kl, ku, uplo, a,
372  + lda, s_work_slatms, info )
373 *
374 * Check error code from SLATMS.
375 *
376  IF( info.NE.0 ) THEN
377  CALL alaerh( 'SPF', 'SLATMS', info, 0, uplo, n,
378  + n, -1, -1, -1, iit, nfail, nerrs,
379  + nout )
380  go to 100
381  END IF
382 *
383 * For types 3-5, zero one row and column of the matrix to
384 * test that INFO is returned correctly.
385 *
386  zerot = imat.GE.3 .AND. imat.LE.5
387  IF( zerot ) THEN
388  IF( iit.EQ.3 ) THEN
389  izero = 1
390  ELSE IF( iit.EQ.4 ) THEN
391  izero = n
392  ELSE
393  izero = n / 2 + 1
394  END IF
395  ioff = ( izero-1 )*lda
396 *
397 * Set row and column IZERO of A to 0.
398 *
399  IF( iuplo.EQ.1 ) THEN
400  DO 20 i = 1, izero - 1
401  a( ioff+i ) = zero
402  20 continue
403  ioff = ioff + izero
404  DO 30 i = izero, n
405  a( ioff ) = zero
406  ioff = ioff + lda
407  30 continue
408  ELSE
409  ioff = izero
410  DO 40 i = 1, izero - 1
411  a( ioff ) = zero
412  ioff = ioff + lda
413  40 continue
414  ioff = ioff - izero
415  DO 50 i = izero, n
416  a( ioff+i ) = zero
417  50 continue
418  END IF
419  ELSE
420  izero = 0
421  END IF
422 *
423 * Save a copy of the matrix A in ASAV.
424 *
425  CALL slacpy( uplo, n, n, a, lda, asav, lda )
426 *
427 * Compute the condition number of A (RCONDC).
428 *
429  IF( zerot ) THEN
430  rcondc = zero
431  ELSE
432 *
433 * Compute the 1-norm of A.
434 *
435  anorm = slansy( '1', uplo, n, a, lda,
436  + s_work_slansy )
437 *
438 * Factor the matrix A.
439 *
440  CALL spotrf( uplo, n, a, lda, info )
441 *
442 * Form the inverse of A.
443 *
444  CALL spotri( uplo, n, a, lda, info )
445 *
446 * Compute the 1-norm condition number of A.
447 *
448  ainvnm = slansy( '1', uplo, n, a, lda,
449  + s_work_slansy )
450  rcondc = ( one / anorm ) / ainvnm
451 *
452 * Restore the matrix A.
453 *
454  CALL slacpy( uplo, n, n, asav, lda, a, lda )
455 *
456  END IF
457 *
458 * Form an exact solution and set the right hand side.
459 *
460  srnamt = 'SLARHS'
461  CALL slarhs( 'SPO', 'N', uplo, ' ', n, n, kl, ku,
462  + nrhs, a, lda, xact, lda, b, lda,
463  + iseed, info )
464  CALL slacpy( 'Full', n, nrhs, b, lda, bsav, lda )
465 *
466 * Compute the L*L' or U'*U factorization of the
467 * matrix and solve the system.
468 *
469  CALL slacpy( uplo, n, n, a, lda, afac, lda )
470  CALL slacpy( 'Full', n, nrhs, b, ldb, x, ldb )
471 *
472  srnamt = 'STRTTF'
473  CALL strttf( cform, uplo, n, afac, lda, arf, info )
474  srnamt = 'SPFTRF'
475  CALL spftrf( cform, uplo, n, arf, info )
476 *
477 * Check error code from SPFTRF.
478 *
479  IF( info.NE.izero ) THEN
480 *
481 * LANGOU: there is a small hick here: IZERO should
482 * always be INFO however if INFO is ZERO, ALAERH does not
483 * complain.
484 *
485  CALL alaerh( 'SPF', 'SPFSV ', info, izero,
486  + uplo, n, n, -1, -1, nrhs, iit,
487  + nfail, nerrs, nout )
488  go to 100
489  END IF
490 *
491 * Skip the tests if INFO is not 0.
492 *
493  IF( info.NE.0 ) THEN
494  go to 100
495  END IF
496 *
497  srnamt = 'SPFTRS'
498  CALL spftrs( cform, uplo, n, nrhs, arf, x, ldb,
499  + info )
500 *
501  srnamt = 'STFTTR'
502  CALL stfttr( cform, uplo, n, arf, afac, lda, info )
503 *
504 * Reconstruct matrix from factors and compute
505 * residual.
506 *
507  CALL slacpy( uplo, n, n, afac, lda, asav, lda )
508  CALL spot01( uplo, n, a, lda, afac, lda,
509  + s_work_spot01, result( 1 ) )
510  CALL slacpy( uplo, n, n, asav, lda, afac, lda )
511 *
512 * Form the inverse and compute the residual.
513 *
514  IF(mod(n,2).EQ.0)THEN
515  CALL slacpy( 'A', n+1, n/2, arf, n+1, arfinv,
516  + n+1 )
517  ELSE
518  CALL slacpy( 'A', n, (n+1)/2, arf, n, arfinv,
519  + n )
520  END IF
521 *
522  srnamt = 'SPFTRI'
523  CALL spftri( cform, uplo, n, arfinv , info )
524 *
525  srnamt = 'STFTTR'
526  CALL stfttr( cform, uplo, n, arfinv, ainv, lda,
527  + info )
528 *
529 * Check error code from SPFTRI.
530 *
531  IF( info.NE.0 )
532  + CALL alaerh( 'SPO', 'SPFTRI', info, 0, uplo, n,
533  + n, -1, -1, -1, imat, nfail, nerrs,
534  + nout )
535 *
536  CALL spot03( uplo, n, a, lda, ainv, lda,
537  + s_temp_spot03, lda, s_work_spot03,
538  + rcondc, result( 2 ) )
539 *
540 * Compute residual of the computed solution.
541 *
542  CALL slacpy( 'Full', n, nrhs, b, lda,
543  + s_temp_spot02, lda )
544  CALL spot02( uplo, n, nrhs, a, lda, x, lda,
545  + s_temp_spot02, lda, s_work_spot02,
546  + result( 3 ) )
547 *
548 * Check solution from generated exact solution.
549 
550  CALL sget04( n, nrhs, x, lda, xact, lda, rcondc,
551  + result( 4 ) )
552  nt = 4
553 *
554 * Print information about the tests that did not
555 * pass the threshold.
556 *
557  DO 60 k = 1, nt
558  IF( result( k ).GE.thresh ) THEN
559  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
560  + CALL aladhd( nout, 'SPF' )
561  WRITE( nout, fmt = 9999 )'SPFSV ', uplo,
562  + n, iit, k, result( k )
563  nfail = nfail + 1
564  END IF
565  60 continue
566  nrun = nrun + nt
567  100 continue
568  110 continue
569  120 continue
570  980 continue
571  130 continue
572 *
573 * Print a summary of the results.
574 *
575  CALL alasvm( 'SPF', nout, nfail, nrun, nerrs )
576 *
577  9999 format( 1x, a6, ', UPLO=''', a1, ''', N =', i5, ', type ', i1,
578  + ', test(', i1, ')=', g12.5 )
579 *
580  return
581 *
582 * End of SDRVRFP
583 *
584  END