ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
pschekpad.f
Go to the documentation of this file.
1  SUBROUTINE pschekpad( 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  REAL CHKVAL
12 * ..
13 * .. Array Arguments ..
14  CHARACTER MESS*(*)
15  REAL A( * )
16 * ..
17 *
18 * Purpose
19 * =======
20 *
21 * PSCHEKPAD checks that the padding around a local array has not
22 * been overwritten since the call to PSFILLPAD. 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) REAL 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) REAL
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 PSCHEKPAD'
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 PSCHEKPAD'
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, ') = ', g11.4 )
150  9997 FORMAT( '{', i5, ',', i5, '}: ', a, ' memory overwrite in ',
151  $ 'lda-m gap: loc(', i3, ',', i3, ') = ', g11.4 )
152 *
153  RETURN
154 *
155 * End of PSCHEKPAD
156 *
157  END
pschekpad
subroutine pschekpad(ICTXT, MESS, M, N, A, LDA, IPRE, IPOST, CHKVAL)
Definition: pschekpad.f:3