SCALAPACK 2.2.2
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
pcchekpad.f
Go to the documentation of this file.
1 SUBROUTINE pcchekpad( 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 COMPLEX CHKVAL
12* ..
13* .. Array Arguments ..
14 CHARACTER MESS*(*)
15 COMPLEX A( * )
16* ..
17*
18* Purpose
19* =======
20*
21* PCCHEKPAD checks that the padding around a local array has not
22* been overwritten since the call to PCFILLPAD. 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) COMPLEX 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) COMPLEX
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* .. Intrinsic Functions ..
88 INTRINSIC real, aimag
89* ..
90* .. Executable Statements ..
91*
92* Get grid parameters
93*
94 CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
95 iam = myrow*npcol + mycol
96 info = -1
97*
98* Check buffer in front of A
99*
100 IF( ipre.GT.0 ) THEN
101 DO 10 i = 1, ipre
102 IF( a( i ).NE.chkval ) THEN
103 WRITE( *, fmt = 9998 ) myrow, mycol, mess, ' pre', i,
104 $ real( a( i ) ), aimag( a( i ) )
105 info = iam
106 END IF
107 10 CONTINUE
108 ELSE
109 WRITE( *, fmt = * ) 'WARNING no pre-guardzone in PCCHEKPAD'
110 END IF
111*
112* Check buffer after A
113*
114 IF( ipost.GT.0 ) THEN
115 j = ipre+lda*n+1
116 DO 20 i = j, j+ipost-1
117 IF( a( i ).NE.chkval ) THEN
118 WRITE( *, fmt = 9998 ) myrow, mycol, mess, 'post',
119 $ i-j+1, real( a( i ) ),
120 $ aimag( a( i ) )
121 info = iam
122 END IF
123 20 CONTINUE
124 ELSE
125 WRITE( *, fmt = * )
126 $ 'WARNING no post-guardzone buffer in PCCHEKPAD'
127 END IF
128*
129* Check all (LDA-M) gaps
130*
131 IF( lda.GT.m ) THEN
132 k = ipre + m + 1
133 DO 40 j = 1, n
134 DO 30 i = k, k + (lda-m) - 1
135 IF( a( i ).NE.chkval ) THEN
136 WRITE( *, fmt = 9997 ) myrow, mycol, mess,
137 $ i-ipre-lda*(j-1), j, real( a( i ) ),
138 $ aimag( a( i ) )
139 info = iam
140 END IF
141 30 CONTINUE
142 k = k + lda
143 40 CONTINUE
144 END IF
145*
146 CALL igamx2d( ictxt, 'All', ' ', 1, 1, info, 1, idumm, idumm, -1,
147 $ 0, 0 )
148 IF( iam.EQ.0 .AND. info.GE.0 ) THEN
149 WRITE( *, fmt = 9999 ) info / npcol, mod( info, npcol ), mess
150 END IF
151*
152 9999 FORMAT( '{', i5, ',', i5, '}: Memory overwrite in ', a )
153 9998 FORMAT( '{', i5, ',', i5, '}: ', a, ' memory overwrite in ',
154 $ a4, '-guardzone: loc(', i3, ') = ', g11.4, '+ i*',
155 $ g11.4 )
156 9997 FORMAT( '{', i5, ',', i5, '}: ', a, ' memory overwrite in ',
157 $ 'lda-m gap: loc(', i3, ',', i3, ') = ', g11.4,
158 $ '+ i*', g11.4 )
159*
160 RETURN
161*
162* End of PCCHEKPAD
163*
164 END
subroutine pcchekpad(ictxt, mess, m, n, a, lda, ipre, ipost, chkval)
Definition pcchekpad.f:3