/[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.9 - (hide annotations) (download)
Tue May 29 14:01:36 2001 UTC (22 years, 11 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, checkpoint40pre2, checkpoint40pre4, checkpoint40pre5, checkpoint40
Changes since 1.8: +37 -24 lines
Merge from branch pre38:
 o essential mods for cubed sphere
 o debugged atmosphere, dynamcis + physics (aim)
 o new packages (mom_vecinv, mom_fluxform, ...)

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

  ViewVC Help
Powered by ViewVC 1.1.22