1 SUBROUTINE DCHKBD( NSIZES, MVAL, NVAL, NTYPES, DOTYPE, NRHS,
2 $ ISEED, THRESH, A, LDA, BD, BE, S1, S2, X, LDX,
3 $ Y, Z, Q, LDQ, PT, LDPT, U, VT, WORK, LWORK,
4 $ IWORK, NOUT, INFO )
5 *
6 * -- LAPACK test routine (version 3.1) --
7 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
8 * November 2006
9 *
10 * .. Scalar Arguments ..
11 INTEGER INFO, LDA, LDPT, LDQ, LDX, LWORK, NOUT, NRHS,
12 $ NSIZES, NTYPES
13 DOUBLE PRECISION THRESH
14 * ..
15 * .. Array Arguments ..
16 LOGICAL DOTYPE( * )
17 INTEGER ISEED( 4 ), IWORK( * ), MVAL( * ), NVAL( * )
18 DOUBLE PRECISION A( LDA, * ), BD( * ), BE( * ), PT( LDPT, * ),
19 $ Q( LDQ, * ), S1( * ), S2( * ), U( LDPT, * ),
20 $ VT( LDPT, * ), WORK( * ), X( LDX, * ),
21 $ Y( LDX, * ), Z( LDX, * )
22 * ..
23 *
24 * Purpose
25 * =======
26 *
27 * DCHKBD checks the singular value decomposition (SVD) routines.
28 *
29 * DGEBRD reduces a real general m by n matrix A to upper or lower
30 * bidiagonal form B by an orthogonal transformation: Q' * A * P = B
31 * (or A = Q * B * P'). The matrix B is upper bidiagonal if m >= n
32 * and lower bidiagonal if m < n.
33 *
34 * DORGBR generates the orthogonal matrices Q and P' from DGEBRD.
35 * Note that Q and P are not necessarily square.
36 *
37 * DBDSQR computes the singular value decomposition of the bidiagonal
38 * matrix B as B = U S V'. It is called three times to compute
39 * 1) B = U S1 V', where S1 is the diagonal matrix of singular
40 * values and the columns of the matrices U and V are the left
41 * and right singular vectors, respectively, of B.
42 * 2) Same as 1), but the singular values are stored in S2 and the
43 * singular vectors are not computed.
44 * 3) A = (UQ) S (P'V'), the SVD of the original matrix A.
45 * In addition, DBDSQR has an option to apply the left orthogonal matrix
46 * U to a matrix X, useful in least squares applications.
47 *
48 * DBDSDC computes the singular value decomposition of the bidiagonal
49 * matrix B as B = U S V' using divide-and-conquer. It is called twice
50 * to compute
51 * 1) B = U S1 V', where S1 is the diagonal matrix of singular
52 * values and the columns of the matrices U and V are the left
53 * and right singular vectors, respectively, of B.
54 * 2) Same as 1), but the singular values are stored in S2 and the
55 * singular vectors are not computed.
56 *
57 * For each pair of matrix dimensions (M,N) and each selected matrix
58 * type, an M by N matrix A and an M by NRHS matrix X are generated.
59 * The problem dimensions are as follows
60 * A: M x N
61 * Q: M x min(M,N) (but M x M if NRHS > 0)
62 * P: min(M,N) x N
63 * B: min(M,N) x min(M,N)
64 * U, V: min(M,N) x min(M,N)
65 * S1, S2 diagonal, order min(M,N)
66 * X: M x NRHS
67 *
68 * For each generated matrix, 14 tests are performed:
69 *
70 * Test DGEBRD and DORGBR
71 *
72 * (1) | A - Q B PT | / ( |A| max(M,N) ulp ), PT = P'
73 *
74 * (2) | I - Q' Q | / ( M ulp )
75 *
76 * (3) | I - PT PT' | / ( N ulp )
77 *
78 * Test DBDSQR on bidiagonal matrix B
79 *
80 * (4) | B - U S1 VT | / ( |B| min(M,N) ulp ), VT = V'
81 *
82 * (5) | Y - U Z | / ( |Y| max(min(M,N),k) ulp ), where Y = Q' X
83 * and Z = U' Y.
84 * (6) | I - U' U | / ( min(M,N) ulp )
85 *
86 * (7) | I - VT VT' | / ( min(M,N) ulp )
87 *
88 * (8) S1 contains min(M,N) nonnegative values in decreasing order.
89 * (Return 0 if true, 1/ULP if false.)
90 *
91 * (9) | S1 - S2 | / ( |S1| ulp ), where S2 is computed without
92 * computing U and V.
93 *
94 * (10) 0 if the true singular values of B are within THRESH of
95 * those in S1. 2*THRESH if they are not. (Tested using
96 * DSVDCH)
97 *
98 * Test DBDSQR on matrix A
99 *
100 * (11) | A - (QU) S (VT PT) | / ( |A| max(M,N) ulp )
101 *
102 * (12) | X - (QU) Z | / ( |X| max(M,k) ulp )
103 *
104 * (13) | I - (QU)'(QU) | / ( M ulp )
105 *
106 * (14) | I - (VT PT) (PT'VT') | / ( N ulp )
107 *
108 * Test DBDSDC on bidiagonal matrix B
109 *
110 * (15) | B - U S1 VT | / ( |B| min(M,N) ulp ), VT = V'
111 *
112 * (16) | I - U' U | / ( min(M,N) ulp )
113 *
114 * (17) | I - VT VT' | / ( min(M,N) ulp )
115 *
116 * (18) S1 contains min(M,N) nonnegative values in decreasing order.
117 * (Return 0 if true, 1/ULP if false.)
118 *
119 * (19) | S1 - S2 | / ( |S1| ulp ), where S2 is computed without
120 * computing U and V.
121 * The possible matrix types are
122 *
123 * (1) The zero matrix.
124 * (2) The identity matrix.
125 *
126 * (3) A diagonal matrix with evenly spaced entries
127 * 1, ..., ULP and random signs.
128 * (ULP = (first number larger than 1) - 1 )
129 * (4) A diagonal matrix with geometrically spaced entries
130 * 1, ..., ULP and random signs.
131 * (5) A diagonal matrix with "clustered" entries 1, ULP, ..., ULP
132 * and random signs.
133 *
134 * (6) Same as (3), but multiplied by SQRT( overflow threshold )
135 * (7) Same as (3), but multiplied by SQRT( underflow threshold )
136 *
137 * (8) A matrix of the form U D V, where U and V are orthogonal and
138 * D has evenly spaced entries 1, ..., ULP with random signs
139 * on the diagonal.
140 *
141 * (9) A matrix of the form U D V, where U and V are orthogonal and
142 * D has geometrically spaced entries 1, ..., ULP with random
143 * signs on the diagonal.
144 *
145 * (10) A matrix of the form U D V, where U and V are orthogonal and
146 * D has "clustered" entries 1, ULP,..., ULP with random
147 * signs on the diagonal.
148 *
149 * (11) Same as (8), but multiplied by SQRT( overflow threshold )
150 * (12) Same as (8), but multiplied by SQRT( underflow threshold )
151 *
152 * (13) Rectangular matrix with random entries chosen from (-1,1).
153 * (14) Same as (13), but multiplied by SQRT( overflow threshold )
154 * (15) Same as (13), but multiplied by SQRT( underflow threshold )
155 *
156 * Special case:
157 * (16) A bidiagonal matrix with random entries chosen from a
158 * logarithmic distribution on [ulp^2,ulp^(-2)] (I.e., each
159 * entry is e^x, where x is chosen uniformly on
160 * [ 2 log(ulp), -2 log(ulp) ] .) For *this* type:
161 * (a) DGEBRD is not called to reduce it to bidiagonal form.
162 * (b) the bidiagonal is min(M,N) x min(M,N); if M<N, the
163 * matrix will be lower bidiagonal, otherwise upper.
164 * (c) only tests 5--8 and 14 are performed.
165 *
166 * A subset of the full set of matrix types may be selected through
167 * the logical array DOTYPE.
168 *
169 * Arguments
170 * ==========
171 *
172 * NSIZES (input) INTEGER
173 * The number of values of M and N contained in the vectors
174 * MVAL and NVAL. The matrix sizes are used in pairs (M,N).
175 *
176 * MVAL (input) INTEGER array, dimension (NM)
177 * The values of the matrix row dimension M.
178 *
179 * NVAL (input) INTEGER array, dimension (NM)
180 * The values of the matrix column dimension N.
181 *
182 * NTYPES (input) INTEGER
183 * The number of elements in DOTYPE. If it is zero, DCHKBD
184 * does nothing. It must be at least zero. If it is MAXTYP+1
185 * and NSIZES is 1, then an additional type, MAXTYP+1 is
186 * defined, which is to use whatever matrices are in A and B.
187 * This is only useful if DOTYPE(1:MAXTYP) is .FALSE. and
188 * DOTYPE(MAXTYP+1) is .TRUE. .
189 *
190 * DOTYPE (input) LOGICAL array, dimension (NTYPES)
191 * If DOTYPE(j) is .TRUE., then for each size (m,n), a matrix
192 * of type j will be generated. If NTYPES is smaller than the
193 * maximum number of types defined (PARAMETER MAXTYP), then
194 * types NTYPES+1 through MAXTYP will not be generated. If
195 * NTYPES is larger than MAXTYP, DOTYPE(MAXTYP+1) through
196 * DOTYPE(NTYPES) will be ignored.
197 *
198 * NRHS (input) INTEGER
199 * The number of columns in the "right-hand side" matrices X, Y,
200 * and Z, used in testing DBDSQR. If NRHS = 0, then the
201 * operations on the right-hand side will not be tested.
202 * NRHS must be at least 0.
203 *
204 * ISEED (input/output) INTEGER array, dimension (4)
205 * On entry ISEED specifies the seed of the random number
206 * generator. The array elements should be between 0 and 4095;
207 * if not they will be reduced mod 4096. Also, ISEED(4) must
208 * be odd. The values of ISEED are changed on exit, and can be
209 * used in the next call to DCHKBD to continue the same random
210 * number sequence.
211 *
212 * THRESH (input) DOUBLE PRECISION
213 * The threshold value for the test ratios. A result is
214 * included in the output file if RESULT >= THRESH. To have
215 * every test ratio printed, use THRESH = 0. Note that the
216 * expected value of the test ratios is O(1), so THRESH should
217 * be a reasonably small multiple of 1, e.g., 10 or 100.
218 *
219 * A (workspace) DOUBLE PRECISION array, dimension (LDA,NMAX)
220 * where NMAX is the maximum value of N in NVAL.
221 *
222 * LDA (input) INTEGER
223 * The leading dimension of the array A. LDA >= max(1,MMAX),
224 * where MMAX is the maximum value of M in MVAL.
225 *
226 * BD (workspace) DOUBLE PRECISION array, dimension
227 * (max(min(MVAL(j),NVAL(j))))
228 *
229 * BE (workspace) DOUBLE PRECISION array, dimension
230 * (max(min(MVAL(j),NVAL(j))))
231 *
232 * S1 (workspace) DOUBLE PRECISION array, dimension
233 * (max(min(MVAL(j),NVAL(j))))
234 *
235 * S2 (workspace) DOUBLE PRECISION array, dimension
236 * (max(min(MVAL(j),NVAL(j))))
237 *
238 * X (workspace) DOUBLE PRECISION array, dimension (LDX,NRHS)
239 *
240 * LDX (input) INTEGER
241 * The leading dimension of the arrays X, Y, and Z.
242 * LDX >= max(1,MMAX)
243 *
244 * Y (workspace) DOUBLE PRECISION array, dimension (LDX,NRHS)
245 *
246 * Z (workspace) DOUBLE PRECISION array, dimension (LDX,NRHS)
247 *
248 * Q (workspace) DOUBLE PRECISION array, dimension (LDQ,MMAX)
249 *
250 * LDQ (input) INTEGER
251 * The leading dimension of the array Q. LDQ >= max(1,MMAX).
252 *
253 * PT (workspace) DOUBLE PRECISION array, dimension (LDPT,NMAX)
254 *
255 * LDPT (input) INTEGER
256 * The leading dimension of the arrays PT, U, and V.
257 * LDPT >= max(1, max(min(MVAL(j),NVAL(j)))).
258 *
259 * U (workspace) DOUBLE PRECISION array, dimension
260 * (LDPT,max(min(MVAL(j),NVAL(j))))
261 *
262 * V (workspace) DOUBLE PRECISION array, dimension
263 * (LDPT,max(min(MVAL(j),NVAL(j))))
264 *
265 * WORK (workspace) DOUBLE PRECISION array, dimension (LWORK)
266 *
267 * LWORK (input) INTEGER
268 * The number of entries in WORK. This must be at least
269 * 3(M+N) and M(M + max(M,N,k) + 1) + N*min(M,N) for all
270 * pairs (M,N)=(MM(j),NN(j))
271 *
272 * IWORK (workspace) INTEGER array, dimension at least 8*min(M,N)
273 *
274 * NOUT (input) INTEGER
275 * The FORTRAN unit number for printing out error messages
276 * (e.g., if a routine returns IINFO not equal to 0.)
277 *
278 * INFO (output) INTEGER
279 * If 0, then everything ran OK.
280 * -1: NSIZES < 0
281 * -2: Some MM(j) < 0
282 * -3: Some NN(j) < 0
283 * -4: NTYPES < 0
284 * -6: NRHS < 0
285 * -8: THRESH < 0
286 * -11: LDA < 1 or LDA < MMAX, where MMAX is max( MM(j) ).
287 * -17: LDB < 1 or LDB < MMAX.
288 * -21: LDQ < 1 or LDQ < MMAX.
289 * -23: LDPT< 1 or LDPT< MNMAX.
290 * -27: LWORK too small.
291 * If DLATMR, SLATMS, DGEBRD, DORGBR, or DBDSQR,
292 * returns an error code, the
293 * absolute value of it is returned.
294 *
295 *-----------------------------------------------------------------------
296 *
297 * Some Local Variables and Parameters:
298 * ---- ----- --------- --- ----------
299 *
300 * ZERO, ONE Real 0 and 1.
301 * MAXTYP The number of types defined.
302 * NTEST The number of tests performed, or which can
303 * be performed so far, for the current matrix.
304 * MMAX Largest value in NN.
305 * NMAX Largest value in NN.
306 * MNMIN min(MM(j), NN(j)) (the dimension of the bidiagonal
307 * matrix.)
308 * MNMAX The maximum value of MNMIN for j=1,...,NSIZES.
309 * NFAIL The number of tests which have exceeded THRESH
310 * COND, IMODE Values to be passed to the matrix generators.
311 * ANORM Norm of A; passed to matrix generators.
312 *
313 * OVFL, UNFL Overflow and underflow thresholds.
314 * RTOVFL, RTUNFL Square roots of the previous 2 values.
315 * ULP, ULPINV Finest relative precision and its inverse.
316 *
317 * The following four arrays decode JTYPE:
318 * KTYPE(j) The general type (1-10) for type "j".
319 * KMODE(j) The MODE value to be passed to the matrix
320 * generator for type "j".
321 * KMAGN(j) The order of magnitude ( O(1),
322 * O(overflow^(1/2) ), O(underflow^(1/2) )
323 *
324 * ======================================================================
325 *
326 * .. Parameters ..
327 DOUBLE PRECISION ZERO, ONE, TWO, HALF
328 PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0, TWO = 2.0D0,
329 $ HALF = 0.5D0 )
330 INTEGER MAXTYP
331 PARAMETER ( MAXTYP = 16 )
332 * ..
333 * .. Local Scalars ..
334 LOGICAL BADMM, BADNN, BIDIAG
335 CHARACTER UPLO
336 CHARACTER*3 PATH
337 INTEGER I, IINFO, IMODE, ITYPE, J, JCOL, JSIZE, JTYPE,
338 $ LOG2UI, M, MINWRK, MMAX, MNMAX, MNMIN, MQ,
339 $ MTYPES, N, NFAIL, NMAX, NTEST
340 DOUBLE PRECISION AMNINV, ANORM, COND, OVFL, RTOVFL, RTUNFL,
341 $ TEMP1, TEMP2, ULP, ULPINV, UNFL
342 * ..
343 * .. Local Arrays ..
344 INTEGER IDUM( 1 ), IOLDSD( 4 ), KMAGN( MAXTYP ),
345 $ KMODE( MAXTYP ), KTYPE( MAXTYP )
346 DOUBLE PRECISION DUM( 1 ), DUMMA( 1 ), RESULT( 19 )
347 * ..
348 * .. External Functions ..
349 DOUBLE PRECISION DLAMCH, DLARND
350 EXTERNAL DLAMCH, DLARND
351 * ..
352 * .. External Subroutines ..
353 EXTERNAL ALASUM, DBDSDC, DBDSQR, DBDT01, DBDT02, DBDT03,
354 $ DCOPY, DGEBRD, DGEMM, DLABAD, DLACPY, DLAHD2,
355 $ DLASET, DLATMR, DLATMS, DORGBR, DORT01, XERBLA
356 * ..
357 * .. Intrinsic Functions ..
358 INTRINSIC ABS, EXP, INT, LOG, MAX, MIN, SQRT
359 * ..
360 * .. Scalars in Common ..
361 LOGICAL LERR, OK
362 CHARACTER*32 SRNAMT
363 INTEGER INFOT, NUNIT
364 * ..
365 * .. Common blocks ..
366 COMMON / INFOC / INFOT, NUNIT, OK, LERR
367 COMMON / SRNAMC / SRNAMT
368 * ..
369 * .. Data statements ..
370 DATA KTYPE / 1, 2, 5*4, 5*6, 3*9, 10 /
371 DATA KMAGN / 2*1, 3*1, 2, 3, 3*1, 2, 3, 1, 2, 3, 0 /
372 DATA KMODE / 2*0, 4, 3, 1, 4, 4, 4, 3, 1, 4, 4, 0,
373 $ 0, 0, 0 /
374 * ..
375 * .. Executable Statements ..
376 *
377 * Check for errors
378 *
379 INFO = 0
380 *
381 BADMM = .FALSE.
382 BADNN = .FALSE.
383 MMAX = 1
384 NMAX = 1
385 MNMAX = 1
386 MINWRK = 1
387 DO 10 J = 1, NSIZES
388 MMAX = MAX( MMAX, MVAL( J ) )
389 IF( MVAL( J ).LT.0 )
390 $ BADMM = .TRUE.
391 NMAX = MAX( NMAX, NVAL( J ) )
392 IF( NVAL( J ).LT.0 )
393 $ BADNN = .TRUE.
394 MNMAX = MAX( MNMAX, MIN( MVAL( J ), NVAL( J ) ) )
395 MINWRK = MAX( MINWRK, 3*( MVAL( J )+NVAL( J ) ),
396 $ MVAL( J )*( MVAL( J )+MAX( MVAL( J ), NVAL( J ),
397 $ NRHS )+1 )+NVAL( J )*MIN( NVAL( J ), MVAL( J ) ) )
398 10 CONTINUE
399 *
400 * Check for errors
401 *
402 IF( NSIZES.LT.0 ) THEN
403 INFO = -1
404 ELSE IF( BADMM ) THEN
405 INFO = -2
406 ELSE IF( BADNN ) THEN
407 INFO = -3
408 ELSE IF( NTYPES.LT.0 ) THEN
409 INFO = -4
410 ELSE IF( NRHS.LT.0 ) THEN
411 INFO = -6
412 ELSE IF( LDA.LT.MMAX ) THEN
413 INFO = -11
414 ELSE IF( LDX.LT.MMAX ) THEN
415 INFO = -17
416 ELSE IF( LDQ.LT.MMAX ) THEN
417 INFO = -21
418 ELSE IF( LDPT.LT.MNMAX ) THEN
419 INFO = -23
420 ELSE IF( MINWRK.GT.LWORK ) THEN
421 INFO = -27
422 END IF
423 *
424 IF( INFO.NE.0 ) THEN
425 CALL XERBLA( 'DCHKBD', -INFO )
426 RETURN
427 END IF
428 *
429 * Initialize constants
430 *
431 PATH( 1: 1 ) = 'Double precision'
432 PATH( 2: 3 ) = 'BD'
433 NFAIL = 0
434 NTEST = 0
435 UNFL = DLAMCH( 'Safe minimum' )
436 OVFL = DLAMCH( 'Overflow' )
437 CALL DLABAD( UNFL, OVFL )
438 ULP = DLAMCH( 'Precision' )
439 ULPINV = ONE / ULP
440 LOG2UI = INT( LOG( ULPINV ) / LOG( TWO ) )
441 RTUNFL = SQRT( UNFL )
442 RTOVFL = SQRT( OVFL )
443 INFOT = 0
444 *
445 * Loop over sizes, types
446 *
447 DO 200 JSIZE = 1, NSIZES
448 M = MVAL( JSIZE )
449 N = NVAL( JSIZE )
450 MNMIN = MIN( M, N )
451 AMNINV = ONE / MAX( M, N, 1 )
452 *
453 IF( NSIZES.NE.1 ) THEN
454 MTYPES = MIN( MAXTYP, NTYPES )
455 ELSE
456 MTYPES = MIN( MAXTYP+1, NTYPES )
457 END IF
458 *
459 DO 190 JTYPE = 1, MTYPES
460 IF( .NOT.DOTYPE( JTYPE ) )
461 $ GO TO 190
462 *
463 DO 20 J = 1, 4
464 IOLDSD( J ) = ISEED( J )
465 20 CONTINUE
466 *
467 DO 30 J = 1, 14
468 RESULT( J ) = -ONE
469 30 CONTINUE
470 *
471 UPLO = ' '
472 *
473 * Compute "A"
474 *
475 * Control parameters:
476 *
477 * KMAGN KMODE KTYPE
478 * =1 O(1) clustered 1 zero
479 * =2 large clustered 2 identity
480 * =3 small exponential (none)
481 * =4 arithmetic diagonal, (w/ eigenvalues)
482 * =5 random symmetric, w/ eigenvalues
483 * =6 nonsymmetric, w/ singular values
484 * =7 random diagonal
485 * =8 random symmetric
486 * =9 random nonsymmetric
487 * =10 random bidiagonal (log. distrib.)
488 *
489 IF( MTYPES.GT.MAXTYP )
490 $ GO TO 100
491 *
492 ITYPE = KTYPE( JTYPE )
493 IMODE = KMODE( JTYPE )
494 *
495 * Compute norm
496 *
497 GO TO ( 40, 50, 60 )KMAGN( JTYPE )
498 *
499 40 CONTINUE
500 ANORM = ONE
501 GO TO 70
502 *
503 50 CONTINUE
504 ANORM = ( RTOVFL*ULP )*AMNINV
505 GO TO 70
506 *
507 60 CONTINUE
508 ANORM = RTUNFL*MAX( M, N )*ULPINV
509 GO TO 70
510 *
511 70 CONTINUE
512 *
513 CALL DLASET( 'Full', LDA, N, ZERO, ZERO, A, LDA )
514 IINFO = 0
515 COND = ULPINV
516 *
517 BIDIAG = .FALSE.
518 IF( ITYPE.EQ.1 ) THEN
519 *
520 * Zero matrix
521 *
522 IINFO = 0
523 *
524 ELSE IF( ITYPE.EQ.2 ) THEN
525 *
526 * Identity
527 *
528 DO 80 JCOL = 1, MNMIN
529 A( JCOL, JCOL ) = ANORM
530 80 CONTINUE
531 *
532 ELSE IF( ITYPE.EQ.4 ) THEN
533 *
534 * Diagonal Matrix, [Eigen]values Specified
535 *
536 CALL DLATMS( MNMIN, MNMIN, 'S', ISEED, 'N', WORK, IMODE,
537 $ COND, ANORM, 0, 0, 'N', A, LDA,
538 $ WORK( MNMIN+1 ), IINFO )
539 *
540 ELSE IF( ITYPE.EQ.5 ) THEN
541 *
542 * Symmetric, eigenvalues specified
543 *
544 CALL DLATMS( MNMIN, MNMIN, 'S', ISEED, 'S', WORK, IMODE,
545 $ COND, ANORM, M, N, 'N', A, LDA,
546 $ WORK( MNMIN+1 ), IINFO )
547 *
548 ELSE IF( ITYPE.EQ.6 ) THEN
549 *
550 * Nonsymmetric, singular values specified
551 *
552 CALL DLATMS( M, N, 'S', ISEED, 'N', WORK, IMODE, COND,
553 $ ANORM, M, N, 'N', A, LDA, WORK( MNMIN+1 ),
554 $ IINFO )
555 *
556 ELSE IF( ITYPE.EQ.7 ) THEN
557 *
558 * Diagonal, random entries
559 *
560 CALL DLATMR( MNMIN, MNMIN, 'S', ISEED, 'N', WORK, 6, ONE,
561 $ ONE, 'T', 'N', WORK( MNMIN+1 ), 1, ONE,
562 $ WORK( 2*MNMIN+1 ), 1, ONE, 'N', IWORK, 0, 0,
563 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
564 *
565 ELSE IF( ITYPE.EQ.8 ) THEN
566 *
567 * Symmetric, random entries
568 *
569 CALL DLATMR( MNMIN, MNMIN, 'S', ISEED, 'S', WORK, 6, ONE,
570 $ ONE, 'T', 'N', WORK( MNMIN+1 ), 1, ONE,
571 $ WORK( M+MNMIN+1 ), 1, ONE, 'N', IWORK, M, N,
572 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
573 *
574 ELSE IF( ITYPE.EQ.9 ) THEN
575 *
576 * Nonsymmetric, random entries
577 *
578 CALL DLATMR( M, N, 'S', ISEED, 'N', WORK, 6, ONE, ONE,
579 $ 'T', 'N', WORK( MNMIN+1 ), 1, ONE,
580 $ WORK( M+MNMIN+1 ), 1, ONE, 'N', IWORK, M, N,
581 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
582 *
583 ELSE IF( ITYPE.EQ.10 ) THEN
584 *
585 * Bidiagonal, random entries
586 *
587 TEMP1 = -TWO*LOG( ULP )
588 DO 90 J = 1, MNMIN
589 BD( J ) = EXP( TEMP1*DLARND( 2, ISEED ) )
590 IF( J.LT.MNMIN )
591 $ BE( J ) = EXP( TEMP1*DLARND( 2, ISEED ) )
592 90 CONTINUE
593 *
594 IINFO = 0
595 BIDIAG = .TRUE.
596 IF( M.GE.N ) THEN
597 UPLO = 'U'
598 ELSE
599 UPLO = 'L'
600 END IF
601 ELSE
602 IINFO = 1
603 END IF
604 *
605 IF( IINFO.EQ.0 ) THEN
606 *
607 * Generate Right-Hand Side
608 *
609 IF( BIDIAG ) THEN
610 CALL DLATMR( MNMIN, NRHS, 'S', ISEED, 'N', WORK, 6,
611 $ ONE, ONE, 'T', 'N', WORK( MNMIN+1 ), 1,
612 $ ONE, WORK( 2*MNMIN+1 ), 1, ONE, 'N',
613 $ IWORK, MNMIN, NRHS, ZERO, ONE, 'NO', Y,
614 $ LDX, IWORK, IINFO )
615 ELSE
616 CALL DLATMR( M, NRHS, 'S', ISEED, 'N', WORK, 6, ONE,
617 $ ONE, 'T', 'N', WORK( M+1 ), 1, ONE,
618 $ WORK( 2*M+1 ), 1, ONE, 'N', IWORK, M,
619 $ NRHS, ZERO, ONE, 'NO', X, LDX, IWORK,
620 $ IINFO )
621 END IF
622 END IF
623 *
624 * Error Exit
625 *
626 IF( IINFO.NE.0 ) THEN
627 WRITE( NOUT, FMT = 9998 )'Generator', IINFO, M, N,
628 $ JTYPE, IOLDSD
629 INFO = ABS( IINFO )
630 RETURN
631 END IF
632 *
633 100 CONTINUE
634 *
635 * Call DGEBRD and DORGBR to compute B, Q, and P, do tests.
636 *
637 IF( .NOT.BIDIAG ) THEN
638 *
639 * Compute transformations to reduce A to bidiagonal form:
640 * B := Q' * A * P.
641 *
642 CALL DLACPY( ' ', M, N, A, LDA, Q, LDQ )
643 CALL DGEBRD( M, N, Q, LDQ, BD, BE, WORK, WORK( MNMIN+1 ),
644 $ WORK( 2*MNMIN+1 ), LWORK-2*MNMIN, IINFO )
645 *
646 * Check error code from DGEBRD.
647 *
648 IF( IINFO.NE.0 ) THEN
649 WRITE( NOUT, FMT = 9998 )'DGEBRD', IINFO, M, N,
650 $ JTYPE, IOLDSD
651 INFO = ABS( IINFO )
652 RETURN
653 END IF
654 *
655 CALL DLACPY( ' ', M, N, Q, LDQ, PT, LDPT )
656 IF( M.GE.N ) THEN
657 UPLO = 'U'
658 ELSE
659 UPLO = 'L'
660 END IF
661 *
662 * Generate Q
663 *
664 MQ = M
665 IF( NRHS.LE.0 )
666 $ MQ = MNMIN
667 CALL DORGBR( 'Q', M, MQ, N, Q, LDQ, WORK,
668 $ WORK( 2*MNMIN+1 ), LWORK-2*MNMIN, IINFO )
669 *
670 * Check error code from DORGBR.
671 *
672 IF( IINFO.NE.0 ) THEN
673 WRITE( NOUT, FMT = 9998 )'DORGBR(Q)', IINFO, M, N,
674 $ JTYPE, IOLDSD
675 INFO = ABS( IINFO )
676 RETURN
677 END IF
678 *
679 * Generate P'
680 *
681 CALL DORGBR( 'P', MNMIN, N, M, PT, LDPT, WORK( MNMIN+1 ),
682 $ WORK( 2*MNMIN+1 ), LWORK-2*MNMIN, IINFO )
683 *
684 * Check error code from DORGBR.
685 *
686 IF( IINFO.NE.0 ) THEN
687 WRITE( NOUT, FMT = 9998 )'DORGBR(P)', IINFO, M, N,
688 $ JTYPE, IOLDSD
689 INFO = ABS( IINFO )
690 RETURN
691 END IF
692 *
693 * Apply Q' to an M by NRHS matrix X: Y := Q' * X.
694 *
695 CALL DGEMM( 'Transpose', 'No transpose', M, NRHS, M, ONE,
696 $ Q, LDQ, X, LDX, ZERO, Y, LDX )
697 *
698 * Test 1: Check the decomposition A := Q * B * PT
699 * 2: Check the orthogonality of Q
700 * 3: Check the orthogonality of PT
701 *
702 CALL DBDT01( M, N, 1, A, LDA, Q, LDQ, BD, BE, PT, LDPT,
703 $ WORK, RESULT( 1 ) )
704 CALL DORT01( 'Columns', M, MQ, Q, LDQ, WORK, LWORK,
705 $ RESULT( 2 ) )
706 CALL DORT01( 'Rows', MNMIN, N, PT, LDPT, WORK, LWORK,
707 $ RESULT( 3 ) )
708 END IF
709 *
710 * Use DBDSQR to form the SVD of the bidiagonal matrix B:
711 * B := U * S1 * VT, and compute Z = U' * Y.
712 *
713 CALL DCOPY( MNMIN, BD, 1, S1, 1 )
714 IF( MNMIN.GT.0 )
715 $ CALL DCOPY( MNMIN-1, BE, 1, WORK, 1 )
716 CALL DLACPY( ' ', M, NRHS, Y, LDX, Z, LDX )
717 CALL DLASET( 'Full', MNMIN, MNMIN, ZERO, ONE, U, LDPT )
718 CALL DLASET( 'Full', MNMIN, MNMIN, ZERO, ONE, VT, LDPT )
719 *
720 CALL DBDSQR( UPLO, MNMIN, MNMIN, MNMIN, NRHS, S1, WORK, VT,
721 $ LDPT, U, LDPT, Z, LDX, WORK( MNMIN+1 ), IINFO )
722 *
723 * Check error code from DBDSQR.
724 *
725 IF( IINFO.NE.0 ) THEN
726 WRITE( NOUT, FMT = 9998 )'DBDSQR(vects)', IINFO, M, N,
727 $ JTYPE, IOLDSD
728 INFO = ABS( IINFO )
729 IF( IINFO.LT.0 ) THEN
730 RETURN
731 ELSE
732 RESULT( 4 ) = ULPINV
733 GO TO 170
734 END IF
735 END IF
736 *
737 * Use DBDSQR to compute only the singular values of the
738 * bidiagonal matrix B; U, VT, and Z should not be modified.
739 *
740 CALL DCOPY( MNMIN, BD, 1, S2, 1 )
741 IF( MNMIN.GT.0 )
742 $ CALL DCOPY( MNMIN-1, BE, 1, WORK, 1 )
743 *
744 CALL DBDSQR( UPLO, MNMIN, 0, 0, 0, S2, WORK, VT, LDPT, U,
745 $ LDPT, Z, LDX, WORK( MNMIN+1 ), IINFO )
746 *
747 * Check error code from DBDSQR.
748 *
749 IF( IINFO.NE.0 ) THEN
750 WRITE( NOUT, FMT = 9998 )'DBDSQR(values)', IINFO, M, N,
751 $ JTYPE, IOLDSD
752 INFO = ABS( IINFO )
753 IF( IINFO.LT.0 ) THEN
754 RETURN
755 ELSE
756 RESULT( 9 ) = ULPINV
757 GO TO 170
758 END IF
759 END IF
760 *
761 * Test 4: Check the decomposition B := U * S1 * VT
762 * 5: Check the computation Z := U' * Y
763 * 6: Check the orthogonality of U
764 * 7: Check the orthogonality of VT
765 *
766 CALL DBDT03( UPLO, MNMIN, 1, BD, BE, U, LDPT, S1, VT, LDPT,
767 $ WORK, RESULT( 4 ) )
768 CALL DBDT02( MNMIN, NRHS, Y, LDX, Z, LDX, U, LDPT, WORK,
769 $ RESULT( 5 ) )
770 CALL DORT01( 'Columns', MNMIN, MNMIN, U, LDPT, WORK, LWORK,
771 $ RESULT( 6 ) )
772 CALL DORT01( 'Rows', MNMIN, MNMIN, VT, LDPT, WORK, LWORK,
773 $ RESULT( 7 ) )
774 *
775 * Test 8: Check that the singular values are sorted in
776 * non-increasing order and are non-negative
777 *
778 RESULT( 8 ) = ZERO
779 DO 110 I = 1, MNMIN - 1
780 IF( S1( I ).LT.S1( I+1 ) )
781 $ RESULT( 8 ) = ULPINV
782 IF( S1( I ).LT.ZERO )
783 $ RESULT( 8 ) = ULPINV
784 110 CONTINUE
785 IF( MNMIN.GE.1 ) THEN
786 IF( S1( MNMIN ).LT.ZERO )
787 $ RESULT( 8 ) = ULPINV
788 END IF
789 *
790 * Test 9: Compare DBDSQR with and without singular vectors
791 *
792 TEMP2 = ZERO
793 *
794 DO 120 J = 1, MNMIN
795 TEMP1 = ABS( S1( J )-S2( J ) ) /
796 $ MAX( SQRT( UNFL )*MAX( S1( 1 ), ONE ),
797 $ ULP*MAX( ABS( S1( J ) ), ABS( S2( J ) ) ) )
798 TEMP2 = MAX( TEMP1, TEMP2 )
799 120 CONTINUE
800 *
801 RESULT( 9 ) = TEMP2
802 *
803 * Test 10: Sturm sequence test of singular values
804 * Go up by factors of two until it succeeds
805 *
806 TEMP1 = THRESH*( HALF-ULP )
807 *
808 DO 130 J = 0, LOG2UI
809 * CALL DSVDCH( MNMIN, BD, BE, S1, TEMP1, IINFO )
810 IF( IINFO.EQ.0 )
811 $ GO TO 140
812 TEMP1 = TEMP1*TWO
813 130 CONTINUE
814 *
815 140 CONTINUE
816 RESULT( 10 ) = TEMP1
817 *
818 * Use DBDSQR to form the decomposition A := (QU) S (VT PT)
819 * from the bidiagonal form A := Q B PT.
820 *
821 IF( .NOT.BIDIAG ) THEN
822 CALL DCOPY( MNMIN, BD, 1, S2, 1 )
823 IF( MNMIN.GT.0 )
824 $ CALL DCOPY( MNMIN-1, BE, 1, WORK, 1 )
825 *
826 CALL DBDSQR( UPLO, MNMIN, N, M, NRHS, S2, WORK, PT, LDPT,
827 $ Q, LDQ, Y, LDX, WORK( MNMIN+1 ), IINFO )
828 *
829 * Test 11: Check the decomposition A := Q*U * S2 * VT*PT
830 * 12: Check the computation Z := U' * Q' * X
831 * 13: Check the orthogonality of Q*U
832 * 14: Check the orthogonality of VT*PT
833 *
834 CALL DBDT01( M, N, 0, A, LDA, Q, LDQ, S2, DUMMA, PT,
835 $ LDPT, WORK, RESULT( 11 ) )
836 CALL DBDT02( M, NRHS, X, LDX, Y, LDX, Q, LDQ, WORK,
837 $ RESULT( 12 ) )
838 CALL DORT01( 'Columns', M, MQ, Q, LDQ, WORK, LWORK,
839 $ RESULT( 13 ) )
840 CALL DORT01( 'Rows', MNMIN, N, PT, LDPT, WORK, LWORK,
841 $ RESULT( 14 ) )
842 END IF
843 *
844 * Use DBDSDC to form the SVD of the bidiagonal matrix B:
845 * B := U * S1 * VT
846 *
847 CALL DCOPY( MNMIN, BD, 1, S1, 1 )
848 IF( MNMIN.GT.0 )
849 $ CALL DCOPY( MNMIN-1, BE, 1, WORK, 1 )
850 CALL DLASET( 'Full', MNMIN, MNMIN, ZERO, ONE, U, LDPT )
851 CALL DLASET( 'Full', MNMIN, MNMIN, ZERO, ONE, VT, LDPT )
852 *
853 CALL DBDSDC( UPLO, 'I', MNMIN, S1, WORK, U, LDPT, VT, LDPT,
854 $ DUM, IDUM, WORK( MNMIN+1 ), IWORK, IINFO )
855 *
856 * Check error code from DBDSDC.
857 *
858 IF( IINFO.NE.0 ) THEN
859 WRITE( NOUT, FMT = 9998 )'DBDSDC(vects)', IINFO, M, N,
860 $ JTYPE, IOLDSD
861 INFO = ABS( IINFO )
862 IF( IINFO.LT.0 ) THEN
863 RETURN
864 ELSE
865 RESULT( 15 ) = ULPINV
866 GO TO 170
867 END IF
868 END IF
869 *
870 * Use DBDSDC to compute only the singular values of the
871 * bidiagonal matrix B; U and VT should not be modified.
872 *
873 CALL DCOPY( MNMIN, BD, 1, S2, 1 )
874 IF( MNMIN.GT.0 )
875 $ CALL DCOPY( MNMIN-1, BE, 1, WORK, 1 )
876 *
877 CALL DBDSDC( UPLO, 'N', MNMIN, S2, WORK, DUM, 1, DUM, 1,
878 $ DUM, IDUM, WORK( MNMIN+1 ), IWORK, IINFO )
879 *
880 * Check error code from DBDSDC.
881 *
882 IF( IINFO.NE.0 ) THEN
883 WRITE( NOUT, FMT = 9998 )'DBDSDC(values)', IINFO, M, N,
884 $ JTYPE, IOLDSD
885 INFO = ABS( IINFO )
886 IF( IINFO.LT.0 ) THEN
887 RETURN
888 ELSE
889 RESULT( 18 ) = ULPINV
890 GO TO 170
891 END IF
892 END IF
893 *
894 * Test 15: Check the decomposition B := U * S1 * VT
895 * 16: Check the orthogonality of U
896 * 17: Check the orthogonality of VT
897 *
898 CALL DBDT03( UPLO, MNMIN, 1, BD, BE, U, LDPT, S1, VT, LDPT,
899 $ WORK, RESULT( 15 ) )
900 CALL DORT01( 'Columns', MNMIN, MNMIN, U, LDPT, WORK, LWORK,
901 $ RESULT( 16 ) )
902 CALL DORT01( 'Rows', MNMIN, MNMIN, VT, LDPT, WORK, LWORK,
903 $ RESULT( 17 ) )
904 *
905 * Test 18: Check that the singular values are sorted in
906 * non-increasing order and are non-negative
907 *
908 RESULT( 18 ) = ZERO
909 DO 150 I = 1, MNMIN - 1
910 IF( S1( I ).LT.S1( I+1 ) )
911 $ RESULT( 18 ) = ULPINV
912 IF( S1( I ).LT.ZERO )
913 $ RESULT( 18 ) = ULPINV
914 150 CONTINUE
915 IF( MNMIN.GE.1 ) THEN
916 IF( S1( MNMIN ).LT.ZERO )
917 $ RESULT( 18 ) = ULPINV
918 END IF
919 *
920 * Test 19: Compare DBDSQR with and without singular vectors
921 *
922 TEMP2 = ZERO
923 *
924 DO 160 J = 1, MNMIN
925 TEMP1 = ABS( S1( J )-S2( J ) ) /
926 $ MAX( SQRT( UNFL )*MAX( S1( 1 ), ONE ),
927 $ ULP*MAX( ABS( S1( 1 ) ), ABS( S2( 1 ) ) ) )
928 TEMP2 = MAX( TEMP1, TEMP2 )
929 160 CONTINUE
930 *
931 RESULT( 19 ) = TEMP2
932 *
933 * End of Loop -- Check for RESULT(j) > THRESH
934 *
935 170 CONTINUE
936 DO 180 J = 1, 19
937 IF( RESULT( J ).GE.THRESH ) THEN
938 IF( NFAIL.EQ.0 )
939 $ CALL DLAHD2( NOUT, PATH )
940 WRITE( NOUT, FMT = 9999 )M, N, JTYPE, IOLDSD, J,
941 $ RESULT( J )
942 NFAIL = NFAIL + 1
943 END IF
944 180 CONTINUE
945 IF( .NOT.BIDIAG ) THEN
946 NTEST = NTEST + 19
947 ELSE
948 NTEST = NTEST + 5
949 END IF
950 *
951 190 CONTINUE
952 200 CONTINUE
953 *
954 * Summary
955 *
956 CALL ALASUM( PATH, NOUT, NFAIL, NTEST, 0 )
957 *
958 RETURN
959 *
960 * End of DCHKBD
961 *
962 9999 FORMAT( ' M=', I5, ', N=', I5, ', type ', I2, ', seed=',
963 $ 4( I4, ',' ), ' test(', I2, ')=', G11.4 )
964 9998 FORMAT( ' DCHKBD: ', A, ' returned INFO=', I6, '.', / 9X, 'M=',
965 $ I6, ', N=', I6, ', JTYPE=', I6, ', ISEED=(', 3( I5, ',' ),
966 $ I5, ')' )
967 *
968 END
2 $ ISEED, THRESH, A, LDA, BD, BE, S1, S2, X, LDX,
3 $ Y, Z, Q, LDQ, PT, LDPT, U, VT, WORK, LWORK,
4 $ IWORK, NOUT, INFO )
5 *
6 * -- LAPACK test routine (version 3.1) --
7 * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
8 * November 2006
9 *
10 * .. Scalar Arguments ..
11 INTEGER INFO, LDA, LDPT, LDQ, LDX, LWORK, NOUT, NRHS,
12 $ NSIZES, NTYPES
13 DOUBLE PRECISION THRESH
14 * ..
15 * .. Array Arguments ..
16 LOGICAL DOTYPE( * )
17 INTEGER ISEED( 4 ), IWORK( * ), MVAL( * ), NVAL( * )
18 DOUBLE PRECISION A( LDA, * ), BD( * ), BE( * ), PT( LDPT, * ),
19 $ Q( LDQ, * ), S1( * ), S2( * ), U( LDPT, * ),
20 $ VT( LDPT, * ), WORK( * ), X( LDX, * ),
21 $ Y( LDX, * ), Z( LDX, * )
22 * ..
23 *
24 * Purpose
25 * =======
26 *
27 * DCHKBD checks the singular value decomposition (SVD) routines.
28 *
29 * DGEBRD reduces a real general m by n matrix A to upper or lower
30 * bidiagonal form B by an orthogonal transformation: Q' * A * P = B
31 * (or A = Q * B * P'). The matrix B is upper bidiagonal if m >= n
32 * and lower bidiagonal if m < n.
33 *
34 * DORGBR generates the orthogonal matrices Q and P' from DGEBRD.
35 * Note that Q and P are not necessarily square.
36 *
37 * DBDSQR computes the singular value decomposition of the bidiagonal
38 * matrix B as B = U S V'. It is called three times to compute
39 * 1) B = U S1 V', where S1 is the diagonal matrix of singular
40 * values and the columns of the matrices U and V are the left
41 * and right singular vectors, respectively, of B.
42 * 2) Same as 1), but the singular values are stored in S2 and the
43 * singular vectors are not computed.
44 * 3) A = (UQ) S (P'V'), the SVD of the original matrix A.
45 * In addition, DBDSQR has an option to apply the left orthogonal matrix
46 * U to a matrix X, useful in least squares applications.
47 *
48 * DBDSDC computes the singular value decomposition of the bidiagonal
49 * matrix B as B = U S V' using divide-and-conquer. It is called twice
50 * to compute
51 * 1) B = U S1 V', where S1 is the diagonal matrix of singular
52 * values and the columns of the matrices U and V are the left
53 * and right singular vectors, respectively, of B.
54 * 2) Same as 1), but the singular values are stored in S2 and the
55 * singular vectors are not computed.
56 *
57 * For each pair of matrix dimensions (M,N) and each selected matrix
58 * type, an M by N matrix A and an M by NRHS matrix X are generated.
59 * The problem dimensions are as follows
60 * A: M x N
61 * Q: M x min(M,N) (but M x M if NRHS > 0)
62 * P: min(M,N) x N
63 * B: min(M,N) x min(M,N)
64 * U, V: min(M,N) x min(M,N)
65 * S1, S2 diagonal, order min(M,N)
66 * X: M x NRHS
67 *
68 * For each generated matrix, 14 tests are performed:
69 *
70 * Test DGEBRD and DORGBR
71 *
72 * (1) | A - Q B PT | / ( |A| max(M,N) ulp ), PT = P'
73 *
74 * (2) | I - Q' Q | / ( M ulp )
75 *
76 * (3) | I - PT PT' | / ( N ulp )
77 *
78 * Test DBDSQR on bidiagonal matrix B
79 *
80 * (4) | B - U S1 VT | / ( |B| min(M,N) ulp ), VT = V'
81 *
82 * (5) | Y - U Z | / ( |Y| max(min(M,N),k) ulp ), where Y = Q' X
83 * and Z = U' Y.
84 * (6) | I - U' U | / ( min(M,N) ulp )
85 *
86 * (7) | I - VT VT' | / ( min(M,N) ulp )
87 *
88 * (8) S1 contains min(M,N) nonnegative values in decreasing order.
89 * (Return 0 if true, 1/ULP if false.)
90 *
91 * (9) | S1 - S2 | / ( |S1| ulp ), where S2 is computed without
92 * computing U and V.
93 *
94 * (10) 0 if the true singular values of B are within THRESH of
95 * those in S1. 2*THRESH if they are not. (Tested using
96 * DSVDCH)
97 *
98 * Test DBDSQR on matrix A
99 *
100 * (11) | A - (QU) S (VT PT) | / ( |A| max(M,N) ulp )
101 *
102 * (12) | X - (QU) Z | / ( |X| max(M,k) ulp )
103 *
104 * (13) | I - (QU)'(QU) | / ( M ulp )
105 *
106 * (14) | I - (VT PT) (PT'VT') | / ( N ulp )
107 *
108 * Test DBDSDC on bidiagonal matrix B
109 *
110 * (15) | B - U S1 VT | / ( |B| min(M,N) ulp ), VT = V'
111 *
112 * (16) | I - U' U | / ( min(M,N) ulp )
113 *
114 * (17) | I - VT VT' | / ( min(M,N) ulp )
115 *
116 * (18) S1 contains min(M,N) nonnegative values in decreasing order.
117 * (Return 0 if true, 1/ULP if false.)
118 *
119 * (19) | S1 - S2 | / ( |S1| ulp ), where S2 is computed without
120 * computing U and V.
121 * The possible matrix types are
122 *
123 * (1) The zero matrix.
124 * (2) The identity matrix.
125 *
126 * (3) A diagonal matrix with evenly spaced entries
127 * 1, ..., ULP and random signs.
128 * (ULP = (first number larger than 1) - 1 )
129 * (4) A diagonal matrix with geometrically spaced entries
130 * 1, ..., ULP and random signs.
131 * (5) A diagonal matrix with "clustered" entries 1, ULP, ..., ULP
132 * and random signs.
133 *
134 * (6) Same as (3), but multiplied by SQRT( overflow threshold )
135 * (7) Same as (3), but multiplied by SQRT( underflow threshold )
136 *
137 * (8) A matrix of the form U D V, where U and V are orthogonal and
138 * D has evenly spaced entries 1, ..., ULP with random signs
139 * on the diagonal.
140 *
141 * (9) A matrix of the form U D V, where U and V are orthogonal and
142 * D has geometrically spaced entries 1, ..., ULP with random
143 * signs on the diagonal.
144 *
145 * (10) A matrix of the form U D V, where U and V are orthogonal and
146 * D has "clustered" entries 1, ULP,..., ULP with random
147 * signs on the diagonal.
148 *
149 * (11) Same as (8), but multiplied by SQRT( overflow threshold )
150 * (12) Same as (8), but multiplied by SQRT( underflow threshold )
151 *
152 * (13) Rectangular matrix with random entries chosen from (-1,1).
153 * (14) Same as (13), but multiplied by SQRT( overflow threshold )
154 * (15) Same as (13), but multiplied by SQRT( underflow threshold )
155 *
156 * Special case:
157 * (16) A bidiagonal matrix with random entries chosen from a
158 * logarithmic distribution on [ulp^2,ulp^(-2)] (I.e., each
159 * entry is e^x, where x is chosen uniformly on
160 * [ 2 log(ulp), -2 log(ulp) ] .) For *this* type:
161 * (a) DGEBRD is not called to reduce it to bidiagonal form.
162 * (b) the bidiagonal is min(M,N) x min(M,N); if M<N, the
163 * matrix will be lower bidiagonal, otherwise upper.
164 * (c) only tests 5--8 and 14 are performed.
165 *
166 * A subset of the full set of matrix types may be selected through
167 * the logical array DOTYPE.
168 *
169 * Arguments
170 * ==========
171 *
172 * NSIZES (input) INTEGER
173 * The number of values of M and N contained in the vectors
174 * MVAL and NVAL. The matrix sizes are used in pairs (M,N).
175 *
176 * MVAL (input) INTEGER array, dimension (NM)
177 * The values of the matrix row dimension M.
178 *
179 * NVAL (input) INTEGER array, dimension (NM)
180 * The values of the matrix column dimension N.
181 *
182 * NTYPES (input) INTEGER
183 * The number of elements in DOTYPE. If it is zero, DCHKBD
184 * does nothing. It must be at least zero. If it is MAXTYP+1
185 * and NSIZES is 1, then an additional type, MAXTYP+1 is
186 * defined, which is to use whatever matrices are in A and B.
187 * This is only useful if DOTYPE(1:MAXTYP) is .FALSE. and
188 * DOTYPE(MAXTYP+1) is .TRUE. .
189 *
190 * DOTYPE (input) LOGICAL array, dimension (NTYPES)
191 * If DOTYPE(j) is .TRUE., then for each size (m,n), a matrix
192 * of type j will be generated. If NTYPES is smaller than the
193 * maximum number of types defined (PARAMETER MAXTYP), then
194 * types NTYPES+1 through MAXTYP will not be generated. If
195 * NTYPES is larger than MAXTYP, DOTYPE(MAXTYP+1) through
196 * DOTYPE(NTYPES) will be ignored.
197 *
198 * NRHS (input) INTEGER
199 * The number of columns in the "right-hand side" matrices X, Y,
200 * and Z, used in testing DBDSQR. If NRHS = 0, then the
201 * operations on the right-hand side will not be tested.
202 * NRHS must be at least 0.
203 *
204 * ISEED (input/output) INTEGER array, dimension (4)
205 * On entry ISEED specifies the seed of the random number
206 * generator. The array elements should be between 0 and 4095;
207 * if not they will be reduced mod 4096. Also, ISEED(4) must
208 * be odd. The values of ISEED are changed on exit, and can be
209 * used in the next call to DCHKBD to continue the same random
210 * number sequence.
211 *
212 * THRESH (input) DOUBLE PRECISION
213 * The threshold value for the test ratios. A result is
214 * included in the output file if RESULT >= THRESH. To have
215 * every test ratio printed, use THRESH = 0. Note that the
216 * expected value of the test ratios is O(1), so THRESH should
217 * be a reasonably small multiple of 1, e.g., 10 or 100.
218 *
219 * A (workspace) DOUBLE PRECISION array, dimension (LDA,NMAX)
220 * where NMAX is the maximum value of N in NVAL.
221 *
222 * LDA (input) INTEGER
223 * The leading dimension of the array A. LDA >= max(1,MMAX),
224 * where MMAX is the maximum value of M in MVAL.
225 *
226 * BD (workspace) DOUBLE PRECISION array, dimension
227 * (max(min(MVAL(j),NVAL(j))))
228 *
229 * BE (workspace) DOUBLE PRECISION array, dimension
230 * (max(min(MVAL(j),NVAL(j))))
231 *
232 * S1 (workspace) DOUBLE PRECISION array, dimension
233 * (max(min(MVAL(j),NVAL(j))))
234 *
235 * S2 (workspace) DOUBLE PRECISION array, dimension
236 * (max(min(MVAL(j),NVAL(j))))
237 *
238 * X (workspace) DOUBLE PRECISION array, dimension (LDX,NRHS)
239 *
240 * LDX (input) INTEGER
241 * The leading dimension of the arrays X, Y, and Z.
242 * LDX >= max(1,MMAX)
243 *
244 * Y (workspace) DOUBLE PRECISION array, dimension (LDX,NRHS)
245 *
246 * Z (workspace) DOUBLE PRECISION array, dimension (LDX,NRHS)
247 *
248 * Q (workspace) DOUBLE PRECISION array, dimension (LDQ,MMAX)
249 *
250 * LDQ (input) INTEGER
251 * The leading dimension of the array Q. LDQ >= max(1,MMAX).
252 *
253 * PT (workspace) DOUBLE PRECISION array, dimension (LDPT,NMAX)
254 *
255 * LDPT (input) INTEGER
256 * The leading dimension of the arrays PT, U, and V.
257 * LDPT >= max(1, max(min(MVAL(j),NVAL(j)))).
258 *
259 * U (workspace) DOUBLE PRECISION array, dimension
260 * (LDPT,max(min(MVAL(j),NVAL(j))))
261 *
262 * V (workspace) DOUBLE PRECISION array, dimension
263 * (LDPT,max(min(MVAL(j),NVAL(j))))
264 *
265 * WORK (workspace) DOUBLE PRECISION array, dimension (LWORK)
266 *
267 * LWORK (input) INTEGER
268 * The number of entries in WORK. This must be at least
269 * 3(M+N) and M(M + max(M,N,k) + 1) + N*min(M,N) for all
270 * pairs (M,N)=(MM(j),NN(j))
271 *
272 * IWORK (workspace) INTEGER array, dimension at least 8*min(M,N)
273 *
274 * NOUT (input) INTEGER
275 * The FORTRAN unit number for printing out error messages
276 * (e.g., if a routine returns IINFO not equal to 0.)
277 *
278 * INFO (output) INTEGER
279 * If 0, then everything ran OK.
280 * -1: NSIZES < 0
281 * -2: Some MM(j) < 0
282 * -3: Some NN(j) < 0
283 * -4: NTYPES < 0
284 * -6: NRHS < 0
285 * -8: THRESH < 0
286 * -11: LDA < 1 or LDA < MMAX, where MMAX is max( MM(j) ).
287 * -17: LDB < 1 or LDB < MMAX.
288 * -21: LDQ < 1 or LDQ < MMAX.
289 * -23: LDPT< 1 or LDPT< MNMAX.
290 * -27: LWORK too small.
291 * If DLATMR, SLATMS, DGEBRD, DORGBR, or DBDSQR,
292 * returns an error code, the
293 * absolute value of it is returned.
294 *
295 *-----------------------------------------------------------------------
296 *
297 * Some Local Variables and Parameters:
298 * ---- ----- --------- --- ----------
299 *
300 * ZERO, ONE Real 0 and 1.
301 * MAXTYP The number of types defined.
302 * NTEST The number of tests performed, or which can
303 * be performed so far, for the current matrix.
304 * MMAX Largest value in NN.
305 * NMAX Largest value in NN.
306 * MNMIN min(MM(j), NN(j)) (the dimension of the bidiagonal
307 * matrix.)
308 * MNMAX The maximum value of MNMIN for j=1,...,NSIZES.
309 * NFAIL The number of tests which have exceeded THRESH
310 * COND, IMODE Values to be passed to the matrix generators.
311 * ANORM Norm of A; passed to matrix generators.
312 *
313 * OVFL, UNFL Overflow and underflow thresholds.
314 * RTOVFL, RTUNFL Square roots of the previous 2 values.
315 * ULP, ULPINV Finest relative precision and its inverse.
316 *
317 * The following four arrays decode JTYPE:
318 * KTYPE(j) The general type (1-10) for type "j".
319 * KMODE(j) The MODE value to be passed to the matrix
320 * generator for type "j".
321 * KMAGN(j) The order of magnitude ( O(1),
322 * O(overflow^(1/2) ), O(underflow^(1/2) )
323 *
324 * ======================================================================
325 *
326 * .. Parameters ..
327 DOUBLE PRECISION ZERO, ONE, TWO, HALF
328 PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0, TWO = 2.0D0,
329 $ HALF = 0.5D0 )
330 INTEGER MAXTYP
331 PARAMETER ( MAXTYP = 16 )
332 * ..
333 * .. Local Scalars ..
334 LOGICAL BADMM, BADNN, BIDIAG
335 CHARACTER UPLO
336 CHARACTER*3 PATH
337 INTEGER I, IINFO, IMODE, ITYPE, J, JCOL, JSIZE, JTYPE,
338 $ LOG2UI, M, MINWRK, MMAX, MNMAX, MNMIN, MQ,
339 $ MTYPES, N, NFAIL, NMAX, NTEST
340 DOUBLE PRECISION AMNINV, ANORM, COND, OVFL, RTOVFL, RTUNFL,
341 $ TEMP1, TEMP2, ULP, ULPINV, UNFL
342 * ..
343 * .. Local Arrays ..
344 INTEGER IDUM( 1 ), IOLDSD( 4 ), KMAGN( MAXTYP ),
345 $ KMODE( MAXTYP ), KTYPE( MAXTYP )
346 DOUBLE PRECISION DUM( 1 ), DUMMA( 1 ), RESULT( 19 )
347 * ..
348 * .. External Functions ..
349 DOUBLE PRECISION DLAMCH, DLARND
350 EXTERNAL DLAMCH, DLARND
351 * ..
352 * .. External Subroutines ..
353 EXTERNAL ALASUM, DBDSDC, DBDSQR, DBDT01, DBDT02, DBDT03,
354 $ DCOPY, DGEBRD, DGEMM, DLABAD, DLACPY, DLAHD2,
355 $ DLASET, DLATMR, DLATMS, DORGBR, DORT01, XERBLA
356 * ..
357 * .. Intrinsic Functions ..
358 INTRINSIC ABS, EXP, INT, LOG, MAX, MIN, SQRT
359 * ..
360 * .. Scalars in Common ..
361 LOGICAL LERR, OK
362 CHARACTER*32 SRNAMT
363 INTEGER INFOT, NUNIT
364 * ..
365 * .. Common blocks ..
366 COMMON / INFOC / INFOT, NUNIT, OK, LERR
367 COMMON / SRNAMC / SRNAMT
368 * ..
369 * .. Data statements ..
370 DATA KTYPE / 1, 2, 5*4, 5*6, 3*9, 10 /
371 DATA KMAGN / 2*1, 3*1, 2, 3, 3*1, 2, 3, 1, 2, 3, 0 /
372 DATA KMODE / 2*0, 4, 3, 1, 4, 4, 4, 3, 1, 4, 4, 0,
373 $ 0, 0, 0 /
374 * ..
375 * .. Executable Statements ..
376 *
377 * Check for errors
378 *
379 INFO = 0
380 *
381 BADMM = .FALSE.
382 BADNN = .FALSE.
383 MMAX = 1
384 NMAX = 1
385 MNMAX = 1
386 MINWRK = 1
387 DO 10 J = 1, NSIZES
388 MMAX = MAX( MMAX, MVAL( J ) )
389 IF( MVAL( J ).LT.0 )
390 $ BADMM = .TRUE.
391 NMAX = MAX( NMAX, NVAL( J ) )
392 IF( NVAL( J ).LT.0 )
393 $ BADNN = .TRUE.
394 MNMAX = MAX( MNMAX, MIN( MVAL( J ), NVAL( J ) ) )
395 MINWRK = MAX( MINWRK, 3*( MVAL( J )+NVAL( J ) ),
396 $ MVAL( J )*( MVAL( J )+MAX( MVAL( J ), NVAL( J ),
397 $ NRHS )+1 )+NVAL( J )*MIN( NVAL( J ), MVAL( J ) ) )
398 10 CONTINUE
399 *
400 * Check for errors
401 *
402 IF( NSIZES.LT.0 ) THEN
403 INFO = -1
404 ELSE IF( BADMM ) THEN
405 INFO = -2
406 ELSE IF( BADNN ) THEN
407 INFO = -3
408 ELSE IF( NTYPES.LT.0 ) THEN
409 INFO = -4
410 ELSE IF( NRHS.LT.0 ) THEN
411 INFO = -6
412 ELSE IF( LDA.LT.MMAX ) THEN
413 INFO = -11
414 ELSE IF( LDX.LT.MMAX ) THEN
415 INFO = -17
416 ELSE IF( LDQ.LT.MMAX ) THEN
417 INFO = -21
418 ELSE IF( LDPT.LT.MNMAX ) THEN
419 INFO = -23
420 ELSE IF( MINWRK.GT.LWORK ) THEN
421 INFO = -27
422 END IF
423 *
424 IF( INFO.NE.0 ) THEN
425 CALL XERBLA( 'DCHKBD', -INFO )
426 RETURN
427 END IF
428 *
429 * Initialize constants
430 *
431 PATH( 1: 1 ) = 'Double precision'
432 PATH( 2: 3 ) = 'BD'
433 NFAIL = 0
434 NTEST = 0
435 UNFL = DLAMCH( 'Safe minimum' )
436 OVFL = DLAMCH( 'Overflow' )
437 CALL DLABAD( UNFL, OVFL )
438 ULP = DLAMCH( 'Precision' )
439 ULPINV = ONE / ULP
440 LOG2UI = INT( LOG( ULPINV ) / LOG( TWO ) )
441 RTUNFL = SQRT( UNFL )
442 RTOVFL = SQRT( OVFL )
443 INFOT = 0
444 *
445 * Loop over sizes, types
446 *
447 DO 200 JSIZE = 1, NSIZES
448 M = MVAL( JSIZE )
449 N = NVAL( JSIZE )
450 MNMIN = MIN( M, N )
451 AMNINV = ONE / MAX( M, N, 1 )
452 *
453 IF( NSIZES.NE.1 ) THEN
454 MTYPES = MIN( MAXTYP, NTYPES )
455 ELSE
456 MTYPES = MIN( MAXTYP+1, NTYPES )
457 END IF
458 *
459 DO 190 JTYPE = 1, MTYPES
460 IF( .NOT.DOTYPE( JTYPE ) )
461 $ GO TO 190
462 *
463 DO 20 J = 1, 4
464 IOLDSD( J ) = ISEED( J )
465 20 CONTINUE
466 *
467 DO 30 J = 1, 14
468 RESULT( J ) = -ONE
469 30 CONTINUE
470 *
471 UPLO = ' '
472 *
473 * Compute "A"
474 *
475 * Control parameters:
476 *
477 * KMAGN KMODE KTYPE
478 * =1 O(1) clustered 1 zero
479 * =2 large clustered 2 identity
480 * =3 small exponential (none)
481 * =4 arithmetic diagonal, (w/ eigenvalues)
482 * =5 random symmetric, w/ eigenvalues
483 * =6 nonsymmetric, w/ singular values
484 * =7 random diagonal
485 * =8 random symmetric
486 * =9 random nonsymmetric
487 * =10 random bidiagonal (log. distrib.)
488 *
489 IF( MTYPES.GT.MAXTYP )
490 $ GO TO 100
491 *
492 ITYPE = KTYPE( JTYPE )
493 IMODE = KMODE( JTYPE )
494 *
495 * Compute norm
496 *
497 GO TO ( 40, 50, 60 )KMAGN( JTYPE )
498 *
499 40 CONTINUE
500 ANORM = ONE
501 GO TO 70
502 *
503 50 CONTINUE
504 ANORM = ( RTOVFL*ULP )*AMNINV
505 GO TO 70
506 *
507 60 CONTINUE
508 ANORM = RTUNFL*MAX( M, N )*ULPINV
509 GO TO 70
510 *
511 70 CONTINUE
512 *
513 CALL DLASET( 'Full', LDA, N, ZERO, ZERO, A, LDA )
514 IINFO = 0
515 COND = ULPINV
516 *
517 BIDIAG = .FALSE.
518 IF( ITYPE.EQ.1 ) THEN
519 *
520 * Zero matrix
521 *
522 IINFO = 0
523 *
524 ELSE IF( ITYPE.EQ.2 ) THEN
525 *
526 * Identity
527 *
528 DO 80 JCOL = 1, MNMIN
529 A( JCOL, JCOL ) = ANORM
530 80 CONTINUE
531 *
532 ELSE IF( ITYPE.EQ.4 ) THEN
533 *
534 * Diagonal Matrix, [Eigen]values Specified
535 *
536 CALL DLATMS( MNMIN, MNMIN, 'S', ISEED, 'N', WORK, IMODE,
537 $ COND, ANORM, 0, 0, 'N', A, LDA,
538 $ WORK( MNMIN+1 ), IINFO )
539 *
540 ELSE IF( ITYPE.EQ.5 ) THEN
541 *
542 * Symmetric, eigenvalues specified
543 *
544 CALL DLATMS( MNMIN, MNMIN, 'S', ISEED, 'S', WORK, IMODE,
545 $ COND, ANORM, M, N, 'N', A, LDA,
546 $ WORK( MNMIN+1 ), IINFO )
547 *
548 ELSE IF( ITYPE.EQ.6 ) THEN
549 *
550 * Nonsymmetric, singular values specified
551 *
552 CALL DLATMS( M, N, 'S', ISEED, 'N', WORK, IMODE, COND,
553 $ ANORM, M, N, 'N', A, LDA, WORK( MNMIN+1 ),
554 $ IINFO )
555 *
556 ELSE IF( ITYPE.EQ.7 ) THEN
557 *
558 * Diagonal, random entries
559 *
560 CALL DLATMR( MNMIN, MNMIN, 'S', ISEED, 'N', WORK, 6, ONE,
561 $ ONE, 'T', 'N', WORK( MNMIN+1 ), 1, ONE,
562 $ WORK( 2*MNMIN+1 ), 1, ONE, 'N', IWORK, 0, 0,
563 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
564 *
565 ELSE IF( ITYPE.EQ.8 ) THEN
566 *
567 * Symmetric, random entries
568 *
569 CALL DLATMR( MNMIN, MNMIN, 'S', ISEED, 'S', WORK, 6, ONE,
570 $ ONE, 'T', 'N', WORK( MNMIN+1 ), 1, ONE,
571 $ WORK( M+MNMIN+1 ), 1, ONE, 'N', IWORK, M, N,
572 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
573 *
574 ELSE IF( ITYPE.EQ.9 ) THEN
575 *
576 * Nonsymmetric, random entries
577 *
578 CALL DLATMR( M, N, 'S', ISEED, 'N', WORK, 6, ONE, ONE,
579 $ 'T', 'N', WORK( MNMIN+1 ), 1, ONE,
580 $ WORK( M+MNMIN+1 ), 1, ONE, 'N', IWORK, M, N,
581 $ ZERO, ANORM, 'NO', A, LDA, IWORK, IINFO )
582 *
583 ELSE IF( ITYPE.EQ.10 ) THEN
584 *
585 * Bidiagonal, random entries
586 *
587 TEMP1 = -TWO*LOG( ULP )
588 DO 90 J = 1, MNMIN
589 BD( J ) = EXP( TEMP1*DLARND( 2, ISEED ) )
590 IF( J.LT.MNMIN )
591 $ BE( J ) = EXP( TEMP1*DLARND( 2, ISEED ) )
592 90 CONTINUE
593 *
594 IINFO = 0
595 BIDIAG = .TRUE.
596 IF( M.GE.N ) THEN
597 UPLO = 'U'
598 ELSE
599 UPLO = 'L'
600 END IF
601 ELSE
602 IINFO = 1
603 END IF
604 *
605 IF( IINFO.EQ.0 ) THEN
606 *
607 * Generate Right-Hand Side
608 *
609 IF( BIDIAG ) THEN
610 CALL DLATMR( MNMIN, NRHS, 'S', ISEED, 'N', WORK, 6,
611 $ ONE, ONE, 'T', 'N', WORK( MNMIN+1 ), 1,
612 $ ONE, WORK( 2*MNMIN+1 ), 1, ONE, 'N',
613 $ IWORK, MNMIN, NRHS, ZERO, ONE, 'NO', Y,
614 $ LDX, IWORK, IINFO )
615 ELSE
616 CALL DLATMR( M, NRHS, 'S', ISEED, 'N', WORK, 6, ONE,
617 $ ONE, 'T', 'N', WORK( M+1 ), 1, ONE,
618 $ WORK( 2*M+1 ), 1, ONE, 'N', IWORK, M,
619 $ NRHS, ZERO, ONE, 'NO', X, LDX, IWORK,
620 $ IINFO )
621 END IF
622 END IF
623 *
624 * Error Exit
625 *
626 IF( IINFO.NE.0 ) THEN
627 WRITE( NOUT, FMT = 9998 )'Generator', IINFO, M, N,
628 $ JTYPE, IOLDSD
629 INFO = ABS( IINFO )
630 RETURN
631 END IF
632 *
633 100 CONTINUE
634 *
635 * Call DGEBRD and DORGBR to compute B, Q, and P, do tests.
636 *
637 IF( .NOT.BIDIAG ) THEN
638 *
639 * Compute transformations to reduce A to bidiagonal form:
640 * B := Q' * A * P.
641 *
642 CALL DLACPY( ' ', M, N, A, LDA, Q, LDQ )
643 CALL DGEBRD( M, N, Q, LDQ, BD, BE, WORK, WORK( MNMIN+1 ),
644 $ WORK( 2*MNMIN+1 ), LWORK-2*MNMIN, IINFO )
645 *
646 * Check error code from DGEBRD.
647 *
648 IF( IINFO.NE.0 ) THEN
649 WRITE( NOUT, FMT = 9998 )'DGEBRD', IINFO, M, N,
650 $ JTYPE, IOLDSD
651 INFO = ABS( IINFO )
652 RETURN
653 END IF
654 *
655 CALL DLACPY( ' ', M, N, Q, LDQ, PT, LDPT )
656 IF( M.GE.N ) THEN
657 UPLO = 'U'
658 ELSE
659 UPLO = 'L'
660 END IF
661 *
662 * Generate Q
663 *
664 MQ = M
665 IF( NRHS.LE.0 )
666 $ MQ = MNMIN
667 CALL DORGBR( 'Q', M, MQ, N, Q, LDQ, WORK,
668 $ WORK( 2*MNMIN+1 ), LWORK-2*MNMIN, IINFO )
669 *
670 * Check error code from DORGBR.
671 *
672 IF( IINFO.NE.0 ) THEN
673 WRITE( NOUT, FMT = 9998 )'DORGBR(Q)', IINFO, M, N,
674 $ JTYPE, IOLDSD
675 INFO = ABS( IINFO )
676 RETURN
677 END IF
678 *
679 * Generate P'
680 *
681 CALL DORGBR( 'P', MNMIN, N, M, PT, LDPT, WORK( MNMIN+1 ),
682 $ WORK( 2*MNMIN+1 ), LWORK-2*MNMIN, IINFO )
683 *
684 * Check error code from DORGBR.
685 *
686 IF( IINFO.NE.0 ) THEN
687 WRITE( NOUT, FMT = 9998 )'DORGBR(P)', IINFO, M, N,
688 $ JTYPE, IOLDSD
689 INFO = ABS( IINFO )
690 RETURN
691 END IF
692 *
693 * Apply Q' to an M by NRHS matrix X: Y := Q' * X.
694 *
695 CALL DGEMM( 'Transpose', 'No transpose', M, NRHS, M, ONE,
696 $ Q, LDQ, X, LDX, ZERO, Y, LDX )
697 *
698 * Test 1: Check the decomposition A := Q * B * PT
699 * 2: Check the orthogonality of Q
700 * 3: Check the orthogonality of PT
701 *
702 CALL DBDT01( M, N, 1, A, LDA, Q, LDQ, BD, BE, PT, LDPT,
703 $ WORK, RESULT( 1 ) )
704 CALL DORT01( 'Columns', M, MQ, Q, LDQ, WORK, LWORK,
705 $ RESULT( 2 ) )
706 CALL DORT01( 'Rows', MNMIN, N, PT, LDPT, WORK, LWORK,
707 $ RESULT( 3 ) )
708 END IF
709 *
710 * Use DBDSQR to form the SVD of the bidiagonal matrix B:
711 * B := U * S1 * VT, and compute Z = U' * Y.
712 *
713 CALL DCOPY( MNMIN, BD, 1, S1, 1 )
714 IF( MNMIN.GT.0 )
715 $ CALL DCOPY( MNMIN-1, BE, 1, WORK, 1 )
716 CALL DLACPY( ' ', M, NRHS, Y, LDX, Z, LDX )
717 CALL DLASET( 'Full', MNMIN, MNMIN, ZERO, ONE, U, LDPT )
718 CALL DLASET( 'Full', MNMIN, MNMIN, ZERO, ONE, VT, LDPT )
719 *
720 CALL DBDSQR( UPLO, MNMIN, MNMIN, MNMIN, NRHS, S1, WORK, VT,
721 $ LDPT, U, LDPT, Z, LDX, WORK( MNMIN+1 ), IINFO )
722 *
723 * Check error code from DBDSQR.
724 *
725 IF( IINFO.NE.0 ) THEN
726 WRITE( NOUT, FMT = 9998 )'DBDSQR(vects)', IINFO, M, N,
727 $ JTYPE, IOLDSD
728 INFO = ABS( IINFO )
729 IF( IINFO.LT.0 ) THEN
730 RETURN
731 ELSE
732 RESULT( 4 ) = ULPINV
733 GO TO 170
734 END IF
735 END IF
736 *
737 * Use DBDSQR to compute only the singular values of the
738 * bidiagonal matrix B; U, VT, and Z should not be modified.
739 *
740 CALL DCOPY( MNMIN, BD, 1, S2, 1 )
741 IF( MNMIN.GT.0 )
742 $ CALL DCOPY( MNMIN-1, BE, 1, WORK, 1 )
743 *
744 CALL DBDSQR( UPLO, MNMIN, 0, 0, 0, S2, WORK, VT, LDPT, U,
745 $ LDPT, Z, LDX, WORK( MNMIN+1 ), IINFO )
746 *
747 * Check error code from DBDSQR.
748 *
749 IF( IINFO.NE.0 ) THEN
750 WRITE( NOUT, FMT = 9998 )'DBDSQR(values)', IINFO, M, N,
751 $ JTYPE, IOLDSD
752 INFO = ABS( IINFO )
753 IF( IINFO.LT.0 ) THEN
754 RETURN
755 ELSE
756 RESULT( 9 ) = ULPINV
757 GO TO 170
758 END IF
759 END IF
760 *
761 * Test 4: Check the decomposition B := U * S1 * VT
762 * 5: Check the computation Z := U' * Y
763 * 6: Check the orthogonality of U
764 * 7: Check the orthogonality of VT
765 *
766 CALL DBDT03( UPLO, MNMIN, 1, BD, BE, U, LDPT, S1, VT, LDPT,
767 $ WORK, RESULT( 4 ) )
768 CALL DBDT02( MNMIN, NRHS, Y, LDX, Z, LDX, U, LDPT, WORK,
769 $ RESULT( 5 ) )
770 CALL DORT01( 'Columns', MNMIN, MNMIN, U, LDPT, WORK, LWORK,
771 $ RESULT( 6 ) )
772 CALL DORT01( 'Rows', MNMIN, MNMIN, VT, LDPT, WORK, LWORK,
773 $ RESULT( 7 ) )
774 *
775 * Test 8: Check that the singular values are sorted in
776 * non-increasing order and are non-negative
777 *
778 RESULT( 8 ) = ZERO
779 DO 110 I = 1, MNMIN - 1
780 IF( S1( I ).LT.S1( I+1 ) )
781 $ RESULT( 8 ) = ULPINV
782 IF( S1( I ).LT.ZERO )
783 $ RESULT( 8 ) = ULPINV
784 110 CONTINUE
785 IF( MNMIN.GE.1 ) THEN
786 IF( S1( MNMIN ).LT.ZERO )
787 $ RESULT( 8 ) = ULPINV
788 END IF
789 *
790 * Test 9: Compare DBDSQR with and without singular vectors
791 *
792 TEMP2 = ZERO
793 *
794 DO 120 J = 1, MNMIN
795 TEMP1 = ABS( S1( J )-S2( J ) ) /
796 $ MAX( SQRT( UNFL )*MAX( S1( 1 ), ONE ),
797 $ ULP*MAX( ABS( S1( J ) ), ABS( S2( J ) ) ) )
798 TEMP2 = MAX( TEMP1, TEMP2 )
799 120 CONTINUE
800 *
801 RESULT( 9 ) = TEMP2
802 *
803 * Test 10: Sturm sequence test of singular values
804 * Go up by factors of two until it succeeds
805 *
806 TEMP1 = THRESH*( HALF-ULP )
807 *
808 DO 130 J = 0, LOG2UI
809 * CALL DSVDCH( MNMIN, BD, BE, S1, TEMP1, IINFO )
810 IF( IINFO.EQ.0 )
811 $ GO TO 140
812 TEMP1 = TEMP1*TWO
813 130 CONTINUE
814 *
815 140 CONTINUE
816 RESULT( 10 ) = TEMP1
817 *
818 * Use DBDSQR to form the decomposition A := (QU) S (VT PT)
819 * from the bidiagonal form A := Q B PT.
820 *
821 IF( .NOT.BIDIAG ) THEN
822 CALL DCOPY( MNMIN, BD, 1, S2, 1 )
823 IF( MNMIN.GT.0 )
824 $ CALL DCOPY( MNMIN-1, BE, 1, WORK, 1 )
825 *
826 CALL DBDSQR( UPLO, MNMIN, N, M, NRHS, S2, WORK, PT, LDPT,
827 $ Q, LDQ, Y, LDX, WORK( MNMIN+1 ), IINFO )
828 *
829 * Test 11: Check the decomposition A := Q*U * S2 * VT*PT
830 * 12: Check the computation Z := U' * Q' * X
831 * 13: Check the orthogonality of Q*U
832 * 14: Check the orthogonality of VT*PT
833 *
834 CALL DBDT01( M, N, 0, A, LDA, Q, LDQ, S2, DUMMA, PT,
835 $ LDPT, WORK, RESULT( 11 ) )
836 CALL DBDT02( M, NRHS, X, LDX, Y, LDX, Q, LDQ, WORK,
837 $ RESULT( 12 ) )
838 CALL DORT01( 'Columns', M, MQ, Q, LDQ, WORK, LWORK,
839 $ RESULT( 13 ) )
840 CALL DORT01( 'Rows', MNMIN, N, PT, LDPT, WORK, LWORK,
841 $ RESULT( 14 ) )
842 END IF
843 *
844 * Use DBDSDC to form the SVD of the bidiagonal matrix B:
845 * B := U * S1 * VT
846 *
847 CALL DCOPY( MNMIN, BD, 1, S1, 1 )
848 IF( MNMIN.GT.0 )
849 $ CALL DCOPY( MNMIN-1, BE, 1, WORK, 1 )
850 CALL DLASET( 'Full', MNMIN, MNMIN, ZERO, ONE, U, LDPT )
851 CALL DLASET( 'Full', MNMIN, MNMIN, ZERO, ONE, VT, LDPT )
852 *
853 CALL DBDSDC( UPLO, 'I', MNMIN, S1, WORK, U, LDPT, VT, LDPT,
854 $ DUM, IDUM, WORK( MNMIN+1 ), IWORK, IINFO )
855 *
856 * Check error code from DBDSDC.
857 *
858 IF( IINFO.NE.0 ) THEN
859 WRITE( NOUT, FMT = 9998 )'DBDSDC(vects)', IINFO, M, N,
860 $ JTYPE, IOLDSD
861 INFO = ABS( IINFO )
862 IF( IINFO.LT.0 ) THEN
863 RETURN
864 ELSE
865 RESULT( 15 ) = ULPINV
866 GO TO 170
867 END IF
868 END IF
869 *
870 * Use DBDSDC to compute only the singular values of the
871 * bidiagonal matrix B; U and VT should not be modified.
872 *
873 CALL DCOPY( MNMIN, BD, 1, S2, 1 )
874 IF( MNMIN.GT.0 )
875 $ CALL DCOPY( MNMIN-1, BE, 1, WORK, 1 )
876 *
877 CALL DBDSDC( UPLO, 'N', MNMIN, S2, WORK, DUM, 1, DUM, 1,
878 $ DUM, IDUM, WORK( MNMIN+1 ), IWORK, IINFO )
879 *
880 * Check error code from DBDSDC.
881 *
882 IF( IINFO.NE.0 ) THEN
883 WRITE( NOUT, FMT = 9998 )'DBDSDC(values)', IINFO, M, N,
884 $ JTYPE, IOLDSD
885 INFO = ABS( IINFO )
886 IF( IINFO.LT.0 ) THEN
887 RETURN
888 ELSE
889 RESULT( 18 ) = ULPINV
890 GO TO 170
891 END IF
892 END IF
893 *
894 * Test 15: Check the decomposition B := U * S1 * VT
895 * 16: Check the orthogonality of U
896 * 17: Check the orthogonality of VT
897 *
898 CALL DBDT03( UPLO, MNMIN, 1, BD, BE, U, LDPT, S1, VT, LDPT,
899 $ WORK, RESULT( 15 ) )
900 CALL DORT01( 'Columns', MNMIN, MNMIN, U, LDPT, WORK, LWORK,
901 $ RESULT( 16 ) )
902 CALL DORT01( 'Rows', MNMIN, MNMIN, VT, LDPT, WORK, LWORK,
903 $ RESULT( 17 ) )
904 *
905 * Test 18: Check that the singular values are sorted in
906 * non-increasing order and are non-negative
907 *
908 RESULT( 18 ) = ZERO
909 DO 150 I = 1, MNMIN - 1
910 IF( S1( I ).LT.S1( I+1 ) )
911 $ RESULT( 18 ) = ULPINV
912 IF( S1( I ).LT.ZERO )
913 $ RESULT( 18 ) = ULPINV
914 150 CONTINUE
915 IF( MNMIN.GE.1 ) THEN
916 IF( S1( MNMIN ).LT.ZERO )
917 $ RESULT( 18 ) = ULPINV
918 END IF
919 *
920 * Test 19: Compare DBDSQR with and without singular vectors
921 *
922 TEMP2 = ZERO
923 *
924 DO 160 J = 1, MNMIN
925 TEMP1 = ABS( S1( J )-S2( J ) ) /
926 $ MAX( SQRT( UNFL )*MAX( S1( 1 ), ONE ),
927 $ ULP*MAX( ABS( S1( 1 ) ), ABS( S2( 1 ) ) ) )
928 TEMP2 = MAX( TEMP1, TEMP2 )
929 160 CONTINUE
930 *
931 RESULT( 19 ) = TEMP2
932 *
933 * End of Loop -- Check for RESULT(j) > THRESH
934 *
935 170 CONTINUE
936 DO 180 J = 1, 19
937 IF( RESULT( J ).GE.THRESH ) THEN
938 IF( NFAIL.EQ.0 )
939 $ CALL DLAHD2( NOUT, PATH )
940 WRITE( NOUT, FMT = 9999 )M, N, JTYPE, IOLDSD, J,
941 $ RESULT( J )
942 NFAIL = NFAIL + 1
943 END IF
944 180 CONTINUE
945 IF( .NOT.BIDIAG ) THEN
946 NTEST = NTEST + 19
947 ELSE
948 NTEST = NTEST + 5
949 END IF
950 *
951 190 CONTINUE
952 200 CONTINUE
953 *
954 * Summary
955 *
956 CALL ALASUM( PATH, NOUT, NFAIL, NTEST, 0 )
957 *
958 RETURN
959 *
960 * End of DCHKBD
961 *
962 9999 FORMAT( ' M=', I5, ', N=', I5, ', type ', I2, ', seed=',
963 $ 4( I4, ',' ), ' test(', I2, ')=', G11.4 )
964 9998 FORMAT( ' DCHKBD: ', A, ' returned INFO=', I6, '.', / 9X, 'M=',
965 $ I6, ', N=', I6, ', JTYPE=', I6, ', ISEED=(', 3( I5, ',' ),
966 $ I5, ')' )
967 *
968 END