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

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

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

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

Legend:
Removed from v.1.7  
changed lines
  Added in v.1.13

  ViewVC Help
Powered by ViewVC 1.1.22