/[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.4 - (show annotations) (download)
Wed Oct 2 23:31:28 2013 UTC (10 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint65, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e
Changes since 1.3: +1 -2 lines
remove unused variable

1 C $Header: /u/gcmpack/MITgcm/pkg/flt/exch2_recv_get_vec.F,v 1.3 2012/09/06 16:17:21 jmc Exp $
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_RECV_GET_VEC_RL
10
11 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
12 CBOP 0
13 C !ROUTINE: EXCH2_RECV_GET_VEC_RL
14
15 C !INTERFACE:
16 SUBROUTINE EXCH2_RECV_GET_VEC_RL(
17 U array,
18 I theHandle,
19 I myd1, myThid )
20 C !DESCRIPTION:
21 C *==========================================================*
22 C | SUBROUTINE EXCH2_RECV_GET_VEC_RL
23 C | o "Receive" edges for RL array.
24 C *==========================================================*
25 C | Routine that invokes actual message passing receive
26 C | of data to update buffer
27 C *==========================================================*
28
29 C !USES:
30 IMPLICIT NONE
31
32 C == Global variables ==
33 #include "SIZE.h"
34 #include "EEPARAMS.h"
35 #include "EESUPPORT.h"
36 #ifdef ALLOW_EXCH2
37 #include "W2_EXCH2_SIZE.h"
38 #include "W2_EXCH2_TOPOLOGY.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 #ifdef ALLOW_EXCH2
49 INTEGER theHandle(2,W2_maxNeighbours,nSx,nSy)
50 #else
51 INTEGER theHandle
52 #endif
53 INTEGER myThid
54 CEOP
55
56 #ifdef ALLOW_EXCH2
57 #ifdef ALLOW_USE_MPI
58 C !LOCAL VARIABLES:
59 C bi, bj :: tile indices
60 C theProc :: Variables used in message building
61 C theTag :: Variables used in message building
62 C theType :: Variables used in message building
63 C theSize :: Variables used in message building
64 INTEGER bi, bj
65 INTEGER ioUnit
66 INTEGER thisTile, nN, tgT, oNb, dir
67 INTEGER theProc, theTag, theType, theSize
68 INTEGER wHandle
69 INTEGER mpiStatus(MPI_STATUS_SIZE,4), mpiRc
70
71 C-- Under a "put" scenario we
72 C-- i. set completetion signal for buffer we put into.
73 C-- ii. wait for completetion signal indicating data has been put in
74 C-- our buffer.
75 C-- Under a messaging mode we "receive" the message.
76 C-- Under a "get" scenario <= not implemented, we
77 C-- i. Check that the data is ready.
78 C-- ii. Read the data.
79 C-- iii. Set data read flag + memory sync.
80
81 ioUnit = errorMessageUnit
82
83 _BEGIN_MASTER(myThid)
84
85 DO bj=1,nSy
86 DO bi=1,nSx
87 thisTile = W2_myTileList(bi,bj)
88
89 C- loop over neighboring tiles
90 DO nN=1,exch2_nNeighbours(thisTile)
91
92 tgT = exch2_neighbourId(nN, thisTile )
93 oNb = exch2_opposingSend(nN, thisTile )
94 dir = exch2_neighbourDir(nN,thisTile)
95
96 #ifdef DBUG_EXCH_VEC
97 write(ioUnit,'(A,5I6)') 'RECV,0 :',myProcId,bi,bj
98 #endif
99 IF ( W2_myCommFlag(nN,bi,bj) .EQ. 'M' ) THEN
100 theProc = W2_tileProc(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 ENDIF
112 #ifdef DBUG_EXCH_VEC
113 write(ioUnit,'(A,5I6)') 'RECV,1 :',myProcId,bi,bj
114 #endif
115 C- nN
116 ENDDO
117 C- bj,bi
118 ENDDO
119 ENDDO
120 #ifdef DBUG_EXCH_VEC
121 write(ioUnit,'(A,5I6,I12)') 'RECV:',myProcId
122 #endif
123
124 C-- Clear message handles/locks
125 DO bj=1,nSy
126 DO bi=1,nSx
127 thisTile = W2_myTileList(bi,bj)
128 DO nN=1,exch2_nNeighbours(thisTile)
129 c tgT = exch2_neighbourId(nN, thisTile )
130
131 C- Note: In a between process tile-tile data transport using
132 C MPI the sender needs to clear an Isend wait handle here.
133 C In a within process tile-tile data transport using true
134 C shared address space/or direct transfer through commonly
135 C addressable memory blocks the receiver needs to assert
136 C that he has consumed the buffer the sender filled here.
137 IF ( W2_myCommFlag(nN,bi,bj) .EQ. 'M' ) THEN
138 wHandle = theHandle(1,nN,bi,bj)
139 CALL MPI_Wait( wHandle, mpiStatus, mpiRc )
140 ENDIF
141
142 ENDDO
143 ENDDO
144 ENDDO
145
146 _END_MASTER(myThid)
147
148 C-- need to sync threads after master has received data
149 _BARRIER
150
151 #endif /* ALLOW_USE_MPI */
152 #endif /* ALLOW_EXCH2 */
153
154 RETURN
155 END

  ViewVC Help
Powered by ViewVC 1.1.22