/[MITgcm]/MITgcm/pkg/obcs/obcs_readparms.F
ViewVC logotype

Contents of /MITgcm/pkg/obcs/obcs_readparms.F

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


Revision 1.46 - (show annotations) (download)
Tue May 27 23:41:30 2014 UTC (10 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65d, checkpoint65, checkpoint64y, checkpoint64z
Changes since 1.45: +12 -2 lines
add a call to S/R packages_unused_msg.F to print a weak warning
when parameter file "data.this_pkg" exist but  but useTHIS_PKG=F

1 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_readparms.F,v 1.45 2012/11/15 15:55:42 dimitri Exp $
2 C $Name: $
3
4 #include "OBCS_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: OBCS_READPARMS
8 C !INTERFACE:
9 SUBROUTINE OBCS_READPARMS( myThid )
10
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | SUBROUTINE OBCS_READPARMS
14 C | o Routine to initialize OBCS variables and constants.
15 C *==========================================================*
16 C \ev
17
18 C !USES:
19 IMPLICIT NONE
20 C === Global variables ===
21 #include "SIZE.h"
22 #include "EEPARAMS.h"
23 #include "PARAMS.h"
24 #include "OBCS_PARAMS.h"
25 #include "OBCS_GRID.h"
26 #include "OBCS_SEAICE.h"
27 #ifdef ALLOW_ORLANSKI
28 #include "ORLANSKI.h"
29 #endif
30 #ifdef ALLOW_PTRACERS
31 #include "PTRACERS_SIZE.h"
32 #include "OBCS_PTRACERS.h"
33 #endif /* ALLOW_PTRACERS */
34 #ifdef ALLOW_EXCH2
35 #include "W2_EXCH2_SIZE.h"
36 #include "W2_EXCH2_TOPOLOGY.h"
37 #include "W2_EXCH2_PARAMS.h"
38 #endif /* ALLOW_EXCH2 */
39
40 C !INPUT/OUTPUT PARAMETERS:
41 C === Routine arguments ===
42 INTEGER myThid
43
44 #ifdef ALLOW_OBCS
45
46 C !LOCAL VARIABLES:
47 C === Local variables ===
48 C msgBuf :: Informational/error message buffer
49 C iUnit :: Work variable for IO unit number
50 C OB_indexUnset :: OB index value for places where no OB is defined
51 CHARACTER*(MAX_LEN_MBUF) msgBuf
52 INTEGER iUnit
53 INTEGER i, j
54 INTEGER bi, bj, iG, jG, iGm, jGm
55 INTEGER OB_indexUnset
56 #ifdef ALLOW_PTRACERS
57 INTEGER iTracer
58 #endif
59 #ifdef ALLOW_EXCH2
60 INTEGER tN
61 #endif /* ALLOW_EXCH2 */
62
63 C These are input arrays (of integers) that contain the *absolute*
64 C computational index of an open-boundary (OB) point.
65 C A zero (0) element means there is no corresponding OB in that column/row.
66 C The computational coordinate refers to "tracer" cells.
67 C For a northern/southern OB, the OB V point is to the south/north.
68 C For an eastern/western OB, the OB U point is to the west/east.
69 C eg.
70 C OB_Jnorth(3)=34 means that:
71 C T( 3 ,34) is a an OB point
72 C U(3:4,34) is a an OB point
73 C V( 4 ,34) is a an OB point
74 C while
75 C OB_Jsouth(3)=1 means that:
76 C T( 3 ,1) is a an OB point
77 C U(3:4,1) is a an OB point
78 C V( 4 ,2) is a an OB point
79 C
80 C For convenience, negative values for Jnorth/Ieast refer to
81 C points relative to the Northern/Eastern edges of the model
82 C eg. OB_Jnorth(3)=-1 means that the point (3,Ny) is a northern O-B.
83 C
84 C With exch2, the global domain used for specifying the boundary (and
85 C boundary value files) is different for N,S and E,W boundaries:
86 C - for N,S, the facets are stacked in x (like W2_mapIO=-1)
87 C - for E,W, the facets are stacked in y, so that E,W boundaries in
88 C different facets cannot have the same I
89 C
90 C OB_Jnorth(W2_maxXStackNx) :: global index array of northern open-boundary point
91 C OB_Jsouth(W2_maxXStackNx) :: global index array of southern open-boundary point
92 C OB_Ieast(W2_maxYStackNy) :: global index array of eastern open-boundary point
93 C OB_Iwest(W2_maxYStackNy) :: global index array of western open-boundary point
94
95 #ifdef ALLOW_EXCH2
96 INTEGER OB_Jnorth(W2_maxXStackNx)
97 INTEGER OB_Jsouth(W2_maxXStackNx)
98 INTEGER OB_Ieast(W2_maxYStackNy)
99 INTEGER OB_Iwest(W2_maxYStackNy)
100 #else
101 INTEGER OB_Jnorth(Nx)
102 INTEGER OB_Jsouth(Nx)
103 INTEGER OB_Ieast(Ny)
104 INTEGER OB_Iwest(Ny)
105 #endif
106
107 C With exch2, we use different global domains for specifying
108 C N,S resp. E,W boundaries (and for reading in the corresponding data):
109 C
110 C OBNS_Nx :: width of global domain for OB_Jnorth, OB_Jsouth
111 C OBNS_Ny :: height of global domain for OB_Jnorth, OB_Jsouth
112 C OBEW_Nx :: width of global domain for OB_Ieast, OB_Iwest
113 C OBEW_Ny :: height of global domain for OB_Ieast, OB_Iwest
114
115 INTEGER OBNS_Nx, OBNS_Ny
116 INTEGER OBEW_Nx, OBEW_Ny
117 CEOP
118
119 C retired parameters
120 INTEGER nRetired
121 LOGICAL useOBCSYearlyFields
122
123 NAMELIST /OBCS_PARM01/
124 & insideOBmaskFile,
125 & OB_Jnorth,OB_Jsouth,OB_Ieast,OB_Iwest,
126 & useOrlanskiNorth,useOrlanskiSouth,
127 & useOrlanskiEast,useOrlanskiWest,
128 & useStevensNorth,useStevensSouth,
129 & useStevensEast,useStevensWest,
130 & OBCS_u1_adv_T, OBCS_u1_adv_S,
131 & OBNuFile,OBNvFile,OBNtFile,OBNsFile,OBNaFile,OBNhFile,
132 & OBSuFile,OBSvFile,OBStFile,OBSsFile,OBSaFile,OBShFile,
133 & OBEuFile,OBEvFile,OBEtFile,OBEsFile,OBEaFile,OBEhFile,
134 & OBWuFile,OBWvFile,OBWtFile,OBWsFile,OBWaFile,OBWhFile,
135 & OBNslFile,OBSslFile,OBEslFile,OBWslFile,
136 & OBNsnFile,OBSsnFile,OBEsnFile,OBWsnFile,
137 & OBNuiceFile,OBSuiceFile,OBEuiceFile,OBWuiceFile,
138 & OBNviceFile,OBSviceFile,OBEviceFile,OBWviceFile,
139 & OBNetaFile, OBSetaFile, OBEetaFile, OBWetaFile,
140 & OBNwFile, OBSwFile, OBEwFile, OBWwFile,
141 & OBNAmFile, OBSAmFile, OBEAmFile, OBWAmFile,
142 & OBNPhFile, OBSPhFile, OBEPhFile, OBWPhFile,
143 #ifdef ALLOW_PTRACERS
144 & OBCS_u1_adv_Tr,
145 & OBNptrFile,OBSptrFile,OBEptrFile,OBWptrFile,
146 #endif
147 & useOBCSsponge, useSeaiceSponge,
148 & useOBCSbalance, useOBCStides, useOBCSprescribe,
149 & OBCS_balanceFacN, OBCS_balanceFacS,
150 & OBCS_balanceFacE, OBCS_balanceFacW,
151 & useOBCSYearlyFields, OBCSfixTopo,
152 & OBCS_uvApplyFac,
153 & OBCS_monitorFreq, OBCS_monSelect, OBCSprintDiags,
154 & tidalPeriod
155
156 #ifdef ALLOW_ORLANSKI
157 NAMELIST /OBCS_PARM02/
158 & CMAX, cvelTimeScale, CFIX, useFixedCEast, useFixedCWest
159 #endif
160
161 #ifdef ALLOW_OBCS_SPONGE
162 NAMELIST /OBCS_PARM03/
163 & Urelaxobcsinner,Urelaxobcsbound,
164 & Vrelaxobcsinner,Vrelaxobcsbound,
165 & spongeThickness
166 #endif
167 #ifdef ALLOW_OBCS_STEVENS
168 NAMELIST /OBCS_PARM04/
169 & TrelaxStevens,SrelaxStevens,
170 & useStevensPhaseVel,useStevensAdvection
171 #endif /* ALLOW_OBCS_STEVENS */
172 #ifdef ALLOW_OBCS_SEAICE_SPONGE
173 NAMELIST /OBCS_PARM05/
174 & Arelaxobcsinner, Arelaxobcsbound,
175 & Hrelaxobcsinner, Hrelaxobcsbound,
176 & SLrelaxobcsinner,SLrelaxobcsbound,
177 & SNrelaxobcsinner,SNrelaxobcsbound,
178 & seaiceSpongeThickness
179 #endif
180
181 IF ( .NOT.useOBCS ) THEN
182 C- pkg OBCS is not used
183 _BEGIN_MASTER(myThid)
184 C- Track pkg activation status:
185 C print a (weak) warning if data.obcs is found
186 CALL PACKAGES_UNUSED_MSG( 'useOBCS', ' ', ' ' )
187 _END_MASTER(myThid)
188 RETURN
189 ENDIF
190
191 _BEGIN_MASTER(myThid)
192
193 #ifdef ALLOW_EXCH2
194 OBNS_Nx = exch2_xStack_Nx
195 OBNS_Ny = exch2_xStack_Ny
196 OBEW_Nx = exch2_yStack_Nx
197 OBEW_Ny = exch2_yStack_Ny
198 #else
199 OBNS_Nx = Nx
200 OBNS_Ny = Ny
201 OBEW_Nx = Nx
202 OBEW_Ny = Ny
203 #endif
204
205 C-- Default flags and values for OBCS
206 OB_indexNone = -99
207 OB_indexUnset = 0
208 insideOBmaskFile = ' '
209 DO i=1,OBNS_Nx
210 OB_Jnorth(i) = OB_indexUnset
211 OB_Jsouth(i) = OB_indexUnset
212 ENDDO
213 DO j=1,OBEW_Ny
214 OB_Ieast(j) = OB_indexUnset
215 OB_Iwest(j) = OB_indexUnset
216 ENDDO
217 OBCS_indexStatus = 0
218 useOrlanskiNorth =.FALSE.
219 useOrlanskiSouth =.FALSE.
220 useOrlanskiEast =.FALSE.
221 useOrlanskiWest =.FALSE.
222 useStevensNorth =.FALSE.
223 useStevensSouth =.FALSE.
224 useStevensEast =.FALSE.
225 useStevensWest =.FALSE.
226 useStevensPhaseVel =.TRUE.
227 useStevensAdvection=.TRUE.
228 useOBCSsponge =.FALSE.
229 useSeaiceSponge =.FALSE.
230 useOBCSbalance =.FALSE.
231 OBCS_balanceFacN = 1. _d 0
232 OBCS_balanceFacS = 1. _d 0
233 OBCS_balanceFacE = 1. _d 0
234 OBCS_balanceFacW = 1. _d 0
235 OBCS_u1_adv_T = 0
236 OBCS_u1_adv_S = 0
237 useOBCSprescribe =.FALSE.
238 OBCSfixTopo =.FALSE.
239 OBCS_uvApplyFac = 1. _d 0
240 OBCS_monitorFreq = monitorFreq
241 OBCS_monSelect = 0
242 OBCSprintDiags = debugLevel.GE.debLevC
243
244 OBNuFile = ' '
245 OBNvFile = ' '
246 OBNtFile = ' '
247 OBNsFile = ' '
248 OBNaFile = ' '
249 OBNhFile = ' '
250 OBNslFile = ' '
251 OBNsnFile = ' '
252 OBNuiceFile = ' '
253 OBNviceFile = ' '
254 OBSuFile = ' '
255 OBSvFile = ' '
256 OBStFile = ' '
257 OBSsFile = ' '
258 OBSaFile = ' '
259 OBShFile = ' '
260 OBSslFile = ' '
261 OBSsnFile = ' '
262 OBSuiceFile = ' '
263 OBSviceFile = ' '
264 OBEuFile = ' '
265 OBEvFile = ' '
266 OBEtFile = ' '
267 OBEsFile = ' '
268 OBEaFile = ' '
269 OBEhFile = ' '
270 OBEslFile = ' '
271 OBEsnFile = ' '
272 OBEuiceFile = ' '
273 OBEviceFile = ' '
274 OBWuFile = ' '
275 OBWvFile = ' '
276 OBWtFile = ' '
277 OBWsFile = ' '
278 OBWaFile = ' '
279 OBWhFile = ' '
280 OBWslFile = ' '
281 OBWsnFile = ' '
282 OBWuiceFile = ' '
283 OBWviceFile = ' '
284 OBNetaFile = ' '
285 OBSetaFile = ' '
286 OBEetaFile = ' '
287 OBWetaFile = ' '
288 OBNwFile = ' '
289 OBSwFile = ' '
290 OBEwFile = ' '
291 OBWwFile = ' '
292 OBNAmFile = ' '
293 OBSAmFile = ' '
294 OBEAmFile = ' '
295 OBWAmFile = ' '
296 OBNPhFile = ' '
297 OBSPhFile = ' '
298 OBEPhFile = ' '
299 OBWPhFile = ' '
300 #ifdef ALLOW_PTRACERS
301 DO iTracer = 1, PTRACERS_num
302 OBCS_u1_adv_Tr(iTracer) = 0
303 OBNptrFile(iTracer) = ' '
304 OBSptrFile(iTracer) = ' '
305 OBEptrFile(iTracer) = ' '
306 OBWptrFile(iTracer) = ' '
307 ENDDO
308 #endif
309 #ifdef ALLOW_OBCS_TIDES
310 DO i = 1, tidalComponents
311 tidalPeriod(i) = 0. _d 0
312 ENDDO
313 #endif
314 C- retired parameters
315 nRetired = 0
316 useOBCSYearlyFields = .FALSE.
317
318 C Open and read the data.obcs file
319 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: opening data.obcs'
320 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
321 & SQUEEZE_RIGHT , myThid )
322 CALL OPEN_COPY_DATA_FILE(
323 I 'data.obcs', 'OBCS_READPARMS',
324 O iUnit,
325 I myThid )
326
327 C-- Read parameters from open data file
328 READ(UNIT=iUnit,NML=OBCS_PARM01)
329
330 C- retired parameter
331 IF ( useOBCSYearlyFields ) THEN
332 nRetired = nRetired + 1
333 WRITE(msgBuf,'(A,A)')
334 & 'OBCS_READPARMS: "useOBCSYearlyFields"',
335 & ' no longer allowed in file "data.obcs"'
336 CALL PRINT_ERROR( msgBuf, myThid )
337 WRITE(msgBuf,'(A,A)') 'OBCS_READPARMS: ',
338 & ' was moved to "data.exf", namelist: "EXF_NML_OBCS"'
339 CALL PRINT_ERROR( msgBuf, myThid )
340 ENDIF
341
342 #ifdef ALLOW_ORLANSKI
343 C Default Orlanski radiation parameters
344 CMAX = 0.45 _d 0 /* maximum allowable phase speed-CFL for AB-II */
345 cvelTimeScale = 2000.0 _d 0 /* Averaging period for phase speed (s) */
346 CFIX = 0.8 _d 0 /* Fixed boundary phase speed in m/s */
347 useFixedCEast=.FALSE.
348 useFixedCWest=.FALSE.
349 IF (useOrlanskiNorth.OR.
350 & useOrlanskiSouth.OR.
351 & useOrlanskiEast.OR.
352 & useOrlanskiWest)
353 & READ(UNIT=iUnit,NML=OBCS_PARM02)
354 #endif
355
356 #ifdef ALLOW_OBCS_SPONGE
357 C Default sponge layer parameters:
358 C sponge layer is turned off by default
359 spongeThickness = 0
360 Urelaxobcsinner = 0. _d 0
361 Urelaxobcsbound = 0. _d 0
362 Vrelaxobcsinner = 0. _d 0
363 Vrelaxobcsbound = 0. _d 0
364 CML this was the previous default in units of days
365 CML spongeThickness = 2
366 CML Urelaxobcsinner = 5. _d 0
367 CML Urelaxobcsbound = 1. _d 0
368 CML Vrelaxobcsinner = 5. _d 0
369 CML Vrelaxobcsbound = 1. _d 0
370 IF (useOBCSsponge)
371 & READ(UNIT=iUnit,NML=OBCS_PARM03)
372 #endif
373 #ifdef ALLOW_OBCS_STEVENS
374 TrelaxStevens = 0. _d 0
375 SrelaxStevens = 0. _d 0
376 IF ( useStevensNorth .OR. useStevensSouth
377 & .OR. useStevensEast .OR. useStevensWest )
378 & READ(UNIT=iUnit,NML=OBCS_PARM04)
379 #endif
380 #ifdef ALLOW_OBCS_SEAICE_SPONGE
381 C Default seaice sponge layer parameters:
382 C seaice sponge layer is turned off by default
383 seaiceSpongeThickness = 0
384 Arelaxobcsinner = 0. _d 0
385 Arelaxobcsbound = 0. _d 0
386 Hrelaxobcsinner = 0. _d 0
387 Hrelaxobcsbound = 0. _d 0
388 SLrelaxobcsinner = 0. _d 0
389 SLrelaxobcsbound = 0. _d 0
390 SNrelaxobcsinner = 0. _d 0
391 SNrelaxobcsbound = 0. _d 0
392 IF (useSeaiceSponge) READ(UNIT=iUnit,NML=OBCS_PARM05)
393 #endif
394
395 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: finished reading data.obcs'
396 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
397 & SQUEEZE_RIGHT , myThid )
398
399 C-- Close the open data file
400 CLOSE(iUnit)
401
402 C- retired parameter
403 IF ( nRetired .GT. 0 ) THEN
404 WRITE(msgBuf,'(A)')
405 & 'OBCS_READPARMS: reading parameter file "data.obcs"'
406 CALL PRINT_ERROR( msgBuf, myThid )
407 WRITE(msgBuf,'(A)')
408 & 'some out of date parameters were found in namelist'
409 CALL PRINT_ERROR( msgBuf, myThid )
410 STOP 'ABNORMAL END: S/R OBCS_READPARMS'
411 ENDIF
412
413 C- Account for periodicity if negative indices were supplied
414 DO j=1,OBEW_Ny
415 IF ( OB_Ieast(j) .NE.OB_indexUnset .AND.
416 & OB_Ieast(j) .LT.0 ) OB_Ieast(j) = OB_Ieast(j)+OBEW_Nx+1
417 ENDDO
418 DO i=1,OBNS_Nx
419 IF ( OB_Jnorth(i).NE.OB_indexUnset .AND.
420 & OB_Jnorth(i).LT.0 ) OB_Jnorth(i)=OB_Jnorth(i)+OBNS_Ny+1
421 ENDDO
422 IF ( debugLevel.GE.debLevA ) THEN
423 CALL WRITE_0D_I( OB_indexUnset, INDEX_NONE,' OB_indexUnset =',
424 & ' /* unset OB index value (i.e. no OB) */')
425 c write(*,*) 'OB Jn =',OB_Jnorth
426 c write(*,*) 'OB Js =',OB_Jsouth
427 c write(*,*) 'OB Ie =',OB_Ieast
428 c write(*,*) 'OB Iw =',OB_Iwest
429 WRITE(msgBuf,'(A)') ' Northern OB global indices : OB_Jnorth ='
430 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
431 & SQUEEZE_RIGHT, myThid )
432 CALL PRINT_LIST_I( OB_Jnorth, 1, OBNS_Nx, INDEX_I,
433 & .FALSE., .TRUE., standardMessageUnit )
434 WRITE(msgBuf,'(A)') ' Southern OB global indices : OB_Jsouth ='
435 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
436 & SQUEEZE_RIGHT, myThid )
437 CALL PRINT_LIST_I( OB_Jsouth, 1, OBNS_Nx, INDEX_I,
438 & .FALSE., .TRUE., standardMessageUnit )
439 WRITE(msgBuf,'(A)') ' Eastern OB global indices : OB_Ieast ='
440 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
441 & SQUEEZE_RIGHT, myThid )
442 CALL PRINT_LIST_I( OB_Ieast, 1, OBEW_Ny, INDEX_J,
443 & .FALSE., .TRUE., standardMessageUnit )
444 WRITE(msgBuf,'(A)') ' Western OB global indices : OB_Iwest ='
445 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
446 & SQUEEZE_RIGHT, myThid )
447 CALL PRINT_LIST_I( OB_Iwest, 1, OBEW_Ny, INDEX_J,
448 & .FALSE., .TRUE., standardMessageUnit )
449 WRITE(msgBuf,'(A)') ' '
450 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
451 & SQUEEZE_RIGHT, myThid )
452 ENDIF
453
454 C-- Continue master-thread only since global OB indices (+ OB_indexUnset)
455 C are not shared (not in common block).
456
457 C-- Calculate the tiled OB index arrays OB_Jn/Js/Ie/Iw here from the
458 C global indices OB_Jnorth/Jsouth/Ieast/Iwest.
459 C Note: This part of the code has been moved from obcs_init_fixed
460 C to this routine because the OB_Jn/Js/Ie/Iw index arrays are
461 C required by INI_DEPTH (calling OBCS_CHECK_DEPTHS, but only needs
462 C valid interior indices) which is called before OBCS_INIT_FIXED.
463 DO bj = 1, nSy
464 DO bi = 1, nSx
465
466 DO i=1-OLx,sNx+OLx
467 OB_Jn(i,bi,bj) = OB_indexNone
468 OB_Js(i,bi,bj) = OB_indexNone
469 ENDDO
470
471 DO j=1-OLy,sNy+OLy
472 OB_Ie(j,bi,bj) = OB_indexNone
473 OB_Iw(J,bi,bj) = OB_indexNone
474 ENDDO
475
476 #ifdef ALLOW_EXCH2
477
478 C-- We apply OBCS only inside tile and exchange overlaps later
479 tN = W2_myTileList(bi,bj)
480 C 1. N/S boundaries
481 C convert from local y index J to global y index jG
482 C for N/S boundaries, we use faces stacked in x direction
483 DO i=1,sNx
484 iG = exch2_txXStackLo(tN)+i-1
485 C- Northern boundaries
486 IF ( OB_Jnorth(iG).NE.OB_indexUnset ) THEN
487 C loop over local y index J
488 DO j=1,sNy+1
489 jG = exch2_tyXStackLo(tN)+j-1
490 IF ( jG.EQ.OB_Jnorth(iG) ) OB_Jn(i,bi,bj) = j
491 ENDDO
492 ENDIF
493 C- Southern boundaries
494 IF ( OB_Jsouth(iG).NE.OB_indexUnset ) THEN
495 DO j=0,sNy
496 jG = exch2_tyXStackLo(tN)+j-1
497 IF ( jG.EQ.OB_Jsouth(iG) ) OB_Js(i,bi,bj) = j
498 ENDDO
499 ENDIF
500 ENDDO
501 C 2. E/W boundaries
502 C convert from local y index J to global y index jG
503 c for E/W boundaries, we use faces stacked in y direction
504 DO j=1,sNy
505 jG = exch2_tyYStackLo(tN)+j-1
506 C- Eastern boundaries
507 IF ( OB_Ieast(jG).NE.OB_indexUnset ) THEN
508 C loop over local x index I
509 DO i=1,sNx+1
510 iG = exch2_txYStackLo(tN)+i-1
511 IF ( iG.EQ.OB_Ieast(jG) ) OB_Ie(j,bi,bj) = i
512 ENDDO
513 ENDIF
514 C- Western boundaries
515 IF ( OB_Iwest(jG).NE.OB_indexUnset ) THEN
516 DO i=0,sNx
517 iG = exch2_txYStackLo(tN)+i-1
518 IF ( iG.EQ.OB_Iwest(jG) ) OB_Iw(j,bi,bj) = i
519 ENDDO
520 ENDIF
521 ENDDO
522
523 C- OB-index tiled-arrays are set for tile-interior region
524 OBCS_indexStatus = 1
525
526 #else /* ALLOW_EXCH2 */
527
528 DO j=1-OLy,sNy+OLy
529 C convert from local y index J to global y index jG
530 jG = myYGlobalLo+(bj-1)*sNy+j-1
531 C use periodicity to deal with out of range points caused by the overlaps.
532 C they will be excluded by the mask in any case, but this saves array
533 C out-of-bounds errors here.
534 jGm = 1+MOD( jG-1+Ny , Ny )
535 C- Eastern boundaries
536 C OB_Ieast(jGm) allows to put the eastern boundary at variable x locations
537 IF ( OB_Ieast(jGm).NE.OB_indexUnset ) THEN
538 C loop over local x index I
539 DO i=1,sNx+1
540 iG = myXGlobalLo+(bi-1)*sNx+i-1
541 iGm = 1+MOD( iG-1+Nx , Nx )
542 IF ( iG.EQ.OB_Ieast(jGm) ) OB_Ie(j,bi,bj) = i
543 ENDDO
544 ENDIF
545 C- Western boundaries
546 IF ( OB_Iwest(jGm).NE.OB_indexUnset ) THEN
547 DO i=0,sNx
548 iG = myXGlobalLo+(bi-1)*sNx+i-1
549 iGm = 1+MOD( iG-1+Nx , Nx )
550 IF ( iG.EQ.OB_Iwest(jGm) ) OB_Iw(j,bi,bj) = i
551 ENDDO
552 ENDIF
553 ENDDO
554
555 DO i=1-OLx,sNx+OLx
556 iG = myXGlobalLo+(bi-1)*sNx+i-1
557 iGm = 1+MOD( iG-1+Nx , Nx )
558 C- Northern boundaries
559 C OB_Jnorth(iG) allows to put the northern boundary at variable y locations
560 IF ( OB_Jnorth(iGm).NE.OB_indexUnset ) THEN
561 DO j=1,sNy+1
562 jG = myYGlobalLo+(bj-1)*sNy+j-1
563 jGm = 1+MOD( jG-1+Ny , Ny )
564 IF ( jG.EQ.OB_Jnorth(iGm) ) OB_Jn(i,bi,bj) = j
565 ENDDO
566 ENDIF
567 C- Southern boundaries
568 IF ( OB_Jsouth(iGm).NE.OB_indexUnset ) THEN
569 DO j=0,sNy
570 jG = myYGlobalLo+(bj-1)*sNy+j-1
571 jGm = 1+MOD( jG-1+Ny , Ny )
572 IF ( jG.EQ.OB_Jsouth(iGm) ) OB_Js(i,bi,bj) = j
573 ENDDO
574 ENDIF
575 ENDDO
576
577 C- OB-index tiled-arrays are set for interior and overlap regions
578 OBCS_indexStatus = 2
579
580 #endif /* ALLOW_EXCH2 */
581
582 C bi,bj-loops
583 ENDDO
584 ENDDO
585
586 _END_MASTER(myThid)
587 C-- Everyone else must wait for the parameters to be loaded
588 C and tiled OB indices to be set.
589 _BARRIER
590
591 #endif /* ALLOW_OBCS */
592 RETURN
593 END

  ViewVC Help
Powered by ViewVC 1.1.22