ScaLAPACK 2.1  2.1
ScaLAPACK: Scalable Linear Algebra PACKage
pmpcol.f
Go to the documentation of this file.
1 ***********************************************************************
2 *
3 * Auxiliary subroutine for eigenpair assignments
4 *
5 ***********************************************************************
6  SUBROUTINE pmpcol( MYPROC, NPROCS, IIL, NEEDIL, NEEDIU,
7  $ PMYILS, PMYIUS,
8  $ COLBRT, FRSTCL, LASTCL )
9 
10  IMPLICIT NONE
11 *
12 * -- ScaLAPACK auxiliary routine (version 2.0.2) --
13 * Univ. of Tennessee, Univ. of California Berkeley, Univ. of Colorado Denver
14 * May 1 2012
15 *
16 * .. Scalar Arguments ..
17  INTEGER FRSTCL, IIL, LASTCL, MYPROC, NEEDIL, NEEDIU,
18  $ NPROCS
19  LOGICAL COLBRT
20 * ..
21 * .. Array Arguments ..
22  INTEGER PMYILS( * ), PMYIUS( * )
23 * ..
24 *
25 * Purpose
26 * =======
27 *
28 * Using the output from PMPIM2 and given the information on
29 * eigenvalue clusters, PMPCOL finds the collaborators of MYPROC.
30 *
31 * Arguments
32 * =========
33 *
34 * MYPROC (input) INTEGER
35 * The processor number, 0 <= MYPROC < NPROCS
36 *
37 * NPROCS (input) INTEGER
38 * The total number of processors available
39 *
40 * IIL (input) INTEGER
41 * The index of the leftmost eigenvalue in W
42 *
43 * NEEDIL (input) INTEGER
44 * The leftmost position in W needed by MYPROC
45 *
46 * NEEDIU (input) INTEGER
47 * The rightmost position in W needed by MYPROC
48 *
49 * PMYILS (input) INTEGER array
50 * For each processor p, PMYILS(p) is the index
51 * of the first eigenvalue in W to be computed
52 * PMYILS(p) equals zero if p stays idle
53 *
54 * PMYIUS (input) INTEGER array
55 * For each processor p, PMYIUS(p) is the index
56 * of the last eigenvalue in W to be computed
57 * PMYIUS(p) equals zero if p stays idle
58 *
59 * COLBRT (output) LOGICAL
60 * TRUE if MYPROC collaborates.
61 *
62 * FRSTCL (output) INTEGER
63 * LASTCL FIRST and LAST collaborator of MYPROC
64 * MYPROC collaborates with
65 * FRSTCL, ..., MYPROC-1, MYPROC+1, ...,LASTCL
66 * If MYPROC == FRSTCL, there are no collaborators
67 * on the left. IF MYPROC == LASTCL, there are no
68 * collaborators on the right.
69 * If FRSTCL == 0 and LASTCL = NPROCS-1, then
70 * MYPROC collaborates with everybody
71 *
72 
73 * .. Local Scalars ..
74  INTEGER I, NEEDIIL, NEEDIIU
75 * ..
76 * .. Executable Statements ..
77 * Compute global eigenvalue index from position in W
78  neediil = needil + iil - 1
79  neediiu = neediu + iil - 1
80 
81 * Find processor responsible for NEEDIL, this is the first
82 * collaborator
83  DO 1 i = 1, nprocs
84  IF( pmyils(i).GT.neediil) GOTO 2
85  frstcl = i-1
86  1 CONTINUE
87  2 CONTINUE
88 
89 * Find processor responsible for NEEDIU, this is the last
90 * collaborator
91  DO 3 i = nprocs,1,-1
92  IF( pmyius(i).LT.neediiu ) THEN
93 * Need to check special case: does this proc work at all?
94  IF( pmyius(i).GT.0 )
95  $ GOTO 4
96  ENDIF
97  lastcl = i-1
98  3 CONTINUE
99  4 CONTINUE
100 
101 * Decide if there is a collaboration
102  IF( (frstcl.LT.myproc).OR.(lastcl.GT.myproc) ) THEN
103  colbrt = .true.
104  ELSE
105  colbrt = .false.
106  ENDIF
107 
108  RETURN
109  END
pmpcol
subroutine pmpcol(MYPROC, NPROCS, IIL, NEEDIL, NEEDIU, PMYILS, PMYIUS, COLBRT, FRSTCL, LASTCL)
Definition: pmpcol.f:9