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

Legend:
Removed from v.1.1.1.1  
changed lines
  Added in v.1.16

  ViewVC Help
Powered by ViewVC 1.1.22