/[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.8 - (hide annotations) (download)
Sun Feb 4 14:38:43 2001 UTC (23 years, 3 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint38, c37_adj, checkpoint39, checkpoint37, checkpoint36, checkpoint35
Branch point for: pre38
Changes since 1.7: +2 -1 lines
Made sure each .F and .h file had
the CVS keywords Header and Name at its start.
Most had header but very few currently have Name, so
lots of changes!

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

  ViewVC Help
Powered by ViewVC 1.1.22