/[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.8 - (hide annotations) (download)
Sat May 30 21:22:13 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61r, checkpoint61p, checkpoint61q
Changes since 1.7: +13 -17 lines
simplify argument list of S/R exch2_get_uv_bounds and exch2_get_scal_bounds
 (which replaces exch2_get_recv_bounds & exch2_get_send_bounds) by including
 Topology header file (and common blocks);
implement EXCH_IGNORE_CORNERS in S/R exch2_get_scal_bounds.

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

  ViewVC Help
Powered by ViewVC 1.1.22