/[MITgcm]/MITgcm/pkg/exch2/exch2_get_rx1.template
ViewVC logotype

Annotation of /MITgcm/pkg/exch2/exch2_get_rx1.template

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


Revision 1.2 - (hide annotations) (download)
Sun Jun 28 01:00:23 2009 UTC (14 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62e, checkpoint62d, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.1: +2 -2 lines
add bj in exch2 arrays and S/R.

1 jmc 1.2 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_get_rx1.template,v 1.1 2009/05/30 21:18:59 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5     #include "W2_OPTIONS.h"
6    
7     CBOP 0
8     C !ROUTINE: EXCH2_GET_RX1
9    
10     C !INTERFACE:
11     SUBROUTINE EXCH2_GET_RX1(
12     I tIlo, tIhi, tiStride,
13     I tJlo, tJhi, tjStride,
14     I tKlo, tKhi, tkStride,
15     I thisTile, nN, bi, bj,
16     I e2BufrRecSize, sizeNb, sizeBi, sizeBj,
17     I e2Bufr1_RX,
18     U array,
19     I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
20     U e2_msgHandles,
21     I commSetting, myThid )
22    
23     C !DESCRIPTION:
24     C Scalar field (1 component) Exchange:
25     C Get from buffer exchanged data to fill in this tile-egde overlap region.
26    
27     C !USES:
28     IMPLICIT NONE
29    
30     #include "SIZE.h"
31     #include "EEPARAMS.h"
32     #include "W2_EXCH2_SIZE.h"
33     #include "W2_EXCH2_TOPOLOGY.h"
34    
35     C !INPUT/OUTPUT PARAMETERS:
36     C === Routine arguments ===
37     C tIlo,tIhi :: index range in I that will be filled in target "array"
38     C tIstride :: index step in I that will be filled in target "array"
39     C tJlo,tJhi :: index range in J that will be filled in target "array"
40     C tJstride :: index step in J that will be filled in target "array"
41     C tKlo,tKhi :: index range in K that will be filled in target "array"
42     C tKstride :: index step in K that will be filled in target "array"
43     C thisTile :: receiveing tile Id. number
44     C bi,bj :: Indices of the receiving tile within this process
45     C :: (used to select buffer slots that are allowed).
46     C nN :: Neighbour entry that we are processing
47     C e2BufrRecSize :: Number of elements in each entry of e2Bufr1_RX
48     C sizeNb :: Second dimension of e2Bufr1_RX
49     C sizeBi :: Third dimension of e2Bufr1_RX
50     C sizeBj :: Fourth dimension of e2Bufr1_RX
51     C e2Bufr1_RX :: Data transport buffer array. This array is used in one of
52     C :: two ways. For PUT communication the entry in the buffer
53     C :: associated with the source for this receive (determined
54     C :: from the opposing_send index) is read.
55     C :: For MSG communication the entry in the buffer associated
56     C :: with this neighbor of this tile is used as a receive
57     C :: location for loading a linear stream of bytes.
58     C array :: Target array that this receive writes to.
59     C i1Lo, i1Hi :: I coordinate bounds of target array
60     C j1Lo, j1Hi :: J coordinate bounds of target array
61     C k1Lo, k1Hi :: K coordinate bounds of target array
62     C e2_msgHandles :: Synchronization and coordination data structure used to
63     C :: coordinate access to e2Bufr1_RX or to regulate message
64     C :: buffering. In PUT communication sender will increment
65     C :: handle entry once data is ready in buffer. Receiver will
66     C :: decrement handle once data is consumed from buffer.
67     C :: For MPI MSG communication MPI_Wait uses hanlde to check
68     C :: Isend has cleared. This is done in routine after receives.
69     C commSetting :: Mode of communication used to exchange with this neighbor
70     C myThid :: my Thread Id. number
71    
72     INTEGER tILo, tIHi, tiStride
73     INTEGER tJLo, tJHi, tjStride
74     INTEGER tKLo, tKHi, tkStride
75     INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
76     INTEGER thisTile, nN, bi, bj
77     INTEGER e2BufrRecSize, sizeNb, sizeBi, sizeBj
78     _RX e2Bufr1_RX( e2BufrRecSize, sizeNb, sizeBi, sizeBj, 2 )
79     _RX array(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
80     INTEGER e2_msgHandles( 2, sizeNb, sizeBi, sizeBj )
81     CHARACTER commSetting
82     INTEGER myThid
83     CEOP
84    
85     C !LOCAL VARIABLES:
86     C == Local variables ==
87     C itl,jtl,ktl :: Loop counters (this tile)
88     C soT :: Source tile Id number
89     C oNb :: Opposing send record number
90     C iBufr :: Buffer counter
91     C sNb :: buffer (source) Neibour index to get data from
92     C sBi :: buffer (source) Tile index (for this Proc) to get data from
93     C sBj :: buffer (source) Tile index (for this Proc) to get data from
94     C sLv :: buffer (source) level index to get data from
95     C i,j :: Loop counters
96     INTEGER itl, jtl, ktl
97     INTEGER soT
98     INTEGER oNb
99     INTEGER iBufr
100     INTEGER sNb, sBi, sBj, sLv
101     INTEGER i,j
102     c CHARACTER*(MAX_LEN_MBUF) msgBuf
103    
104     soT = exch2_neighbourId( nN, thisTile )
105     oNb = exch2_opposingSend(nN, thisTile )
106    
107     C Handle receive end data transport according to communication mechanism
108     C between source and target tile
109     IF ( commSetting .EQ. 'P' ) THEN
110     C 1 Need to check and spin on data ready assertion for multithreaded mode,
111     C for now, ensure global sync using barrier.
112     C 2 get directly data from 1rst level buffer (sLv=1);
113    
114     C find the tile indices (local to this Proc) corresponding to
115     C this source tile Id "soT"
116     sLv = 1
117     sNb = oNb
118     DO j=1,sizeBj
119     DO i=1,sizeBi
120 jmc 1.2 IF ( W2_myTileList(i,j).EQ.soT ) THEN
121 jmc 1.1 sBi = i
122     sBj = j
123     ENDIF
124     ENDDO
125     ENDDO
126     #ifdef ALLOW_USE_MPI
127     ELSEIF ( commSetting .EQ. 'M' ) THEN
128     sLv = 2
129     sBi = bi
130     sBj = bj
131     sNb = nN
132     #endif /* ALLOW_USE_MPI */
133     ELSE
134     STOP 'EXCH2_GET_RX1:: commSetting VALUE IS INVALID'
135     ENDIF
136    
137     iBufr = 0
138     DO ktl=tKlo,tKhi,tKStride
139     DO jtl=tJLo, tJHi, tjStride
140     DO itl=tILo, tIHi, tiStride
141     C Read from e2Bufr1_RX(iBufr,sNb,sBi,sBj,sLv)
142     iBufr = iBufr+1
143     array(itl,jtl,ktl) = e2Bufr1_RX(iBufr,sNb,sBi,sBj,sLv)
144     ENDDO
145     ENDDO
146     ENDDO
147    
148     RETURN
149     END
150    
151     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
152    
153     CEH3 ;;; Local Variables: ***
154     CEH3 ;;; mode:fortran ***
155     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22