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

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

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


Revision 1.11 - (hide annotations) (download)
Fri Apr 23 20:21:07 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.10: +4 -4 lines
fix propagating typo (& others) in variable description

1 jmc 1.11 C $Header: /u/gcmpack/MITgcm/pkg/exch2/exch2_recv_rx2.template,v 1.10 2009/05/30 21:18:59 jmc Exp $
2 edhill 1.2 C $Name: $
3    
4 jmc 1.4 #include "CPP_EEOPTIONS.h"
5     #include "W2_OPTIONS.h"
6 afe 1.1
7 jmc 1.10 CBOP 0
8     C !ROUTINE: EXCH2_RECV_RX2
9    
10     C !INTERFACE:
11 afe 1.1 SUBROUTINE EXCH2_RECV_RX2(
12 jmc 1.10 I thisTile, nN,
13     I e2BufrRecSize,
14     I iBufr1, iBufr2,
15     I e2Bufr1_RX, e2Bufr2_RX,
16     I commSetting, myThid )
17    
18     C !DESCRIPTION:
19     C Two components vector field Exchange:
20     C Receive into buffer exchanged data from the source Process.
21     C buffer data will be used to fill in the tile-edge overlap region.
22 afe 1.1
23 jmc 1.10 C !USES:
24 afe 1.1 IMPLICIT NONE
25    
26 jmc 1.4 #include "SIZE.h"
27     #include "EEPARAMS.h"
28     #include "EESUPPORT.h"
29 jmc 1.8 #include "W2_EXCH2_SIZE.h"
30 afe 1.1 #include "W2_EXCH2_TOPOLOGY.h"
31    
32 jmc 1.10 C !INPUT/OUTPUT PARAMETERS:
33 afe 1.1 C === Routine arguments ===
34 jmc 1.11 C thisTile :: receiving tile Id. number
35 jmc 1.10 C nN :: Neighbour entry that we are processing
36     C e2BufrRecSize :: Number of elements in each entry of e2Bufr1_RX
37 jmc 1.11 C iBufr1 :: number of buffer-1 elements to transfer
38     C iBufr2 :: number of buffer-2 elements to transfer
39 jmc 1.10 C e2Bufr1_RX :: Data transport buffer array. This array is used in one of
40     C e2Bufr2_RX :: two ways. For PUT communication the entry in the buffer
41     C :: associated with the source for this receive (determined
42     C :: from the opposing_send index) is read.
43     C :: For MSG communication the entry in the buffer associated
44     C :: with this neighbor of this tile is used as a receive
45     C :: location for loading a linear stream of bytes.
46     C commSetting :: Mode of communication used to exchange with this neighbor
47     C myThid :: my Thread Id. number
48    
49     INTEGER thisTile, nN
50 jmc 1.5 INTEGER e2BufrRecSize
51 jmc 1.10 INTEGER iBufr1, iBufr2
52     _RX e2Bufr1_RX( e2BufrRecSize )
53     _RX e2Bufr2_RX( e2BufrRecSize )
54     CHARACTER commSetting
55 afe 1.1 INTEGER myThid
56 jmc 1.10 CEOP
57 afe 1.1
58 jmc 1.10 #ifdef ALLOW_USE_MPI
59     C !LOCAL VARIABLES:
60 afe 1.1 C == Local variables ==
61 jmc 1.10 C soT :: Source tile Id. number
62     C oNb :: Opposing send record number
63     INTEGER soT
64     INTEGER oNb
65 afe 1.1
66     C MPI setup
67 jmc 1.3 INTEGER theTag1, theTag2, theType
68 afe 1.1 INTEGER sProc, tProc
69     INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc
70 jmc 1.3 #ifdef W2_E2_DEBUG_ON
71 jmc 1.10 CHARACTER*(MAX_LEN_MBUF) msgBuf
72 afe 1.1 #endif
73    
74 jmc 1.10 soT = exch2_neighbourId(nN, thisTile )
75     oNb = exch2_opposingSend(nN, thisTile )
76 afe 1.1
77 jmc 1.10 C Handle receive end data transport according to communication mechanism
78     C between source and target tile
79     IF ( commSetting .EQ. 'M' ) THEN
80 afe 1.1 C Setup MPI stuff here
81 jmc 1.10 theTag1 = (soT-1)*W2_maxNeighbours*2 + oNb-1
82     theTag2 = (soT-1)*W2_maxNeighbours*2 + W2_maxNeighbours + oNb-1
83 afe 1.1 tProc = exch2_tProc(thisTile)-1
84 jmc 1.10 sProc = exch2_tProc(soT)-1
85 jmc 1.9 theType = _MPI_TYPE_RX
86 jmc 1.10 CALL MPI_Recv( e2Bufr1_RX, iBufr1, theType, sProc,
87     & theTag1, MPI_COMM_MODEL, mpiStatus, mpiRc )
88     CALL MPI_Recv( e2Bufr2_RX, iBufr2, theType, sProc,
89     & theTag2, MPI_COMM_MODEL, mpiStatus, mpiRc )
90 afe 1.1 #ifdef W2_E2_DEBUG_ON
91 jmc 1.10 WRITE(msgBuf,'(A,I4,A,I4,A)')
92     & ' RECV FROM TILE=', soT, ' (proc = ',sProc,')'
93     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
94     I SQUEEZE_RIGHT, myThid )
95     WRITE(msgBuf,'(A,I4,A,I4,A)')
96     & ' INTO TILE=', thisTile, ' (proc = ',tProc,')'
97     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
98     I SQUEEZE_RIGHT, myThid )
99     WRITE(msgBuf,'(A,I10)') ' TAG1=', theTag1
100     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
101     I SQUEEZE_RIGHT, myThid )
102     WRITE(msgBuf,'(A,I4)') ' NEL1=', iBufr1
103     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
104     I SQUEEZE_RIGHT, myThid )
105     WRITE(msgBuf,'(A,I10)') ' TAG2=', theTag2
106     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
107     I SQUEEZE_RIGHT, myThid )
108     WRITE(msgBuf,'(A,I4)') ' NEL2=', iBufr2
109     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
110     I SQUEEZE_RIGHT, myThid )
111 afe 1.1 #endif /* W2_E2_DEBUG_ON */
112     ENDIF
113 jmc 1.10 #endif /* ALLOW_USE_MPI */
114 jmc 1.5
115 afe 1.1 RETURN
116     END
117 edhill 1.2
118     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
119    
120     CEH3 ;;; Local Variables: ***
121     CEH3 ;;; mode:fortran ***
122     CEH3 ;;; End: ***

  ViewVC Help
Powered by ViewVC 1.1.22