LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
dchktz.f
Go to the documentation of this file.
1 *> \brief \b DCHKTZ
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 DCHKTZ( DOTYPE, NM, MVAL, NN, NVAL, THRESH, TSTERR, A,
12 * COPYA, S, TAU, WORK, NOUT )
13 *
14 * .. Scalar Arguments ..
15 * LOGICAL TSTERR
16 * INTEGER NM, NN, NOUT
17 * DOUBLE PRECISION THRESH
18 * ..
19 * .. Array Arguments ..
20 * LOGICAL DOTYPE( * )
21 * INTEGER MVAL( * ), NVAL( * )
22 * DOUBLE PRECISION A( * ), COPYA( * ), S( * ),
23 * $ TAU( * ), WORK( * )
24 * ..
25 *
26 *
27 *> \par Purpose:
28 * =============
29 *>
30 *> \verbatim
31 *>
32 *> DCHKTZ tests DTZRQF and STZRZF.
33 *> \endverbatim
34 *
35 * Arguments:
36 * ==========
37 *
38 *> \param[in] DOTYPE
39 *> \verbatim
40 *> DOTYPE is LOGICAL array, dimension (NTYPES)
41 *> The matrix types to be used for testing. Matrices of type j
42 *> (for 1 <= j <= NTYPES) are used for testing if DOTYPE(j) =
43 *> .TRUE.; if DOTYPE(j) = .FALSE., then type j is not used.
44 *> \endverbatim
45 *>
46 *> \param[in] NM
47 *> \verbatim
48 *> NM is INTEGER
49 *> The number of values of M contained in the vector MVAL.
50 *> \endverbatim
51 *>
52 *> \param[in] MVAL
53 *> \verbatim
54 *> MVAL is INTEGER array, dimension (NM)
55 *> The values of the matrix row dimension M.
56 *> \endverbatim
57 *>
58 *> \param[in] NN
59 *> \verbatim
60 *> NN is INTEGER
61 *> The number of values of N contained in the vector NVAL.
62 *> \endverbatim
63 *>
64 *> \param[in] NVAL
65 *> \verbatim
66 *> NVAL is INTEGER array, dimension (NN)
67 *> The values of the matrix column dimension N.
68 *> \endverbatim
69 *>
70 *> \param[in] THRESH
71 *> \verbatim
72 *> THRESH is DOUBLE PRECISION
73 *> The threshold value for the test ratios. A result is
74 *> included in the output file if RESULT >= THRESH. To have
75 *> every test ratio printed, use THRESH = 0.
76 *> \endverbatim
77 *>
78 *> \param[in] TSTERR
79 *> \verbatim
80 *> TSTERR is LOGICAL
81 *> Flag that indicates whether error exits are to be tested.
82 *> \endverbatim
83 *>
84 *> \param[out] A
85 *> \verbatim
86 *> A is DOUBLE PRECISION array, dimension (MMAX*NMAX)
87 *> where MMAX is the maximum value of M in MVAL and NMAX is the
88 *> maximum value of N in NVAL.
89 *> \endverbatim
90 *>
91 *> \param[out] COPYA
92 *> \verbatim
93 *> COPYA is DOUBLE PRECISION array, dimension (MMAX*NMAX)
94 *> \endverbatim
95 *>
96 *> \param[out] S
97 *> \verbatim
98 *> S is DOUBLE PRECISION array, dimension
99 *> (min(MMAX,NMAX))
100 *> \endverbatim
101 *>
102 *> \param[out] TAU
103 *> \verbatim
104 *> TAU is DOUBLE PRECISION array, dimension (MMAX)
105 *> \endverbatim
106 *>
107 *> \param[out] WORK
108 *> \verbatim
109 *> WORK is DOUBLE PRECISION array, dimension
110 *> (MMAX*NMAX + 4*NMAX + MMAX)
111 *> \endverbatim
112 *>
113 *> \param[in] NOUT
114 *> \verbatim
115 *> NOUT is INTEGER
116 *> The unit number for output.
117 *> \endverbatim
118 *
119 * Authors:
120 * ========
121 *
122 *> \author Univ. of Tennessee
123 *> \author Univ. of California Berkeley
124 *> \author Univ. of Colorado Denver
125 *> \author NAG Ltd.
126 *
127 *> \date November 2011
128 *
129 *> \ingroup double_lin
130 *
131 * =====================================================================
132  SUBROUTINE dchktz( DOTYPE, NM, MVAL, NN, NVAL, THRESH, TSTERR, A,
133  $ copya, s, tau, work, nout )
134 *
135 * -- LAPACK test routine (version 3.4.0) --
136 * -- LAPACK is a software package provided by Univ. of Tennessee, --
137 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
138 * November 2011
139 *
140 * .. Scalar Arguments ..
141  LOGICAL tsterr
142  INTEGER nm, nn, nout
143  DOUBLE PRECISION thresh
144 * ..
145 * .. Array Arguments ..
146  LOGICAL dotype( * )
147  INTEGER mval( * ), nval( * )
148  DOUBLE PRECISION a( * ), copya( * ), s( * ),
149  $ tau( * ), work( * )
150 * ..
151 *
152 * =====================================================================
153 *
154 * .. Parameters ..
155  INTEGER ntypes
156  parameter( ntypes = 3 )
157  INTEGER ntests
158  parameter( ntests = 6 )
159  DOUBLE PRECISION one, zero
160  parameter( one = 1.0d0, zero = 0.0d0 )
161 * ..
162 * .. Local Scalars ..
163  CHARACTER*3 path
164  INTEGER i, im, imode, in, info, k, lda, lwork, m,
165  $ mnmin, mode, n, nerrs, nfail, nrun
166  DOUBLE PRECISION eps
167 * ..
168 * .. Local Arrays ..
169  INTEGER iseed( 4 ), iseedy( 4 )
170  DOUBLE PRECISION result( ntests )
171 * ..
172 * .. External Functions ..
173  DOUBLE PRECISION dlamch, dqrt12, drzt01, drzt02, dtzt01, dtzt02
174  EXTERNAL dlamch, dqrt12, drzt01, drzt02, dtzt01, dtzt02
175 * ..
176 * .. External Subroutines ..
177  EXTERNAL alahd, alasum, derrtz, dgeqr2, dlacpy, dlaord,
179 * ..
180 * .. Intrinsic Functions ..
181  INTRINSIC max, min
182 * ..
183 * .. Scalars in Common ..
184  LOGICAL lerr, ok
185  CHARACTER*32 srnamt
186  INTEGER infot, iounit
187 * ..
188 * .. Common blocks ..
189  common / infoc / infot, iounit, ok, lerr
190  common / srnamc / srnamt
191 * ..
192 * .. Data statements ..
193  DATA iseedy / 1988, 1989, 1990, 1991 /
194 * ..
195 * .. Executable Statements ..
196 *
197 * Initialize constants and the random number seed.
198 *
199  path( 1: 1 ) = 'Double precision'
200  path( 2: 3 ) = 'TZ'
201  nrun = 0
202  nfail = 0
203  nerrs = 0
204  DO 10 i = 1, 4
205  iseed( i ) = iseedy( i )
206  10 continue
207  eps = dlamch( 'Epsilon' )
208 *
209 * Test the error exits
210 *
211  IF( tsterr )
212  $ CALL derrtz( path, nout )
213  infot = 0
214 *
215  DO 70 im = 1, nm
216 *
217 * Do for each value of M in MVAL.
218 *
219  m = mval( im )
220  lda = max( 1, m )
221 *
222  DO 60 in = 1, nn
223 *
224 * Do for each value of N in NVAL for which M .LE. N.
225 *
226  n = nval( in )
227  mnmin = min( m, n )
228  lwork = max( 1, n*n+4*m+n, m*n+2*mnmin+4*n )
229 *
230  IF( m.LE.n ) THEN
231  DO 50 imode = 1, ntypes
232  IF( .NOT.dotype( imode ) )
233  $ go to 50
234 *
235 * Do for each type of singular value distribution.
236 * 0: zero matrix
237 * 1: one small singular value
238 * 2: exponential distribution
239 *
240  mode = imode - 1
241 *
242 * Test DTZRQF
243 *
244 * Generate test matrix of size m by n using
245 * singular value distribution indicated by `mode'.
246 *
247  IF( mode.EQ.0 ) THEN
248  CALL dlaset( 'Full', m, n, zero, zero, a, lda )
249  DO 20 i = 1, mnmin
250  s( i ) = zero
251  20 continue
252  ELSE
253  CALL dlatms( m, n, 'Uniform', iseed,
254  $ 'Nonsymmetric', s, imode,
255  $ one / eps, one, m, n, 'No packing', a,
256  $ lda, work, info )
257  CALL dgeqr2( m, n, a, lda, work, work( mnmin+1 ),
258  $ info )
259  CALL dlaset( 'Lower', m-1, n, zero, zero, a( 2 ),
260  $ lda )
261  CALL dlaord( 'Decreasing', mnmin, s, 1 )
262  END IF
263 *
264 * Save A and its singular values
265 *
266  CALL dlacpy( 'All', m, n, a, lda, copya, lda )
267 *
268 * Call DTZRQF to reduce the upper trapezoidal matrix to
269 * upper triangular form.
270 *
271  srnamt = 'DTZRQF'
272  CALL dtzrqf( m, n, a, lda, tau, info )
273 *
274 * Compute norm(svd(a) - svd(r))
275 *
276  result( 1 ) = dqrt12( m, m, a, lda, s, work,
277  $ lwork )
278 *
279 * Compute norm( A - R*Q )
280 *
281  result( 2 ) = dtzt01( m, n, copya, a, lda, tau, work,
282  $ lwork )
283 *
284 * Compute norm(Q'*Q - I).
285 *
286  result( 3 ) = dtzt02( m, n, a, lda, tau, work, lwork )
287 *
288 * Test DTZRZF
289 *
290 * Generate test matrix of size m by n using
291 * singular value distribution indicated by `mode'.
292 *
293  IF( mode.EQ.0 ) THEN
294  CALL dlaset( 'Full', m, n, zero, zero, a, lda )
295  DO 30 i = 1, mnmin
296  s( i ) = zero
297  30 continue
298  ELSE
299  CALL dlatms( m, n, 'Uniform', iseed,
300  $ 'Nonsymmetric', s, imode,
301  $ one / eps, one, m, n, 'No packing', a,
302  $ lda, work, info )
303  CALL dgeqr2( m, n, a, lda, work, work( mnmin+1 ),
304  $ info )
305  CALL dlaset( 'Lower', m-1, n, zero, zero, a( 2 ),
306  $ lda )
307  CALL dlaord( 'Decreasing', mnmin, s, 1 )
308  END IF
309 *
310 * Save A and its singular values
311 *
312  CALL dlacpy( 'All', m, n, a, lda, copya, lda )
313 *
314 * Call DTZRZF to reduce the upper trapezoidal matrix to
315 * upper triangular form.
316 *
317  srnamt = 'DTZRZF'
318  CALL dtzrzf( m, n, a, lda, tau, work, lwork, info )
319 *
320 * Compute norm(svd(a) - svd(r))
321 *
322  result( 4 ) = dqrt12( m, m, a, lda, s, work,
323  $ lwork )
324 *
325 * Compute norm( A - R*Q )
326 *
327  result( 5 ) = drzt01( m, n, copya, a, lda, tau, work,
328  $ lwork )
329 *
330 * Compute norm(Q'*Q - I).
331 *
332  result( 6 ) = drzt02( m, n, a, lda, tau, work, lwork )
333 *
334 * Print information about the tests that did not pass
335 * the threshold.
336 *
337  DO 40 k = 1, 6
338  IF( result( k ).GE.thresh ) THEN
339  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
340  $ CALL alahd( nout, path )
341  WRITE( nout, fmt = 9999 )m, n, imode, k,
342  $ result( k )
343  nfail = nfail + 1
344  END IF
345  40 continue
346  nrun = nrun + 6
347  50 continue
348  END IF
349  60 continue
350  70 continue
351 *
352 * Print a summary of the results.
353 *
354  CALL alasum( path, nout, nfail, nrun, nerrs )
355 *
356  9999 format( ' M =', i5, ', N =', i5, ', type ', i2, ', test ', i2,
357  $ ', ratio =', g12.5 )
358 *
359 * End if DCHKTZ
360 *
361  END