ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
pifillpad.f
Go to the documentation of this file.
1  SUBROUTINE pifillpad( ICTXT, M, N, A, LDA, IPRE, IPOST, CHKVAL )
2 *
3 * -- ScaLAPACK tools routine (version 1.7) --
4 * University of Tennessee, Knoxville, Oak Ridge National Laboratory,
5 * and University of California, Berkeley.
6 * May 1, 1997
7 *
8 * .. Scalar Arguments ..
9  INTEGER ICTXT, IPOST, IPRE, LDA, M, N
10  INTEGER CHKVAL
11 * ..
12 * .. Array Arguments ..
13  INTEGER A( * )
14 * ..
15 *
16 * Purpose
17 * =======
18 *
19 * PIFILLPAD surrounds a two dimensional local array with a guard-
20 * zone initialized to the value CHKVAL. The user may later call the
21 * routine PICHEKPAD to discover if the guardzone has been
22 * violated. There are three guardzones. The first is a buffer of size
23 * IPRE that is before the start of the array. The second is the buffer
24 * of size IPOST which is after the end of the array to be padded.
25 * Finally, there is a guard zone inside every column of the array to
26 * be padded, in the elements of A(M+1:LDA, J).
27 *
28 * Arguments
29 * =========
30 *
31 * ICTXT (global input) INTEGER
32 * The BLACS context handle, indicating the global context of
33 * the operation. The context itself is global.
34 *
35 * M (local input) INTEGER
36 * The number of rows in the local array.
37 *
38 * N (local input) INTEGER
39 * The number of columns in the local array.
40 *
41 * A (local input/local output) @(typec), array of
42 * dimension (LDA,N). A location IPRE elements in front of
43 * the matrix to be padded.
44 *
45 * LDA (local input) INTEGER
46 * The leading Dimension of the local array to be padded.
47 *
48 * IPRE (local input) INTEGER
49 * The size of the guard zone to put before the start of
50 * padded array.
51 *
52 * IPOST (local input) INTEGER
53 * The size of the guard zone to put after padded array.
54 *
55 * CHKVAL (local input) @(typec)
56 * The value to pad matrix with.
57 *
58 * =====================================================================
59 *
60 * .. Local Scalars ..
61  INTEGER I, J, K
62 * ..
63 * .. Executable Statements ..
64 *
65 * Put check buffer in front of A
66 *
67  IF( ipre.GT.0 ) THEN
68  DO 10 i = 1, ipre
69  a( i ) = chkval
70  10 CONTINUE
71  ELSE
72  WRITE( *, fmt = * ) 'WARNING no pre-guardzone in PIFILLPAD'
73  END IF
74 *
75 * Put check buffer in back of A
76 *
77  IF( ipost.GT.0 ) THEN
78  j = ipre+lda*n+1
79  DO 20 i = j, j+ipost-1
80  a( i ) = chkval
81  20 CONTINUE
82  ELSE
83  WRITE( *, fmt = * ) 'WARNING no post-guardzone in PIFILLPAD'
84  END IF
85 *
86 * Put check buffer in all (LDA-M) gaps
87 *
88  IF( lda.GT.m ) THEN
89  k = ipre + m + 1
90  DO 40 j = 1, n
91  DO 30 i = k, k + (lda-m) - 1
92  a( i ) = chkval
93  30 CONTINUE
94  k = k + lda
95  40 CONTINUE
96  END IF
97 *
98  RETURN
99 *
100 * End of PIFILLPAD
101 *
102  END
pifillpad
subroutine pifillpad(ICTXT, M, N, A, LDA, IPRE, IPOST, CHKVAL)
Definition: pifillpad.f:2