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