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

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

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

revision 1.10 by jmc, Wed May 20 21:01:45 2009 UTC revision 1.11 by jmc, Sat May 30 21:18:59 2009 UTC
# Line 4  C $Name$ Line 4  C $Name$
4  #include "CPP_EEOPTIONS.h"  #include "CPP_EEOPTIONS.h"
5  #include "W2_OPTIONS.h"  #include "W2_OPTIONS.h"
6    
7    CBOP 0
8    C !ROUTINE: EXCH2_SEND_RX2
9    
10    C !INTERFACE:
11        SUBROUTINE EXCH2_SEND_RX2 (        SUBROUTINE EXCH2_SEND_RX2 (
12       I       tIlo1, tIhi1, tIlo2, tIhi2, tiStride,       I       thisTile, nN,
      I       tJlo1, tJhi1, tJlo2, tJhi2, tjStride,  
      I       tKlo, tKhi, tkStride,  
      I       thisTile, nN, oIs1, oJs1, oIs2, oJs2,  
      O       e2Bufr1_RX, e2Bufr2_RX,  
13       I       e2BufrRecSize,       I       e2BufrRecSize,
14       I       array1,       I       iBufr1, iBufr2,
15       I       i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi,       I       e2Bufr1_RX, e2Bufr2_RX,
16       I       array2,       O       e2_msgHandle,
17       I       i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi,       I       commSetting, myThid )
18       O       e2_msgHandle1,  
19       O       e2_msgHandle2,  C !DESCRIPTION:
20       I       commSetting, withSigns, myThid )  C     Two components vector field Exchange:
21    C     Send buffer to the target Process.
22  C     Vector exchange with bufr1 along +i axis in target tile and  C     Buffer has been previously filled with interior data point
23  C     bufr2 along +j axis in target tile.  C     corresponding to the target-neighbour-edge overlap region.
24    
25    C !USES:
26        IMPLICIT NONE        IMPLICIT NONE
27    
28  #include "SIZE.h"  #include "SIZE.h"
# Line 30  C     bufr2 along +j axis in target tile Line 31  C     bufr2 along +j axis in target tile
31  #include "W2_EXCH2_SIZE.h"  #include "W2_EXCH2_SIZE.h"
32  #include "W2_EXCH2_TOPOLOGY.h"  #include "W2_EXCH2_TOPOLOGY.h"
33    
34    C !INPUT/OUTPUT PARAMETERS:
35  C     === Routine arguments ===  C     === Routine arguments ===
36        INTEGER tIlo1, tIhi1, tIlo2, tIhi2, tiStride  C     thisTile      :: sending tile Id. number
37        INTEGER tJlo1, tJhi1, tJlo2, tJhi2, tjStride  C     nN            :: Neighbour entry that we are processing
38        INTEGER tKlo, tKhi, tkStride  C     e2BufrRecSize :: Number of elements in each entry of e2Bufr1_RX
39        INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi  C     iBufr1        :: number of buffer-1 elements to transfert
40        INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi  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        INTEGER thisTile, nN
       INTEGER oIs1, oJs1, oIs2, oJs2  
59        INTEGER e2BufrRecSize        INTEGER e2BufrRecSize
60          INTEGER iBufr1, iBufr2
61        _RX     e2Bufr1_RX( e2BufrRecSize )        _RX     e2Bufr1_RX( e2BufrRecSize )
62        _RX     e2Bufr2_RX( e2BufrRecSize )        _RX     e2Bufr2_RX( e2BufrRecSize )
63        _RX     array1(i1Lo:i1Hi,j1Lo:j1Hi,k1Lo:k1Hi)        INTEGER e2_msgHandle(2)
       _RX     array2(i2Lo:i2Hi,j2Lo:j2Hi,k2Lo:k2Hi)  
       INTEGER e2_msgHandle1(1)  
       INTEGER e2_msgHandle2(1)  
       INTEGER myThid  
64        CHARACTER commSetting        CHARACTER commSetting
65        LOGICAL   withSigns        INTEGER myThid
66    CEOP
67    
68    #ifdef ALLOW_USE_MPI
69    C !LOCAL VARIABLES:
70  C     == Local variables ==  C     == Local variables ==
71  C     itl, jtl, ktl  :: Loop counters  C     tgT         :: Target tile
72  C                    :: itl etc... target local        INTEGER  tgT
 C                    :: itc etc... target canonical  
 C                    :: isl etc... source local  
 C                    :: isc etc... source canonical  
       INTEGER itl, jtl, ktl  
       INTEGER itc, jtc  
       INTEGER isc, jsc  
       INTEGER isl, jsl  
 C     tt         :: Target tile  
 C     itb, jtb   :: Target local to canonical offsets  
 C  
       INTEGER  tt  
       INTEGER itb, jtb  
       INTEGER isb, jsb  
       INTEGER pi(2), pj(2)  
       _RX     sa1, sa2, val1, val2  
       INTEGER iBufr1, iBufr2  
73    
74  C     MPI setup  C     MPI setup
 #ifdef ALLOW_USE_MPI  
75        INTEGER theTag1, theTag2, theType, theHandle1, theHandle2        INTEGER theTag1, theTag2, theType, theHandle1, theHandle2
76        INTEGER sProc, tProc, mpiRc        INTEGER sProc, tProc, mpiRc
77    #ifdef W2_E2_DEBUG_ON
78          CHARACTER*(MAX_LEN_MBUF) msgBuf
79  #endif  #endif
       CHARACTER*(MAX_LEN_MBUF) messageBuffer  
   
       IF     ( commSetting .EQ. 'P' ) THEN  
 C      Need to check that buffer synchronisation token is decremented  
 C      before filling buffer. This is needed for parallel processing  
 C      shared memory modes only.  
       ENDIF  
80    
81        tt=exch2_neighbourId(nN, thisTile )        tgT = exch2_neighbourId(nN, thisTile )
       itb=exch2_tBasex(tt)  
       jtb=exch2_tBasey(tt)  
       isb=exch2_tBasex(thisTile)  
       jsb=exch2_tBasey(thisTile)  
       pi(1)=exch2_pij(1,nN,thisTile)  
       pi(2)=exch2_pij(2,nN,thisTile)  
       pj(1)=exch2_pij(3,nN,thisTile)  
       pj(2)=exch2_pij(4,nN,thisTile)  
   
 C     Extract into bufr1 (target i-index array)  
 C     if pi(1) is  1 then +i in target <=> +i in source so bufr1 should get +array1  
 C     if pi(1) is -1 then +i in target <=> -i in source so bufr1 should get -array1  
 C     if pj(1) is  1 then +i in target <=> +j in source so bufr1 should get +array2  
 C     if pj(1) is -1 then +i in target <=> -j in source so bufr1 should get -array2  
       sa1 = pi(1)  
       sa2 = pj(1)  
       IF ( .NOT. withSigns ) THEN  
        sa1 = ABS(sa1)  
        sa2 = ABS(sa2)  
       ENDIF  
 C     if pi(1) is 1 then +i in source aligns with +i in target  
 C     if pj(1) is 1 then +i in source aligns with +j in target  
       iBufr1=0  
 #ifdef W2_E2_DEBUG_ON  
       WRITE(messageBuffer,'(A,I4,A,I4)') 'EXCH2_SEND_RX2 sourceTile= ',  
      &                                   thisTile,  
      &                                   ' targetTile= ',tt  
       CALL PRINT_MESSAGE(messageBuffer,  
      I      standardMessageUnit,SQUEEZE_BOTH,  
      I      myThid)  
 #endif /* W2_E2_DEBUG_ON */  
       DO ktl=tKlo,tKhi,tkStride  
        DO jtl=tJlo1, tJhi1, tjStride  
         DO itl=tIlo1, tIhi1, tiStride  
          iBufr1=iBufr1+1  
          itc=itl+itb  
          jtc=jtl+jtb  
          isc=pi(1)*itc+pi(2)*jtc+oIs1  
          jsc=pj(1)*itc+pj(2)*jtc+oJs1  
          isl=isc-isb  
          jsl=jsc-jsb  
          val1=sa1*array1(isl,jsl,ktl)  
      &       +sa2*array2(isl,jsl,ktl)  
          e2Bufr1_RX(iBufr1)=val1  
 #ifdef W2_E2_DEBUG_ON  
          WRITE(messageBuffer,'(A,2I4)')  
      &           'EXCH2_SEND_RX2 target  u(itl, jtl) = ', itl, jtl  
          CALL PRINT_MESSAGE(messageBuffer,  
      I         standardMessageUnit,SQUEEZE_RIGHT,  
      I         myThid)  
          IF (     pi(1) .EQ. 1 ) THEN  
 C         i index aligns  
           WRITE(messageBuffer,'(A,2I4)')  
      &           '               source +u(isl, jsl) = ', isl, jsl  
          ELSEIF ( pi(1) .EQ. -1 ) THEN  
 C         reversed i index aligns  
           WRITE(messageBuffer,'(A,2I4)')  
      &            '               source -u(isl, jsl) = ', isl, jsl  
          ELSEIF ( pj(1) .EQ.  1 ) THEN  
           WRITE(messageBuffer,'(A,2I4)')  
      &            '               source +v(isl, jsl) = ', isl, jsl  
          ELSEIF ( pj(1) .EQ. -1 ) THEN  
           WRITE(messageBuffer,'(A,2I4)')  
      &            '               source -v(isl, jsl) = ', isl, jsl  
          ENDIF  
          CALL PRINT_MESSAGE(messageBuffer,  
      I         standardMessageUnit,SQUEEZE_RIGHT,  
      I         myThid)  
          IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN  
           WRITE(messageBuffer,'(A,2I4)')  
      &           '               *** isl is out of bounds '  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_RIGHT,  
      I     myThid)  
          ENDIF  
          IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN  
           WRITE(messageBuffer,'(A,2I4)')  
      &           '               *** jsl is out of bounds '  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_RIGHT,  
      I     myThid)  
          ENDIF  
 #endif /* W2_E2_DEBUG_ON */  
 #ifdef   W2_USE_E2_SAFEMODE  
          IF ( iBufr1 .GT. e2BufrRecSize ) THEN  
 C         Ran off end of buffer. This should not happen  
           STOP 'EXCH2_SEND_RX2:: E2BUFR LIMIT EXCEEDED'  
          ENDIF  
          IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN  
 C         Forward mode send getting from points outside of the  
 C         tiles exclusive domain bounds in X. This should not happen  
           WRITE(messageBuffer,'(A,I4,I4)')  
      &     'EXCH2_SEND_RX2 tIlo1,tIhi1=', tIlo1, tIhi1  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_BOTH,  
      I     myThid)  
           WRITE(messageBuffer,'(A,3I4)')  
      &     'EXCH2_SEND_RX2 itl, jtl, isl =', itl, jtl, isl  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_BOTH,  
      I     myThid)  
           STOP 'EXCH2_SEND_RX2:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'  
          ENDIF  
          IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN  
 C         Forward mode send getting from points outside of the  
 C         tiles exclusive domain bounds in Y. This should not happen  
           WRITE(messageBuffer,'(A,I4,I4)')  
      &     'EXCH2_SEND_RX2 tJlo1,tJhi1=', tJlo1, tJhi1  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_BOTH,  
      I     myThid)  
           WRITE(messageBuffer,'(A,2I4)')  
      &     'EXCH2_SEND_RX2 itl, jtl =', itl, jtl  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_BOTH,  
      I     myThid)  
           WRITE(messageBuffer,'(A,2I4)')  
      &     'EXCH2_SEND_RX2 isl, jsl =', isl, jsl  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_BOTH,  
      I     myThid)  
   
           STOP 'EXCH2_SEND_RX2:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'  
          ENDIF  
 #endif /* W2_USE_E2_SAFEMODE */  
         ENDDO  
        ENDDO  
       ENDDO  
   
 C     Extract values into bufr2  
 C     if pi(2) is  1 then +j in target <=> +i in source so bufr1 should get +array1  
 C     if pi(2) is -1 then +j in target <=> -i in source so bufr1 should get -array1  
 C     if pj(2) is  1 then +j in target <=> +j in source so bufr1 should get +array2  
 C     if pj(2) is -1 then +j in target <=> -j in source so bufr1 should get -array2  
       sa1 = pi(2)  
       sa2 = pj(2)  
       IF ( .NOT. withSigns ) THEN  
        sa1 = ABS(sa1)  
        sa2 = ABS(sa2)  
       ENDIF  
       iBufr2=0  
 #ifdef W2_E2_DEBUG_ON  
       WRITE(messageBuffer,'(A,I4,A,I4)') 'EXCH2_SEND_RX2 sourceTile= ',  
      &                                   thisTile,  
      &                                   ' targetTile= ',tt  
       CALL PRINT_MESSAGE(messageBuffer,  
      I      standardMessageUnit,SQUEEZE_BOTH,  
      I      myThid)  
 #endif /* W2_E2_DEBUG_ON */  
       DO ktl=tKlo,tKhi,tkStride  
        DO jtl=tJlo2, tJhi2, tjStride  
         DO itl=tIlo2, tIhi2, tiStride  
          iBufr2=iBufr2+1  
          itc=itl+itb  
          jtc=jtl+jtb  
          isc=pi(1)*itc+pi(2)*jtc+oIs2  
          jsc=pj(1)*itc+pj(2)*jtc+oJs2  
          isl=isc-isb  
          jsl=jsc-jsb  
          val2=sa1*array1(isl,jsl,ktl)  
      &       +sa2*array2(isl,jsl,ktl)  
          e2Bufr2_RX(iBufr2)=val2  
 #ifdef W2_E2_DEBUG_ON  
          WRITE(messageBuffer,'(A,2I4)')  
      &            'EXCH2_SEND_RX2 target  v(itl, jtl) = ', itl, jtl  
          CALL PRINT_MESSAGE(messageBuffer,  
      I         standardMessageUnit,SQUEEZE_RIGHT,  
      I         myThid)  
          IF (     pi(2) .EQ. 1 ) THEN  
 C         i index aligns  
           WRITE(messageBuffer,'(A,2I4)')  
      &          '               source +u(isl, jsl) = ', isl, jsl  
          ELSEIF ( pi(2) .EQ. -1 ) THEN  
 C         reversed i index aligns  
           WRITE(messageBuffer,'(A,2I4)')  
      &          '               source -u(isl, jsl) = ', isl, jsl  
          ELSEIF ( pj(2) .EQ.  1 ) THEN  
           WRITE(messageBuffer,'(A,2I4)')  
      &          '               source +v(isl, jsl) = ', isl, jsl  
          ELSEIF ( pj(2) .EQ. -1 ) THEN  
           WRITE(messageBuffer,'(A,2I4)')  
      &          '               source -v(isl, jsl) = ', isl, jsl  
          ENDIF  
          CALL PRINT_MESSAGE(messageBuffer,  
      I         standardMessageUnit,SQUEEZE_RIGHT,  
      I         myThid)  
          IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN  
           WRITE(messageBuffer,'(A,2I4)')  
      &          '               *** isl is out of bounds '  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_RIGHT,  
      I     myThid)  
          ENDIF  
          IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN  
           WRITE(messageBuffer,'(A,2I4)')  
      &          '               *** jsl is out of bounds '  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_RIGHT,  
      I     myThid)  
          ENDIF  
82    
83  #endif /* W2_E2_DEBUG_ON */  C     Do data transport depending on communication mechanism between
84  #ifdef   W2_USE_E2_SAFEMODE  C     source and target tile
85           IF ( iBufr2 .GT. e2BufrRecSize ) THEN        IF ( commSetting .EQ. 'M' ) THEN
 C         Ran off end of buffer. This should not happen  
           STOP 'EXCH2_SEND_RX2:: E2BUFR LIMIT EXCEEDED'  
          ENDIF  
          IF ( isl .LT. i1Lo .OR. isl .GT. i1Hi ) THEN  
 C         Forward mode send getting from points outside of the  
 C         tiles exclusive domain bounds in X. This should not happen  
           WRITE(messageBuffer,'(A,I4,I4)')  
      &     'EXCH2_SEND_RX2 tIlo2,tIhi2=', tIlo2, tIhi2  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_BOTH,  
      I     myThid)  
           WRITE(messageBuffer,'(A,3I4)')  
      &     'EXCH2_SEND_RX2 itl, jtl, isl =', itl, jtl, isl  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_BOTH,  
      I     myThid)  
           STOP 'EXCH2_SEND_RX2:: ISL OUTSIDE TILE EXCLUSIVE DOMAIN'  
          ENDIF  
          IF ( jsl .LT. j1Lo .OR. jsl .GT. j1Hi ) THEN  
 C         Forward mode send getting from points outside of the  
 C         tiles exclusive domain bounds in Y. This should not happen  
           WRITE(messageBuffer,'(A,I4,I4)')  
      &     'EXCH2_SEND_RX2 tJlo2,tJhi2=', tJlo2, tJhi2  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_BOTH,  
      I     myThid)  
           WRITE(messageBuffer,'(A,2I4)')  
      &     'EXCH2_SEND_RX2 itl, jtl =', itl, jtl  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_BOTH,  
      I     myThid)  
           WRITE(messageBuffer,'(A,2I4)')  
      &     'EXCH2_SEND_RX2 isl, jsl =', isl, jsl  
           CALL PRINT_MESSAGE(messageBuffer,  
      I     standardMessageUnit,SQUEEZE_BOTH,  
      I     myThid)  
   
           STOP 'EXCH2_SEND_RX2:: JSL OUTSIDE TILE EXCLUSIVE DOMAIN'  
          ENDIF  
 #endif /* W2_USE_E2_SAFEMODE */  
         ENDDO  
        ENDDO  
       ENDDO  
   
 C     Do data transport depending on communication mechanism between source and target tile  
       IF     ( commSetting .EQ. 'P' ) THEN  
 C      Need to set data ready assertion (increment buffer  
 C      synchronisation token) for multithreaded mode, for now do  
 C      nothing i.e. assume only one thread per process.  
       ELSEIF ( commSetting .EQ. 'M' ) THEN  
 #ifdef ALLOW_USE_MPI  
86  C      Setup MPI stuff here  C      Setup MPI stuff here
87         theTag1 =  (thisTile-1)*W2_maxNeighbours*2 + nN-1         theTag1 =  (thisTile-1)*W2_maxNeighbours*2 + nN-1
88         theTag2 =  (thisTile-1)*W2_maxNeighbours*2         theTag2 =  (thisTile-1)*W2_maxNeighbours*2
89       &         + W2_maxNeighbours + nN-1       &         + W2_maxNeighbours + nN-1
90         tProc = exch2_tProc(tt)-1         tProc = exch2_tProc(tgT)-1
91         sProc = exch2_tProc(thisTile)-1         sProc = exch2_tProc(thisTile)-1
92         theType = _MPI_TYPE_RX         theType = _MPI_TYPE_RX
93  #ifdef W2_E2_DEBUG_ON  #ifdef W2_E2_DEBUG_ON
94         WRITE(messageBuffer,'(A,I4,A,I4,A)') ' SEND FROM TILE=',thisTile,         WRITE(msgBuf,'(A,I5,A,I5,A)')
95       &                                   ' (proc = ',sProc,')'       &  ' SEND FROM TILE=', thisTile, ' (proc =',sProc,')'
96         CALL PRINT_MESSAGE(messageBuffer,         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
97       I      standardMessageUnit,SQUEEZE_RIGHT,       I                     SQUEEZE_RIGHT, myThid)
98       I      myThid)         WRITE(msgBuf,'(A,I5,A,I5,A)')
99         WRITE(messageBuffer,'(A,I4,A,I4,A)') '        TO TILE=', tt,       &  '        TO TILE=', tgT ' (proc =',tProc,')'
100       &                                   ' (proc = ',tProc,')'         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
101         CALL PRINT_MESSAGE(messageBuffer,       I                     SQUEEZE_RIGHT, myThid)
102       I      standardMessageUnit,SQUEEZE_RIGHT,         WRITE(msgBuf,'(A,I10)') '            TAG1=', theTag1
103       I      myThid)         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
104         WRITE(messageBuffer,'(A,I10)') '            TAG1=', theTag1       I                     SQUEEZE_RIGHT, myThid)
105         CALL PRINT_MESSAGE(messageBuffer,         WRITE(msgBuf,'(A,I4)')  '            NEL1=', iBufr1
106       I      standardMessageUnit,SQUEEZE_RIGHT,         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
107       I      myThid)       I                     SQUEEZE_RIGHT, myThid)
108         WRITE(messageBuffer,'(A,I4)') '            NEL1=', iBufr1         WRITE(msgBuf,'(A,I10)') '            TAG2=', theTag2
109         CALL PRINT_MESSAGE(messageBuffer,         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
110       I      standardMessageUnit,SQUEEZE_RIGHT,       I                     SQUEEZE_RIGHT, myThid)
111       I      myThid)         WRITE(msgBuf,'(A,I4)')  '            NEL2=', iBufr2
112         WRITE(messageBuffer,'(A,I10)') '            TAG2=', theTag2         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
113         CALL PRINT_MESSAGE(messageBuffer,       I                     SQUEEZE_RIGHT, myThid)
      I      standardMessageUnit,SQUEEZE_RIGHT,  
      I      myThid)  
        WRITE(messageBuffer,'(A,I4)') '            NEL2=', iBufr2  
        CALL PRINT_MESSAGE(messageBuffer,  
      I      standardMessageUnit,SQUEEZE_RIGHT,  
      I      myThid)  
114  #endif /* W2_E2_DEBUG_ON */  #endif /* W2_E2_DEBUG_ON */
115         CALL MPI_Isend( e2Bufr1_RX, iBufr1, theType,         CALL MPI_Isend( e2Bufr1_RX, iBufr1, theType,
116       I                 tProc, theTag1, MPI_COMM_MODEL,       I                 tProc, theTag1, MPI_COMM_MODEL,
# Line 380  C      Setup MPI stuff here Line 119  C      Setup MPI stuff here
119       I                 tProc, theTag2, MPI_COMM_MODEL,       I                 tProc, theTag2, MPI_COMM_MODEL,
120       O                 theHandle2, mpiRc )       O                 theHandle2, mpiRc )
121  C      Store MPI_Wait token in messageHandle.  C      Store MPI_Wait token in messageHandle.
122         e2_msgHandle1(1) = theHandle1         e2_msgHandle(1) = theHandle1
123         e2_msgHandle2(1) = theHandle2         e2_msgHandle(2) = theHandle2
 #endif  
       ELSE  
        STOP 'EXCH2_SEND_RX2:: commSetting VALUE IS INVALID'  
124        ENDIF        ENDIF
125    #endif /* ALLOW_USE_MPI */
126    
127        RETURN        RETURN
128        END        END

Legend:
Removed from v.1.10  
changed lines
  Added in v.1.11

  ViewVC Help
Powered by ViewVC 1.1.22