LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dchktr()

subroutine dchktr ( logical, dimension( * )  dotype,
integer  nn,
integer, dimension( * )  nval,
integer  nnb,
integer, dimension( * )  nbval,
integer  nns,
integer, dimension( * )  nsval,
double precision  thresh,
logical  tsterr,
integer  nmax,
double precision, dimension( * )  a,
double precision, dimension( * )  ainv,
double precision, dimension( * )  b,
double precision, dimension( * )  x,
double precision, dimension( * )  xact,
double precision, dimension( * )  work,
double precision, dimension( * )  rwork,
integer, dimension( * )  iwork,
integer  nout 
)

DCHKTR

Purpose:
 DCHKTR tests DTRTRI, -TRS, -RFS, and -CON, and DLATRS(3)
Parameters
[in]DOTYPE
          DOTYPE is LOGICAL array, dimension (NTYPES)
          The matrix types to be used for testing.  Matrices of type j
          (for 1 <= j <= NTYPES) are used for testing if DOTYPE(j) =
          .TRUE.; if DOTYPE(j) = .FALSE., then type j is not used.
[in]NN
          NN is INTEGER
          The number of values of N contained in the vector NVAL.
[in]NVAL
          NVAL is INTEGER array, dimension (NN)
          The values of the matrix column dimension N.
[in]NNB
          NNB is INTEGER
          The number of values of NB contained in the vector NBVAL.
[in]NBVAL
          NBVAL is INTEGER array, dimension (NNB)
          The values of the blocksize NB.
[in]NNS
          NNS is INTEGER
          The number of values of NRHS contained in the vector NSVAL.
[in]NSVAL
          NSVAL is INTEGER array, dimension (NNS)
          The values of the number of right hand sides NRHS.
[in]THRESH
          THRESH is DOUBLE PRECISION
          The threshold value for the test ratios.  A result is
          included in the output file if RESULT >= THRESH.  To have
          every test ratio printed, use THRESH = 0.
[in]TSTERR
          TSTERR is LOGICAL
          Flag that indicates whether error exits are to be tested.
[in]NMAX
          NMAX is INTEGER
          The leading dimension of the work arrays.
          NMAX >= the maximum value of N in NVAL.
[out]A
          A is DOUBLE PRECISION array, dimension (NMAX*NMAX)
[out]AINV
          AINV is DOUBLE PRECISION array, dimension (NMAX*NMAX)
[out]B
          B is DOUBLE PRECISION array, dimension (NMAX*NSMAX)
          where NSMAX is the largest entry in NSVAL.
[out]X
          X is DOUBLE PRECISION array, dimension (NMAX*NSMAX)
[out]XACT
          XACT is DOUBLE PRECISION array, dimension (NMAX*NSMAX)
[out]WORK
          WORK is DOUBLE PRECISION array, dimension
                      (NMAX*max(3,NSMAX))
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension
                      (max(NMAX,2*NSMAX))
[out]IWORK
          IWORK is INTEGER array, dimension (NMAX)
[in]NOUT
          NOUT is INTEGER
          The unit number for output.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 164 of file dchktr.f.

167*
168* -- LAPACK test routine --
169* -- LAPACK is a software package provided by Univ. of Tennessee, --
170* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
171*
172* .. Scalar Arguments ..
173 LOGICAL TSTERR
174 INTEGER NMAX, NN, NNB, NNS, NOUT
175 DOUBLE PRECISION THRESH
176* ..
177* .. Array Arguments ..
178 LOGICAL DOTYPE( * )
179 INTEGER IWORK( * ), NBVAL( * ), NSVAL( * ), NVAL( * )
180 DOUBLE PRECISION A( * ), AINV( * ), B( * ), RWORK( * ),
181 $ WORK( * ), X( * ), XACT( * )
182* ..
183*
184* =====================================================================
185*
186* .. Parameters ..
187 INTEGER NTYPE1, NTYPES
188 parameter( ntype1 = 10, ntypes = 18 )
189 INTEGER NTESTS
190 parameter( ntests = 10 )
191 INTEGER NTRAN
192 parameter( ntran = 3 )
193 DOUBLE PRECISION ONE, ZERO
194 parameter( one = 1.0d0, zero = 0.0d0 )
195* ..
196* .. Local Scalars ..
197 CHARACTER DIAG, NORM, TRANS, UPLO, XTYPE
198 CHARACTER*3 PATH
199 INTEGER I, IDIAG, IMAT, IN, INB, INFO, IRHS, ITRAN,
200 $ IUPLO, K, LDA, N, NB, NERRS, NFAIL, NRHS, NRUN
201 DOUBLE PRECISION AINVNM, ANORM, BIGNUM, DLAMCH, DUMMY, RCOND,
202 $ RCONDC, RCONDI, RCONDO, RES, SCALE
203* ..
204* .. Local Arrays ..
205 CHARACTER TRANSS( NTRAN ), UPLOS( 2 )
206 INTEGER ISEED( 4 ), ISEEDY( 4 )
207 DOUBLE PRECISION RESULT( NTESTS ), SCALE3( 2 )
208* ..
209* .. External Functions ..
210 LOGICAL LSAME
211 DOUBLE PRECISION DLANTR
212 EXTERNAL lsame, dlantr
213* ..
214* .. External Subroutines ..
215 EXTERNAL alaerh, alahd, alasum, dcopy, derrtr, dget04,
219* ..
220* .. Scalars in Common ..
221 LOGICAL LERR, OK
222 CHARACTER*32 SRNAMT
223 INTEGER INFOT, IOUNIT
224* ..
225* .. Common blocks ..
226 COMMON / infoc / infot, iounit, ok, lerr
227 COMMON / srnamc / srnamt
228* ..
229* .. Intrinsic Functions ..
230 INTRINSIC max
231* ..
232* .. Data statements ..
233 DATA iseedy / 1988, 1989, 1990, 1991 /
234 DATA uplos / 'U', 'L' / , transs / 'N', 'T', 'C' /
235* ..
236* .. Executable Statements ..
237*
238* Initialize constants and the random number seed.
239*
240 path( 1: 1 ) = 'Double precision'
241 path( 2: 3 ) = 'TR'
242 bignum = dlamch('Overflow') / dlamch('Precision')
243 nrun = 0
244 nfail = 0
245 nerrs = 0
246 DO 10 i = 1, 4
247 iseed( i ) = iseedy( i )
248 10 CONTINUE
249*
250* Test the error exits
251*
252 IF( tsterr )
253 $ CALL derrtr( path, nout )
254 infot = 0
255 CALL xlaenv( 2, 2 )
256*
257 DO 120 in = 1, nn
258*
259* Do for each value of N in NVAL
260*
261 n = nval( in )
262 lda = max( 1, n )
263 xtype = 'N'
264*
265 DO 80 imat = 1, ntype1
266*
267* Do the tests only if DOTYPE( IMAT ) is true.
268*
269 IF( .NOT.dotype( imat ) )
270 $ GO TO 80
271*
272 DO 70 iuplo = 1, 2
273*
274* Do first for UPLO = 'U', then for UPLO = 'L'
275*
276 uplo = uplos( iuplo )
277*
278* Call DLATTR to generate a triangular test matrix.
279*
280 srnamt = 'DLATTR'
281 CALL dlattr( imat, uplo, 'No transpose', diag, iseed, n,
282 $ a, lda, x, work, info )
283*
284* Set IDIAG = 1 for non-unit matrices, 2 for unit.
285*
286 IF( lsame( diag, 'N' ) ) THEN
287 idiag = 1
288 ELSE
289 idiag = 2
290 END IF
291*
292 DO 60 inb = 1, nnb
293*
294* Do for each blocksize in NBVAL
295*
296 nb = nbval( inb )
297 CALL xlaenv( 1, nb )
298*
299*+ TEST 1
300* Form the inverse of A.
301*
302 CALL dlacpy( uplo, n, n, a, lda, ainv, lda )
303 srnamt = 'DTRTRI'
304 CALL dtrtri( uplo, diag, n, ainv, lda, info )
305*
306* Check error code from DTRTRI.
307*
308 IF( info.NE.0 )
309 $ CALL alaerh( path, 'DTRTRI', info, 0, uplo // diag,
310 $ n, n, -1, -1, nb, imat, nfail, nerrs,
311 $ nout )
312*
313* Compute the infinity-norm condition number of A.
314*
315 anorm = dlantr( 'I', uplo, diag, n, n, a, lda, rwork )
316 ainvnm = dlantr( 'I', uplo, diag, n, n, ainv, lda,
317 $ rwork )
318 IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
319 rcondi = one
320 ELSE
321 rcondi = ( one / anorm ) / ainvnm
322 END IF
323*
324* Compute the residual for the triangular matrix times
325* its inverse. Also compute the 1-norm condition number
326* of A.
327*
328 CALL dtrt01( uplo, diag, n, a, lda, ainv, lda, rcondo,
329 $ rwork, result( 1 ) )
330*
331* Print the test ratio if it is .GE. THRESH.
332*
333 IF( result( 1 ).GE.thresh ) THEN
334 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
335 $ CALL alahd( nout, path )
336 WRITE( nout, fmt = 9999 )uplo, diag, n, nb, imat,
337 $ 1, result( 1 )
338 nfail = nfail + 1
339 END IF
340 nrun = nrun + 1
341*
342* Skip remaining tests if not the first block size.
343*
344 IF( inb.NE.1 )
345 $ GO TO 60
346*
347 DO 40 irhs = 1, nns
348 nrhs = nsval( irhs )
349 xtype = 'N'
350*
351 DO 30 itran = 1, ntran
352*
353* Do for op(A) = A, A**T, or A**H.
354*
355 trans = transs( itran )
356 IF( itran.EQ.1 ) THEN
357 norm = 'O'
358 rcondc = rcondo
359 ELSE
360 norm = 'I'
361 rcondc = rcondi
362 END IF
363*
364*+ TEST 2
365* Solve and compute residual for op(A)*x = b.
366*
367 srnamt = 'DLARHS'
368 CALL dlarhs( path, xtype, uplo, trans, n, n, 0,
369 $ idiag, nrhs, a, lda, xact, lda, b,
370 $ lda, iseed, info )
371 xtype = 'C'
372 CALL dlacpy( 'Full', n, nrhs, b, lda, x, lda )
373*
374 srnamt = 'DTRTRS'
375 CALL dtrtrs( uplo, trans, diag, n, nrhs, a, lda,
376 $ x, lda, info )
377*
378* Check error code from DTRTRS.
379*
380 IF( info.NE.0 )
381 $ CALL alaerh( path, 'DTRTRS', info, 0,
382 $ uplo // trans // diag, n, n, -1,
383 $ -1, nrhs, imat, nfail, nerrs,
384 $ nout )
385*
386* This line is needed on a Sun SPARCstation.
387*
388 IF( n.GT.0 )
389 $ dummy = a( 1 )
390*
391 CALL dtrt02( uplo, trans, diag, n, nrhs, a, lda,
392 $ x, lda, b, lda, work, result( 2 ) )
393*
394*+ TEST 3
395* Check solution from generated exact solution.
396*
397 CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
398 $ result( 3 ) )
399*
400*+ TESTS 4, 5, and 6
401* Use iterative refinement to improve the solution
402* and compute error bounds.
403*
404 srnamt = 'DTRRFS'
405 CALL dtrrfs( uplo, trans, diag, n, nrhs, a, lda,
406 $ b, lda, x, lda, rwork,
407 $ rwork( nrhs+1 ), work, iwork,
408 $ info )
409*
410* Check error code from DTRRFS.
411*
412 IF( info.NE.0 )
413 $ CALL alaerh( path, 'DTRRFS', info, 0,
414 $ uplo // trans // diag, n, n, -1,
415 $ -1, nrhs, imat, nfail, nerrs,
416 $ nout )
417*
418 CALL dget04( n, nrhs, x, lda, xact, lda, rcondc,
419 $ result( 4 ) )
420 CALL dtrt05( uplo, trans, diag, n, nrhs, a, lda,
421 $ b, lda, x, lda, xact, lda, rwork,
422 $ rwork( nrhs+1 ), result( 5 ) )
423*
424* Print information about the tests that did not
425* pass the threshold.
426*
427 DO 20 k = 2, 6
428 IF( result( k ).GE.thresh ) THEN
429 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
430 $ CALL alahd( nout, path )
431 WRITE( nout, fmt = 9998 )uplo, trans,
432 $ diag, n, nrhs, imat, k, result( k )
433 nfail = nfail + 1
434 END IF
435 20 CONTINUE
436 nrun = nrun + 5
437 30 CONTINUE
438 40 CONTINUE
439*
440*+ TEST 7
441* Get an estimate of RCOND = 1/CNDNUM.
442*
443 DO 50 itran = 1, 2
444 IF( itran.EQ.1 ) THEN
445 norm = 'O'
446 rcondc = rcondo
447 ELSE
448 norm = 'I'
449 rcondc = rcondi
450 END IF
451 srnamt = 'DTRCON'
452 CALL dtrcon( norm, uplo, diag, n, a, lda, rcond,
453 $ work, iwork, info )
454*
455* Check error code from DTRCON.
456*
457 IF( info.NE.0 )
458 $ CALL alaerh( path, 'DTRCON', info, 0,
459 $ norm // uplo // diag, n, n, -1, -1,
460 $ -1, imat, nfail, nerrs, nout )
461*
462 CALL dtrt06( rcond, rcondc, uplo, diag, n, a, lda,
463 $ rwork, result( 7 ) )
464*
465* Print the test ratio if it is .GE. THRESH.
466*
467 IF( result( 7 ).GE.thresh ) THEN
468 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
469 $ CALL alahd( nout, path )
470 WRITE( nout, fmt = 9997 )norm, uplo, n, imat,
471 $ 7, result( 7 )
472 nfail = nfail + 1
473 END IF
474 nrun = nrun + 1
475 50 CONTINUE
476 60 CONTINUE
477 70 CONTINUE
478 80 CONTINUE
479*
480* Use pathological test matrices to test DLATRS.
481*
482 DO 110 imat = ntype1 + 1, ntypes
483*
484* Do the tests only if DOTYPE( IMAT ) is true.
485*
486 IF( .NOT.dotype( imat ) )
487 $ GO TO 110
488*
489 DO 100 iuplo = 1, 2
490*
491* Do first for UPLO = 'U', then for UPLO = 'L'
492*
493 uplo = uplos( iuplo )
494 DO 90 itran = 1, ntran
495*
496* Do for op(A) = A, A**T, and A**H.
497*
498 trans = transs( itran )
499*
500* Call DLATTR to generate a triangular test matrix.
501*
502 srnamt = 'DLATTR'
503 CALL dlattr( imat, uplo, trans, diag, iseed, n, a,
504 $ lda, x, work, info )
505*
506*+ TEST 8
507* Solve the system op(A)*x = b.
508*
509 srnamt = 'DLATRS'
510 CALL dcopy( n, x, 1, b, 1 )
511 CALL dlatrs( uplo, trans, diag, 'N', n, a, lda, b,
512 $ scale, rwork, info )
513*
514* Check error code from DLATRS.
515*
516 IF( info.NE.0 )
517 $ CALL alaerh( path, 'DLATRS', info, 0,
518 $ uplo // trans // diag // 'N', n, n,
519 $ -1, -1, -1, imat, nfail, nerrs, nout )
520*
521 CALL dtrt03( uplo, trans, diag, n, 1, a, lda, scale,
522 $ rwork, one, b, lda, x, lda, work,
523 $ result( 8 ) )
524*
525*+ TEST 9
526* Solve op(A)*X = b again with NORMIN = 'Y'.
527*
528 CALL dcopy( n, x, 1, b( n+1 ), 1 )
529 CALL dlatrs( uplo, trans, diag, 'Y', n, a, lda,
530 $ b( n+1 ), scale, rwork, info )
531*
532* Check error code from DLATRS.
533*
534 IF( info.NE.0 )
535 $ CALL alaerh( path, 'DLATRS', info, 0,
536 $ uplo // trans // diag // 'Y', n, n,
537 $ -1, -1, -1, imat, nfail, nerrs, nout )
538*
539 CALL dtrt03( uplo, trans, diag, n, 1, a, lda, scale,
540 $ rwork, one, b( n+1 ), lda, x, lda, work,
541 $ result( 9 ) )
542*
543*+ TEST 10
544* Solve op(A)*X = B
545*
546 srnamt = 'DLATRS3'
547 CALL dcopy( n, x, 1, b, 1 )
548 CALL dcopy( n, x, 1, b( n+1 ), 1 )
549 CALL dscal( n, bignum, b( n+1 ), 1 )
550 CALL dlatrs3( uplo, trans, diag, 'N', n, 2, a, lda,
551 $ b, max(1, n), scale3, rwork, work, nmax,
552 $ info )
553*
554* Check error code from DLATRS3.
555*
556 IF( info.NE.0 )
557 $ CALL alaerh( path, 'DLATRS3', info, 0,
558 $ uplo // trans // diag // 'N', n, n,
559 $ -1, -1, -1, imat, nfail, nerrs, nout )
560 CALL dtrt03( uplo, trans, diag, n, 1, a, lda,
561 $ scale3( 1 ), rwork, one, b( 1 ), lda,
562 $ x, lda, work, result( 10 ) )
563 CALL dscal( n, bignum, x, 1 )
564 CALL dtrt03( uplo, trans, diag, n, 1, a, lda,
565 $ scale3( 2 ), rwork, one, b( n+1 ), lda,
566 $ x, lda, work, res )
567 result( 10 ) = max( result( 10 ), res )
568*
569* Print information about the tests that did not pass
570* the threshold.
571*
572 IF( result( 8 ).GE.thresh ) THEN
573 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
574 $ CALL alahd( nout, path )
575 WRITE( nout, fmt = 9996 )'DLATRS', uplo, trans,
576 $ diag, 'N', n, imat, 8, result( 8 )
577 nfail = nfail + 1
578 END IF
579 IF( result( 9 ).GE.thresh ) THEN
580 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
581 $ CALL alahd( nout, path )
582 WRITE( nout, fmt = 9996 )'DLATRS', uplo, trans,
583 $ diag, 'Y', n, imat, 9, result( 9 )
584 nfail = nfail + 1
585 END IF
586 IF( result( 10 ).GE.thresh ) THEN
587 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
588 $ CALL alahd( nout, path )
589 WRITE( nout, fmt = 9996 )'DLATRS3', uplo, trans,
590 $ diag, 'N', n, imat, 10, result( 10 )
591 nfail = nfail + 1
592 END IF
593 nrun = nrun + 3
594 90 CONTINUE
595 100 CONTINUE
596 110 CONTINUE
597 120 CONTINUE
598*
599* Print a summary of the results.
600*
601 CALL alasum( path, nout, nfail, nrun, nerrs )
602*
603 9999 FORMAT( ' UPLO=''', a1, ''', DIAG=''', a1, ''', N=', i5, ', NB=',
604 $ i4, ', type ', i2, ', test(', i2, ')= ', g12.5 )
605 9998 FORMAT( ' UPLO=''', a1, ''', TRANS=''', a1, ''', DIAG=''', a1,
606 $ ''', N=', i5, ', NB=', i4, ', type ', i2, ', test(',
607 $ i2, ')= ', g12.5 )
608 9997 FORMAT( ' NORM=''', a1, ''', UPLO =''', a1, ''', N=', i5, ',',
609 $ 11x, ' type ', i2, ', test(', i2, ')=', g12.5 )
610 9996 FORMAT( 1x, a, '( ''', a1, ''', ''', a1, ''', ''', a1, ''', ''',
611 $ a1, ''',', i5, ', ... ), type ', i2, ', test(', i2, ')=',
612 $ g12.5 )
613 RETURN
614*
615* End of DCHKTR
616*
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
Definition alasum.f:73
subroutine dlarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
DLARHS
Definition dlarhs.f:205
subroutine xlaenv(ispec, nvalue)
XLAENV
Definition xlaenv.f:81
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
Definition alaerh.f:147
subroutine alahd(iounit, path)
ALAHD
Definition alahd.f:107
subroutine derrtr(path, nunit)
DERRTR
Definition derrtr.f:55
subroutine dget04(n, nrhs, x, ldx, xact, ldxact, rcond, resid)
DGET04
Definition dget04.f:102
subroutine dlattr(imat, uplo, trans, diag, iseed, n, a, lda, b, work, info)
DLATTR
Definition dlattr.f:133
subroutine dtrt01(uplo, diag, n, a, lda, ainv, ldainv, rcond, work, resid)
DTRT01
Definition dtrt01.f:124
subroutine dtrt02(uplo, trans, diag, n, nrhs, a, lda, x, ldx, b, ldb, work, resid)
DTRT02
Definition dtrt02.f:150
subroutine dtrt03(uplo, trans, diag, n, nrhs, a, lda, scale, cnorm, tscal, x, ldx, b, ldb, work, resid)
DTRT03
Definition dtrt03.f:169
subroutine dtrt05(uplo, trans, diag, n, nrhs, a, lda, b, ldb, x, ldx, xact, ldxact, ferr, berr, reslts)
DTRT05
Definition dtrt05.f:181
subroutine dtrt06(rcond, rcondc, uplo, diag, n, a, lda, work, rat)
DTRT06
Definition dtrt06.f:121
subroutine dcopy(n, dx, incx, dy, incy)
DCOPY
Definition dcopy.f:82
subroutine dlacpy(uplo, m, n, a, lda, b, ldb)
DLACPY copies all or part of one two-dimensional array to another.
Definition dlacpy.f:103
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
double precision function dlantr(norm, uplo, diag, m, n, a, lda, work)
DLANTR returns the value of the 1-norm, or the Frobenius norm, or the infinity norm,...
Definition dlantr.f:141
subroutine dlatrs3(uplo, trans, diag, normin, n, nrhs, a, lda, x, ldx, scale, cnorm, work, lwork, info)
DLATRS3 solves a triangular system of equations with the scale factors set to prevent overflow.
Definition dlatrs3.f:229
subroutine dlatrs(uplo, trans, diag, normin, n, a, lda, x, scale, cnorm, info)
DLATRS solves a triangular system of equations with the scale factor set to prevent overflow.
Definition dlatrs.f:238
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine dscal(n, da, dx, incx)
DSCAL
Definition dscal.f:79
subroutine dtrcon(norm, uplo, diag, n, a, lda, rcond, work, iwork, info)
DTRCON
Definition dtrcon.f:137
subroutine dtrrfs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, x, ldx, ferr, berr, work, iwork, info)
DTRRFS
Definition dtrrfs.f:182
subroutine dtrtri(uplo, diag, n, a, lda, info)
DTRTRI
Definition dtrtri.f:109
subroutine dtrtrs(uplo, trans, diag, n, nrhs, a, lda, b, ldb, info)
DTRTRS
Definition dtrtrs.f:140
Here is the call graph for this function:
Here is the caller graph for this function: