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

◆ pzchkmin()

subroutine pzchkmin ( double precision  errmax,
integer  m,
integer  n,
complex*16, dimension( * )  a,
complex*16, dimension( * )  pa,
integer  ia,
integer  ja,
integer, dimension( * )  desca,
integer  info 
)

Definition at line 3331 of file pzblastst.f.

3332*
3333* -- PBLAS test routine (version 2.0) --
3334* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
3335* and University of California, Berkeley.
3336* April 1, 1998
3337*
3338* .. Scalar Arguments ..
3339 INTEGER IA, INFO, JA, M, N
3340 DOUBLE PRECISION ERRMAX
3341* ..
3342* .. Array Arguments ..
3343 INTEGER DESCA( * )
3344 COMPLEX*16 PA( * ), A( * )
3345* ..
3346*
3347* Purpose
3348* =======
3349*
3350* PZCHKMIN checks that the submatrix sub( PA ) remained unchanged. The
3351* local array entries are compared element by element, and their dif-
3352* ference is tested against 0.0 as well as the epsilon machine. Notice
3353* that this difference should be numerically exactly the zero machine,
3354* but because of the possible fluctuation of some of the data we flag-
3355* ged differently a difference less than twice the epsilon machine. The
3356* largest error is also returned.
3357*
3358* Notes
3359* =====
3360*
3361* A description vector is associated with each 2D block-cyclicly dis-
3362* tributed matrix. This vector stores the information required to
3363* establish the mapping between a matrix entry and its corresponding
3364* process and memory location.
3365*
3366* In the following comments, the character _ should be read as
3367* "of the distributed matrix". Let A be a generic term for any 2D
3368* block cyclicly distributed matrix. Its description vector is DESCA:
3369*
3370* NOTATION STORED IN EXPLANATION
3371* ---------------- --------------- ------------------------------------
3372* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
3373* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
3374* the NPROW x NPCOL BLACS process grid
3375* A is distributed over. The context
3376* itself is global, but the handle
3377* (the integer value) may vary.
3378* M_A (global) DESCA( M_ ) The number of rows in the distribu-
3379* ted matrix A, M_A >= 0.
3380* N_A (global) DESCA( N_ ) The number of columns in the distri-
3381* buted matrix A, N_A >= 0.
3382* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
3383* block of the matrix A, IMB_A > 0.
3384* INB_A (global) DESCA( INB_ ) The number of columns of the upper
3385* left block of the matrix A,
3386* INB_A > 0.
3387* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
3388* bute the last M_A-IMB_A rows of A,
3389* MB_A > 0.
3390* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
3391* bute the last N_A-INB_A columns of
3392* A, NB_A > 0.
3393* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
3394* row of the matrix A is distributed,
3395* NPROW > RSRC_A >= 0.
3396* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
3397* first column of A is distributed.
3398* NPCOL > CSRC_A >= 0.
3399* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
3400* array storing the local blocks of
3401* the distributed matrix A,
3402* IF( Lc( 1, N_A ) > 0 )
3403* LLD_A >= MAX( 1, Lr( 1, M_A ) )
3404* ELSE
3405* LLD_A >= 1.
3406*
3407* Let K be the number of rows of a matrix A starting at the global in-
3408* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
3409* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
3410* receive if these K rows were distributed over NPROW processes. If K
3411* is the number of columns of a matrix A starting at the global index
3412* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
3413* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
3414* these K columns were distributed over NPCOL processes.
3415*
3416* The values of Lr() and Lc() may be determined via a call to the func-
3417* tion PB_NUMROC:
3418* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
3419* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
3420*
3421* Arguments
3422* =========
3423*
3424* ERRMAX (global output) DOUBLE PRECISION
3425* On exit, ERRMAX specifies the largest absolute element-wise
3426* difference between sub( A ) and sub( PA ).
3427*
3428* M (global input) INTEGER
3429* On entry, M specifies the number of rows of the submatrix
3430* operand sub( A ). M must be at least zero.
3431*
3432* N (global input) INTEGER
3433* On entry, N specifies the number of columns of the submatrix
3434* operand sub( A ). N must be at least zero.
3435*
3436* A (local input) COMPLEX*16 array
3437* On entry, A is an array of dimension (DESCA( M_ ),*). This
3438* array contains a local copy of the initial entire matrix PA.
3439*
3440* PA (local input) COMPLEX*16 array
3441* On entry, PA is an array of dimension (DESCA( LLD_ ),*). This
3442* array contains the local entries of the matrix PA.
3443*
3444* IA (global input) INTEGER
3445* On entry, IA specifies A's global row index, which points to
3446* the beginning of the submatrix sub( A ).
3447*
3448* JA (global input) INTEGER
3449* On entry, JA specifies A's global column index, which points
3450* to the beginning of the submatrix sub( A ).
3451*
3452* DESCA (global and local input) INTEGER array
3453* On entry, DESCA is an integer array of dimension DLEN_. This
3454* is the array descriptor for the matrix A.
3455*
3456* INFO (global output) INTEGER
3457* On exit, if INFO = 0, no error has been found,
3458* If INFO > 0, the maximum abolute error found is in (0,eps],
3459* If INFO < 0, the maximum abolute error found is in (eps,+oo).
3460*
3461* -- Written on April 1, 1998 by
3462* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
3463*
3464* =====================================================================
3465*
3466* .. Parameters ..
3467 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
3468 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
3469 $ RSRC_
3470 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
3471 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
3472 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
3473 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
3474 DOUBLE PRECISION ZERO
3475 parameter( zero = 0.0d+0 )
3476* ..
3477* .. Local Scalars ..
3478 LOGICAL COLREP, ROWREP
3479 INTEGER H, I, IACOL, IAROW, IB, ICTXT, ICURCOL,
3480 $ ICURROW, II, IIA, IN, J, JB, JJ, JJA, JN, K,
3481 $ KK, LDA, LDPA, LL, MYCOL, MYROW, NPCOL, NPROW
3482 DOUBLE PRECISION ERR, EPS
3483* ..
3484* .. External Subroutines ..
3485 EXTERNAL blacs_gridinfo, dgamx2d, pb_infog2l, pzerrset
3486* ..
3487* .. External Functions ..
3488 DOUBLE PRECISION PDLAMCH
3489 EXTERNAL pdlamch
3490* ..
3491* .. Intrinsic Functions ..
3492 INTRINSIC abs, dble, dimag, max, min, mod
3493* ..
3494* .. Executable Statements ..
3495*
3496 info = 0
3497 errmax = zero
3498*
3499* Quick return if posssible
3500*
3501 IF( ( m.EQ.0 ).OR.( n.EQ.0 ) )
3502 $ RETURN
3503*
3504* Start the operations
3505*
3506 ictxt = desca( ctxt_ )
3507 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
3508*
3509 eps = pdlamch( ictxt, 'eps' )
3510*
3511 CALL pb_infog2l( ia, ja, desca, nprow, npcol, myrow, mycol, iia,
3512 $ jja, iarow, iacol )
3513*
3514 ii = iia
3515 jj = jja
3516 lda = desca( m_ )
3517 ldpa = desca( lld_ )
3518 icurrow = iarow
3519 icurcol = iacol
3520 rowrep = ( iarow.EQ.-1 )
3521 colrep = ( iacol.EQ.-1 )
3522*
3523* Handle the first block of column separately
3524*
3525 jb = desca( inb_ ) - ja + 1
3526 IF( jb.LE.0 )
3527 $ jb = ( ( -jb ) / desca( nb_ ) + 1 ) * desca( nb_ ) + jb
3528 jb = min( jb, n )
3529 jn = ja + jb - 1
3530*
3531 IF( mycol.EQ.icurcol .OR. colrep ) THEN
3532*
3533 DO 40 h = 0, jb-1
3534 ib = desca( imb_ ) - ia + 1
3535 IF( ib.LE.0 )
3536 $ ib = ( ( -ib ) / desca( mb_ ) + 1 ) * desca( mb_ ) + ib
3537 ib = min( ib, m )
3538 in = ia + ib - 1
3539 IF( myrow.EQ.icurrow .OR. rowrep ) THEN
3540 DO 10 k = 0, ib-1
3541 CALL pzerrset( err, errmax, a( ia+k+(ja+h-1)*lda ),
3542 $ pa( ii+k+(jj+h-1)*ldpa ) )
3543 10 CONTINUE
3544 ii = ii + ib
3545 END IF
3546 icurrow = mod( icurrow+1, nprow )
3547*
3548* Loop over remaining block of rows
3549*
3550 DO 30 i = in+1, ia+m-1, desca( mb_ )
3551 ib = min( desca( mb_ ), ia+m-i )
3552 IF( myrow.EQ.icurrow .OR. rowrep ) THEN
3553 DO 20 k = 0, ib-1
3554 CALL pzerrset( err, errmax, a( i+k+(ja+h-1)*lda ),
3555 $ pa( ii+k+(jj+h-1)*ldpa ) )
3556 20 CONTINUE
3557 ii = ii + ib
3558 END IF
3559 icurrow = mod( icurrow+1, nprow )
3560 30 CONTINUE
3561*
3562 ii = iia
3563 icurrow = iarow
3564 40 CONTINUE
3565*
3566 jj = jj + jb
3567*
3568 END IF
3569*
3570 icurcol = mod( icurcol+1, npcol )
3571*
3572* Loop over remaining column blocks
3573*
3574 DO 90 j = jn+1, ja+n-1, desca( nb_ )
3575 jb = min( desca( nb_ ), ja+n-j )
3576 IF( mycol.EQ.icurcol .OR. colrep ) THEN
3577 DO 80 h = 0, jb-1
3578 ib = desca( imb_ ) - ia + 1
3579 IF( ib.LE.0 )
3580 $ ib = ( ( -ib ) / desca( mb_ ) + 1 )*desca( mb_ ) + ib
3581 ib = min( ib, m )
3582 in = ia + ib - 1
3583 IF( myrow.EQ.icurrow .OR. rowrep ) THEN
3584 DO 50 k = 0, ib-1
3585 CALL pzerrset( err, errmax, a( ia+k+(j+h-1)*lda ),
3586 $ pa( ii+k+(jj+h-1)*ldpa ) )
3587 50 CONTINUE
3588 ii = ii + ib
3589 END IF
3590 icurrow = mod( icurrow+1, nprow )
3591*
3592* Loop over remaining block of rows
3593*
3594 DO 70 i = in+1, ia+m-1, desca( mb_ )
3595 ib = min( desca( mb_ ), ia+m-i )
3596 IF( myrow.EQ.icurrow .OR. rowrep ) THEN
3597 DO 60 k = 0, ib-1
3598 CALL pzerrset( err, errmax,
3599 $ a( i+k+(j+h-1)*lda ),
3600 $ pa( ii+k+(jj+h-1)*ldpa ) )
3601 60 CONTINUE
3602 ii = ii + ib
3603 END IF
3604 icurrow = mod( icurrow+1, nprow )
3605 70 CONTINUE
3606*
3607 ii = iia
3608 icurrow = iarow
3609 80 CONTINUE
3610*
3611 jj = jj + jb
3612 END IF
3613*
3614 icurcol = mod( icurcol+1, npcol )
3615*
3616 90 CONTINUE
3617*
3618 CALL dgamx2d( ictxt, 'All', ' ', 1, 1, errmax, 1, kk, ll, -1,
3619 $ -1, -1 )
3620*
3621 IF( errmax.GT.zero .AND. errmax.LE.eps ) THEN
3622 info = 1
3623 ELSE IF( errmax.GT.eps ) THEN
3624 info = -1
3625 END IF
3626*
3627 RETURN
3628*
3629* End of PZCHKMIN
3630*
subroutine pb_infog2l(i, j, desc, nprow, npcol, myrow, mycol, ii, jj, prow, pcol)
Definition pblastst.f:1673
#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: