/[MITgcm]/MITgcm/eesupp/src/global_sum.F
ViewVC logotype

Annotation of /MITgcm/eesupp/src/global_sum.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.1 - (hide annotations) (download)
Wed Apr 22 19:15:30 1998 UTC (26 years ago) by cnh
Branch: MAIN
Branch point for: cnh
Initial revision

1 cnh 1.1 C $Id$
2    
3     C-- File global_sum.F: Routines that perform global sum on an array
4     C of thread values.
5     C Contents
6     C o global_sum_r4
7     C o global_sum_r8
8     #include "CPP_EEOPTIONS.h"
9    
10     CStartOfInterface
11     SUBROUTINE GLOBAL_SUM_R4(
12     I phi,
13     O sumPhi,
14     I myThid )
15     C /==========================================================\
16     C | SUBROUTINE GLOBAL_SUM_R4 |
17     C | o Handle sum for real*4 data. |
18     C |==========================================================|
19     C | Perform sum an array of one value per thread and then |
20     C | sum result of all the processes. |
21     C | Notes |
22     C | ===== |
23     C | Within a process only one thread does the sum, each |
24     C | thread is assumed to have already summed its local data. |
25     C | The same thread also does the inter-process sum for |
26     C | example with MPI and then writes the result into a shared|
27     C | location. All threads wait until the sum is avaiailable. |
28     C \==========================================================/
29    
30     C == Global data ==
31     #include "SIZE.h"
32     #include "EEPARAMS.h"
33     #include "EESUPPORT.h"
34    
35     C == Routine arguments ==
36     C phi - Array to be summed.
37     C sumPhi - Result of sum.
38     C myThid - My thread id.
39     Real*4 phi(lShare4,MAX_NO_THREADS)
40     Real*4 sumPhi
41     INTEGER myThid
42     CEndOfInterface
43    
44     C == Local variables ==
45     C I - Loop counters
46     C mpiRC - MPI return code
47     INTEGER I
48     Real*4 tmp
49     #ifdef ALLOW_USE_MPI
50     INTEGER mpiRC
51     #endif /* ALLOW_USE_MPI */
52    
53     C-- Can't start until everyone is ready
54     _BARRIER
55    
56     C-- Sum within the process first
57     _BEGIN_MASTER( myThid )
58     tmp = 0.
59     DO I=1,nThreads
60     tmp = tmp + phi(1,I)
61     ENDDO
62     sumPhi = tmp
63     #ifdef ALLOW_USE_MPI
64     #ifndef ALWAYS_USE_MPI
65     IF ( usingMPI ) THEN
66     #endif
67     CALL MPI_Allreduce(tmp,sumPhi,1,MPI_REAL,MPI_SUM,
68     & MPI_COMM_WORLD,mpiRC)
69     #ifndef ALWAYS_USE_MPI
70     ENDIF
71     #endif
72     #endif /* ALLOW_USE_MPI */
73     phi(1,1) = sumPhi
74     _END_MASTER( myThid )
75     C--
76     _BARRIER
77     C
78     RETURN
79     END
80    
81    
82     CStartOfInterface
83     SUBROUTINE GLOBAL_SUM_R8(
84     I phi,
85     O sumPhi,
86     I myThid )
87     C /==========================================================\
88     C | SUBROUTINE GLOBAL_SUM_R8 |
89     C | o Handle sum for real*8 data. |
90     C |==========================================================|
91     C | Perform sum an array of one value per thread and then |
92     C | sum result of all the processes. |
93     C | Notes |
94     C | ===== |
95     C | Within a process only one thread does the sum, each |
96     C | thread is assumed to have already summed its local data. |
97     C | The same thread also does the inter-process sum for |
98     C | example with MPI and then writes the result into a shared|
99     C | location. All threads wait until the sum is avaiailable. |
100     C \==========================================================/
101    
102     C === Global data ===
103     #include "SIZE.h"
104     #include "EEPARAMS.h"
105     #include "EESUPPORT.h"
106    
107     C === Routine arguments ===
108     C phi - Array to be summed.
109     C sumPhi - Result of sum.
110     C myThid - My thread id.
111     Real*8 phi(lShare8,MAX_NO_THREADS)
112     Real*8 sumPhi
113     INTEGER myThid
114     CEndOfInterface
115    
116     C === Local variables ===
117     C I - Loop counters
118     C mpiRC - MPI return code
119     INTEGER I
120     Real*8 tmp
121     #ifdef ALLOW_USE_MPI
122     INTEGER mpiRC
123     #endif /* ALLOW_USE_MPI */
124    
125     C-- Can't start until everyone is ready
126     _BARRIER
127    
128     C-- Sum within the process first
129     _BEGIN_MASTER( myThid )
130     tmp = 0. _d 0
131     DO I=1,nThreads
132     tmp = tmp + phi(1,I)
133     ENDDO
134     sumPhi = tmp
135     #ifdef ALLOW_USE_MPI
136     #ifndef ALWAYS_USE_MPI
137     IF ( usingMPI ) THEN
138     #endif
139     CALL MPI_Allreduce(tmp,sumPhi,1,MPI_DOUBLE_PRECISION,MPI_SUM,
140     & MPI_COMM_WORLD,mpiRC)
141     #ifndef ALWAYS_USE_MPI
142     ENDIF
143     #endif
144     #endif /* ALLOW_USE_MPI */
145     C-- Write solution to place where all threads can see it
146     phi(1,1) = sumPhi
147     _END_MASTER( myThid )
148    
149     C-- Don't leave until we are sure that the sum is done
150     _BARRIER
151     C
152     RETURN
153     END
154    
155     C $Id: $

  ViewVC Help
Powered by ViewVC 1.1.22