/[MITgcm]/MITgcm/pkg/generic_advdiff/gad_som_advect.F
ViewVC logotype

Contents of /MITgcm/pkg/generic_advdiff/gad_som_advect.F

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


Revision 1.1 - (show annotations) (download)
Tue Jan 16 04:38:34 2007 UTC (17 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58w_post, checkpoint58x_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58y_post, checkpoint58v_post
2nd-Order Moment Advection Scheme (Prather, 1986): first check-in
 - enable by setting #define GAD_ALLOW_SOM_ADVECT (in GAD_OPTIONS.h)
 - used without limiter (AdvScheme=80) or with Prather limiter (AdvScheme=81)
 - still needs work (not working with some options ; efficiency to improve)
   and serious testing.

1 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_advection.F,v 1.43 2006/12/05 05:26:46 jmc Exp $
2 C $Name: $
3
4 #include "GAD_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP
8 C !ROUTINE: GAD_SOM_ADVECT
9
10 C !INTERFACE: ==========================================================
11 SUBROUTINE GAD_SOM_ADVECT(
12 I implicitAdvection, advectionScheme, vertAdvecScheme,
13 I tracerIdentity,
14 I uVel, vVel, wVel, tracer,
15 U smTr,
16 O gTracer,
17 I bi,bj, myTime,myIter,myThid)
18
19 C !DESCRIPTION:
20 C Calculates the tendency of a tracer due to advection.
21 C It uses the 2nd-Order moment advection scheme with multi-dimensional method
22 C see Prather, 1986, JGR, v.91, D-6, pp.6671-6681.
23 C
24 C The tendency (output) is over-written by this routine.
25
26 C !USES: ===============================================================
27 IMPLICIT NONE
28 #include "SIZE.h"
29 #include "EEPARAMS.h"
30 #include "PARAMS.h"
31 #include "GRID.h"
32 #include "GAD.h"
33
34 C !INPUT PARAMETERS: ===================================================
35 C implicitAdvection :: implicit vertical advection (later on)
36 C advectionScheme :: advection scheme to use (Horizontal plane)
37 C vertAdvecScheme :: advection scheme to use (vertical direction)
38 C tracerIdentity :: tracer identifier (required only for OBCS)
39 C uVel :: velocity, zonal component
40 C vVel :: velocity, meridional component
41 C wVel :: velocity, vertical component
42 C tracer :: tracer field
43 C bi,bj :: tile indices
44 C myTime :: current time
45 C myIter :: iteration number
46 C myThid :: thread number
47 LOGICAL implicitAdvection
48 INTEGER advectionScheme, vertAdvecScheme
49 INTEGER tracerIdentity
50 _RL uVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
51 _RL vVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
52 _RL wVel (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
53 _RL tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
54 INTEGER bi,bj
55 _RL myTime
56 INTEGER myIter
57 INTEGER myThid
58
59 C !OUTPUT PARAMETERS: ==================================================
60 C smTr :: tracer 1rst & 2nd Order moments
61 C gTracer :: tendency array
62 _RL smTr (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy,nSOM)
63 _RL gTracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
64
65 #ifdef GAD_ALLOW_SOM_ADVECT
66 C !LOCAL VARIABLES: ====================================================
67 C maskLocW :: 2-D array for mask at West points
68 C maskLocS :: 2-D array for mask at South points
69 C maskUp :: 2-D array mask for W points
70 C iMin,iMax, :: loop range for called routines
71 C jMin,jMax :: loop range for called routines
72 C [iMin,iMax]Upd :: loop range to update tracer field
73 C [jMin,jMax]Upd :: loop range to update tracer field
74 C i,j,k :: loop indices
75 C kUp :: index into 2 1/2D array, toggles between 1 and 2
76 C kDown :: index into 2 1/2D array, toggles between 2 and 1
77 C kp1 :: =k+1 for k<Nr, =Nr for k=Nr
78 C xA,yA :: areas of X and Y face of tracer cells
79 C uFld,vFld :: 2-D local copy of horizontal velocity, U,V components
80 C wFld :: 2-D local copy of vertical velocity
81 C uTrans,vTrans :: 2-D arrays of volume transports at U,V points
82 C rTrans :: 2-D arrays of volume transports at W points
83 C rTransKp1 :: vertical volume transport at interface k+1
84 C af :: 2-D array for horizontal advective flux
85 C afx :: 2-D array for horizontal advective flux, x direction
86 C afy :: 2-D array for horizontal advective flux, y direction
87 C afr :: 2-D array for vertical advective flux
88 C fVerT :: 2 1/2D arrays for vertical advective flux
89 C localTij :: 2-D array, temporary local copy of tracer fld
90 C localTijk :: 3-D array, temporary local copy of tracer fld
91 C kp1Msk :: flag (0,1) for over-riding mask for W levels
92 C calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
93 C calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
94 C interiorOnly :: only update the interior of myTile, but not the edges
95 C overlapOnly :: only update the edges of myTile, but not the interior
96 C npass :: number of passes in multi-dimensional method
97 C ipass :: number of the current pass being made
98 C myTile :: variables used to determine which cube face
99 C nCFace :: owns a tile for cube grid runs using
100 C :: multi-dim advection.
101 C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
102 C msgBuf :: Informational/error meesage buffer
103 c _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
104 c _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
105 _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
106 INTEGER iMin,iMax,jMin,jMax
107 c INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd
108 INTEGER i,j,k,km1,kUp,kDown
109 _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
110 _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
111 _RL uFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
112 _RL vFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
113 _RL wFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
114 _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
115 _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
116 _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
117 c _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
118 c _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
119 _RL afx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120 _RL afy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121 _RL afr (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122 ccc _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
123 c _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
124 _RL smVol (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
125 _RL smTr0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
126 _RL alp (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
127 _RL aln (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
128 _RL fp_v (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
129 _RL fn_v (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
130 _RL fp_o (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
131 _RL fn_o (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
132 _RL fp_x (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
133 _RL fn_x (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
134 _RL fp_y (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
135 _RL fn_y (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
136 _RL fp_z (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
137 _RL fn_z (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
138 _RL fp_xx (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
139 _RL fn_xx (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
140 _RL fp_yy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
141 _RL fn_yy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
142 _RL fp_zz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
143 _RL fn_zz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
144 _RL fp_xy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
145 _RL fn_xy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
146 _RL fp_xz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
147 _RL fn_xz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
148 _RL fp_yz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
149 _RL fn_yz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
150 _RL localTr
151 c _RL kp1Msk
152 LOGICAL calc_fluxes_X, calc_fluxes_Y
153 c LOGICAL interiorOnly, overlapOnly
154 INTEGER limiter
155 INTEGER npass, ipass
156 c INTEGER nCFace
157 c LOGICAL N_edge, S_edge, E_edge, W_edge
158 CHARACTER*(MAX_LEN_MBUF) msgBuf
159 #ifdef ALLOW_DIAGNOSTICS
160 CHARACTER*8 diagName
161 CHARACTER*4 GAD_DIAG_SUFX, diagSufx
162 EXTERNAL GAD_DIAG_SUFX
163 #endif
164 CEOP
165
166 #ifdef ALLOW_DIAGNOSTICS
167 C-- Set diagnostic suffix for the current tracer
168 IF ( useDiagnostics ) THEN
169 diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
170 ENDIF
171 #endif
172
173 C-- Set up work arrays with valid (i.e. not NaN) values
174 C These inital values do not alter the numerical results. They
175 C just ensure that all memory references are to valid floating
176 C point numbers. This prevents spurious hardware signals due to
177 C uninitialised but inert locations.
178 c DO j=1-OLy,sNy+OLy
179 c DO i=1-OLx,sNx+OLx
180 C- xA,yA,uFld,vFld,uTrans,vTrans are set over the full domain
181 C in CALC_COMMON_FACTORS: no need for extra initialisation
182 c xA(i,j) = 0. _d 0
183 c yA(i,j) = 0. _d 0
184 c uTrans(i,j) = 0. _d 0
185 c vTrans(i,j) = 0. _d 0
186 C- rTrans is set over the full domain: no need for extra initialisation
187 c rTrans(i,j) = 0. _d 0
188 c rTransKp1(i,j)= 0. _d 0
189 c ENDDO
190 c ENDDO
191
192 C-- Set tile-specific parameters for horizontal fluxes
193 IF (useCubedSphereExchange) THEN
194 WRITE(msgBuf,'(2A)') 'S/R GAD_SOM_ADVECT: ',
195 & 'not coded for CubedSphere (useCubedSphereExchange=T)'
196 CALL PRINT_ERROR( msgBuf, myThid )
197 STOP 'ABNORMAL END: S/R GAD_SOM_ADVECT'
198 ENDIF
199 IF ( implicitAdvection ) THEN
200 WRITE(msgBuf,'(2A)') 'S/R GAD_SOM_ADVECT: ',
201 & 'not coded for implicit-vertical Advection'
202 CALL PRINT_ERROR( msgBuf, myThid )
203 STOP 'ABNORMAL END: S/R GAD_SOM_ADVECT'
204 ENDIF
205 IF ( vertAdvecScheme .NE. advectionScheme ) THEN
206 WRITE(msgBuf,'(2A)') 'S/R GAD_SOM_ADVECT: ',
207 & 'not coded for different vertAdvecScheme'
208 CALL PRINT_ERROR( msgBuf, myThid )
209 STOP 'ABNORMAL END: S/R GAD_SOM_ADVECT'
210 ENDIF
211
212 limiter = MOD(advectionScheme, 10)
213 npass= 2
214 iMin = 1-OLx
215 iMax = sNx+OLx
216 jMin = 1-OLy
217 jMax = sNy+OLy
218
219 C-- Start of k loop for horizontal fluxes
220 DO k=1,Nr
221
222 C-- Get temporary terms used by tendency routines
223 CALL CALC_COMMON_FACTORS (
224 I uVel, vVel,
225 O uFld, vFld, uTrans, vTrans, xA, yA,
226 I k,bi,bj, myThid )
227
228 #ifdef ALLOW_GMREDI
229 C-- Residual transp = Bolus transp + Eulerian transp
230 IF (useGMRedi)
231 & CALL GMREDI_CALC_UVFLOW(
232 U uFld, vFld, uTrans, vTrans,
233 I k, bi, bj, myThid )
234 #endif /* ALLOW_GMREDI */
235
236 C-- grid-box volume and tracer content (zero order moment)
237 DO j=1-OLy,sNy+OLy
238 DO i=1-OLx,sNx+OLx
239 smVol(i,j,k) = rA(i,j,bi,bj)*deepFac2C(k)
240 & *drF(k)*hFacC(i,j,k,bi,bj)
241 & *rhoFacC(k)
242 smTr0(i,j,k) = tracer(i,j,k,bi,bj)*smVol(i,j,k)
243 C- fill empty grid-box:
244 smVol(i,j,k) = smVol(i,j,k)
245 & + (1. _d 0 - maskC(i,j,k,bi,bj))
246 ENDDO
247 ENDDO
248
249 c IF (useCubedSphereExchange) THEN
250 c CALL FILL_CS_CORNER_UV_RS(
251 c & .FALSE., maskLocW,maskLocS, bi,bj, myThid )
252 c ENDIF
253
254 C-- Multiple passes for different directions on different tiles
255 C-- For cube need one pass for each of red, green and blue axes.
256 DO ipass=1,npass
257
258 C- not CubedSphere
259 calc_fluxes_X = MOD(ipass,2).EQ.1
260 calc_fluxes_Y = .NOT.calc_fluxes_X
261
262 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
263 C-- X direction
264 IF (calc_fluxes_X) THEN
265
266 C- Advective flux in X
267 DO j=1-OLy,sNy+OLy
268 DO i=1-OLx,sNx+OLx
269 afx(i,j) = 0.
270 ENDDO
271 ENDDO
272
273 IF ( advectionScheme.EQ.ENUM_SOM_PRATHER
274 & .OR. advectionScheme.EQ.ENUM_SOM_LIMITER ) THEN
275 CALL GAD_SOM_ADV_X(
276 I bi,bj,k, limiter,
277 I dTtracerLev(k), uTrans,
278 U smVol(1-OLx,1-OLy,k),
279 U smTr0(1-OLx,1-OLy,k),
280 U smTr(1-OLx,1-OLy,k,bi,bj,1),
281 U smTr(1-OLx,1-OLy,k,bi,bj,2),
282 U smTr(1-OLx,1-OLy,k,bi,bj,3),
283 U smTr(1-OLx,1-OLy,k,bi,bj,4),
284 U smTr(1-OLx,1-OLy,k,bi,bj,5),
285 U smTr(1-OLx,1-OLy,k,bi,bj,6),
286 U smTr(1-OLx,1-OLy,k,bi,bj,7),
287 U smTr(1-OLx,1-OLy,k,bi,bj,8),
288 U smTr(1-OLx,1-OLy,k,bi,bj,9),
289 O afx, myThid )
290 ELSE
291 STOP 'GAD_SOM_ADVECT: adv. scheme incompatibale with SOM'
292 ENDIF
293
294 C- Update the local tracer field where needed:
295
296 C- keep advective flux (for diagnostics)
297 c DO j=1-OLy,sNy+OLy
298 c DO i=1-OLx,sNx+OLx
299 c afx(i,j) = af(i,j)
300 c ENDDO
301 c ENDDO
302
303 #ifdef ALLOW_OBCS
304 C- Apply open boundary conditions
305 c IF ( useOBCS ) THEN
306 ccc localTij(i,j) = smTr0(i,j)/smVol(i,j)
307 c IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
308 c CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
309 c ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
310 c CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
311 #ifdef ALLOW_PTRACERS
312 c ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
313 c CALL OBCS_APPLY_PTRACER( bi, bj, k,
314 c & tracerIdentity-GAD_TR1+1, localTij, myThid )
315 #endif /* ALLOW_PTRACERS */
316 c ENDIF
317 ccc smTr0(i,j) = localTij(i,j)*smVol(i,j)
318 c ENDIF
319 #endif /* ALLOW_OBCS */
320
321 C-- End of X direction
322 ENDIF
323
324 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
325 C-- Y direction
326 C
327 IF (calc_fluxes_Y) THEN
328
329 C- Do not compute fluxes if
330 C a) needed in overlap only
331 C and b) the overlap of myTile are not cube-face edges
332 c IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
333
334 C- Advective flux in Y
335 DO j=1-OLy,sNy+OLy
336 DO i=1-OLx,sNx+OLx
337 afy(i,j) = 0.
338 ENDDO
339 ENDDO
340
341 IF ( advectionScheme.EQ.ENUM_SOM_PRATHER
342 & .OR. advectionScheme.EQ.ENUM_SOM_LIMITER ) THEN
343 CALL GAD_SOM_ADV_Y(
344 I bi,bj,k, limiter,
345 I dTtracerLev(k), vTrans,
346 U smVol(1-OLx,1-OLy,k),
347 U smTr0(1-OLx,1-OLy,k),
348 U smTr(1-OLx,1-OLy,k,bi,bj,1),
349 U smTr(1-OLx,1-OLy,k,bi,bj,2),
350 U smTr(1-OLx,1-OLy,k,bi,bj,3),
351 U smTr(1-OLx,1-OLy,k,bi,bj,4),
352 U smTr(1-OLx,1-OLy,k,bi,bj,5),
353 U smTr(1-OLx,1-OLy,k,bi,bj,6),
354 U smTr(1-OLx,1-OLy,k,bi,bj,7),
355 U smTr(1-OLx,1-OLy,k,bi,bj,8),
356 U smTr(1-OLx,1-OLy,k,bi,bj,9),
357 O afy, myThid )
358 ELSE
359 STOP 'GAD_SOM_ADVECT: adv. scheme incompatibale with SOM'
360 ENDIF
361
362 C- Advective flux in Y : done
363 c ENDIF
364
365 C- Update the local tracer field where needed:
366
367 C- keep advective flux (for diagnostics)
368 c DO j=1-OLy,sNy+OLy
369 c DO i=1-OLx,sNx+OLx
370 c afy(i,j) = af(i,j)
371 c ENDDO
372 c ENDDO
373
374 #ifdef ALLOW_OBCS
375 C- Apply open boundary conditions
376 c IF (useOBCS) THEN
377 ccc localTij(i,j) = smTr0(i,j)/smVol(i,j)
378 c IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
379 c CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
380 c ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
381 c CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
382 #ifdef ALLOW_PTRACERS
383 c ELSEIF (tracerIdentity.GE.GAD_TR1) THEN
384 c CALL OBCS_APPLY_PTRACER( bi, bj, k,
385 c & tracerIdentity-GAD_TR1+1, localTij, myThid )
386 #endif /* ALLOW_PTRACERS */
387 c ENDIF
388 ccc smTr0(i,j) = localTij(i,j)*smVol(i,j)
389 c ENDIF
390 #endif /* ALLOW_OBCS */
391
392 C end if/else update overlap-Only
393 c ENDIF
394
395 C-- End of Y direction
396 ENDIF
397
398 C-- End of ipass loop
399 ENDDO
400
401 IF ( implicitAdvection ) THEN
402 C- explicit advection is done ; store tendency in gTracer:
403 DO j=1-OLy,sNy+OLy
404 DO i=1-OLx,sNx+OLx
405 localTr = smTr0(i,j,k)/smVol(i,j,k)
406 gTracer(i,j,k,bi,bj) = ( localTr - tracer(i,j,k,bi,bj) )
407 & / dTtracerLev(k)
408 ENDDO
409 ENDDO
410 ELSE
411 C- horizontal advection done; store intermediate result in 3D array:
412 c DO j=1-OLy,sNy+OLy
413 c DO i=1-OLx,sNx+OLx
414 c localTijk(i,j,k)=localTij(i,j)
415 c ENDDO
416 c ENDDO
417 ENDIF
418
419 #ifdef ALLOW_DIAGNOSTICS
420 IF ( useDiagnostics ) THEN
421 diagName = 'ADVx'//diagSufx
422 CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid)
423 diagName = 'ADVy'//diagSufx
424 CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid)
425 ENDIF
426 #endif
427
428 #ifdef ALLOW_DEBUG
429 IF ( debugLevel .GE. debLevB
430 & .AND. tracerIdentity.EQ.GAD_TEMPERATURE
431 & .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
432 & .AND. nPx.EQ.1 .AND. nPy.EQ.1
433 & .AND. useCubedSphereExchange ) THEN
434 CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_SOM_ADVECT',
435 & afx,afy, k, standardMessageUnit,bi,bj,myThid )
436 ENDIF
437 #endif /* ALLOW_DEBUG */
438
439 C-- End of K loop for horizontal fluxes
440 ENDDO
441
442 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
443
444 IF ( .NOT.implicitAdvection ) THEN
445 C-- Apply limiter (if any):
446 CALL GAD_SOM_LIM_R( bi,bj, limiter,
447 U smVol,
448 U smTr0,
449 U smTr(1-OLx,1-OLy,1,bi,bj,1),
450 U smTr(1-OLx,1-OLy,1,bi,bj,2),
451 U smTr(1-OLx,1-OLy,1,bi,bj,3),
452 U smTr(1-OLx,1-OLy,1,bi,bj,4),
453 U smTr(1-OLx,1-OLy,1,bi,bj,5),
454 U smTr(1-OLx,1-OLy,1,bi,bj,6),
455 U smTr(1-OLx,1-OLy,1,bi,bj,7),
456 U smTr(1-OLx,1-OLy,1,bi,bj,8),
457 U smTr(1-OLx,1-OLy,1,bi,bj,9),
458 I myThid )
459
460 C-- Start of k loop for vertical flux
461 DO k=Nr,1,-1
462 C-- kUp Cycles through 1,2 to point to w-layer above
463 C-- kDown Cycles through 2,1 to point to w-layer below
464 kUp = 1+MOD(Nr-k,2)
465 kDown= 1+MOD(Nr-k+1,2)
466 c kp1=min(Nr,k+1)
467 c kp1Msk = 1. _d 0
468 IF (k.EQ.Nr) THEN
469 c kp1Msk = 0. _d 0
470 C-- Set advective fluxes at the very bottom:
471 DO j=1-OLy,sNy+OLy
472 DO i=1-OLx,sNx+OLx
473 alp (i,j,kDown) = 0. _d 0
474 aln (i,j,kDown) = 0. _d 0
475 fp_v (i,j,kDown) = 0. _d 0
476 fn_v (i,j,kDown) = 0. _d 0
477 fp_o (i,j,kDown) = 0. _d 0
478 fn_o (i,j,kDown) = 0. _d 0
479 fp_x (i,j,kDown) = 0. _d 0
480 fn_x (i,j,kDown) = 0. _d 0
481 fp_y (i,j,kDown) = 0. _d 0
482 fn_y (i,j,kDown) = 0. _d 0
483 fp_z (i,j,kDown) = 0. _d 0
484 fn_z (i,j,kDown) = 0. _d 0
485 fp_xx(i,j,kDown) = 0. _d 0
486 fn_xx(i,j,kDown) = 0. _d 0
487 fp_yy(i,j,kDown) = 0. _d 0
488 fn_yy(i,j,kDown) = 0. _d 0
489 fp_zz(i,j,kDown) = 0. _d 0
490 fn_zz(i,j,kDown) = 0. _d 0
491 fp_xy(i,j,kDown) = 0. _d 0
492 fn_xy(i,j,kDown) = 0. _d 0
493 fp_xz(i,j,kDown) = 0. _d 0
494 fn_xz(i,j,kDown) = 0. _d 0
495 fp_yz(i,j,kDown) = 0. _d 0
496 fn_yz(i,j,kDown) = 0. _d 0
497 ENDDO
498 ENDDO
499 ENDIF
500
501 C-- Compute Vertical transport
502 #ifdef ALLOW_AIM
503 C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
504 c IF ( k.EQ.1 .OR.
505 c & (useAIM .AND. tracerIdentity.EQ.GAD_SALINITY .AND. k.EQ.Nr)
506 c & ) THEN
507 #else
508 c IF ( k.EQ.1 ) THEN
509 #endif
510 IF ( (rigidLid.OR.nonlinFreeSurf.GE.1) .AND. k.EQ.1 ) THEN
511 C- Surface interface :
512 DO j=1-OLy,sNy+OLy
513 DO i=1-OLx,sNx+OLx
514 wFld(i,j) = 0.
515 rTrans(i,j) = 0.
516 maskUp(i,j) = 0.
517 ENDDO
518 ENDDO
519
520 ELSEIF ( rigidLid.OR.nonlinFreeSurf.GE.1 ) THEN
521 C- Interior interface :
522 DO j=1-OLy,sNy+OLy
523 DO i=1-OLx,sNx+OLx
524 wFld(i,j) = wVel(i,j,k,bi,bj)
525 rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
526 & *deepFac2F(k)*rhoFacF(k)
527 & *maskC(i,j,k-1,bi,bj)
528 maskUp(i,j) = 1.
529 ENDDO
530 ENDDO
531
532 ELSE
533 C- Linear Free-Surface: do not mask rTrans :
534 km1= MAX(k-1,1)
535 DO j=1-OLy,sNy+OLy
536 DO i=1-OLx,sNx+OLx
537 wFld(i,j) = wVel(i,j,k,bi,bj)
538 rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
539 & *deepFac2F(k)*rhoFacF(k)
540 maskUp(i,j) = maskC(i,j,km1,bi,bj)*maskC(i,j,k,bi,bj)
541 ENDDO
542 ENDDO
543
544 C- end Surface/Interior if bloc
545 ENDIF
546
547 #ifdef ALLOW_GMREDI
548 C-- Residual transp = Bolus transp + Eulerian transp
549 IF (useGMRedi .AND. k.GT.1 )
550 & CALL GMREDI_CALC_WFLOW(
551 U wFld, rTrans,
552 I k, bi, bj, myThid )
553 #endif /* ALLOW_GMREDI */
554
555 C- Compute vertical advective flux in the interior:
556 IF ( vertAdvecScheme.EQ.ENUM_SOM_PRATHER
557 & .OR. vertAdvecScheme.EQ.ENUM_SOM_LIMITER ) THEN
558 CALL GAD_SOM_ADV_R(
559 I bi,bj,k, kUp, kDown,
560 I dTtracerLev(k), rTrans, maskUp,
561 U smVol,
562 U smTr0,
563 U smTr(1-OLx,1-OLy,1,bi,bj,1),
564 U smTr(1-OLx,1-OLy,1,bi,bj,2),
565 U smTr(1-OLx,1-OLy,1,bi,bj,3),
566 U smTr(1-OLx,1-OLy,1,bi,bj,4),
567 U smTr(1-OLx,1-OLy,1,bi,bj,5),
568 U smTr(1-OLx,1-OLy,1,bi,bj,6),
569 U smTr(1-OLx,1-OLy,1,bi,bj,7),
570 U smTr(1-OLx,1-OLy,1,bi,bj,8),
571 U smTr(1-OLx,1-OLy,1,bi,bj,9),
572 U alp, aln, fp_v, fn_v, fp_o, fn_o,
573 U fp_x, fn_x, fp_y, fn_y, fp_z, fn_z,
574 U fp_xx, fn_xx, fp_yy, fn_yy, fp_zz, fn_zz,
575 U fp_xy, fn_xy, fp_xz, fn_xz, fp_yz, fn_yz,
576 O afr, myThid )
577 ELSE
578 STOP 'GAD_SOM_ADVECT: adv.scheme incompatibale with SOM'
579 ENDIF
580
581 C-- Divergence of vertical fluxes
582 DO j=1-OLy,sNy+OLy
583 DO i=1-OLx,sNx+OLx
584 c localTij(i,j) = localTijk(i,j,k)
585 c & -dTtracerLev(k)*recip_rhoFacC(k)
586 c & *_recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
587 c & *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
588 c & *( fVerT(i,j,kDown)-fVerT(i,j,kUp)
589 c & -tracer(i,j,k,bi,bj)*(rTransKp1(i,j)-rTrans(i,j))
590 c & )*rkSign
591 c gTracer(i,j,k,bi,bj)=
592 c & (localTij(i,j)-tracer(i,j,k,bi,bj))/dTtracerLev(k)
593 localTr = smTr0(i,j,k)
594 & *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
595 & *recip_drF(k)*_recip_hFacC(i,j,k,bi,bj)
596 & *recip_rhoFacC(k)
597 c localTr = smTr0(i,j,k)/smVol(i,j,k)
598 gTracer(i,j,k,bi,bj) = ( localTr - tracer(i,j,k,bi,bj) )
599 & / dTtracerLev(k)
600 ENDDO
601 ENDDO
602
603 #ifdef ALLOW_DIAGNOSTICS
604 IF ( useDiagnostics ) THEN
605 diagName = 'ADVr'//diagSufx
606 CALL DIAGNOSTICS_FILL( afr,
607 & diagName, k,1, 2,bi,bj, myThid)
608 ENDIF
609 #endif
610
611 C-- End of K loop for vertical flux
612 ENDDO
613 C-- end of if not.implicitAdvection block
614 ENDIF
615
616 #endif /* GAD_ALLOW_SOM_ADVECT */
617
618 RETURN
619 END

  ViewVC Help
Powered by ViewVC 1.1.22