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

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

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


Revision 1.12 - (hide annotations) (download)
Tue Nov 19 16:59:33 2013 UTC (10 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint65, checkpoint65b, checkpoint65a
Changes since 1.11: +28 -40 lines
- compute locally (in thermodynamics.F) 3-D velocity field that is used to
  advect tracers; pass it as argument to GAD_ADVECTION, GAD_SOM_ADVECT,
  PTRACERS_ADVECTION, TEMP_INTEGRATE, SALT_INTEGRATE, PTRACERS_INTEGRATE,
  GAD_IMPLICIT_R and PTRACERS_IMPLICIT

1 jmc 1.12 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_som_advect.F,v 1.11 2013/03/02 00:32:30 jmc Exp $
2 jmc 1.1 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 jahn 1.7 I tracerIdentity, deltaTLev,
14 jmc 1.12 I uFld, vFld, wFld, tracer,
15 jmc 1.1 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 jmc 1.2 #ifdef ALLOW_EXCH2
34 jmc 1.6 #include "W2_EXCH2_SIZE.h"
35 jmc 1.2 #include "W2_EXCH2_TOPOLOGY.h"
36     #endif /* ALLOW_EXCH2 */
37 jmc 1.1
38     C !INPUT PARAMETERS: ===================================================
39     C implicitAdvection :: implicit vertical advection (later on)
40     C advectionScheme :: advection scheme to use (Horizontal plane)
41     C vertAdvecScheme :: advection scheme to use (vertical direction)
42     C tracerIdentity :: tracer identifier (required only for OBCS)
43 jmc 1.12 C uFld :: Advection velocity field, zonal component
44     C vFld :: Advection velocity field, meridional component
45     C wFld :: Advection velocity field, vertical component
46 jmc 1.1 C tracer :: tracer field
47     C bi,bj :: tile indices
48     C myTime :: current time
49     C myIter :: iteration number
50     C myThid :: thread number
51     LOGICAL implicitAdvection
52     INTEGER advectionScheme, vertAdvecScheme
53     INTEGER tracerIdentity
54 jahn 1.7 _RL deltaTLev(Nr)
55 jmc 1.12 _RL uFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
56     _RL vFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
57     _RL wFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
58 jmc 1.1 _RL tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
59     INTEGER bi,bj
60     _RL myTime
61     INTEGER myIter
62     INTEGER myThid
63    
64     C !OUTPUT PARAMETERS: ==================================================
65     C smTr :: tracer 1rst & 2nd Order moments
66     C gTracer :: tendency array
67     _RL smTr (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy,nSOM)
68     _RL gTracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
69    
70     C !LOCAL VARIABLES: ====================================================
71     C maskUp :: 2-D array mask for W points
72     C i,j,k :: loop indices
73     C kUp :: index into 2 1/2D array, toggles between 1 and 2
74     C kDown :: index into 2 1/2D array, toggles between 2 and 1
75     C xA,yA :: areas of X and Y face of tracer cells
76     C uTrans,vTrans :: 2-D arrays of volume transports at U,V points
77     C rTrans :: 2-D arrays of volume transports at W points
78     C afx :: 2-D array for horizontal advective flux, x direction
79     C afy :: 2-D array for horizontal advective flux, y direction
80     C afr :: 2-D array for vertical advective flux
81     C fVerT :: 2 1/2D arrays for vertical advective flux
82     C calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
83     C calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
84     C interiorOnly :: only update the interior of myTile, but not the edges
85     C overlapOnly :: only update the edges of myTile, but not the interior
86     C npass :: number of passes in multi-dimensional method
87     C ipass :: number of the current pass being made
88     C myTile :: variables used to determine which cube face
89     C nCFace :: owns a tile for cube grid runs using
90     C :: multi-dim advection.
91     C [N,S,E,W]_edge :: true if N,S,E,W edge of myTile is an Edge of the cube
92 jmc 1.11 C msgBuf :: Informational/error message buffer
93 jmc 1.1 _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
94     INTEGER i,j,k,km1,kUp,kDown
95     _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96     _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
97     _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98     _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
99     _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
100     _RL afx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
101     _RL afy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
102     _RL afr (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
103     _RL smVol (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
104     _RL smTr0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
105     _RL alp (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
106     _RL aln (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
107     _RL fp_v (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
108     _RL fn_v (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
109     _RL fp_o (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
110     _RL fn_o (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
111     _RL fp_x (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
112     _RL fn_x (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
113     _RL fp_y (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
114     _RL fn_y (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
115     _RL fp_z (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
116     _RL fn_z (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
117     _RL fp_xx (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
118     _RL fn_xx (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
119     _RL fp_yy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
120     _RL fn_yy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
121     _RL fp_zz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
122     _RL fn_zz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
123     _RL fp_xy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
124     _RL fn_xy (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
125     _RL fp_xz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
126     _RL fn_xz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
127     _RL fp_yz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
128     _RL fn_yz (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
129 jmc 1.2 _RL smCorners(OLx,OLy,4,-1:nSOM)
130 jmc 1.5 c _RL localTr
131 jmc 1.1 LOGICAL calc_fluxes_X, calc_fluxes_Y
132 jmc 1.2 LOGICAL interiorOnly, overlapOnly
133 jmc 1.1 INTEGER limiter
134     INTEGER npass, ipass
135 jmc 1.2 INTEGER nCFace, n
136     LOGICAL N_edge, S_edge, E_edge, W_edge
137 jmc 1.11 LOGICAL noFlowAcrossSurf
138 jmc 1.1 CHARACTER*(MAX_LEN_MBUF) msgBuf
139 jmc 1.2 #ifdef ALLOW_EXCH2
140     INTEGER myTile
141     #endif
142 jmc 1.1 #ifdef ALLOW_DIAGNOSTICS
143     CHARACTER*8 diagName
144 jmc 1.2 CHARACTER*4 diagSufx
145     LOGICAL doDiagAdvX, doDiagAdvY, doDiagAdvR
146     C- Functions:
147     CHARACTER*4 GAD_DIAG_SUFX
148 jmc 1.1 EXTERNAL GAD_DIAG_SUFX
149 jmc 1.2 LOGICAL DIAGNOSTICS_IS_ON
150     EXTERNAL DIAGNOSTICS_IS_ON
151 jmc 1.1 #endif
152     CEOP
153    
154     #ifdef ALLOW_DIAGNOSTICS
155 jmc 1.2 C-- Set diagnostics flags and suffix for the current tracer
156     doDiagAdvX = .FALSE.
157     doDiagAdvY = .FALSE.
158     doDiagAdvR = .FALSE.
159 jmc 1.1 IF ( useDiagnostics ) THEN
160     diagSufx = GAD_DIAG_SUFX( tracerIdentity, myThid )
161 jmc 1.2 diagName = 'ADVx'//diagSufx
162     doDiagAdvX = DIAGNOSTICS_IS_ON( diagName, myThid )
163     diagName = 'ADVy'//diagSufx
164     doDiagAdvY = DIAGNOSTICS_IS_ON( diagName, myThid )
165     diagName = 'ADVr'//diagSufx
166     doDiagAdvR = DIAGNOSTICS_IS_ON( diagName, myThid )
167 jmc 1.1 ENDIF
168     #endif
169    
170     C-- Set up work arrays with valid (i.e. not NaN) values
171     C These inital values do not alter the numerical results. They
172     C just ensure that all memory references are to valid floating
173     C point numbers. This prevents spurious hardware signals due to
174     C uninitialised but inert locations.
175 jmc 1.2 DO j=1-OLy,sNy+OLy
176     DO i=1-OLx,sNx+OLx
177     afx(i,j) = 0.
178     afy(i,j) = 0.
179 jmc 1.12 C- xA,yA,uTrans,vTrans are set over the full domain
180     C => no need for extra initialisation
181 jmc 1.1 c xA(i,j) = 0. _d 0
182     c yA(i,j) = 0. _d 0
183     c uTrans(i,j) = 0. _d 0
184     c vTrans(i,j) = 0. _d 0
185     C- rTrans is set over the full domain: no need for extra initialisation
186     c rTrans(i,j) = 0. _d 0
187 jmc 1.2 ENDDO
188     ENDDO
189     DO n=-1,nSOM
190     DO k=1,4
191     DO j=1,OLy
192     DO i=1,OLx
193     smCorners(i,j,k,n) = 0.
194     ENDDO
195     ENDDO
196     ENDDO
197     ENDDO
198 jmc 1.1
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 jmc 1.2 C-- Set tile-specific parameters for horizontal fluxes
213     IF (useCubedSphereExchange) THEN
214     npass = 3
215     #ifdef ALLOW_EXCH2
216 jmc 1.8 myTile = W2_myTileList(bi,bj)
217 jmc 1.2 nCFace = exch2_myFace(myTile)
218     N_edge = exch2_isNedge(myTile).EQ.1
219     S_edge = exch2_isSedge(myTile).EQ.1
220     E_edge = exch2_isEedge(myTile).EQ.1
221     W_edge = exch2_isWedge(myTile).EQ.1
222     #else
223     nCFace = bi
224     N_edge = .TRUE.
225     S_edge = .TRUE.
226     E_edge = .TRUE.
227     W_edge = .TRUE.
228     #endif
229     ELSE
230     npass = 2
231     nCFace = 0
232     N_edge = .FALSE.
233     S_edge = .FALSE.
234     E_edge = .FALSE.
235     W_edge = .FALSE.
236     ENDIF
237    
238 jmc 1.1 limiter = MOD(advectionScheme, 10)
239    
240     C-- Start of k loop for horizontal fluxes
241     DO k=1,Nr
242    
243     C-- Get temporary terms used by tendency routines
244 jmc 1.12 DO j=1-OLy,sNy+OLy
245     DO i=1-OLx,sNx+OLx
246     xA(i,j) = _dyG(i,j,bi,bj)*deepFacC(k)
247     & *drF(k)*_hFacW(i,j,k,bi,bj)
248     yA(i,j) = _dxG(i,j,bi,bj)*deepFacC(k)
249     & *drF(k)*_hFacS(i,j,k,bi,bj)
250     ENDDO
251     ENDDO
252     C-- Calculate "volume transports" through tracer cell faces.
253     C anelastic: scaled by rhoFacC (~ mass transport)
254     DO j=1-OLy,sNy+OLy
255     DO i=1-OLx,sNx+OLx
256     uTrans(i,j) = uFld(i,j,k)*xA(i,j)*rhoFacC(k)
257     vTrans(i,j) = vFld(i,j,k)*yA(i,j)*rhoFacC(k)
258     ENDDO
259     ENDDO
260 jmc 1.1
261     C-- grid-box volume and tracer content (zero order moment)
262 jmc 1.2 DO j=1-OLy,sNy+OLy
263     DO i=1-OLx,sNx+OLx
264 jmc 1.1 smVol(i,j,k) = rA(i,j,bi,bj)*deepFac2C(k)
265     & *drF(k)*hFacC(i,j,k,bi,bj)
266     & *rhoFacC(k)
267     smTr0(i,j,k) = tracer(i,j,k,bi,bj)*smVol(i,j,k)
268     C- fill empty grid-box:
269     smVol(i,j,k) = smVol(i,j,k)
270     & + (1. _d 0 - maskC(i,j,k,bi,bj))
271 jmc 1.2 ENDDO
272 jmc 1.1 ENDDO
273    
274     C-- Multiple passes for different directions on different tiles
275     C-- For cube need one pass for each of red, green and blue axes.
276 jmc 1.2 DO ipass=1,npass
277 jmc 1.1
278 jmc 1.2 interiorOnly = .FALSE.
279     overlapOnly = .FALSE.
280     IF (useCubedSphereExchange) THEN
281     C- CubedSphere : pass 3 times, with partial update of local tracer field
282     IF (ipass.EQ.1) THEN
283     overlapOnly = MOD(nCFace,3).EQ.0
284     interiorOnly = MOD(nCFace,3).NE.0
285     calc_fluxes_X = nCFace.EQ.6 .OR. nCFace.EQ.1 .OR. nCFace.EQ.2
286     calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
287     ELSEIF (ipass.EQ.2) THEN
288     overlapOnly = MOD(nCFace,3).EQ.2
289     interiorOnly = MOD(nCFace,3).EQ.1
290     calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
291     calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
292     ELSE
293     interiorOnly = .TRUE.
294     calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
295     calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
296     ENDIF
297     ELSE
298 jmc 1.1 C- not CubedSphere
299 jmc 1.2 calc_fluxes_X = MOD(ipass,2).EQ.1
300     calc_fluxes_Y = .NOT.calc_fluxes_X
301     ENDIF
302 jmc 1.1
303     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
304 jmc 1.2
305 jmc 1.1 C-- X direction
306 jmc 1.2 C- Do not compute fluxes if
307     C a) needed in overlap only
308     C and b) the overlap of myTile are not cube-face Edges
309     IF ( calc_fluxes_X .AND.
310     & (.NOT.overlapOnly .OR. N_edge .OR. S_edge)
311     & ) THEN
312    
313     C- Internal exchange for calculations in X
314     IF ( useCubedSphereExchange .AND. .NOT.interiorOnly ) THEN
315     CALL GAD_SOM_PREP_CS_CORNER(
316     U smVol, smTr0, smTr, smCorners,
317     I .TRUE., overlapOnly, interiorOnly,
318     I N_edge, S_edge, E_edge, W_edge,
319     I ipass, k, Nr, bi, bj, myThid )
320     ENDIF
321    
322     C- Solve advection in X and update moments
323     IF ( advectionScheme.EQ.ENUM_SOM_PRATHER
324     & .OR. advectionScheme.EQ.ENUM_SOM_LIMITER ) THEN
325     CALL GAD_SOM_ADV_X(
326 jmc 1.1 I bi,bj,k, limiter,
327 jmc 1.2 I overlapOnly, interiorOnly,
328     I N_edge, S_edge, E_edge, W_edge,
329 jahn 1.7 I deltaTLev(k), uTrans,
330 jmc 1.10 I maskInC(1-OLx,1-OLy,bi,bj),
331 jmc 1.1 U smVol(1-OLx,1-OLy,k),
332     U smTr0(1-OLx,1-OLy,k),
333     U smTr(1-OLx,1-OLy,k,bi,bj,1),
334     U smTr(1-OLx,1-OLy,k,bi,bj,2),
335     U smTr(1-OLx,1-OLy,k,bi,bj,3),
336     U smTr(1-OLx,1-OLy,k,bi,bj,4),
337     U smTr(1-OLx,1-OLy,k,bi,bj,5),
338     U smTr(1-OLx,1-OLy,k,bi,bj,6),
339     U smTr(1-OLx,1-OLy,k,bi,bj,7),
340     U smTr(1-OLx,1-OLy,k,bi,bj,8),
341     U smTr(1-OLx,1-OLy,k,bi,bj,9),
342     O afx, myThid )
343 jmc 1.2 ELSE
344     STOP 'GAD_SOM_ADVECT: adv. scheme incompatibale with SOM'
345     ENDIF
346 jmc 1.1
347     C-- End of X direction
348 jmc 1.2 ENDIF
349 jmc 1.1
350     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
351 jmc 1.2
352 jmc 1.1 C-- Y direction
353     C- Do not compute fluxes if
354     C a) needed in overlap only
355     C and b) the overlap of myTile are not cube-face edges
356 jmc 1.2 IF ( calc_fluxes_Y .AND.
357     & (.NOT.overlapOnly .OR. E_edge .OR. W_edge)
358     & ) THEN
359    
360     C- Internal exchange for calculations in Y
361     IF ( useCubedSphereExchange .AND. .NOT.interiorOnly ) THEN
362     CALL GAD_SOM_PREP_CS_CORNER(
363     U smVol, smTr0, smTr, smCorners,
364     I .FALSE., overlapOnly, interiorOnly,
365     I N_edge, S_edge, E_edge, W_edge,
366     I iPass, k, Nr, bi, bj, myThid )
367     ENDIF
368    
369     C- Solve advection in Y and update moments
370     IF ( advectionScheme.EQ.ENUM_SOM_PRATHER
371     & .OR. advectionScheme.EQ.ENUM_SOM_LIMITER ) THEN
372     CALL GAD_SOM_ADV_Y(
373 jmc 1.1 I bi,bj,k, limiter,
374 jmc 1.2 I overlapOnly, interiorOnly,
375     I N_edge, S_edge, E_edge, W_edge,
376 jahn 1.7 I deltaTLev(k), vTrans,
377 jmc 1.10 I maskInC(1-OLx,1-OLy,bi,bj),
378 jmc 1.1 U smVol(1-OLx,1-OLy,k),
379     U smTr0(1-OLx,1-OLy,k),
380     U smTr(1-OLx,1-OLy,k,bi,bj,1),
381     U smTr(1-OLx,1-OLy,k,bi,bj,2),
382     U smTr(1-OLx,1-OLy,k,bi,bj,3),
383     U smTr(1-OLx,1-OLy,k,bi,bj,4),
384     U smTr(1-OLx,1-OLy,k,bi,bj,5),
385     U smTr(1-OLx,1-OLy,k,bi,bj,6),
386     U smTr(1-OLx,1-OLy,k,bi,bj,7),
387     U smTr(1-OLx,1-OLy,k,bi,bj,8),
388     U smTr(1-OLx,1-OLy,k,bi,bj,9),
389     O afy, myThid )
390 jmc 1.2 ELSE
391     STOP 'GAD_SOM_ADVECT: adv. scheme incompatibale with SOM'
392     ENDIF
393 jmc 1.1
394     C-- End of Y direction
395 jmc 1.2 ENDIF
396 jmc 1.1
397     C-- End of ipass loop
398 jmc 1.2 ENDDO
399 jmc 1.1
400 jmc 1.2 IF ( implicitAdvection ) THEN
401 jmc 1.1 C- explicit advection is done ; store tendency in gTracer:
402     DO j=1-OLy,sNy+OLy
403     DO i=1-OLx,sNx+OLx
404 jmc 1.5 C-- without rescaling of tendencies:
405     c localTr = smTr0(i,j,k)/smVol(i,j,k)
406     c gTracer(i,j,k,bi,bj) = ( localTr - tracer(i,j,k,bi,bj) )
407 jahn 1.7 c & / deltaTLev(k)
408 jmc 1.5 C-- consistent with rescaling of tendencies (in FREESURF_RESCALE_G):
409     gTracer(i,j,k,bi,bj) =
410     & ( smTr0(i,j,k) - tracer(i,j,k,bi,bj)*smVol(i,j,k) )
411     & *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
412     & *recip_drF(k)*_recip_hFacC(i,j,k,bi,bj)
413     & *recip_rhoFacC(k)
414 jahn 1.7 & /deltaTLev(k)
415 jmc 1.1 ENDDO
416     ENDDO
417 jmc 1.2 ENDIF
418 jmc 1.1
419     #ifdef ALLOW_DIAGNOSTICS
420 jmc 1.2 IF ( doDiagAdvX ) THEN
421     diagName = 'ADVx'//diagSufx
422     CALL DIAGNOSTICS_FILL(afx,diagName, k,1, 2,bi,bj, myThid )
423     ENDIF
424     IF ( doDiagAdvY ) THEN
425     diagName = 'ADVy'//diagSufx
426     CALL DIAGNOSTICS_FILL(afy,diagName, k,1, 2,bi,bj, myThid )
427     ENDIF
428 jmc 1.1 #endif
429    
430     #ifdef ALLOW_DEBUG
431 jmc 1.9 IF ( debugLevel .GE. debLevC
432 jmc 1.1 & .AND. tracerIdentity.EQ.GAD_TEMPERATURE
433     & .AND. k.LE.3 .AND. myIter.EQ.1+nIter0
434     & .AND. nPx.EQ.1 .AND. nPy.EQ.1
435     & .AND. useCubedSphereExchange ) THEN
436     CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_SOM_ADVECT',
437     & afx,afy, k, standardMessageUnit,bi,bj,myThid )
438 jmc 1.2 ENDIF
439 jmc 1.1 #endif /* ALLOW_DEBUG */
440    
441     C-- End of K loop for horizontal fluxes
442     ENDDO
443    
444     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
445    
446 jmc 1.11 noFlowAcrossSurf = rigidLid .OR. nonlinFreeSurf.GE.1
447     & .OR. select_rStar.NE.0
448    
449 jmc 1.1 IF ( .NOT.implicitAdvection ) THEN
450     C-- Apply limiter (if any):
451     CALL GAD_SOM_LIM_R( bi,bj, limiter,
452     U smVol,
453     U smTr0,
454     U smTr(1-OLx,1-OLy,1,bi,bj,1),
455     U smTr(1-OLx,1-OLy,1,bi,bj,2),
456     U smTr(1-OLx,1-OLy,1,bi,bj,3),
457     U smTr(1-OLx,1-OLy,1,bi,bj,4),
458     U smTr(1-OLx,1-OLy,1,bi,bj,5),
459     U smTr(1-OLx,1-OLy,1,bi,bj,6),
460     U smTr(1-OLx,1-OLy,1,bi,bj,7),
461     U smTr(1-OLx,1-OLy,1,bi,bj,8),
462     U smTr(1-OLx,1-OLy,1,bi,bj,9),
463     I myThid )
464    
465     C-- Start of k loop for vertical flux
466     DO k=Nr,1,-1
467     C-- kUp Cycles through 1,2 to point to w-layer above
468     C-- kDown Cycles through 2,1 to point to w-layer below
469     kUp = 1+MOD(Nr-k,2)
470     kDown= 1+MOD(Nr-k+1,2)
471     IF (k.EQ.Nr) THEN
472     C-- Set advective fluxes at the very bottom:
473     DO j=1-OLy,sNy+OLy
474     DO i=1-OLx,sNx+OLx
475     alp (i,j,kDown) = 0. _d 0
476     aln (i,j,kDown) = 0. _d 0
477     fp_v (i,j,kDown) = 0. _d 0
478     fn_v (i,j,kDown) = 0. _d 0
479     fp_o (i,j,kDown) = 0. _d 0
480     fn_o (i,j,kDown) = 0. _d 0
481     fp_x (i,j,kDown) = 0. _d 0
482     fn_x (i,j,kDown) = 0. _d 0
483     fp_y (i,j,kDown) = 0. _d 0
484     fn_y (i,j,kDown) = 0. _d 0
485     fp_z (i,j,kDown) = 0. _d 0
486     fn_z (i,j,kDown) = 0. _d 0
487     fp_xx(i,j,kDown) = 0. _d 0
488     fn_xx(i,j,kDown) = 0. _d 0
489     fp_yy(i,j,kDown) = 0. _d 0
490     fn_yy(i,j,kDown) = 0. _d 0
491     fp_zz(i,j,kDown) = 0. _d 0
492     fn_zz(i,j,kDown) = 0. _d 0
493     fp_xy(i,j,kDown) = 0. _d 0
494     fn_xy(i,j,kDown) = 0. _d 0
495     fp_xz(i,j,kDown) = 0. _d 0
496     fn_xz(i,j,kDown) = 0. _d 0
497     fp_yz(i,j,kDown) = 0. _d 0
498     fn_yz(i,j,kDown) = 0. _d 0
499     ENDDO
500     ENDDO
501     ENDIF
502    
503     C-- Compute Vertical transport
504     #ifdef ALLOW_AIM
505     C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
506     c IF ( k.EQ.1 .OR.
507     c & (useAIM .AND. tracerIdentity.EQ.GAD_SALINITY .AND. k.EQ.Nr)
508     c & ) THEN
509     #else
510     c IF ( k.EQ.1 ) THEN
511     #endif
512 jmc 1.11 IF ( noFlowAcrossSurf .AND. k.EQ.1 ) THEN
513 jmc 1.1 C- Surface interface :
514     DO j=1-OLy,sNy+OLy
515     DO i=1-OLx,sNx+OLx
516     rTrans(i,j) = 0.
517     maskUp(i,j) = 0.
518     ENDDO
519     ENDDO
520    
521 jmc 1.11 ELSEIF ( noFlowAcrossSurf ) THEN
522 jmc 1.1 C- Interior interface :
523     DO j=1-OLy,sNy+OLy
524     DO i=1-OLx,sNx+OLx
525 jmc 1.12 rTrans(i,j) = wFld(i,j,k)*rA(i,j,bi,bj)
526 jmc 1.1 & *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 jmc 1.12 rTrans(i,j) = wFld(i,j,k)*rA(i,j,bi,bj)
538 jmc 1.1 & *deepFac2F(k)*rhoFacF(k)
539     maskUp(i,j) = maskC(i,j,km1,bi,bj)*maskC(i,j,k,bi,bj)
540     ENDDO
541     ENDDO
542    
543     C- end Surface/Interior if bloc
544     ENDIF
545    
546     C- Compute vertical advective flux in the interior:
547     IF ( vertAdvecScheme.EQ.ENUM_SOM_PRATHER
548 jmc 1.2 & .OR. vertAdvecScheme.EQ.ENUM_SOM_LIMITER ) THEN
549     CALL GAD_SOM_ADV_R(
550 jmc 1.1 I bi,bj,k, kUp, kDown,
551 jahn 1.7 I deltaTLev(k), rTrans, maskUp,
552 jmc 1.10 I maskInC(1-OLx,1-OLy,bi,bj),
553 jmc 1.1 U smVol,
554     U smTr0,
555     U smTr(1-OLx,1-OLy,1,bi,bj,1),
556     U smTr(1-OLx,1-OLy,1,bi,bj,2),
557     U smTr(1-OLx,1-OLy,1,bi,bj,3),
558     U smTr(1-OLx,1-OLy,1,bi,bj,4),
559     U smTr(1-OLx,1-OLy,1,bi,bj,5),
560     U smTr(1-OLx,1-OLy,1,bi,bj,6),
561     U smTr(1-OLx,1-OLy,1,bi,bj,7),
562     U smTr(1-OLx,1-OLy,1,bi,bj,8),
563     U smTr(1-OLx,1-OLy,1,bi,bj,9),
564     U alp, aln, fp_v, fn_v, fp_o, fn_o,
565     U fp_x, fn_x, fp_y, fn_y, fp_z, fn_z,
566     U fp_xx, fn_xx, fp_yy, fn_yy, fp_zz, fn_zz,
567     U fp_xy, fn_xy, fp_xz, fn_xz, fp_yz, fn_yz,
568     O afr, myThid )
569     ELSE
570 jmc 1.2 STOP 'GAD_SOM_ADVECT: adv. scheme incompatibale with SOM'
571 jmc 1.1 ENDIF
572    
573 jmc 1.2 C-- Compute new tracer value and store tracer tendency
574 jmc 1.1 DO j=1-OLy,sNy+OLy
575     DO i=1-OLx,sNx+OLx
576 jmc 1.5 C-- without rescaling of tendencies:
577     c localTr = smTr0(i,j,k)/smVol(i,j,k)
578     c gTracer(i,j,k,bi,bj) = ( localTr - tracer(i,j,k,bi,bj) )
579 jahn 1.7 c & / deltaTLev(k)
580 jmc 1.11 C-- Non-Lin Free-Surf: consistent with rescaling of tendencies
581     C (in FREESURF_RESCALE_G) and RealFreshFlux/addMass.
582     C Also valid for linear Free-Surf (r & r* coords) except that surf tracer
583     C loss/gain is computed (in GAD_SOM_ADV_R) from partially updated tracer
584     C (instead of from Tr^n as fresh-water dilution effect) resulting in
585     C inaccurate linFSConserveTr and "surfExpan_" monitor.
586 jmc 1.5 gTracer(i,j,k,bi,bj) =
587     & ( smTr0(i,j,k) - tracer(i,j,k,bi,bj)*smVol(i,j,k) )
588 jmc 1.1 & *recip_rA(i,j,bi,bj)*recip_deepFac2C(k)
589     & *recip_drF(k)*_recip_hFacC(i,j,k,bi,bj)
590     & *recip_rhoFacC(k)
591 jahn 1.7 & /deltaTLev(k)
592 jmc 1.1 ENDDO
593     ENDDO
594    
595     #ifdef ALLOW_DIAGNOSTICS
596 jmc 1.2 IF ( doDiagAdvR ) THEN
597     diagName = 'ADVr'//diagSufx
598     CALL DIAGNOSTICS_FILL( afr,
599     & diagName, k,1, 2,bi,bj, myThid )
600 jmc 1.1 ENDIF
601     #endif
602    
603 jmc 1.2 C-- End of k loop for vertical flux
604 jmc 1.1 ENDDO
605     C-- end of if not.implicitAdvection block
606     ENDIF
607    
608     RETURN
609     END

  ViewVC Help
Powered by ViewVC 1.1.22