LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
dckgqr.f
Go to the documentation of this file.
1 *> \brief \b DCKGQR
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 DCKGQR( NM, MVAL, NP, PVAL, NN, NVAL, NMATS, ISEED,
12 * THRESH, NMAX, A, AF, AQ, AR, TAUA, B, BF, BZ,
13 * BT, BWK, TAUB, WORK, RWORK, NIN, NOUT, INFO )
14 *
15 * .. Scalar Arguments ..
16 * INTEGER INFO, NIN, NM, NMATS, NMAX, NN, NOUT, NP
17 * DOUBLE PRECISION THRESH
18 * ..
19 * .. Array Arguments ..
20 * INTEGER ISEED( 4 ), MVAL( * ), NVAL( * ), PVAL( * )
21 * DOUBLE PRECISION A( * ), AF( * ), AQ( * ), AR( * ), B( * ),
22 * $ BF( * ), BT( * ), BWK( * ), BZ( * ),
23 * $ RWORK( * ), TAUA( * ), TAUB( * ), WORK( * )
24 * ..
25 *
26 *
27 *> \par Purpose:
28 * =============
29 *>
30 *> \verbatim
31 *>
32 *> DCKGQR tests
33 *> DGGQRF: GQR factorization for N-by-M matrix A and N-by-P matrix B,
34 *> DGGRQF: GRQ factorization for M-by-N matrix A and P-by-N matrix B.
35 *> \endverbatim
36 *
37 * Arguments:
38 * ==========
39 *
40 *> \param[in] NM
41 *> \verbatim
42 *> NM is INTEGER
43 *> The number of values of M contained in the vector MVAL.
44 *> \endverbatim
45 *>
46 *> \param[in] MVAL
47 *> \verbatim
48 *> MVAL is INTEGER array, dimension (NM)
49 *> The values of the matrix row(column) dimension M.
50 *> \endverbatim
51 *>
52 *> \param[in] NP
53 *> \verbatim
54 *> NP is INTEGER
55 *> The number of values of P contained in the vector PVAL.
56 *> \endverbatim
57 *>
58 *> \param[in] PVAL
59 *> \verbatim
60 *> PVAL is INTEGER array, dimension (NP)
61 *> The values of the matrix row(column) dimension P.
62 *> \endverbatim
63 *>
64 *> \param[in] NN
65 *> \verbatim
66 *> NN is INTEGER
67 *> The number of values of N contained in the vector NVAL.
68 *> \endverbatim
69 *>
70 *> \param[in] NVAL
71 *> \verbatim
72 *> NVAL is INTEGER array, dimension (NN)
73 *> The values of the matrix column(row) dimension N.
74 *> \endverbatim
75 *>
76 *> \param[in] NMATS
77 *> \verbatim
78 *> NMATS is INTEGER
79 *> The number of matrix types to be tested for each combination
80 *> of matrix dimensions. If NMATS >= NTYPES (the maximum
81 *> number of matrix types), then all the different types are
82 *> generated for testing. If NMATS < NTYPES, another input line
83 *> is read to get the numbers of the matrix types to be used.
84 *> \endverbatim
85 *>
86 *> \param[in,out] ISEED
87 *> \verbatim
88 *> ISEED is INTEGER array, dimension (4)
89 *> On entry, the seed of the random number generator. The array
90 *> elements should be between 0 and 4095, otherwise they will be
91 *> reduced mod 4096, and ISEED(4) must be odd.
92 *> On exit, the next seed in the random number sequence after
93 *> all the test matrices have been generated.
94 *> \endverbatim
95 *>
96 *> \param[in] THRESH
97 *> \verbatim
98 *> THRESH is DOUBLE PRECISION
99 *> The threshold value for the test ratios. A result is
100 *> included in the output file if RESULT >= THRESH. To have
101 *> every test ratio printed, use THRESH = 0.
102 *> \endverbatim
103 *>
104 *> \param[in] NMAX
105 *> \verbatim
106 *> NMAX is INTEGER
107 *> The maximum value permitted for M or N, used in dimensioning
108 *> the work arrays.
109 *> \endverbatim
110 *>
111 *> \param[out] A
112 *> \verbatim
113 *> A is DOUBLE PRECISION array, dimension (NMAX*NMAX)
114 *> \endverbatim
115 *>
116 *> \param[out] AF
117 *> \verbatim
118 *> AF is DOUBLE PRECISION array, dimension (NMAX*NMAX)
119 *> \endverbatim
120 *>
121 *> \param[out] AQ
122 *> \verbatim
123 *> AQ is DOUBLE PRECISION array, dimension (NMAX*NMAX)
124 *> \endverbatim
125 *>
126 *> \param[out] AR
127 *> \verbatim
128 *> AR is DOUBLE PRECISION array, dimension (NMAX*NMAX)
129 *> \endverbatim
130 *>
131 *> \param[out] TAUA
132 *> \verbatim
133 *> TAUA is DOUBLE PRECISION array, dimension (NMAX)
134 *> \endverbatim
135 *>
136 *> \param[out] B
137 *> \verbatim
138 *> B is DOUBLE PRECISION array, dimension (NMAX*NMAX)
139 *> \endverbatim
140 *>
141 *> \param[out] BF
142 *> \verbatim
143 *> BF is DOUBLE PRECISION array, dimension (NMAX*NMAX)
144 *> \endverbatim
145 *>
146 *> \param[out] BZ
147 *> \verbatim
148 *> BZ is DOUBLE PRECISION array, dimension (NMAX*NMAX)
149 *> \endverbatim
150 *>
151 *> \param[out] BT
152 *> \verbatim
153 *> BT is DOUBLE PRECISION array, dimension (NMAX*NMAX)
154 *> \endverbatim
155 *>
156 *> \param[out] BWK
157 *> \verbatim
158 *> BWK is DOUBLE PRECISION array, dimension (NMAX*NMAX)
159 *> \endverbatim
160 *>
161 *> \param[out] TAUB
162 *> \verbatim
163 *> TAUB is DOUBLE PRECISION array, dimension (NMAX)
164 *> \endverbatim
165 *>
166 *> \param[out] WORK
167 *> \verbatim
168 *> WORK is DOUBLE PRECISION array, dimension (NMAX*NMAX)
169 *> \endverbatim
170 *>
171 *> \param[out] RWORK
172 *> \verbatim
173 *> RWORK is DOUBLE PRECISION array, dimension (NMAX)
174 *> \endverbatim
175 *>
176 *> \param[in] NIN
177 *> \verbatim
178 *> NIN is INTEGER
179 *> The unit number for input.
180 *> \endverbatim
181 *>
182 *> \param[in] NOUT
183 *> \verbatim
184 *> NOUT is INTEGER
185 *> The unit number for output.
186 *> \endverbatim
187 *>
188 *> \param[out] INFO
189 *> \verbatim
190 *> INFO is INTEGER
191 *> = 0 : successful exit
192 *> > 0 : If DLATMS returns an error code, the absolute value
193 *> of it is returned.
194 *> \endverbatim
195 *
196 * Authors:
197 * ========
198 *
199 *> \author Univ. of Tennessee
200 *> \author Univ. of California Berkeley
201 *> \author Univ. of Colorado Denver
202 *> \author NAG Ltd.
203 *
204 *> \date November 2011
205 *
206 *> \ingroup double_eig
207 *
208 * =====================================================================
209  SUBROUTINE dckgqr( NM, MVAL, NP, PVAL, NN, NVAL, NMATS, ISEED,
210  $ thresh, nmax, a, af, aq, ar, taua, b, bf, bz,
211  $ bt, bwk, taub, work, rwork, nin, nout, info )
212 *
213 * -- LAPACK test routine (version 3.4.0) --
214 * -- LAPACK is a software package provided by Univ. of Tennessee, --
215 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
216 * November 2011
217 *
218 * .. Scalar Arguments ..
219  INTEGER info, nin, nm, nmats, nmax, nn, nout, np
220  DOUBLE PRECISION thresh
221 * ..
222 * .. Array Arguments ..
223  INTEGER iseed( 4 ), mval( * ), nval( * ), pval( * )
224  DOUBLE PRECISION a( * ), af( * ), aq( * ), ar( * ), b( * ),
225  $ bf( * ), bt( * ), bwk( * ), bz( * ),
226  $ rwork( * ), taua( * ), taub( * ), work( * )
227 * ..
228 *
229 * =====================================================================
230 *
231 * .. Parameters ..
232  INTEGER ntests
233  parameter( ntests = 7 )
234  INTEGER ntypes
235  parameter( ntypes = 8 )
236 * ..
237 * .. Local Scalars ..
238  LOGICAL firstt
239  CHARACTER dista, distb, type
240  CHARACTER*3 path
241  INTEGER i, iinfo, im, imat, in, ip, kla, klb, kua, kub,
242  $ lda, ldb, lwork, m, modea, modeb, n, nfail,
243  $ nrun, nt, p
244  DOUBLE PRECISION anorm, bnorm, cndnma, cndnmb
245 * ..
246 * .. Local Arrays ..
247  LOGICAL dotype( ntypes )
248  DOUBLE PRECISION result( ntests )
249 * ..
250 * .. External Subroutines ..
251  EXTERNAL alahdg, alareq, alasum, dgqrts, dgrqts, dlatb9,
252  $ dlatms
253 * ..
254 * .. Intrinsic Functions ..
255  INTRINSIC abs
256 * ..
257 * .. Executable Statements ..
258 *
259 * Initialize constants.
260 *
261  path( 1: 3 ) = 'GQR'
262  info = 0
263  nrun = 0
264  nfail = 0
265  firstt = .true.
266  CALL alareq( path, nmats, dotype, ntypes, nin, nout )
267  lda = nmax
268  ldb = nmax
269  lwork = nmax*nmax
270 *
271 * Do for each value of M in MVAL.
272 *
273  DO 60 im = 1, nm
274  m = mval( im )
275 *
276 * Do for each value of P in PVAL.
277 *
278  DO 50 ip = 1, np
279  p = pval( ip )
280 *
281 * Do for each value of N in NVAL.
282 *
283  DO 40 in = 1, nn
284  n = nval( in )
285 *
286  DO 30 imat = 1, ntypes
287 *
288 * Do the tests only if DOTYPE( IMAT ) is true.
289 *
290  IF( .NOT.dotype( imat ) )
291  $ go to 30
292 *
293 * Test DGGRQF
294 *
295 * Set up parameters with DLATB9 and generate test
296 * matrices A and B with DLATMS.
297 *
298  CALL dlatb9( 'GRQ', imat, m, p, n, type, kla, kua,
299  $ klb, kub, anorm, bnorm, modea, modeb,
300  $ cndnma, cndnmb, dista, distb )
301 *
302 * Generate M by N matrix A
303 *
304  CALL dlatms( m, n, dista, iseed, type, rwork, modea,
305  $ cndnma, anorm, kla, kua, 'No packing', a,
306  $ lda, work, iinfo )
307  IF( iinfo.NE.0 ) THEN
308  WRITE( nout, fmt = 9999 )iinfo
309  info = abs( iinfo )
310  go to 30
311  END IF
312 *
313 * Generate P by N matrix B
314 *
315  CALL dlatms( p, n, distb, iseed, type, rwork, modeb,
316  $ cndnmb, bnorm, klb, kub, 'No packing', b,
317  $ ldb, work, iinfo )
318  IF( iinfo.NE.0 ) THEN
319  WRITE( nout, fmt = 9999 )iinfo
320  info = abs( iinfo )
321  go to 30
322  END IF
323 *
324  nt = 4
325 *
326  CALL dgrqts( m, p, n, a, af, aq, ar, lda, taua, b, bf,
327  $ bz, bt, bwk, ldb, taub, work, lwork,
328  $ rwork, result )
329 *
330 * Print information about the tests that did not
331 * pass the threshold.
332 *
333  DO 10 i = 1, nt
334  IF( result( i ).GE.thresh ) THEN
335  IF( nfail.EQ.0 .AND. firstt ) THEN
336  firstt = .false.
337  CALL alahdg( nout, 'GRQ' )
338  END IF
339  WRITE( nout, fmt = 9998 )m, p, n, imat, i,
340  $ result( i )
341  nfail = nfail + 1
342  END IF
343  10 continue
344  nrun = nrun + nt
345 *
346 * Test DGGQRF
347 *
348 * Set up parameters with DLATB9 and generate test
349 * matrices A and B with DLATMS.
350 *
351  CALL dlatb9( 'GQR', imat, m, p, n, type, kla, kua,
352  $ klb, kub, anorm, bnorm, modea, modeb,
353  $ cndnma, cndnmb, dista, distb )
354 *
355 * Generate N-by-M matrix A
356 *
357  CALL dlatms( n, m, dista, iseed, type, rwork, modea,
358  $ cndnma, anorm, kla, kua, 'No packing', a,
359  $ lda, work, iinfo )
360  IF( iinfo.NE.0 ) THEN
361  WRITE( nout, fmt = 9999 )iinfo
362  info = abs( iinfo )
363  go to 30
364  END IF
365 *
366 * Generate N-by-P matrix B
367 *
368  CALL dlatms( n, p, distb, iseed, type, rwork, modea,
369  $ cndnma, bnorm, klb, kub, 'No packing', b,
370  $ ldb, work, iinfo )
371  IF( iinfo.NE.0 ) THEN
372  WRITE( nout, fmt = 9999 )iinfo
373  info = abs( iinfo )
374  go to 30
375  END IF
376 *
377  nt = 4
378 *
379  CALL dgqrts( n, m, p, a, af, aq, ar, lda, taua, b, bf,
380  $ bz, bt, bwk, ldb, taub, work, lwork,
381  $ rwork, result )
382 *
383 * Print information about the tests that did not
384 * pass the threshold.
385 *
386  DO 20 i = 1, nt
387  IF( result( i ).GE.thresh ) THEN
388  IF( nfail.EQ.0 .AND. firstt ) THEN
389  firstt = .false.
390  CALL alahdg( nout, path )
391  END IF
392  WRITE( nout, fmt = 9997 )n, m, p, imat, i,
393  $ result( i )
394  nfail = nfail + 1
395  END IF
396  20 continue
397  nrun = nrun + nt
398 *
399  30 continue
400  40 continue
401  50 continue
402  60 continue
403 *
404 * Print a summary of the results.
405 *
406  CALL alasum( path, nout, nfail, nrun, 0 )
407 *
408  9999 format( ' DLATMS in DCKGQR: INFO = ', i5 )
409  9998 format( ' M=', i4, ' P=', i4, ', N=', i4, ', type ', i2,
410  $ ', test ', i2, ', ratio=', g13.6 )
411  9997 format( ' N=', i4, ' M=', i4, ', P=', i4, ', type ', i2,
412  $ ', test ', i2, ', ratio=', g13.6 )
413  return
414 *
415 * End of DCKGQR
416 *
417  END