LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zchktz.f
Go to the documentation of this file.
1 *> \brief \b ZCHKTZ
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 ZCHKTZ( DOTYPE, NM, MVAL, NN, NVAL, THRESH, TSTERR, A,
12 * COPYA, S, TAU, WORK, RWORK, 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 S( * ), RWORK( * )
23 * COMPLEX*16 A( * ), COPYA( * ), TAU( * ), WORK( * )
24 * ..
25 *
26 *
27 *> \par Purpose:
28 * =============
29 *>
30 *> \verbatim
31 *>
32 *> ZCHKTZ tests ZTZRQF and ZTZRZF.
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 COMPLEX*16 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 COMPLEX*16 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 COMPLEX*16 array, dimension (MMAX)
105 *> \endverbatim
106 *>
107 *> \param[out] WORK
108 *> \verbatim
109 *> WORK is COMPLEX*16 array, dimension
110 *> (MMAX*NMAX + 4*NMAX + MMAX)
111 *> \endverbatim
112 *>
113 *> \param[out] RWORK
114 *> \verbatim
115 *> RWORK is DOUBLE PRECISION array, dimension (2*NMAX)
116 *> \endverbatim
117 *>
118 *> \param[in] NOUT
119 *> \verbatim
120 *> NOUT is INTEGER
121 *> The unit number for output.
122 *> \endverbatim
123 *
124 * Authors:
125 * ========
126 *
127 *> \author Univ. of Tennessee
128 *> \author Univ. of California Berkeley
129 *> \author Univ. of Colorado Denver
130 *> \author NAG Ltd.
131 *
132 *> \date November 2011
133 *
134 *> \ingroup complex16_lin
135 *
136 * =====================================================================
137  SUBROUTINE zchktz( DOTYPE, NM, MVAL, NN, NVAL, THRESH, TSTERR, A,
138  $ copya, s, tau, work, rwork, nout )
139 *
140 * -- LAPACK test routine (version 3.4.0) --
141 * -- LAPACK is a software package provided by Univ. of Tennessee, --
142 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
143 * November 2011
144 *
145 * .. Scalar Arguments ..
146  LOGICAL tsterr
147  INTEGER nm, nn, nout
148  DOUBLE PRECISION thresh
149 * ..
150 * .. Array Arguments ..
151  LOGICAL dotype( * )
152  INTEGER mval( * ), nval( * )
153  DOUBLE PRECISION s( * ), rwork( * )
154  COMPLEX*16 a( * ), copya( * ), tau( * ), work( * )
155 * ..
156 *
157 * =====================================================================
158 *
159 * .. Parameters ..
160  INTEGER ntypes
161  parameter( ntypes = 3 )
162  INTEGER ntests
163  parameter( ntests = 6 )
164  DOUBLE PRECISION one, zero
165  parameter( one = 1.0d0, zero = 0.0d0 )
166 * ..
167 * .. Local Scalars ..
168  CHARACTER*3 path
169  INTEGER i, im, imode, in, info, k, lda, lwork, m,
170  $ mnmin, mode, n, nerrs, nfail, nrun
171  DOUBLE PRECISION eps
172 * ..
173 * .. Local Arrays ..
174  INTEGER iseed( 4 ), iseedy( 4 )
175  DOUBLE PRECISION result( ntests )
176 * ..
177 * .. External Functions ..
178  DOUBLE PRECISION dlamch, zqrt12, zrzt01, zrzt02, ztzt01, ztzt02
179  EXTERNAL dlamch, zqrt12, zrzt01, zrzt02, ztzt01, ztzt02
180 * ..
181 * .. External Subroutines ..
182  EXTERNAL alahd, alasum, dlaord, zerrtz, zgeqr2, zlacpy,
184 * ..
185 * .. Intrinsic Functions ..
186  INTRINSIC dcmplx, max, min
187 * ..
188 * .. Scalars in Common ..
189  LOGICAL lerr, ok
190  CHARACTER*32 srnamt
191  INTEGER infot, iounit
192 * ..
193 * .. Common blocks ..
194  common / infoc / infot, iounit, ok, lerr
195  common / srnamc / srnamt
196 * ..
197 * .. Data statements ..
198  DATA iseedy / 1988, 1989, 1990, 1991 /
199 * ..
200 * .. Executable Statements ..
201 *
202 * Initialize constants and the random number seed.
203 *
204  path( 1: 1 ) = 'Zomplex precision'
205  path( 2: 3 ) = 'TZ'
206  nrun = 0
207  nfail = 0
208  nerrs = 0
209  DO 10 i = 1, 4
210  iseed( i ) = iseedy( i )
211  10 continue
212  eps = dlamch( 'Epsilon' )
213 *
214 * Test the error exits
215 *
216  IF( tsterr )
217  $ CALL zerrtz( path, nout )
218  infot = 0
219 *
220  DO 70 im = 1, nm
221 *
222 * Do for each value of M in MVAL.
223 *
224  m = mval( im )
225  lda = max( 1, m )
226 *
227  DO 60 in = 1, nn
228 *
229 * Do for each value of N in NVAL for which M .LE. N.
230 *
231  n = nval( in )
232  mnmin = min( m, n )
233  lwork = max( 1, n*n+4*m+n )
234 *
235  IF( m.LE.n ) THEN
236  DO 50 imode = 1, ntypes
237  IF( .NOT.dotype( imode ) )
238  $ go to 50
239 *
240 * Do for each type of singular value distribution.
241 * 0: zero matrix
242 * 1: one small singular value
243 * 2: exponential distribution
244 *
245  mode = imode - 1
246 *
247 * Test ZTZRQF
248 *
249 * Generate test matrix of size m by n using
250 * singular value distribution indicated by `mode'.
251 *
252  IF( mode.EQ.0 ) THEN
253  CALL zlaset( 'Full', m, n, dcmplx( zero ),
254  $ dcmplx( zero ), a, lda )
255  DO 20 i = 1, mnmin
256  s( i ) = zero
257  20 continue
258  ELSE
259  CALL zlatms( m, n, 'Uniform', iseed,
260  $ 'Nonsymmetric', s, imode,
261  $ one / eps, one, m, n, 'No packing', a,
262  $ lda, work, info )
263  CALL zgeqr2( m, n, a, lda, work, work( mnmin+1 ),
264  $ info )
265  CALL zlaset( 'Lower', m-1, n, dcmplx( zero ),
266  $ dcmplx( zero ), a( 2 ), lda )
267  CALL dlaord( 'Decreasing', mnmin, s, 1 )
268  END IF
269 *
270 * Save A and its singular values
271 *
272  CALL zlacpy( 'All', m, n, a, lda, copya, lda )
273 *
274 * Call ZTZRQF to reduce the upper trapezoidal matrix to
275 * upper triangular form.
276 *
277  srnamt = 'ZTZRQF'
278  CALL ztzrqf( m, n, a, lda, tau, info )
279 *
280 * Compute norm(svd(a) - svd(r))
281 *
282  result( 1 ) = zqrt12( m, m, a, lda, s, work,
283  $ lwork, rwork )
284 *
285 * Compute norm( A - R*Q )
286 *
287  result( 2 ) = ztzt01( m, n, copya, a, lda, tau, work,
288  $ lwork )
289 *
290 * Compute norm(Q'*Q - I).
291 *
292  result( 3 ) = ztzt02( m, n, a, lda, tau, work, lwork )
293 *
294 * Test ZTZRZF
295 *
296 * Generate test matrix of size m by n using
297 * singular value distribution indicated by `mode'.
298 *
299  IF( mode.EQ.0 ) THEN
300  CALL zlaset( 'Full', m, n, dcmplx( zero ),
301  $ dcmplx( zero ), a, lda )
302  DO 30 i = 1, mnmin
303  s( i ) = zero
304  30 continue
305  ELSE
306  CALL zlatms( m, n, 'Uniform', iseed,
307  $ 'Nonsymmetric', s, imode,
308  $ one / eps, one, m, n, 'No packing', a,
309  $ lda, work, info )
310  CALL zgeqr2( m, n, a, lda, work, work( mnmin+1 ),
311  $ info )
312  CALL zlaset( 'Lower', m-1, n, dcmplx( zero ),
313  $ dcmplx( zero ), a( 2 ), lda )
314  CALL dlaord( 'Decreasing', mnmin, s, 1 )
315  END IF
316 *
317 * Save A and its singular values
318 *
319  CALL zlacpy( 'All', m, n, a, lda, copya, lda )
320 *
321 * Call ZTZRZF to reduce the upper trapezoidal matrix to
322 * upper triangular form.
323 *
324  srnamt = 'ZTZRZF'
325  CALL ztzrzf( m, n, a, lda, tau, work, lwork, info )
326 *
327 * Compute norm(svd(a) - svd(r))
328 *
329  result( 4 ) = zqrt12( m, m, a, lda, s, work,
330  $ lwork, rwork )
331 *
332 * Compute norm( A - R*Q )
333 *
334  result( 5 ) = zrzt01( m, n, copya, a, lda, tau, work,
335  $ lwork )
336 *
337 * Compute norm(Q'*Q - I).
338 *
339  result( 6 ) = zrzt02( m, n, a, lda, tau, work, lwork )
340 *
341 * Print information about the tests that did not pass
342 * the threshold.
343 *
344  DO 40 k = 1, 6
345  IF( result( k ).GE.thresh ) THEN
346  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
347  $ CALL alahd( nout, path )
348  WRITE( nout, fmt = 9999 )m, n, imode, k,
349  $ result( k )
350  nfail = nfail + 1
351  END IF
352  40 continue
353  nrun = nrun + 6
354  50 continue
355  END IF
356  60 continue
357  70 continue
358 *
359 * Print a summary of the results.
360 *
361  CALL alasum( path, nout, nfail, nrun, nerrs )
362 *
363  9999 format( ' M =', i5, ', N =', i5, ', type ', i2, ', test ', i2,
364  $ ', ratio =', g12.5 )
365 *
366 * End if ZCHKTZ
367 *
368  END