SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dprinterrs()

subroutine dprinterrs ( integer  outnum,
integer  maxerr,
integer  nerr,
integer, dimension(6, maxerr)  erribuf,
double precision, dimension(2, maxerr)  errdbuf,
logical  counting,
integer, dimension(*)  tfailed 
)

Definition at line 9274 of file blacstest.f.

9276*
9277* -- BLACS tester (version 1.0) --
9278* University of Tennessee
9279* December 15, 1994
9280*
9281*
9282* .. Scalar Arguments ..
9283 LOGICAL COUNTING
9284 INTEGER OUTNUM, MAXERR, NERR
9285* ..
9286* .. Array Arguments ..
9287 INTEGER ERRIBUF(6, MAXERR), TFAILED(*)
9288 DOUBLE PRECISION ERRDBUF(2, MAXERR)
9289* ..
9290*
9291* Purpose
9292* =======
9293* DPRINTERRS: Print errors that have been recorded
9294*
9295* Arguments
9296* =========
9297* OUTNUM (input) INTEGER
9298* Device number for output.
9299*
9300* MAXERR (input) INTEGER
9301* Max number of errors that can be stored in ERRIBUFF or
9302* ERRDBUFF
9303*
9304* NERR (output) INTEGER
9305* The number of errors that have been found.
9306*
9307* ERRIBUF (output) INTEGER array, dimension (6,MAXERRS)
9308* Buffer in which to store integer error information. It will
9309* be built up in the following format for the call to TSEND.
9310* All integer information is recorded in the following 6-tuple
9311* {TESTNUM, SRC, DEST, I, J, WHAT}. These values are figured:
9312* SRC = RSRC * NPROCS + CSRC
9313* DEST = RDEST * NPROCS + CDEST
9314* WHAT
9315* = 1 : Error in pre-padding
9316* = 2 : Error in post-padding
9317* = 3 : Error in LDA-M gap
9318* = 4 : Error in complementory triangle
9319* ELSE: Error in matrix
9320* If there are more errors than can fit in the error buffer,
9321* the error number will indicate the actual number of errors
9322* found, but the buffer will be truncated to the maximum
9323* number of errors which can fit.
9324*
9325* ERRDBUF (output) @(doctype) array, dimension (2, MAXERRS)
9326* Buffer in which to store error data information.
9327* {Incorrect, Predicted}
9328*
9329* TFAILED (input/ourput) INTEGER array, dimension NTESTS
9330* Workspace used to keep track of which tests failed.
9331* This array not accessed unless COUNTING is true.
9332*
9333* ===================================================================
9334*
9335* .. Parameters ..
9336 INTEGER ERR_PRE, ERR_POST, ERR_GAP, ERR_TRI, ERR_MAT
9337 parameter( err_pre = 1, err_post = 2, err_gap = 3, err_tri = 4 )
9338 parameter( err_mat = 5 )
9339* ..
9340* .. External Functions ..
9341 INTEGER IBTMYPROC, IBTNPROCS
9342 EXTERNAL ibtmyproc, ibtnprocs
9343* ..
9344* .. Local Scalars ..
9345 CHARACTER*1 MAT
9346 LOGICAL MATISINT
9347 INTEGER OLDTEST, NPROCS, PROW, PCOL, I, ERRTYPE
9348* ..
9349* .. Executable Statements ..
9350*
9351 IF( (ibtmyproc().NE.0) .OR. (nerr.LE.0) ) RETURN
9352 oldtest = -1
9353 nprocs = ibtnprocs()
9354 prow = erribuf(3,1) / nprocs
9355 pcol = mod( erribuf(3,1), nprocs )
9356 IF( nerr .GT. maxerr ) WRITE(outnum,13000)
9357*
9358 DO 20 i = 1, min( nerr, maxerr )
9359 IF( erribuf(1,i) .NE. oldtest ) THEN
9360 IF( oldtest .NE. -1 )
9361 $ WRITE(outnum,12000) prow, pcol, oldtest
9362 WRITE(outnum,*) ' '
9363 WRITE(outnum,1000) prow, pcol, erribuf(1,i)
9364 IF( counting ) tfailed( erribuf(1,i) ) = 1
9365 oldtest = erribuf(1, i)
9366 END IF
9367*
9368* Print out error message depending on type of error
9369*
9370 errtype = erribuf(6, i)
9371 IF( errtype .LT. -10 ) THEN
9372 errtype = -errtype - 10
9373 mat = 'C'
9374 matisint = .true.
9375 ELSE IF( errtype .LT. 0 ) THEN
9376 errtype = -errtype
9377 mat = 'R'
9378 matisint = .true.
9379 ELSE
9380 matisint = .false.
9381 END IF
9382*
9383* RA/CA arrays from MAX/MIN have different printing protocol
9384*
9385 IF( matisint ) THEN
9386 IF( erribuf(2, i) .EQ. -1 ) THEN
9387 WRITE(outnum,11000) erribuf(4,i), erribuf(5,i), mat,
9388 $ int( errdbuf(2,i) ), int( errdbuf(1,i) )
9389 ELSE IF( errtype .EQ. err_pre ) THEN
9390 WRITE(outnum,7000) erribuf(5,i), mat,
9391 $ int( errdbuf(2,i) ), int( errdbuf(1,i) )
9392 ELSE IF( errtype .EQ. err_post ) THEN
9393 WRITE(outnum,8000) erribuf(4,i), mat,
9394 $ int( errdbuf(2,i) ), int( errdbuf(1,i) )
9395 ELSE IF( errtype .EQ. err_gap ) THEN
9396 WRITE(outnum,9000) mat, erribuf(4,i), erribuf(5,i),
9397 $ int( errdbuf(2,i) ), int( errdbuf(1,i) )
9398 ELSE
9399 WRITE(outnum,10000) mat, erribuf(4,i), erribuf(5,i),
9400 $ int( errdbuf(2,i) ),
9401 $ int( errdbuf(1,i) )
9402 END IF
9403*
9404* Have memory overwrites in matrix A
9405*
9406 ELSE
9407 IF( errtype .EQ. err_pre ) THEN
9408 WRITE(outnum,2000) erribuf(5,i), errdbuf(2,i),
9409 $ errdbuf(1,i)
9410 ELSE IF( errtype .EQ. err_post ) THEN
9411 WRITE(outnum,3000) erribuf(4,i), errdbuf(2,i),
9412 $ errdbuf(1,i)
9413 ELSE IF( errtype .EQ. err_gap ) THEN
9414 WRITE(outnum,4000) erribuf(4,i), erribuf(5,i),
9415 $ errdbuf(2,i), errdbuf(1,i)
9416 ELSE IF( errtype .EQ. err_tri ) THEN
9417 WRITE(outnum,5000) erribuf(4,i), erribuf(5,i),
9418 $ errdbuf(2,i), errdbuf(1,i)
9419 ELSE
9420 WRITE(outnum,6000) erribuf(4,i), erribuf(5,i),
9421 $ errdbuf(2,i), errdbuf(1,i)
9422 END IF
9423 END IF
9424 20 CONTINUE
9425 WRITE(outnum,12000) prow, pcol, oldtest
9426*
9427 1000 FORMAT('PROCESS {',i4,',',i4,'} REPORTS ERRORS IN TEST#',i6,':')
9428 2000 FORMAT(' Buffer overwrite ',i4,
9429 $ ' elements before the start of A:',/,
9430 $ ' Expected=',g22.15,
9431 $ '; Received=',g22.15)
9432 3000 FORMAT(' Buffer overwrite ',i4,' elements after the end of A:',
9433 $ /,' Expected=',g22.15,
9434 $ '; Received=',g22.15)
9435 4000 FORMAT(' LDA-M gap overwrite at postion (',i4,',',i4,'):',/,
9436 $ ' Expected=',g22.15,
9437 $ '; Received=',g22.15)
9438 5000 FORMAT(' Complementory triangle overwrite at A(',i4,',',i4,
9439 $ '):',/,' Expected=',g22.15,
9440 $ '; Received=',g22.15)
9441 6000 FORMAT(' Invalid element at A(',i4,',',i4,'):',/,
9442 $ ' Expected=',g22.15,
9443 $ '; Received=',g22.15)
9444 7000 FORMAT(' Buffer overwrite ',i4,' elements before the start of ',
9445 $ a1,'A:',/,' Expected=',i12,'; Received=',i12)
9446 8000 FORMAT(' Buffer overwrite ',i4,' elements after the end of ',
9447 $ a1,'A:',/,' Expected=',i12,'; Received=',i12)
9448*
9449 9000 FORMAT(' LD',a1,'A-M gap overwrite at postion (',i4,',',i4,'):'
9450 $ ,/,' Expected=',i12,'; Received=',i12)
9451*
945210000 FORMAT(' Invalid element at ',a1,'A(',i4,',',i4,'):',/,
9453 $ ' Expected=',i12,'; Received=',i12)
945411000 FORMAT(' Overwrite at position (',i4,',',i4,') of non-existent '
9455 $ ,a1,'A array.',/,' Expected=',i12,'; Received=',i12)
945612000 FORMAT('PROCESS {',i4,',',i4,'} DONE ERROR REPORT FOR TEST#',
9457 $ i6,'.')
945813000 FORMAT('WARNING: There were more errors than could be recorded.',
9459 $ /,'Increase MEMELTS to get complete listing.')
9460 RETURN
9461*
9462* End DPRINTERRS
9463*
integer function ibtnprocs()
Definition btprim.f:81
integer function ibtmyproc()
Definition btprim.f:47
#define min(A, B)
Definition pcgemr.c:181
Here is the caller graph for this function: