--- MITgcm/pkg/exch2/exch2_recv_rx2.template 2004/04/05 15:27:06 1.2 +++ MITgcm/pkg/exch2/exch2_recv_rx2.template 2009/05/12 19:44:58 1.8 @@ -1,11 +1,12 @@ -C $Header: /home/ubuntu/mnt/e9_copy/MITgcm/pkg/exch2/exch2_recv_rx2.template,v 1.2 2004/04/05 15:27:06 edhill Exp $ +C $Header: /home/ubuntu/mnt/e9_copy/MITgcm/pkg/exch2/exch2_recv_rx2.template,v 1.8 2009/05/12 19:44:58 jmc Exp $ C $Name: $ -#include "CPP_OPTIONS.h" +#include "CPP_EEOPTIONS.h" +#include "W2_OPTIONS.h" SUBROUTINE EXCH2_RECV_RX2( - I tIlo, tIhi, tiStride, - I tJlo, tJhi, tjStride, + I tIlo1, tIhi1, tIlo2, tIhi2, tiStride, + I tJlo1, tJhi1, tJlo2, tJhi2, tjStride, I tKlo, tKhi, tkStride, I thisTile, thisI, nN, I e2Bufr1_RX, e2Bufr2_RX, e2BufrRecSize, @@ -20,17 +21,18 @@ IMPLICIT NONE -C -#include "W2_OPTIONS.h" +#include "SIZE.h" +#include "EEPARAMS.h" +#include "EESUPPORT.h" +#include "W2_EXCH2_SIZE.h" #include "W2_EXCH2_TOPOLOGY.h" -#include "EEPARAMS.h" - CHARACTER*(MAX_LEN_MBUF) messageBuffer -C C === Routine arguments === -C tIlo, tIhi, tIstride :: index range in I that will be filled in target "array" -C tJlo, tJhi, tJstride :: index range in J that will be filled in target "array" -C tKlo, tKhi, tKstride :: index range in K that will be filled in target "array" +C tIlo1,tIhi1,tIstride :: index range in I that will be filled in target "array1" +C tIlo2,tIhi2,tIstride :: index range in I that will be filled in target "array2" +C tJlo1,tJhi1,tJstride :: index range in J that will be filled in target "array1" +C tJlo2,tJhi2,tJstride :: index range in J that will be filled in target "array2" +C tKlo, tKhi, tKstride :: index range in K that will be filled in target arrays C thisTile :: Rank of the receiveing tile C thisI :: Index of the receiving tile within this process (used C :: to select buffer slots that are allowed). @@ -57,15 +59,15 @@ C :: This is done in routine after receives. C myTiles :: List of nt tiles that this process owns. C commSetting :: Mode of communication used to exchnage with this neighbor -C myThid :: Thread number of this instance of EXCH2_RECV_RX1 -C - INTEGER tILo, tIHi, tiStride - INTEGER tJLo, tJHi, tjStride - INTEGER tKLo, tKHi, tkStride +C myThid :: Thread number of this instance of EXCH2_RECV_RX2 + + INTEGER tIlo1, tIhi1, tIlo2, tIhi2, tiStride + INTEGER tJlo1, tJhi1, tJlo2, tJhi2, tjStride + INTEGER tKlo, tKhi, tkStride INTEGER i1Lo, i1Hi, j1Lo, j1Hi, k1Lo, k1Hi INTEGER i2Lo, i2Hi, j2Lo, j2Hi, k2Lo, k2Hi INTEGER thisTile, nN, thisI - INTEGER e2BufrRecSize + INTEGER e2BufrRecSize INTEGER mnb, nt _RX e2Bufr1_RX( e2BufrRecSize, mnb, nt, 2 ) _RX e2Bufr2_RX( e2BufrRecSize, mnb, nt, 2 ) @@ -79,13 +81,7 @@ C == Local variables == C itl, jtl, ktl :: Loop counters C :: itl etc... target local -C :: itc etc... target canonical -C :: isl etc... source local -C :: isc etc... source canonical INTEGER itl, jtl, ktl - INTEGER itc, jtc, ktc - INTEGER isc, jsc, ksc - INTEGER isl, jsl, ksl C tt :: Target tile C iBufr1 :: Buffer counter C iBufr2 :: @@ -94,43 +90,34 @@ C mb, nb :: Selects e2Bufr, msgHandle record to use C ir :: INTEGER mb, nb, ir -C oN :: Opposing send record number +C oN :: Opposing send record number INTEGER oN C Loop counters - INTEGER I, nri1, nrj1, nrk1 - INTEGER nri2, nrj2, nrk2 - INTEGER itl1reduce, jtl1reduce - INTEGER itl2reduce, jtl2reduce + INTEGER I C MPI setup -#include "SIZE.h" -#include "EESUPPORT.h" - INTEGER theTag1, theSize1, theType - INTEGER theTag2, theSize2 - INTEGER sProc, tProc #ifdef ALLOW_USE_MPI + INTEGER nri1, nrj1, nrk1 + INTEGER nri2, nrj2, nrk2 + INTEGER theTag1, theTag2, theType + INTEGER sProc, tProc INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc +#ifdef W2_E2_DEBUG_ON + CHARACTER*(MAX_LEN_MBUF) messageBuffer +#endif #endif tt=exch2_neighbourId(nN, thisTile ) - oN=exch2_opposingSend_record(nN, thisTile ) - itl1reduce=0 - jtl1reduce=0 - itl2reduce=0 - jtl2reduce=0 - IF ( exch2_pi(1,oN,tt) .EQ. -1 ) itl1reduce=1 - IF ( exch2_pj(1,oN,tt) .EQ. -1 ) itl1reduce=1 - IF ( exch2_pi(2,oN,tt) .EQ. -1 ) jtl2reduce=1 - IF ( exch2_pj(2,oN,tt) .EQ. -1 ) jtl2reduce=1 + oN=exch2_opposingSend(nN, thisTile ) -C Handle receive end data transport according to communication mechanism between +C Handle receive end data transport according to communication mechanism between C source and target tile IF ( commSetting .EQ. 'P' ) THEN C 1 Need to check and spin on data ready assertion for multithreaded mode, for now do nothing i.e. C assume only one thread per process. C 2 Need to set e2Bufr to use put buffer from opposing send. - oN = exch2_opposingSend_record(nN, thisTile ) + oN = exch2_opposingSend(nN, thisTile ) mb = oN ir = 1 DO I=1,nt @@ -145,23 +132,17 @@ nb = thisI mb = nN ir = 2 - theTag1 = (tt-1)*MAX_NEIGHBOURS*2 + oN-1 - & + 10000*( - & (thisTile-1)*MAX_NEIGHBOURS*2 + oN-1 - & ) - theTag2 = (tt-1)*MAX_NEIGHBOURS*2 + MAX_NEIGHBOURS + oN-1 - & + 10000*( - & (thisTile-1)*MAX_NEIGHBOURS*2 + MAX_NEIGHBOURS + oN-1 - & ) + theTag1 = (tt-1)*W2_maxNeighbours*2 + oN-1 + theTag2 = (tt-1)*W2_maxNeighbours*2 + W2_maxNeighbours + oN-1 tProc = exch2_tProc(thisTile)-1 sProc = exch2_tProc(tt)-1 theType = MPI_REAL8 - nri1 = (tIhi-tIlo+1-itl1reduce)/tiStride - nrj1 = (tJhi-tJlo+1-jtl1reduce)/tjStride + nri1 = (tIhi1-tIlo1+1)/tiStride + nrj1 = (tJhi1-tJlo1+1)/tjStride nrk1 = (tKhi-tKlo+1)/tkStride iBufr1 = nri1*nrj1*nrk1 - nri2 = (tIhi-tIlo+1-itl2reduce)/tiStride - nrj2 = (tJhi-tJlo+1-jtl2reduce)/tjStride + nri2 = (tIhi2-tIlo2+1)/tiStride + nrj2 = (tJhi2-tJlo2+1)/tjStride nrk2 = (tKhi-tKlo+1)/tkStride iBufr2 = nri2*nrj2*nrk2 CALL MPI_Recv( e2Bufr1_RX(1,mb,nb,ir), iBufr1, theType, sProc, @@ -174,7 +155,7 @@ CALL PRINT_MESSAGE(messageBuffer, I standardMessageUnit,SQUEEZE_RIGHT, I myThid) - WRITE(messageBuffer,'(A,I4,A,I4,A)') ' INTO TILE=', thisTile, + WRITE(messageBuffer,'(A,I4,A,I4,A)') ' INTO TILE=',thisTile, & ' (proc = ',tProc,')' CALL PRINT_MESSAGE(messageBuffer, I standardMessageUnit,SQUEEZE_RIGHT, @@ -205,9 +186,9 @@ ENDIF iBufr1=0 - DO ktl=tKlo,tKhi,tKStride - DO jtl=tJLo+jtl1reduce, tJHi, tjStride - DO itl=tILo+itl1reduce, tIHi, tiStride + DO ktl=tKlo,tKhi,tkStride + DO jtl=tJLo1, tJHi1, tjStride + DO itl=tILo1, tIHi1, tiStride C Read from e2Bufr1_RX(iBufr,mb,nb) iBufr1=iBufr1+1 array1(itl,jtl,ktl)=e2Bufr1_RX(iBufr1,mb,nb,ir) @@ -216,16 +197,16 @@ ENDDO iBufr2=0 - DO ktl=tKlo,tKhi,tKStride - DO jtl=tJLo+jtl2reduce, tJHi, tjStride - DO itl=tILo+itl2reduce, tIHi, tiStride + DO ktl=tKlo,tKhi,tkStride + DO jtl=tJLo2, tJHi2, tjStride + DO itl=tILo2, tIHi2, tiStride C Read from e2Bufr1_RX(iBufr,mb,nb) iBufr2=iBufr2+1 array2(itl,jtl,ktl)=e2Bufr2_RX(iBufr2,mb,nb,ir) ENDDO ENDDO ENDDO - + RETURN END