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

◆ ichkmat()

subroutine ichkmat ( character*1  uplo,
character*1  diag,
integer  m,
integer  n,
integer, 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,
integer, dimension(2, maxerr)  errdbuf 
)

Definition at line 6940 of file blacstest.f.

6943*
6944* -- BLACS tester (version 1.0) --
6945* University of Tennessee
6946* December 15, 1994
6947*
6948*
6949* .. Scalar Arguments ..
6950 CHARACTER*1 UPLO, DIAG
6951 INTEGER M, N, LDA, RSRC, CSRC, MYROW, MYCOL, TESTNUM
6952 INTEGER MAXERR, NERR
6953* ..
6954* .. Array Arguments ..
6955 INTEGER ERRIBUF(6, MAXERR)
6956 INTEGER A(LDA,N), ERRDBUF(2, MAXERR)
6957* ..
6958*
6959* Purpose
6960* =======
6961* iCHKMAT: Check matrix to see whether there were any transmission
6962* errors.
6963*
6964* Arguments
6965* =========
6966* UPLO (input) CHARACTER*1
6967* Is the matrix A 'U'pper or 'L'ower trapezoidal, or 'G'eneral
6968* rectangular?
6969*
6970* DIAG (input) CHARACTER*1
6971* For trapezoidal matrices, is the main diagonal included
6972* ('N') or not ('U')?
6973*
6974* M (input) INTEGER
6975* The number of rows of the matrix A. M >= 0.
6976*
6977* N (input) INTEGER
6978* The number of columns of the matrix A. N >= 0.
6979*
6980* A (input) @up@(doctype) array, dimension (LDA,N)
6981* The m by n matrix A. Fortran77 (column-major) storage
6982* assumed.
6983*
6984* LDA (input) INTEGER
6985* The leading dimension of the array A. LDA >= max(1, M).
6986*
6987* RSRC (input) INTEGER
6988* The process row of the source of the matrix.
6989*
6990* CSRC (input) INTEGER
6991* The process column of the source of the matrix.
6992*
6993* MYROW (input) INTEGER
6994* Row of this process in the process grid.
6995*
6996* MYCOL (input) INTEGER
6997* Column of this process in the process grid.
6998*
6999*
7000* TESTNUM (input) INTEGER
7001* The number of the test being checked.
7002*
7003* MAXERR (input) INTEGER
7004* Max number of errors that can be stored in ERRIBUFF or
7005* ERRIBUFF
7006*
7007* NERR (output) INTEGER
7008* The number of errors that have been found.
7009*
7010* ERRIBUF (output) INTEGER array, dimension (6,MAXERRS)
7011* Buffer in which to store integer error information. It will
7012* be built up in the following format for the call to TSEND.
7013* All integer information is recorded in the following 6-tuple
7014* {TESTNUM, SRC, DEST, I, J, WHAT}. These values are figured:
7015* SRC = RSRC * NPROCS + CSRC
7016* DEST = RDEST * NPROCS + CDEST
7017* WHAT
7018* = 1 : Error in pre-padding
7019* = 2 : Error in post-padding
7020* = 3 : Error in LDA-M gap
7021* = 4 : Error in complementory triangle
7022* ELSE: Error in matrix
7023* If there are more errors than can fit in the error buffer,
7024* the error number will indicate the actual number of errors
7025* found, but the buffer will be truncated to the maximum
7026* number of errors which can fit.
7027*
7028* ERRDBUF (output) @(doctype) array, dimension (2, MAXERRS)
7029* Buffer in which to store error data information.
7030* {Incorrect, Predicted}
7031*
7032* ===================================================================
7033*
7034* .. Local Scalars ..
7035 INTEGER I, J, NPROCS, SRC, DEST
7036 LOGICAL USEIT
7037 INTEGER COMPVAL
7038* ..
7039* .. Local Arrays ..
7040 INTEGER ISEED(4)
7041* ..
7042* .. External Functions ..
7043 INTEGER IBTNPROCS
7044 INTEGER IBTRAN
7045 EXTERNAL ibtran, ibtnprocs
7046* ..
7047* .. Executable Statements ..
7048*
7049 nprocs = ibtnprocs()
7050 src = rsrc * nprocs + csrc
7051 dest = myrow * nprocs + mycol
7052*
7053* Initialize ISEED with the same values as used in IGENMAT.
7054*
7055 iseed(1) = mod( 1002 + testnum*5 + src*3, 4096 )
7056 iseed(2) = mod( 2027 + testnum*7 + src, 4096 )
7057 iseed(3) = mod( 1234 + testnum + src*3, 4096 )
7058 iseed(4) = mod( 4311 + testnum*10 + src*2, 4096 )
7059*
7060* Generate the elements randomly with the same method used in GENMAT.
7061* Note that for trapezoidal matrices, we generate all elements in the
7062* enclosing rectangle and then ignore the complementary triangle.
7063*
7064 DO 100 j = 1, n
7065 DO 105 i = 1, m
7066 compval = ibtran( iseed )
7067*
7068* Now determine whether we actually need this value. The
7069* strategy is to chop out the proper triangle based on what
7070* particular kind of trapezoidal matrix we're dealing with.
7071*
7072 useit = .true.
7073 IF( uplo .EQ. 'U' ) THEN
7074 IF( m .LE. n ) THEN
7075 IF( diag .EQ. 'U' ) THEN
7076 IF( i .GE. j ) THEN
7077 useit = .false.
7078 END IF
7079 ELSE
7080 IF( i .GT. j ) THEN
7081 useit = .false.
7082 END IF
7083 END IF
7084 ELSE
7085 IF( diag .EQ. 'U' ) THEN
7086 IF( i .GE. m-n+j ) THEN
7087 useit = .false.
7088 END IF
7089 ELSE
7090 IF( i .GT. m-n+j ) THEN
7091 useit = .false.
7092 END IF
7093 END IF
7094 END IF
7095 ELSE IF( uplo .EQ. 'L' ) THEN
7096 IF( m .LE. n ) THEN
7097 IF( diag .EQ. 'U' ) THEN
7098 IF( j. ge. i+(n-m) ) THEN
7099 useit = .false.
7100 END IF
7101 ELSE
7102 IF( j .GT. i+(n-m) ) THEN
7103 useit = .false.
7104 END IF
7105 END IF
7106 ELSE
7107 IF( diag .EQ. 'U' ) THEN
7108 IF( j .GE. i ) THEN
7109 useit = .false.
7110 END IF
7111 ELSE
7112 IF( j .GT. i ) THEN
7113 useit = .false.
7114 END IF
7115 END IF
7116 END IF
7117 END IF
7118*
7119* Compare the generated value to the one that's in the
7120* received matrix. If they don't match, tack another
7121* error record onto what's already there.
7122*
7123 IF( useit ) THEN
7124 IF( a(i,j) .NE. compval ) THEN
7125 nerr = nerr + 1
7126 IF( nerr .LE. maxerr ) THEN
7127 erribuf(1, nerr) = testnum
7128 erribuf(2, nerr) = src
7129 erribuf(3, nerr) = dest
7130 erribuf(4, nerr) = i
7131 erribuf(5, nerr) = j
7132 erribuf(6, nerr) = 5
7133 errdbuf(1, nerr) = a(i, j)
7134 errdbuf(2, nerr) = compval
7135 END IF
7136 END IF
7137 END IF
7138 105 CONTINUE
7139 100 CONTINUE
7140 RETURN
7141*
7142* End of ICHKMAT.
7143*
integer function ibtran(iseed)
Definition blacstest.f:6486
integer function ibtnprocs()
Definition btprim.f:81