--- MITgcm/pkg/exch2/exch2_recv_rx2.template 2008/07/29 20:25:23 1.5 +++ MITgcm/pkg/exch2/exch2_recv_rx2.template 2008/08/01 00:45:16 1.6 @@ -1,12 +1,12 @@ -C $Header: /home/ubuntu/mnt/e9_copy/MITgcm/pkg/exch2/exch2_recv_rx2.template,v 1.5 2008/07/29 20:25:23 jmc Exp $ +C $Header: /home/ubuntu/mnt/e9_copy/MITgcm/pkg/exch2/exch2_recv_rx2.template,v 1.6 2008/08/01 00:45:16 jmc Exp $ C $Name: $ #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, @@ -27,9 +27,11 @@ #include "W2_EXCH2_TOPOLOGY.h" 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). @@ -56,11 +58,11 @@ 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 @@ -78,13 +80,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 -c INTEGER itc, jtc, ktc -c INTEGER isc, jsc, ksc -c INTEGER isl, jsl, ksl C tt :: Target tile C iBufr1 :: Buffer counter C iBufr2 :: @@ -97,15 +93,12 @@ INTEGER oN C Loop counters INTEGER I - INTEGER itl1reduce, jtl1reduce - INTEGER itl2reduce, jtl2reduce C MPI setup #ifdef ALLOW_USE_MPI - INTEGER nri1, nrj1, nrk1 - INTEGER nri2, nrj2, nrk2 + INTEGER nri1, nrj1, nrk1 + INTEGER nri2, nrj2, nrk2 INTEGER theTag1, theTag2, theType -c INTEGER theSize1, theSize2 INTEGER sProc, tProc INTEGER mpiStatus(MPI_STATUS_SIZE), mpiRc #ifdef W2_E2_DEBUG_ON @@ -115,14 +108,6 @@ tt=exch2_neighbourId(nN, thisTile ) oN=exch2_opposingSend(nN, thisTile ) - itl1reduce=0 - jtl1reduce=0 - itl2reduce=0 - jtl2reduce=0 - IF ( exch2_pij(1,oN,tt) .EQ. -1 ) itl1reduce=1 - IF ( exch2_pij(3,oN,tt) .EQ. -1 ) itl1reduce=1 - IF ( exch2_pij(2,oN,tt) .EQ. -1 ) jtl2reduce=1 - IF ( exch2_pij(4,oN,tt) .EQ. -1 ) jtl2reduce=1 C Handle receive end data transport according to communication mechanism between C source and target tile @@ -157,12 +142,12 @@ 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, @@ -175,7 +160,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, @@ -206,9 +191,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) @@ -217,9 +202,9 @@ 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)