163
164
165
166
167
168
169 LOGICAL TSTERR
170 INTEGER NMAX, NN, NNB, NNS, NOUT
171 DOUBLE PRECISION THRESH
172
173
174 LOGICAL DOTYPE( * )
175 INTEGER NBVAL( * ), NSVAL( * ), NVAL( * )
176 DOUBLE PRECISION RWORK( * )
177 COMPLEX*16 A( * ), AINV( * ), B( * ), WORK( * ), X( * ),
178 $ XACT( * )
179
180
181
182
183
184 INTEGER NTYPE1, NTYPES
185 parameter( ntype1 = 10, ntypes = 18 )
186 INTEGER NTESTS
187 parameter( ntests = 10 )
188 INTEGER NTRAN
189 parameter( ntran = 3 )
190 DOUBLE PRECISION ONE, ZERO
191 parameter( one = 1.0d0, zero = 0.0d0 )
192
193
194 CHARACTER DIAG, NORM, TRANS, UPLO, XTYPE
195 CHARACTER*3 PATH
196 INTEGER I, IDIAG, IMAT, IN, INB, INFO, IRHS, ITRAN,
197 $ IUPLO, K, LDA, N, NB, NERRS, NFAIL, NRHS, NRUN
198 DOUBLE PRECISION AINVNM, ANORM, BIGNUM, DUMMY, RCOND, RCONDC,
199 $ RCONDI, RCONDO, RES, SCALE, DLAMCH
200
201
202 CHARACTER TRANSS( NTRAN ), UPLOS( 2 )
203 INTEGER ISEED( 4 ), ISEEDY( 4 )
204 DOUBLE PRECISION RESULT( NTESTS ), RWORK2( 2*NMAX ),
205 $ SCALE3( 2 )
206
207
208 LOGICAL LSAME
209 DOUBLE PRECISION ZLANTR
211
212
217
218
219 LOGICAL LERR, OK
220 CHARACTER*32 SRNAMT
221 INTEGER INFOT, IOUNIT
222
223
224 COMMON / infoc / infot, iounit, ok, lerr
225 COMMON / srnamc / srnamt
226
227
228 INTRINSIC max
229
230
231 DATA iseedy / 1988, 1989, 1990, 1991 /
232 DATA uplos / 'U', 'L' / , transs / 'N', 'T', 'C' /
233
234
235
236
237
238 path( 1: 1 ) = 'Zomplex precision'
239 path( 2: 3 ) = 'TR'
241 nrun = 0
242 nfail = 0
243 nerrs = 0
244 DO 10 i = 1, 4
245 iseed( i ) = iseedy( i )
246 10 CONTINUE
247
248
249
250 IF( tsterr )
251 $
CALL zerrtr( path, nout )
252 infot = 0
253
254 DO 120 in = 1, nn
255
256
257
258 n = nval( in )
259 lda = max( 1, n )
260 xtype = 'N'
261
262 DO 80 imat = 1, ntype1
263
264
265
266 IF( .NOT.dotype( imat ) )
267 $ GO TO 80
268
269 DO 70 iuplo = 1, 2
270
271
272
273 uplo = uplos( iuplo )
274
275
276
277 srnamt = 'ZLATTR'
278 CALL zlattr( imat, uplo,
'No transpose', diag, iseed, n,
279 $ a, lda, x, work, rwork, info )
280
281
282
283 IF(
lsame( diag,
'N' ) )
THEN
284 idiag = 1
285 ELSE
286 idiag = 2
287 END IF
288
289 DO 60 inb = 1, nnb
290
291
292
293 nb = nbval( inb )
295
296
297
298
299 CALL zlacpy( uplo, n, n, a, lda, ainv, lda )
300 srnamt = 'ZTRTRI'
301 CALL ztrtri( uplo, diag, n, ainv, lda, info )
302
303
304
305 IF( info.NE.0 )
306 $
CALL alaerh( path,
'ZTRTRI', info, 0, uplo // diag,
307 $ n, n, -1, -1, nb, imat, nfail, nerrs,
308 $ nout )
309
310
311
312 anorm =
zlantr(
'I', uplo, diag, n, n, a, lda, rwork )
313 ainvnm =
zlantr(
'I', uplo, diag, n, n, ainv, lda,
314 $ rwork )
315 IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
316 rcondi = one
317 ELSE
318 rcondi = ( one / anorm ) / ainvnm
319 END IF
320
321
322
323
324
325 CALL ztrt01( uplo, diag, n, a, lda, ainv, lda, rcondo,
326 $ rwork, result( 1 ) )
327
328
329 IF( result( 1 ).GE.thresh ) THEN
330 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
331 $
CALL alahd( nout, path )
332 WRITE( nout, fmt = 9999 )uplo, diag, n, nb, imat,
333 $ 1, result( 1 )
334 nfail = nfail + 1
335 END IF
336 nrun = nrun + 1
337
338
339
340 IF( inb.NE.1 )
341 $ GO TO 60
342
343 DO 40 irhs = 1, nns
344 nrhs = nsval( irhs )
345 xtype = 'N'
346
347 DO 30 itran = 1, ntran
348
349
350
351 trans = transs( itran )
352 IF( itran.EQ.1 ) THEN
353 norm = 'O'
354 rcondc = rcondo
355 ELSE
356 norm = 'I'
357 rcondc = rcondi
358 END IF
359
360
361
362
363 srnamt = 'ZLARHS'
364 CALL zlarhs( path, xtype, uplo, trans, n, n, 0,
365 $ idiag, nrhs, a, lda, xact, lda, b,
366 $ lda, iseed, info )
367 xtype = 'C'
368 CALL zlacpy(
'Full', n, nrhs, b, lda, x, lda )
369
370 srnamt = 'ZTRTRS'
371 CALL ztrtrs( uplo, trans, diag, n, nrhs, a, lda,
372 $ x, lda, info )
373
374
375
376 IF( info.NE.0 )
377 $
CALL alaerh( path,
'ZTRTRS', info, 0,
378 $ uplo // trans // diag, n, n, -1,
379 $ -1, nrhs, imat, nfail, nerrs,
380 $ nout )
381
382
383
384 IF( n.GT.0 )
385 $ dummy = dble( a( 1 ) )
386
387 CALL ztrt02( uplo, trans, diag, n, nrhs, a, lda,
388 $ x, lda, b, lda, work, rwork,
389 $ result( 2 ) )
390
391
392
393
394 CALL zget04( n, nrhs, x, lda, xact, lda, rcondc,
395 $ result( 3 ) )
396
397
398
399
400
401 srnamt = 'ZTRRFS'
402 CALL ztrrfs( uplo, trans, diag, n, nrhs, a, lda,
403 $ b, lda, x, lda, rwork,
404 $ rwork( nrhs+1 ), work,
405 $ rwork( 2*nrhs+1 ), info )
406
407
408
409 IF( info.NE.0 )
410 $
CALL alaerh( path,
'ZTRRFS', info, 0,
411 $ uplo // trans // diag, n, n, -1,
412 $ -1, nrhs, imat, nfail, nerrs,
413 $ nout )
414
415 CALL zget04( n, nrhs, x, lda, xact, lda, rcondc,
416 $ result( 4 ) )
417 CALL ztrt05( uplo, trans, diag, n, nrhs, a, lda,
418 $ b, lda, x, lda, xact, lda, rwork,
419 $ rwork( nrhs+1 ), result( 5 ) )
420
421
422
423
424 DO 20 k = 2, 6
425 IF( result( k ).GE.thresh ) THEN
426 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
427 $
CALL alahd( nout, path )
428 WRITE( nout, fmt = 9998 )uplo, trans,
429 $ diag, n, nrhs, imat, k, result( k )
430 nfail = nfail + 1
431 END IF
432 20 CONTINUE
433 nrun = nrun + 5
434 30 CONTINUE
435 40 CONTINUE
436
437
438
439
440 DO 50 itran = 1, 2
441 IF( itran.EQ.1 ) THEN
442 norm = 'O'
443 rcondc = rcondo
444 ELSE
445 norm = 'I'
446 rcondc = rcondi
447 END IF
448 srnamt = 'ZTRCON'
449 CALL ztrcon( norm, uplo, diag, n, a, lda, rcond,
450 $ work, rwork, info )
451
452
453
454 IF( info.NE.0 )
455 $
CALL alaerh( path,
'ZTRCON', info, 0,
456 $ norm // uplo // diag, n, n, -1, -1,
457 $ -1, imat, nfail, nerrs, nout )
458
459 CALL ztrt06( rcond, rcondc, uplo, diag, n, a, lda,
460 $ rwork, result( 7 ) )
461
462
463
464 IF( result( 7 ).GE.thresh ) THEN
465 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
466 $
CALL alahd( nout, path )
467 WRITE( nout, fmt = 9997 )norm, uplo, n, imat,
468 $ 7, result( 7 )
469 nfail = nfail + 1
470 END IF
471 nrun = nrun + 1
472 50 CONTINUE
473 60 CONTINUE
474 70 CONTINUE
475 80 CONTINUE
476
477
478
479 DO 110 imat = ntype1 + 1, ntypes
480
481
482
483 IF( .NOT.dotype( imat ) )
484 $ GO TO 110
485
486 DO 100 iuplo = 1, 2
487
488
489
490 uplo = uplos( iuplo )
491 DO 90 itran = 1, ntran
492
493
494
495 trans = transs( itran )
496
497
498
499 srnamt = 'ZLATTR'
500 CALL zlattr( imat, uplo, trans, diag, iseed, n, a,
501 $ lda, x, work, rwork, info )
502
503
504
505
506 srnamt = 'ZLATRS'
507 CALL zcopy( n, x, 1, b, 1 )
508 CALL zlatrs( uplo, trans, diag,
'N', n, a, lda, b,
509 $ scale, rwork, info )
510
511
512
513 IF( info.NE.0 )
514 $
CALL alaerh( path,
'ZLATRS', info, 0,
515 $ uplo // trans // diag // 'N', n, n,
516 $ -1, -1, -1, imat, nfail, nerrs, nout )
517
518 CALL ztrt03( uplo, trans, diag, n, 1, a, lda, scale,
519 $ rwork, one, b, lda, x, lda, work,
520 $ result( 8 ) )
521
522
523
524
525 CALL zcopy( n, x, 1, b( n+1 ), 1 )
526 CALL zlatrs( uplo, trans, diag,
'Y', n, a, lda,
527 $ b( n+1 ), scale, rwork, info )
528
529
530
531 IF( info.NE.0 )
532 $
CALL alaerh( path,
'ZLATRS', info, 0,
533 $ uplo // trans // diag // 'Y', n, n,
534 $ -1, -1, -1, imat, nfail, nerrs, nout )
535
536 CALL ztrt03( uplo, trans, diag, n, 1, a, lda, scale,
537 $ rwork, one, b( n+1 ), lda, x, lda, work,
538 $ result( 9 ) )
539
540
541
542
543 srnamt = 'ZLATRS3'
544 CALL zcopy( n, x, 1, b, 1 )
545 CALL zcopy( n, x, 1, b( n+1 ), 1 )
546 CALL zdscal( n, bignum, b( n+1 ), 1 )
547 CALL zlatrs3( uplo, trans, diag,
'N', n, 2, a, lda,
548 $ b, max(1, n), scale3, rwork, rwork2,
549 $ 2*nmax, info )
550
551
552
553 IF( info.NE.0 )
554 $
CALL alaerh( path,
'ZLATRS3', info, 0,
555 $ uplo // trans // diag // 'N', n, n,
556 $ -1, -1, -1, imat, nfail, nerrs, nout )
557 CALL ztrt03( uplo, trans, diag, n, 1, a, lda,
558 $ scale3( 1 ), rwork, one, b( 1 ), lda,
559 $ x, lda, work, result( 10 ) )
560 CALL zdscal( n, bignum, x, 1 )
561 CALL ztrt03( uplo, trans, diag, n, 1, a, lda,
562 $ scale3( 2 ), rwork, one, b( n+1 ), lda,
563 $ x, lda, work, res )
564 result( 10 ) = max( result( 10 ), res )
565
566
567
568
569 IF( result( 8 ).GE.thresh ) THEN
570 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
571 $
CALL alahd( nout, path )
572 WRITE( nout, fmt = 9996 )'ZLATRS', uplo, trans,
573 $ diag, 'N', n, imat, 8, result( 8 )
574 nfail = nfail + 1
575 END IF
576 IF( result( 9 ).GE.thresh ) THEN
577 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
578 $
CALL alahd( nout, path )
579 WRITE( nout, fmt = 9996 )'ZLATRS', uplo, trans,
580 $ diag, 'Y', n, imat, 9, result( 9 )
581 nfail = nfail + 1
582 END IF
583 IF( result( 10 ).GE.thresh ) THEN
584 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
585 $
CALL alahd( nout, path )
586 WRITE( nout, fmt = 9996 )'ZLATRS3', uplo, trans,
587 $ diag, 'N', n, imat, 10, result( 10 )
588 nfail = nfail + 1
589 END IF
590 nrun = nrun + 3
591 90 CONTINUE
592 100 CONTINUE
593 110 CONTINUE
594 120 CONTINUE
595
596
597
598 CALL alasum( path, nout, nfail, nrun, nerrs )
599
600 9999 FORMAT( ' UPLO=''', a1, ''', DIAG=''', a1, ''', N=', i5, ', NB=',
601 $ i4, ', type ', i2, ', test(', i2, ')= ', g12.5 )
602 9998 FORMAT( ' UPLO=''', a1, ''', TRANS=''', a1, ''', DIAG=''', a1,
603 $ ''', N=', i5, ', NB=', i4, ', type ', i2, ', test(',
604 $ i2, ')= ', g12.5 )
605 9997 FORMAT( ' NORM=''', a1, ''', UPLO =''', a1, ''', N=', i5, ',',
606 $ 11x, ' type ', i2, ', test(', i2, ')=', g12.5 )
607 9996 FORMAT( 1x, a, '( ''', a1, ''', ''', a1, ''', ''', a1, ''', ''',
608 $ a1, ''',', i5, ', ... ), type ', i2, ', test(', i2, ')=',
609 $ g12.5 )
610 RETURN
611
612
613
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
subroutine xlaenv(ispec, nvalue)
XLAENV
subroutine zlarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
ZLARHS
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine alahd(iounit, path)
ALAHD
subroutine zcopy(n, zx, incx, zy, incy)
ZCOPY
subroutine zlacpy(uplo, m, n, a, lda, b, ldb)
ZLACPY copies all or part of one two-dimensional array to another.
double precision function dlamch(cmach)
DLAMCH
double precision function zlantr(norm, uplo, diag, m, n, a, lda, work)
ZLANTR returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
subroutine zlatrs3(uplo, trans, diag, normin, n, nrhs, a, lda, x, ldx, scale, cnorm, work, lwork, info)
ZLATRS3 solves a triangular system of equations with the scale factors set to prevent overflow.
subroutine zlatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)
ZLATRS solves a triangular system of equations with the scale factor set to prevent overflow.
logical function lsame(ca, cb)
LSAME
subroutine zdscal(n, da, zx, incx)
ZDSCAL
subroutine ztrcon(norm, uplo, diag, n, a, lda, rcond, work, rwork, info)
ZTRCON
subroutine ztrrfs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, x, ldx, ferr, berr, work, rwork, info)
ZTRRFS
subroutine ztrtri(uplo, diag, n, a, lda, info)
ZTRTRI
subroutine ztrtrs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, info)
ZTRTRS
subroutine zerrtr(path, nunit)
ZERRTR
subroutine zget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
ZGET04
subroutine zlattr(imat, uplo, trans, diag, iseed, n, a, lda, b, work, rwork, info)
ZLATTR
subroutine ztrt01(uplo, diag, n, a, lda, ainv, ldainv, rcond, rwork, resid)
ZTRT01
subroutine ztrt02(uplo, trans, diag, n, nrhs, a, lda, x, ldx, b, ldb, work, rwork, resid)
ZTRT02
subroutine ztrt03(uplo, trans, diag, n, nrhs, a, lda, scale, cnorm, tscal, x, ldx, b, ldb, work, resid)
ZTRT03
subroutine ztrt05(uplo, trans, diag, n, nrhs, a, lda, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
ZTRT05
subroutine ztrt06(rcond, rcondc, uplo, diag, n, a, lda, rwork, rat)
ZTRT06