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

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

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


Revision 1.9 - (show annotations) (download)
Sun Jun 28 01:00:23 2009 UTC (14 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.8: +75 -71 lines
add bj in exch2 arrays and S/R.

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

  ViewVC Help
Powered by ViewVC 1.1.22