ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
pdbmatgen.f
Go to the documentation of this file.
1  SUBROUTINE pdbmatgen( ICTXT, AFORM, AFORM2, BWL, BWU, N,
2  $ MB, NB, A,
3  $ LDA, IAROW, IACOL, ISEED,
4  $ MYROW, MYCOL, NPROW, NPCOL )
5 *
6 *
7 *
8 * -- ScaLAPACK routine (version 1.7) --
9 * University of Tennessee, Knoxville, Oak Ridge National Laboratory,
10 * and University of California, Berkeley.
11 * November 15, 1997
12 *
13 * .. Scalar Arguments ..
14 * .. Scalar Arguments ..
15  CHARACTER*1 AFORM, AFORM2
16  INTEGER IACOL, IAROW, ICTXT,
17  $ ISEED, LDA, MB, MYCOL, MYROW, N,
18  $ nb, npcol, nprow, bwl, bwu
19 * ..
20 * .. Array Arguments ..
21  DOUBLE PRECISION A( LDA, * )
22 * ..
23 *
24 * Purpose
25 * =======
26 *
27 * PDBMATGEN : Parallel Real Double precision Band MATrix GENerator.
28 * (Re)Generate a distributed Band matrix A (or sub-matrix of A).
29 *
30 * Arguments
31 * =========
32 *
33 * ICTXT (global input) INTEGER
34 * The BLACS context handle, indicating the global context of
35 * the operation. The context itself is global.
36 *
37 * AFORM (global input) CHARACTER*1
38 * if AFORM = 'L' : A is returned as a symmetric lower
39 * triangular matrix, and is diagonally dominant.
40 * if AFORM = 'U' : A is returned as a symmetric upper
41 * triangular matrix, and is diagonally dominant.
42 * if AFORM = 'G' : A is returned as a general matrix.
43 * if AFORM = 'T' : A is returned as a general matrix in
44 * tridiagonal-compatible form.
45 *
46 * AFORM2 (global input) CHARACTER*1
47 * if the matrix is general:
48 * if AFORM2 = 'D' : A is returned diagonally dominant.
49 * if AFORM2 != 'D' : A is not returned diagonally dominant.
50 * if the matrix is symmetric or hermitian:
51 * if AFORM2 = 'T' : A is returned in tridiagonally-compatible
52 * form (a transpose form).
53 * if AFORM2 != 'T' : A is returned in banded-compatible form.
54 *
55 * M (global input) INTEGER
56 * The number of nonzero rows in the generated distributed
57 * band matrix.
58 *
59 * N (global input) INTEGER
60 * The number of columns in the generated distributed
61 * matrix.
62 *
63 * MB (global input) INTEGER
64 * The row blocking factor of the distributed matrix A.
65 *
66 * NB (global input) INTEGER
67 * The column blocking factor of the distributed matrix A.
68 *
69 * A (local output) DOUBLE PRECISION, pointer into the local
70 * memory to an array of dimension ( LDA, * ) containing the
71 * local pieces of the distributed matrix.
72 *
73 * LDA (local input) INTEGER
74 * The leading dimension of the array containing the local
75 * pieces of the distributed matrix A.
76 *
77 * IAROW (global input) INTEGER
78 * The row processor coordinate which holds the first block
79 * of the distributed matrix A.
80 * A( DIAG_INDEX, I ) = A( DIAG_INDEX, I ) + BWL+BWU
81 *
82 * IACOL (global input) INTEGER
83 * The column processor coordinate which holds the first
84 * block of the distributed matrix A.
85 *
86 * ISEED (global input) INTEGER
87 * The seed number to generate the distributed matrix A.
88 *
89 * MYROW (local input) INTEGER
90 * The row process coordinate of the calling process.
91 *
92 * MYCOL (local input) INTEGER
93 * The column process coordinate of the calling process.
94 *
95 * NPROW (global input) INTEGER
96 * The number of process rows in the grid.
97 *
98 * NPCOL (global input) INTEGER
99 * The number of process columns in the grid.
100 *
101 * Notes
102 * =====
103 *
104 * This code is a simple wrapper around PDMATGEN, for band matrices.
105 *
106 * =====================================================================
107 *
108 * Code Developer: Andrew J. Cleary, University of Tennessee.
109 * Current address: Lawrence Livermore National Labs.
110 * This version released: August, 2001.
111 *
112 * =====================================================================
113 *
114 * ..
115 * .. Parameters ..
116  DOUBLE PRECISION ONE, ZERO
117  PARAMETER ( ONE = 1.0d+0 )
118  parameter( zero = 0.0d+0 )
119 * ..
120 * .. Local Scalars ..
121  INTEGER DIAG_INDEX, I, J, M_MATGEN, NQ, N_MATGEN,
122  $ START_INDEX
123 * ..
124 * .. External Subroutines ..
125  EXTERNAL pdmatgen
126 * ..
127 * .. External Functions ..
128  LOGICAL LSAME
129  INTEGER ICEIL, NUMROC
130  EXTERNAL ICEIL, NUMROC, LSAME
131 * ..
132 * .. Executable Statements ..
133 *
134 *
135  IF( lsame( aform, 'L' ).OR.lsame( aform, 'U' ) ) THEN
136  m_matgen = bwl + 1
137  n_matgen = n
138  start_index = 1
139  IF( lsame( aform, 'L' ) ) THEN
140  diag_index = 1
141  ELSE
142  diag_index = bwl + 1
143  ENDIF
144  ELSE
145  m_matgen = bwl + bwu + 1
146  n_matgen = n
147  diag_index = bwu + 1
148  start_index = 1
149  ENDIF
150 *
151  nq = numroc( n, nb, mycol, iacol, npcol )
152 *
153 *
154 * Generate a random matrix initially
155 *
156  IF( lsame( aform, 'T' ) .OR.
157  $ ( lsame( aform2, 'T' ) ) ) THEN
158 *
159  CALL pdmatgen( ictxt, 'T', 'N',
160  $ n_matgen, m_matgen,
161  $ nb, m_matgen, a( start_index, 1 ),
162  $ lda, iarow, iacol,
163  $ iseed, 0, nq, 0, m_matgen,
164  $ mycol, myrow, npcol, nprow )
165 *
166  ELSE
167 *
168  CALL pdmatgen( ictxt, 'N', 'N',
169  $ m_matgen, n_matgen,
170  $ m_matgen, nb, a( start_index, 1 ),
171  $ lda, iarow, iacol,
172  $ iseed, 0, m_matgen, 0, nq,
173  $ myrow, mycol, nprow, npcol )
174 *
175 * Zero out padding at tops of columns
176 *
177  DO 1000 j=1,nb
178 *
179  DO 2000 i=1, lda-m_matgen
180 *
181 * Indexing goes negative; BMATGEN assumes that space
182 * has been preallocated above the first column as it
183 * has to be if the matrix is to be input to
184 * Scalapack's band solvers.
185 *
186  a( i-lda+m_matgen, j ) = zero
187 *
188  2000 CONTINUE
189 *
190  1000 CONTINUE
191 *
192  ENDIF
193 *
194  IF( lsame( aform2, 'D' ).OR.
195  $ ( lsame( aform, 'L' ).OR.lsame( aform, 'U' ) ) ) THEN
196 *
197 * Loop over diagonal elements stored on this processor.
198 *
199 *
200  DO 330 i=1, nq
201  IF( lsame( aform, 'T' ) .OR.
202  $ ( lsame( aform2, 'T' ) ) ) THEN
203  IF( nprow .EQ. 1 ) THEN
204  a( i, diag_index ) = a( i, diag_index )
205  $ + dble( bwl+bwu+1 )
206  ENDIF
207  ELSE
208  IF( nprow .EQ. 1 ) THEN
209  a( diag_index, i ) = a( diag_index, i )
210  $ + dble( bwl+bwu+1 )
211  ENDIF
212  END IF
213  330 CONTINUE
214 *
215 *
216  ELSE
217 *
218 * Must add elements to keep condition of matrix in check
219 *
220  DO 380 i=1, nq
221 *
222  IF( nprow .EQ. 1 ) THEN
223 *
224  IF( mod(i+mycol*nb,2) .EQ. 1 ) THEN
225  a( diag_index+1, i ) = a( diag_index+1, i )
226  $ + dble( bwl+bwu+1 )
227 *
228  ELSE
229 *
230  a( diag_index-1, i ) = a( diag_index-1, i )
231  $ + dble( bwl+bwu+1 )
232  ENDIF
233 *
234  ENDIF
235 *
236  380 CONTINUE
237 *
238  END IF
239 *
240  RETURN
241 *
242 * End of PDBMATGEN
243 *
244  END
pdmatgen
subroutine pdmatgen(ICTXT, AFORM, DIAG, M, N, MB, NB, A, LDA, IAROW, IACOL, ISEED, IROFF, IRNUM, ICOFF, ICNUM, MYROW, MYCOL, NPROW, NPCOL)
Definition: pdmatgen.f:4
pdbmatgen
subroutine pdbmatgen(ICTXT, AFORM, AFORM2, BWL, BWU, N, MB, NB, A, LDA, IAROW, IACOL, ISEED, MYROW, MYCOL, NPROW, NPCOL)
Definition: pdbmatgen.f:5