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

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

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


Revision 1.8 - (hide annotations) (download)
Fri Sep 28 16:49:54 2001 UTC (22 years, 7 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint44e_post, checkpoint43a-release1mods, chkpt44d_post, checkpoint44e_pre, release1_b1, checkpoint43, release1_chkpt44d_post, release1-branch_tutorials, chkpt44a_post, chkpt44c_pre, ecco_c44_e18, ecco_c44_e17, ecco_c44_e16, release1-branch-end, checkpoint44b_post, chkpt44a_pre, ecco-branch-mod1, ecco-branch-mod2, ecco-branch-mod3, ecco-branch-mod4, ecco-branch-mod5, release1_beta1, checkpoint44b_pre, checkpoint44, chkpt44c_post, checkpoint44f_pre, release1-branch_branchpoint
Branch point for: release1_final, release1-branch, release1, ecco-branch, release1_coupled
Changes since 1.7: +2 -3 lines
Changes for structuing protex document.

1 adcroft 1.8 C $Header: /u/gcmpack/models/MITgcmUV/pkg/generic_advdiff/gad_advection.F,v 1.7 2001/09/28 02:26:57 adcroft Exp $
2 adcroft 1.2 C $Name: $
3 adcroft 1.1
4 adcroft 1.4 CBOI
5     C !TITLE: pkg/generic\_advdiff
6     C !AUTHORS: adcroft@mit.edu
7 adcroft 1.8 C !INTRODUCTION: Generic Advection Diffusion Package
8 adcroft 1.4 C
9     C Package "generic\_advdiff" provides a common set of routines for calculating
10     C advective/diffusive fluxes for tracers (cell centered quantities on a C-grid).
11     C
12     C Many different advection schemes are available: the standard centered
13     C second order, centered fourth order and upwind biased third order schemes
14     C are known as linear methods and require some stable time-stepping method
15     C such as Adams-Bashforth. Alternatives such as flux-limited schemes are
16     C stable in the forward sense and are best combined with the multi-dimensional
17     C method provided in gad\_advection.
18     C
19     C There are two high-level routines:
20     C \begin{itemize}
21     C \item{GAD\_CALC\_RHS} calculates all fluxes at time level "n" and is used
22     C for the standard linear schemes. This must be used in conjuction with
23     C Adams-Bashforth time-stepping. Diffusive and parameterized fluxes are
24     C always calculated here.
25     C \item{GAD\_ADVECTION} calculates just the advective fluxes using the
26     C non-linear schemes and can not be used in conjuction with Adams-Bashforth
27     C time-stepping.
28     C \end{itemize}
29     CEOI
30    
31 adcroft 1.1 #include "GAD_OPTIONS.h"
32    
33 adcroft 1.4 CBOP
34     C !ROUTINE: GAD_ADVECTION
35    
36     C !INTERFACE: ==========================================================
37 adcroft 1.1 SUBROUTINE GAD_ADVECTION(bi,bj,advectionScheme,tracerIdentity,
38     U Tracer,Gtracer,
39     I myTime,myIter,myThid)
40 adcroft 1.4
41     C !DESCRIPTION:
42     C Calculates the tendancy of a tracer due to advection.
43     C It uses the multi-dimensional method given in \ref{sect:multiDimAdvection}
44     C and can only be used for the non-linear advection schemes such as the
45     C direct-space-time method and flux-limiters.
46     C
47     C The algorithm is as follows:
48     C \begin{itemize}
49     C \item{$\theta^{(n+1/3)} = \theta^{(n)}
50 adcroft 1.5 C - \Delta t \partial_x (u\theta^{(n)}) + \theta^{(n)} \partial_x u$}
51 adcroft 1.4 C \item{$\theta^{(n+2/3)} = \theta^{(n+1/3)}
52 adcroft 1.5 C - \Delta t \partial_y (v\theta^{(n+1/3)}) + \theta^{(n)} \partial_y v$}
53 adcroft 1.4 C \item{$\theta^{(n+3/3)} = \theta^{(n+2/3)}
54 adcroft 1.5 C - \Delta t \partial_r (w\theta^{(n+2/3)}) + \theta^{(n)} \partial_r w$}
55 adcroft 1.4 C \item{$G_\theta = ( \theta^{(n+3/3)} - \theta^{(n)} )/\Delta t$}
56     C \end{itemize}
57     C
58     C The tendancy (output) is over-written by this routine.
59    
60     C !USES: ===============================================================
61 adcroft 1.1 IMPLICIT NONE
62     #include "SIZE.h"
63     #include "EEPARAMS.h"
64     #include "PARAMS.h"
65     #include "DYNVARS.h"
66     #include "GRID.h"
67     #include "GAD.h"
68 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
69     # include "tamc.h"
70     # include "tamc_keys.h"
71     #endif
72 adcroft 1.1
73 adcroft 1.4 C !INPUT PARAMETERS: ===================================================
74     C bi,bj :: tile indices
75     C advectionScheme :: advection scheme to use
76     C tracerIdentity :: identifier for the tracer (required only for OBCS)
77     C Tracer :: tracer field
78     C myTime :: current time
79     C myIter :: iteration number
80     C myThid :: thread number
81 adcroft 1.1 INTEGER bi,bj
82     INTEGER advectionScheme
83     INTEGER tracerIdentity
84     _RL Gtracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
85     _RL myTime
86     INTEGER myIter
87     INTEGER myThid
88    
89 adcroft 1.4 C !OUTPUT PARAMETERS: ==================================================
90     C gTracer :: tendancy array
91     _RL Tracer(1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr,nSx,nSy)
92    
93     C !LOCAL VARIABLES: ====================================================
94     C maskUp :: 2-D array for mask at W points
95     C iMin,iMax,jMin,jMax :: loop range for called routines
96     C i,j,k :: loop indices
97     C kup :: index into 2 1/2D array, toggles between 1 and 2
98     C kdown :: index into 2 1/2D array, toggles between 2 and 1
99     C kp1 :: =k+1 for k<Nr, =Nr for k=Nr
100     C xA,yA :: areas of X and Y face of tracer cells
101     C uTrans,vTrans,rTrans :: 2-D arrays of volume transports at U,V and W points
102     C af :: 2-D array for horizontal advective flux
103     C fVerT :: 2 1/2D arrays for vertical advective flux
104     C localTij :: 2-D array used as temporary local copy of tracer fld
105     C localTijk :: 3-D array used as temporary local copy of tracer fld
106     C kp1Msk :: flag (0,1) to act as over-riding mask for W levels
107     C calc_fluxes_X :: logical to indicate to calculate fluxes in X dir
108     C calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
109     C nipass :: number of passes to make in multi-dimensional method
110     C ipass :: number of the current pass being made
111 adcroft 1.1 _RS maskUp (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
112     INTEGER iMin,iMax,jMin,jMax
113     INTEGER i,j,k,kup,kDown,kp1
114     _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
115     _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
116     _RL uTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
117     _RL vTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
118     _RL rTrans (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
119     _RL af (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120     _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
121     _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122     _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
123     _RL kp1Msk
124 adcroft 1.3 LOGICAL calc_fluxes_X,calc_fluxes_Y
125     INTEGER nipass,ipass
126 adcroft 1.4 CEOP
127 adcroft 1.1
128 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
129     act1 = bi - myBxLo(myThid)
130     max1 = myBxHi(myThid) - myBxLo(myThid) + 1
131     act2 = bj - myByLo(myThid)
132     max2 = myByHi(myThid) - myByLo(myThid) + 1
133     act3 = myThid - 1
134     max3 = nTx*nTy
135     act4 = ikey_dynamics - 1
136     ikey = (act1 + 1) + act2*max1
137     & + act3*max1*max2
138     & + act4*max1*max2*max3
139     #endif /* ALLOW_AUTODIFF_TAMC */
140    
141 adcroft 1.1 C-- Set up work arrays with valid (i.e. not NaN) values
142     C These inital values do not alter the numerical results. They
143     C just ensure that all memory references are to valid floating
144     C point numbers. This prevents spurious hardware signals due to
145     C uninitialised but inert locations.
146     DO j=1-OLy,sNy+OLy
147     DO i=1-OLx,sNx+OLx
148     xA(i,j) = 0. _d 0
149     yA(i,j) = 0. _d 0
150     uTrans(i,j) = 0. _d 0
151     vTrans(i,j) = 0. _d 0
152     rTrans(i,j) = 0. _d 0
153     fVerT(i,j,1) = 0. _d 0
154     fVerT(i,j,2) = 0. _d 0
155     ENDDO
156     ENDDO
157    
158     iMin = 1-OLx
159     iMax = sNx+OLx
160     jMin = 1-OLy
161     jMax = sNy+OLy
162    
163     C-- Start of k loop for horizontal fluxes
164     DO k=1,Nr
165 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
166     kkey = (ikey-1)*Nr + k
167     CADJ STORE tracer(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
168     #endif /* ALLOW_AUTODIFF_TAMC */
169 adcroft 1.1
170     C-- Get temporary terms used by tendency routines
171     CALL CALC_COMMON_FACTORS (
172     I bi,bj,iMin,iMax,jMin,jMax,k,
173     O xA,yA,uTrans,vTrans,rTrans,maskUp,
174     I myThid)
175    
176     C-- Make local copy of tracer array
177     DO j=1-OLy,sNy+OLy
178     DO i=1-OLx,sNx+OLx
179     localTij(i,j)=tracer(i,j,k,bi,bj)
180     ENDDO
181     ENDDO
182    
183 adcroft 1.3 IF (useCubedSphereExchange) THEN
184     nipass=3
185     ELSE
186     nipass=1
187     ENDIF
188 heimbach 1.6 cph nipass=1
189 adcroft 1.3
190     C-- Multiple passes for different directions on different tiles
191     DO ipass=1,nipass
192 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
193     passkey = ipass + (k-1) *maxpass
194     & + (ikey-1)*maxpass*Nr
195     IF (nipass .GT. maxpass) THEN
196     STOP 'GAD_ADVECTION: nipass > maxpass. check tamc.h'
197     ENDIF
198     #endif /* ALLOW_AUTODIFF_TAMC */
199 adcroft 1.3
200     IF (nipass.EQ.3) THEN
201     calc_fluxes_X=.FALSE.
202     calc_fluxes_Y=.FALSE.
203     IF (ipass.EQ.1 .AND. (bi.EQ.1 .OR. bi.EQ.2) ) THEN
204     calc_fluxes_X=.TRUE.
205     ELSEIF (ipass.EQ.1 .AND. (bi.EQ.4 .OR. bi.EQ.5) ) THEN
206     calc_fluxes_Y=.TRUE.
207     ELSEIF (ipass.EQ.2 .AND. (bi.EQ.1 .OR. bi.EQ.6) ) THEN
208     calc_fluxes_Y=.TRUE.
209     ELSEIF (ipass.EQ.2 .AND. (bi.EQ.3 .OR. bi.EQ.4) ) THEN
210     calc_fluxes_X=.TRUE.
211     ELSEIF (ipass.EQ.3 .AND. (bi.EQ.2 .OR. bi.EQ.3) ) THEN
212     calc_fluxes_Y=.TRUE.
213     ELSEIF (ipass.EQ.3 .AND. (bi.EQ.5 .OR. bi.EQ.6) ) THEN
214     calc_fluxes_X=.TRUE.
215     ENDIF
216     ELSE
217     calc_fluxes_X=.TRUE.
218     calc_fluxes_Y=.TRUE.
219     ENDIF
220    
221     C-- X direction
222     IF (calc_fluxes_X) THEN
223    
224     C-- Internal exchange for calculations in X
225     IF (useCubedSphereExchange) THEN
226     DO j=1,Oly
227     DO i=1,Olx
228     localTij( 1-i , 1-j )=localTij( 1-j , i )
229     localTij( 1-i ,sNy+j)=localTij( 1-j , sNy+1-i )
230     localTij(sNx+i, 1-j )=localTij(sNx+j, i )
231     localTij(sNx+i,sNy+j)=localTij(sNx+j, sNy+1-i )
232     ENDDO
233     ENDDO
234     ENDIF
235    
236 adcroft 1.1 C- Advective flux in X
237     DO j=1-Oly,sNy+Oly
238     DO i=1-Olx,sNx+Olx
239     af(i,j) = 0.
240     ENDDO
241     ENDDO
242 heimbach 1.6
243     #ifdef ALLOW_AUTODIFF_TAMC
244 adcroft 1.7 #ifndef DISABLE_MULTIDIM_ADVECTION
245 heimbach 1.6 CADJ STORE localTij(:,:) = comlev1_bibj_pass, key=passkey, byte=isbyte
246     #endif
247     #endif /* ALLOW_AUTODIFF_TAMC */
248    
249 adcroft 1.1 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
250     CALL GAD_FLUXLIMIT_ADV_X(
251     & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
252     ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
253     CALL GAD_DST3_ADV_X(
254     & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
255     ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
256     CALL GAD_DST3FL_ADV_X(
257     & bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)
258     ELSE
259     STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
260     ENDIF
261 heimbach 1.6
262 adcroft 1.1 DO j=1-Oly,sNy+Oly
263     DO i=1-Olx,sNx+Olx-1
264     localTij(i,j)=localTij(i,j)-deltaTtracer*
265     & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
266     & *recip_rA(i,j,bi,bj)
267     & *( af(i+1,j)-af(i,j)
268     & -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
269     & )
270     ENDDO
271     ENDDO
272    
273     #ifdef ALLOW_OBCS
274     C-- Apply open boundary conditions
275     IF (useOBCS) THEN
276     IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
277     CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
278     ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
279     CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
280     END IF
281     END IF
282     #endif /* ALLOW_OBCS */
283    
284 adcroft 1.3 C-- End of X direction
285     ENDIF
286    
287     C-- Y direction
288     IF (calc_fluxes_Y) THEN
289    
290     C-- Internal exchange for calculations in Y
291     IF (useCubedSphereExchange) THEN
292     DO j=1,Oly
293     DO i=1,Olx
294     localTij( 1-i , 1-j )=localTij( j , 1-i )
295     localTij( 1-i ,sNy+j)=localTij( j ,sNy+i)
296     localTij(sNx+i, 1-j )=localTij(sNx+1-j, 1-i )
297     localTij(sNx+i,sNy+j)=localTij(sNx+1-j,sNy+i)
298     ENDDO
299     ENDDO
300     ENDIF
301    
302 adcroft 1.1 C- Advective flux in Y
303     DO j=1-Oly,sNy+Oly
304     DO i=1-Olx,sNx+Olx
305     af(i,j) = 0.
306     ENDDO
307     ENDDO
308 heimbach 1.6
309     #ifdef ALLOW_AUTODIFF_TAMC
310 adcroft 1.7 #ifndef DISABLE_MULTIDIM_ADVECTION
311 heimbach 1.6 CADJ STORE localTij(:,:) = comlev1_bibj_pass, key=passkey, byte=isbyte
312     #endif
313     #endif /* ALLOW_AUTODIFF_TAMC */
314    
315 adcroft 1.1 IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
316     CALL GAD_FLUXLIMIT_ADV_Y(
317     & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
318     ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
319     CALL GAD_DST3_ADV_Y(
320     & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
321     ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
322     CALL GAD_DST3FL_ADV_Y(
323     & bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)
324     ELSE
325     STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
326     ENDIF
327 heimbach 1.6
328 adcroft 1.1 DO j=1-Oly,sNy+Oly-1
329     DO i=1-Olx,sNx+Olx
330     localTij(i,j)=localTij(i,j)-deltaTtracer*
331     & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
332     & *recip_rA(i,j,bi,bj)
333     & *( af(i,j+1)-af(i,j)
334     & -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
335     & )
336     ENDDO
337     ENDDO
338 adcroft 1.3
339 adcroft 1.1 #ifdef ALLOW_OBCS
340     C-- Apply open boundary conditions
341     IF (useOBCS) THEN
342     IF (tracerIdentity.EQ.GAD_TEMPERATURE) THEN
343     CALL OBCS_APPLY_TLOC( bi, bj, k, localTij, myThid )
344     ELSEIF (tracerIdentity.EQ.GAD_SALINITY) THEN
345     CALL OBCS_APPLY_SLOC( bi, bj, k, localTij, myThid )
346     END IF
347     END IF
348     #endif /* ALLOW_OBCS */
349 adcroft 1.3
350     C-- End of Y direction
351     ENDIF
352    
353     DO j=1-Oly,sNy+Oly
354 adcroft 1.1 DO i=1-Olx,sNx+Olx
355     localTijk(i,j,k)=localTij(i,j)
356     ENDDO
357     ENDDO
358    
359 adcroft 1.3 C-- End of ipass loop
360     ENDDO
361 adcroft 1.1
362     C-- End of K loop for horizontal fluxes
363     ENDDO
364    
365     C-- Start of k loop for vertical flux
366     DO k=Nr,1,-1
367 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
368     kkey = (ikey-1)*Nr + k
369     #endif /* ALLOW_AUTODIFF_TAMC */
370 adcroft 1.1
371     C-- kup Cycles through 1,2 to point to w-layer above
372     C-- kDown Cycles through 2,1 to point to w-layer below
373     kup = 1+MOD(k+1,2)
374     kDown= 1+MOD(k,2)
375    
376     C-- Get temporary terms used by tendency routines
377     CALL CALC_COMMON_FACTORS (
378     I bi,bj,iMin,iMax,jMin,jMax,k,
379     O xA,yA,uTrans,vTrans,rTrans,maskUp,
380     I myThid)
381    
382     C- Advective flux in R
383     DO j=1-Oly,sNy+Oly
384     DO i=1-Olx,sNx+Olx
385     af(i,j) = 0.
386     ENDDO
387     ENDDO
388 heimbach 1.6
389     #ifdef ALLOW_AUTODIFF_TAMC
390     CADJ STORE localTijk(:,:,k)
391     CADJ & = comlev1_bibj_k, key=kkey, byte=isbyte
392     #endif /* ALLOW_AUTODIFF_TAMC */
393 adcroft 1.1
394     C Note: wVel needs to be masked
395     IF (K.GE.2) THEN
396     C- Compute vertical advective flux in the interior:
397     IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
398     CALL GAD_FLUXLIMIT_ADV_R(
399     & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
400     ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
401 adcroft 1.2 CALL GAD_DST3_ADV_R(
402     & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
403 adcroft 1.1 ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
404 adcroft 1.2 CALL GAD_DST3FL_ADV_R(
405     & bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)
406 adcroft 1.1 ELSE
407     STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
408     ENDIF
409     C- Surface "correction" term at k>1 :
410     DO j=1-Oly,sNy+Oly
411     DO i=1-Olx,sNx+Olx
412     af(i,j) = af(i,j)
413     & + (maskC(i,j,k,bi,bj)-maskC(i,j,k-1,bi,bj))*
414     & rTrans(i,j)*localTijk(i,j,k)
415     ENDDO
416     ENDDO
417     ELSE
418     C- Surface "correction" term at k=1 :
419     DO j=1-Oly,sNy+Oly
420     DO i=1-Olx,sNx+Olx
421     af(i,j) = rTrans(i,j)*localTijk(i,j,k)
422     ENDDO
423     ENDDO
424     ENDIF
425     C- add the advective flux to fVerT
426     DO j=1-Oly,sNy+Oly
427     DO i=1-Olx,sNx+Olx
428     fVerT(i,j,kUp) = af(i,j)
429     ENDDO
430     ENDDO
431    
432     C-- Divergence of fluxes
433     kp1=min(Nr,k+1)
434     kp1Msk=1.
435     if (k.EQ.Nr) kp1Msk=0.
436     DO j=1-Oly,sNy+Oly
437     DO i=1-Olx,sNx+Olx
438     localTij(i,j)=localTijk(i,j,k)-deltaTtracer*
439     & _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
440     & *recip_rA(i,j,bi,bj)
441     & *( fVerT(i,j,kUp)-fVerT(i,j,kDown)
442     & -tracer(i,j,k,bi,bj)*rA(i,j,bi,bj)*
443     & (wVel(i,j,k,bi,bj)-kp1Msk*wVel(i,j,kp1,bi,bj))
444     & )*rkFac
445     gTracer(i,j,k,bi,bj)=
446     & (localTij(i,j)-tracer(i,j,k,bi,bj))/deltaTtracer
447     ENDDO
448     ENDDO
449    
450     C-- End of K loop for vertical flux
451     ENDDO
452    
453     RETURN
454     END

  ViewVC Help
Powered by ViewVC 1.1.22