/[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.6 - (hide annotations) (download)
Wed Apr 29 19:44:44 2009 UTC (15 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61n
Changes since 1.5: +57 -19 lines
option (Off for now) to print topology report in a log-file (instead of STDOUT);
 skip suffix (PID.TID...) when printing most of the topology report.

1 jmc 1.6 C $Header: /u/gcmpack/MITgcm/pkg/exch2/w2_print_comm_sequence.F,v 1.5 2008/07/29 20:25:23 jmc Exp $
2 afe 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5 jmc 1.6 #undef W2_PRINT_PREFIX
6 afe 1.1
7 jmc 1.3 CBOP
8 afe 1.1 C !ROUTINE: W2_PRINT_COMM_SEQUENCE
9    
10     C !INTERFACE:
11 jmc 1.6 SUBROUTINE W2_PRINT_COMM_SEQUENCE( W2_oUnit )
12 afe 1.1
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 jmc 1.6 C | topology
18 afe 1.1 C *==========================================================*
19 jmc 1.6
20     C !USES:
21     IMPLICIT NONE
22     C == Global data ==
23 afe 1.1 #include "SIZE.h"
24     #include "EEPARAMS.h"
25     #include "EESUPPORT.h"
26     #include "W2_EXCH2_TOPOLOGY.h"
27     #include "W2_EXCH2_PARAMS.h"
28    
29 jmc 1.6 C !INPUT/OUTPUT PARAMETERS:
30     C W2_oUnit :: fortran I/O unit
31     INTEGER W2_oUnit
32    
33     #ifndef W2_PRINT_PREFIX
34     C !FUNCTIONS:
35     INTEGER ILNBLNK
36     EXTERNAL ILNBLNK
37     #endif
38    
39     C !LOCAL VARIABLES:
40 afe 1.1 C == Local variables ==
41 jmc 1.6 C bi :: tile index
42     C N :: Neighbours index
43     C nN :: number of Neighbours
44     C targetTile ::
45     C sourceProc ::
46 afe 1.1 INTEGER myTileId, nN
47 jmc 1.2 c INTEGER PI_TC2SC(2), PJ_TC2SC(2), O_TC2SC(2)
48     c _RL SXDIR_TX2CX(2), SYDIR_TX2CX(2)
49 afe 1.1 INTEGER targetIlo, targetIhi, targetJlo, targetJhi
50     INTEGER sourceIlo, sourceIhi, sourceJlo, sourceJhi
51 jmc 1.6 INTEGER targetTile, targetProc, sourceProc
52     INTEGER bi, N
53 afe 1.1 INTEGER iStride, jStride
54     INTEGER pi(2), pj(2), oi, oj, tN
55 jmc 1.3 INTEGER itb, jtb, isb, jsb
56 jmc 1.6 CHARACTER*(MAX_LEN_MBUF) msgBuf
57     INTEGER myThid
58     #ifndef W2_PRINT_PREFIX
59     INTEGER iLen
60     #endif
61     CEOP
62 afe 1.1
63     myThid = 1
64    
65     C Send loop for cell centered
66 jmc 1.6 DO bi=1,nSx
67     myTileId=W2_myTileList(bi)
68 afe 1.1 nN=exch2_nNeighbours(myTileId)
69     sourceProc=exch2_tProc(myTileId)
70     DO N=1,nN
71     targetTile=exch2_neighbourId(N,myTileId)
72     targetProc=exch2_tProc(targetTile)
73 jmc 1.5 tN = exch2_opposingSend(N,myTileId)
74     targetIlo =exch2_iLo(tN,targetTile)
75     targetIhi =exch2_iHi(tN,targetTile)
76     targetJlo =exch2_jLo(tN,targetTile)
77     targetJhi =exch2_jHi(tN,targetTile)
78     pi(1) =exch2_pij(1,N,myTileId)
79     pi(2) =exch2_pij(2,N,myTileId)
80     pj(1) =exch2_pij(3,N,myTileId)
81     pj(2) =exch2_pij(4,N,myTileId)
82 afe 1.1 oi =exch2_oi(N,myTileId)
83     oj =exch2_oj(N,myTileId)
84 jmc 1.3 CALL EXCH2_GET_SEND_BOUNDS(
85     I 'T ', OLx,
86     O iStride, jStride,
87     U targetIlo, targetIhi, targetJlo, targetJhi )
88    
89 jmc 1.5 itb = exch2_tBasex(targetTile)
90     jtb = exch2_tBasey(targetTile)
91     isb = exch2_tBasex(myTileId)
92     jsb = exch2_tBasey(myTileId)
93 jmc 1.3 sourceIlo=pi(1)*(targetIlo+itb)+pi(2)*(targetJlo+jtb)+oi-isb
94     sourceJlo=pj(1)*(targetIlo+itb)+pj(2)*(targetJlo+jtb)+oj-jsb
95     sourceIhi=pi(1)*(targetIhi+itb)+pi(2)*(targetJhi+jtb)+oi-isb
96     sourceJhi=pj(1)*(targetIhi+itb)+pj(2)*(targetJhi+jtb)+oj-jsb
97 afe 1.1 C Tile XX sends to points i=ilo:ihi,j=jlo:jhi in tile YY
98 jmc 1.6 WRITE(msgBuf,'(A,I6,A,I4,A,4(A,I4))')
99 jmc 1.3 & 'Tile', myTileId,' (pr=',sourceProc,')',
100     & ' sends pts i=',sourceIlo,':',sourceIhi,
101     & ', j=',sourceJlo,':',sourceJhi
102 jmc 1.6 #ifdef W2_PRINT_PREFIX
103     CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
104     #else
105     iLen = ILNBLNK(msgBuf)
106     WRITE(W2_oUnit,'(A)') msgBuf(1:iLen)
107     #endif
108     WRITE(msgBuf,'(4(A,I4),A,I6,A,I4,A)')
109 jmc 1.3 & ' to pts i=',targetIlo,':',targetIhi,
110     & ', j=',targetJlo,':',targetJhi,
111     & ' in tile ',targetTile,' (pr=',targetProc,')'
112 jmc 1.6 #ifdef W2_PRINT_PREFIX
113     CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
114     #else
115     iLen = ILNBLNK(msgBuf)
116     WRITE(W2_oUnit,'(A)') msgBuf(1:iLen)
117     #endif
118 afe 1.1 ENDDO
119     ENDDO
120    
121     C Recv loop for cell centered
122 jmc 1.6 DO bi=1,nSx
123     myTileId=W2_myTileList(bi)
124 afe 1.1 nN=exch2_nNeighbours(myTileId)
125     sourceProc=exch2_tProc(myTileId)
126     DO N=1,nN
127     targetTile=exch2_neighbourId(N,myTileId)
128     targetProc=exch2_tProc(targetTile)
129     C Find entry for tile targetTile entry that sent to this edge.
130 jmc 1.5 tN=exch2_opposingSend(N,myTileId)
131 afe 1.1 C Get the range of points associated with that entry
132 jmc 1.5 targetIlo =exch2_iLo(N,myTileId)
133     targetIhi =exch2_iHi(N,myTileId)
134     targetJlo =exch2_jLo(N,myTileId)
135     targetJhi =exch2_jHi(N,myTileId)
136 jmc 1.4 CALL EXCH2_GET_RECV_BOUNDS(
137 jmc 1.3 I 'T ', OLx,
138     O iStride, jStride,
139     U targetIlo, targetIhi, targetJlo, targetJhi )
140 afe 1.1 C Tile XX receives points i=ilo:ihi,j=jlo:jhi in tile YY
141 jmc 1.6 WRITE(msgBuf,'(A,I6,A,I4,A,4(A,I4),A,I6,A,I4,A)')
142 jmc 1.3 & 'Tile', myTileId,' (pr=',sourceProc,')',
143     & ' recv pts i=',targetIlo,':',targetIhi,
144     & ', j=',targetJlo, ':',targetJhi,
145     & ' from tile',targetTile,' (pr=',targetProc,')'
146 jmc 1.6 #ifdef W2_PRINT_PREFIX
147     CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
148     #else
149     iLen = ILNBLNK(msgBuf)
150     WRITE(W2_oUnit,'(A)') msgBuf(1:iLen)
151     #endif
152 afe 1.1 ENDDO
153     ENDDO
154    
155     RETURN
156     END

  ViewVC Help
Powered by ViewVC 1.1.22