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

Annotation of /MITgcm/eesupp/src/scatter_xz.F

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


Revision 1.1 - (hide annotations) (download)
Wed Jun 7 21:29:15 2006 UTC (17 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint58r_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58q_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59, checkpoint58i_post, checkpoint58o_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58m_post
Support routines for sliced useSingleCpuIO
with fixes by M. Mazloff

1 heimbach 1.1 #include "CPP_OPTIONS.h"
2    
3     SUBROUTINE SCATTER_XZ( global, local, myThid )
4     C Scatter elements of a x-z 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)
13     _RL local(1-OLx:sNx+OLx,nSx,nSy)
14    
15     INTEGER iG, i, bi, bj
16     #ifdef ALLOW_USE_MPI
17    
18     _RL temp(1-OLx:sNx+OLx,nSx,nSy)
19    
20     INTEGER istatus(MPI_STATUS_SIZE), ierr
21     INTEGER isource, itag, npe
22     INTEGER lbuff
23     #endif /* ALLOW_USE_MPI */
24    
25     C-- Make everyone wait except for master thread.
26     _BARRIER
27     _BEGIN_MASTER( myThid )
28    
29     #ifndef ALLOW_USE_MPI
30    
31     DO bj=1,nSy
32     DO bi=1,nSx
33     DO i=1,sNx
34     iG = myXGlobalLo-1+(bi-1)*sNx+i
35     local(i,bi,bj) = global(iG)
36     ENDDO
37     ENDDO
38     ENDDO
39    
40     #else /* ALLOW_USE_MPI */
41    
42     lbuff=(sNx+2*OLx)*nSx*nSy
43     isource = 0
44     itag = 0
45    
46     IF( mpiMyId .EQ. 0 ) THEN
47    
48     C-- Process 0 fills-in its local data
49     npe = 0
50     DO bj=1,nSy
51     DO bi=1,nSx
52     DO i=1,sNx
53     iG = mpi_myXGlobalLo(npe+1)-1+(bi-1)*sNx+i
54     local(i,bi,bj) = global(iG)
55     ENDDO
56     ENDDO
57     ENDDO
58    
59     C-- Process 0 sends local arrays to all other processes
60     DO npe = 1, numberOfProcs-1
61     DO bj=1,nSy
62     DO bi=1,nSx
63     DO i=1,sNx
64     iG = mpi_myXGlobalLo(npe+1)-1+(bi-1)*sNx+i
65     temp(i,bi,bj) = global(iG)
66     ENDDO
67     ENDDO
68     ENDDO
69     CALL MPI_SEND (temp, lbuff, MPI_DOUBLE_PRECISION,
70     & npe, itag, MPI_COMM_MODEL, ierr)
71     ENDDO
72    
73     ELSE
74    
75     C-- All proceses except 0 receive local array from process 0
76     CALL MPI_RECV (local, lbuff, MPI_DOUBLE_PRECISION,
77     & isource, itag, MPI_COMM_MODEL, istatus, ierr)
78    
79     ENDIF
80    
81     #endif /* ALLOW_USE_MPI */
82    
83     _END_MASTER( myThid )
84     _BARRIER
85    
86     C-- Fill in edges.
87     CMM _EXCH_XY_R8( local, myThid )
88    
89     RETURN
90     END

  ViewVC Help
Powered by ViewVC 1.1.22