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

◆ cchksum()

subroutine cchksum ( character*1  scope,
integer  ictxt,
integer  m,
integer  n,
complex, dimension(lda,*)  a,
integer  lda,
integer  testnum,
integer  maxerr,
integer  nerr,
integer, dimension(6, maxerr)  erribuf,
complex, dimension(2, maxerr)  errdbuf,
integer, dimension(*)  iseed 
)

Definition at line 13713 of file blacstest.f.

13715*
13716* .. Scalar Arguments ..
13717 CHARACTER*1 SCOPE
13718 INTEGER ICTXT, M, N, LDA, TESTNUM, MAXERR, NERR
13719* ..
13720* .. Array Arguments ..
13721 INTEGER ERRIBUF(6, MAXERR), ISEED(*)
13722 COMPLEX A(LDA,*), ERRDBUF(2, MAXERR)
13723* ..
13724* .. External Functions ..
13725 INTEGER IBTMYPROC, IBTNPROCS
13726 REAL SBTEPS
13727 COMPLEX CBTRAN
13728 EXTERNAL ibtmyproc, ibtnprocs, sbteps, cbtran
13729* ..
13730* .. Local Scalars ..
13731 LOGICAL NUMOK
13732 INTEGER NPROCS, NPROW, NPCOL, MYROW, MYCOL, NODE, NNODES, DEST
13733 INTEGER I, J, K
13734 COMPLEX ANS, TMP
13735 REAL EPS, ERRBND, RPOSNUM, RNEGNUM, IPOSNUM, INEGNUM
13736* ..
13737* .. Executable Statements ..
13738*
13739 nprocs = ibtnprocs()
13740 eps = sbteps()
13741 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
13742 dest = myrow*nprocs + mycol
13743*
13744* Set up seeds to match those used by each proc's genmat call
13745*
13746 IF( scope .EQ. 'R' ) THEN
13747 nnodes = npcol
13748 DO 10 i = 0, nnodes-1
13749 node = myrow * nprocs + i
13750 iseed(i*4+1) = mod( 1002 + testnum*5 + node*3, 4096 )
13751 iseed(i*4+2) = mod( 2027 + testnum*7 + node, 4096 )
13752 iseed(i*4+3) = mod( 1234 + testnum + node*3, 4096 )
13753 iseed(i*4+4) = mod( 4311 + testnum*10 + node*2, 4096 )
13754 10 CONTINUE
13755 ELSE IF( scope .EQ. 'C' ) THEN
13756 nnodes = nprow
13757 DO 20 i = 0, nnodes-1
13758 node = i * nprocs + mycol
13759 iseed(i*4+1) = mod( 1002 + testnum*5 + node*3, 4096 )
13760 iseed(i*4+2) = mod( 2027 + testnum*7 + node, 4096 )
13761 iseed(i*4+3) = mod( 1234 + testnum + node*3, 4096 )
13762 iseed(i*4+4) = mod( 4311 + testnum*10 + node*2, 4096 )
13763 20 CONTINUE
13764 ELSE
13765 nnodes = nprow * npcol
13766 DO 30 i = 0, nnodes-1
13767 node = (i / npcol) * nprocs + mod(i, npcol)
13768 iseed(i*4+1) = mod( 1002 + testnum*5 + node*3, 4096 )
13769 iseed(i*4+2) = mod( 2027 + testnum*7 + node, 4096 )
13770 iseed(i*4+3) = mod( 1234 + testnum + node*3, 4096 )
13771 iseed(i*4+4) = mod( 4311 + testnum*10 + node*2, 4096 )
13772 30 CONTINUE
13773 END IF
13774*
13775 DO 100 j = 1, n
13776 DO 90 i = 1, m
13777 ans = 0
13778 rposnum = 0
13779 rnegnum = 0
13780 iposnum = 0
13781 inegnum = 0
13782 DO 40 k = 0, nnodes-1
13783 tmp = cbtran( iseed(k*4+1) )
13784 IF( real( tmp ) .LT. 0 ) THEN
13785 rnegnum = rnegnum + real( tmp )
13786 ELSE
13787 rposnum = rposnum + real( tmp )
13788 END IF
13789 IF( aimag( tmp ) .LT. 0 ) THEN
13790 inegnum = inegnum + aimag( tmp )
13791 ELSE
13792 iposnum = iposnum + aimag( tmp )
13793 END IF
13794 ans = ans + tmp
13795 40 CONTINUE
13796*
13797* The error bound is figured by
13798* 2 * eps * (nnodes-1) * max(|max element|, |ans|).
13799* The 2 allows for errors in the distributed _AND_ local result.
13800* The eps is machine epsilon. The number of floating point adds
13801* is (nnodes - 1). We use the fact that 0.5 is the maximum element
13802* in order to save ourselves some computation.
13803*
13804 tmp = ans - a(i,j)
13805 errbnd = 2 * eps * nnodes * max( rposnum, -rnegnum )
13806 numok = ( real(tmp) .LE. errbnd )
13807 errbnd = 2 * eps * nnodes * max( iposnum, -inegnum )
13808 numok = numok .AND. ( aimag(tmp) .LE. errbnd )
13809 IF( .NOT.numok ) THEN
13810 nerr = nerr + 1
13811 IF( nerr .LE. maxerr ) THEN
13812 erribuf(1, nerr) = testnum
13813 erribuf(2, nerr) = nnodes
13814 erribuf(3, nerr) = dest
13815 erribuf(4, nerr) = i
13816 erribuf(5, nerr) = j
13817 erribuf(6, nerr) = 5
13818 errdbuf(1, nerr) = a(i,j)
13819 errdbuf(2, nerr) = ans
13820 END IF
13821 END IF
13822 90 CONTINUE
13823 100 CONTINUE
13824*
13825 RETURN
13826*
13827* End of CCHKSUM
13828*
complex function cbtran(iseed)
Definition blacstest.f:9683
real function sbteps()
integer function ibtnprocs()
Definition btprim.f:81
integer function ibtmyproc()
Definition btprim.f:47
#define max(A, B)
Definition pcgemr.c:180
Here is the caller graph for this function: