/[MITgcm]/MITgcm/pkg/exch2/w2_print_comm_sequence.F
ViewVC logotype

Annotation of /MITgcm/pkg/exch2/w2_print_comm_sequence.F

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


Revision 1.5 - (hide annotations) (download)
Tue Jul 29 20:25:23 2008 UTC (15 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i
Changes since 1.4: +19 -18 lines
- change index-bounds storage (move from target to local tile,
  more intuitive this way)
- rename/remove some variables

1 jmc 1.5 C $Header: /u/gcmpack/MITgcm/pkg/exch2/w2_print_comm_sequence.F,v 1.4 2008/07/28 21:33:45 jmc Exp $
2 afe 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5    
6 jmc 1.3 CBOP
7 afe 1.1 C !ROUTINE: W2_PRINT_COMM_SEQUENCE
8    
9     C !INTERFACE:
10     SUBROUTINE W2_PRINT_COMM_SEQUENCE
11     IMPLICIT NONE
12    
13     C !DESCRIPTION:
14     C *==========================================================*
15 jmc 1.3 C | SUBROUTINE W2_PRINT_COMM_SEQUENCE
16     C | o Write communication sequence for a given WRAPPER2
17 afe 1.1 C | toplogy
18     C *==========================================================*
19     #include "SIZE.h"
20     #include "EEPARAMS.h"
21     #include "EESUPPORT.h"
22     #include "W2_EXCH2_TOPOLOGY.h"
23     #include "W2_EXCH2_PARAMS.h"
24    
25     C == Local variables ==
26     CHARACTER*(MAX_LEN_MBUF) msgBuffer
27     INTEGER myTileId, nN
28 jmc 1.2 c INTEGER PI_TC2SC(2), PJ_TC2SC(2), O_TC2SC(2)
29     c _RL SXDIR_TX2CX(2), SYDIR_TX2CX(2)
30 afe 1.1 INTEGER targetIlo, targetIhi, targetJlo, targetJhi
31     INTEGER sourceIlo, sourceIhi, sourceJlo, sourceJhi
32     INTEGER I, N, targetTile, myThid, targetProc, sourceProc
33     INTEGER iStride, jStride
34     INTEGER pi(2), pj(2), oi, oj, tN
35 jmc 1.3 INTEGER itb, jtb, isb, jsb
36 afe 1.1
37     myThid = 1
38    
39     C Send loop for cell centered
40     DO I=1,nSx
41     myTileId=W2_myTileList(I)
42     nN=exch2_nNeighbours(myTileId)
43     sourceProc=exch2_tProc(myTileId)
44     DO N=1,nN
45     targetTile=exch2_neighbourId(N,myTileId)
46     targetProc=exch2_tProc(targetTile)
47 jmc 1.5 tN = exch2_opposingSend(N,myTileId)
48     targetIlo =exch2_iLo(tN,targetTile)
49     targetIhi =exch2_iHi(tN,targetTile)
50     targetJlo =exch2_jLo(tN,targetTile)
51     targetJhi =exch2_jHi(tN,targetTile)
52     pi(1) =exch2_pij(1,N,myTileId)
53     pi(2) =exch2_pij(2,N,myTileId)
54     pj(1) =exch2_pij(3,N,myTileId)
55     pj(2) =exch2_pij(4,N,myTileId)
56 afe 1.1 oi =exch2_oi(N,myTileId)
57     oj =exch2_oj(N,myTileId)
58 jmc 1.3 CALL EXCH2_GET_SEND_BOUNDS(
59     I 'T ', OLx,
60     O iStride, jStride,
61     U targetIlo, targetIhi, targetJlo, targetJhi )
62    
63 jmc 1.5 itb = exch2_tBasex(targetTile)
64     jtb = exch2_tBasey(targetTile)
65     isb = exch2_tBasex(myTileId)
66     jsb = exch2_tBasey(myTileId)
67 jmc 1.3 sourceIlo=pi(1)*(targetIlo+itb)+pi(2)*(targetJlo+jtb)+oi-isb
68     sourceJlo=pj(1)*(targetIlo+itb)+pj(2)*(targetJlo+jtb)+oj-jsb
69     sourceIhi=pi(1)*(targetIhi+itb)+pi(2)*(targetJhi+jtb)+oi-isb
70     sourceJhi=pj(1)*(targetIhi+itb)+pj(2)*(targetJhi+jtb)+oj-jsb
71 afe 1.1 C Tile XX sends to points i=ilo:ihi,j=jlo:jhi in tile YY
72 jmc 1.3 WRITE(msgBuffer,'(A,I6,A,I4,A,4(A,I4))')
73     & 'Tile', myTileId,' (pr=',sourceProc,')',
74     & ' sends pts i=',sourceIlo,':',sourceIhi,
75     & ', j=',sourceJlo,':',sourceJhi
76 afe 1.1 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
77     & SQUEEZE_RIGHT,myThid)
78 jmc 1.3 WRITE(msgBuffer,'(4(A,I4),A,I6,A,I4,A)')
79     & ' to pts i=',targetIlo,':',targetIhi,
80     & ', j=',targetJlo,':',targetJhi,
81     & ' in tile ',targetTile,' (pr=',targetProc,')'
82 afe 1.1 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
83     & SQUEEZE_RIGHT,myThid)
84     ENDDO
85     ENDDO
86    
87     C Recv loop for cell centered
88     DO I=1,nSx
89     myTileId=W2_myTileList(I)
90     nN=exch2_nNeighbours(myTileId)
91     sourceProc=exch2_tProc(myTileId)
92     DO N=1,nN
93     targetTile=exch2_neighbourId(N,myTileId)
94     targetProc=exch2_tProc(targetTile)
95     C Find entry for tile targetTile entry that sent to this edge.
96 jmc 1.5 tN=exch2_opposingSend(N,myTileId)
97 afe 1.1 C Get the range of points associated with that entry
98 jmc 1.5 targetIlo =exch2_iLo(N,myTileId)
99     targetIhi =exch2_iHi(N,myTileId)
100     targetJlo =exch2_jLo(N,myTileId)
101     targetJhi =exch2_jHi(N,myTileId)
102 jmc 1.4 CALL EXCH2_GET_RECV_BOUNDS(
103 jmc 1.3 I 'T ', OLx,
104     O iStride, jStride,
105     U targetIlo, targetIhi, targetJlo, targetJhi )
106 afe 1.1 C Tile XX receives points i=ilo:ihi,j=jlo:jhi in tile YY
107 jmc 1.3 WRITE(msgBuffer,'(A,I6,A,I4,A,4(A,I4),A,I6,A,I4,A)')
108     & 'Tile', myTileId,' (pr=',sourceProc,')',
109     & ' recv pts i=',targetIlo,':',targetIhi,
110     & ', j=',targetJlo, ':',targetJhi,
111     & ' from tile',targetTile,' (pr=',targetProc,')'
112 afe 1.1 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
113     & SQUEEZE_RIGHT,myThid)
114     ENDDO
115     ENDDO
116    
117     RETURN
118     END

  ViewVC Help
Powered by ViewVC 1.1.22