LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
dchkq3.f
Go to the documentation of this file.
1 *> \brief \b DCHKQ3
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 DCHKQ3( DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL,
12 * THRESH, A, COPYA, S, TAU, WORK, IWORK,
13 * NOUT )
14 *
15 * .. Scalar Arguments ..
16 * INTEGER NM, NN, NNB, NOUT
17 * DOUBLE PRECISION THRESH
18 * ..
19 * .. Array Arguments ..
20 * LOGICAL DOTYPE( * )
21 * INTEGER IWORK( * ), MVAL( * ), NBVAL( * ), NVAL( * ),
22 * $ NXVAL( * )
23 * DOUBLE PRECISION A( * ), COPYA( * ), S( * ),
24 * $ TAU( * ), WORK( * )
25 * ..
26 *
27 *
28 *> \par Purpose:
29 * =============
30 *>
31 *> \verbatim
32 *>
33 *> DCHKQ3 tests DGEQP3.
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] NM
48 *> \verbatim
49 *> NM is INTEGER
50 *> The number of values of M contained in the vector MVAL.
51 *> \endverbatim
52 *>
53 *> \param[in] MVAL
54 *> \verbatim
55 *> MVAL is INTEGER array, dimension (NM)
56 *> The values of the matrix row dimension M.
57 *> \endverbatim
58 *>
59 *> \param[in] NN
60 *> \verbatim
61 *> NN is INTEGER
62 *> The number of values of N contained in the vector NVAL.
63 *> \endverbatim
64 *>
65 *> \param[in] NVAL
66 *> \verbatim
67 *> NVAL is INTEGER array, dimension (NN)
68 *> The values of the matrix column dimension N.
69 *> \endverbatim
70 *>
71 *> \param[in] NNB
72 *> \verbatim
73 *> NNB is INTEGER
74 *> The number of values of NB and NX contained in the
75 *> vectors NBVAL and NXVAL. The blocking parameters are used
76 *> in pairs (NB,NX).
77 *> \endverbatim
78 *>
79 *> \param[in] NBVAL
80 *> \verbatim
81 *> NBVAL is INTEGER array, dimension (NNB)
82 *> The values of the blocksize NB.
83 *> \endverbatim
84 *>
85 *> \param[in] NXVAL
86 *> \verbatim
87 *> NXVAL is INTEGER array, dimension (NNB)
88 *> The values of the crossover point NX.
89 *> \endverbatim
90 *>
91 *> \param[in] THRESH
92 *> \verbatim
93 *> THRESH is DOUBLE PRECISION
94 *> The threshold value for the test ratios. A result is
95 *> included in the output file if RESULT >= THRESH. To have
96 *> every test ratio printed, use THRESH = 0.
97 *> \endverbatim
98 *>
99 *> \param[out] A
100 *> \verbatim
101 *> A is DOUBLE PRECISION array, dimension (MMAX*NMAX)
102 *> where MMAX is the maximum value of M in MVAL and NMAX is the
103 *> maximum value of N in NVAL.
104 *> \endverbatim
105 *>
106 *> \param[out] COPYA
107 *> \verbatim
108 *> COPYA is DOUBLE PRECISION array, dimension (MMAX*NMAX)
109 *> \endverbatim
110 *>
111 *> \param[out] S
112 *> \verbatim
113 *> S is DOUBLE PRECISION array, dimension
114 *> (min(MMAX,NMAX))
115 *> \endverbatim
116 *>
117 *> \param[out] TAU
118 *> \verbatim
119 *> TAU is DOUBLE PRECISION array, dimension (MMAX)
120 *> \endverbatim
121 *>
122 *> \param[out] WORK
123 *> \verbatim
124 *> WORK is DOUBLE PRECISION array, dimension
125 *> (MMAX*NMAX + 4*NMAX + MMAX)
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 double_lin
150 *
151 * =====================================================================
152  SUBROUTINE dchkq3( DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL,
153  $ thresh, a, copya, s, tau, work, 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  INTEGER NM, NN, NNB, NOUT
163  DOUBLE PRECISION THRESH
164 * ..
165 * .. Array Arguments ..
166  LOGICAL DOTYPE( * )
167  INTEGER IWORK( * ), MVAL( * ), NBVAL( * ), NVAL( * ),
168  $ nxval( * )
169  DOUBLE PRECISION A( * ), COPYA( * ), S( * ),
170  $ tau( * ), work( * )
171 * ..
172 *
173 * =====================================================================
174 *
175 * .. Parameters ..
176  INTEGER NTYPES
177  parameter ( ntypes = 6 )
178  INTEGER NTESTS
179  parameter ( ntests = 3 )
180  DOUBLE PRECISION ONE, ZERO
181  parameter ( one = 1.0d0, zero = 0.0d0 )
182 * ..
183 * .. Local Scalars ..
184  CHARACTER*3 PATH
185  INTEGER I, IHIGH, ILOW, IM, IMODE, IN, INB, INFO,
186  $ istep, k, lda, lw, lwork, m, mnmin, mode, n,
187  $ nb, nerrs, nfail, nrun, nx
188  DOUBLE PRECISION EPS
189 * ..
190 * .. Local Arrays ..
191  INTEGER ISEED( 4 ), ISEEDY( 4 )
192  DOUBLE PRECISION RESULT( ntests )
193 * ..
194 * .. External Functions ..
195  DOUBLE PRECISION DLAMCH, DQPT01, DQRT11, DQRT12
196  EXTERNAL dlamch, dqpt01, dqrt11, dqrt12
197 * ..
198 * .. External Subroutines ..
199  EXTERNAL alahd, alasum, dgeqp3, dlacpy, dlaord, dlaset,
200  $ dlatms, icopy, xlaenv
201 * ..
202 * .. Intrinsic Functions ..
203  INTRINSIC max, min
204 * ..
205 * .. Scalars in Common ..
206  LOGICAL LERR, OK
207  CHARACTER*32 SRNAMT
208  INTEGER INFOT, IOUNIT
209 * ..
210 * .. Common blocks ..
211  COMMON / infoc / infot, iounit, ok, lerr
212  COMMON / srnamc / srnamt
213 * ..
214 * .. Data statements ..
215  DATA iseedy / 1988, 1989, 1990, 1991 /
216 * ..
217 * .. Executable Statements ..
218 *
219 * Initialize constants and the random number seed.
220 *
221  path( 1: 1 ) = 'Double precision'
222  path( 2: 3 ) = 'Q3'
223  nrun = 0
224  nfail = 0
225  nerrs = 0
226  DO 10 i = 1, 4
227  iseed( i ) = iseedy( i )
228  10 CONTINUE
229  eps = dlamch( 'Epsilon' )
230  infot = 0
231 *
232  DO 90 im = 1, nm
233 *
234 * Do for each value of M in MVAL.
235 *
236  m = mval( im )
237  lda = max( 1, m )
238 *
239  DO 80 in = 1, nn
240 *
241 * Do for each value of N in NVAL.
242 *
243  n = nval( in )
244  mnmin = min( m, n )
245  lwork = max( 1, m*max( m, n )+4*mnmin+max( m, n ),
246  $ m*n + 2*mnmin + 4*n )
247 *
248  DO 70 imode = 1, ntypes
249  IF( .NOT.dotype( imode ) )
250  $ GO TO 70
251 *
252 * Do for each type of matrix
253 * 1: zero matrix
254 * 2: one small singular value
255 * 3: geometric distribution of singular values
256 * 4: first n/2 columns fixed
257 * 5: last n/2 columns fixed
258 * 6: every second column fixed
259 *
260  mode = imode
261  IF( imode.GT.3 )
262  $ mode = 1
263 *
264 * Generate test matrix of size m by n using
265 * singular value distribution indicated by `mode'.
266 *
267  DO 20 i = 1, n
268  iwork( i ) = 0
269  20 CONTINUE
270  IF( imode.EQ.1 ) THEN
271  CALL dlaset( 'Full', m, n, zero, zero, copya, lda )
272  DO 30 i = 1, mnmin
273  s( i ) = zero
274  30 CONTINUE
275  ELSE
276  CALL dlatms( m, n, 'Uniform', iseed, 'Nonsymm', s,
277  $ mode, one / eps, one, m, n, 'No packing',
278  $ copya, lda, work, info )
279  IF( imode.GE.4 ) THEN
280  IF( imode.EQ.4 ) THEN
281  ilow = 1
282  istep = 1
283  ihigh = max( 1, n / 2 )
284  ELSE IF( imode.EQ.5 ) THEN
285  ilow = max( 1, n / 2 )
286  istep = 1
287  ihigh = n
288  ELSE IF( imode.EQ.6 ) THEN
289  ilow = 1
290  istep = 2
291  ihigh = n
292  END IF
293  DO 40 i = ilow, ihigh, istep
294  iwork( i ) = 1
295  40 CONTINUE
296  END IF
297  CALL dlaord( 'Decreasing', mnmin, s, 1 )
298  END IF
299 *
300  DO 60 inb = 1, nnb
301 *
302 * Do for each pair of values (NB,NX) in NBVAL and NXVAL.
303 *
304  nb = nbval( inb )
305  CALL xlaenv( 1, nb )
306  nx = nxval( inb )
307  CALL xlaenv( 3, nx )
308 *
309 * Get a working copy of COPYA into A and a copy of
310 * vector IWORK.
311 *
312  CALL dlacpy( 'All', m, n, copya, lda, a, lda )
313  CALL icopy( n, iwork( 1 ), 1, iwork( n+1 ), 1 )
314 *
315 * Compute the QR factorization with pivoting of A
316 *
317  lw = max( 1, 2*n+nb*( n+1 ) )
318 *
319 * Compute the QP3 factorization of A
320 *
321  srnamt = 'DGEQP3'
322  CALL dgeqp3( m, n, a, lda, iwork( n+1 ), tau, work,
323  $ lw, info )
324 *
325 * Compute norm(svd(a) - svd(r))
326 *
327  result( 1 ) = dqrt12( m, n, a, lda, s, work,
328  $ lwork )
329 *
330 * Compute norm( A*P - Q*R )
331 *
332  result( 2 ) = dqpt01( m, n, mnmin, copya, a, lda, tau,
333  $ iwork( n+1 ), work, lwork )
334 *
335 * Compute Q'*Q
336 *
337  result( 3 ) = dqrt11( m, mnmin, a, lda, tau, work,
338  $ lwork )
339 *
340 * Print information about the tests that did not pass
341 * the threshold.
342 *
343  DO 50 k = 1, ntests
344  IF( result( k ).GE.thresh ) THEN
345  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
346  $ CALL alahd( nout, path )
347  WRITE( nout, fmt = 9999 )'DGEQP3', m, n, nb,
348  $ imode, k, result( k )
349  nfail = nfail + 1
350  END IF
351  50 CONTINUE
352  nrun = nrun + ntests
353 *
354  60 CONTINUE
355  70 CONTINUE
356  80 CONTINUE
357  90 CONTINUE
358 *
359 * Print a summary of the results.
360 *
361  CALL alasum( path, nout, nfail, nrun, nerrs )
362 *
363  9999 FORMAT( 1x, a, ' M =', i5, ', N =', i5, ', NB =', i4, ', type ',
364  $ i2, ', test ', i2, ', ratio =', g12.5 )
365 *
366 * End of DCHKQ3
367 *
368  END
subroutine dlaset(UPLO, M, N, ALPHA, BETA, A, LDA)
DLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values...
Definition: dlaset.f:112
subroutine alahd(IOUNIT, PATH)
ALAHD
Definition: alahd.f:95
subroutine icopy(N, SX, INCX, SY, INCY)
ICOPY
Definition: icopy.f:77
subroutine dgeqp3(M, N, A, LDA, JPVT, TAU, WORK, LWORK, INFO)
DGEQP3
Definition: dgeqp3.f:153
subroutine dlacpy(UPLO, M, N, A, LDA, B, LDB)
DLACPY copies all or part of one two-dimensional array to another.
Definition: dlacpy.f:105
subroutine dlaord(JOB, N, X, INCX)
DLAORD
Definition: dlaord.f:75
subroutine xlaenv(ISPEC, NVALUE)
XLAENV
Definition: xlaenv.f:83
subroutine dchkq3(DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL, THRESH, A, COPYA, S, TAU, WORK, IWORK, NOUT)
DCHKQ3
Definition: dchkq3.f:155
subroutine dlatms(M, N, DIST, ISEED, SYM, D, MODE, COND, DMAX, KL, KU, PACK, A, LDA, WORK, INFO)
DLATMS
Definition: dlatms.f:323
subroutine alasum(TYPE, NOUT, NFAIL, NRUN, NERRS)
ALASUM
Definition: alasum.f:75