ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
pdscaexinfo.f
Go to the documentation of this file.
1  SUBROUTINE pdscaexinfo( SUMMRY, NOUT, N, NRHS, NB, NPROW, NPCOL,
2  $ WORK, IAM, NPROCS )
3 *
4 * -- ScaLAPACK example code --
5 * University of Tennessee, Knoxville, Oak Ridge National Laboratory,
6 * and University of California, Berkeley.
7 *
8 * Written by Antoine Petitet, August 1995 (petitet@cs.utk.edu)
9 *
10 * This program solves a linear system by calling the ScaLAPACK
11 * routine PDGESV. The input matrix and right-and-sides are
12 * read from a file. The solution is written to a file.
13 *
14 * .. Scalar Arguments ..
15  CHARACTER*( * ) SUMMRY
16  INTEGER IAM, N, NRHS, NB, NOUT, NPCOL, NPROCS, NPROW
17 * ..
18 * .. Array Arguments ..
19  INTEGER WORK( * )
20 * ..
21 *
22 * ======================================================================
23 *
24 * .. Parameters ..
25  INTEGER NIN
26  parameter( nin = 11 )
27 * ..
28 * .. Local Scalars ..
29  CHARACTER*79 USRINFO
30  INTEGER ICTXT
31 * ..
32 * .. External Subroutines ..
33  EXTERNAL blacs_abort, blacs_get, blacs_gridexit,
34  $ blacs_gridinit, blacs_setup, igebr2d, igebs2d
35 * ..
36 * .. Executable Statements ..
37 *
38 * Process 0 reads the input data, broadcasts to other processes and
39 * writes needed information to NOUT
40 *
41  IF( iam.EQ.0 ) THEN
42 *
43 * Open file and skip data file header
44 *
45  OPEN( nin, file='SCAEX.dat', status='OLD' )
46  READ( nin, fmt = * ) summry
47  summry = ' '
48 *
49 * Read in user-supplied info about machine type, compiler, etc.
50 *
51  READ( nin, fmt = 9999 ) usrinfo
52 *
53 * Read name and unit number for summary output file
54 *
55  READ( nin, fmt = * ) summry
56  READ( nin, fmt = * ) nout
57  IF( nout.NE.0 .AND. nout.NE.6 )
58  $ OPEN( nout, file = summry, status = 'UNKNOWN' )
59 *
60 * Read and check the parameter values for the tests.
61 *
62 * Get matrix dimensions
63 *
64  READ( nin, fmt = * ) n
65  READ( nin, fmt = * ) nrhs
66 *
67 * Get value of NB
68 *
69  READ( nin, fmt = * ) nb
70 *
71 * Get grid shape
72 *
73  READ( nin, fmt = * ) nprow
74  READ( nin, fmt = * ) npcol
75 *
76 * Close input file
77 *
78  CLOSE( nin )
79 *
80 * If underlying system needs additional set up, do it now
81 *
82  IF( nprocs.LT.1 ) THEN
83  nprocs = nprow * npcol
84  CALL blacs_setup( iam, nprocs )
85  END IF
86 *
87 * Temporarily define blacs grid to include all processes so
88 * information can be broadcast to all processes
89 *
90  CALL blacs_get( -1, 0, ictxt )
91  CALL blacs_gridinit( ictxt, 'Row-major', 1, nprocs )
92 *
93 * Pack information arrays and broadcast
94 *
95  work( 1 ) = n
96  work( 2 ) = nrhs
97  work( 3 ) = nb
98  work( 4 ) = nprow
99  work( 5 ) = npcol
100  CALL igebs2d( ictxt, 'All', ' ', 5, 1, work, 5 )
101 *
102 * regurgitate input
103 *
104  WRITE( nout, fmt = 9999 )
105  $ 'SCALAPACK example driver.'
106  WRITE( nout, fmt = 9999 ) usrinfo
107  WRITE( nout, fmt = * )
108  WRITE( nout, fmt = 9999 )
109  $ 'The matrices A and B are read from '//
110  $ 'a file.'
111  WRITE( nout, fmt = * )
112  WRITE( nout, fmt = 9999 )
113  $ 'An explanation of the input/output '//
114  $ 'parameters follows:'
115 *
116  WRITE( nout, fmt = 9999 )
117  $ 'N : The order of the matrix A.'
118  WRITE( nout, fmt = 9999 )
119  $ 'NRHS : The number of right and sides.'
120  WRITE( nout, fmt = 9999 )
121  $ 'NB : The size of the square blocks the'//
122  $ ' matrices A and B are split into.'
123  WRITE( nout, fmt = 9999 )
124  $ 'P : The number of process rows.'
125  WRITE( nout, fmt = 9999 )
126  $ 'Q : The number of process columns.'
127  WRITE( nout, fmt = * )
128  WRITE( nout, fmt = 9999 )
129  $ 'The following parameter values will be used:'
130  WRITE( nout, fmt = 9998 ) 'N ', n
131  WRITE( nout, fmt = 9998 ) 'NRHS ', nrhs
132  WRITE( nout, fmt = 9998 ) 'NB ', nb
133  WRITE( nout, fmt = 9998 ) 'P ', nprow
134  WRITE( nout, fmt = 9998 ) 'Q ', npcol
135  WRITE( nout, fmt = * )
136 *
137  ELSE
138 *
139 * If underlying system needs additional set up, do it now
140 *
141  IF( nprocs.LT.1 )
142  $ CALL blacs_setup( iam, nprocs )
143 *
144 * Temporarily define blacs grid to include all processes so
145 * information can be broadcast to all processes
146 *
147  CALL blacs_get( -1, 0, ictxt )
148  CALL blacs_gridinit( ictxt, 'Row-major', 1, nprocs )
149 *
150  CALL igebr2d( ictxt, 'All', ' ', 5, 1, work, 5, 0, 0 )
151  n = work( 1 )
152  nrhs = work( 2 )
153  nb = work( 3 )
154  nprow = work( 4 )
155  npcol = work( 5 )
156 *
157  END IF
158 *
159  CALL blacs_gridexit( ictxt )
160 *
161  RETURN
162 *
163  20 WRITE( nout, fmt = 9997 )
164  CLOSE( nin )
165  IF( nout.NE.6 .AND. nout.NE.0 )
166  $ CLOSE( nout )
167  CALL blacs_abort( ictxt, 1 )
168 *
169  stop
170 *
171  9999 FORMAT( a )
172  9998 FORMAT( 2x, a5, ' : ', i6 )
173  9997 FORMAT( ' Illegal input in file ',40a,'. Aborting run.' )
174 *
175 * End of PDSCAEXINFO
176 *
177  END
pdscaexinfo
subroutine pdscaexinfo(SUMMRY, NOUT, N, NRHS, NB, NPROW, NPCOL, WORK, IAM, NPROCS)
Definition: pdscaexinfo.f:3