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

Contents of /MITgcm/pkg/exch2/exch2_send_rx1_ad.template

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


Revision 1.6 - (show annotations) (download)
Sat May 30 21:18:59 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: HEAD
Changes since 1.5: +1 -1 lines
FILE REMOVED
take buffer copy from/to array out of S/R exch2_send/recv into new
 S/R exch2_put/get ; adjoint of send/recv no longer needed.

1 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_send_rx1_ad.template,v 1.5 2009/05/20 21:01:45 jmc Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5 #include "W2_OPTIONS.h"
6
7 SUBROUTINE EXCH2_SEND_RX1_AD(
8 I tIlo, tIhi, tiStride,
9 I tJlo, tJhi, tjStride,
10 I tKlo, tKhi, tkStride,
11 I thisTile, nN,
12 I e2Bufr1_RX, e2BufrRecSize,
13 I array,
14 I i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,
15 O e2_msgHandle,
16 I commSetting, myThid )
17
18 IMPLICIT NONE
19
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "EESUPPORT.h"
23 #include "W2_EXCH2_SIZE.h"
24 #include "W2_EXCH2_TOPOLOGY.h"
25
26 C === Routine arguments ===
27 INTEGER tILo, tIHi, tiStride
28 INTEGER tJLo, tJHi, tjStride
29 INTEGER tKLo, tKHi, tkStride
30 INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi
31 INTEGER thisTile, nN
32 INTEGER e2BufrRecSize
33 _RX e2Bufr1_RX( e2BufrRecSize )
34 _RX array(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)
35 INTEGER e2_msgHandle(1)
36 INTEGER myThid
37 CHARACTER commSetting
38
39 C == Local variables ==
40 C itl, jtl, ktl :: Loop counters
41 C :: itl etc... target local
42 C :: itc etc... target canonical
43 C :: isl etc... source local
44 C :: isc etc... source canonical
45 INTEGER itl, jtl, ktl
46 INTEGER itc, jtc
47 INTEGER isc, jsc
48 INTEGER isl, jsl
49 c INTEGER ktc, ksc, ksl
50 C tt :: Target tile
51 C itb, jtb :: Target local to canonical offsets
52 C
53 INTEGER tt
54 INTEGER itb, jtb
55 INTEGER isb, jsb
56 INTEGER pi(2), pj(2), oi, oj
57 INTEGER iBufr
58
59 C MPI setup
60 #ifdef ALLOW_USE_MPI
61 INTEGER theTag, theType
62 INTEGER sProc, tProc, mpiRc
63 INTEGER mpiStatus(MPI_STATUS_SIZE)
64 #endif
65 #ifdef W2_E2_DEBUG_ON
66 CHARACTER*(MAX_LEN_MBUF) messageBuffer
67 #endif
68
69 IF ( commSetting .EQ. 'P' ) THEN
70 C Need to check that buffer synchronisation token is decremented
71 C before filling buffer.
72 ENDIF
73
74 tt=exch2_neighbourId(nN, thisTile )
75 itb=exch2_tBasex(tt)
76 jtb=exch2_tBasey(tt)
77 isb=exch2_tBasex(thisTile)
78 jsb=exch2_tBasey(thisTile)
79 pi(1)=exch2_pij(1,nN,thisTile)
80 pi(2)=exch2_pij(2,nN,thisTile)
81 pj(1)=exch2_pij(3,nN,thisTile)
82 pj(2)=exch2_pij(4,nN,thisTile)
83 oi=exch2_oi(nN,thisTile)
84 oj=exch2_oj(nN,thisTile)
85 #ifdef W2_E2_DEBUG_ON
86 WRITE(messageBuffer,'(A,I4,A,I4)')
87 & 'EXCH2_SEND_RX1_AD sourceTile= ',
88 & thisTile,
89 & 'targetTile= ',tt
90 CALL PRINT_MESSAGE(messageBuffer,
91 I standardMessageUnit,SQUEEZE_BOTH,
92 I myThid)
93 #endif /* W2_E2_DEBUG_ON */
94
95 iBufr=0
96 DO ktl=tKlo,tKhi,tKStride
97 DO jtl=tJLo, tJHi, tjStride
98 DO itl=tILo, tIHi, tiStride
99 iBufr=iBufr+1
100 ENDDO
101 ENDDO
102 ENDDO
103
104 C Do data transport depending on communication mechanism between source and target tile
105 IF ( commSetting .EQ. 'P' ) THEN
106 C Need to set data ready assertion (increment buffer synchronisation token)
107 C for multithreaded mode, for now do nothing i.e. assume only one thread per process.
108 ELSEIF ( commSetting .EQ. 'M' ) THEN
109 #ifdef ALLOW_USE_MPI
110 C Setup MPI stuff here
111 theTag = (thisTile-1)*W2_maxNeighbours + nN
112 tProc = exch2_tProc(tt)-1
113 sProc = exch2_tProc(thisTile)-1
114 theType = _MPI_TYPE_RX
115 #ifdef W2_E2_DEBUG_ON
116 WRITE(messageBuffer,'(A,I4,A,I4,A)') ' SEND FROM TILE=', thisTile,
117 & ' (proc = ',sProc,')'
118 CALL PRINT_MESSAGE(messageBuffer,
119 I standardMessageUnit,SQUEEZE_RIGHT,
120 I myThid)
121 WRITE(messageBuffer,'(A,I4,A,I4,A)') ' TO TILE=', tt,
122 & ' (proc = ',tProc,')'
123 CALL PRINT_MESSAGE(messageBuffer,
124 I standardMessageUnit,SQUEEZE_RIGHT,
125 I myThid)
126 WRITE(messageBuffer,'(A,I10)') ' TAG=', theTag
127 CALL PRINT_MESSAGE(messageBuffer,
128 I standardMessageUnit,SQUEEZE_RIGHT,
129 I myThid)
130 WRITE(messageBuffer,'(A,I4)') ' NEL=', iBufr
131 CALL PRINT_MESSAGE(messageBuffer,
132 I standardMessageUnit,SQUEEZE_RIGHT,
133 I myThid)
134 #endif /* W2_E2_DEBUG_ON */
135 CALL MPI_Recv( e2Bufr1_RX, iBufr, theType,
136 I tProc, theTag, MPI_COMM_MODEL,
137 O mpiStatus, mpiRc )
138 #endif
139 ELSE
140 STOP 'EXCH2_SEND_RX1_AD:: commSetting VALUE IS INVALID'
141 ENDIF
142
143 iBufr=0
144 DO ktl=tKlo,tKhi,tKStride
145 DO jtl=tJLo, tJHi, tjStride
146 DO itl=tILo, tIHi, tiStride
147 iBufr=iBufr+1
148 itc=itl+itb
149 jtc=jtl+jtb
150 isc=pi(1)*itc+pi(2)*jtc+oi
151 jsc=pj(1)*itc+pj(2)*jtc+oj
152 isl=isc-isb
153 jsl=jsc-jsb
154 array(isl,jsl,ktl) = array(isl,jsl,ktl) + e2Bufr1_RX(iBufr)
155 e2Bufr1_RX(iBufr) = 0. _d 0
156 ENDDO
157 ENDDO
158 ENDDO
159
160 RETURN
161 END
162
163 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
164
165 CEH3 ;;; Local Variables: ***
166 CEH3 ;;; mode:fortran ***
167 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22