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

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

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

revision 1.28 by jmc, Tue Sep 21 12:13:44 2004 UTC revision 1.29 by jmc, Fri Sep 24 16:52:44 2004 UTC
# Line 84  C  gTracer           :: tendancy array Line 84  C  gTracer           :: tendancy array
84    
85  C !LOCAL VARIABLES: ====================================================  C !LOCAL VARIABLES: ====================================================
86  C  maskUp        :: 2-D array for mask at W points  C  maskUp        :: 2-D array for mask at W points
87    C  maskLocW      :: 2-D array for mask at West points
88    C  maskLocS      :: 2-D array for mask at South points
89  C  iMin,iMax,    :: loop range for called routines  C  iMin,iMax,    :: loop range for called routines
90  C  jMin,jMax     :: loop range for called routines  C  jMin,jMax     :: loop range for called routines
91  C  i,j,k         :: loop indices  C  i,j,k         :: loop indices
# Line 94  C  xA,yA         :: areas of X and Y fac Line 96  C  xA,yA         :: areas of X and Y fac
96  C  uTrans,vTrans :: 2-D arrays of volume transports at U,V points  C  uTrans,vTrans :: 2-D arrays of volume transports at U,V points
97  C  rTrans        :: 2-D arrays of volume transports at W points  C  rTrans        :: 2-D arrays of volume transports at W points
98  C  rTransKp1     :: vertical volume transport at interface k+1  C  rTransKp1     :: vertical volume transport at interface k+1
99  C  af            :: 2-D array for horizontal advective flux  C  afx           :: 2-D array for horizontal advective flux, x direction
100    C  afy           :: 2-D array for horizontal advective flux, y direction
101  C  fVerT         :: 2 1/2D arrays for vertical advective flux  C  fVerT         :: 2 1/2D arrays for vertical advective flux
102  C  localTij      :: 2-D array, temporary local copy of tracer fld  C  localTij      :: 2-D array, temporary local copy of tracer fld
103  C  localTijk     :: 3-D array, temporary local copy of tracer fld  C  localTijk     :: 3-D array, temporary local copy of tracer fld
# Line 107  C  myTile        :: variables used to de Line 110  C  myTile        :: variables used to de
110  C  nCFace        :: owns a tile for cube grid runs using  C  nCFace        :: owns a tile for cube grid runs using
111  C                :: multi-dim advection.  C                :: multi-dim advection.
112        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
113          _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
114          _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
115        INTEGER iMin,iMax,jMin,jMax        INTEGER iMin,iMax,jMin,jMax
116        INTEGER i,j,k,kup,kDown        INTEGER i,j,k,kup,kDown
117        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 115  C                :: multi-dim advection. Line 120  C                :: multi-dim advection.
120        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
122        _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
123        _RL af      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL afx     (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
124          _RL afy     (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
125        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
126        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL localTij(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
127        _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL localTijk(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
128        _RL kp1Msk        _RL kp1Msk
129        LOGICAL calc_fluxes_X,calc_fluxes_Y        LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns
130        INTEGER nipass,ipass        INTEGER nipass,ipass
131        INTEGER myTile, nCFace        INTEGER myTile, nCFace
       LOGICAL southWestCorner  
       LOGICAL southEastCorner  
       LOGICAL northWestCorner  
       LOGICAL northEastCorner  
132  CEOP  CEOP
133    
134  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 194  C--   Residual transp = Bolus transp + E Line 196  C--   Residual transp = Bolus transp + E
196       &            uTrans, vTrans, bi, bj, k, myThid)       &            uTrans, vTrans, bi, bj, k, myThid)
197  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
198    
199  C--   Make local copy of tracer array  C--   Make local copy of tracer array and mask West & South
200        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
201         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
202          localTij(i,j)=tracer(i,j,k,bi,bj)          localTij(i,j)=tracer(i,j,k,bi,bj)
203            maskLocW(i,j)=maskW(i,j,k,bi,bj)
204            maskLocS(i,j)=maskS(i,j,k,bi,bj)
205         ENDDO         ENDDO
206        ENDDO        ENDDO
207    
208  cph  The following block is needed for useCubedSphereExchange only,        IF (useCubedSphereExchange) THEN
209  cph  but needs to be set for all cases to avoid spurious          withSigns = .FALSE.
210  cph  TAF dependencies          CALL FILL_CS_CORNER_UV_RS(
211         southWestCorner = .TRUE.       &            withSigns, maskLocW,maskLocS, bi,bj, myThid )
212         southEastCorner = .TRUE.        ENDIF
        northWestCorner = .TRUE.  
        northEastCorner = .TRUE.  
213  #ifdef ALLOW_EXCH2  #ifdef ALLOW_EXCH2
214         myTile = W2_myTileList(bi)         myTile = W2_myTileList(bi)
215         nCFace = exch2_myFace(myTile)         nCFace = exch2_myFace(myTile)
        southWestCorner = exch2_isWedge(myTile).EQ.1  
      &             .AND. exch2_isSedge(myTile).EQ.1  
        southEastCorner = exch2_isEedge(myTile).EQ.1  
      &             .AND. exch2_isSedge(myTile).EQ.1  
        northEastCorner = exch2_isEedge(myTile).EQ.1  
      &             .AND. exch2_isNedge(myTile).EQ.1  
        northWestCorner = exch2_isWedge(myTile).EQ.1  
      &             .AND. exch2_isNedge(myTile).EQ.1  
216  #else  #else
217         nCFace = bi         nCFace = bi
218  #endif  #endif
# Line 232  cph  TAF dependencies Line 226  cph  TAF dependencies
226        ELSE        ELSE
227         nipass=1         nipass=1
228        ENDIF        ENDIF
 cph       nipass=1  
229    
230  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
231  C--   For cube need one pass for each of red, green and blue axes.  C--   For cube need one pass for each of red, green and blue axes.
# Line 266  C--   For cube need one pass for each of Line 259  C--   For cube need one pass for each of
259         calc_fluxes_Y=.TRUE.         calc_fluxes_Y=.TRUE.
260        ENDIF        ENDIF
261    
262    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
263  C--   X direction  C--   X direction
264        IF (calc_fluxes_X) THEN        IF (calc_fluxes_X) THEN
265    
266  C--   Internal exchange for calculations in X  C--   Internal exchange for calculations in X
267        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
268  C--    For cube face corners we need to duplicate the           CALL FILL_CS_CORNER_TR_RL( .TRUE., localTij, bi,bj, myThid )
 C--    i-1 and i+1 values into the null space as follows:  
 C  
 C  
 C      o NW corner: copy T(    0,sNy  ) into T(    0,sNy+1) e.g.  
 C                      |  
 C         x T(0,sNy+1) |  
 C        /\            |  
 C      --||------------|-----------  
 C        ||            |  
 C         x T(0,sNy)   |   x T(1,sNy)  
 C                      |  
 C  
 C      o SW corner: copy T(0,1) into T(0,0) e.g.  
 C                      |  
 C         x T(0,1)     |  x T(1,1)  
 C        ||            |  
 C      --||------------|-----------  
 C        \/            |  
 C         x T(0,0)     |  
 C                      |  
 C  
 C      o NE corner: copy T(sNx+1,sNy  ) into T(sNx+1,sNy+1) e.g.  
 C                      |  
 C                      |   x T(sNx+1,sNy+1)  
 C                      |  /\  
 C      ----------------|--||-------  
 C                      |  ||  
 C         x T(sNx,sNy) |   x T(sNx+1,sNy  )  
 C                      |  
 C      o SE corner: copy T(sNx+1,1    ) into T(sNx+1,0    ) e.g.  
 C                      |  
 C         x T(sNx,1)   |   x T(sNx+1,    1)  
 C                      |  ||  
 C      ----------------|--||-------  
 C                      |  \/  
 C                      |   x T(sNx+1,    0)  
        IF ( southWestCorner ) THEN  
         DO j=1,OLy  
          DO i=1,OLx  
           localTij( 1-i , 1-j )=localTij( 1-j , i  )  
          ENDDO  
         ENDDO  
        ENDIF  
        IF ( southEastCorner ) THEN  
         DO J=1,OLy  
          DO I=1,OLx  
           localTij(sNx+I, 1-J )=localTij(sNx+J, I  )  
          ENDDO  
         ENDDO  
        ENDIF  
        IF ( northWestCorner ) THEN  
         DO J=1,OLy  
          DO I=1,OLx  
           localTij( 1-I ,sNy+J)=localTij( 1-J , sNy+1-I )  
          ENDDO  
         ENDDO  
        ENDIF  
        IF ( northEastCorner ) THEN  
         DO J=1,OLy  
          DO I=1,OLx  
           localTij(sNx+I,sNy+J)=localTij(sNx+J, sNy+1-I )  
          ENDDO  
         ENDDO  
        ENDIF  
269        ENDIF        ENDIF
270    
271  C-    Advective flux in X  C-    Advective flux in X
272        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
273         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
274          af(i,j) = 0.          afx(i,j) = 0.
275         ENDDO         ENDDO
276        ENDDO        ENDDO
277    
# Line 353  CADJ &     comlev1_bibj_k_gad_pass, key= Line 283  CADJ &     comlev1_bibj_k_gad_pass, key=
283  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
284    
285        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
286         CALL GAD_FLUXLIMIT_ADV_X(          CALL GAD_FLUXLIMIT_ADV_X( bi,bj,k, deltaTtracer,
287       &      bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       I                            uTrans, uVel, maskLocW, localTij,
288         O                            afx, myThid )
289        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
290         CALL GAD_DST3_ADV_X(          CALL GAD_DST3_ADV_X(      bi,bj,k, deltaTtracer,
291       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       I                            uTrans, uVel, maskLocW, localTij,
292         O                            afx, myThid )
293        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
294         CALL GAD_DST3FL_ADV_X(          CALL GAD_DST3FL_ADV_X(    bi,bj,k, deltaTtracer,
295       &       bi,bj,k,deltaTtracer,uTrans,uVel,localTij,af,myThid)       I                            uTrans, uVel, maskLocW, localTij,
296         O                            afx, myThid )
297        ELSE        ELSE
298         STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'         STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
299        ENDIF        ENDIF
# Line 370  CADJ &     comlev1_bibj_k_gad_pass, key= Line 303  CADJ &     comlev1_bibj_k_gad_pass, key=
303          localTij(i,j)=localTij(i,j)-deltaTtracer*          localTij(i,j)=localTij(i,j)-deltaTtracer*
304       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
305       &    *recip_rA(i,j,bi,bj)       &    *recip_rA(i,j,bi,bj)
306       &    *( af(i+1,j)-af(i,j)       &    *( afx(i+1,j)-afx(i,j)
307       &      -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))       &      -tracer(i,j,k,bi,bj)*(uTrans(i+1,j)-uTrans(i,j))
308       &     )       &     )
309         ENDDO         ENDDO
# Line 390  C--   Apply open boundary conditions Line 323  C--   Apply open boundary conditions
323  C--   End of X direction  C--   End of X direction
324        ENDIF        ENDIF
325    
326    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
327  C--   Y direction  C--   Y direction
328        IF (calc_fluxes_Y) THEN        IF (calc_fluxes_Y) THEN
329    
       IF (useCubedSphereExchange) THEN  
330  C--   Internal exchange for calculations in Y  C--   Internal exchange for calculations in Y
331  C--    For cube face corners we need to duplicate the        IF (useCubedSphereExchange) THEN
332  C--    j-1 and j+1 values into the null space as follows:           CALL FILL_CS_CORNER_TR_RL(.FALSE., localTij, bi,bj, myThid )
 C  
 C      o SW corner: copy T(0,1) into T(0,0) e.g.  
 C                      |  
 C                      |  x T(1,1)  
 C                      |  
 C      ----------------|-----------  
 C                      |  
 C         x T(0,0)<====== x T(1,0)  
 C                      |  
 C  
 C      o NW corner: copy T(    0,sNy  ) into T(    0,sNy+1) e.g.  
 C                      |  
 C         x T(0,sNy+1)<=== x T(1,sNy+1)  
 C                      |  
 C      ----------------|-----------  
 C                      |  
 C                      |   x T(1,sNy)  
 C                      |  
 C  
 C      o NE corner: copy T(sNx+1,sNy  ) into T(sNx+1,sNy+1) e.g.  
 C                      |  
 C      x T(sNx,sNy+1)=====>x T(sNx+1,sNy+1)  
 C                      |      
 C      ----------------|-----------  
 C                      |      
 C      x T(sNx,sNy)    |                        
 C                      |  
 C      o SE corner: copy T(sNx+1,1    ) into T(sNx+1,0    ) e.g.  
 C                      |  
 C         x T(sNx,1)   |                      
 C                      |      
 C      ----------------|-----------  
 C                      |      
 C         x T(sNx,0) =====>x T(sNx+1,    0)  
        IF ( southWestCorner ) THEN  
         DO J=1,Oly  
          DO I=1,Olx  
           localTij( 1-i , 1-j ) = localTij(j   , 1-i )  
          ENDDO  
         ENDDO  
        ENDIF  
        IF ( southEastCorner ) THEN  
         DO J=1,Oly  
          DO I=1,Olx  
           localTij(sNx+i, 1-j ) = localTij(sNx+1-j, 1-i )  
          ENDDO  
         ENDDO  
        ENDIF  
        IF ( northWestCorner ) THEN  
         DO J=1,Oly  
          DO I=1,Olx  
           localTij( 1-i ,sNy+j) = localTij(j   ,sNy+i)  
          ENDDO  
         ENDDO  
        ENDIF  
        IF ( northEastCorner ) THEN  
         DO J=1,Oly  
          DO I=1,Olx  
           localTij(sNx+i,sNy+j) = localTij(sNx+1-j,sNy+i)  
          ENDDO  
         ENDDO  
        ENDIF  
333        ENDIF        ENDIF
334    
335  C-    Advective flux in Y  C-    Advective flux in Y
336        DO j=1-Oly,sNy+Oly        DO j=1-Oly,sNy+Oly
337         DO i=1-Olx,sNx+Olx         DO i=1-Olx,sNx+Olx
338          af(i,j) = 0.          afy(i,j) = 0.
339         ENDDO         ENDDO
340        ENDDO        ENDDO
341    
# Line 476  CADJ &     comlev1_bibj_k_gad_pass, key= Line 347  CADJ &     comlev1_bibj_k_gad_pass, key=
347  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
348    
349        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN        IF (advectionScheme.EQ.ENUM_FLUX_LIMIT) THEN
350         CALL GAD_FLUXLIMIT_ADV_Y(          CALL GAD_FLUXLIMIT_ADV_Y( bi,bj,k, deltaTtracer,
351       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)       I                            vTrans, vVel, maskLocS, localTij,
352         O                            afy, myThid )
353        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN        ELSEIF (advectionScheme.EQ.ENUM_DST3 ) THEN
354         CALL GAD_DST3_ADV_Y(          CALL GAD_DST3_ADV_Y(      bi,bj,k, deltaTtracer,
355       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)       I                            vTrans, vVel, maskLocS, localTij,
356         O                            afy, myThid )
357        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN        ELSEIF (advectionScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
358         CALL GAD_DST3FL_ADV_Y(          CALL GAD_DST3FL_ADV_Y(    bi,bj,k, deltaTtracer,
359       &       bi,bj,k,deltaTtracer,vTrans,vVel,localTij,af,myThid)       I                            vTrans, vVel, maskLocS, localTij,
360         O                            afy, myThid )
361        ELSE        ELSE
362         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'         STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
363        ENDIF        ENDIF
# Line 493  CADJ &     comlev1_bibj_k_gad_pass, key= Line 367  CADJ &     comlev1_bibj_k_gad_pass, key=
367          localTij(i,j)=localTij(i,j)-deltaTtracer*          localTij(i,j)=localTij(i,j)-deltaTtracer*
368       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)       &    _recip_hFacC(i,j,k,bi,bj)*recip_drF(k)
369       &    *recip_rA(i,j,bi,bj)       &    *recip_rA(i,j,bi,bj)
370       &    *( af(i,j+1)-af(i,j)       &    *( afy(i,j+1)-afy(i,j)
371       &      -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))       &      -tracer(i,j,k,bi,bj)*(vTrans(i,j+1)-vTrans(i,j))
372       &     )       &     )
373         ENDDO         ENDDO
# Line 533  C-    horizontal advection done; store i Line 407  C-    horizontal advection done; store i
407         ENDDO         ENDDO
408        ENDIF        ENDIF
409    
410    #ifdef ALLOW_DEBUG
411          IF ( debugLevel .GE. debLevB
412         &   .AND. k.EQ.3 .AND. myIter.EQ.1+nIter0
413         &   .AND. nPx.EQ.1 .AND. nPy.EQ.1
414         &   .AND. useCubedSphereExchange ) THEN
415            CALL DEBUG_CS_CORNER_UV( ' afx,afy from GAD_ADVECTION',
416         &             afx,afy, k, standardMessageUnit,bi,bj,myThid )
417          ENDIF
418    #endif /* ALLOW_DEBUG */
419    
420  C--   End of K loop for horizontal fluxes  C--   End of K loop for horizontal fluxes
421        ENDDO        ENDDO
422    
423    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
424    
425        IF ( .NOT.implicitAdvection ) THEN        IF ( .NOT.implicitAdvection ) THEN
426  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
427         DO k=Nr,1,-1         DO k=Nr,1,-1
# Line 566  C- Surface interface : Line 452  C- Surface interface :
452             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
453             rTrans(i,j) = 0.             rTrans(i,j) = 0.
454             fVerT(i,j,kUp) = 0.             fVerT(i,j,kUp) = 0.
            af(i,j) = 0.  
455            ENDDO            ENDDO
456           ENDDO           ENDDO
457    
# Line 578  C- Interior interface : Line 463  C- Interior interface :
463             rTransKp1(i,j) = kp1Msk*rTrans(i,j)             rTransKp1(i,j) = kp1Msk*rTrans(i,j)
464             rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)             rTrans(i,j) = wVel(i,j,k,bi,bj)*rA(i,j,bi,bj)
465       &                 *maskC(i,j,k-1,bi,bj)       &                 *maskC(i,j,k-1,bi,bj)
466             af(i,j) = 0.             fVerT(i,j,kUp) = 0.
467            ENDDO            ENDDO
468           ENDDO           ENDDO
469    
# Line 598  CADJ &     = comlev1_bibj_k_gad, key=kke Line 483  CADJ &     = comlev1_bibj_k_gad, key=kke
483    
484  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
485           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN           IF (vertAdvecScheme.EQ.ENUM_FLUX_LIMIT) THEN
486            CALL GAD_FLUXLIMIT_ADV_R(  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
487       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)             CALL GAD_FLUXLIMIT_ADV_R( bi,bj,k, deltaTtracer,
488         I                               rTrans, wVel, localTijk,
489         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
490           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3 ) THEN
491            CALL GAD_DST3_ADV_R(             CALL GAD_DST3_ADV_R(      bi,bj,k, deltaTtracer,
492       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       I                               rTrans, wVel, localTijk,
493         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
494           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN           ELSEIF (vertAdvecScheme.EQ.ENUM_DST3_FLUX_LIMIT ) THEN
495            CALL GAD_DST3FL_ADV_R(             CALL GAD_DST3FL_ADV_R(    bi,bj,k, deltaTtracer,
496       &        bi,bj,k,deltaTtracer,rTrans,wVel,localTijk,af,myThid)       I                               rTrans, wVel, localTijk,
497         O                               fVerT(1-Olx,1-Oly,kUp), myThid )
498           ELSE           ELSE
499            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'            STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
500           ENDIF           ENDIF
 C-    add the advective flux to fVerT  
          DO j=1-Oly,sNy+Oly  
           DO i=1-Olx,sNx+Olx  
            fVerT(i,j,kUp) = af(i,j)  
           ENDDO  
          ENDDO  
501    
502  C- end Surface/Interior if bloc  C- end Surface/Interior if bloc
503          ENDIF          ENDIF

Legend:
Removed from v.1.28  
changed lines
  Added in v.1.29

  ViewVC Help
Powered by ViewVC 1.1.22