ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
descinit.f
Go to the documentation of this file.
1  SUBROUTINE descinit( DESC, M, N, MB, NB, IRSRC, ICSRC, ICTXT,
2  $ LLD, INFO )
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 ICSRC, ICTXT, INFO, IRSRC, LLD, M, MB, N, NB
11 * ..
12 * .. Array Arguments ..
13  INTEGER DESC( * )
14 * ..
15 *
16 * Purpose
17 * =======
18 *
19 * DESCINIT initializes the descriptor vector with the 8 input arguments
20 * M, N, MB, NB, IRSRC, ICSRC, ICTXT, LLD.
21 *
22 * Notes
23 * =====
24 *
25 * Each global data object is described by an associated description
26 * vector. This vector stores the information required to establish
27 * the mapping between an object element and its corresponding process
28 * and memory location.
29 *
30 * Let A be a generic term for any 2D block cyclicly distributed array.
31 * Such a global array has an associated description vector DESCA.
32 * In the following comments, the character _ should be read as
33 * "of the global array".
34 *
35 * NOTATION STORED IN EXPLANATION
36 * --------------- -------------- --------------------------------------
37 * DTYPE_A(global) DESCA( DTYPE_ )The descriptor type. In this case,
38 * DTYPE_A = 1.
39 * CTXT_A (global) DESCA( CTXT_ ) The BLACS context handle, indicating
40 * the BLACS process grid A is distribu-
41 * ted over. The context itself is glo-
42 * bal, but the handle (the integer
43 * value) may vary.
44 * M_A (global) DESCA( M_ ) The number of rows in the global
45 * array A.
46 * N_A (global) DESCA( N_ ) The number of columns in the global
47 * array A.
48 * MB_A (global) DESCA( MB_ ) The blocking factor used to distribute
49 * the rows of the array.
50 * NB_A (global) DESCA( NB_ ) The blocking factor used to distribute
51 * the columns of the array.
52 * RSRC_A (global) DESCA( RSRC_ ) The process row over which the first
53 * row of the array A is distributed.
54 * CSRC_A (global) DESCA( CSRC_ ) The process column over which the
55 * first column of the array A is
56 * distributed.
57 * LLD_A (local) DESCA( LLD_ ) The leading dimension of the local
58 * array. LLD_A >= MAX(1,LOCr(M_A)).
59 *
60 * Let K be the number of rows or columns of a distributed matrix,
61 * and assume that its process grid has dimension p x q.
62 * LOCr( K ) denotes the number of elements of K that a process
63 * would receive if K were distributed over the p processes of its
64 * process column.
65 * Similarly, LOCc( K ) denotes the number of elements of K that a
66 * process would receive if K were distributed over the q processes of
67 * its process row.
68 * The values of LOCr() and LOCc() may be determined via a call to the
69 * ScaLAPACK tool function, NUMROC:
70 * LOCr( M ) = NUMROC( M, MB_A, MYROW, RSRC_A, NPROW ),
71 * LOCc( N ) = NUMROC( N, NB_A, MYCOL, CSRC_A, NPCOL ).
72 * An upper bound for these quantities may be computed by:
73 * LOCr( M ) <= ceil( ceil(M/MB_A)/NPROW )*MB_A
74 * LOCc( N ) <= ceil( ceil(N/NB_A)/NPCOL )*NB_A
75 *
76 * Arguments
77 * =========
78 *
79 * DESC (output) INTEGER array of dimension DLEN_.
80 * The array descriptor of a distributed matrix to be set.
81 *
82 * M (global input) INTEGER
83 * The number of rows in the distributed matrix. M >= 0.
84 *
85 * N (global input) INTEGER
86 * The number of columns in the distributed matrix. N >= 0.
87 *
88 * MB (global input) INTEGER
89 * The blocking factor used to distribute the rows of the
90 * matrix. MB >= 1.
91 *
92 * NB (global input) INTEGER
93 * The blocking factor used to distribute the columns of the
94 * matrix. NB >= 1.
95 *
96 * IRSRC (global input) INTEGER
97 * The process row over which the first row of the matrix is
98 * distributed. 0 <= IRSRC < NPROW.
99 *
100 * ICSRC (global input) INTEGER
101 * The process column over which the first column of the
102 * matrix is distributed. 0 <= ICSRC < NPCOL.
103 *
104 * ICTXT (global input) INTEGER
105 * The BLACS context handle, indicating the global context of
106 * the operation on the matrix. The context itself is global.
107 *
108 * LLD (local input) INTEGER
109 * The leading dimension of the local array storing the local
110 * blocks of the distributed matrix. LLD >= MAX(1,LOCr(M)).
111 *
112 * INFO (output) INTEGER
113 * = 0: successful exit
114 * < 0: if INFO = -i, the i-th argument had an illegal value
115 *
116 * Note
117 * ====
118 *
119 * If the routine can recover from an erroneous input argument, it will
120 * return an acceptable descriptor vector. For example, if LLD = 0 on
121 * input, DESC(LLD_) will contain the smallest leading dimension
122 * required to store the specified M-by-N distributed matrix, INFO
123 * will be set -9 in that case.
124 *
125 * =====================================================================
126 *
127 * .. Parameters ..
128  INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DTYPE_,
129  $ lld_, mb_, m_, nb_, n_, rsrc_
130  parameter( block_cyclic_2d = 1, dlen_ = 9, dtype_ = 1,
131  $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
132  $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
133 * ..
134 * .. Local Scalars ..
135  INTEGER MYCOL, MYROW, NPCOL, NPROW
136 * ..
137 * .. External Subroutines ..
138  EXTERNAL blacs_gridinfo, pxerbla
139 * ..
140 * .. External Functions ..
141  INTEGER NUMROC
142  EXTERNAL numroc
143 * ..
144 * .. Intrinsic Functions ..
145  INTRINSIC max, min
146 * ..
147 * .. Executable Statements ..
148 *
149 * Get grid parameters
150 *
151  CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
152 *
153  info = 0
154  IF( m.LT.0 ) THEN
155  info = -2
156  ELSE IF( n.LT.0 ) THEN
157  info = -3
158  ELSE IF( mb.LT.1 ) THEN
159  info = -4
160  ELSE IF( nb.LT.1 ) THEN
161  info = -5
162  ELSE IF( irsrc.LT.0 .OR. irsrc.GE.nprow ) THEN
163  info = -6
164  ELSE IF( icsrc.LT.0 .OR. icsrc.GE.npcol ) THEN
165  info = -7
166  ELSE IF( nprow.EQ.-1 ) THEN
167  info = -8
168  ELSE IF( lld.LT.max( 1, numroc( m, mb, myrow, irsrc,
169  $ nprow ) ) ) THEN
170  info = -9
171  END IF
172 *
173  IF( info.NE.0 )
174  $ CALL pxerbla( ictxt, 'DESCINIT', -info )
175 *
176  desc( dtype_ ) = block_cyclic_2d
177  desc( m_ ) = max( 0, m )
178  desc( n_ ) = max( 0, n )
179  desc( mb_ ) = max( 1, mb )
180  desc( nb_ ) = max( 1, nb )
181  desc( rsrc_ ) = max( 0, min( irsrc, nprow-1 ) )
182  desc( csrc_ ) = max( 0, min( icsrc, npcol-1 ) )
183  desc( ctxt_ ) = ictxt
184  desc( lld_ ) = max( lld, max( 1, numroc( desc( m_ ), desc( mb_ ),
185  $ myrow, desc( rsrc_ ), nprow ) ) )
186 *
187  RETURN
188 *
189 * End DESCINIT
190 *
191  END
max
#define max(A, B)
Definition: pcgemr.c:180
descinit
subroutine descinit(DESC, M, N, MB, NB, IRSRC, ICSRC, ICTXT, LLD, INFO)
Definition: descinit.f:3
pxerbla
subroutine pxerbla(ICTXT, SRNAME, INFO)
Definition: pxerbla.f:2
min
#define min(A, B)
Definition: pcgemr.c:181