ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
pslaread.f
Go to the documentation of this file.
1  SUBROUTINE pslaread( FILNAM, A, DESCA, IRREAD, ICREAD, WORK )
2 *
3 * -- ScaLAPACK tools routine (version 1.8) --
4 * University of Tennessee, Knoxville, Oak Ridge National Laboratory,
5 * and University of California, Berkeley.
6 *
7 * written by Antoine Petitet, August 1995 (petitet@cs.utk.edu)
8 * adapted by Julie Langou, April 2007 (julie@cs.utk.edu)
9 *
10 * .. Scalar Arguments ..
11  INTEGER ICREAD, IRREAD
12 * ..
13 * .. Array Arguments ..
14  CHARACTER*(*) FILNAM
15  INTEGER DESCA( * )
16  REAL A( * ), WORK( * )
17 * ..
18 *
19 * Purpose
20 * =======
21 *
22 * PSLAREAD reads from a file named FILNAM a matrix and distribute
23 * it to the process grid.
24 *
25 * Only the process of coordinates {IRREAD, ICREAD} read the file.
26 *
27 * WORK must be of size >= MB_ = DESCA( MB_ ).
28 *
29 * =====================================================================
30 *
31 * .. Parameters ..
32  INTEGER NIN
33  parameter( nin = 11 )
34  INTEGER BLOCK_CYCLIC_2D, CSRC_, CTXT_, DLEN_, DT_,
35  $ LLD_, MB_, M_, NB_, N_, RSRC_
36  parameter( block_cyclic_2d = 1, dlen_ = 9, dt_ = 1,
37  $ ctxt_ = 2, m_ = 3, n_ = 4, mb_ = 5, nb_ = 6,
38  $ rsrc_ = 7, csrc_ = 8, lld_ = 9 )
39 * ..
40 * .. Local Scalars ..
41  INTEGER H, I, IB, ICTXT, ICURCOL, ICURROW, II, J, JB,
42  $ JJ, K, LDA, M, MYCOL, MYROW, N, NPCOL, NPROW
43 * ..
44 * .. Local Arrays ..
45  INTEGER IWORK( 2 )
46 * ..
47 * .. External Subroutines ..
48  EXTERNAL blacs_gridinfo, infog2l, sgerv2d, sgesd2d,
49  $ igebs2d, igebr2d
50 * ..
51 * .. External Functions ..
52  INTEGER ICEIL
53  EXTERNAL iceil
54 * ..
55 * .. Intrinsic Functions ..
56  INTRINSIC min, mod
57 * ..
58 * .. Executable Statements ..
59 *
60 * Get grid parameters
61 *
62  ictxt = desca( ctxt_ )
63  CALL blacs_gridinfo( ictxt, nprow, npcol, myrow, mycol )
64 *
65  IF( myrow.EQ.irread .AND. mycol.EQ.icread ) THEN
66  OPEN( nin, file=filnam, status='OLD' )
67  READ( nin, fmt = * ) ( iwork( i ), i = 1, 2 )
68  CALL igebs2d( ictxt, 'All', ' ', 2, 1, iwork, 2 )
69  ELSE
70  CALL igebr2d( ictxt, 'All', ' ', 2, 1, iwork, 2, irread,
71  $ icread )
72  END IF
73  m = iwork( 1 )
74  n = iwork( 2 )
75 *
76  IF( m.LE.0 .OR. n.LE.0 )
77  $ RETURN
78 *
79  IF( m.GT.desca( m_ ).OR. n.GT.desca( n_ ) ) THEN
80  IF( myrow.EQ.0 .AND. mycol.EQ.0 ) THEN
81  WRITE( *, fmt = * ) 'PSLAREAD: Matrix too big to fit in'
82  WRITE( *, fmt = * ) 'Abort ...'
83  END IF
84  CALL blacs_abort( ictxt, 0 )
85  END IF
86 *
87  ii = 1
88  jj = 1
89  icurrow = desca( rsrc_ )
90  icurcol = desca( csrc_ )
91  lda = desca( lld_ )
92 *
93 * Loop over column blocks
94 *
95  DO 50 j = 1, n, desca( nb_ )
96  jb = min( desca( nb_ ), n-j+1 )
97  DO 40 h = 0, jb-1
98 *
99 * Loop over block of rows
100 *
101  DO 30 i = 1, m, desca( mb_ )
102  ib = min( desca( mb_ ), m-i+1 )
103  IF( icurrow.EQ.irread .AND. icurcol.EQ.icread ) THEN
104  IF( myrow.EQ.irread .AND. mycol.EQ.icread ) THEN
105  DO 10 k = 0, ib-1
106  READ( nin, fmt = * ) a( ii+k+(jj+h-1)*lda )
107  10 CONTINUE
108  END IF
109  ELSE
110  IF( myrow.EQ.icurrow .AND. mycol.EQ.icurcol ) THEN
111  CALL sgerv2d( ictxt, ib, 1, a( ii+(jj+h-1)*lda ),
112  $ lda, irread, icread )
113  ELSE IF( myrow.EQ.irread .AND. mycol.EQ.icread ) THEN
114  DO 20 k = 1, ib
115  READ( nin, fmt = * ) work( k )
116  20 CONTINUE
117  CALL sgesd2d( ictxt, ib, 1, work, desca( mb_ ),
118  $ icurrow, icurcol )
119  END IF
120  END IF
121  IF( myrow.EQ.icurrow )
122  $ ii = ii + ib
123  icurrow = mod( icurrow+1, nprow )
124  30 CONTINUE
125 *
126  ii = 1
127  icurrow = desca( rsrc_ )
128  40 CONTINUE
129 *
130  IF( mycol.EQ.icurcol )
131  $ jj = jj + jb
132  icurcol = mod( icurcol+1, npcol )
133 *
134  50 CONTINUE
135 *
136  IF( myrow.EQ.irread .AND. mycol.EQ.icread ) THEN
137  CLOSE( nin )
138  END IF
139 *
140  RETURN
141 *
142 * End of PSLAREAD
143 *
144  END
infog2l
subroutine infog2l(GRINDX, GCINDX, DESC, NPROW, NPCOL, MYROW, MYCOL, LRINDX, LCINDX, RSRC, CSRC)
Definition: infog2l.f:3
pslaread
subroutine pslaread(FILNAM, A, DESCA, IRREAD, ICREAD, WORK)
Definition: pslaread.f:2
min
#define min(A, B)
Definition: pcgemr.c:181