/[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.3 - (hide annotations) (download)
Mon Jul 28 18:15:39 2008 UTC (15 years, 10 months ago) by jmc
Branch: MAIN
Changes since 1.2: +35 -150 lines
- fix processor Nb ; fix source index range (send) ;
- call standard S/R to get index bounds (S/R exch2_get_send/recv_bounds)

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/exch2/w2_print_comm_sequence.F,v 1.2 2005/07/22 18:21:55 jmc Exp $
2 afe 1.1 C $Name: $
3    
4     #include "CPP_EEOPTIONS.h"
5    
6 jmc 1.3 CBOP
7 afe 1.1 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 jmc 1.3 C | SUBROUTINE W2_PRINT_COMM_SEQUENCE
16     C | o Write communication sequence for a given WRAPPER2
17 afe 1.1 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 jmc 1.2 c INTEGER PI_TC2SC(2), PJ_TC2SC(2), O_TC2SC(2)
29     c _RL SXDIR_TX2CX(2), SYDIR_TX2CX(2)
30 afe 1.1 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 jmc 1.3 INTEGER itb, jtb, isb, jsb
36 afe 1.1
37     myThid = 1
38    
39     C Send loop for cell centered
40     DO I=1,nSx
41     myTileId=W2_myTileList(I)
42     nN=exch2_nNeighbours(myTileId)
43     sourceProc=exch2_tProc(myTileId)
44     DO N=1,nN
45     targetTile=exch2_neighbourId(N,myTileId)
46     targetProc=exch2_tProc(targetTile)
47     targetIlo =exch2_itlo_c(N,myTileId)
48     targetIhi =exch2_ithi_c(N,myTileId)
49     targetJlo =exch2_jtlo_c(N,myTileId)
50     targetJhi =exch2_jthi_c(N,myTileId)
51     pi(1) =exch2_pi(1,N,myTileId)
52     pi(2) =exch2_pi(2,N,myTileId)
53     pj(1) =exch2_pj(1,N,myTileId)
54     pj(2) =exch2_pj(2,N,myTileId)
55     oi =exch2_oi(N,myTileId)
56     oj =exch2_oj(N,myTileId)
57 jmc 1.3 CALL EXCH2_GET_SEND_BOUNDS(
58     I 'T ', OLx,
59     O iStride, jStride,
60     U targetIlo, targetIhi, targetJlo, targetJhi )
61    
62     itb = exch2_tbasex(targetTile)
63     jtb = exch2_tbasey(targetTile)
64     isb = exch2_tbasex(myTileId)
65     jsb = exch2_tbasey(myTileId)
66     sourceIlo=pi(1)*(targetIlo+itb)+pi(2)*(targetJlo+jtb)+oi-isb
67     sourceJlo=pj(1)*(targetIlo+itb)+pj(2)*(targetJlo+jtb)+oj-jsb
68     sourceIhi=pi(1)*(targetIhi+itb)+pi(2)*(targetJhi+jtb)+oi-isb
69     sourceJhi=pj(1)*(targetIhi+itb)+pj(2)*(targetJhi+jtb)+oj-jsb
70 afe 1.1 C Tile XX sends to points i=ilo:ihi,j=jlo:jhi in tile YY
71 jmc 1.3 WRITE(msgBuffer,'(A,I6,A,I4,A,4(A,I4))')
72     & 'Tile', myTileId,' (pr=',sourceProc,')',
73     & ' sends pts i=',sourceIlo,':',sourceIhi,
74     & ', j=',sourceJlo,':',sourceJhi
75 afe 1.1 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
76     & SQUEEZE_RIGHT,myThid)
77 jmc 1.3 WRITE(msgBuffer,'(4(A,I4),A,I6,A,I4,A)')
78     & ' to pts i=',targetIlo,':',targetIhi,
79     & ', j=',targetJlo,':',targetJhi,
80     & ' in tile ',targetTile,' (pr=',targetProc,')'
81 afe 1.1 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
82     & SQUEEZE_RIGHT,myThid)
83     ENDDO
84     ENDDO
85    
86     C Recv loop for cell centered
87     DO I=1,nSx
88     myTileId=W2_myTileList(I)
89     nN=exch2_nNeighbours(myTileId)
90     sourceProc=exch2_tProc(myTileId)
91     DO N=1,nN
92     targetTile=exch2_neighbourId(N,myTileId)
93     targetProc=exch2_tProc(targetTile)
94     C Find entry for tile targetTile entry that sent to this edge.
95     tN=exch2_opposingSend_record(N,myTileId)
96     C Get the range of points associated with that entry
97     targetIlo =exch2_itlo_c(tN,targetTile)
98     targetIhi =exch2_ithi_c(tN,targetTile)
99     targetJlo =exch2_jtlo_c(tN,targetTile)
100     targetJhi =exch2_jthi_c(tN,targetTile)
101 jmc 1.3 CALL EXCH2_GET_REC_BOUNDS(
102     I 'T ', OLx,
103     O iStride, jStride,
104     U targetIlo, targetIhi, targetJlo, targetJhi )
105 afe 1.1 C Tile XX receives points i=ilo:ihi,j=jlo:jhi in tile YY
106 jmc 1.3 WRITE(msgBuffer,'(A,I6,A,I4,A,4(A,I4),A,I6,A,I4,A)')
107     & 'Tile', myTileId,' (pr=',sourceProc,')',
108     & ' recv pts i=',targetIlo,':',targetIhi,
109     & ', j=',targetJlo, ':',targetJhi,
110     & ' from tile',targetTile,' (pr=',targetProc,')'
111 afe 1.1 CALL PRINT_MESSAGE(msgBuffer,standardMessageUnit,
112     & SQUEEZE_RIGHT,myThid)
113     ENDDO
114     ENDDO
115    
116     RETURN
117     END

  ViewVC Help
Powered by ViewVC 1.1.22