/[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.49 - (show annotations) (download)
Wed Aug 9 15:23:37 2017 UTC (6 years, 10 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint66l, checkpoint66k, checkpoint66j
Changes since 1.48: +6 -2 lines
replace CLOSE(nmlfileUnit) with CLOSE(nmlfileUnit,STATUS='DELETE') to remove
scratchfiles after closing, except for SINGLE_DISK_IO, when everything
stays the same

1 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_readparms.F,v 1.48 2014/11/25 01:07:23 jmc Exp $
2 C $Name: BASE $
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 & OBNconnectFile, OBSconnectFile,
126 & OBEconnectFile, OBWconnectFile,
127 & OB_Jnorth,OB_Jsouth,OB_Ieast,OB_Iwest,
128 & useOrlanskiNorth,useOrlanskiSouth,
129 & useOrlanskiEast,useOrlanskiWest,
130 & useStevensNorth,useStevensSouth,
131 & useStevensEast,useStevensWest,
132 & OBCS_u1_adv_T, OBCS_u1_adv_S,
133 & OBNuFile,OBNvFile,OBNtFile,OBNsFile,OBNaFile,OBNhFile,
134 & OBSuFile,OBSvFile,OBStFile,OBSsFile,OBSaFile,OBShFile,
135 & OBEuFile,OBEvFile,OBEtFile,OBEsFile,OBEaFile,OBEhFile,
136 & OBWuFile,OBWvFile,OBWtFile,OBWsFile,OBWaFile,OBWhFile,
137 & OBNslFile,OBSslFile,OBEslFile,OBWslFile,
138 & OBNsnFile,OBSsnFile,OBEsnFile,OBWsnFile,
139 & OBNuiceFile,OBSuiceFile,OBEuiceFile,OBWuiceFile,
140 & OBNviceFile,OBSviceFile,OBEviceFile,OBWviceFile,
141 & OBNetaFile, OBSetaFile, OBEetaFile, OBWetaFile,
142 & OBNwFile, OBSwFile, OBEwFile, OBWwFile,
143 & OBNAmFile, OBSAmFile, OBEAmFile, OBWAmFile,
144 & OBNPhFile, OBSPhFile, OBEPhFile, OBWPhFile,
145 #ifdef ALLOW_PTRACERS
146 & OBCS_u1_adv_Tr,
147 & OBNptrFile,OBSptrFile,OBEptrFile,OBWptrFile,
148 #endif
149 & useOBCSsponge, useSeaiceSponge,
150 & OBCSsponge_N , OBCSsponge_S,
151 & OBCSsponge_E, OBCSsponge_W,
152 & OBCSsponge_UatNS, OBCSsponge_UatEW,
153 & OBCSsponge_VatNS, OBCSsponge_VatEW,
154 & OBCSsponge_Theta, OBCSsponge_Salt, useLinearSponge,
155 & useOBCSbalance, useOBCStides, useOBCSprescribe,
156 & OBCS_balanceFacN, OBCS_balanceFacS,
157 & OBCS_balanceFacE, OBCS_balanceFacW,
158 & useOBCSYearlyFields, OBCSfixTopo,
159 & OBCS_uvApplyFac,
160 & OBCS_monitorFreq, OBCS_monSelect, OBCSprintDiags,
161 & tidalPeriod
162
163 #ifdef ALLOW_ORLANSKI
164 NAMELIST /OBCS_PARM02/
165 & CMAX, cvelTimeScale, CFIX, useFixedCEast, useFixedCWest
166 #endif
167
168 #ifdef ALLOW_OBCS_SPONGE
169 NAMELIST /OBCS_PARM03/
170 & Urelaxobcsinner,Urelaxobcsbound,
171 & Vrelaxobcsinner,Vrelaxobcsbound,
172 & spongeThickness
173 #endif
174 #ifdef ALLOW_OBCS_STEVENS
175 NAMELIST /OBCS_PARM04/
176 & TrelaxStevens,SrelaxStevens,
177 & useStevensPhaseVel,useStevensAdvection
178 #endif /* ALLOW_OBCS_STEVENS */
179 #ifdef ALLOW_OBCS_SEAICE_SPONGE
180 NAMELIST /OBCS_PARM05/
181 & Arelaxobcsinner, Arelaxobcsbound,
182 & Hrelaxobcsinner, Hrelaxobcsbound,
183 & SLrelaxobcsinner,SLrelaxobcsbound,
184 & SNrelaxobcsinner,SNrelaxobcsbound,
185 & seaiceSpongeThickness
186 #endif
187
188 IF ( .NOT.useOBCS ) THEN
189 C- pkg OBCS is not used
190 _BEGIN_MASTER(myThid)
191 C- Track pkg activation status:
192 C print a (weak) warning if data.obcs is found
193 CALL PACKAGES_UNUSED_MSG( 'useOBCS', ' ', ' ' )
194 _END_MASTER(myThid)
195 RETURN
196 ENDIF
197
198 _BEGIN_MASTER(myThid)
199
200 #ifdef ALLOW_EXCH2
201 OBNS_Nx = exch2_xStack_Nx
202 OBNS_Ny = exch2_xStack_Ny
203 OBEW_Nx = exch2_yStack_Nx
204 OBEW_Ny = exch2_yStack_Ny
205 #else
206 OBNS_Nx = Nx
207 OBNS_Ny = Ny
208 OBEW_Nx = Nx
209 OBEW_Ny = Ny
210 #endif
211
212 C-- Default flags and values for OBCS
213 OB_indexNone = -99
214 OB_indexUnset = 0
215 insideOBmaskFile = ' '
216 OBNconnectFile = ' '
217 OBSconnectFile = ' '
218 OBEconnectFile = ' '
219 OBWconnectFile = ' '
220 DO i=1,OBNS_Nx
221 OB_Jnorth(i) = OB_indexUnset
222 OB_Jsouth(i) = OB_indexUnset
223 ENDDO
224 DO j=1,OBEW_Ny
225 OB_Ieast(j) = OB_indexUnset
226 OB_Iwest(j) = OB_indexUnset
227 ENDDO
228 OBCS_indexStatus = 0
229 useOrlanskiNorth =.FALSE.
230 useOrlanskiSouth =.FALSE.
231 useOrlanskiEast =.FALSE.
232 useOrlanskiWest =.FALSE.
233 useStevensNorth =.FALSE.
234 useStevensSouth =.FALSE.
235 useStevensEast =.FALSE.
236 useStevensWest =.FALSE.
237 useStevensPhaseVel =.TRUE.
238 useStevensAdvection=.TRUE.
239 useOBCSsponge =.FALSE.
240 useSeaiceSponge =.FALSE.
241 OBCSsponge_N =.TRUE.
242 OBCSsponge_S =.TRUE.
243 OBCSsponge_E =.TRUE.
244 OBCSsponge_W =.TRUE.
245 OBCSsponge_UatNS =.TRUE.
246 OBCSsponge_UatEW =.TRUE.
247 OBCSsponge_VatNS =.TRUE.
248 OBCSsponge_VatEW =.TRUE.
249 OBCSsponge_Theta =.TRUE.
250 OBCSsponge_Salt =.TRUE.
251 useLinearSponge =.FALSE.
252 useOBCSbalance =.FALSE.
253 OBCS_balanceFacN = 1. _d 0
254 OBCS_balanceFacS = 1. _d 0
255 OBCS_balanceFacE = 1. _d 0
256 OBCS_balanceFacW = 1. _d 0
257 OBCS_u1_adv_T = 0
258 OBCS_u1_adv_S = 0
259 useOBCSprescribe =.FALSE.
260 OBCSfixTopo =.FALSE.
261 OBCS_uvApplyFac = 1. _d 0
262 OBCS_monitorFreq = monitorFreq
263 OBCS_monSelect = 0
264 OBCSprintDiags = debugLevel.GE.debLevC
265
266 OBNuFile = ' '
267 OBNvFile = ' '
268 OBNtFile = ' '
269 OBNsFile = ' '
270 OBNaFile = ' '
271 OBNhFile = ' '
272 OBNslFile = ' '
273 OBNsnFile = ' '
274 OBNuiceFile = ' '
275 OBNviceFile = ' '
276 OBSuFile = ' '
277 OBSvFile = ' '
278 OBStFile = ' '
279 OBSsFile = ' '
280 OBSaFile = ' '
281 OBShFile = ' '
282 OBSslFile = ' '
283 OBSsnFile = ' '
284 OBSuiceFile = ' '
285 OBSviceFile = ' '
286 OBEuFile = ' '
287 OBEvFile = ' '
288 OBEtFile = ' '
289 OBEsFile = ' '
290 OBEaFile = ' '
291 OBEhFile = ' '
292 OBEslFile = ' '
293 OBEsnFile = ' '
294 OBEuiceFile = ' '
295 OBEviceFile = ' '
296 OBWuFile = ' '
297 OBWvFile = ' '
298 OBWtFile = ' '
299 OBWsFile = ' '
300 OBWaFile = ' '
301 OBWhFile = ' '
302 OBWslFile = ' '
303 OBWsnFile = ' '
304 OBWuiceFile = ' '
305 OBWviceFile = ' '
306 OBNetaFile = ' '
307 OBSetaFile = ' '
308 OBEetaFile = ' '
309 OBWetaFile = ' '
310 OBNwFile = ' '
311 OBSwFile = ' '
312 OBEwFile = ' '
313 OBWwFile = ' '
314 OBNAmFile = ' '
315 OBSAmFile = ' '
316 OBEAmFile = ' '
317 OBWAmFile = ' '
318 OBNPhFile = ' '
319 OBSPhFile = ' '
320 OBEPhFile = ' '
321 OBWPhFile = ' '
322 #ifdef ALLOW_PTRACERS
323 DO iTracer = 1, PTRACERS_num
324 OBCS_u1_adv_Tr(iTracer) = 0
325 OBNptrFile(iTracer) = ' '
326 OBSptrFile(iTracer) = ' '
327 OBEptrFile(iTracer) = ' '
328 OBWptrFile(iTracer) = ' '
329 ENDDO
330 #endif
331 #ifdef ALLOW_OBCS_TIDES
332 DO i = 1, tidalComponents
333 tidalPeriod(i) = 0. _d 0
334 ENDDO
335 #endif
336 C- retired parameters
337 nRetired = 0
338 useOBCSYearlyFields = .FALSE.
339
340 C Open and read the data.obcs file
341 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: opening data.obcs'
342 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
343 & SQUEEZE_RIGHT , myThid )
344 CALL OPEN_COPY_DATA_FILE(
345 I 'data.obcs', 'OBCS_READPARMS',
346 O iUnit,
347 I myThid )
348
349 C-- Read parameters from open data file
350 READ(UNIT=iUnit,NML=OBCS_PARM01)
351
352 C- retired parameter
353 IF ( useOBCSYearlyFields ) THEN
354 nRetired = nRetired + 1
355 WRITE(msgBuf,'(A,A)')
356 & 'OBCS_READPARMS: "useOBCSYearlyFields"',
357 & ' no longer allowed in file "data.obcs"'
358 CALL PRINT_ERROR( msgBuf, myThid )
359 WRITE(msgBuf,'(A,A)') 'OBCS_READPARMS: ',
360 & ' was moved to "data.exf", namelist: "EXF_NML_OBCS"'
361 CALL PRINT_ERROR( msgBuf, myThid )
362 ENDIF
363
364 #ifdef ALLOW_ORLANSKI
365 C Default Orlanski radiation parameters
366 CMAX = 0.45 _d 0 /* maximum allowable phase speed-CFL for AB-II */
367 cvelTimeScale = 2000.0 _d 0 /* Averaging period for phase speed (s) */
368 CFIX = 0.8 _d 0 /* Fixed boundary phase speed in m/s */
369 useFixedCEast=.FALSE.
370 useFixedCWest=.FALSE.
371 IF (useOrlanskiNorth.OR.
372 & useOrlanskiSouth.OR.
373 & useOrlanskiEast.OR.
374 & useOrlanskiWest)
375 & READ(UNIT=iUnit,NML=OBCS_PARM02)
376 #endif
377
378 #ifdef ALLOW_OBCS_SPONGE
379 C Default sponge layer parameters:
380 C sponge layer is turned off by default
381 spongeThickness = 0
382 Urelaxobcsinner = 0. _d 0
383 Urelaxobcsbound = 0. _d 0
384 Vrelaxobcsinner = 0. _d 0
385 Vrelaxobcsbound = 0. _d 0
386 CML this was the previous default in units of days
387 CML spongeThickness = 2
388 CML Urelaxobcsinner = 5. _d 0
389 CML Urelaxobcsbound = 1. _d 0
390 CML Vrelaxobcsinner = 5. _d 0
391 CML Vrelaxobcsbound = 1. _d 0
392 IF (useOBCSsponge)
393 & READ(UNIT=iUnit,NML=OBCS_PARM03)
394 #endif
395 #ifdef ALLOW_OBCS_STEVENS
396 TrelaxStevens = 0. _d 0
397 SrelaxStevens = 0. _d 0
398 IF ( useStevensNorth .OR. useStevensSouth
399 & .OR. useStevensEast .OR. useStevensWest )
400 & READ(UNIT=iUnit,NML=OBCS_PARM04)
401 #endif
402 #ifdef ALLOW_OBCS_SEAICE_SPONGE
403 C Default seaice sponge layer parameters:
404 C seaice sponge layer is turned off by default
405 seaiceSpongeThickness = 0
406 Arelaxobcsinner = 0. _d 0
407 Arelaxobcsbound = 0. _d 0
408 Hrelaxobcsinner = 0. _d 0
409 Hrelaxobcsbound = 0. _d 0
410 SLrelaxobcsinner = 0. _d 0
411 SLrelaxobcsbound = 0. _d 0
412 SNrelaxobcsinner = 0. _d 0
413 SNrelaxobcsbound = 0. _d 0
414 IF (useSeaiceSponge) READ(UNIT=iUnit,NML=OBCS_PARM05)
415 #endif
416
417 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: finished reading data.obcs'
418 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
419 & SQUEEZE_RIGHT , myThid )
420
421 C-- Close the open data file
422 #ifdef SINGLE_DISK_IO
423 CLOSE(iUnit)
424 #else
425 CLOSE(iUnit,STATUS='DELETE')
426 #endif /* SINGLE_DISK_IO */
427
428 C- retired parameter
429 IF ( nRetired .GT. 0 ) THEN
430 WRITE(msgBuf,'(A)')
431 & 'OBCS_READPARMS: reading parameter file "data.obcs"'
432 CALL PRINT_ERROR( msgBuf, myThid )
433 WRITE(msgBuf,'(A)')
434 & 'some out of date parameters were found in namelist'
435 CALL PRINT_ERROR( msgBuf, myThid )
436 STOP 'ABNORMAL END: S/R OBCS_READPARMS'
437 ENDIF
438
439 C- Account for periodicity if negative indices were supplied
440 DO j=1,OBEW_Ny
441 IF ( OB_Ieast(j) .NE.OB_indexUnset .AND.
442 & OB_Ieast(j) .LT.0 ) OB_Ieast(j) = OB_Ieast(j)+OBEW_Nx+1
443 ENDDO
444 DO i=1,OBNS_Nx
445 IF ( OB_Jnorth(i).NE.OB_indexUnset .AND.
446 & OB_Jnorth(i).LT.0 ) OB_Jnorth(i)=OB_Jnorth(i)+OBNS_Ny+1
447 ENDDO
448 IF ( debugLevel.GE.debLevA ) THEN
449 CALL WRITE_0D_I( OB_indexUnset, INDEX_NONE,' OB_indexUnset =',
450 & ' /* unset OB index value (i.e. no OB) */')
451 c write(*,*) 'OB Jn =',OB_Jnorth
452 c write(*,*) 'OB Js =',OB_Jsouth
453 c write(*,*) 'OB Ie =',OB_Ieast
454 c write(*,*) 'OB Iw =',OB_Iwest
455 WRITE(msgBuf,'(A)') ' Northern OB global indices : OB_Jnorth ='
456 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
457 & SQUEEZE_RIGHT, myThid )
458 CALL PRINT_LIST_I( OB_Jnorth, 1, OBNS_Nx, INDEX_I,
459 & .FALSE., .TRUE., standardMessageUnit )
460 WRITE(msgBuf,'(A)') ' Southern OB global indices : OB_Jsouth ='
461 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
462 & SQUEEZE_RIGHT, myThid )
463 CALL PRINT_LIST_I( OB_Jsouth, 1, OBNS_Nx, INDEX_I,
464 & .FALSE., .TRUE., standardMessageUnit )
465 WRITE(msgBuf,'(A)') ' Eastern OB global indices : OB_Ieast ='
466 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
467 & SQUEEZE_RIGHT, myThid )
468 CALL PRINT_LIST_I( OB_Ieast, 1, OBEW_Ny, INDEX_J,
469 & .FALSE., .TRUE., standardMessageUnit )
470 WRITE(msgBuf,'(A)') ' Western OB global indices : OB_Iwest ='
471 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
472 & SQUEEZE_RIGHT, myThid )
473 CALL PRINT_LIST_I( OB_Iwest, 1, OBEW_Ny, INDEX_J,
474 & .FALSE., .TRUE., standardMessageUnit )
475 WRITE(msgBuf,'(A)') ' '
476 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
477 & SQUEEZE_RIGHT, myThid )
478 ENDIF
479
480 C-- Continue master-thread only since global OB indices (+ OB_indexUnset)
481 C are not shared (not in common block).
482
483 C-- Calculate the tiled OB index arrays OB_Jn/Js/Ie/Iw here from the
484 C global indices OB_Jnorth/Jsouth/Ieast/Iwest.
485 C Note: This part of the code has been moved from obcs_init_fixed
486 C to this routine because the OB_Jn/Js/Ie/Iw index arrays are
487 C required by INI_DEPTH (calling OBCS_CHECK_DEPTHS, but only needs
488 C valid interior indices) which is called before OBCS_INIT_FIXED.
489 DO bj = 1, nSy
490 DO bi = 1, nSx
491
492 DO i=1-OLx,sNx+OLx
493 OB_Jn(i,bi,bj) = OB_indexNone
494 OB_Js(i,bi,bj) = OB_indexNone
495 ENDDO
496
497 DO j=1-OLy,sNy+OLy
498 OB_Ie(j,bi,bj) = OB_indexNone
499 OB_Iw(J,bi,bj) = OB_indexNone
500 ENDDO
501
502 #ifdef ALLOW_EXCH2
503
504 C-- We apply OBCS only inside tile and exchange overlaps later
505 tN = W2_myTileList(bi,bj)
506 C 1. N/S boundaries
507 C convert from local y index J to global y index jG
508 C for N/S boundaries, we use faces stacked in x direction
509 DO i=1,sNx
510 iG = exch2_txXStackLo(tN)+i-1
511 C- Northern boundaries
512 IF ( OB_Jnorth(iG).NE.OB_indexUnset ) THEN
513 C loop over local y index J
514 DO j=1,sNy+1
515 jG = exch2_tyXStackLo(tN)+j-1
516 IF ( jG.EQ.OB_Jnorth(iG) ) OB_Jn(i,bi,bj) = j
517 ENDDO
518 ENDIF
519 C- Southern boundaries
520 IF ( OB_Jsouth(iG).NE.OB_indexUnset ) THEN
521 DO j=0,sNy
522 jG = exch2_tyXStackLo(tN)+j-1
523 IF ( jG.EQ.OB_Jsouth(iG) ) OB_Js(i,bi,bj) = j
524 ENDDO
525 ENDIF
526 ENDDO
527 C 2. E/W boundaries
528 C convert from local y index J to global y index jG
529 c for E/W boundaries, we use faces stacked in y direction
530 DO j=1,sNy
531 jG = exch2_tyYStackLo(tN)+j-1
532 C- Eastern boundaries
533 IF ( OB_Ieast(jG).NE.OB_indexUnset ) THEN
534 C loop over local x index I
535 DO i=1,sNx+1
536 iG = exch2_txYStackLo(tN)+i-1
537 IF ( iG.EQ.OB_Ieast(jG) ) OB_Ie(j,bi,bj) = i
538 ENDDO
539 ENDIF
540 C- Western boundaries
541 IF ( OB_Iwest(jG).NE.OB_indexUnset ) THEN
542 DO i=0,sNx
543 iG = exch2_txYStackLo(tN)+i-1
544 IF ( iG.EQ.OB_Iwest(jG) ) OB_Iw(j,bi,bj) = i
545 ENDDO
546 ENDIF
547 ENDDO
548
549 C- OB-index tiled-arrays are set for tile-interior region
550 OBCS_indexStatus = 1
551
552 #else /* ALLOW_EXCH2 */
553
554 DO j=1-OLy,sNy+OLy
555 C convert from local y index J to global y index jG
556 jG = myYGlobalLo+(bj-1)*sNy+j-1
557 C use periodicity to deal with out of range points caused by the overlaps.
558 C they will be excluded by the mask in any case, but this saves array
559 C out-of-bounds errors here.
560 jGm = 1+MOD( jG-1+Ny , Ny )
561 C- Eastern boundaries
562 C OB_Ieast(jGm) allows to put the eastern boundary at variable x locations
563 IF ( OB_Ieast(jGm).NE.OB_indexUnset ) THEN
564 C loop over local x index I
565 DO i=1,sNx+1
566 iG = myXGlobalLo+(bi-1)*sNx+i-1
567 iGm = 1+MOD( iG-1+Nx , Nx )
568 IF ( iG.EQ.OB_Ieast(jGm) ) OB_Ie(j,bi,bj) = i
569 ENDDO
570 ENDIF
571 C- Western boundaries
572 IF ( OB_Iwest(jGm).NE.OB_indexUnset ) THEN
573 DO i=0,sNx
574 iG = myXGlobalLo+(bi-1)*sNx+i-1
575 iGm = 1+MOD( iG-1+Nx , Nx )
576 IF ( iG.EQ.OB_Iwest(jGm) ) OB_Iw(j,bi,bj) = i
577 ENDDO
578 ENDIF
579 ENDDO
580
581 DO i=1-OLx,sNx+OLx
582 iG = myXGlobalLo+(bi-1)*sNx+i-1
583 iGm = 1+MOD( iG-1+Nx , Nx )
584 C- Northern boundaries
585 C OB_Jnorth(iG) allows to put the northern boundary at variable y locations
586 IF ( OB_Jnorth(iGm).NE.OB_indexUnset ) THEN
587 DO j=1,sNy+1
588 jG = myYGlobalLo+(bj-1)*sNy+j-1
589 jGm = 1+MOD( jG-1+Ny , Ny )
590 IF ( jG.EQ.OB_Jnorth(iGm) ) OB_Jn(i,bi,bj) = j
591 ENDDO
592 ENDIF
593 C- Southern boundaries
594 IF ( OB_Jsouth(iGm).NE.OB_indexUnset ) THEN
595 DO j=0,sNy
596 jG = myYGlobalLo+(bj-1)*sNy+j-1
597 jGm = 1+MOD( jG-1+Ny , Ny )
598 IF ( jG.EQ.OB_Jsouth(iGm) ) OB_Js(i,bi,bj) = j
599 ENDDO
600 ENDIF
601 ENDDO
602
603 C- OB-index tiled-arrays are set for interior and overlap regions
604 OBCS_indexStatus = 2
605
606 #endif /* ALLOW_EXCH2 */
607
608 C bi,bj-loops
609 ENDDO
610 ENDDO
611
612 _END_MASTER(myThid)
613 C-- Everyone else must wait for the parameters to be loaded
614 C and tiled OB indices to be set.
615 _BARRIER
616
617 #endif /* ALLOW_OBCS */
618 RETURN
619 END

  ViewVC Help
Powered by ViewVC 1.1.22