/[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.11 - (hide annotations) (download)
Tue Sep 4 00:45:25 2012 UTC (12 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63s, checkpoint64, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.10: +5 -5 lines
rename "exch2_tProc" to "W2_tileProc"

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

  ViewVC Help
Powered by ViewVC 1.1.22