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

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

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


Revision 1.12 - (hide annotations) (download)
Fri Apr 23 20:21:06 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.11: +4 -4 lines
fix propagating typo (& others) in variable description

1 jmc 1.12 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_send_rx2.template,v 1.11 2009/05/30 21:18:59 jmc Exp $
2 edhill 1.3 C $Name: $
3    
4 jmc 1.5 #include "CPP_EEOPTIONS.h"
5     #include "W2_OPTIONS.h"
6 afe 1.1
7 jmc 1.11 CBOP 0
8     C !ROUTINE: EXCH2_SEND_RX2
9    
10     C !INTERFACE:
11 afe 1.1 SUBROUTINE EXCH2_SEND_RX2 (
12 jmc 1.11 I thisTile, nN,
13 jmc 1.7 I e2BufrRecSize,
14 jmc 1.11 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 afe 1.1
25 jmc 1.11 C !USES:
26 afe 1.1 IMPLICIT NONE
27    
28 jmc 1.5 #include "SIZE.h"
29     #include "EEPARAMS.h"
30     #include "EESUPPORT.h"
31 jmc 1.9 #include "W2_EXCH2_SIZE.h"
32 afe 1.1 #include "W2_EXCH2_TOPOLOGY.h"
33    
34 jmc 1.11 C !INPUT/OUTPUT PARAMETERS:
35 afe 1.1 C === Routine arguments ===
36 jmc 1.11 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 jmc 1.12 C iBufr1 :: number of buffer-1 elements to transfer
40     C iBufr2 :: number of buffer-2 elements to transfer
41 jmc 1.11 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 jmc 1.12 C :: For MPI MSG communication MPI_Wait uses handle to check
54 jmc 1.11 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 afe 1.1 INTEGER thisTile, nN
59 jmc 1.6 INTEGER e2BufrRecSize
60 jmc 1.11 INTEGER iBufr1, iBufr2
61 afe 1.1 _RX e2Bufr1_RX( e2BufrRecSize )
62     _RX e2Bufr2_RX( e2BufrRecSize )
63 jmc 1.11 INTEGER e2_msgHandle(2)
64     CHARACTER commSetting
65 afe 1.1 INTEGER myThid
66 jmc 1.11 CEOP
67 afe 1.1
68 jmc 1.11 #ifdef ALLOW_USE_MPI
69     C !LOCAL VARIABLES:
70 afe 1.1 C == Local variables ==
71 jmc 1.11 C tgT :: Target tile
72     INTEGER tgT
73 afe 1.1
74     C MPI setup
75     INTEGER theTag1, theTag2, theType, theHandle1, theHandle2
76     INTEGER sProc, tProc, mpiRc
77 jmc 1.11 #ifdef W2_E2_DEBUG_ON
78     CHARACTER*(MAX_LEN_MBUF) msgBuf
79 jmc 1.4 #endif
80 afe 1.1
81 jmc 1.11 tgT = exch2_neighbourId(nN, thisTile )
82 afe 1.1
83 jmc 1.11 C Do data transport depending on communication mechanism between
84     C source and target tile
85     IF ( commSetting .EQ. 'M' ) THEN
86 afe 1.1 C Setup MPI stuff here
87 jmc 1.9 theTag1 = (thisTile-1)*W2_maxNeighbours*2 + nN-1
88     theTag2 = (thisTile-1)*W2_maxNeighbours*2
89     & + W2_maxNeighbours + nN-1
90 jmc 1.11 tProc = exch2_tProc(tgT)-1
91 afe 1.1 sProc = exch2_tProc(thisTile)-1
92 jmc 1.10 theType = _MPI_TYPE_RX
93 afe 1.1 #ifdef W2_E2_DEBUG_ON
94 jmc 1.11 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 afe 1.1 #endif /* W2_E2_DEBUG_ON */
115     CALL MPI_Isend( e2Bufr1_RX, iBufr1, theType,
116 jmc 1.6 I tProc, theTag1, MPI_COMM_MODEL,
117 afe 1.1 O theHandle1, mpiRc )
118     CALL MPI_Isend( e2Bufr2_RX, iBufr2, theType,
119 jmc 1.6 I tProc, theTag2, MPI_COMM_MODEL,
120 afe 1.1 O theHandle2, mpiRc )
121     C Store MPI_Wait token in messageHandle.
122 jmc 1.11 e2_msgHandle(1) = theHandle1
123     e2_msgHandle(2) = theHandle2
124 afe 1.1 ENDIF
125 jmc 1.11 #endif /* ALLOW_USE_MPI */
126 jmc 1.6
127 afe 1.1 RETURN
128     END
129 edhill 1.3
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