1      SUBROUTINE PICHEKPAD( ICTXT, MESS, M, N, A, LDA, IPRE, IPOST,
2     $                     CHKVAL )
3*
4*  -- ScaLAPACK tools routine (version 1.7) --
5*     University of Tennessee, Knoxville, Oak Ridge National Laboratory,
6*     and University of California, Berkeley.
7*     May 1, 1997
8*
9*     .. Scalar Arguments ..
10      INTEGER            ICTXT, IPOST, IPRE, LDA, M, N
11      INTEGER            CHKVAL
12*     ..
13*     .. Array Arguments ..
14      CHARACTER          MESS*(*)
15      INTEGER            A( * )
16*     ..
17*
18*  Purpose
19*  =======
20*
21*  PICHEKPAD checks that the padding around a local array has not
22*  been overwritten since the call to PIFILLPAD.  3 types of errors
23*  are reported:
24*
25*  1) Overwrite in pre-guardzone. This indicates a memory overwrite has
26*  occurred in the first IPRE elements which form a buffer before the
27*  beginning of A.  Therefore, the error message:
28*     'Overwrite in  pre-guardzone: loc(  5) =         18.00000'
29*  tells you that the 5th element of the IPRE long buffer has been
30*  overwritten with the value 18, where it should still have the value
31*  of CHKVAL.
32*
33*  2) Overwrite in post-guardzone. This indicates a memory overwrite has
34*  occurred in the last IPOST elements which form a buffer after the end
35*  of A. Error reports are refered from the end of A.  Therefore,
36*     'Overwrite in post-guardzone: loc( 19) =         24.00000'
37*  tells you that the 19th element after the end of A was overwritten
38*  with the value 24, where it should still have the value of CHKVAL.
39*
40*  3) Overwrite in lda-m gap.  Tells you elements between M and LDA were
41*  overwritten.  So,
42*     'Overwrite in lda-m gap: A( 12,  3) =         22.00000'
43*  tells you that the element at the 12th row and 3rd column of A was
44*  overwritten with the value of 22, where it should still have the
45*  value of CHKVAL.
46*
47*  Arguments
48*  =========
49*
50*  ICTXT   (global input) INTEGER
51*          The BLACS context handle, indicating the global context of
52*          the operation. The context itself is global.
53*
54*  MESS    (local input) CHARACTER*(*)
55*          String containing a user-defined message.
56*
57*  M       (local input) INTEGER
58*          The number of rows in the local array A.
59*
60*  N       (input) INTEGER
61*          The number of columns in the local array A.
62*
63*  A       (local input) @(typec) array of dimension (LDA,N).
64*          A location IPRE elements in front of the array to be checked.
65*
66*  LDA     (local input) INTEGER
67*          The leading Dimension of the local array to be checked.
68*
69*  IPRE    (local input) INTEGER
70*          The size of the guard zone before the start of padded array.
71*
72*  IPOST   (local input) INTEGER
73*          The size of guard zone after the padded array.
74*
75*  CHKVAL  (local input) @(typec)
76*          The value the local array was padded with.
77*
78*  =====================================================================
79*
80*     .. Local Scalars ..
81      INTEGER            I, IAM, IDUMM, INFO, J, K, MYCOL, MYROW,
82     $                   NPCOL, NPROW
83*     ..
84*     .. External Subroutines ..
85      EXTERNAL           BLACS_GRIDINFO, IGAMX2D
86*     ..
87*     .. Executable Statements ..
88*
89*     Get grid parameters
90*
91      CALL BLACS_GRIDINFO( ICTXT, NPROW, NPCOL, MYROW, MYCOL )
92      IAM = MYROW*NPCOL + MYCOL
93      INFO = -1
94*
95*     Check buffer in front of A
96*
97      IF( IPRE.GT.0 ) THEN
98         DO 10 I = 1, IPRE
99            IF( A( I ).NE.CHKVAL ) THEN
100               WRITE( *, FMT = 9998 ) MYROW, MYCOL, MESS, ' pre', I,
101     $                                A( I )
102               INFO = IAM
103            END IF
104   10    CONTINUE
105      ELSE
106         WRITE( *, FMT = * ) 'WARNING no pre-guardzone in PICHEKPAD'
107      END IF
108*
109*     Check buffer after A
110*
111      IF( IPOST.GT.0 ) THEN
112         J = IPRE+LDA*N+1
113         DO 20 I = J, J+IPOST-1
114            IF( A( I ).NE.CHKVAL ) THEN
115               WRITE( *, FMT = 9998 ) MYROW, MYCOL, MESS, 'post',
116     $                                I-J+1, A( I )
117               INFO = IAM
118            END IF
119   20    CONTINUE
120      ELSE
121         WRITE( *, FMT = * )
122     $          'WARNING no post-guardzone buffer in PICHEKPAD'
123      END IF
124*
125*     Check all (LDA-M) gaps
126*
127      IF( LDA.GT.M ) THEN
128         K = IPRE + M + 1
129         DO 40 J = 1, N
130            DO 30 I = K, K + (LDA-M) - 1
131               IF( A( I ).NE.CHKVAL ) THEN
132                  WRITE( *, FMT = 9997 ) MYROW, MYCOL, MESS,
133     $               I-IPRE-LDA*(J-1), J, A( I )
134                  INFO = IAM
135               END IF
136   30       CONTINUE
137            K = K + LDA
138   40    CONTINUE
139      END IF
140*
141      CALL IGAMX2D( ICTXT, 'All', ' ', 1, 1, INFO, 1, IDUMM, IDUMM, -1,
142     $              0, 0 )
143      IF( IAM.EQ.0 .AND. INFO.GE.0 ) THEN
144         WRITE( *, FMT = 9999 ) INFO / NPCOL, MOD( INFO, NPCOL ), MESS
145      END IF
146*
147 9999 FORMAT( '{', I5, ',', I5, '}:  Memory overwrite in ', A )
148 9998 FORMAT( '{', I5, ',', I5, '}:  ', A, ' memory overwrite in ',
149     $        A4, '-guardzone: loc(', I3, ') = ', I8 )
150 9997 FORMAT( '{', I5, ',', I5, '}: ', A, ' memory overwrite in ',
151     $        'lda-m gap: loc(', I3, ',', I3, ') = ', I8 )
152*
153      RETURN
154*
155*     End of PICHEKPAD
156*
157      END
158