LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
ddrvls.f
Go to the documentation of this file.
1 *> \brief \b DDRVLS
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 DDRVLS( DOTYPE, NM, MVAL, NN, NVAL, NNS, NSVAL, NNB,
12 * NBVAL, NXVAL, THRESH, TSTERR, A, COPYA, B,
13 * COPYB, C, S, COPYS, WORK, IWORK, NOUT )
14 *
15 * .. Scalar Arguments ..
16 * LOGICAL TSTERR
17 * INTEGER NM, NN, NNB, NNS, NOUT
18 * DOUBLE PRECISION THRESH
19 * ..
20 * .. Array Arguments ..
21 * LOGICAL DOTYPE( * )
22 * INTEGER IWORK( * ), MVAL( * ), NBVAL( * ), NSVAL( * ),
23 * $ NVAL( * ), NXVAL( * )
24 * DOUBLE PRECISION A( * ), B( * ), C( * ), COPYA( * ), COPYB( * ),
25 * $ COPYS( * ), S( * ), WORK( * )
26 * ..
27 *
28 *
29 *> \par Purpose:
30 * =============
31 *>
32 *> \verbatim
33 *>
34 *> DDRVLS tests the least squares driver routines DGELS, DGELSS, DGELSY,
35 *> and DGELSD.
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 *> The matrix of type j is generated as follows:
48 *> j=1: A = U*D*V where U and V are random orthogonal matrices
49 *> and D has random entries (> 0.1) taken from a uniform
50 *> distribution (0,1). A is full rank.
51 *> j=2: The same of 1, but A is scaled up.
52 *> j=3: The same of 1, but A is scaled down.
53 *> j=4: A = U*D*V where U and V are random orthogonal matrices
54 *> and D has 3*min(M,N)/4 random entries (> 0.1) taken
55 *> from a uniform distribution (0,1) and the remaining
56 *> entries set to 0. A is rank-deficient.
57 *> j=5: The same of 4, but A is scaled up.
58 *> j=6: The same of 5, but A is scaled down.
59 *> \endverbatim
60 *>
61 *> \param[in] NM
62 *> \verbatim
63 *> NM is INTEGER
64 *> The number of values of M contained in the vector MVAL.
65 *> \endverbatim
66 *>
67 *> \param[in] MVAL
68 *> \verbatim
69 *> MVAL is INTEGER array, dimension (NM)
70 *> The values of the matrix row dimension M.
71 *> \endverbatim
72 *>
73 *> \param[in] NN
74 *> \verbatim
75 *> NN is INTEGER
76 *> The number of values of N contained in the vector NVAL.
77 *> \endverbatim
78 *>
79 *> \param[in] NVAL
80 *> \verbatim
81 *> NVAL is INTEGER array, dimension (NN)
82 *> The values of the matrix column dimension N.
83 *> \endverbatim
84 *>
85 *> \param[in] NNS
86 *> \verbatim
87 *> NNS is INTEGER
88 *> The number of values of NRHS contained in the vector NSVAL.
89 *> \endverbatim
90 *>
91 *> \param[in] NSVAL
92 *> \verbatim
93 *> NSVAL is INTEGER array, dimension (NNS)
94 *> The values of the number of right hand sides NRHS.
95 *> \endverbatim
96 *>
97 *> \param[in] NNB
98 *> \verbatim
99 *> NNB is INTEGER
100 *> The number of values of NB and NX contained in the
101 *> vectors NBVAL and NXVAL. The blocking parameters are used
102 *> in pairs (NB,NX).
103 *> \endverbatim
104 *>
105 *> \param[in] NBVAL
106 *> \verbatim
107 *> NBVAL is INTEGER array, dimension (NNB)
108 *> The values of the blocksize NB.
109 *> \endverbatim
110 *>
111 *> \param[in] NXVAL
112 *> \verbatim
113 *> NXVAL is INTEGER array, dimension (NNB)
114 *> The values of the crossover point NX.
115 *> \endverbatim
116 *>
117 *> \param[in] THRESH
118 *> \verbatim
119 *> THRESH is DOUBLE PRECISION
120 *> The threshold value for the test ratios. A result is
121 *> included in the output file if RESULT >= THRESH. To have
122 *> every test ratio printed, use THRESH = 0.
123 *> \endverbatim
124 *>
125 *> \param[in] TSTERR
126 *> \verbatim
127 *> TSTERR is LOGICAL
128 *> Flag that indicates whether error exits are to be tested.
129 *> \endverbatim
130 *>
131 *> \param[out] A
132 *> \verbatim
133 *> A is DOUBLE PRECISION array, dimension (MMAX*NMAX)
134 *> where MMAX is the maximum value of M in MVAL and NMAX is the
135 *> maximum value of N in NVAL.
136 *> \endverbatim
137 *>
138 *> \param[out] COPYA
139 *> \verbatim
140 *> COPYA is DOUBLE PRECISION array, dimension (MMAX*NMAX)
141 *> \endverbatim
142 *>
143 *> \param[out] B
144 *> \verbatim
145 *> B is DOUBLE PRECISION array, dimension (MMAX*NSMAX)
146 *> where MMAX is the maximum value of M in MVAL and NSMAX is the
147 *> maximum value of NRHS in NSVAL.
148 *> \endverbatim
149 *>
150 *> \param[out] COPYB
151 *> \verbatim
152 *> COPYB is DOUBLE PRECISION array, dimension (MMAX*NSMAX)
153 *> \endverbatim
154 *>
155 *> \param[out] C
156 *> \verbatim
157 *> C is DOUBLE PRECISION array, dimension (MMAX*NSMAX)
158 *> \endverbatim
159 *>
160 *> \param[out] S
161 *> \verbatim
162 *> S is DOUBLE PRECISION array, dimension
163 *> (min(MMAX,NMAX))
164 *> \endverbatim
165 *>
166 *> \param[out] COPYS
167 *> \verbatim
168 *> COPYS is DOUBLE PRECISION array, dimension
169 *> (min(MMAX,NMAX))
170 *> \endverbatim
171 *>
172 *> \param[out] WORK
173 *> \verbatim
174 *> WORK is DOUBLE PRECISION array,
175 *> dimension (MMAX*NMAX + 4*NMAX + MMAX).
176 *> \endverbatim
177 *>
178 *> \param[out] IWORK
179 *> \verbatim
180 *> IWORK is INTEGER array, dimension (15*NMAX)
181 *> \endverbatim
182 *>
183 *> \param[in] NOUT
184 *> \verbatim
185 *> NOUT is INTEGER
186 *> The unit number for output.
187 *> \endverbatim
188 *
189 * Authors:
190 * ========
191 *
192 *> \author Univ. of Tennessee
193 *> \author Univ. of California Berkeley
194 *> \author Univ. of Colorado Denver
195 *> \author NAG Ltd.
196 *
197 *> \date November 2015
198 *
199 *> \ingroup double_lin
200 *
201 * =====================================================================
202  SUBROUTINE ddrvls( DOTYPE, NM, MVAL, NN, NVAL, NNS, NSVAL, NNB,
203  $ nbval, nxval, thresh, tsterr, a, copya, b,
204  $ copyb, c, s, copys, work, iwork, nout )
205 *
206 * -- LAPACK test routine (version 3.6.0) --
207 * -- LAPACK is a software package provided by Univ. of Tennessee, --
208 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
209 * November 2015
210 *
211 * .. Scalar Arguments ..
212  LOGICAL TSTERR
213  INTEGER NM, NN, NNB, NNS, NOUT
214  DOUBLE PRECISION THRESH
215 * ..
216 * .. Array Arguments ..
217  LOGICAL DOTYPE( * )
218  INTEGER IWORK( * ), MVAL( * ), NBVAL( * ), NSVAL( * ),
219  $ nval( * ), nxval( * )
220  DOUBLE PRECISION A( * ), B( * ), C( * ), COPYA( * ), COPYB( * ),
221  $ copys( * ), s( * ), work( * )
222 * ..
223 *
224 * =====================================================================
225 *
226 * .. Parameters ..
227  INTEGER NTESTS
228  parameter ( ntests = 14 )
229  INTEGER SMLSIZ
230  parameter ( smlsiz = 25 )
231  DOUBLE PRECISION ONE, TWO, ZERO
232  parameter ( one = 1.0d0, two = 2.0d0, zero = 0.0d0 )
233 * ..
234 * .. Local Scalars ..
235  CHARACTER TRANS
236  CHARACTER*3 PATH
237  INTEGER CRANK, I, IM, IN, INB, INFO, INS, IRANK,
238  $ iscale, itran, itype, j, k, lda, ldb, ldwork,
239  $ lwlsy, lwork, m, mnmin, n, nb, ncols, nerrs,
240  $ nfail, nlvl, nrhs, nrows, nrun, rank
241  DOUBLE PRECISION EPS, NORMA, NORMB, RCOND
242 * ..
243 * .. Local Arrays ..
244  INTEGER ISEED( 4 ), ISEEDY( 4 )
245  DOUBLE PRECISION RESULT( ntests )
246 * ..
247 * .. External Functions ..
248  DOUBLE PRECISION DASUM, DLAMCH, DQRT12, DQRT14, DQRT17
249  EXTERNAL dasum, dlamch, dqrt12, dqrt14, dqrt17
250 * ..
251 * .. External Subroutines ..
252  EXTERNAL alaerh, alahd, alasvm, daxpy, derrls, dgels,
255  $ xlaenv
256 * ..
257 * .. Intrinsic Functions ..
258  INTRINSIC dble, int, log, max, min, sqrt
259 * ..
260 * .. Scalars in Common ..
261  LOGICAL LERR, OK
262  CHARACTER*32 SRNAMT
263  INTEGER INFOT, IOUNIT
264 * ..
265 * .. Common blocks ..
266  COMMON / infoc / infot, iounit, ok, lerr
267  COMMON / srnamc / srnamt
268 * ..
269 * .. Data statements ..
270  DATA iseedy / 1988, 1989, 1990, 1991 /
271 * ..
272 * .. Executable Statements ..
273 *
274 * Initialize constants and the random number seed.
275 *
276  path( 1: 1 ) = 'Double precision'
277  path( 2: 3 ) = 'LS'
278  nrun = 0
279  nfail = 0
280  nerrs = 0
281  DO 10 i = 1, 4
282  iseed( i ) = iseedy( i )
283  10 CONTINUE
284  eps = dlamch( 'Epsilon' )
285 *
286 * Threshold for rank estimation
287 *
288  rcond = sqrt( eps ) - ( sqrt( eps )-eps ) / 2
289 *
290 * Test the error exits
291 *
292  CALL xlaenv( 2, 2 )
293  CALL xlaenv( 9, smlsiz )
294  IF( tsterr )
295  $ CALL derrls( path, nout )
296 *
297 * Print the header if NM = 0 or NN = 0 and THRESH = 0.
298 *
299  IF( ( nm.EQ.0 .OR. nn.EQ.0 ) .AND. thresh.EQ.zero )
300  $ CALL alahd( nout, path )
301  infot = 0
302  CALL xlaenv( 2, 2 )
303  CALL xlaenv( 9, smlsiz )
304 *
305  DO 150 im = 1, nm
306  m = mval( im )
307  lda = max( 1, m )
308 *
309  DO 140 in = 1, nn
310  n = nval( in )
311  mnmin = min( m, n )
312  ldb = max( 1, m, n )
313 *
314  DO 130 ins = 1, nns
315  nrhs = nsval( ins )
316  nlvl = max( int( log( max( one, dble( mnmin ) ) /
317  $ dble( smlsiz+1 ) ) / log( two ) ) + 1, 0 )
318  lwork = max( 1, ( m+nrhs )*( n+2 ), ( n+nrhs )*( m+2 ),
319  $ m*n+4*mnmin+max( m, n ), 12*mnmin+2*mnmin*smlsiz+
320  $ 8*mnmin*nlvl+mnmin*nrhs+(smlsiz+1)**2 )
321 *
322  DO 120 irank = 1, 2
323  DO 110 iscale = 1, 3
324  itype = ( irank-1 )*3 + iscale
325  IF( .NOT.dotype( itype ) )
326  $ GO TO 110
327 *
328  IF( irank.EQ.1 ) THEN
329 *
330 * Test DGELS
331 *
332 * Generate a matrix of scaling type ISCALE
333 *
334  CALL dqrt13( iscale, m, n, copya, lda, norma,
335  $ iseed )
336  DO 40 inb = 1, nnb
337  nb = nbval( inb )
338  CALL xlaenv( 1, nb )
339  CALL xlaenv( 3, nxval( inb ) )
340 *
341  DO 30 itran = 1, 2
342  IF( itran.EQ.1 ) THEN
343  trans = 'N'
344  nrows = m
345  ncols = n
346  ELSE
347  trans = 'T'
348  nrows = n
349  ncols = m
350  END IF
351  ldwork = max( 1, ncols )
352 *
353 * Set up a consistent rhs
354 *
355  IF( ncols.GT.0 ) THEN
356  CALL dlarnv( 2, iseed, ncols*nrhs,
357  $ work )
358  CALL dscal( ncols*nrhs,
359  $ one / dble( ncols ), work,
360  $ 1 )
361  END IF
362  CALL dgemm( trans, 'No transpose', nrows,
363  $ nrhs, ncols, one, copya, lda,
364  $ work, ldwork, zero, b, ldb )
365  CALL dlacpy( 'Full', nrows, nrhs, b, ldb,
366  $ copyb, ldb )
367 *
368 * Solve LS or overdetermined system
369 *
370  IF( m.GT.0 .AND. n.GT.0 ) THEN
371  CALL dlacpy( 'Full', m, n, copya, lda,
372  $ a, lda )
373  CALL dlacpy( 'Full', nrows, nrhs,
374  $ copyb, ldb, b, ldb )
375  END IF
376  srnamt = 'DGELS '
377  CALL dgels( trans, m, n, nrhs, a, lda, b,
378  $ ldb, work, lwork, info )
379  IF( info.NE.0 )
380  $ CALL alaerh( path, 'DGELS ', info, 0,
381  $ trans, m, n, nrhs, -1, nb,
382  $ itype, nfail, nerrs,
383  $ nout )
384 *
385 * Check correctness of results
386 *
387  ldwork = max( 1, nrows )
388  IF( nrows.GT.0 .AND. nrhs.GT.0 )
389  $ CALL dlacpy( 'Full', nrows, nrhs,
390  $ copyb, ldb, c, ldb )
391  CALL dqrt16( trans, m, n, nrhs, copya,
392  $ lda, b, ldb, c, ldb, work,
393  $ result( 1 ) )
394 *
395  IF( ( itran.EQ.1 .AND. m.GE.n ) .OR.
396  $ ( itran.EQ.2 .AND. m.LT.n ) ) THEN
397 *
398 * Solving LS system
399 *
400  result( 2 ) = dqrt17( trans, 1, m, n,
401  $ nrhs, copya, lda, b, ldb,
402  $ copyb, ldb, c, work,
403  $ lwork )
404  ELSE
405 *
406 * Solving overdetermined system
407 *
408  result( 2 ) = dqrt14( trans, m, n,
409  $ nrhs, copya, lda, b, ldb,
410  $ work, lwork )
411  END IF
412 *
413 * Print information about the tests that
414 * did not pass the threshold.
415 *
416  DO 20 k = 1, 2
417  IF( result( k ).GE.thresh ) THEN
418  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
419  $ CALL alahd( nout, path )
420  WRITE( nout, fmt = 9999 )trans, m,
421  $ n, nrhs, nb, itype, k,
422  $ result( k )
423  nfail = nfail + 1
424  END IF
425  20 CONTINUE
426  nrun = nrun + 2
427  30 CONTINUE
428  40 CONTINUE
429  END IF
430 *
431 * Generate a matrix of scaling type ISCALE and rank
432 * type IRANK.
433 *
434  CALL dqrt15( iscale, irank, m, n, nrhs, copya, lda,
435  $ copyb, ldb, copys, rank, norma, normb,
436  $ iseed, work, lwork )
437 *
438 * workspace used: MAX(M+MIN(M,N),NRHS*MIN(M,N),2*N+M)
439 *
440  ldwork = max( 1, m )
441 *
442 * Loop for testing different block sizes.
443 *
444  DO 100 inb = 1, nnb
445  nb = nbval( inb )
446  CALL xlaenv( 1, nb )
447  CALL xlaenv( 3, nxval( inb ) )
448 *
449 * Test DGELSY
450 *
451 * DGELSY: Compute the minimum-norm solution X
452 * to min( norm( A * X - B ) )
453 * using the rank-revealing orthogonal
454 * factorization.
455 *
456 * Initialize vector IWORK.
457 *
458  DO 70 j = 1, n
459  iwork( j ) = 0
460  70 CONTINUE
461 *
462 * Set LWLSY to the adequate value.
463 *
464  lwlsy = max( 1, mnmin+2*n+nb*( n+1 ),
465  $ 2*mnmin+nb*nrhs )
466 *
467  CALL dlacpy( 'Full', m, n, copya, lda, a, lda )
468  CALL dlacpy( 'Full', m, nrhs, copyb, ldb, b,
469  $ ldb )
470 *
471  srnamt = 'DGELSY'
472  CALL dgelsy( m, n, nrhs, a, lda, b, ldb, iwork,
473  $ rcond, crank, work, lwlsy, info )
474  IF( info.NE.0 )
475  $ CALL alaerh( path, 'DGELSY', info, 0, ' ', m,
476  $ n, nrhs, -1, nb, itype, nfail,
477  $ nerrs, nout )
478 *
479 * Test 3: Compute relative error in svd
480 * workspace: M*N + 4*MIN(M,N) + MAX(M,N)
481 *
482  result( 3 ) = dqrt12( crank, crank, a, lda,
483  $ copys, work, lwork )
484 *
485 * Test 4: Compute error in solution
486 * workspace: M*NRHS + M
487 *
488  CALL dlacpy( 'Full', m, nrhs, copyb, ldb, work,
489  $ ldwork )
490  CALL dqrt16( 'No transpose', m, n, nrhs, copya,
491  $ lda, b, ldb, work, ldwork,
492  $ work( m*nrhs+1 ), result( 4 ) )
493 *
494 * Test 5: Check norm of r'*A
495 * workspace: NRHS*(M+N)
496 *
497  result( 5 ) = zero
498  IF( m.GT.crank )
499  $ result( 5 ) = dqrt17( 'No transpose', 1, m,
500  $ n, nrhs, copya, lda, b, ldb,
501  $ copyb, ldb, c, work, lwork )
502 *
503 * Test 6: Check if x is in the rowspace of A
504 * workspace: (M+NRHS)*(N+2)
505 *
506  result( 6 ) = zero
507 *
508  IF( n.GT.crank )
509  $ result( 6 ) = dqrt14( 'No transpose', m, n,
510  $ nrhs, copya, lda, b, ldb,
511  $ work, lwork )
512 *
513 * Test DGELSS
514 *
515 * DGELSS: Compute the minimum-norm solution X
516 * to min( norm( A * X - B ) )
517 * using the SVD.
518 *
519  CALL dlacpy( 'Full', m, n, copya, lda, a, lda )
520  CALL dlacpy( 'Full', m, nrhs, copyb, ldb, b,
521  $ ldb )
522  srnamt = 'DGELSS'
523  CALL dgelss( m, n, nrhs, a, lda, b, ldb, s,
524  $ rcond, crank, work, lwork, info )
525  IF( info.NE.0 )
526  $ CALL alaerh( path, 'DGELSS', info, 0, ' ', m,
527  $ n, nrhs, -1, nb, itype, nfail,
528  $ nerrs, nout )
529 *
530 * workspace used: 3*min(m,n) +
531 * max(2*min(m,n),nrhs,max(m,n))
532 *
533 * Test 7: Compute relative error in svd
534 *
535  IF( rank.GT.0 ) THEN
536  CALL daxpy( mnmin, -one, copys, 1, s, 1 )
537  result( 7 ) = dasum( mnmin, s, 1 ) /
538  $ dasum( mnmin, copys, 1 ) /
539  $ ( eps*dble( mnmin ) )
540  ELSE
541  result( 7 ) = zero
542  END IF
543 *
544 * Test 8: Compute error in solution
545 *
546  CALL dlacpy( 'Full', m, nrhs, copyb, ldb, work,
547  $ ldwork )
548  CALL dqrt16( 'No transpose', m, n, nrhs, copya,
549  $ lda, b, ldb, work, ldwork,
550  $ work( m*nrhs+1 ), result( 8 ) )
551 *
552 * Test 9: Check norm of r'*A
553 *
554  result( 9 ) = zero
555  IF( m.GT.crank )
556  $ result( 9 ) = dqrt17( 'No transpose', 1, m,
557  $ n, nrhs, copya, lda, b, ldb,
558  $ copyb, ldb, c, work, lwork )
559 *
560 * Test 10: Check if x is in the rowspace of A
561 *
562  result( 10 ) = zero
563  IF( n.GT.crank )
564  $ result( 10 ) = dqrt14( 'No transpose', m, n,
565  $ nrhs, copya, lda, b, ldb,
566  $ work, lwork )
567 *
568 * Test DGELSD
569 *
570 * DGELSD: Compute the minimum-norm solution X
571 * to min( norm( A * X - B ) ) using a
572 * divide and conquer SVD.
573 *
574 * Initialize vector IWORK.
575 *
576  DO 80 j = 1, n
577  iwork( j ) = 0
578  80 CONTINUE
579 *
580  CALL dlacpy( 'Full', m, n, copya, lda, a, lda )
581  CALL dlacpy( 'Full', m, nrhs, copyb, ldb, b,
582  $ ldb )
583 *
584  srnamt = 'DGELSD'
585  CALL dgelsd( m, n, nrhs, a, lda, b, ldb, s,
586  $ rcond, crank, work, lwork, iwork,
587  $ info )
588  IF( info.NE.0 )
589  $ CALL alaerh( path, 'DGELSD', info, 0, ' ', m,
590  $ n, nrhs, -1, nb, itype, nfail,
591  $ nerrs, nout )
592 *
593 * Test 11: Compute relative error in svd
594 *
595  IF( rank.GT.0 ) THEN
596  CALL daxpy( mnmin, -one, copys, 1, s, 1 )
597  result( 11 ) = dasum( mnmin, s, 1 ) /
598  $ dasum( mnmin, copys, 1 ) /
599  $ ( eps*dble( mnmin ) )
600  ELSE
601  result( 11 ) = zero
602  END IF
603 *
604 * Test 12: Compute error in solution
605 *
606  CALL dlacpy( 'Full', m, nrhs, copyb, ldb, work,
607  $ ldwork )
608  CALL dqrt16( 'No transpose', m, n, nrhs, copya,
609  $ lda, b, ldb, work, ldwork,
610  $ work( m*nrhs+1 ), result( 12 ) )
611 *
612 * Test 13: Check norm of r'*A
613 *
614  result( 13 ) = zero
615  IF( m.GT.crank )
616  $ result( 13 ) = dqrt17( 'No transpose', 1, m,
617  $ n, nrhs, copya, lda, b, ldb,
618  $ copyb, ldb, c, work, lwork )
619 *
620 * Test 14: Check if x is in the rowspace of A
621 *
622  result( 14 ) = zero
623  IF( n.GT.crank )
624  $ result( 14 ) = dqrt14( 'No transpose', m, n,
625  $ nrhs, copya, lda, b, ldb,
626  $ work, lwork )
627 *
628 * Print information about the tests that did not
629 * pass the threshold.
630 *
631  DO 90 k = 3, ntests
632  IF( result( k ).GE.thresh ) THEN
633  IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
634  $ CALL alahd( nout, path )
635  WRITE( nout, fmt = 9998 )m, n, nrhs, nb,
636  $ itype, k, result( k )
637  nfail = nfail + 1
638  END IF
639  90 CONTINUE
640  nrun = nrun + 12
641 *
642  100 CONTINUE
643  110 CONTINUE
644  120 CONTINUE
645  130 CONTINUE
646  140 CONTINUE
647  150 CONTINUE
648 *
649 * Print a summary of the results.
650 *
651  CALL alasvm( path, nout, nfail, nrun, nerrs )
652 *
653  9999 FORMAT( ' TRANS=''', a1, ''', M=', i5, ', N=', i5, ', NRHS=', i4,
654  $ ', NB=', i4, ', type', i2, ', test(', i2, ')=', g12.5 )
655  9998 FORMAT( ' M=', i5, ', N=', i5, ', NRHS=', i4, ', NB=', i4,
656  $ ', type', i2, ', test(', i2, ')=', g12.5 )
657  RETURN
658 *
659 * End of DDRVLS
660 *
661  END
subroutine alasvm(TYPE, NOUT, NFAIL, NRUN, NERRS)
ALASVM
Definition: alasvm.f:75
subroutine dlasrt(ID, N, D, INFO)
DLASRT sorts numbers in increasing or decreasing order.
Definition: dlasrt.f:90
subroutine alahd(IOUNIT, PATH)
ALAHD
Definition: alahd.f:95
subroutine alaerh(PATH, SUBNAM, INFO, INFOE, OPTS, M, N, KL, KU, N5, IMAT, NFAIL, NERRS, NOUT)
ALAERH
Definition: alaerh.f:149
subroutine dqrt16(TRANS, M, N, NRHS, A, LDA, X, LDX, B, LDB, RWORK, RESID)
DQRT16
Definition: dqrt16.f:135
subroutine derrls(PATH, NUNIT)
DERRLS
Definition: derrls.f:57
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 dgelsd(M, N, NRHS, A, LDA, B, LDB, S, RCOND, RANK, WORK, LWORK, IWORK, INFO)
DGELSD computes the minimum-norm solution to a linear least squares problem for GE matrices ...
Definition: dgelsd.f:211
subroutine daxpy(N, DA, DX, INCX, DY, INCY)
DAXPY
Definition: daxpy.f:54
subroutine dgemm(TRANSA, TRANSB, M, N, K, ALPHA, A, LDA, B, LDB, BETA, C, LDC)
DGEMM
Definition: dgemm.f:189
subroutine xlaenv(ISPEC, NVALUE)
XLAENV
Definition: xlaenv.f:83
subroutine dqrt15(SCALE, RKSEL, M, N, NRHS, A, LDA, B, LDB, S, RANK, NORMA, NORMB, ISEED, WORK, LWORK)
DQRT15
Definition: dqrt15.f:150
subroutine dgelss(M, N, NRHS, A, LDA, B, LDB, S, RCOND, RANK, WORK, LWORK, INFO)
DGELSS solves overdetermined or underdetermined systems for GE matrices
Definition: dgelss.f:174
subroutine ddrvls(DOTYPE, NM, MVAL, NN, NVAL, NNS, NSVAL, NNB, NBVAL, NXVAL, THRESH, TSTERR, A, COPYA, B, COPYB, C, S, COPYS, WORK, IWORK, NOUT)
DDRVLS
Definition: ddrvls.f:205
subroutine dgels(TRANS, M, N, NRHS, A, LDA, B, LDB, WORK, LWORK, INFO)
DGELS solves overdetermined or underdetermined systems for GE matrices
Definition: dgels.f:185
subroutine dscal(N, DA, DX, INCX)
DSCAL
Definition: dscal.f:55
subroutine dqrt13(SCALE, M, N, A, LDA, NORMA, ISEED)
DQRT13
Definition: dqrt13.f:93
subroutine dgelsy(M, N, NRHS, A, LDA, B, LDB, JPVT, RCOND, RANK, WORK, LWORK, INFO)
DGELSY solves overdetermined or underdetermined systems for GE matrices
Definition: dgelsy.f:206
subroutine dlarnv(IDIST, ISEED, N, X)
DLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition: dlarnv.f:99