/[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.1 - (hide annotations) (download)
Fri Jan 9 20:46:10 2004 UTC (20 years, 4 months ago) by afe
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, checkpoint52n_post, checkpoint52j_post, checkpoint53d_post, checkpoint54a_pre, checkpoint55c_post, checkpoint54e_post, checkpoint54a_post, checkpoint53c_post, checkpoint57k_post, checkpoint55d_pre, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint57i_post, checkpoint57e_post, checkpoint52l_post, checkpoint55h_post, checkpoint53b_post, checkpoint52k_post, checkpoint57g_pre, checkpoint54b_post, checkpoint53b_pre, checkpoint55b_post, checkpoint54d_post, checkpoint56c_post, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint57f_pre, checkpoint57a_post, checkpoint54, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, checkpoint53, eckpoint57e_pre, checkpoint57h_done, checkpoint53g_post, checkpoint52f_post, checkpoint57f_post, hrcube5, checkpoint57c_post, checkpoint55e_post, checkpoint52i_post, checkpoint52j_pre, checkpoint53f_post, checkpoint55a_post, checkpoint53d_pre, checkpoint54c_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint52i_pre, checkpoint52h_pre, checkpoint57h_post, hrcube_2, hrcube_3, checkpoint56a_post, checkpoint55d_post
Added exch2 routines and pointed hs94.cs-32x32x5 at them

1 afe 1.1 C $Header: /u/u0/gcmpack/MITgcm_contrib/high_res_cube/code-mods/w2_print_comm_sequence.F,v 1.1.1.1 2003/11/11 18:08:07 cnh Exp $
2     C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5    
6     CBOP
7     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     C | SUBROUTINE W2_PRINT_COMM_SEQUENCE
16     C | o Write communication sequence for a given WRAPPER2
17     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     INTEGER PI_TC2SC(2), PJ_TC2SC(2), O_TC2SC(2)
29     _RL SXDIR_TX2CX(2), SYDIR_TX2CX(2)
30     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    
36     myThid = 1
37    
38     C Send loop for cell centered
39     DO I=1,nSx
40     myTileId=W2_myTileList(I)
41     nN=exch2_nNeighbours(myTileId)
42     sourceProc=exch2_tProc(myTileId)
43     DO N=1,nN
44     targetTile=exch2_neighbourId(N,myTileId)
45     targetProc=exch2_tProc(targetTile)
46     targetIlo =exch2_itlo_c(N,myTileId)
47     targetIhi =exch2_ithi_c(N,myTileId)
48     targetJlo =exch2_jtlo_c(N,myTileId)
49     targetJhi =exch2_jthi_c(N,myTileId)
50     pi(1) =exch2_pi(1,N,myTileId)
51     pi(2) =exch2_pi(2,N,myTileId)
52     pj(1) =exch2_pj(1,N,myTileId)
53     pj(2) =exch2_pj(2,N,myTileId)
54     oi =exch2_oi(N,myTileId)
55     oj =exch2_oj(N,myTileId)
56     IF ( targetIlo .EQ. targetIhi .AND. targetIlo .EQ. 0 ) THEN
57     C Sending to a west edge
58     targetIlo=1-OLx
59     targetIhi=0
60     istride=1
61     IF ( targetJlo .LE. targetJhi ) THEN
62     targetJlo=targetJlo-OLx+1
63     targetJhi=targetJhi+OLx-1
64     jstride=1
65     ELSE
66     targetJlo=targetJlo+OLx-1
67     targetJhi=targetJhi-OLx+1
68     jstride=-1
69     ENDIF
70     ENDIF
71     IF ( targetIlo .EQ. targetIhi .AND. targetIlo .GT. 1 ) THEN
72     C Sending to an east edge
73     targetIhi=targetIhi+OLx-1
74     istride=1
75     IF ( targetJlo .LE. targetJhi ) THEN
76     targetJlo=targetJlo-OLx+1
77     targetJhi=targetJhi+OLx-1
78     jstride=1
79     ELSE
80     targetJlo=targetJlo+OLx-1
81     targetJhi=targetJhi-OLx+1
82     jstride=-1
83     ENDIF
84     ENDIF
85     IF ( targetJlo .EQ. targetJhi .AND. targetJlo .EQ. 0 ) THEN
86     C Sending to a south edge
87     targetJlo=1-OLx
88     targetJhi=0
89     jstride=1
90     IF ( targetIlo .LE. targetIhi ) THEN
91     targetIlo=targetIlo-OLx+1
92     targetIhi=targetIhi+OLx-1
93     istride=1
94     ELSE
95     targetIlo=targetIlo+OLx-1
96     targetIhi=targetIhi-OLx+1
97     istride=-1
98     ENDIF
99     ENDIF
100     IF ( targetJlo .EQ. targetJhi .AND. targetJlo .GT. 1 ) THEN
101     C Sending to an north edge
102     targetJhi=targetJhi+OLx-1
103     jstride=1
104     IF ( targetIlo .LE. targetIhi ) THEN
105     targetIlo=targetIlo-OLx+1
106     targetIhi=targetIhi+OLx-1
107     istride=1
108     ELSE
109     targetIlo=targetIlo+OLx-1
110     targetIhi=targetIhi-OLx+1
111     istride=-1
112     ENDIF
113     ENDIF
114     sourceIlo=pi(1)*targetIlo+pi(2)*targetJlo+oi
115     sourceJlo=pj(1)*targetIlo+pj(2)*targetJlo+oj
116     sourceIhi=pi(1)*targetIhi+pi(2)*targetJhi+oi
117     sourceJhi=pj(1)*targetIhi+pj(2)*targetJhi+oj
118     C Tile XX sends to points i=ilo:ihi,j=jlo:jhi in tile YY
119     WRITE(msgBuffer,
120     & '(A,I4,A,I4,A,A,I4,A,I4,A,I4,A,I4)')
121     & 'Tile ',myTileId
122     & ,'(proc =',sourceProc,')',
123     & ' sends points i=',sourceIlo,
124     & ':',sourceIhi,
125     & ', j=',sourceJlo,
126     & ':',sourceJhi
127     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
128     & SQUEEZE_RIGHT,myThid)
129     WRITE(msgBuffer,
130     & '(A,I4,A,I4,A,I4,A,I4,A,I4,A,I4,A)')
131     & ' to points i=',targetIlo,
132     & ':',targetIhi,
133     & ', j=',targetJlo,
134     & ':',targetJhi,
135     & ' in tile ',targetTile,
136     & '(proc =',targetProc,')'
137     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
138     & SQUEEZE_RIGHT,myThid)
139     ENDDO
140     ENDDO
141    
142     C Recv loop for cell centered
143     DO I=1,nSx
144     myTileId=W2_myTileList(I)
145     nN=exch2_nNeighbours(myTileId)
146     sourceProc=exch2_tProc(myTileId)
147     DO N=1,nN
148     targetTile=exch2_neighbourId(N,myTileId)
149     targetProc=exch2_tProc(targetTile)
150     C Find entry for tile targetTile entry that sent to this edge.
151     tN=exch2_opposingSend_record(N,myTileId)
152     C Get the range of points associated with that entry
153     targetIlo =exch2_itlo_c(tN,targetTile)
154     targetIhi =exch2_ithi_c(tN,targetTile)
155     targetJlo =exch2_jtlo_c(tN,targetTile)
156     targetJhi =exch2_jthi_c(tN,targetTile)
157     IF ( targetIlo .EQ. targetIhi .AND. targetIlo .EQ. 0 ) THEN
158     C Sending to a west edge
159     targetIlo=1-OLx
160     targetIhi=0
161     istride=1
162     IF ( targetJlo .LE. targetJhi ) THEN
163     targetJlo=targetJlo-OLx+1
164     targetJhi=targetJhi+OLx-1
165     jstride=1
166     ELSE
167     targetJlo=targetJlo+OLx-1
168     targetJhi=targetJhi-OLx+1
169     jstride=-1
170     ENDIF
171     ENDIF
172     IF ( targetIlo .EQ. targetIhi .AND. targetIlo .GT. 1 ) THEN
173     C Sending to an east edge
174     targetIhi=targetIhi+OLx-1
175     istride=1
176     IF ( targetJlo .LE. targetJhi ) THEN
177     targetJlo=targetJlo-OLx+1
178     targetJhi=targetJhi+OLx-1
179     jstride=1
180     ELSE
181     targetJlo=targetJlo+OLx-1
182     targetJhi=targetJhi-OLx+1
183     jstride=-1
184     ENDIF
185     ENDIF
186     IF ( targetJlo .EQ. targetJhi .AND. targetJlo .EQ. 0 ) THEN
187     C Sending to a south edge
188     targetJlo=1-OLx
189     targetJhi=0
190     jstride=1
191     IF ( targetIlo .LE. targetIhi ) THEN
192     targetIlo=targetIlo-OLx+1
193     targetIhi=targetIhi+OLx-1
194     istride=1
195     ELSE
196     targetIlo=targetIlo+OLx-1
197     targetIhi=targetIhi-OLx+1
198     istride=-1
199     ENDIF
200     ENDIF
201     IF ( targetJlo .EQ. targetJhi .AND. targetJlo .GT. 1 ) THEN
202     C Sending to an north edge
203     targetJhi=targetJhi+OLx-1
204     jstride=1
205     IF ( targetIlo .LE. targetIhi ) THEN
206     targetIlo=targetIlo-OLx+1
207     targetIhi=targetIhi+OLx-1
208     istride=1
209     ELSE
210     targetIlo=targetIlo+OLx-1
211     targetIhi=targetIhi-OLx+1
212     istride=-1
213     ENDIF
214     ENDIF
215     C Tile XX receives points i=ilo:ihi,j=jlo:jhi in tile YY
216     WRITE(msgBuffer,
217     & '(A,I4,A,I4,A,A,I4,A,I4,A,I4,A,I4,A,I4,A,I4,A)')
218     & 'Tile ',myTileId
219     & ,'(proc =',targetProc,')',
220     & 'recv to points i=',targetIlo,
221     & ':',targetIhi,
222     & ', j=',targetJlo,
223     & ':',targetJhi,
224     & 'from tile',targetTile,
225     & '(proc =',targetProc,')'
226     CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
227     & SQUEEZE_RIGHT,myThid)
228     ENDDO
229     ENDDO
230    
231     RETURN
232     END

  ViewVC Help
Powered by ViewVC 1.1.22