LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zchklq.f
Go to the documentation of this file.
1 *> \brief \b ZCHKLQ
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 ZCHKLQ( DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL,
12 * NRHS, THRESH, TSTERR, NMAX, A, AF, AQ, AL, AC,
13 * B, X, XACT, TAU, WORK, RWORK, NOUT )
14 *
15 * .. Scalar Arguments ..
16 * LOGICAL TSTERR
17 * INTEGER NM, NMAX, NN, NNB, NOUT, NRHS
18 * DOUBLE PRECISION THRESH
19 * ..
20 * .. Array Arguments ..
21 * LOGICAL DOTYPE( * )
22 * INTEGER MVAL( * ), NBVAL( * ), NVAL( * ),
23 * $ NXVAL( * )
24 * DOUBLE PRECISION RWORK( * )
25 * COMPLEX*16 A( * ), AC( * ), AF( * ), AL( * ), AQ( * ),
26 * $ B( * ), TAU( * ), WORK( * ), X( * ), XACT( * )
27 * ..
28 *
29 *
30 *> \par Purpose:
31 * =============
32 *>
33 *> \verbatim
34 *>
35 *> ZCHKLQ tests ZGELQF, ZUNGLQ and CUNMLQ.
36 *> \endverbatim
37 *
38 * Arguments:
39 * ==========
40 *
41 *> \param[in] DOTYPE
42 *> \verbatim
43 *> DOTYPE is LOGICAL array, dimension (NTYPES)
44 *> The matrix types to be used for testing. Matrices of type j
45 *> (for 1 <= j <= NTYPES) are used for testing if DOTYPE(j) =
46 *> .TRUE.; if DOTYPE(j) = .FALSE., then type j is not used.
47 *> \endverbatim
48 *>
49 *> \param[in] NM
50 *> \verbatim
51 *> NM is INTEGER
52 *> The number of values of M contained in the vector MVAL.
53 *> \endverbatim
54 *>
55 *> \param[in] MVAL
56 *> \verbatim
57 *> MVAL is INTEGER array, dimension (NM)
58 *> The values of the matrix row dimension M.
59 *> \endverbatim
60 *>
61 *> \param[in] NN
62 *> \verbatim
63 *> NN is INTEGER
64 *> The number of values of N contained in the vector NVAL.
65 *> \endverbatim
66 *>
67 *> \param[in] NVAL
68 *> \verbatim
69 *> NVAL is INTEGER array, dimension (NN)
70 *> The values of the matrix column dimension N.
71 *> \endverbatim
72 *>
73 *> \param[in] NNB
74 *> \verbatim
75 *> NNB is INTEGER
76 *> The number of values of NB and NX contained in the
77 *> vectors NBVAL and NXVAL. The blocking parameters are used
78 *> in pairs (NB,NX).
79 *> \endverbatim
80 *>
81 *> \param[in] NBVAL
82 *> \verbatim
83 *> NBVAL is INTEGER array, dimension (NNB)
84 *> The values of the blocksize NB.
85 *> \endverbatim
86 *>
87 *> \param[in] NXVAL
88 *> \verbatim
89 *> NXVAL is INTEGER array, dimension (NNB)
90 *> The values of the crossover point NX.
91 *> \endverbatim
92 *>
93 *> \param[in] NRHS
94 *> \verbatim
95 *> NRHS is INTEGER
96 *> The number of right hand side vectors to be generated for
97 *> each linear system.
98 *> \endverbatim
99 *>
100 *> \param[in] THRESH
101 *> \verbatim
102 *> THRESH is DOUBLE PRECISION
103 *> The threshold value for the test ratios. A result is
104 *> included in the output file if RESULT >= THRESH. To have
105 *> every test ratio printed, use THRESH = 0.
106 *> \endverbatim
107 *>
108 *> \param[in] TSTERR
109 *> \verbatim
110 *> TSTERR is LOGICAL
111 *> Flag that indicates whether error exits are to be tested.
112 *> \endverbatim
113 *>
114 *> \param[in] NMAX
115 *> \verbatim
116 *> NMAX is INTEGER
117 *> The maximum value permitted for M or N, used in dimensioning
118 *> the work arrays.
119 *> \endverbatim
120 *>
121 *> \param[out] A
122 *> \verbatim
123 *> A is COMPLEX*16 array, dimension (NMAX*NMAX)
124 *> \endverbatim
125 *>
126 *> \param[out] AF
127 *> \verbatim
128 *> AF is COMPLEX*16 array, dimension (NMAX*NMAX)
129 *> \endverbatim
130 *>
131 *> \param[out] AQ
132 *> \verbatim
133 *> AQ is COMPLEX*16 array, dimension (NMAX*NMAX)
134 *> \endverbatim
135 *>
136 *> \param[out] AL
137 *> \verbatim
138 *> AL is COMPLEX*16 array, dimension (NMAX*NMAX)
139 *> \endverbatim
140 *>
141 *> \param[out] AC
142 *> \verbatim
143 *> AC is COMPLEX*16 array, dimension (NMAX*NMAX)
144 *> \endverbatim
145 *>
146 *> \param[out] B
147 *> \verbatim
148 *> B is COMPLEX*16 array, dimension (NMAX*NRHS)
149 *> \endverbatim
150 *>
151 *> \param[out] X
152 *> \verbatim
153 *> X is COMPLEX*16 array, dimension (NMAX*NRHS)
154 *> \endverbatim
155 *>
156 *> \param[out] XACT
157 *> \verbatim
158 *> XACT is COMPLEX*16 array, dimension (NMAX*NRHS)
159 *> \endverbatim
160 *>
161 *> \param[out] TAU
162 *> \verbatim
163 *> TAU is COMPLEX*16 array, dimension (NMAX)
164 *> \endverbatim
165 *>
166 *> \param[out] WORK
167 *> \verbatim
168 *> WORK is COMPLEX*16 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] NOUT
177 *> \verbatim
178 *> NOUT is INTEGER
179 *> The unit number for output.
180 *> \endverbatim
181 *
182 * Authors:
183 * ========
184 *
185 *> \author Univ. of Tennessee
186 *> \author Univ. of California Berkeley
187 *> \author Univ. of Colorado Denver
188 *> \author NAG Ltd.
189 *
190 *> \date November 2011
191 *
192 *> \ingroup complex16_lin
193 *
194 * =====================================================================
195  SUBROUTINE zchklq( DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL,
196  $ nrhs, thresh, tsterr, nmax, a, af, aq, al, ac,
197  $ b, x, xact, tau, work, rwork, nout )
198 *
199 * -- LAPACK test routine (version 3.4.0) --
200 * -- LAPACK is a software package provided by Univ. of Tennessee, --
201 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
202 * November 2011
203 *
204 * .. Scalar Arguments ..
205  LOGICAL tsterr
206  INTEGER nm, nmax, nn, nnb, nout, nrhs
207  DOUBLE PRECISION thresh
208 * ..
209 * .. Array Arguments ..
210  LOGICAL dotype( * )
211  INTEGER mval( * ), nbval( * ), nval( * ),
212  $ nxval( * )
213  DOUBLE PRECISION rwork( * )
214  COMPLEX*16 a( * ), ac( * ), af( * ), al( * ), aq( * ),
215  $ b( * ), tau( * ), work( * ), x( * ), xact( * )
216 * ..
217 *
218 * =====================================================================
219 *
220 * .. Parameters ..
221  INTEGER ntests
222  parameter( ntests = 7 )
223  INTEGER ntypes
224  parameter( ntypes = 8 )
225  DOUBLE PRECISION zero
226  parameter( zero = 0.0d0 )
227 * ..
228 * .. Local Scalars ..
229  CHARACTER dist, type
230  CHARACTER*3 path
231  INTEGER i, ik, im, imat, in, inb, info, k, kl, ku, lda,
232  $ lwork, m, minmn, mode, n, nb, nerrs, nfail, nk,
233  $ nrun, nt, nx
234  DOUBLE PRECISION anorm, cndnum
235 * ..
236 * .. Local Arrays ..
237  INTEGER iseed( 4 ), iseedy( 4 ), kval( 4 )
238  DOUBLE PRECISION result( ntests )
239 * ..
240 * .. External Subroutines ..
241  EXTERNAL alaerh, alahd, alasum, xlaenv, zerrlq, zgelqs,
243  $ zlqt02, zlqt03
244 * ..
245 * .. Intrinsic Functions ..
246  INTRINSIC max, min
247 * ..
248 * .. Scalars in Common ..
249  LOGICAL lerr, ok
250  CHARACTER*32 srnamt
251  INTEGER infot, nunit
252 * ..
253 * .. Common blocks ..
254  common / infoc / infot, nunit, ok, lerr
255  common / srnamc / srnamt
256 * ..
257 * .. Data statements ..
258  DATA iseedy / 1988, 1989, 1990, 1991 /
259 * ..
260 * .. Executable Statements ..
261 *
262 * Initialize constants and the random number seed.
263 *
264  path( 1: 1 ) = 'Zomplex precision'
265  path( 2: 3 ) = 'LQ'
266  nrun = 0
267  nfail = 0
268  nerrs = 0
269  DO 10 i = 1, 4
270  iseed( i ) = iseedy( i )
271  10 continue
272 *
273 * Test the error exits
274 *
275  IF( tsterr )
276  $ CALL zerrlq( path, nout )
277  infot = 0
278  CALL xlaenv( 2, 2 )
279 *
280  lda = nmax
281  lwork = nmax*max( nmax, nrhs )
282 *
283 * Do for each value of M in MVAL.
284 *
285  DO 70 im = 1, nm
286  m = mval( im )
287 *
288 * Do for each value of N in NVAL.
289 *
290  DO 60 in = 1, nn
291  n = nval( in )
292  minmn = min( m, n )
293  DO 50 imat = 1, ntypes
294 *
295 * Do the tests only if DOTYPE( IMAT ) is true.
296 *
297  IF( .NOT.dotype( imat ) )
298  $ go to 50
299 *
300 * Set up parameters with ZLATB4 and generate a test matrix
301 * with ZLATMS.
302 *
303  CALL zlatb4( path, imat, m, n, type, kl, ku, anorm, mode,
304  $ cndnum, dist )
305 *
306  srnamt = 'ZLATMS'
307  CALL zlatms( m, n, dist, iseed, type, rwork, mode,
308  $ cndnum, anorm, kl, ku, 'No packing', a, lda,
309  $ work, info )
310 *
311 * Check error code from ZLATMS.
312 *
313  IF( info.NE.0 ) THEN
314  CALL alaerh( path, 'ZLATMS', info, 0, ' ', m, n, -1,
315  $ -1, -1, imat, nfail, nerrs, nout )
316  go to 50
317  END IF
318 *
319 * Set some values for K: the first value must be MINMN,
320 * corresponding to the call of ZLQT01; other values are
321 * used in the calls of ZLQT02, and must not exceed MINMN.
322 *
323  kval( 1 ) = minmn
324  kval( 2 ) = 0
325  kval( 3 ) = 1
326  kval( 4 ) = minmn / 2
327  IF( minmn.EQ.0 ) THEN
328  nk = 1
329  ELSE IF( minmn.EQ.1 ) THEN
330  nk = 2
331  ELSE IF( minmn.LE.3 ) THEN
332  nk = 3
333  ELSE
334  nk = 4
335  END IF
336 *
337 * Do for each value of K in KVAL
338 *
339  DO 40 ik = 1, nk
340  k = kval( ik )
341 *
342 * Do for each pair of values (NB,NX) in NBVAL and NXVAL.
343 *
344  DO 30 inb = 1, nnb
345  nb = nbval( inb )
346  CALL xlaenv( 1, nb )
347  nx = nxval( inb )
348  CALL xlaenv( 3, nx )
349  DO i = 1, ntests
350  result( i ) = zero
351  END DO
352  nt = 2
353  IF( ik.EQ.1 ) THEN
354 *
355 * Test ZGELQF
356 *
357  CALL zlqt01( m, n, a, af, aq, al, lda, tau,
358  $ work, lwork, rwork, result( 1 ) )
359  ELSE IF( m.LE.n ) THEN
360 *
361 * Test ZUNGLQ, using factorization
362 * returned by ZLQT01
363 *
364  CALL zlqt02( m, n, k, a, af, aq, al, lda, tau,
365  $ work, lwork, rwork, result( 1 ) )
366  END IF
367  IF( m.GE.k ) THEN
368 *
369 * Test ZUNMLQ, using factorization returned
370 * by ZLQT01
371 *
372  CALL zlqt03( m, n, k, af, ac, al, aq, lda, tau,
373  $ work, lwork, rwork, result( 3 ) )
374  nt = nt + 4
375 *
376 * If M>=N and K=N, call ZGELQS to solve a system
377 * with NRHS right hand sides and compute the
378 * residual.
379 *
380  IF( k.EQ.m .AND. inb.EQ.1 ) THEN
381 *
382 * Generate a solution and set the right
383 * hand side.
384 *
385  srnamt = 'ZLARHS'
386  CALL zlarhs( path, 'New', 'Full',
387  $ 'No transpose', m, n, 0, 0,
388  $ nrhs, a, lda, xact, lda, b, lda,
389  $ iseed, info )
390 *
391  CALL zlacpy( 'Full', m, nrhs, b, lda, x,
392  $ lda )
393  srnamt = 'ZGELQS'
394  CALL zgelqs( m, n, nrhs, af, lda, tau, x,
395  $ lda, work, lwork, info )
396 *
397 * Check error code from ZGELQS.
398 *
399  IF( info.NE.0 )
400  $ CALL alaerh( path, 'ZGELQS', info, 0, ' ',
401  $ m, n, nrhs, -1, nb, imat,
402  $ nfail, nerrs, nout )
403 *
404  CALL zget02( 'No transpose', m, n, nrhs, a,
405  $ lda, x, lda, b, lda, rwork,
406  $ result( 7 ) )
407  nt = nt + 1
408  END IF
409  END IF
410 *
411 * Print information about the tests that did not
412 * pass the threshold.
413 *
414  DO 20 i = 1, nt
415  IF( result( i ).GE.thresh ) THEN
416  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
417  $ CALL alahd( nout, path )
418  WRITE( nout, fmt = 9999 )m, n, k, nb, nx,
419  $ imat, i, result( i )
420  nfail = nfail + 1
421  END IF
422  20 continue
423  nrun = nrun + nt
424  30 continue
425  40 continue
426  50 continue
427  60 continue
428  70 continue
429 *
430 * Print a summary of the results.
431 *
432  CALL alasum( path, nout, nfail, nrun, nerrs )
433 *
434  9999 format( ' M=', i5, ', N=', i5, ', K=', i5, ', NB=', i4, ', NX=',
435  $ i5, ', type ', i2, ', test(', i2, ')=', g12.5 )
436  return
437 *
438 * End of ZCHKLQ
439 *
440  END