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

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

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

revision 1.1 by dimitri, Wed Feb 5 07:12:59 2003 UTC revision 1.2 by dimitri, Tue Feb 18 05:33:53 2003 UTC
# Line 0  Line 1 
1    #include "CPP_OPTIONS.h"
2    
3          SUBROUTINE SCATTER_2D( global, local, myThid )
4    C     Scatter elements of a 2-D array from mpi process 0 to all processes.
5          IMPLICIT NONE
6    #include "SIZE.h"
7    #include "EEPARAMS.h"
8    #include "EESUPPORT.h"
9    C     mythid - thread number for this instance of the routine.
10    C     global,local - working arrays used to transfer 2-D fields
11          INTEGER mythid
12          Real*8  global(Nx,Ny)
13          _RL     local(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
14    
15    #ifdef ALLOW_USE_MPI
16          COMMON /GlobalLo/ mpi_myXGlobalLo, mpi_myYGlobalLo
17          INTEGER mpi_myXGlobalLo(nPx*nPy)
18          INTEGER mpi_myYGlobalLo(nPx*nPy)
19    
20          _RL     temp(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
21          INTEGER istatus(MPI_STATUS_SIZE), ierr
22          INTEGER isource, itag, npe
23          INTEGER iP, jP, iG,jG, i, j, bi, bj, lbuff
24    
25    C--   Make everyone wait except for master thread.
26          _BARRIER
27          _BEGIN_MASTER( myThid )
28          lbuff=(sNx+2*OLx)*nSx*(sNy+2*OLy)*nSy
29          isource = 0
30          itag = 0
31    
32          IF( mpiMyId .EQ. 0 ) THEN
33    
34    C--   Process 0 fills-in its local data
35             npe = 0
36             DO bj=1,nSy
37                DO bi=1,nSx
38                   DO j=1,sNy
39                      DO i=1,sNx
40                         iP = (bi-1)*sNx+i
41                         jP = (bj-1)*sNy+j
42                         iG = mpi_myXGlobalLo(npe+1)-1+(bi-1)*sNx+i
43                         jG = mpi_myYGlobalLo(npe+1)-1+(bj-1)*sNy+j
44                         local(i,j,bi,bj) = global(iG,jG)
45                      ENDDO
46                   ENDDO
47                ENDDO
48             ENDDO
49    
50    C--   Process 0 sends local arrays to all other processes
51             DO npe = 1, numberOfProcs-1
52                DO bj=1,nSy
53                   DO bi=1,nSx
54                      DO j=1,sNy
55                         DO i=1,sNx
56                            iP = (bi-1)*sNx+i
57                            jP = (bj-1)*sNy+j
58                            iG = mpi_myXGlobalLo(npe+1)-1+(bi-1)*sNx+i
59                            jG = mpi_myYGlobalLo(npe+1)-1+(bj-1)*sNy+j
60                            temp(i,j,bi,bj) = global(iG,jG)
61                         ENDDO
62                      ENDDO
63                   ENDDO
64                ENDDO
65                CALL MPI_SEND (temp, lbuff, MPI_DOUBLE_PRECISION,
66         &           npe, itag, MPI_COMM_MODEL, ierr)
67             ENDDO
68    
69          ELSE
70    
71    C--   All proceses except 0 receive local array from process 0
72             CALL MPI_RECV (local, lbuff, MPI_DOUBLE_PRECISION,
73         &        isource, itag, MPI_COMM_MODEL, istatus, ierr)
74    
75          ENDIF
76    
77          _END_MASTER( myThid )
78          _BARRIER
79    
80    C--   Fill in edges.
81          _EXCH_XY_R8( local, myThid )
82    
83    #endif /* ALLOW_USE_MPI */
84          RETURN
85          END

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

  ViewVC Help
Powered by ViewVC 1.1.22