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

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

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


Revision 1.5 - (show annotations) (download)
Thu Jun 18 22:37:58 2009 UTC (14 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62e, checkpoint62d, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.4: +2 -7 lines
remove unused variables

1 C $Header: /u/gcmpack/MITgcm/pkg/exch2/w2_e2setup.F,v 1.4 2009/05/12 19:40:32 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_EEOPTIONS.h"
6 #include "W2_OPTIONS.h"
7
8 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
9 CBOP 0
10 C !ROUTINE: W2_E2SETUP
11
12 C !INTERFACE:
13 SUBROUTINE W2_E2SETUP( myThid )
14
15 C !DESCRIPTION:
16 C Set-up W2_EXCH2 tile topology structures
17
18 C !USES:
19 IMPLICIT NONE
20
21 C Tile toplogy settings data structures
22 #include "SIZE.h"
23 #include "EEPARAMS.h"
24 #ifdef ALLOW_EXCH2
25 #include "W2_EXCH2_SIZE.h"
26 #include "W2_EXCH2_TOPOLOGY.h"
27 #include "W2_EXCH2_PARAMS.h"
28 #endif
29
30 C !INPUT PARAMETERS:
31 C myThid :: my Thread Id number
32 C (Note: not relevant since threading has not yet started)
33 INTEGER myThid
34
35 #ifdef ALLOW_EXCH2
36
37 C !LOCAL VARIABLES:
38 C === Local variables ===
39 C msgBuf :: Informational/error meesage buffer
40 C stdUnit :: Standard-Output IO unit number
41 CHARACTER*(MAX_LEN_MBUF) msgBuf
42 INTEGER stdUnit
43 INTEGER i, j, k
44 LOGICAL addBlank
45 CEOP
46
47 stdUnit = standardMessageUnit
48
49 C-- Initialise parameters from EXCH2_PARAMS common blocks
50 C (except params from namelist which are set in W2_READPARMS)
51 DO j=1,W2_maxNbFacets
52 facet_owns(1,j) = 0
53 facet_owns(2,j) = 0
54 DO i=1,4
55 DO k=1,4
56 facet_pij(k,i,j) = 0
57 ENDDO
58 facet_oi(i,j) = 0
59 facet_oj(i,j) = 0
60 ENDDO
61 ENDDO
62
63 C-- Count Nb of Blank-Tiles and set Number of tiles:
64 nBlankTiles = 0
65 DO i=1,W2_maxNbTiles
66 IF (blankList(i).NE.0 ) THEN
67 addBlank = .TRUE.
68 DO j=1,nBlankTiles
69 IF ( blankList(i).EQ.blankList(j) ) THEN
70 addBlank = .FALSE.
71 WRITE(msgBuf,'(A,I5,A,2I3,A)')
72 & '** WARNING ** W2_E2SETUP: #', blankList(i),
73 & ' appears several times in blankList (',j,i,')'
74 CALL PRINT_MESSAGE( msgBuf, W2_oUnit,SQUEEZE_RIGHT,myThid )
75 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
76 & SQUEEZE_RIGHT, myThid )
77 ENDIF
78 ENDDO
79 IF ( addBlank ) THEN
80 nBlankTiles = nBlankTiles + 1
81 blankList(nBlankTiles) = blankList(i)
82 ENDIF
83 ENDIF
84 ENDDO
85 nTiles = nBlankTiles + (nSx*nSy*nPx*nPy)
86
87 WRITE(msgBuf,'(A,I8)')
88 & 'W2_E2SETUP: number of Active Tiles =', nSx*nSy*nPx*nPy
89 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
90 WRITE(msgBuf,'(A,I8)')
91 & 'W2_E2SETUP: number of Blank Tiles =', nBlankTiles
92 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
93 WRITE(msgBuf,'(A,I8)')
94 & 'W2_E2SETUP: Total number of Tiles =', nTiles
95 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
96
97 IF ( nTiles.GT.W2_maxNbTiles ) THEN
98 WRITE(msgBuf,'(3(A,I7))') 'W2_E2SETUP: Number of Tiles=',
99 & nTiles, ' >', W2_maxNbTiles, ' =W2_maxNbTiles'
100 CALL PRINT_ERROR( msgBuf, myThid )
101 WRITE(msgBuf,'(2A)') 'Must increase "W2_maxNbTiles"',
102 & ' in "W2_EXCH2_SIZE.h" + recompile'
103 CALL PRINT_ERROR( msgBuf, myThid )
104 STOP 'ABNORMAL END: S/R W2_E2SETUP (nTiles>maxNbTiles)'
105 ENDIF
106
107 C-- Check blankList:
108 DO i=1,nBlankTiles
109 IF ( blankList(i).LT.1 .OR. blankList(i).GT.nTiles ) THEN
110 WRITE(msgBuf,'(A,I5,A,I8)')
111 & 'W2_E2SETUP: Invalid blankTile number (i=', i,
112 & ' )=', blankList(i)
113 WRITE(msgBuf,'(A,I7,A,I4,A)') 'W2_E2SETUP:', blankList(i),
114 & ' = Invalid blankTile number (i=', i, ')'
115 CALL PRINT_ERROR( msgBuf, myThid )
116 STOP 'ABNORMAL END: S/R W2_E2SETUP (blankList error)'
117 ENDIF
118 ENDDO
119
120 C-- Define Facet (sub-domain) Topology: Size and Connections
121 IF ( preDefTopol.EQ.0 ) THEN
122 CALL W2_SET_GEN_FACETS( myThid )
123 ELSEIF ( preDefTopol.EQ.1 ) THEN
124 CALL W2_SET_SINGLE_FACET( myThid )
125 ELSEIF ( preDefTopol.EQ.2 ) THEN
126 CALL W2_SET_MYOWN_FACETS( myThid )
127 ELSEIF ( preDefTopol.EQ.3 ) THEN
128 CALL W2_SET_CS6_FACETS( myThid )
129 ELSE
130 STOP 'ABNORMAL END: S/R W2_E2SETUP (invalid preDefTopol)'
131 ENDIF
132
133 WRITE(msgBuf,'(A,I8)')
134 & 'W2_E2SETUP: Total number of Facets =', nFacets
135 CALL PRINT_MESSAGE( msgBuf, W2_oUnit, SQUEEZE_RIGHT, myThid )
136
137 C-- Check Topology; setup correspondence matrix for connected Facet-Edges
138 CALL W2_SET_F2F_INDEX( myThid )
139
140 C-- Define Tile Mapping (+ IO global mapping)
141 CALL W2_SET_MAP_TILES( myThid )
142
143 C-- Set-up tile neighbours and index relations for EXCH2
144 CALL W2_SET_TILE2TILES( myThid )
145
146 #endif /* ALLOW_EXCH2 */
147
148 RETURN
149 END

  ViewVC Help
Powered by ViewVC 1.1.22