/[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.7 - (hide annotations) (download)
Tue Jan 30 20:49:49 2001 UTC (23 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint34
Changes since 1.6: +79 -1 lines
Included routine SUBROUTINE GLOBAL_SUM_INT.

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

  ViewVC Help
Powered by ViewVC 1.1.22