/[MITgcm]/MITgcm/eesupp/src/gather_2d_rx.template
ViewVC logotype

Diff of /MITgcm/eesupp/src/gather_2d_rx.template

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

revision 1.1 by jmc, Mon May 11 02:13:29 2009 UTC revision 1.5 by jmc, Mon Jun 8 03:34:03 2009 UTC
# Line 11  C !INTERFACE: Line 11  C !INTERFACE:
11       O                  gloBuff,       O                  gloBuff,
12       I                  myField,       I                  myField,
13       I                  xSize, ySize,       I                  xSize, ySize,
14       I                  keepBlankTileIO,       I                  useExch2GlobLayOut,
15       I                  zeroBuff,       I                  zeroBuff,
16       I                  myThid )       I                  myThid )
17  C !DESCRIPTION:  C !DESCRIPTION:
18  C     Gather elements of a global 2-D array from all mpi processes to process 0.  C     Gather elements of a global 2-D array from all mpi processes to process 0.
19    C     Note: done by Master-Thread ; might need barrier calls before and after
20    C           this S/R call.
21    
22  C     !USES:  C     !USES:
23        IMPLICIT NONE        IMPLICIT NONE
# Line 23  C     !USES: Line 25  C     !USES:
25  #include "EEPARAMS.h"  #include "EEPARAMS.h"
26  #include "EESUPPORT.h"  #include "EESUPPORT.h"
27  #ifdef ALLOW_EXCH2  #ifdef ALLOW_EXCH2
28    #include "W2_EXCH2_SIZE.h"
29  #include "W2_EXCH2_TOPOLOGY.h"  #include "W2_EXCH2_TOPOLOGY.h"
 #include "W2_EXCH2_PARAMS.h"  
30  #endif /* ALLOW_EXCH2 */  #endif /* ALLOW_EXCH2 */
31    
32  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
# Line 32  C gloBuff   ( _RX ) :: full-domain 2D IO Line 34  C gloBuff   ( _RX ) :: full-domain 2D IO
34  C myField   ( _RX ) :: tiled, local (i.e. my Proc. tiles) 2D array (Input)  C myField   ( _RX ) :: tiled, local (i.e. my Proc. tiles) 2D array (Input)
35  C xSize    (integer):: global buffer 1rst dim (x)  C xSize    (integer):: global buffer 1rst dim (x)
36  C ySize    (integer):: global buffer 2nd  dim (y)  C ySize    (integer):: global buffer 2nd  dim (y)
37  C keepBlankTileIO   :: =T: keep blank-tiles in global IO (only with EXCH2)  C useExch2GlobLayOut:: =T: Use Exch2 global-map layout (only with EXCH2)
38  C zeroBuff (logical):: =T: initialise the buffer to zero before copy  C zeroBuff (logical):: =T: initialise the buffer to zero before copy
39  C myThid   (integer):: my Thread Id number  C myThid   (integer):: my Thread Id number
40    
41        INTEGER xSize, ySize        INTEGER xSize, ySize
42        _RX     gloBuff(xSize,ySize)        _RX     gloBuff(xSize,ySize)
43        _RX     myField(1:sNx,1:sNy,nSx,nSy)        _RX     myField(1:sNx,1:sNy,nSx,nSy)
44        LOGICAL keepBlankTileIO        LOGICAL useExch2GlobLayOut
45        LOGICAL zeroBuff        LOGICAL zeroBuff
46        INTEGER myThid        INTEGER myThid
47  CEOP  CEOP
# Line 59  C !LOCAL VARIABLES: Line 61  C !LOCAL VARIABLES:
61        INTEGER lbuff, idest, itag, ready_to_receive        INTEGER lbuff, idest, itag, ready_to_receive
62  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
63    
 C--   Make everyone wait except for master thread.  
       _BARRIER  
64        _BEGIN_MASTER( myThid )        _BEGIN_MASTER( myThid )
65    
66        IF( myProcId .EQ. 0 ) THEN        IF( myProcId .EQ. 0 ) THEN
67  C--   Process 0 fills-in its local data  C--   Process 0 fills-in its local data
68    
69  #ifdef ALLOW_EXCH2  #ifdef ALLOW_EXCH2
70          IF ( keepBlankTileIO ) THEN          IF ( useExch2GlobLayOut ) THEN
71  C--   If using blank-tiles, buffer will not be completely filled;  C--   If using blank-tiles, buffer will not be completely filled;
72  C     safer to reset to zero to avoid unknown values in output file  C     safer to reset to zero to avoid unknown values in output file
73            IF ( zeroBuff ) THEN            IF ( zeroBuff ) THEN
# Line 115  c         ENDDO Line 115  c         ENDDO
115          IF (.TRUE.) THEN          IF (.TRUE.) THEN
116  #endif /* ALLOW_EXCH2 */  #endif /* ALLOW_EXCH2 */
117    
118            iBase = 0            iBase = myXGlobalLo-1
119            jBase = 0            jBase = myYGlobalLo-1
 c         iBase = myXGlobalLo-1  
 c         jBase = myYGlobalLo-1  
120    
121            DO bj=1,nSy            DO bj=1,nSy
122             DO bi=1,nSx             DO bi=1,nSx
# Line 135  c         jBase = myYGlobalLo-1 Line 133  c         jBase = myYGlobalLo-1
133             ENDDO             ENDDO
134            ENDDO            ENDDO
135    
136  C       end if-else keepBlankTileIO  C       end if-else useExch2GlobLayOut
137          ENDIF          ENDIF
138    
139  C-    end if myProcId = 0  C-    end if myProcId = 0
# Line 162  C--   Process 0 polls and receives data Line 160  C--   Process 0 polls and receives data
160    
161  C--   Process 0 gathers the local arrays into the global buffer.  C--   Process 0 gathers the local arrays into the global buffer.
162  #ifdef ALLOW_EXCH2  #ifdef ALLOW_EXCH2
163           IF ( keepBlankTileIO ) THEN           IF ( useExch2GlobLayOut ) THEN
164    
165  c         DO bj=1,nSy  c         DO bj=1,nSy
166            bj=1            bj=1
167             DO bi=1,nSx             DO bi=1,nSx
168               tN = W2_mpi_myTileList(np,bi)               tN = W2_procTileList(bi,np)
169               IF   ( exch2_mydNx(tN) .GT. xSize ) THEN               IF   ( exch2_mydNx(tN) .GT. xSize ) THEN
170  C-           face x-size larger than glob-size : fold it  C-           face x-size larger than glob-size : fold it
171                 iGjLoc = 0                 iGjLoc = 0
# Line 201  c         ENDDO Line 199  c         ENDDO
199           IF (.TRUE.) THEN           IF (.TRUE.) THEN
200  #endif /* ALLOW_EXCH2 */  #endif /* ALLOW_EXCH2 */
201    
202            iBase = MOD(np0,nPx)            iBase = mpi_myXGlobalLo(np)-1
203            jBase = np0/nPx            jBase = mpi_myYGlobalLo(np)-1
           iBase = iBase*nSx*sNx  
           jBase = jBase*nSy*sNy  
 c         iBase = mpi_myXGlobalLo(np)-1  
 c         jBase = mpi_myYGlobalLo(np)-1  
204    
205            DO bj=1,nSy            DO bj=1,nSy
206             DO bi=1,nSx             DO bi=1,nSx
# Line 223  c         jBase = mpi_myYGlobalLo(np)-1 Line 217  c         jBase = mpi_myYGlobalLo(np)-1
217             ENDDO             ENDDO
218            ENDDO            ENDDO
219    
220  C        end if-else keepBlankTileIO  C        end if-else useExch2GlobLayOut
221           ENDIF           ENDIF
222    
223  C-      end loop on np  C-      end loop on np
# Line 244  C--   All proceses except 0 wait to be p Line 238  C--   All proceses except 0 wait to be p
238  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
239    
240        _END_MASTER( myThid )        _END_MASTER( myThid )
       _BARRIER  
241    
242        RETURN        RETURN
243        END        END

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.5

  ViewVC Help
Powered by ViewVC 1.1.22