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

◆ pzchkmout()

subroutine pzchkmout ( integer  m,
integer  n,
complex*16, dimension( * )  a,
complex*16, dimension( * )  pa,
integer  ia,
integer  ja,
integer, dimension( * )  desca,
integer  info 
)

Definition at line 3632 of file pzblastst.f.

3633*
3634* -- PBLAS test routine (version 2.0) --
3635* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
3636* and University of California, Berkeley.
3637* April 1, 1998
3638*
3639* .. Scalar Arguments ..
3640 INTEGER IA, INFO, JA, M, N
3641* ..
3642* .. Array Arguments ..
3643 INTEGER DESCA( * )
3644 COMPLEX*16 A( * ), PA( * )
3645* ..
3646*
3647* Purpose
3648* =======
3649*
3650* PZCHKMOUT checks that the matrix PA \ sub( PA ) remained unchanged.
3651* The local array entries are compared element by element, and their
3652* difference is tested against 0.0 as well as the epsilon machine. No-
3653* tice that this difference should be numerically exactly the zero ma-
3654* chine, but because of the possible movement of some of the data we
3655* flagged differently a difference less than twice the epsilon machine.
3656* The largest error is reported.
3657*
3658* Notes
3659* =====
3660*
3661* A description vector is associated with each 2D block-cyclicly dis-
3662* tributed matrix. This vector stores the information required to
3663* establish the mapping between a matrix entry and its corresponding
3664* process and memory location.
3665*
3666* In the following comments, the character _ should be read as
3667* "of the distributed matrix". Let A be a generic term for any 2D
3668* block cyclicly distributed matrix. Its description vector is DESCA:
3669*
3670* NOTATION STORED IN EXPLANATION
3671* ---------------- --------------- ------------------------------------
3672* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
3673* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
3674* the NPROW x NPCOL BLACS process grid
3675* A is distributed over. The context
3676* itself is global, but the handle
3677* (the integer value) may vary.
3678* M_A (global) DESCA( M_ ) The number of rows in the distribu-
3679* ted matrix A, M_A >= 0.
3680* N_A (global) DESCA( N_ ) The number of columns in the distri-
3681* buted matrix A, N_A >= 0.
3682* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
3683* block of the matrix A, IMB_A > 0.
3684* INB_A (global) DESCA( INB_ ) The number of columns of the upper
3685* left block of the matrix A,
3686* INB_A > 0.
3687* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
3688* bute the last M_A-IMB_A rows of A,
3689* MB_A > 0.
3690* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
3691* bute the last N_A-INB_A columns of
3692* A, NB_A > 0.
3693* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
3694* row of the matrix A is distributed,
3695* NPROW > RSRC_A >= 0.
3696* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
3697* first column of A is distributed.
3698* NPCOL > CSRC_A >= 0.
3699* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
3700* array storing the local blocks of
3701* the distributed matrix A,
3702* IF( Lc( 1, N_A ) > 0 )
3703* LLD_A >= MAX( 1, Lr( 1, M_A ) )
3704* ELSE
3705* LLD_A >= 1.
3706*
3707* Let K be the number of rows of a matrix A starting at the global in-
3708* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
3709* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
3710* receive if these K rows were distributed over NPROW processes. If K
3711* is the number of columns of a matrix A starting at the global index
3712* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
3713* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
3714* these K columns were distributed over NPCOL processes.
3715*
3716* The values of Lr() and Lc() may be determined via a call to the func-
3717* tion PB_NUMROC:
3718* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
3719* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
3720*
3721* Arguments
3722* =========
3723*
3724* M (global input) INTEGER
3725* On entry, M specifies the number of rows of the submatrix
3726* sub( PA ). M must be at least zero.
3727*
3728* N (global input) INTEGER
3729* On entry, N specifies the number of columns of the submatrix
3730* sub( PA ). N must be at least zero.
3731*
3732* A (local input) COMPLEX*16 array
3733* On entry, A is an array of dimension (DESCA( M_ ),*). This
3734* array contains a local copy of the initial entire matrix PA.
3735*
3736* PA (local input) COMPLEX*16 array
3737* On entry, PA is an array of dimension (DESCA( LLD_ ),*). This
3738* array contains the local entries of the matrix PA.
3739*
3740* IA (global input) INTEGER
3741* On entry, IA specifies A's global row index, which points to
3742* the beginning of the submatrix sub( A ).
3743*
3744* JA (global input) INTEGER
3745* On entry, JA specifies A's global column index, which points
3746* to the beginning of the submatrix sub( A ).
3747*
3748* DESCA (global and local input) INTEGER array
3749* On entry, DESCA is an integer array of dimension DLEN_. This
3750* is the array descriptor for the matrix A.
3751*
3752* INFO (global output) INTEGER
3753* On exit, if INFO = 0, no error has been found,
3754* If INFO > 0, the maximum abolute error found is in (0,eps],
3755* If INFO < 0, the maximum abolute error found is in (eps,+oo).
3756*
3757* -- Written on April 1, 1998 by
3758* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
3759*
3760* =====================================================================
3761*
3762* .. Parameters ..
3763 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
3764 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
3765 $ RSRC_
3766 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
3767 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
3768 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
3769 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
3770 DOUBLE PRECISION ZERO
3771 parameter( zero = 0.0d+0 )
3772* ..
3773* .. Local Scalars ..
3774 LOGICAL COLREP, ROWREP
3775 INTEGER I, IB, ICTXT, ICURCOL, II, IMBA, J, JB, JJ, KK,
3776 $ LDA, LDPA, LL, MPALL, MYCOL, MYROW, MYROWDIST,
3777 $ NPCOL, NPROW
3778 DOUBLE PRECISION EPS, ERR, ERRMAX
3779* ..
3780* .. External Subroutines ..
3781 EXTERNAL blacs_gridinfo, dgamx2d, pzerrset
3782* ..
3783* .. External Functions ..
3784 INTEGER PB_NUMROC
3785 DOUBLE PRECISION PDLAMCH
3786 EXTERNAL pdlamch, pb_numroc
3787* ..
3788* .. Intrinsic Functions ..
3789 INTRINSIC max, min, mod
3790* ..
3791* .. Executable Statements ..
3792*
3793 info = 0
3794 errmax = zero
3795*
3796* Quick return if possible
3797*
3798 IF( ( desca( m_ ).LE.0 ).OR.( desca( n_ ).LE.0 ) )
3799 $ RETURN
3800*
3801* Start the operations
3802*
3803 ictxt = desca( ctxt_ )
3804 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
3805*
3806 eps = pdlamch( ictxt, 'eps' )
3807*
3808 mpall = pb_numroc( desca( m_ ), 1, desca( imb_ ), desca( mb_ ),
3809 $ myrow, desca( rsrc_ ), nprow )
3810*
3811 lda = desca( m_ )
3812 ldpa = desca( lld_ )
3813*
3814 ii = 1
3815 jj = 1
3816 rowrep = ( desca( rsrc_ ).EQ.-1 )
3817 colrep = ( desca( csrc_ ).EQ.-1 )
3818 icurcol = desca( csrc_ )
3819 IF( myrow.EQ.desca( rsrc_ ) .OR. rowrep ) THEN
3820 imba = desca( imb_ )
3821 ELSE
3822 imba = desca( mb_ )
3823 END IF
3824 IF( rowrep ) THEN
3825 myrowdist = 0
3826 ELSE
3827 myrowdist = mod( myrow - desca( rsrc_ ) + nprow, nprow )
3828 END IF
3829*
3830 IF( mycol.EQ.icurcol .OR. colrep ) THEN
3831*
3832 j = 1
3833 IF( myrowdist.EQ.0 ) THEN
3834 i = 1
3835 ELSE
3836 i = desca( imb_ ) + ( myrowdist - 1 ) * desca( mb_ ) + 1
3837 END IF
3838 ib = min( max( 0, desca( m_ ) - i + 1 ), imba )
3839 jb = min( desca( n_ ), desca( inb_ ) )
3840*
3841 DO 20 kk = 0, jb-1
3842 DO 10 ll = 0, ib-1
3843 IF( i+ll.LT.ia .OR. i+ll.GT.ia+m-1 .OR.
3844 $ j+kk.LT.ja .OR. j+kk.GT.ja+n-1 )
3845 $ CALL pzerrset( err, errmax, a( i+ll+(j+kk-1)*lda ),
3846 $ pa( ii+ll+(jj+kk-1)*ldpa ) )
3847 10 CONTINUE
3848 20 CONTINUE
3849 IF( rowrep ) THEN
3850 i = i + imba
3851 ELSE
3852 i = i + imba + ( nprow - 1 ) * desca( mb_ )
3853 END IF
3854*
3855 DO 50 ii = imba + 1, mpall, desca( mb_ )
3856 ib = min( mpall-ii+1, desca( mb_ ) )
3857*
3858 DO 40 kk = 0, jb-1
3859 DO 30 ll = 0, ib-1
3860 IF( i+ll.LT.ia .OR. i+ll.GT.ia+m-1 .OR.
3861 $ j+kk.LT.ja .OR. j+kk.GT.ja+n-1 )
3862 $ CALL pzerrset( err, errmax,
3863 $ a( i+ll+(j+kk-1)*lda ),
3864 $ pa( ii+ll+(jj+kk-1)*ldpa ) )
3865 30 CONTINUE
3866 40 CONTINUE
3867*
3868 IF( rowrep ) THEN
3869 i = i + desca( mb_ )
3870 ELSE
3871 i = i + nprow * desca( mb_ )
3872 END IF
3873*
3874 50 CONTINUE
3875*
3876 jj = jj + jb
3877*
3878 END IF
3879*
3880 icurcol = mod( icurcol + 1, npcol )
3881*
3882 DO 110 j = desca( inb_ ) + 1, desca( n_ ), desca( nb_ )
3883 jb = min( desca( n_ ) - j + 1, desca( nb_ ) )
3884*
3885 IF( mycol.EQ.icurcol .OR. colrep ) THEN
3886*
3887 IF( myrowdist.EQ.0 ) THEN
3888 i = 1
3889 ELSE
3890 i = desca( imb_ ) + ( myrowdist - 1 ) * desca( mb_ ) + 1
3891 END IF
3892*
3893 ii = 1
3894 ib = min( max( 0, desca( m_ ) - i + 1 ), imba )
3895 DO 70 kk = 0, jb-1
3896 DO 60 ll = 0, ib-1
3897 IF( i+ll.LT.ia .OR. i+ll.GT.ia+m-1 .OR.
3898 $ j+kk.LT.ja .OR. j+kk.GT.ja+n-1 )
3899 $ CALL pzerrset( err, errmax,
3900 $ a( i+ll+(j+kk-1)*lda ),
3901 $ pa( ii+ll+(jj+kk-1)*ldpa ) )
3902 60 CONTINUE
3903 70 CONTINUE
3904 IF( rowrep ) THEN
3905 i = i + imba
3906 ELSE
3907 i = i + imba + ( nprow - 1 ) * desca( mb_ )
3908 END IF
3909*
3910 DO 100 ii = imba+1, mpall, desca( mb_ )
3911 ib = min( mpall-ii+1, desca( mb_ ) )
3912*
3913 DO 90 kk = 0, jb-1
3914 DO 80 ll = 0, ib-1
3915 IF( i+ll.LT.ia .OR. i+ll.GT.ia+m-1 .OR.
3916 $ j+kk.LT.ja .OR. j+kk.GT.ja+n-1 )
3917 $ CALL pzerrset( err, errmax,
3918 $ a( i+ll+(j+kk-1)*lda ),
3919 $ pa( ii+ll+(jj+kk-1)*ldpa ) )
3920 80 CONTINUE
3921 90 CONTINUE
3922*
3923 IF( rowrep ) THEN
3924 i = i + desca( mb_ )
3925 ELSE
3926 i = i + nprow * desca( mb_ )
3927 END IF
3928*
3929 100 CONTINUE
3930*
3931 jj = jj + jb
3932*
3933 END IF
3934*
3935 icurcol = mod( icurcol + 1, npcol )
3936* INSERT MODE
3937 110 CONTINUE
3938*
3939 CALL dgamx2d( ictxt, 'All', ' ', 1, 1, errmax, 1, kk, ll, -1,
3940 $ -1, -1 )
3941*
3942 IF( errmax.GT.zero .AND. errmax.LE.eps ) THEN
3943 info = 1
3944 ELSE IF( errmax.GT.eps ) THEN
3945 info = -1
3946 END IF
3947*
3948 RETURN
3949*
3950* End of PZCHKMOUT
3951*
integer function pb_numroc(n, i, inb, nb, proc, srcproc, nprocs)
Definition pblastst.f:2548
#define max(A, B)
Definition pcgemr.c:180
#define min(A, B)
Definition pcgemr.c:181
double precision function pdlamch(ictxt, cmach)
Definition pdblastst.f:6769
subroutine pzerrset(err, errmax, xtrue, x)
Definition pzblastst.f:2460
Here is the call graph for this function:
Here is the caller graph for this function: