/[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.36 - (show annotations) (download)
Tue Jun 7 22:23:46 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62z, checkpoint63g, checkpoint63, checkpoint63h, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c
Changes since 1.35: +2 -2 lines
refine debugLevel criteria when printing messages

1 C $Header: /u/gcmpack/MITgcm/pkg/obcs/obcs_readparms.F,v 1.35 2011/06/02 22:49:39 jmc 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 CHARACTER*(MAX_LEN_MBUF) msgBuf
51 INTEGER iUnit
52 INTEGER I, J
53 INTEGER bi, bj, iG, jG, iGm, jGm
54 #ifdef ALLOW_PTRACERS
55 INTEGER iTracer
56 #endif
57 #ifdef ALLOW_EXCH2
58 INTEGER tN
59 #endif /* ALLOW_EXCH2 */
60
61 C These are input arrays (of integers) that contain the *absolute*
62 C computational index of an open-boundary (OB) point.
63 C A zero (0) element means there is no corresponding OB in that column/row.
64 C The computational coordinate refers to "tracer" cells.
65 C For a northern/southern OB, the OB V point is to the south/north.
66 C For an eastern/western OB, the OB U point is to the west/east.
67 C eg.
68 C OB_Jnorth(3)=34 means that:
69 C T( 3 ,34) is a an OB point
70 C U(3:4,34) is a an OB point
71 C V( 4 ,34) is a an OB point
72 C while
73 C OB_Jsouth(3)=1 means that:
74 C T( 3 ,1) is a an OB point
75 C U(3:4,1) is a an OB point
76 C V( 4 ,2) is a an OB point
77 C
78 C For convenience, negative values for Jnorth/Ieast refer to
79 C points relative to the Northern/Eastern edges of the model
80 C eg. OB_Jnorth(3)=-1 means that the point (3,Ny) is a northern O-B.
81 C
82 C With exch2, the global domain used for specifying the boundary (and
83 C boundary value files) is different for N,S and E,W boundaries:
84 C - for N,S, the facets are stacked in x (like W2_mapIO=-1)
85 C - for E,W, the facets are stacked in y, so that E,W boundaries in
86 C different facets cannot have the same I
87 C
88 C OB_Jnorth(W2_maxXStackNx) :: global index array of northern open-boundary point
89 C OB_Jsouth(W2_maxXStackNx) :: global index array of southern open-boundary point
90 C OB_Ieast(W2_maxYStackNy) :: global index array of eastern open-boundary point
91 C OB_Iwest(W2_maxYStackNy) :: global index array of western open-boundary point
92
93 COMMON/OBCS_GLOBAL/ OB_Jnorth, OB_Jsouth, OB_Ieast, OB_Iwest
94 #ifdef ALLOW_EXCH2
95 INTEGER OB_Jnorth(W2_maxXStackNx)
96 INTEGER OB_Jsouth(W2_maxXStackNx)
97 INTEGER OB_Ieast(W2_maxYStackNy)
98 INTEGER OB_Iwest(W2_maxYStackNy)
99 #else
100 INTEGER OB_Jnorth(Nx)
101 INTEGER OB_Jsouth(Nx)
102 INTEGER OB_Ieast(Ny)
103 INTEGER OB_Iwest(Ny)
104 #endif
105
106 C With exch2, we use different global domains for specifying
107 C N,S resp. E,W boundaries (and for reading in the corresponding data):
108 C
109 C OBNS_Nx :: width of global domain for OB_Jnorth, OB_Jsouth
110 C OBNS_Ny :: height of global domain for OB_Jnorth, OB_Jsouth
111 C OBEW_Nx :: width of global domain for OB_Ieast, OB_Iwest
112 C OBEW_Ny :: height of global domain for OB_Ieast, OB_Iwest
113
114 INTEGER OBNS_Nx, OBNS_Ny
115 INTEGER OBEW_Nx, OBEW_Ny
116
117 #ifdef ALLOW_EXCH2
118 C buf :: used to exchange OB_Jnorth, ...
119 _RS buf(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nSx,nSy)
120 #endif
121 CEOP
122
123 C retired parameters
124 INTEGER nRetired
125 LOGICAL useOBCSYearlyFields
126
127 NAMELIST /OBCS_PARM01/
128 & insideOBmaskFile,
129 & OB_Jnorth,OB_Jsouth,OB_Ieast,OB_Iwest,
130 & useOrlanskiNorth,useOrlanskiSouth,
131 & useOrlanskiEast,useOrlanskiWest,
132 & useStevensNorth,useStevensSouth,
133 & useStevensEast,useStevensWest,
134 & OBNuFile,OBNvFile,OBNtFile,OBNsFile,OBNaFile,OBNhFile,
135 & OBSuFile,OBSvFile,OBStFile,OBSsFile,OBSaFile,OBShFile,
136 & OBEuFile,OBEvFile,OBEtFile,OBEsFile,OBEaFile,OBEhFile,
137 & OBWuFile,OBWvFile,OBWtFile,OBWsFile,OBWaFile,OBWhFile,
138 & OBNslFile,OBSslFile,OBEslFile,OBWslFile,
139 & OBNsnFile,OBSsnFile,OBEsnFile,OBWsnFile,
140 & OBNuiceFile,OBSuiceFile,OBEuiceFile,OBWuiceFile,
141 & OBNviceFile,OBSviceFile,OBEviceFile,OBWviceFile,
142 & OBNetaFile, OBSetaFile, OBEetaFile, OBWetaFile,
143 & OBNwFile, OBSwFile, OBEwFile, OBWwFile,
144 #ifdef ALLOW_PTRACERS
145 & OBNptrFile,OBSptrFile,OBEptrFile,OBWptrFile,
146 #endif
147 & useOBCSsponge, useOBCSbalance, useOBCSprescribe,
148 & OBCS_balanceFacN, OBCS_balanceFacS,
149 & OBCS_balanceFacE, OBCS_balanceFacW,
150 & useOBCSYearlyFields, OBCSfixTopo,
151 & OBCS_uvApplyFac,
152 & OBCS_monitorFreq, OBCS_monSelect, OBCSprintDiags
153
154 #ifdef ALLOW_ORLANSKI
155 NAMELIST /OBCS_PARM02/
156 & CMAX, cvelTimeScale, CFIX, useFixedCEast, useFixedCWest
157 #endif
158
159 #ifdef ALLOW_OBCS_SPONGE
160 NAMELIST /OBCS_PARM03/
161 & Urelaxobcsinner,Urelaxobcsbound,
162 & Vrelaxobcsinner,Vrelaxobcsbound,
163 & spongeThickness
164 #endif
165 #ifdef ALLOW_OBCS_STEVENS
166 NAMELIST /OBCS_PARM04/
167 & TrelaxStevens,SrelaxStevens,
168 & useStevensPhaseVel,useStevensAdvection
169 #endif /* ALLOW_OBCS_STEVENS */
170
171 _BEGIN_MASTER(myThid)
172
173 #ifdef ALLOW_EXCH2
174 OBNS_Nx = exch2_xStack_Nx
175 OBNS_Ny = exch2_xStack_Ny
176 OBEW_Nx = exch2_yStack_Nx
177 OBEW_Ny = exch2_yStack_Ny
178 #else
179 OBNS_Nx = Nx
180 OBNS_Ny = Ny
181 OBEW_Nx = Nx
182 OBEW_Ny = Ny
183 #endif
184
185 C-- Default flags and values for OBCS
186 insideOBmaskFile = ' '
187 DO I=1,OBNS_Nx
188 OB_Jnorth(I)=0
189 OB_Jsouth(I)=0
190 ENDDO
191 DO J=1,OBEW_Ny
192 OB_Ieast(J)=0
193 OB_Iwest(J)=0
194 ENDDO
195 useOrlanskiNorth =.FALSE.
196 useOrlanskiSouth =.FALSE.
197 useOrlanskiEast =.FALSE.
198 useOrlanskiWest =.FALSE.
199 useStevensNorth =.FALSE.
200 useStevensSouth =.FALSE.
201 useStevensEast =.FALSE.
202 useStevensWest =.FALSE.
203 useStevensPhaseVel =.TRUE.
204 useStevensAdvection=.TRUE.
205 useOBCSsponge =.FALSE.
206 useOBCSbalance =.FALSE.
207 OBCS_balanceFacN = 1. _d 0
208 OBCS_balanceFacS = 1. _d 0
209 OBCS_balanceFacE = 1. _d 0
210 OBCS_balanceFacW = 1. _d 0
211 useOBCSprescribe =.FALSE.
212 OBCSfixTopo =.FALSE.
213 OBCS_uvApplyFac = 1. _d 0
214 OBCS_monitorFreq = monitorFreq
215 OBCS_monSelect = 0
216 OBCSprintDiags = debugLevel.GE.debLevC
217
218 OBNuFile = ' '
219 OBNvFile = ' '
220 OBNtFile = ' '
221 OBNsFile = ' '
222 OBNaFile = ' '
223 OBNslFile = ' '
224 OBNsnFile = ' '
225 OBNuiceFile = ' '
226 OBNviceFile = ' '
227 OBNhFile = ' '
228 OBSuFile = ' '
229 OBSvFile = ' '
230 OBStFile = ' '
231 OBSsFile = ' '
232 OBSaFile = ' '
233 OBShFile = ' '
234 OBSslFile = ' '
235 OBSsnFile = ' '
236 OBSuiceFile = ' '
237 OBSviceFile = ' '
238 OBEuFile = ' '
239 OBEvFile = ' '
240 OBEtFile = ' '
241 OBEsFile = ' '
242 OBEaFile = ' '
243 OBEhFile = ' '
244 OBEslFile = ' '
245 OBEsnFile = ' '
246 OBEuiceFile = ' '
247 OBEviceFile = ' '
248 OBWuFile = ' '
249 OBWvFile = ' '
250 OBWtFile = ' '
251 OBWsFile = ' '
252 OBWaFile = ' '
253 OBWhFile = ' '
254 OBWslFile = ' '
255 OBWsnFile = ' '
256 OBWuiceFile = ' '
257 OBWviceFile = ' '
258 OBNetaFile = ' '
259 OBSetaFile = ' '
260 OBEetaFile = ' '
261 OBWetaFile = ' '
262 OBNwFile = ' '
263 OBSwFile = ' '
264 OBEwFile = ' '
265 OBWwFile = ' '
266 #ifdef ALLOW_PTRACERS
267 DO iTracer = 1, PTRACERS_num
268 OBNptrFile(iTracer) = ' '
269 OBSptrFile(iTracer) = ' '
270 OBEptrFile(iTracer) = ' '
271 OBWptrFile(iTracer) = ' '
272 ENDDO
273 #endif
274 C- retired parameters
275 nRetired = 0
276 useOBCSYearlyFields = .FALSE.
277
278 C Open and read the data.obcs file
279 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: opening data.obcs'
280 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
281 & SQUEEZE_RIGHT , myThid )
282 CALL OPEN_COPY_DATA_FILE(
283 I 'data.obcs', 'OBCS_READPARMS',
284 O iUnit,
285 I myThid )
286
287 C-- Read parameters from open data file
288 READ(UNIT=iUnit,NML=OBCS_PARM01)
289
290 C- retired parameter
291 IF ( useOBCSYearlyFields ) THEN
292 nRetired = nRetired + 1
293 WRITE(msgBuf,'(A,A)')
294 & 'OBCS_READPARMS: "useOBCSYearlyFields"',
295 & ' no longer allowed in file "data.obcs"'
296 CALL PRINT_ERROR( msgBuf, myThid )
297 WRITE(msgBuf,'(A,A)') 'OBCS_READPARMS: ',
298 & ' was moved to "data.exf", namelist: "EXF_NML_OBCS"'
299 CALL PRINT_ERROR( msgBuf, myThid )
300 ENDIF
301
302 #ifdef ALLOW_ORLANSKI
303 C Default Orlanski radiation parameters
304 CMAX = 0.45 _d 0 /* maximum allowable phase speed-CFL for AB-II */
305 cvelTimeScale = 2000.0 _d 0 /* Averaging period for phase speed in sec. */
306 CFIX = 0.8 _d 0 /* Fixed boundary phase speed in m/s */
307 useFixedCEast=.FALSE.
308 useFixedCWest=.FALSE.
309 IF (useOrlanskiNorth.OR.
310 & useOrlanskiSouth.OR.
311 & useOrlanskiEast.OR.
312 & useOrlanskiWest)
313 & READ(UNIT=iUnit,NML=OBCS_PARM02)
314 #endif
315
316 #ifdef ALLOW_OBCS_SPONGE
317 C Default sponge layer parameters:
318 C sponge layer is turned off by default
319 spongeThickness = 0
320 Urelaxobcsinner = 0. _d 0
321 Urelaxobcsbound = 0. _d 0
322 Vrelaxobcsinner = 0. _d 0
323 Vrelaxobcsbound = 0. _d 0
324 CML this was the previous default in units of days
325 CML spongeThickness = 2
326 CML Urelaxobcsinner = 5. _d 0
327 CML Urelaxobcsbound = 1. _d 0
328 CML Vrelaxobcsinner = 5. _d 0
329 CML Vrelaxobcsbound = 1. _d 0
330 IF (useOBCSsponge)
331 & READ(UNIT=iUnit,NML=OBCS_PARM03)
332 #endif
333 #ifdef ALLOW_OBCS_STEVENS
334 TrelaxStevens = 0. _d 0
335 SrelaxStevens = 0. _d 0
336 IF ( useStevensNorth .OR. useStevensSouth
337 & .OR. useStevensEast .OR. useStevensWest )
338 & READ(UNIT=iUnit,NML=OBCS_PARM04)
339 #endif
340
341 WRITE(msgBuf,'(A)') ' OBCS_READPARMS: finished reading data.obcs'
342 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
343 & SQUEEZE_RIGHT , myThid )
344
345 C-- Close the open data file
346 CLOSE(iUnit)
347
348 C- retired parameter
349 IF ( nRetired .GT. 0 ) THEN
350 WRITE(msgBuf,'(A)')
351 & 'OBCS_READPARMS: reading parameter file "data.obcs"'
352 CALL PRINT_ERROR( msgBuf, myThid )
353 WRITE(msgBuf,'(A)')
354 & 'some out of date parameters were found in namelist'
355 CALL PRINT_ERROR( msgBuf, myThid )
356 STOP 'ABNORMAL END: S/R OBCS_READPARMS'
357 ENDIF
358
359 C- Account for periodicity if negative indices were supplied
360 DO J=1,OBEW_Ny
361 IF (OB_Ieast(J).LT.0) OB_Ieast(J)=OB_Ieast(J)+OBEW_Nx+1
362 ENDDO
363 DO I=1,OBNS_Nx
364 IF (OB_Jnorth(I).LT.0) OB_Jnorth(I)=OB_Jnorth(I)+OBNS_Ny+1
365 ENDDO
366 IF ( debugLevel.GE.debLevA ) THEN
367 c write(*,*) 'OB Jn =',OB_Jnorth
368 c write(*,*) 'OB Js =',OB_Jsouth
369 c write(*,*) 'OB Ie =',OB_Ieast
370 c write(*,*) 'OB Iw =',OB_Iwest
371 WRITE(msgBuf,'(A)') ' Northern OB global indices : OB_Jnorth ='
372 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
373 & SQUEEZE_RIGHT, myThid )
374 CALL PRINT_LIST_I( OB_Jnorth, 1, OBNS_Nx, INDEX_I,
375 & .FALSE., .TRUE., standardMessageUnit )
376 WRITE(msgBuf,'(A)') ' Southern OB global indices : OB_Jsouth ='
377 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
378 & SQUEEZE_RIGHT, myThid )
379 CALL PRINT_LIST_I( OB_Jsouth, 1, OBNS_Nx, INDEX_I,
380 & .FALSE., .TRUE., standardMessageUnit )
381 WRITE(msgBuf,'(A)') ' Eastern OB global indices : OB_Ieast ='
382 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
383 & SQUEEZE_RIGHT, myThid )
384 CALL PRINT_LIST_I( OB_Ieast, 1, OBEW_Ny, INDEX_J,
385 & .FALSE., .TRUE., standardMessageUnit )
386 WRITE(msgBuf,'(A)') ' Western OB global indices : OB_Iwest ='
387 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
388 & SQUEEZE_RIGHT, myThid )
389 CALL PRINT_LIST_I( OB_Iwest, 1, OBEW_Ny, INDEX_J,
390 & .FALSE., .TRUE., standardMessageUnit )
391 WRITE(msgBuf,'(A)') ' '
392 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
393 & SQUEEZE_RIGHT, myThid )
394 ENDIF
395
396 _END_MASTER(myThid)
397 C-- Everyone else must wait for the parameters to be loaded
398 _BARRIER
399
400 C-- Calculate the tiled index arrays OB_Jn/Js/Ie/Iw here from the
401 C global arrays OB_Jnorth/Jsouth/Ieast/Iwest.
402 C Note: This part of the code has been moved from obcs_init_fixed to
403 C routine routine because the OB_Jn/Js/Ie/Iw index arrays are
404 C required by ini_depth which is called before obcs_init_fixed
405 DO bj = myByLo(myThid), myByHi(myThid)
406 DO bi = myBxLo(myThid), myBxHi(myThid)
407
408 DO I=1-Olx,sNx+Olx
409 OB_Jn(I,bi,bj)=0
410 OB_Js(I,bi,bj)=0
411 ENDDO
412
413 DO J=1-Oly,sNy+Oly
414 OB_Ie(J,bi,bj)=0
415 OB_Iw(J,bi,bj)=0
416 ENDDO
417
418 #ifdef ALLOW_EXCH2
419 C We apply OBCS only inside tile and exchange overlaps later
420 tN = W2_myTileList(bi,bj)
421 C 1. N/S boundaries
422 DO J=1,sNy
423 C convert from local y index J to global y index jG
424 c for N/S boundaries, we use faces stacked in x direction
425 jG = exch2_tyXStackLo(tN)+J-1
426 C loop over local x index I
427 DO I=1,sNx
428 iG = exch2_txXStackLo(tN)+I-1
429 IF (jG.EQ.OB_Jnorth(iG)) OB_Jn(I,bi,bj)=J
430 IF (jG.EQ.OB_Jsouth(iG)) OB_Js(I,bi,bj)=J
431 ENDDO
432 ENDDO
433 C 2. E/W boundaries
434 DO J=1,sNy
435 C convert from local y index J to global y index jG
436 c for E/W boundaries, we use faces stacked in y direction
437 jG = exch2_tyYStackLo(tN)+J-1
438 C loop over local x index I
439 DO I=1,sNx
440 iG = exch2_txYStackLo(tN)+I-1
441 IF (iG.EQ.OB_Ieast(jG)) OB_Ie(J,bi,bj)=I
442 IF (iG.EQ.OB_Iwest(jG)) OB_Iw(J,bi,bj)=I
443 ENDDO
444 ENDDO
445
446 #else /* ALLOW_EXCH2 */
447
448 DO J=1-Oly,sNy+Oly
449 C convert from local y index J to global y index jG
450 jG = myYGlobalLo-1+(bj-1)*sNy+J
451 C use periodicity to deal with out of range points caused by the overlaps.
452 C they will be excluded by the mask in any case, but this saves array
453 C out-of-bounds errors here.
454 jGm = 1+mod( jG-1+Ny , Ny )
455 C loop over local x index I
456 DO I=1,sNx
457 iG = myXGlobalLo-1+(bi-1)*sNx+I
458 iGm = 1+mod( iG-1+Nx , Nx )
459 C OB_Ieast(jGm) allows for the eastern boundary to be at variable x locations
460 IF (iG.EQ.OB_Ieast(jGm)) OB_Ie(J,bi,bj)=I
461 IF (iG.EQ.OB_Iwest(jGm)) OB_Iw(J,bi,bj)=I
462 ENDDO
463 ENDDO
464 DO J=1,sNy
465 jG = myYGlobalLo-1+(bj-1)*sNy+J
466 jGm = 1+mod( jG-1+Ny , Ny )
467 DO I=1-Olx,sNx+Olx
468 iG = myXGlobalLo-1+(bi-1)*sNx+I
469 iGm = 1+mod( iG-1+Nx , Nx )
470 C OB_Jnorth(iGm) allows for the northern boundary to be at variable y locations
471 IF (jG.EQ.OB_Jnorth(iGm)) OB_Jn(I,bi,bj)=J
472 IF (jG.EQ.OB_Jsouth(iGm)) OB_Js(I,bi,bj)=J
473 ENDDO
474 ENDDO
475 #endif /* ALLOW_EXCH2 */
476
477 C bi,bj-loops
478 ENDDO
479 ENDDO
480
481 #ifdef ALLOW_EXCH2
482 C exchange with neighbors
483 DO bj = myByLo(myThid), myByHi(myThid)
484 DO bi = myBxLo(myThid), myBxHi(myThid)
485 DO J=1,sNy
486 buf(sNx,J,bi,bj) = OB_Ie(J,bi,bj)
487 buf( 1,J,bi,bj) = OB_Iw(J,bi,bj)
488 ENDDO
489 ENDDO
490 ENDDO
491 CALL EXCH_3D_RS( buf, 1, myThid )
492 DO bj = myByLo(myThid), myByHi(myThid)
493 DO bi = myBxLo(myThid), myBxHi(myThid)
494 DO J=1-Oly,sNy+Oly
495 OB_Ie(J,bi,bj) = buf(sNx,J,bi,bj)
496 OB_Iw(J,bi,bj) = buf( 1,J,bi,bj)
497 ENDDO
498 ENDDO
499 ENDDO
500
501 DO bj = myByLo(myThid), myByHi(myThid)
502 DO bi = myBxLo(myThid), myBxHi(myThid)
503 DO I=1,sNx
504 buf(I,sNy,bi,bj) = OB_Jn(I,bi,bj)
505 buf(I, 1,bi,bj) = OB_Js(I,bi,bj)
506 ENDDO
507 ENDDO
508 ENDDO
509 CALL EXCH_3D_RS( buf, 1, myThid )
510 DO bj = myByLo(myThid), myByHi(myThid)
511 DO bi = myBxLo(myThid), myBxHi(myThid)
512 DO I=1-Olx,sNx+Olx
513 OB_Jn(I,bi,bj) = buf(I,sNy,bi,bj)
514 OB_Js(I,bi,bj) = buf(I, 1,bi,bj)
515 ENDDO
516 ENDDO
517 ENDDO
518 #endif /* ALLOW_EXCH2 */
519
520 #endif /* ALLOW_OBCS */
521 RETURN
522 END

  ViewVC Help
Powered by ViewVC 1.1.22