/[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.50 by jmc, Thu Aug 16 02:16:37 2007 UTC revision 1.55 by jmc, Thu Feb 7 23:59:02 2008 UTC
# Line 87  C !LOCAL VARIABLES: ==================== Line 87  C !LOCAL VARIABLES: ====================
87  C  maskUp        :: 2-D array for mask at W points  C  maskUp        :: 2-D array for mask at W points
88  C  maskLocW      :: 2-D array for mask at West points  C  maskLocW      :: 2-D array for mask at West points
89  C  maskLocS      :: 2-D array for mask at South points  C  maskLocS      :: 2-D array for mask at South points
 C  iMin,iMax,    :: loop range for called routines  
 C  jMin,jMax     :: loop range for called routines  
90  C [iMin,iMax]Upd :: loop range to update tracer field  C [iMin,iMax]Upd :: loop range to update tracer field
91  C [jMin,jMax]Upd :: loop range to update tracer field  C [jMin,jMax]Upd :: loop range to update tracer field
92  C  i,j,k         :: loop indices  C  i,j,k         :: loop indices
# Line 112  C  calc_fluxes_X :: logical to indicate Line 110  C  calc_fluxes_X :: logical to indicate
110  C  calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir  C  calc_fluxes_Y :: logical to indicate to calculate fluxes in Y dir
111  C  interiorOnly  :: only update the interior of myTile, but not the edges  C  interiorOnly  :: only update the interior of myTile, but not the edges
112  C  overlapOnly   :: only update the edges of myTile, but not the interior  C  overlapOnly   :: only update the edges of myTile, but not the interior
113  C  nipass        :: number of passes in multi-dimensional method  C  npass         :: number of passes in multi-dimensional method
114  C  ipass         :: number of the current pass being made  C  ipass         :: number of the current pass being made
115  C  myTile        :: variables used to determine which cube face  C  myTile        :: variables used to determine which cube face
116  C  nCFace        :: owns a tile for cube grid runs using  C  nCFace        :: owns a tile for cube grid runs using
# Line 121  C [N,S,E,W]_edge :: true if N,S,E,W edge Line 119  C [N,S,E,W]_edge :: true if N,S,E,W edge
119  c     _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  c     _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
120        _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskLocW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
121        _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       INTEGER iMin,iMax,jMin,jMax  
122        INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd        INTEGER iMinUpd,iMaxUpd,jMinUpd,jMaxUpd
123        INTEGER i,j,k,kUp,kDown        INTEGER i,j,k,kUp,kDown
124        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
# Line 142  c     _RS maskUp  (1-OLx:sNx+OLx,1-OLy:s Line 139  c     _RS maskUp  (1-OLx:sNx+OLx,1-OLy:s
139        _RL kp1Msk        _RL kp1Msk
140        LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns        LOGICAL calc_fluxes_X, calc_fluxes_Y, withSigns
141        LOGICAL interiorOnly, overlapOnly        LOGICAL interiorOnly, overlapOnly
142        INTEGER nipass,ipass        INTEGER npass, ipass
143        INTEGER nCFace        INTEGER nCFace
144        LOGICAL N_edge, S_edge, E_edge, W_edge        LOGICAL N_edge, S_edge, E_edge, W_edge
145  #ifdef ALLOW_EXCH2  #ifdef ALLOW_EXCH2
# Line 156  c     _RS maskUp  (1-OLx:sNx+OLx,1-OLy:s Line 153  c     _RS maskUp  (1-OLx:sNx+OLx,1-OLy:s
153  CEOP  CEOP
154    
155  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
156            act0 = tracerIdentity - 1            act0 = tracerIdentity
157            max0 = maxpass            max0 = maxpass
158            act1 = bi - myBxLo(myThid)            act1 = bi - myBxLo(myThid)
159            max1 = myBxHi(myThid) - myBxLo(myThid) + 1            max1 = myBxHi(myThid) - myBxLo(myThid) + 1
# Line 165  CEOP Line 162  CEOP
162            act3 = myThid - 1            act3 = myThid - 1
163            max3 = nTx*nTy            max3 = nTx*nTy
164            act4 = ikey_dynamics - 1            act4 = ikey_dynamics - 1
165            igadkey = (act0 + 1)            igadkey = act0
166       &                      + act1*max0       &                      + act1*max0
167       &                      + act2*max0*max1       &                      + act2*max0*max1
168       &                      + act3*max0*max1*max2       &                      + act3*max0*max1*max2
# Line 207  C     uninitialised but inert locations. Line 204  C     uninitialised but inert locations.
204    
205  C--   Set tile-specific parameters for horizontal fluxes  C--   Set tile-specific parameters for horizontal fluxes
206        IF (useCubedSphereExchange) THEN        IF (useCubedSphereExchange) THEN
207         nipass=3         npass  = 3
208  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
209         IF ( nipass.GT.maxcube ) STOP 'maxcube needs to be = 3'         IF ( npass.GT.maxcube ) STOP 'maxcube needs to be = 3'
210  #endif  #endif
211  #ifdef ALLOW_EXCH2  #ifdef ALLOW_EXCH2
212         myTile = W2_myTileList(bi)         myTile = W2_myTileList(bi)
# Line 226  C--   Set tile-specific parameters for h Line 223  C--   Set tile-specific parameters for h
223         W_edge = .TRUE.         W_edge = .TRUE.
224  #endif  #endif
225        ELSE        ELSE
226         nipass=2         npass  = 2
227         nCFace = bi         nCFace = 0
228         N_edge = .FALSE.         N_edge = .FALSE.
229         S_edge = .FALSE.         S_edge = .FALSE.
230         E_edge = .FALSE.         E_edge = .FALSE.
231         W_edge = .FALSE.         W_edge = .FALSE.
232        ENDIF        ENDIF
233    
       iMin = 1-OLx  
       iMax = sNx+OLx  
       jMin = 1-OLy  
       jMax = sNy+OLy  
   
234  C--   Start of k loop for horizontal fluxes  C--   Start of k loop for horizontal fluxes
235        DO k=1,Nr        DO k=1,Nr
236  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
237           kkey = (igadkey-1)*Nr + k           kkey = (igadkey-1)*Nr + k
238  CADJ STORE tracer(:,:,k,bi,bj) =  CADJ STORE tracer(:,:,k,bi,bj) =
239  CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
240  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
241    
# Line 265  C--   Make local copy of tracer array an Line 257  C--   Make local copy of tracer array an
257        DO j=1-OLy,sNy+OLy        DO j=1-OLy,sNy+OLy
258         DO i=1-OLx,sNx+OLx         DO i=1-OLx,sNx+OLx
259           localTij(i,j)=tracer(i,j,k,bi,bj)           localTij(i,j)=tracer(i,j,k,bi,bj)
260           maskLocW(i,j)=maskW(i,j,k,bi,bj)           maskLocW(i,j)=_maskW(i,j,k,bi,bj)
261           maskLocS(i,j)=maskS(i,j,k,bi,bj)           maskLocS(i,j)=_maskS(i,j,k,bi,bj)
262         ENDDO         ENDDO
263        ENDDO        ENDDO
264    
# Line 280  cph-exch2#endif Line 272  cph-exch2#endif
272    
273  C--   Multiple passes for different directions on different tiles  C--   Multiple passes for different directions on different tiles
274  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.
275        DO ipass=1,nipass        DO ipass=1,npass
276  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
277           passkey = ipass + (k-1)      *maxcube           passkey = ipass
278       &                   + (igadkey-1)*maxcube*Nr       &                   + (k-1)      *maxpass
279           IF (nipass .GT. maxpass) THEN       &                   + (igadkey-1)*maxpass*Nr
280            STOP 'GAD_ADVECTION: nipass > maxcube. check tamc.h'           IF (npass .GT. maxpass) THEN
281              STOP 'GAD_ADVECTION: npass > maxcube. check tamc.h'
282           ENDIF           ENDIF
283  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
284    
# Line 309  C-    CubedSphere : pass 3 times, with p Line 302  C-    CubedSphere : pass 3 times, with p
302          calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5          calc_fluxes_Y = nCFace.EQ.3 .OR. nCFace.EQ.4 .OR. nCFace.EQ.5
303         ELSEIF (ipass.EQ.2) THEN         ELSEIF (ipass.EQ.2) THEN
304          overlapOnly  = MOD(nCFace,3).EQ.2          overlapOnly  = MOD(nCFace,3).EQ.2
305            interiorOnly = MOD(nCFace,3).EQ.1
306          calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4          calc_fluxes_X = nCFace.EQ.2 .OR. nCFace.EQ.3 .OR. nCFace.EQ.4
307          calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1          calc_fluxes_Y = nCFace.EQ.5 .OR. nCFace.EQ.6 .OR. nCFace.EQ.1
308  #endif /* MULTIDIM_OLD_VERSION */  #endif /* MULTIDIM_OLD_VERSION */
309         ELSE         ELSE
310            interiorOnly = .TRUE.
311          calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6          calc_fluxes_X = nCFace.EQ.5 .OR. nCFace.EQ.6
312          calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3          calc_fluxes_Y = nCFace.EQ.2 .OR. nCFace.EQ.3
313         ENDIF         ENDIF
# Line 333  C-     Advective flux in X Line 328  C-     Advective flux in X
328  C  C
329  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
330  # ifndef DISABLE_MULTIDIM_ADVECTION  # ifndef DISABLE_MULTIDIM_ADVECTION
331  CADJ STORE localTij(:,:)  =  CADJ STORE localTij(:,:)  =
332  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
333  CADJ STORE af(:,:)  =  CADJ STORE af(:,:)  =
334  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
335  # endif  # endif
336  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
# Line 347  C       a) needed in overlap only Line 342  C       a) needed in overlap only
342  C   and b) the overlap of myTile are not cube-face Edges  C   and b) the overlap of myTile are not cube-face Edges
343         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN         IF ( .NOT.overlapOnly .OR. N_edge .OR. S_edge ) THEN
344    
 cph-exch2#ifndef ALLOW_AUTODIFF_TAMC  
345  C-     Internal exchange for calculations in X  C-     Internal exchange for calculations in X
346  #ifdef MULTIDIM_OLD_VERSION  #ifdef MULTIDIM_OLD_VERSION
347          IF ( useCubedSphereExchange ) THEN          IF ( useCubedSphereExchange ) THEN
348  #else  #else
349          IF ( useCubedSphereExchange .AND.          IF ( overlapOnly ) THEN
      &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN  
350  #endif  #endif
351           CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,           CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,
352       &                              localTij, bi,bj, myThid )       &                              localTij, bi,bj, myThid )
353          ENDIF          ENDIF
 cph-exch2#endif  
354    
355  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
356  # ifndef DISABLE_MULTIDIM_ADVECTION  # ifndef DISABLE_MULTIDIM_ADVECTION
357  CADJ STORE localTij(:,:)  =  CADJ STORE localTij(:,:)  =
358  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
359  # endif  # endif
360  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
# Line 394  CADJ &     comlev1_bibj_k_gad_pass, key= Line 386  CADJ &     comlev1_bibj_k_gad_pass, key=
386           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with multi-dim'
387          ENDIF          ENDIF
388    
 C-     Advective flux in X : done  
        ENDIF  
   
 cph-exch2#ifndef ALLOW_AUTODIFF_TAMC  
389  C-     Internal exchange for next calculations in Y  C-     Internal exchange for next calculations in Y
390         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN          IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
391           CALL FILL_CS_CORNER_TR_RL(.FALSE., .FALSE.,           CALL FILL_CS_CORNER_TR_RL( .FALSE., .FALSE.,
392       &                              localTij, bi,bj, myThid )       &                              localTij, bi,bj, myThid )
393            ENDIF
394    
395    C-     Advective flux in X : done
396         ENDIF         ENDIF
 cph-exch2#endif  
397    
398  C-     Update the local tracer field where needed:  C-     Update the local tracer field where needed:
399    
# Line 501  C-     Advective flux in Y Line 491  C-     Advective flux in Y
491  C  C
492  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
493  # ifndef DISABLE_MULTIDIM_ADVECTION  # ifndef DISABLE_MULTIDIM_ADVECTION
494  CADJ STORE localTij(:,:)  =  CADJ STORE localTij(:,:)  =
495  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
496  CADJ STORE af(:,:)  =  CADJ STORE af(:,:)  =
497  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
498  # endif  # endif
499  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
# Line 515  C       a) needed in overlap only Line 505  C       a) needed in overlap only
505  C   and b) the overlap of myTile are not cube-face edges  C   and b) the overlap of myTile are not cube-face edges
506         IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN         IF ( .NOT.overlapOnly .OR. E_edge .OR. W_edge ) THEN
507    
 cph-exch2#ifndef ALLOW_AUTODIFF_TAMC  
508  C-     Internal exchange for calculations in Y  C-     Internal exchange for calculations in Y
509  #ifdef MULTIDIM_OLD_VERSION  #ifdef MULTIDIM_OLD_VERSION
510          IF ( useCubedSphereExchange ) THEN          IF ( useCubedSphereExchange ) THEN
511  #else  #else
512          IF ( useCubedSphereExchange .AND.          IF ( overlapOnly ) THEN
      &       ( overlapOnly .OR. ipass.EQ.1 ) ) THEN  
513  #endif  #endif
514           CALL FILL_CS_CORNER_TR_RL(.FALSE., .FALSE.,           CALL FILL_CS_CORNER_TR_RL( .FALSE., .FALSE.,
515       &                              localTij, bi,bj, myThid )       &                              localTij, bi,bj, myThid )
516          ENDIF          ENDIF
 cph-exch2#endif  
517    
518  C-     Advective flux in Y  C-     Advective flux in Y
519          DO j=1-Oly,sNy+Oly          DO j=1-Oly,sNy+Oly
# Line 535  C-     Advective flux in Y Line 522  C-     Advective flux in Y
522           ENDDO           ENDDO
523          ENDDO          ENDDO
524    
525  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
526  #ifndef DISABLE_MULTIDIM_ADVECTION  #ifndef DISABLE_MULTIDIM_ADVECTION
527  CADJ STORE localTij(:,:)  =  CADJ STORE localTij(:,:)  =
528  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte  CADJ &     comlev1_bibj_k_gad_pass, key=passkey, byte=isbyte
529  #endif  #endif
530  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
# Line 569  CADJ &     comlev1_bibj_k_gad_pass, key= Line 556  CADJ &     comlev1_bibj_k_gad_pass, key=
556           STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'           STOP 'GAD_ADVECTION: adv. scheme incompatibale with mutli-dim'
557          ENDIF          ENDIF
558    
 C-     Advective flux in Y : done  
        ENDIF  
   
 cph-exch2#ifndef ALLOW_AUTODIFF_TAMC  
559  C-     Internal exchange for next calculations in X  C-     Internal exchange for next calculations in X
560         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN         IF ( overlapOnly .AND. ipass.EQ.1 ) THEN
561           CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,           CALL FILL_CS_CORNER_TR_RL( .TRUE., .FALSE.,
562       &                              localTij, bi,bj, myThid )       &                              localTij, bi,bj, myThid )
563         ENDIF         ENDIF
564  cph-exch2#endif  
565    C-     Advective flux in Y : done
566           ENDIF
567    
568  C-     Update the local tracer field where needed:  C-     Update the local tracer field where needed:
569    
# Line 712  C---+----1----+----2----+----3----+----4 Line 697  C---+----1----+----2----+----3----+----4
697        IF ( .NOT.implicitAdvection ) THEN        IF ( .NOT.implicitAdvection ) THEN
698  C--   Start of k loop for vertical flux  C--   Start of k loop for vertical flux
699         DO k=Nr,1,-1         DO k=Nr,1,-1
700  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
701           kkey = (igadkey-1)*Nr + k           kkey = (igadkey-1)*Nr + (Nr-k+1)
702  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
703  C--   kUp    Cycles through 1,2 to point to w-layer above  C--   kUp    Cycles through 1,2 to point to w-layer above
704  C--   kDown  Cycles through 2,1 to point to w-layer below  C--   kDown  Cycles through 2,1 to point to w-layer below
# Line 723  c       kp1=min(Nr,k+1) Line 708  c       kp1=min(Nr,k+1)
708          kp1Msk=1.          kp1Msk=1.
709          if (k.EQ.Nr) kp1Msk=0.          if (k.EQ.Nr) kp1Msk=0.
710    
711    #ifdef ALLOW_AUTODIFF_TAMC
712    CADJ STORE rtrans(:,:)  =
713    CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
714    cphCADJ STORE wfld(:,:)  =
715    cphCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
716    #endif
717    
718  C-- Compute Vertical transport  C-- Compute Vertical transport
719  #ifdef ALLOW_AIM  #ifdef ALLOW_AIM
720  C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr  C- a hack to prevent Water-Vapor vert.transport into the stratospheric level Nr
# Line 733  C- a hack to prevent Water-Vapor vert.tr Line 725  C- a hack to prevent Water-Vapor vert.tr
725          IF ( k.EQ.1 ) THEN          IF ( k.EQ.1 ) THEN
726  #endif  #endif
727    
728  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
729  CADJ STORE rtrans(:,:)  =  cphmultiCADJ STORE wfld(:,:)  =
730  CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
 CADJ STORE wfld(:,:)  =  
 CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte  
731  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
732    
733  C- Surface interface :  C- Surface interface :
# Line 752  C- Surface interface : Line 742  C- Surface interface :
742    
743          ELSE          ELSE
744    
745  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
746  CADJ STORE rtrans(:,:)  =  cphmultiCADJ STORE wfld(:,:)  =
747  CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte
 CADJ STORE wfld(:,:)  =  
 CADJ &     comlev1_bibj_k_gad, key=kkey, byte=isbyte  
748  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
749    
750  C- Interior interface :  C- Interior interface :
# Line 779  C--   Residual transp = Bolus transp + E Line 767  C--   Residual transp = Bolus transp + E
767       I                 k, bi, bj, myThid )       I                 k, bi, bj, myThid )
768  #endif /* ALLOW_GMREDI */  #endif /* ALLOW_GMREDI */
769    
770  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
771  CADJ STORE localTijk(:,:,k)    cphmultiCADJ STORE localTijk(:,:,k)
772  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
773  CADJ STORE rTrans(:,:)    cphmultiCADJ STORE rTrans(:,:)
774  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
775  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
776    
777  C-    Compute vertical advective flux in the interior:  C-    Compute vertical advective flux in the interior:
# Line 817  C-    Compute vertical advective flux in Line 805  C-    Compute vertical advective flux in
805  C- end Surface/Interior if bloc  C- end Surface/Interior if bloc
806          ENDIF          ENDIF
807    
808  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
809  CADJ STORE rTrans(:,:)    cphmultiCADJ STORE rTrans(:,:)
810  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
811  CADJ STORE rTranskp1(:,:)    cphmultiCADJ STORE rTranskp1(:,:)
812    cphmultiCADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
813    cph --- following storing of fVerT is critical for correct
814    cph --- gradient with multiDimAdvection
815    cph --- Without it, kDown component is not properly recomputed
816    cph --- This is a TAF bug (and no warning available)
817    CADJ STORE fVerT(:,:,:)
818  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte  CADJ &     = comlev1_bibj_k_gad, key=kkey, byte=isbyte
819  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
820    

Legend:
Removed from v.1.50  
changed lines
  Added in v.1.55

  ViewVC Help
Powered by ViewVC 1.1.22