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

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

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

revision 1.2 by jmc, Sun Jun 7 15:19:41 2009 UTC revision 1.3 by jmc, Wed Jun 10 03:47:03 2009 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4    #include "CPP_EEOPTIONS.h"
5    
6  C--   File global_sum_tile.F: Routines that perform global sum  C--   File global_sum_tile.F: Routines that perform global sum
7  C                             on a tile array  C                             on a tile array
8  C      Contents  C      Contents
9  C      o global_sum_tile_rl  C      o GLOBAL_SUM_TILE_RL
10  C      o global_sum_tile_rs <- not yet coded  C      o GLOBAL_SUM_TILE_RS <- not yet coded
 #include "CPP_EEOPTIONS.h"  
11    
12    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
13  CBOP  CBOP
14  C     !ROUTINE: GLOBAL_SUM_TILE_RL  C     !ROUTINE: GLOBAL_SUM_TILE_RL
15    
# Line 16  C     !INTERFACE: Line 18  C     !INTERFACE:
18       I                       phiTile,       I                       phiTile,
19       O                       sumPhi,       O                       sumPhi,
20       I                       myThid )       I                       myThid )
21        IMPLICIT NONE  
22  C     !DESCRIPTION:  C     !DESCRIPTION:
23  C     *==========================================================*  C     *==========================================================*
24  C     | SUBROUTINE GLOBAL\_SUM\_TILE\_RL  C     | SUBROUTINE GLOBAL\_SUM\_TILE\_RL
# Line 27  C     |  and operate over all tiles & al Line 29  C     |  and operate over all tiles & al
29  C     *==========================================================*  C     *==========================================================*
30    
31  C     !USES:  C     !USES:
32          IMPLICIT NONE
33    
34  C     == Global data ==  C     == Global data ==
35  #include "SIZE.h"  #include "SIZE.h"
36  #include "EEPARAMS.h"  #include "EEPARAMS.h"
# Line 51  C         all 4 needs to have the same l Line 55  C         all 4 needs to have the same l
55        INTEGER bi,bj        INTEGER bi,bj
56  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
57  #ifdef GLOBAL_SUM_SEND_RECV  #ifdef GLOBAL_SUM_SEND_RECV
58        INTEGER biG, bjG, npe        INTEGER biG, bjG, npe, np1
59        INTEGER lbuff, idest, itag, ready_to_receive        INTEGER lbuff, idest, itag, ready_to_receive
60        INTEGER istatus(MPI_STATUS_SIZE), ierr        INTEGER istatus(MPI_STATUS_SIZE), ierr
61        Real*8  localBuf (nSx,nSy)        Real*8  localBuf (nSx,nSy)
# Line 104  C--   All proceses except 0 receive resu Line 108  C--   All proceses except 0 receive resu
108        ELSE        ELSE
109    
110  C--   Process 0 fills-in its local data  C--   Process 0 fills-in its local data
111          npe = 0          np1 = 1
112          DO bj=1,nSy          DO bj=1,nSy
113            DO bi=1,nSx            DO bi=1,nSx
114              biG = (mpi_myXGlobalLo(npe+1)-1)/sNx+bi              biG = (mpi_myXGlobalLo(np1)-1)/sNx+bi
115              bjG = (mpi_myYGlobalLo(npe+1)-1)/sNy+bj              bjG = (mpi_myYGlobalLo(np1)-1)/sNy+bj
116              globalBuf(biG,bjG) = shareBufGSR8(bi,bj)              globalBuf(biG,bjG) = shareBufGSR8(bi,bj)
117            ENDDO            ENDDO
118          ENDDO          ENDDO
# Line 123  C--   Process 0 polls and receives data Line 127  C--   Process 0 polls and receives data
127       &           npe, itag, MPI_COMM_MODEL, istatus, ierr)       &           npe, itag, MPI_COMM_MODEL, istatus, ierr)
128    
129  C--   Process 0 gathers the local arrays into a global array.  C--   Process 0 gathers the local arrays into a global array.
130              np1 = npe + 1
131            DO bj=1,nSy            DO bj=1,nSy
132             DO bi=1,nSx             DO bi=1,nSx
133              biG = (mpi_myXGlobalLo(npe+1)-1)/sNx+bi              biG = (mpi_myXGlobalLo(np1)-1)/sNx+bi
134              bjG = (mpi_myYGlobalLo(npe+1)-1)/sNy+bj              bjG = (mpi_myYGlobalLo(np1)-1)/sNy+bj
135              globalBuf(biG,bjG) = localBuf(bi,bj)              globalBuf(biG,bjG) = localBuf(bi,bj)
136             ENDDO             ENDDO
137            ENDDO            ENDDO
# Line 177  C      in case MPI is not used: Line 182  C      in case MPI is not used:
182  #endif /* not (GLOBAL_SUM_SEND_RECV & ALLOW_USE_MPI) */  #endif /* not (GLOBAL_SUM_SEND_RECV & ALLOW_USE_MPI) */
183    
184  C--    Write solution to shared buffer (all threads can see it)  C--    Write solution to shared buffer (all threads can see it)
185         shareBufGSR8(1,1) = sumAllP  c      shareBufGSR8(1,1) = sumAllP
186           phiGSR8(1,0) = sumAllP
187    
188        _END_MASTER( myThid )        _END_MASTER( myThid )
189  C--   Everyone wait for Master thread to be ready  C--   Everyone wait for Master thread to be ready
190        CALL BAR2( myThid )        CALL BAR2( myThid )
191    
192  C--   set result for every threads  C--   set result for every threads
193        sumPhi = shareBufGSR8(1,1)  c     sumPhi = shareBufGSR8(1,1)
194          sumPhi = phiGSR8(1,0)
195    
196  C-    Need a barrier here to prevent thread 1 to modify shareBufGSR8(1,1)  C--   A barrier was needed here to prevent thread 1 to modify shareBufGSR8(1,1)
197  C     (as it would in the following call to this S/R) before all threads get  C     (as it would in the following call to this S/R) before all threads get
198  C     their global-sum result out.  C     their global-sum result out.
199        CALL BAR2( myThid )  C     No longer needed since a dedicated shared var. is used to share the output
200    c     CALL BAR2( myThid )
201    
202        RETURN        RETURN
203        END        END

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

  ViewVC Help
Powered by ViewVC 1.1.22