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

◆ pdchkvin()

subroutine pdchkvin ( double precision  errmax,
integer  n,
double precision, dimension( * )  x,
double precision, dimension( * )  px,
integer  ix,
integer  jx,
integer, dimension( * )  descx,
integer  incx,
integer  info 
)

Definition at line 2574 of file pdblastst.f.

2576*
2577* -- PBLAS test routine (version 2.0) --
2578* University of Tennessee, Knoxville, Oak Ridge National Laboratory,
2579* and University of California, Berkeley.
2580* April 1, 1998
2581*
2582* .. Scalar Arguments ..
2583 INTEGER INCX, INFO, IX, JX, N
2584 DOUBLE PRECISION ERRMAX
2585* ..
2586* .. Array Arguments ..
2587 INTEGER DESCX( * )
2588 DOUBLE PRECISION PX( * ), X( * )
2589* ..
2590*
2591* Purpose
2592* =======
2593*
2594* PDCHKVIN checks that the submatrix sub( PX ) remained unchanged. The
2595* local array entries are compared element by element, and their dif-
2596* ference is tested against 0.0 as well as the epsilon machine. Notice
2597* that this difference should be numerically exactly the zero machine,
2598* but because of the possible fluctuation of some of the data we flag-
2599* ged differently a difference less than twice the epsilon machine. The
2600* largest error is also returned.
2601*
2602* Notes
2603* =====
2604*
2605* A description vector is associated with each 2D block-cyclicly dis-
2606* tributed matrix. This vector stores the information required to
2607* establish the mapping between a matrix entry and its corresponding
2608* process and memory location.
2609*
2610* In the following comments, the character _ should be read as
2611* "of the distributed matrix". Let A be a generic term for any 2D
2612* block cyclicly distributed matrix. Its description vector is DESCA:
2613*
2614* NOTATION STORED IN EXPLANATION
2615* ---------------- --------------- ------------------------------------
2616* DTYPE_A (global) DESCA( DTYPE_ ) The descriptor type.
2617* CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
2618* the NPROW x NPCOL BLACS process grid
2619* A is distributed over. The context
2620* itself is global, but the handle
2621* (the integer value) may vary.
2622* M_A (global) DESCA( M_ ) The number of rows in the distribu-
2623* ted matrix A, M_A >= 0.
2624* N_A (global) DESCA( N_ ) The number of columns in the distri-
2625* buted matrix A, N_A >= 0.
2626* IMB_A (global) DESCA( IMB_ ) The number of rows of the upper left
2627* block of the matrix A, IMB_A > 0.
2628* INB_A (global) DESCA( INB_ ) The number of columns of the upper
2629* left block of the matrix A,
2630* INB_A > 0.
2631* MB_A (global) DESCA( MB_ ) The blocking factor used to distri-
2632* bute the last M_A-IMB_A rows of A,
2633* MB_A > 0.
2634* NB_A (global) DESCA( NB_ ) The blocking factor used to distri-
2635* bute the last N_A-INB_A columns of
2636* A, NB_A > 0.
2637* RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
2638* row of the matrix A is distributed,
2639* NPROW > RSRC_A >= 0.
2640* CSRC_A (global) DESCA( CSRC_ ) The process column over which the
2641* first column of A is distributed.
2642* NPCOL > CSRC_A >= 0.
2643* LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
2644* array storing the local blocks of
2645* the distributed matrix A,
2646* IF( Lc( 1, N_A ) > 0 )
2647* LLD_A >= MAX( 1, Lr( 1, M_A ) )
2648* ELSE
2649* LLD_A >= 1.
2650*
2651* Let K be the number of rows of a matrix A starting at the global in-
2652* dex IA,i.e, A( IA:IA+K-1, : ). Lr( IA, K ) denotes the number of rows
2653* that the process of row coordinate MYROW ( 0 <= MYROW < NPROW ) would
2654* receive if these K rows were distributed over NPROW processes. If K
2655* is the number of columns of a matrix A starting at the global index
2656* JA, i.e, A( :, JA:JA+K-1, : ), Lc( JA, K ) denotes the number of co-
2657* lumns that the process MYCOL ( 0 <= MYCOL < NPCOL ) would receive if
2658* these K columns were distributed over NPCOL processes.
2659*
2660* The values of Lr() and Lc() may be determined via a call to the func-
2661* tion PB_NUMROC:
2662* Lr( IA, K ) = PB_NUMROC( K, IA, IMB_A, MB_A, MYROW, RSRC_A, NPROW )
2663* Lc( JA, K ) = PB_NUMROC( K, JA, INB_A, NB_A, MYCOL, CSRC_A, NPCOL )
2664*
2665* Arguments
2666* =========
2667*
2668* ERRMAX (global output) DOUBLE PRECISION
2669* On exit, ERRMAX specifies the largest absolute element-wise
2670* difference between sub( X ) and sub( PX ).
2671*
2672* N (global input) INTEGER
2673* On entry, N specifies the length of the subvector operand
2674* sub( X ). N must be at least zero.
2675*
2676* X (local input) DOUBLE PRECISION array
2677* On entry, X is an array of dimension (DESCX( M_ ),*). This
2678* array contains a local copy of the initial entire matrix PX.
2679*
2680* PX (local input) DOUBLE PRECISION array
2681* On entry, PX is an array of dimension (DESCX( LLD_ ),*). This
2682* array contains the local entries of the matrix PX.
2683*
2684* IX (global input) INTEGER
2685* On entry, IX specifies X's global row index, which points to
2686* the beginning of the submatrix sub( X ).
2687*
2688* JX (global input) INTEGER
2689* On entry, JX specifies X's global column index, which points
2690* to the beginning of the submatrix sub( X ).
2691*
2692* DESCX (global and local input) INTEGER array
2693* On entry, DESCX is an integer array of dimension DLEN_. This
2694* is the array descriptor for the matrix X.
2695*
2696* INCX (global input) INTEGER
2697* On entry, INCX specifies the global increment for the
2698* elements of X. Only two values of INCX are supported in
2699* this version, namely 1 and M_X. INCX must not be zero.
2700*
2701* INFO (global output) INTEGER
2702* On exit, if INFO = 0, no error has been found,
2703* If INFO > 0, the maximum abolute error found is in (0,eps],
2704* If INFO < 0, the maximum abolute error found is in (eps,+oo).
2705*
2706* -- Written on April 1, 1998 by
2707* Antoine Petitet, University of Tennessee, Knoxville 37996, USA.
2708*
2709* =====================================================================
2710*
2711* .. Parameters ..
2712 INTEGER BLOCK_CYCLIC_2D_INB, CSRC_, CTXT_, DLEN_,
2713 $ DTYPE_, IMB_, INB_, LLD_, MB_, M_, NB_, N_,
2714 $ RSRC_
2715 parameter( block_cyclic_2d_inb = 2, dlen_ = 11,
2716 $ dtype_ = 1, ctxt_ = 2, m_ = 3, n_ = 4,
2717 $ imb_ = 5, inb_ = 6, mb_ = 7, nb_ = 8,
2718 $ rsrc_ = 9, csrc_ = 10, lld_ = 11 )
2719 DOUBLE PRECISION ZERO
2720 parameter( zero = 0.0d+0 )
2721* ..
2722* .. Local Scalars ..
2723 LOGICAL COLREP, ROWREP
2724 INTEGER I, IB, ICTXT, ICURCOL, ICURROW, IIX, IN, IXCOL,
2725 $ IXROW, J, JB, JJX, JN, KK, LDPX, LDX, LL,
2726 $ MYCOL, MYROW, NPCOL, NPROW
2727 DOUBLE PRECISION ERR, EPS
2728* ..
2729* .. External Subroutines ..
2730 EXTERNAL blacs_gridinfo, dgamx2d, pb_infog2l, pderrset
2731* ..
2732* .. External Functions ..
2733 DOUBLE PRECISION PDLAMCH
2734 EXTERNAL pdlamch
2735* ..
2736* .. Intrinsic Functions ..
2737 INTRINSIC abs, max, min, mod
2738* ..
2739* .. Executable Statements ..
2740*
2741 info = 0
2742 errmax = zero
2743*
2744* Quick return if possible
2745*
2746 IF( n.LE.0 )
2747 $ RETURN
2748*
2749 ictxt = descx( ctxt_ )
2750 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
2751*
2752 eps = pdlamch( ictxt, 'eps' )
2753*
2754 CALL pb_infog2l( ix, jx, descx, nprow, npcol, myrow, mycol, iix,
2755 $ jjx, ixrow, ixcol )
2756*
2757 ldx = descx( m_ )
2758 ldpx = descx( lld_ )
2759 rowrep = ( ixrow.EQ.-1 )
2760 colrep = ( ixcol.EQ.-1 )
2761*
2762 IF( n.EQ.1 ) THEN
2763*
2764 IF( ( myrow.EQ.ixrow .OR. rowrep ) .AND.
2765 $ ( mycol.EQ.ixcol .OR. colrep ) )
2766 $ CALL pderrset( err, errmax, x( ix+(jx-1)*ldx ),
2767 $ px( iix+(jjx-1)*ldpx ) )
2768*
2769 ELSE IF( incx.EQ.descx( m_ ) ) THEN
2770*
2771* sub( X ) is a row vector
2772*
2773 jb = descx( inb_ ) - jx + 1
2774 IF( jb.LE.0 )
2775 $ jb = ( ( -jb ) / descx( nb_ ) + 1 ) * descx( nb_ ) + jb
2776 jb = min( jb, n )
2777 jn = jx + jb - 1
2778*
2779 IF( myrow.EQ.ixrow .OR. rowrep ) THEN
2780*
2781 icurcol = ixcol
2782 IF( mycol.EQ.icurcol .OR. colrep ) THEN
2783 DO 10 j = jx, jn
2784 CALL pderrset( err, errmax, x( ix+(j-1)*ldx ),
2785 $ px( iix+(jjx-1)*ldpx ) )
2786 jjx = jjx + 1
2787 10 CONTINUE
2788 END IF
2789 icurcol = mod( icurcol+1, npcol )
2790*
2791 DO 30 j = jn+1, jx+n-1, descx( nb_ )
2792 jb = min( jx+n-j, descx( nb_ ) )
2793*
2794 IF( mycol.EQ.icurcol .OR. colrep ) THEN
2795*
2796 DO 20 kk = 0, jb-1
2797 CALL pderrset( err, errmax, x( ix+(j+kk-1)*ldx ),
2798 $ px( iix+(jjx+kk-1)*ldpx ) )
2799 20 CONTINUE
2800*
2801 jjx = jjx + jb
2802*
2803 END IF
2804*
2805 icurcol = mod( icurcol+1, npcol )
2806*
2807 30 CONTINUE
2808*
2809 END IF
2810*
2811 ELSE
2812*
2813* sub( X ) is a column vector
2814*
2815 ib = descx( imb_ ) - ix + 1
2816 IF( ib.LE.0 )
2817 $ ib = ( ( -ib ) / descx( mb_ ) + 1 ) * descx( mb_ ) + ib
2818 ib = min( ib, n )
2819 in = ix + ib - 1
2820*
2821 IF( mycol.EQ.ixcol .OR. colrep ) THEN
2822*
2823 icurrow = ixrow
2824 IF( myrow.EQ.icurrow .OR. rowrep ) THEN
2825 DO 40 i = ix, in
2826 CALL pderrset( err, errmax, x( i+(jx-1)*ldx ),
2827 $ px( iix+(jjx-1)*ldpx ) )
2828 iix = iix + 1
2829 40 CONTINUE
2830 END IF
2831 icurrow = mod( icurrow+1, nprow )
2832*
2833 DO 60 i = in+1, ix+n-1, descx( mb_ )
2834 ib = min( ix+n-i, descx( mb_ ) )
2835*
2836 IF( myrow.EQ.icurrow .OR. rowrep ) THEN
2837*
2838 DO 50 kk = 0, ib-1
2839 CALL pderrset( err, errmax, x( i+kk+(jx-1)*ldx ),
2840 $ px( iix+kk+(jjx-1)*ldpx ) )
2841 50 CONTINUE
2842*
2843 iix = iix + ib
2844*
2845 END IF
2846*
2847 icurrow = mod( icurrow+1, nprow )
2848*
2849 60 CONTINUE
2850*
2851 END IF
2852*
2853 END IF
2854*
2855 CALL dgamx2d( ictxt, 'All', ' ', 1, 1, errmax, 1, kk, ll, -1,
2856 $ -1, -1 )
2857*
2858 IF( errmax.GT.zero .AND. errmax.LE.eps ) THEN
2859 info = 1
2860 ELSE IF( errmax.GT.eps ) THEN
2861 info = -1
2862 END IF
2863*
2864 RETURN
2865*
2866* End of PDCHKVIN
2867*
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
subroutine pderrset(err, errmax, xtrue, x)
Definition pdblastst.f:2456
double precision function pdlamch(ictxt, cmach)
Definition pdblastst.f:6769
Here is the call graph for this function:
Here is the caller graph for this function: