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

◆ pcchkvin()

subroutine pcchkvin ( real  errmax,
integer  n,
complex, dimension( * )  x,
complex, dimension( * )  px,
integer  ix,
integer  jx,
integer, dimension( * )  descx,
integer  incx,
integer  info 
)

Definition at line 2580 of file pcblastst.f.

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