LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
schkps.f
Go to the documentation of this file.
1 *> \brief \b SCHKPS
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 SCHKPS( DOTYPE, NN, NVAL, NNB, NBVAL, NRANK, RANKVAL,
12 * THRESH, TSTERR, NMAX, A, AFAC, PERM, PIV, WORK,
13 * RWORK, NOUT )
14 *
15 * .. Scalar Arguments ..
16 * REAL THRESH
17 * INTEGER NMAX, NN, NNB, NOUT, NRANK
18 * LOGICAL TSTERR
19 * ..
20 * .. Array Arguments ..
21 * REAL A( * ), AFAC( * ), PERM( * ), RWORK( * ),
22 * $ WORK( * )
23 * INTEGER NBVAL( * ), NVAL( * ), PIV( * ), RANKVAL( * )
24 * LOGICAL DOTYPE( * )
25 * ..
26 *
27 *
28 *> \par Purpose:
29 * =============
30 *>
31 *> \verbatim
32 *>
33 *> SCHKPS tests SPSTRF.
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] NNB
60 *> \verbatim
61 *> NNB is INTEGER
62 *> The number of values of NB contained in the vector NBVAL.
63 *> \endverbatim
64 *>
65 *> \param[in] NBVAL
66 *> \verbatim
67 *> NBVAL is INTEGER array, dimension (NBVAL)
68 *> The values of the block size NB.
69 *> \endverbatim
70 *>
71 *> \param[in] NRANK
72 *> \verbatim
73 *> NRANK is INTEGER
74 *> The number of values of RANK contained in the vector RANKVAL.
75 *> \endverbatim
76 *>
77 *> \param[in] RANKVAL
78 *> \verbatim
79 *> RANKVAL is INTEGER array, dimension (NBVAL)
80 *> The values of the block size NB.
81 *> \endverbatim
82 *>
83 *> \param[in] THRESH
84 *> \verbatim
85 *> THRESH is REAL
86 *> The threshold value for the test ratios. A result is
87 *> included in the output file if RESULT >= THRESH. To have
88 *> every test ratio printed, use THRESH = 0.
89 *> \endverbatim
90 *>
91 *> \param[in] TSTERR
92 *> \verbatim
93 *> TSTERR is LOGICAL
94 *> Flag that indicates whether error exits are to be tested.
95 *> \endverbatim
96 *>
97 *> \param[in] NMAX
98 *> \verbatim
99 *> NMAX is INTEGER
100 *> The maximum value permitted for N, used in dimensioning the
101 *> work arrays.
102 *> \endverbatim
103 *>
104 *> \param[out] A
105 *> \verbatim
106 *> A is REAL array, dimension (NMAX*NMAX)
107 *> \endverbatim
108 *>
109 *> \param[out] AFAC
110 *> \verbatim
111 *> AFAC is REAL array, dimension (NMAX*NMAX)
112 *> \endverbatim
113 *>
114 *> \param[out] PERM
115 *> \verbatim
116 *> PERM is REAL array, dimension (NMAX*NMAX)
117 *> \endverbatim
118 *>
119 *> \param[out] PIV
120 *> \verbatim
121 *> PIV is INTEGER array, dimension (NMAX)
122 *> \endverbatim
123 *>
124 *> \param[out] WORK
125 *> \verbatim
126 *> WORK is REAL array, dimension (NMAX*3)
127 *> \endverbatim
128 *>
129 *> \param[out] RWORK
130 *> \verbatim
131 *> RWORK is REAL array, dimension (NMAX)
132 *> \endverbatim
133 *>
134 *> \param[in] NOUT
135 *> \verbatim
136 *> NOUT is INTEGER
137 *> The unit number for output.
138 *> \endverbatim
139 *
140 * Authors:
141 * ========
142 *
143 *> \author Univ. of Tennessee
144 *> \author Univ. of California Berkeley
145 *> \author Univ. of Colorado Denver
146 *> \author NAG Ltd.
147 *
148 *> \date November 2011
149 *
150 *> \ingroup single_lin
151 *
152 * =====================================================================
153  SUBROUTINE schkps( DOTYPE, NN, NVAL, NNB, NBVAL, NRANK, RANKVAL,
154  $ thresh, tsterr, nmax, a, afac, perm, piv, work,
155  $ rwork, nout )
156 *
157 * -- LAPACK test routine (version 3.4.0) --
158 * -- LAPACK is a software package provided by Univ. of Tennessee, --
159 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
160 * November 2011
161 *
162 * .. Scalar Arguments ..
163  REAL thresh
164  INTEGER nmax, nn, nnb, nout, nrank
165  LOGICAL tsterr
166 * ..
167 * .. Array Arguments ..
168  REAL a( * ), afac( * ), perm( * ), rwork( * ),
169  $ work( * )
170  INTEGER nbval( * ), nval( * ), piv( * ), rankval( * )
171  LOGICAL dotype( * )
172 * ..
173 *
174 * =====================================================================
175 *
176 * .. Parameters ..
177  REAL one
178  parameter( one = 1.0e+0 )
179  INTEGER ntypes
180  parameter( ntypes = 9 )
181 * ..
182 * .. Local Scalars ..
183  REAL anorm, cndnum, result, tol
184  INTEGER comprank, i, imat, in, inb, info, irank, iuplo,
185  $ izero, kl, ku, lda, mode, n, nb, nerrs, nfail,
186  $ nimat, nrun, rank, rankdiff
187  CHARACTER dist, type, uplo
188  CHARACTER*3 path
189 * ..
190 * .. Local Arrays ..
191  INTEGER iseed( 4 ), iseedy( 4 )
192  CHARACTER uplos( 2 )
193 * ..
194 * .. External Subroutines ..
195  EXTERNAL alaerh, alahd, alasum, serrps, slacpy, slatb5,
197 * ..
198 * .. Scalars in Common ..
199  INTEGER infot, nunit
200  LOGICAL lerr, ok
201  CHARACTER*32 srnamt
202 * ..
203 * .. Common blocks ..
204  common / infoc / infot, nunit, ok, lerr
205  common / srnamc / srnamt
206 * ..
207 * .. Intrinsic Functions ..
208  INTRINSIC max, REAL, ceiling
209 * ..
210 * .. Data statements ..
211  DATA iseedy / 1988, 1989, 1990, 1991 /
212  DATA uplos / 'U', 'L' /
213 * ..
214 * .. Executable Statements ..
215 *
216 * Initialize constants and the random number seed.
217 *
218  path( 1: 1 ) = 'Single Precision'
219  path( 2: 3 ) = 'PS'
220  nrun = 0
221  nfail = 0
222  nerrs = 0
223  DO 100 i = 1, 4
224  iseed( i ) = iseedy( i )
225  100 continue
226 *
227 * Test the error exits
228 *
229  IF( tsterr )
230  $ CALL serrps( path, nout )
231  infot = 0
232  CALL xlaenv( 2, 2 )
233 *
234 * Do for each value of N in NVAL
235 *
236  DO 150 in = 1, nn
237  n = nval( in )
238  lda = max( n, 1 )
239  nimat = ntypes
240  IF( n.LE.0 )
241  $ nimat = 1
242 *
243  izero = 0
244  DO 140 imat = 1, nimat
245 *
246 * Do the tests only if DOTYPE( IMAT ) is true.
247 *
248  IF( .NOT.dotype( imat ) )
249  $ go to 140
250 *
251 * Do for each value of RANK in RANKVAL
252 *
253  DO 130 irank = 1, nrank
254 *
255 * Only repeat test 3 to 5 for different ranks
256 * Other tests use full rank
257 *
258  IF( ( imat.LT.3 .OR. imat.GT.5 ) .AND. irank.GT.1 )
259  $ go to 130
260 *
261  rank = ceiling( ( n * REAL( RANKVAL( IRANK ) ) )
262  $ / 100.e+0 )
263 *
264 *
265 * Do first for UPLO = 'U', then for UPLO = 'L'
266 *
267  DO 120 iuplo = 1, 2
268  uplo = uplos( iuplo )
269 *
270 * Set up parameters with SLATB5 and generate a test matrix
271 * with SLATMT.
272 *
273  CALL slatb5( path, imat, n, type, kl, ku, anorm,
274  $ mode, cndnum, dist )
275 *
276  srnamt = 'SLATMT'
277  CALL slatmt( n, n, dist, iseed, type, rwork, mode,
278  $ cndnum, anorm, rank, kl, ku, uplo, a,
279  $ lda, work, info )
280 *
281 * Check error code from SLATMT.
282 *
283  IF( info.NE.0 ) THEN
284  CALL alaerh( path, 'SLATMT', info, 0, uplo, n,
285  $ n, -1, -1, -1, imat, nfail, nerrs,
286  $ nout )
287  go to 120
288  END IF
289 *
290 * Do for each value of NB in NBVAL
291 *
292  DO 110 inb = 1, nnb
293  nb = nbval( inb )
294  CALL xlaenv( 1, nb )
295 *
296 * Compute the pivoted L*L' or U'*U factorization
297 * of the matrix.
298 *
299  CALL slacpy( uplo, n, n, a, lda, afac, lda )
300  srnamt = 'SPSTRF'
301 *
302 * Use default tolerance
303 *
304  tol = -one
305  CALL spstrf( uplo, n, afac, lda, piv, comprank,
306  $ tol, work, info )
307 *
308 * Check error code from SPSTRF.
309 *
310  IF( (info.LT.izero)
311  $ .OR.(info.NE.izero.AND.rank.EQ.n)
312  $ .OR.(info.LE.izero.AND.rank.LT.n) ) THEN
313  CALL alaerh( path, 'SPSTRF', info, izero,
314  $ uplo, n, n, -1, -1, nb, imat,
315  $ nfail, nerrs, nout )
316  go to 110
317  END IF
318 *
319 * Skip the test if INFO is not 0.
320 *
321  IF( info.NE.0 )
322  $ go to 110
323 *
324 * Reconstruct matrix from factors and compute residual.
325 *
326 * PERM holds permuted L*L^T or U^T*U
327 *
328  CALL spst01( uplo, n, a, lda, afac, lda, perm, lda,
329  $ piv, rwork, result, comprank )
330 *
331 * Print information about the tests that did not pass
332 * the threshold or where computed rank was not RANK.
333 *
334  IF( n.EQ.0 )
335  $ comprank = 0
336  rankdiff = rank - comprank
337  IF( result.GE.thresh ) THEN
338  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
339  $ CALL alahd( nout, path )
340  WRITE( nout, fmt = 9999 )uplo, n, rank,
341  $ rankdiff, nb, imat, result
342  nfail = nfail + 1
343  END IF
344  nrun = nrun + 1
345  110 continue
346 *
347  120 continue
348  130 continue
349  140 continue
350  150 continue
351 *
352 * Print a summary of the results.
353 *
354  CALL alasum( path, nout, nfail, nrun, nerrs )
355 *
356  9999 format( ' UPLO = ''', a1, ''', N =', i5, ', RANK =', i3,
357  $ ', Diff =', i5, ', NB =', i4, ', type ', i2, ', Ratio =',
358  $ g12.5 )
359  return
360 *
361 * End of SCHKPS
362 *
363  END