/[MITgcm]/MITgcm/pkg/flt/exch2_recv_get_vec.F
ViewVC logotype

Contents of /MITgcm/pkg/flt/exch2_recv_get_vec.F

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


Revision 1.1 - (show annotations) (download)
Wed Dec 22 21:24:58 2010 UTC (13 years, 4 months ago) by jahn
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
add exch2 support (1 facet only so far)

1 C $Header$
2 C $Name$
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_EEOPTIONS.h"
6 #undef DBUG_EXCH_VEC
7
8 C-- Contents
9 C-- o EXCH2_RL_RECV_GET_VEC
10
11 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
12 CBOP 0
13 C !ROUTINE: EXCH2_RL_RECV_GET_VEC
14
15 C !INTERFACE:
16 SUBROUTINE EXCH2_RL_RECV_GET_VEC(
17 U array,
18 I myd1, myThid )
19 C !DESCRIPTION:
20 C *==========================================================*
21 C | SUBROUTINE EXCH2_RL_RECV_GET_VEC
22 C | o "Receive" or "Get" edges for RL array.
23 C *==========================================================*
24 C | Routine that invokes actual message passing receive
25 C | of data to update buffer
26 C *==========================================================*
27
28 C !USES:
29 IMPLICIT NONE
30
31 C == Global variables ==
32 #include "SIZE.h"
33 #include "EEPARAMS.h"
34 #include "EESUPPORT.h"
35 #ifdef ALLOW_EXCH2
36 #include "W2_EXCH2_SIZE.h"
37 #include "W2_EXCH2_TOPOLOGY.h"
38 #include "W2_EXCH2_BUFFER.h"
39 #endif
40
41 C !INPUT/OUTPUT PARAMETERS:
42 C arrayE :: buffer array to collect Eastern Neighbour values
43 C arrayW :: buffer array to collect Western Neighbour values
44 C myd1 :: size
45 C myThid :: my Thread Id. number
46 INTEGER myd1
47 _RL array(myd1, nSx, nSy, 4)
48 INTEGER myThid
49 CEOP
50
51 #ifdef ALLOW_EXCH2
52
53 C !LOCAL VARIABLES:
54 C bi, bj :: tile indices
55 C theProc :: Variables used in message building
56 C theTag :: Variables used in message building
57 C theType :: Variables used in message building
58 C theSize :: Variables used in message building
59 INTEGER bi, bj
60 INTEGER spinCount
61 INTEGER ioUnit
62 INTEGER thisTile, nN, tgT, oNb, dir
63 #ifdef ALLOW_USE_MPI
64 INTEGER theProc, theTag, theType, theSize
65 INTEGER mpiStatus(MPI_STATUS_SIZE,4), mpiRc
66 #endif
67
68 C-- Under a "put" scenario we
69 C-- i. set completetion signal for buffer we put into.
70 C-- ii. wait for completetion signal indicating data has been put in
71 C-- our buffer.
72 C-- Under a messaging mode we "receive" the message.
73 C-- Under a "get" scenario <= not implemented, we
74 C-- i. Check that the data is ready.
75 C-- ii. Read the data.
76 C-- iii. Set data read flag + memory sync.
77
78 ioUnit = errorMessageUnit
79
80 DO bj=myByLo(myThid),myByHi(myThid)
81 DO bi=myBxLo(myThid),myBxHi(myThid)
82
83 thisTile = W2_myTileList(bi,bj)
84
85 C- loop over neighboring tiles
86 DO nN=1,exch2_nNeighbours(thisTile)
87
88 tgT = exch2_neighbourId(nN, thisTile )
89 oNb = exch2_opposingSend(nN, thisTile )
90 dir = exch2_neighbourDir(nN,thisTile)
91
92 #ifdef DBUG_EXCH_VEC
93 write(ioUnit,'(A,5I6)') 'RECV,0 :',myProcId,bi,bj
94 #endif
95 IF ( W2_myCommFlag(nN,bi,bj) .EQ. 'M' ) THEN
96 #ifdef ALLOW_USE_MPI
97 #ifndef ALWAYS_USE_MPI
98 IF ( usingMPI ) THEN
99 #endif
100 theProc = exch2_tProc(tgT) - 1
101 theTag = (tgT-1)*W2_maxNeighbours + oNb
102 theSize = myd1
103 theType = _MPI_TYPE_RL
104 #ifdef DBUG_EXCH_VEC
105 write(ioUnit,'(A,5I5,I8)') 'qq2xW: ',myProcId,bi,bj,
106 & theProc,theTag,theSize
107 #endif
108 CALL MPI_Recv( array(1,bi,bj,dir), theSize, theType,
109 & theProc, theTag, MPI_COMM_MODEL,
110 & mpiStatus, mpiRc )
111 #ifndef ALWAYS_USE_MPI
112 ENDIF
113 #endif
114 #endif /* ALLOW_USE_MPI */
115 ENDIF
116 #ifdef DBUG_EXCH_VEC
117 write(ioUnit,'(A,5I6)') 'RECV,1 :',myProcId,bi,bj
118 #endif
119 C- nN
120 ENDDO
121 C- bj,bi
122 ENDDO
123 ENDDO
124 #ifdef DBUG_EXCH_VEC
125 write(ioUnit,'(A,5I6,I12)') 'RECV:',myProcId
126 #endif
127
128 #endif /* ALLOW_EXCH2 */
129
130 RETURN
131 END

  ViewVC Help
Powered by ViewVC 1.1.22