/[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.44 - (show annotations) (download)
Tue Sep 25 16:39:20 2012 UTC (11 years, 8 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint64
Changes since 1.43: +14 -9 lines
  - fixed some indexing bugs in obcs_seaice_sponge.F
  - added obcs relaxation subroutines for HSALT and HSNOW
  - changes verification/seaice_obcs/results/obcs_seaice_sponge.F
Modified Files:
 pkg/obcs/OBCS_SEAICE.h obcs_readparms.F obcs_seaice_sponge.F
 verification/seaice_obcs/input.seaiceSponge/data.obcs
 verification/seaice_obcs/results/output.seaiceSponge.txt

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

  ViewVC Help
Powered by ViewVC 1.1.22