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

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

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


Revision 1.11 - (show annotations) (download)
Sat May 30 21:18:59 2009 UTC (14 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62e, checkpoint62d, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.10: +78 -341 lines
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_rx2.template,v 1.10 2009/05/20 21:01:45 jmc Exp $
2 C $Name: $
3
4 #include "CPP_EEOPTIONS.h"
5 #include "W2_OPTIONS.h"
6
7 CBOP 0
8 C !ROUTINE: EXCH2_SEND_RX2
9
10 C !INTERFACE:
11 SUBROUTINE EXCH2_SEND_RX2 (
12 I thisTile, nN,
13 I e2BufrRecSize,
14 I iBufr1, iBufr2,
15 I e2Bufr1_RX, e2Bufr2_RX,
16 O e2_msgHandle,
17 I commSetting, myThid )
18
19 C !DESCRIPTION:
20 C Two components vector field Exchange:
21 C Send buffer to the target Process.
22 C Buffer has been previously filled with interior data point
23 C corresponding to the target-neighbour-edge overlap region.
24
25 C !USES:
26 IMPLICIT NONE
27
28 #include "SIZE.h"
29 #include "EEPARAMS.h"
30 #include "EESUPPORT.h"
31 #include "W2_EXCH2_SIZE.h"
32 #include "W2_EXCH2_TOPOLOGY.h"
33
34 C !INPUT/OUTPUT PARAMETERS:
35 C === Routine arguments ===
36 C thisTile :: sending tile Id. number
37 C nN :: Neighbour entry that we are processing
38 C e2BufrRecSize :: Number of elements in each entry of e2Bufr1_RX
39 C iBufr1 :: number of buffer-1 elements to transfert
40 C iBufr2 :: number of buffer-2 elements to transfert
41 C e2Bufr1_RX :: Data transport buffer array. This array is used in one of
42 C e2Bufr2_RX :: two ways. For PUT communication the entry in the buffer
43 C :: associated with the source for this receive (determined
44 C :: from the opposing_send index) is read.
45 C :: For MSG communication the entry in the buffer associated
46 C :: with this neighbor of this tile is used as a receive
47 C :: location for loading a linear stream of bytes.
48 C e2_msgHandles :: Synchronization and coordination data structure used to
49 C :: coordinate access to e2Bufr1_RX or to regulate message
50 C :: buffering. In PUT communication sender will increment
51 C :: handle entry once data is ready in buffer. Receiver will
52 C :: decrement handle once data is consumed from buffer.
53 C :: For MPI MSG communication MPI_Wait uses hanlde to check
54 C :: Isend has cleared. This is done in routine after receives.
55 C commSetting :: Mode of communication used to exchange with this neighbor
56 C myThid :: my Thread Id. number
57
58 INTEGER thisTile, nN
59 INTEGER e2BufrRecSize
60 INTEGER iBufr1, iBufr2
61 _RX e2Bufr1_RX( e2BufrRecSize )
62 _RX e2Bufr2_RX( e2BufrRecSize )
63 INTEGER e2_msgHandle(2)
64 CHARACTER commSetting
65 INTEGER myThid
66 CEOP
67
68 #ifdef ALLOW_USE_MPI
69 C !LOCAL VARIABLES:
70 C == Local variables ==
71 C tgT :: Target tile
72 INTEGER tgT
73
74 C MPI setup
75 INTEGER theTag1, theTag2, theType, theHandle1, theHandle2
76 INTEGER sProc, tProc, mpiRc
77 #ifdef W2_E2_DEBUG_ON
78 CHARACTER*(MAX_LEN_MBUF) msgBuf
79 #endif
80
81 tgT = exch2_neighbourId(nN, thisTile )
82
83 C Do data transport depending on communication mechanism between
84 C source and target tile
85 IF ( commSetting .EQ. 'M' ) THEN
86 C Setup MPI stuff here
87 theTag1 = (thisTile-1)*W2_maxNeighbours*2 + nN-1
88 theTag2 = (thisTile-1)*W2_maxNeighbours*2
89 & + W2_maxNeighbours + nN-1
90 tProc = exch2_tProc(tgT)-1
91 sProc = exch2_tProc(thisTile)-1
92 theType = _MPI_TYPE_RX
93 #ifdef W2_E2_DEBUG_ON
94 WRITE(msgBuf,'(A,I5,A,I5,A)')
95 & ' SEND FROM TILE=', thisTile, ' (proc =',sProc,')'
96 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
97 I SQUEEZE_RIGHT, myThid)
98 WRITE(msgBuf,'(A,I5,A,I5,A)')
99 & ' TO TILE=', tgT ' (proc =',tProc,')'
100 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
101 I SQUEEZE_RIGHT, myThid)
102 WRITE(msgBuf,'(A,I10)') ' TAG1=', theTag1
103 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
104 I SQUEEZE_RIGHT, myThid)
105 WRITE(msgBuf,'(A,I4)') ' NEL1=', iBufr1
106 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
107 I SQUEEZE_RIGHT, myThid)
108 WRITE(msgBuf,'(A,I10)') ' TAG2=', theTag2
109 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
110 I SQUEEZE_RIGHT, myThid)
111 WRITE(msgBuf,'(A,I4)') ' NEL2=', iBufr2
112 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
113 I SQUEEZE_RIGHT, myThid)
114 #endif /* W2_E2_DEBUG_ON */
115 CALL MPI_Isend( e2Bufr1_RX, iBufr1, theType,
116 I tProc, theTag1, MPI_COMM_MODEL,
117 O theHandle1, mpiRc )
118 CALL MPI_Isend( e2Bufr2_RX, iBufr2, theType,
119 I tProc, theTag2, MPI_COMM_MODEL,
120 O theHandle2, mpiRc )
121 C Store MPI_Wait token in messageHandle.
122 e2_msgHandle(1) = theHandle1
123 e2_msgHandle(2) = theHandle2
124 ENDIF
125 #endif /* ALLOW_USE_MPI */
126
127 RETURN
128 END
129
130 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
131
132 CEH3 ;;; Local Variables: ***
133 CEH3 ;;; mode:fortran ***
134 CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22