/[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.15 - (hide annotations) (download)
Tue Apr 27 16:09:47 2010 UTC (14 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62g, checkpoint62f, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63g, checkpoint63, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.14: +2 -2 lines
fix bug in GLOBAL_RUM_R4 (spotted by Ralf; but don't think it's ever used)

1 jmc 1.15 C $Header: /u/gcmpack/MITgcm/eesupp/src/global_sum.F,v 1.14 2009/06/10 03:47:03 jmc Exp $
2 adcroft 1.9 C $Name: $
3 cnh 1.1
4 jmc 1.14 #include "CPP_EEOPTIONS.h"
5    
6 cnh 1.1 C-- File global_sum.F: Routines that perform global sum on an array
7     C of thread values.
8     C Contents
9 jmc 1.13 C o GLOBAL_SUM_R4
10     C o GLOBAL_SUM_R8
11     C o GLOBAL_SUM_INT
12    
13 jmc 1.14 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
14 cnh 1.10 CBOP
15     C !ROUTINE: GLOBAL_SUM_R4
16    
17     C !INTERFACE:
18 jmc 1.13 SUBROUTINE GLOBAL_SUM_R4(
19 adcroft 1.6 U sumPhi,
20 cnh 1.1 I myThid )
21 jmc 1.13
22 cnh 1.10 C !DESCRIPTION:
23     C *==========================================================*
24 jmc 1.13 C | SUBROUTINE GLOBAL\_SUM\_R4
25     C | o Handle sum for real*4 data.
26 cnh 1.10 C *==========================================================*
27 jmc 1.13 C | Perform sum an array of one value per thread and then
28     C | sum result of all the processes.
29     C | Notes:
30     C | Within a process only one thread does the sum.
31     C | The same thread also does the inter-process sum for
32     C | example with MPI and then writes the result into a shared
33     C | location. All threads wait until the sum is avaiailable.
34 cnh 1.10 C *==========================================================*
35 cnh 1.1
36 cnh 1.10 C !USES:
37 jmc 1.13 IMPLICIT NONE
38    
39 cnh 1.1 C == Global data ==
40     #include "SIZE.h"
41     #include "EEPARAMS.h"
42     #include "EESUPPORT.h"
43 adcroft 1.9 #include "GLOBAL_SUM.h"
44 cnh 1.1
45 cnh 1.10 C !INPUT/OUTPUT PARAMETERS:
46 cnh 1.1 C == Routine arguments ==
47 jmc 1.14 C sumPhi :: Result of sum.
48     C myThid :: My thread id.
49 cnh 1.1 Real*4 sumPhi
50     INTEGER myThid
51    
52 cnh 1.10 C !LOCAL VARIABLES:
53 cnh 1.1 C == Local variables ==
54 jmc 1.14 C I :: Loop counters
55     C mpiRC :: MPI return code
56 cnh 1.1 INTEGER I
57     Real*4 tmp
58     #ifdef ALLOW_USE_MPI
59     INTEGER mpiRC
60     #endif /* ALLOW_USE_MPI */
61 cnh 1.10 CEOP
62 cnh 1.1
63 adcroft 1.6 C-- write local sum into array
64 jmc 1.14 phiGSR4(1,myThid) = sumPhi
65 adcroft 1.6
66 cnh 1.4 C-- Can not start until everyone is ready
67 adcroft 1.9 CALL BAR2( myThid )
68 cnh 1.1
69     C-- Sum within the process first
70     _BEGIN_MASTER( myThid )
71     tmp = 0.
72     DO I=1,nThreads
73 jmc 1.14 tmp = tmp + phiGSR4(1,I)
74 cnh 1.1 ENDDO
75     sumPhi = tmp
76     #ifdef ALLOW_USE_MPI
77     #ifndef ALWAYS_USE_MPI
78     IF ( usingMPI ) THEN
79     #endif
80     CALL MPI_Allreduce(tmp,sumPhi,1,MPI_REAL,MPI_SUM,
81 jmc 1.11 & MPI_COMM_MODEL,mpiRC)
82 cnh 1.1 #ifndef ALWAYS_USE_MPI
83     ENDIF
84     #endif
85     #endif /* ALLOW_USE_MPI */
86 adcroft 1.6 C-- Write solution to place where all threads can see it
87 jmc 1.14 phiGSR4(1,0) = sumPhi
88 adcroft 1.6
89 cnh 1.1 _END_MASTER( myThid )
90     C--
91 adcroft 1.9 CALL BAR2( myThid )
92 adcroft 1.6
93     C-- set result for every process
94 jmc 1.15 sumPhi = phiGSR4(1,0)
95 adcroft 1.6
96 cnh 1.1 RETURN
97     END
98 jmc 1.13
99 cnh 1.1
100 jmc 1.14 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
101 cnh 1.10 CBOP
102     C !ROUTINE: GLOBAL_SUM_R8
103    
104     C !INTERFACE:
105 jmc 1.13 SUBROUTINE GLOBAL_SUM_R8(
106 adcroft 1.6 U sumPhi,
107 cnh 1.1 I myThid )
108 jmc 1.14
109 cnh 1.10 C !DESCRIPTION:
110     C *==========================================================*
111 jmc 1.13 C | SUBROUTINE GLOBAL\_SUM\_R8
112     C | o Handle sum for real*8 data.
113 cnh 1.10 C *==========================================================*
114 jmc 1.13 C | Perform sum an array of one value per thread and then
115     C | sum result of all the processes.
116     C | Notes:
117     C | Within a process only one thread does the sum.
118     C | The same thread also does the inter-process sum for
119     C | example with MPI and then writes the result into a shared
120     C | location. All threads wait until the sum is avaiailable.
121 cnh 1.10 C *==========================================================*
122 cnh 1.1
123 cnh 1.10 C !USES:
124 jmc 1.14 IMPLICIT NONE
125    
126 cnh 1.1 C === Global data ===
127     #include "SIZE.h"
128     #include "EEPARAMS.h"
129     #include "EESUPPORT.h"
130 adcroft 1.9 #include "GLOBAL_SUM.h"
131 cnh 1.1
132 cnh 1.10 C !INPUT/OUTPUT PARAMETERS:
133 cnh 1.1 C === Routine arguments ===
134 jmc 1.14 C sumPhi :: Result of sum.
135     C myThid :: My thread id.
136 cnh 1.1 Real*8 sumPhi
137     INTEGER myThid
138    
139 cnh 1.10 C !LOCAL VARIABLES:
140 cnh 1.1 C === Local variables ===
141 jmc 1.14 C I :: Loop counters
142     C mpiRC :: MPI return code
143 cnh 1.1 INTEGER I
144     Real*8 tmp
145     #ifdef ALLOW_USE_MPI
146     INTEGER mpiRC
147     #endif /* ALLOW_USE_MPI */
148 cnh 1.10 CEOP
149 cnh 1.1
150 adcroft 1.6 C-- write local sum into array
151 jmc 1.14 phiGSR8(1,myThid) = sumPhi
152 adcroft 1.6
153 cnh 1.4 C-- Can not start until everyone is ready
154 jmc 1.14 C CALL FOOL_THE_COMPILER( phiGSR8 )
155 adcroft 1.9 C CALL MS
156     CALL BAR2( myThid )
157     C _BARRIER
158     C _BARRIER
159 jmc 1.14 C CALL FOOL_THE_COMPILER( phiGSR8 )
160 cnh 1.1
161     C-- Sum within the process first
162     _BEGIN_MASTER( myThid )
163     tmp = 0. _d 0
164     DO I=1,nThreads
165 jmc 1.14 tmp = tmp + phiGSR8(1,I)
166 cnh 1.1 ENDDO
167     sumPhi = tmp
168     #ifdef ALLOW_USE_MPI
169     #ifndef ALWAYS_USE_MPI
170     IF ( usingMPI ) THEN
171     #endif
172     CALL MPI_Allreduce(tmp,sumPhi,1,MPI_DOUBLE_PRECISION,MPI_SUM,
173 jmc 1.11 & MPI_COMM_MODEL,mpiRC)
174 heimbach 1.7 #ifndef ALWAYS_USE_MPI
175     ENDIF
176     #endif
177     #endif /* ALLOW_USE_MPI */
178     C-- Write solution to place where all threads can see it
179 jmc 1.14 phiGSR8(1,0) = sumPhi
180 heimbach 1.7 _END_MASTER( myThid )
181    
182     C-- Do not leave until we are sure that the sum is done
183 jmc 1.14 C CALL FOOL_THE_COMPILER( phiGSR8 )
184 adcroft 1.9 C CALL MS
185     C _BARRIER
186     C _BARRIER
187     CALL BAR2( myThid )
188 jmc 1.14 C CALL FOOL_THE_COMPILER( phiGSR8 )
189 heimbach 1.7
190     C-- set result for every process
191 jmc 1.14 sumPhi = phiGSR8(1,0)
192 heimbach 1.7
193     RETURN
194     END
195 cnh 1.10
196 jmc 1.14 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
197 cnh 1.10 CBOP
198     C !ROUTINE: GLOBAL_SUM_INT
199     C !INTERFACE:
200 jmc 1.13 SUBROUTINE GLOBAL_SUM_INT(
201 heimbach 1.7 U sumPhi,
202     I myThid )
203 jmc 1.14
204 cnh 1.10 C !DESCRIPTION:
205     C *==========================================================*
206 jmc 1.13 C | SUBROUTINE GLOBAL\_SUM\_INT
207     C | o Handle sum for integer data.
208 cnh 1.10 C *==========================================================*
209 jmc 1.13 C | Perform sum an array of one value per thread and then
210     C | sum result of all the processes.
211     C | Notes:
212     C | Within a process only one thread does the sum.
213     C | The same thread also does the inter-process sum for
214     C | example with MPI and then writes the result into a shared
215     C | location. All threads wait until the sum is avaiailable.
216 cnh 1.10 C *==========================================================*
217 heimbach 1.7
218 cnh 1.10 C !USES:
219 jmc 1.14 IMPLICIT NONE
220    
221 heimbach 1.7 C === Global data ===
222     #include "SIZE.h"
223     #include "EEPARAMS.h"
224     #include "EESUPPORT.h"
225 adcroft 1.9 #include "GLOBAL_SUM.h"
226 heimbach 1.7
227 cnh 1.10 C !INPUT/OUTPUT PARAMETERS:
228 heimbach 1.7 C === Routine arguments ===
229 jmc 1.14 C sumPhi :: Result of sum.
230     C myThid :: My thread id.
231 heimbach 1.7 INTEGER sumPhi
232     INTEGER myThid
233    
234 cnh 1.10 C !LOCAL VARIABLES:
235 heimbach 1.7 C === Local variables ===
236 jmc 1.14 C I :: Loop counters
237     C mpiRC :: MPI return code
238 heimbach 1.7 INTEGER I
239     INTEGER tmp
240     #ifdef ALLOW_USE_MPI
241     INTEGER mpiRC
242     #endif /* ALLOW_USE_MPI */
243 cnh 1.10 CEOP
244 heimbach 1.7
245     C-- write local sum into array
246 adcroft 1.9 phiGSI(1,myThid) = sumPhi
247 heimbach 1.7
248     C-- Can not start until everyone is ready
249     _BARRIER
250    
251     C-- Sum within the process first
252     _BEGIN_MASTER( myThid )
253 jmc 1.13 tmp = 0
254 heimbach 1.7 DO I=1,nThreads
255 adcroft 1.9 tmp = tmp + phiGSI(1,I)
256 heimbach 1.7 ENDDO
257     sumPhi = tmp
258     #ifdef ALLOW_USE_MPI
259     #ifndef ALWAYS_USE_MPI
260     IF ( usingMPI ) THEN
261     #endif
262     CALL MPI_Allreduce(tmp,sumPhi,1,MPI_INTEGER,MPI_SUM,
263 jmc 1.11 & MPI_COMM_MODEL,mpiRC)
264 cnh 1.1 #ifndef ALWAYS_USE_MPI
265     ENDIF
266     #endif
267     #endif /* ALLOW_USE_MPI */
268     C-- Write solution to place where all threads can see it
269 jmc 1.14 phiGSI(1,0) = sumPhi
270 cnh 1.1 _END_MASTER( myThid )
271    
272 cnh 1.4 C-- Do not leave until we are sure that the sum is done
273 cnh 1.1 _BARRIER
274 adcroft 1.6
275     C-- set result for every process
276 jmc 1.14 sumPhi = phiGSI(1,0)
277 adcroft 1.6
278 cnh 1.1 RETURN
279     END

  ViewVC Help
Powered by ViewVC 1.1.22