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

◆ zchkmat()

subroutine zchkmat ( character*1  uplo,
character*1  diag,
integer  m,
integer  n,
double complex, dimension(lda,n)  a,
integer  lda,
integer  rsrc,
integer  csrc,
integer  myrow,
integer  mycol,
integer  testnum,
integer  maxerr,
integer  nerr,
integer, dimension(6, maxerr)  erribuf,
double complex, dimension(2, maxerr)  errdbuf 
)

Definition at line 11198 of file blacstest.f.

11201*
11202* -- BLACS tester (version 1.0) --
11203* University of Tennessee
11204* December 15, 1994
11205*
11206*
11207* .. Scalar Arguments ..
11208 CHARACTER*1 UPLO, DIAG
11209 INTEGER M, N, LDA, RSRC, CSRC, MYROW, MYCOL, TESTNUM
11210 INTEGER MAXERR, NERR
11211* ..
11212* .. Array Arguments ..
11213 INTEGER ERRIBUF(6, MAXERR)
11214 DOUBLE COMPLEX A(LDA,N), ERRDBUF(2, MAXERR)
11215* ..
11216*
11217* Purpose
11218* =======
11219* zCHKMAT: Check matrix to see whether there were any transmission
11220* errors.
11221*
11222* Arguments
11223* =========
11224* UPLO (input) CHARACTER*1
11225* Is the matrix A 'U'pper or 'L'ower trapezoidal, or 'G'eneral
11226* rectangular?
11227*
11228* DIAG (input) CHARACTER*1
11229* For trapezoidal matrices, is the main diagonal included
11230* ('N') or not ('U')?
11231*
11232* M (input) INTEGER
11233* The number of rows of the matrix A. M >= 0.
11234*
11235* N (input) INTEGER
11236* The number of columns of the matrix A. N >= 0.
11237*
11238* A (input) @up@(doctype) array, dimension (LDA,N)
11239* The m by n matrix A. Fortran77 (column-major) storage
11240* assumed.
11241*
11242* LDA (input) INTEGER
11243* The leading dimension of the array A. LDA >= max(1, M).
11244*
11245* RSRC (input) INTEGER
11246* The process row of the source of the matrix.
11247*
11248* CSRC (input) INTEGER
11249* The process column of the source of the matrix.
11250*
11251* MYROW (input) INTEGER
11252* Row of this process in the process grid.
11253*
11254* MYCOL (input) INTEGER
11255* Column of this process in the process grid.
11256*
11257*
11258* TESTNUM (input) INTEGER
11259* The number of the test being checked.
11260*
11261* MAXERR (input) INTEGER
11262* Max number of errors that can be stored in ERRIBUFF or
11263* ERRZBUFF
11264*
11265* NERR (output) INTEGER
11266* The number of errors that have been found.
11267*
11268* ERRIBUF (output) INTEGER array, dimension (6,MAXERRS)
11269* Buffer in which to store integer error information. It will
11270* be built up in the following format for the call to TSEND.
11271* All integer information is recorded in the following 6-tuple
11272* {TESTNUM, SRC, DEST, I, J, WHAT}. These values are figured:
11273* SRC = RSRC * NPROCS + CSRC
11274* DEST = RDEST * NPROCS + CDEST
11275* WHAT
11276* = 1 : Error in pre-padding
11277* = 2 : Error in post-padding
11278* = 3 : Error in LDA-M gap
11279* = 4 : Error in complementory triangle
11280* ELSE: Error in matrix
11281* If there are more errors than can fit in the error buffer,
11282* the error number will indicate the actual number of errors
11283* found, but the buffer will be truncated to the maximum
11284* number of errors which can fit.
11285*
11286* ERRDBUF (output) @(doctype) array, dimension (2, MAXERRS)
11287* Buffer in which to store error data information.
11288* {Incorrect, Predicted}
11289*
11290* ===================================================================
11291*
11292* .. Local Scalars ..
11293 INTEGER I, J, NPROCS, SRC, DEST
11294 LOGICAL USEIT
11295 DOUBLE COMPLEX COMPVAL
11296* ..
11297* .. Local Arrays ..
11298 INTEGER ISEED(4)
11299* ..
11300* .. External Functions ..
11301 INTEGER IBTNPROCS
11302 DOUBLE COMPLEX ZBTRAN
11303 EXTERNAL zbtran, ibtnprocs
11304* ..
11305* .. Executable Statements ..
11306*
11307 nprocs = ibtnprocs()
11308 src = rsrc * nprocs + csrc
11309 dest = myrow * nprocs + mycol
11310*
11311* Initialize ISEED with the same values as used in ZGENMAT.
11312*
11313 iseed(1) = mod( 1002 + testnum*5 + src*3, 4096 )
11314 iseed(2) = mod( 2027 + testnum*7 + src, 4096 )
11315 iseed(3) = mod( 1234 + testnum + src*3, 4096 )
11316 iseed(4) = mod( 4311 + testnum*10 + src*2, 4096 )
11317*
11318* Generate the elements randomly with the same method used in GENMAT.
11319* Note that for trapezoidal matrices, we generate all elements in the
11320* enclosing rectangle and then ignore the complementary triangle.
11321*
11322 DO 100 j = 1, n
11323 DO 105 i = 1, m
11324 compval = zbtran( iseed )
11325*
11326* Now determine whether we actually need this value. The
11327* strategy is to chop out the proper triangle based on what
11328* particular kind of trapezoidal matrix we're dealing with.
11329*
11330 useit = .true.
11331 IF( uplo .EQ. 'U' ) THEN
11332 IF( m .LE. n ) THEN
11333 IF( diag .EQ. 'U' ) THEN
11334 IF( i .GE. j ) THEN
11335 useit = .false.
11336 END IF
11337 ELSE
11338 IF( i .GT. j ) THEN
11339 useit = .false.
11340 END IF
11341 END IF
11342 ELSE
11343 IF( diag .EQ. 'U' ) THEN
11344 IF( i .GE. m-n+j ) THEN
11345 useit = .false.
11346 END IF
11347 ELSE
11348 IF( i .GT. m-n+j ) THEN
11349 useit = .false.
11350 END IF
11351 END IF
11352 END IF
11353 ELSE IF( uplo .EQ. 'L' ) THEN
11354 IF( m .LE. n ) THEN
11355 IF( diag .EQ. 'U' ) THEN
11356 IF( j. ge. i+(n-m) ) THEN
11357 useit = .false.
11358 END IF
11359 ELSE
11360 IF( j .GT. i+(n-m) ) THEN
11361 useit = .false.
11362 END IF
11363 END IF
11364 ELSE
11365 IF( diag .EQ. 'U' ) THEN
11366 IF( j .GE. i ) THEN
11367 useit = .false.
11368 END IF
11369 ELSE
11370 IF( j .GT. i ) THEN
11371 useit = .false.
11372 END IF
11373 END IF
11374 END IF
11375 END IF
11376*
11377* Compare the generated value to the one that's in the
11378* received matrix. If they don't match, tack another
11379* error record onto what's already there.
11380*
11381 IF( useit ) THEN
11382 IF( a(i,j) .NE. compval ) THEN
11383 nerr = nerr + 1
11384 IF( nerr .LE. maxerr ) THEN
11385 erribuf(1, nerr) = testnum
11386 erribuf(2, nerr) = src
11387 erribuf(3, nerr) = dest
11388 erribuf(4, nerr) = i
11389 erribuf(5, nerr) = j
11390 erribuf(6, nerr) = 5
11391 errdbuf(1, nerr) = a(i, j)
11392 errdbuf(2, nerr) = compval
11393 END IF
11394 END IF
11395 END IF
11396 105 CONTINUE
11397 100 CONTINUE
11398 RETURN
11399*
11400* End of ZCHKMAT.
11401*
double complex function zbtran(iseed)
integer function ibtnprocs()
Definition btprim.f:81