/[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.3 by cnh, Thu Apr 23 20:56:54 1998 UTC revision 1.9 by adcroft, Tue May 29 14:01:36 2001 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.
# Line 9  C      o global_sum_r8 Line 10  C      o global_sum_r8
10    
11  CStartOfInterface  CStartOfInterface
12        SUBROUTINE GLOBAL_SUM_R4(        SUBROUTINE GLOBAL_SUM_R4(
13       I                       phi,       U                       sumPhi,
      O                       sumPhi,  
14       I                       myThid )       I                       myThid )
15  C     /==========================================================\  C     /==========================================================\
16  C     | SUBROUTINE GLOBAL_SUM_R4                                 |  C     | SUBROUTINE GLOBAL_SUM_R4                                 |
# Line 26  C     | The same thread also does the in Line 26  C     | The same thread also does the in
26  C     | example with MPI and then writes the result into a shared|  C     | example with MPI and then writes the result into a shared|
27  C     | location. All threads wait until the sum is avaiailable. |  C     | location. All threads wait until the sum is avaiailable. |
28  C     \==========================================================/  C     \==========================================================/
29          IMPLICIT NONE
30    
31  C     == Global data ==  C     == Global data ==
32  #include "SIZE.h"  #include "SIZE.h"
33  #include "EEPARAMS.h"  #include "EEPARAMS.h"
34  #include "EESUPPORT.h"  #include "EESUPPORT.h"
35    #include "GLOBAL_SUM.h"
36    
37  C     == Routine arguments ==  C     == Routine arguments ==
 C     phi    - Array to be summed.  
38  C     sumPhi - Result of sum.  C     sumPhi - Result of sum.
39  C     myThid - My thread id.  C     myThid - My thread id.
       Real*4 phi(lShare4,MAX_NO_THREADS)  
40        Real*4 sumPhi        Real*4 sumPhi
41        INTEGER myThid        INTEGER myThid
42  CEndOfInterface  CEndOfInterface
# Line 50  C     mpiRC  - MPI return code Line 50  C     mpiRC  - MPI return code
50        INTEGER mpiRC        INTEGER mpiRC
51  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
52    
53  C--   Can't start until everyone is ready  C--   write local sum into array
54        _BARRIER        CALL BAR2( myThid )
55          phiGSRS(1,myThid) = sumPhi
56    
57    C--   Can not start until everyone is ready
58          CALL BAR2( myThid )
59    
60  C--   Sum within the process first  C--   Sum within the process first
61        _BEGIN_MASTER( myThid )        _BEGIN_MASTER( myThid )
62         tmp = 0.         tmp = 0.
63         DO I=1,nThreads         DO I=1,nThreads
64          tmp = tmp + phi(1,I)          tmp = tmp + phiGSRS(1,I)
65         ENDDO         ENDDO
66         sumPhi = tmp         sumPhi = tmp
67  #ifdef  ALLOW_USE_MPI  #ifdef  ALLOW_USE_MPI
# Line 70  C--   Sum within the process first Line 74  C--   Sum within the process first
74         ENDIF         ENDIF
75  #endif  #endif
76  #endif /*  ALLOW_USE_MPI */  #endif /*  ALLOW_USE_MPI */
77         phi(1,1) = sumPhi  C--     Write solution to place where all threads can see it
78           phiGSRS(1,1) = sumPhi
79    
80        _END_MASTER( myThid )        _END_MASTER( myThid )
81  C--  C--
82        _BARRIER        CALL BAR2( myThid )
83  C  
84    C--   set result for every process
85          sumPhi = phiGSRS(1,1)
86          CALL BAR2( myThid )
87    
88        RETURN        RETURN
89        END        END
90                
91    
92  CStartOfInterface  CStartOfInterface
93        SUBROUTINE GLOBAL_SUM_R8(        SUBROUTINE GLOBAL_SUM_R8(
94       I                       phi,       U                       sumPhi,
      O                       sumPhi,  
95       I                       myThid )       I                       myThid )
96  C     /==========================================================\  C     /==========================================================\
97  C     | SUBROUTINE GLOBAL_SUM_R8                                 |  C     | SUBROUTINE GLOBAL_SUM_R8                                 |
# Line 98  C     | The same thread also does the in Line 107  C     | The same thread also does the in
107  C     | example with MPI and then writes the result into a shared|  C     | example with MPI and then writes the result into a shared|
108  C     | location. All threads wait until the sum is avaiailable. |  C     | location. All threads wait until the sum is avaiailable. |
109  C     \==========================================================/  C     \==========================================================/
110          IMPLICIT NONE
111    
112  C     === Global data ===  C     === Global data ===
113  #include "SIZE.h"  #include "SIZE.h"
114  #include "EEPARAMS.h"  #include "EEPARAMS.h"
115  #include "EESUPPORT.h"  #include "EESUPPORT.h"
116    #include "GLOBAL_SUM.h"
117    
118  C     === Routine arguments ===  C     === Routine arguments ===
 C     phi    - Array to be summed.  
119  C     sumPhi - Result of sum.  C     sumPhi - Result of sum.
120  C     myThid - My thread id.  C     myThid - My thread id.
       Real*8 phi(lShare8,MAX_NO_THREADS)  
121        Real*8 sumPhi        Real*8 sumPhi
122        INTEGER myThid        INTEGER myThid
123  CEndOfInterface  CEndOfInterface
# Line 122  C     mpiRC  - MPI return code Line 131  C     mpiRC  - MPI return code
131        INTEGER mpiRC        INTEGER mpiRC
132  #endif   /* ALLOW_USE_MPI */  #endif   /* ALLOW_USE_MPI */
133    
134  C--   Can't start until everyone is ready        CALL BAR2( myThid )
135        _BARRIER  C--   write local sum into array
136          phiGSRL(1,myThid) = sumPhi
137    
138    C--   Can not start until everyone is ready
139    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    
146  C--   Sum within the process first  C--   Sum within the process first
147        _BEGIN_MASTER( myThid )        _BEGIN_MASTER( myThid )
148         tmp = 0. _d 0         tmp = 0. _d 0
149         DO I=1,nThreads         DO I=1,nThreads
150          tmp = tmp + phi(1,I)          tmp = tmp + phiGSRL(1,I)
151         ENDDO         ENDDO
152         sumPhi = tmp         sumPhi = tmp
153  #ifdef  ALLOW_USE_MPI  #ifdef  ALLOW_USE_MPI
# Line 143  C--   Sum within the process first Line 161  C--   Sum within the process first
161  #endif  #endif
162  #endif /*  ALLOW_USE_MPI */  #endif /*  ALLOW_USE_MPI */
163  C--     Write solution to place where all threads can see it  C--     Write solution to place where all threads can see it
164          phi(1,1) = sumPhi          phiGSRL(1,1) = sumPhi
165          _END_MASTER( myThid )
166    
167    C--   Do not leave until we are sure that the sum is done
168    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    
175    C--   set result for every process
176          sumPhi = phiGSRL(1,1)
177          CALL BAR2( myThid )
178    
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    #include "GLOBAL_SUM.h"
206    
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          _BARRIER
224    C--   write local sum into array
225          phiGSI(1,myThid) = sumPhi
226    
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            tmp = tmp + phiGSI(1,I)
235           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         &                   MPI_COMM_WORLD,mpiRC)
243    #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            phiGSI(1,1) = sumPhi
249        _END_MASTER( myThid )        _END_MASTER( myThid )
250    
251  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
252          _BARRIER
253    
254    C--   set result for every process
255          sumPhi = phiGSI(1,1)
256        _BARRIER        _BARRIER
257  C  
258        RETURN        RETURN
259        END        END

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.9

  ViewVC Help
Powered by ViewVC 1.1.22