/[MITgcm]/MITgcm/model/src/dynamics.F
ViewVC logotype

Diff of /MITgcm/model/src/dynamics.F

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

revision 1.66 by heimbach, Sun Mar 25 22:33:52 2001 UTC revision 1.121 by jmc, Sat Jul 30 22:09:38 2005 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4    #include "PACKAGES_CONFIG.h"
5  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
6    
7    CBOP
8    C     !ROUTINE: DYNAMICS
9    C     !INTERFACE:
10        SUBROUTINE DYNAMICS(myTime, myIter, myThid)        SUBROUTINE DYNAMICS(myTime, myIter, myThid)
11  C     /==========================================================\  C     !DESCRIPTION: \bv
12  C     | SUBROUTINE DYNAMICS                                      |  C     *==========================================================*
13  C     | o Controlling routine for the explicit part of the model |  C     | SUBROUTINE DYNAMICS                                      
14  C     |   dynamics.                                              |  C     | o Controlling routine for the explicit part of the model  
15  C     |==========================================================|  C     |   dynamics.                                              
16  C     | This routine evaluates the "dynamics" terms for each     |  C     *==========================================================*
17  C     | block of ocean in turn. Because the blocks of ocean have |  C     | This routine evaluates the "dynamics" terms for each      
18  C     | overlap regions they are independent of one another.     |  C     | block of ocean in turn. Because the blocks of ocean have  
19  C     | If terms involving lateral integrals are needed in this  |  C     | overlap regions they are independent of one another.      
20  C     | routine care will be needed. Similarly finite-difference |  C     | If terms involving lateral integrals are needed in this  
21  C     | operations with stencils wider than the overlap region   |  C     | routine care will be needed. Similarly finite-difference  
22  C     | require special consideration.                           |  C     | operations with stencils wider than the overlap region    
23  C     | Notes                                                    |  C     | require special consideration.                            
24  C     | =====                                                    |  C     | The algorithm...
25  C     | C*P* comments indicating place holders for which code is |  C     |
26  C     |      presently being developed.                          |  C     | "Correction Step"
27  C     \==========================================================/  C     | =================
28    C     | Here we update the horizontal velocities with the surface
29    C     | pressure such that the resulting flow is either consistent
30    C     | with the free-surface evolution or the rigid-lid:
31    C     |   U[n] = U* + dt x d/dx P
32    C     |   V[n] = V* + dt x d/dy P
33    C     |
34    C     | "Calculation of Gs"
35    C     | ===================
36    C     | This is where all the accelerations and tendencies (ie.
37    C     | physics, parameterizations etc...) are calculated
38    C     |   rho = rho ( theta[n], salt[n] )
39    C     |   b   = b(rho, theta)
40    C     |   K31 = K31 ( rho )
41    C     |   Gu[n] = Gu( u[n], v[n], wVel, b, ... )
42    C     |   Gv[n] = Gv( u[n], v[n], wVel, b, ... )
43    C     |   Gt[n] = Gt( theta[n], u[n], v[n], wVel, K31, ... )
44    C     |   Gs[n] = Gs( salt[n], u[n], v[n], wVel, K31, ... )
45    C     |
46    C     | "Time-stepping" or "Prediction"
47    C     | ================================
48    C     | The models variables are stepped forward with the appropriate
49    C     | time-stepping scheme (currently we use Adams-Bashforth II)
50    C     | - For momentum, the result is always *only* a "prediction"
51    C     | in that the flow may be divergent and will be "corrected"
52    C     | later with a surface pressure gradient.
53    C     | - Normally for tracers the result is the new field at time
54    C     | level [n+1} *BUT* in the case of implicit diffusion the result
55    C     | is also *only* a prediction.
56    C     | - We denote "predictors" with an asterisk (*).
57    C     |   U* = U[n] + dt x ( 3/2 Gu[n] - 1/2 Gu[n-1] )
58    C     |   V* = V[n] + dt x ( 3/2 Gv[n] - 1/2 Gv[n-1] )
59    C     |   theta[n+1] = theta[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
60    C     |   salt[n+1] = salt[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
61    C     | With implicit diffusion:
62    C     |   theta* = theta[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
63    C     |   salt* = salt[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
64    C     |   (1 + dt * K * d_zz) theta[n] = theta*
65    C     |   (1 + dt * K * d_zz) salt[n] = salt*
66    C     |
67    C     *==========================================================*
68    C     \ev
69    C     !USES:
70        IMPLICIT NONE        IMPLICIT NONE
   
71  C     == Global variables ===  C     == Global variables ===
72  #include "SIZE.h"  #include "SIZE.h"
73  #include "EEPARAMS.h"  #include "EEPARAMS.h"
74  #include "PARAMS.h"  #include "PARAMS.h"
75  #include "DYNVARS.h"  #include "DYNVARS.h"
76    #ifdef ALLOW_CD_CODE
77    #include "CD_CODE_VARS.h"
78    #endif
79  #include "GRID.h"  #include "GRID.h"
   
80  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
81  # include "tamc.h"  # include "tamc.h"
82  # include "tamc_keys.h"  # include "tamc_keys.h"
83  #endif /* ALLOW_AUTODIFF_TAMC */  # include "FFIELDS.h"
84    # include "EOS.h"
85  #ifdef ALLOW_KPP  # ifdef ALLOW_KPP
86  # include "KPP.h"  #  include "KPP.h"
87  #endif  # endif
88    #endif /* ALLOW_AUTODIFF_TAMC */
89  #ifdef ALLOW_TIMEAVE  
90  #include "TIMEAVE_STATV.h"  C     !CALLING SEQUENCE:
91  #endif  C     DYNAMICS()
92    C      |
93    C      |-- CALC_GRAD_PHI_SURF
94    C      |
95    C      |-- CALC_VISCOSITY
96    C      |
97    C      |-- CALC_PHI_HYD  
98    C      |
99    C      |-- MOM_FLUXFORM  
100    C      |
101    C      |-- MOM_VECINV    
102    C      |
103    C      |-- TIMESTEP      
104    C      |
105    C      |-- OBCS_APPLY_UV
106    C      |
107    C      |-- IMPLDIFF      
108    C      |
109    C      |-- OBCS_APPLY_UV
110    C      |
111    C      |-- CALL DEBUG_STATS_RL
112    
113    C     !INPUT/OUTPUT PARAMETERS:
114  C     == Routine arguments ==  C     == Routine arguments ==
115  C     myTime - Current time in simulation  C     myTime - Current time in simulation
116  C     myIter - Current iteration number in simulation  C     myIter - Current iteration number in simulation
# Line 51  C     myThid - Thread number for this in Line 119  C     myThid - Thread number for this in
119        INTEGER myIter        INTEGER myIter
120        INTEGER myThid        INTEGER myThid
121    
122    C     !LOCAL VARIABLES:
123  C     == Local variables  C     == Local variables
124  C     xA, yA                 - Per block temporaries holding face areas  C     fVer[UV]               o fVer: Vertical flux term - note fVer
125  C     uTrans, vTrans, rTrans - Per block temporaries holding flow  C                                    is "pipelined" in the vertical
126  C                              transport  C                                    so we need an fVer for each
127  C                              o uTrans: Zonal transport  C                                    variable.
128  C                              o vTrans: Meridional transport  C     phiHydC    :: hydrostatic potential anomaly at cell center
129  C                              o rTrans: Vertical transport  C                   In z coords phiHyd is the hydrostatic potential
130  C     maskC,maskUp             o maskC: land/water mask for tracer cells  C                      (=pressure/rho0) anomaly
131  C                              o maskUp: land/water mask for W points  C                   In p coords phiHyd is the geopotential height anomaly.
132  C     fVer[STUV]               o fVer: Vertical flux term - note fVer  C     phiHydF    :: hydrostatic potential anomaly at middle between 2 centers
133  C                                      is "pipelined" in the vertical  C     dPhiHydX,Y :: Gradient (X & Y directions) of hydrostatic potential anom.
134  C                                      so we need an fVer for each  C     phiSurfX,  ::  gradient of Surface potential (Pressure/rho, ocean)
135  C                                      variable.  C     phiSurfY             or geopotential (atmos) in X and Y direction
136  C     rhoK, rhoKM1   - Density at current level, and level above  C     guDissip   :: dissipation tendency (all explicit terms), u component
137  C     phiHyd         - Hydrostatic part of the potential phiHydi.  C     gvDissip   :: dissipation tendency (all explicit terms), v component
 C                      In z coords phiHydiHyd is the hydrostatic  
 C                      Potential (=pressure/rho0) anomaly  
 C                      In p coords phiHydiHyd is the geopotential  
 C                      surface height anomaly.  
 C     phiSurfX, - gradient of Surface potentiel (Pressure/rho, ocean)  
 C     phiSurfY             or geopotentiel (atmos) in X and Y direction  
 C     KappaRT,       - Total diffusion in vertical for T and S.  
 C     KappaRS          (background + spatially varying, isopycnal term).  
138  C     iMin, iMax     - Ranges and sub-block indices on which calculations  C     iMin, iMax     - Ranges and sub-block indices on which calculations
139  C     jMin, jMax       are applied.  C     jMin, jMax       are applied.
140  C     bi, bj  C     bi, bj
141  C     k, kup,        - Index for layer above and below. kup and kDown  C     k, kup,        - Index for layer above and below. kup and kDown
142  C     kDown, km1       are switched with layer to be the appropriate  C     kDown, km1       are switched with layer to be the appropriate
143  C                      index into fVerTerm.  C                      index into fVerTerm.
       _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RS maskC   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)  
       _RL fVerS   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)  
144        _RL fVerU   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerU   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
145        _RL fVerV   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerV   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
146        _RL phiHyd  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL phiHydF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
147        _RL rhokm1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL phiHydC (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
148        _RL rhok    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
149          _RL dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
150        _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
151        _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
152        _RL KappaRT (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)        _RL guDissip(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
153        _RL KappaRS (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)        _RL gvDissip(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
154        _RL KappaRU (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)        _RL KappaRU (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
155        _RL KappaRV (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)        _RL KappaRV (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
       _RL sigmaX  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
       _RL sigmaY  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
       _RL sigmaR  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
   
 C This is currently used by IVDC and Diagnostics  
       _RL ConvectCount (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
156    
157        INTEGER iMin, iMax        INTEGER iMin, iMax
158        INTEGER jMin, jMax        INTEGER jMin, jMax
159        INTEGER bi, bj        INTEGER bi, bj
160        INTEGER i, j        INTEGER i, j
161        INTEGER k, km1, kup, kDown        INTEGER k, km1, kp1, kup, kDown
162    
163    #ifdef ALLOW_DIAGNOSTICS
164          _RL tmpFac
165    #endif /* ALLOW_DIAGNOSTICS */
166    
 Cjmc : add for phiHyd output <- but not working if multi tile per CPU  
 c     CHARACTER*(MAX_LEN_MBUF) suff  
 c     LOGICAL  DIFFERENT_MULTIPLE  
 c     EXTERNAL DIFFERENT_MULTIPLE  
 Cjmc(end)  
167    
168  C---    The algorithm...  C---    The algorithm...
169  C  C
# Line 162  C         salt* = salt[n] + dt x ( 3/2 G Line 208  C         salt* = salt[n] + dt x ( 3/2 G
208  C         (1 + dt * K * d_zz) theta[n] = theta*  C         (1 + dt * K * d_zz) theta[n] = theta*
209  C         (1 + dt * K * d_zz) salt[n] = salt*  C         (1 + dt * K * d_zz) salt[n] = salt*
210  C---  C---
211    CEOP
212    
213  #ifdef ALLOW_AUTODIFF_TAMC  C-- Call to routine for calculation of
214  C--   dummy statement to end declaration part  C   Eliassen-Palm-flux-forced U-tendency,
215        ikey = 1  C   if desired:
216  #endif /* ALLOW_AUTODIFF_TAMC */  #ifdef INCLUDE_EP_FORCING_CODE
217          CALL CALC_EP_FORCING(myThid)
218  C--   Set up work arrays with valid (i.e. not NaN) values  #endif
 C     These inital values do not alter the numerical results. They  
 C     just ensure that all memory references are to valid floating  
 C     point numbers. This prevents spurious hardware signals due to  
 C     uninitialised but inert locations.  
       DO j=1-OLy,sNy+OLy  
        DO i=1-OLx,sNx+OLx  
         xA(i,j)      = 0. _d 0  
         yA(i,j)      = 0. _d 0  
         uTrans(i,j)  = 0. _d 0  
         vTrans(i,j)  = 0. _d 0  
         DO k=1,Nr  
          phiHyd(i,j,k)  = 0. _d 0  
          KappaRU(i,j,k) = 0. _d 0  
          KappaRV(i,j,k) = 0. _d 0  
          sigmaX(i,j,k) = 0. _d 0  
          sigmaY(i,j,k) = 0. _d 0  
          sigmaR(i,j,k) = 0. _d 0  
         ENDDO  
         rhoKM1 (i,j) = 0. _d 0  
         rhok   (i,j) = 0. _d 0  
         maskC  (i,j) = 0. _d 0  
         phiSurfX(i,j) = 0. _d 0  
         phiSurfY(i,j) = 0. _d 0  
        ENDDO  
       ENDDO  
   
219    
220  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
221  C--   HPF directive to help TAMC  C--   HPF directive to help TAMC
# Line 205  CHPF$ INDEPENDENT Line 226  CHPF$ INDEPENDENT
226    
227  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
228  C--    HPF directive to help TAMC  C--    HPF directive to help TAMC
229  CHPF$  INDEPENDENT, NEW (rTrans,fVerT,fVerS,fVerU,fVerV  CHPF$  INDEPENDENT, NEW (fVerU,fVerV
230  CHPF$&                  ,phiHyd,utrans,vtrans,maskc,xA,yA  CHPF$&                  ,phiHydF
231  CHPF$&                  ,KappaRT,KappaRS,KappaRU,KappaRV  CHPF$&                  ,KappaRU,KappaRV
232  CHPF$&                  )  CHPF$&                  )
233  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
234    
# Line 216  CHPF$&                  ) Line 237  CHPF$&                  )
237  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
238            act1 = bi - myBxLo(myThid)            act1 = bi - myBxLo(myThid)
239            max1 = myBxHi(myThid) - myBxLo(myThid) + 1            max1 = myBxHi(myThid) - myBxLo(myThid) + 1
   
240            act2 = bj - myByLo(myThid)            act2 = bj - myByLo(myThid)
241            max2 = myByHi(myThid) - myByLo(myThid) + 1            max2 = myByHi(myThid) - myByLo(myThid) + 1
   
242            act3 = myThid - 1            act3 = myThid - 1
243            max3 = nTx*nTy            max3 = nTx*nTy
   
244            act4 = ikey_dynamics - 1            act4 = ikey_dynamics - 1
245              idynkey = (act1 + 1) + act2*max1
           ikey = (act1 + 1) + act2*max1  
246       &                      + act3*max1*max2       &                      + act3*max1*max2
247       &                      + act4*max1*max2*max3       &                      + act4*max1*max2*max3
248  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
249    
250  C--     Set up work arrays that need valid initial values  C--   Set up work arrays with valid (i.e. not NaN) values
251          DO j=1-OLy,sNy+OLy  C     These inital values do not alter the numerical results. They
252           DO i=1-OLx,sNx+OLx  C     just ensure that all memory references are to valid floating
253            rTrans(i,j)   = 0. _d 0  C     point numbers. This prevents spurious hardware signals due to
254            fVerT (i,j,1) = 0. _d 0  C     uninitialised but inert locations.
           fVerT (i,j,2) = 0. _d 0  
           fVerS (i,j,1) = 0. _d 0  
           fVerS (i,j,2) = 0. _d 0  
           fVerU (i,j,1) = 0. _d 0  
           fVerU (i,j,2) = 0. _d 0  
           fVerV (i,j,1) = 0. _d 0  
           fVerV (i,j,2) = 0. _d 0  
          ENDDO  
         ENDDO  
255    
256          DO k=1,Nr          DO k=1,Nr
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  C This is currently also used by IVDC and Diagnostics             KappaRU(i,j,k) = 0. _d 0
260             ConvectCount(i,j,k) = 0.             KappaRV(i,j,k) = 0. _d 0
261             KappaRT(i,j,k) = 0. _d 0  #ifdef ALLOW_AUTODIFF_TAMC
262             KappaRS(i,j,k) = 0. _d 0  cph(
263    c--   need some re-initialisation here to break dependencies
264    cph)
265               gu(i,j,k,bi,bj) = 0. _d 0
266               gv(i,j,k,bi,bj) = 0. _d 0
267    #endif
268            ENDDO            ENDDO
269           ENDDO           ENDDO
270          ENDDO          ENDDO
271            DO j=1-OLy,sNy+OLy
272          iMin = 1-OLx+1           DO i=1-OLx,sNx+OLx
273          iMax = sNx+OLx            fVerU  (i,j,1) = 0. _d 0
274          jMin = 1-OLy+1            fVerU  (i,j,2) = 0. _d 0
275          jMax = sNy+OLy            fVerV  (i,j,1) = 0. _d 0
276              fVerV  (i,j,2) = 0. _d 0
277              phiHydF (i,j)  = 0. _d 0
278  #ifdef ALLOW_AUTODIFF_TAMC            phiHydC (i,j)  = 0. _d 0
279  CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte            dPhiHydX(i,j)  = 0. _d 0
280  CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte            dPhiHydY(i,j)  = 0. _d 0
281  CADJ STORE uvel(:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte            phiSurfX(i,j)  = 0. _d 0
282  CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte            phiSurfY(i,j)  = 0. _d 0
283  #endif /* ALLOW_AUTODIFF_TAMC */            guDissip(i,j)  = 0. _d 0
284              gvDissip(i,j)  = 0. _d 0
285  C--     Start of diagnostic loop           ENDDO
         DO k=Nr,1,-1  
   
 #ifdef ALLOW_AUTODIFF_TAMC  
 C? Patrick, is this formula correct now that we change the loop range?  
 C? Do we still need this?  
 cph kkey formula corrected.  
 cph Needed for rhok, rhokm1, in the case useGMREDI.  
          kkey = (ikey-1)*Nr + k  
 CADJ STORE rhokm1(:,:) = comlev1_bibj_k , key = kkey, byte = isbyte  
 CADJ STORE rhok  (:,:) = comlev1_bibj_k , key = kkey, byte = isbyte  
 #endif /* ALLOW_AUTODIFF_TAMC */  
   
 C--       Integrate continuity vertically for vertical velocity  
           CALL INTEGRATE_FOR_W(  
      I                         bi, bj, k, uVel, vVel,  
      O                         wVel,  
      I                         myThid )  
   
 #ifdef    ALLOW_OBCS  
 #ifdef    ALLOW_NONHYDROSTATIC  
 C--       Apply OBC to W if in N-H mode  
           IF (useOBCS.AND.nonHydrostatic) THEN  
             CALL OBCS_APPLY_W( bi, bj, k, wVel, myThid )  
           ENDIF  
 #endif    /* ALLOW_NONHYDROSTATIC */  
 #endif    /* ALLOW_OBCS */  
   
 C--       Calculate gradients of potential density for isoneutral  
 C         slope terms (e.g. GM/Redi tensor or IVDC diffusivity)  
 c         IF ( k.GT.1 .AND. (useGMRedi.OR.ivdc_kappa.NE.0.) ) THEN  
           IF ( useGMRedi .OR. (k.GT.1 .AND. ivdc_kappa.NE.0.) ) THEN  
             CALL FIND_RHO(  
      I        bi, bj, iMin, iMax, jMin, jMax, k, k, eosType,  
      I        theta, salt,  
      O        rhoK,  
      I        myThid )  
             IF (k.GT.1) CALL FIND_RHO(  
      I        bi, bj, iMin, iMax, jMin, jMax, k-1, k, eosType,  
      I        theta, salt,  
      O        rhoKm1,  
      I        myThid )  
             CALL GRAD_SIGMA(  
      I             bi, bj, iMin, iMax, jMin, jMax, k,  
      I             rhoK, rhoKm1, rhoK,  
      O             sigmaX, sigmaY, sigmaR,  
      I             myThid )  
           ENDIF  
   
 C--       Implicit Vertical Diffusion for Convection  
 c ==> should use sigmaR !!!  
           IF (k.GT.1 .AND. ivdc_kappa.NE.0.) THEN  
             CALL CALC_IVDC(  
      I        bi, bj, iMin, iMax, jMin, jMax, k,  
      I        rhoKm1, rhoK,  
      U        ConvectCount, KappaRT, KappaRS,  
      I        myTime, myIter, myThid)  
           ENDIF  
   
 C--     end of diagnostic k loop (Nr:1)  
286          ENDDO          ENDDO
287    
288  #ifdef  ALLOW_OBCS  C--     Start computation of dynamics
289  C--     Calculate future values on open boundaries          iMin = 0
290          IF (useOBCS) THEN          iMax = sNx+1
291            CALL OBCS_CALC( bi, bj, myTime+deltaT,          jMin = 0
292       I            uVel, vVel, wVel, theta, salt,          jMax = sNy+1
      I            myThid )  
         ENDIF  
 #endif  /* ALLOW_OBCS */  
293    
 C--     Determines forcing terms based on external fields  
 C       relaxation terms, etc.  
         CALL EXTERNAL_FORCING_SURF(  
      I             bi, bj, iMin, iMax, jMin, jMax,  
      I             myThid )  
   
 #ifdef  ALLOW_GMREDI  
 C--     Calculate iso-neutral slopes for the GM/Redi parameterisation  
         IF (useGMRedi) THEN  
           DO k=1,Nr  
             CALL GMREDI_CALC_TENSOR(  
      I             bi, bj, iMin, iMax, jMin, jMax, k,  
      I             sigmaX, sigmaY, sigmaR,  
      I             myThid )  
           ENDDO  
294  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
295          ELSE  CADJ STORE wvel (:,:,:,bi,bj) =
296            DO k=1, Nr  CADJ &     comlev1_bibj, key = idynkey, byte = isbyte
             CALL GMREDI_CALC_TENSOR_DUMMY(  
      I             bi, bj, iMin, iMax, jMin, jMax, k,  
      I             sigmaX, sigmaY, sigmaR,  
      I             myThid )  
           ENDDO  
297  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
         ENDIF  
 #endif  /* ALLOW_GMREDI */  
298    
299  #ifdef  ALLOW_KPP  C--     Explicit part of the Surface Potentiel Gradient (add in TIMESTEP)
300  C--     Compute KPP mixing coefficients  C       (note: this loop will be replaced by CALL CALC_GRAD_ETA)
301          IF (useKPP) THEN          IF (implicSurfPress.NE.1.) THEN
302            CALL KPP_CALC(            CALL CALC_GRAD_PHI_SURF(
303       I                  bi, bj, myTime, myThid )       I         bi,bj,iMin,iMax,jMin,jMax,
304  #ifdef ALLOW_AUTODIFF_TAMC       I         etaN,
305          ELSE       O         phiSurfX,phiSurfY,
306            DO j=1-OLy,sNy+OLy       I         myThid )                        
             DO i=1-OLx,sNx+OLx  
               KPPhbl (i,j,bi,bj) = 1.0  
               KPPfrac(i,j,bi,bj) = 0.0  
               DO k = 1,Nr  
                  KPPghat   (i,j,k,bi,bj) = 0.0  
                  KPPviscAz (i,j,k,bi,bj) = viscAz  
                  KPPdiffKzT(i,j,k,bi,bj) = diffKzT  
                  KPPdiffKzS(i,j,k,bi,bj) = diffKzS  
               ENDDO  
             ENDDO  
           ENDDO  
 #endif /* ALLOW_AUTODIFF_TAMC */  
307          ENDIF          ENDIF
308    
309  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
310  CADJ STORE KPPghat   (:,:,:,bi,bj)  CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key=idynkey, byte=isbyte
311  CADJ &   , KPPviscAz (:,:,:,bi,bj)  CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key=idynkey, byte=isbyte
312  CADJ &   , KPPdiffKzT(:,:,:,bi,bj)  #ifdef ALLOW_KPP
313  CADJ &   , KPPdiffKzS(:,:,:,bi,bj)  CADJ STORE KPPviscAz (:,:,:,bi,bj)
314  CADJ &   , KPPfrac   (:,:  ,bi,bj)  CADJ &                 = comlev1_bibj, key=idynkey, byte=isbyte
315  CADJ &                 = comlev1_bibj, key=ikey, byte=isbyte  #endif /* ALLOW_KPP */
 #endif /* ALLOW_AUTODIFF_TAMC */  
   
 #endif  /* ALLOW_KPP */  
   
 #ifdef ALLOW_AUTODIFF_TAMC  
 CADJ STORE KappaRT(:,:,:)     = comlev1_bibj, key = ikey, byte = isbyte  
 CADJ STORE KappaRS(:,:,:)     = comlev1_bibj, key = ikey, byte = isbyte  
 CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  
 CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  
 CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  
 CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  
 #endif /* ALLOW_AUTODIFF_TAMC */  
   
 #ifdef ALLOW_AIM  
 C       AIM - atmospheric intermediate model, physics package code.  
 C note(jmc) : phiHyd=0 at this point but is not really used in Molteni Physics  
         IF ( useAIM ) THEN  
          CALL TIMER_START('AIM_DO_ATMOS_PHYS      [DYNAMICS]', myThid)  
          CALL AIM_DO_ATMOS_PHYSICS( phiHyd, myTime, myThid )  
          CALL TIMER_STOP ('AIM_DO_ATMOS_PHYS      [DYNAMICS]', myThid)  
         ENDIF  
 #endif /* ALLOW_AIM */  
   
   
 C--     Start of thermodynamics loop  
         DO k=Nr,1,-1  
   
 C--       km1    Points to level above k (=k-1)  
 C--       kup    Cycles through 1,2 to point to layer above  
 C--       kDown  Cycles through 2,1 to point to current layer  
   
           km1  = MAX(1,k-1)  
           kup  = 1+MOD(k+1,2)  
           kDown= 1+MOD(k,2)  
   
           iMin = 1-OLx+2  
           iMax = sNx+OLx-1  
           jMin = 1-OLy+2  
           jMax = sNy+OLy-1  
   
 #ifdef ALLOW_AUTODIFF_TAMC  
 C? Patrick Is this formula correct?  
 cph Yes, but I rewrote it.  
 cph Also, the KappaR? need the index k!  
          kkey = (ikey-1)*Nr + k  
 CADJ STORE KappaRT(:,:,k)    = comlev1_bibj_k, key = kkey, byte = isbyte  
 CADJ STORE KappaRS(:,:,k)    = comlev1_bibj_k, key = kkey, byte = isbyte  
316  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
317    
 C--      Get temporary terms used by tendency routines  
          CALL CALC_COMMON_FACTORS (  
      I        bi,bj,iMin,iMax,jMin,jMax,k,km1,kup,kDown,  
      O        xA,yA,uTrans,vTrans,rTrans,maskC,maskUp,  
      I        myThid)  
   
318  #ifdef  INCLUDE_CALC_DIFFUSIVITY_CALL  #ifdef  INCLUDE_CALC_DIFFUSIVITY_CALL
319  C--      Calculate the total vertical diffusivity  C--      Calculate the total vertical diffusivity
320           CALL CALC_DIFFUSIVITY(          DO k=1,Nr
321             CALL CALC_VISCOSITY(
322       I        bi,bj,iMin,iMax,jMin,jMax,k,       I        bi,bj,iMin,iMax,jMin,jMax,k,
323       I        maskC,maskup,       O        KappaRU,KappaRV,
      O        KappaRT,KappaRS,KappaRU,KappaRV,  
324       I        myThid)       I        myThid)
325           ENDDO
326  #endif  #endif
327    
 C--      Calculate active tracer tendencies (gT,gS,...)  
 C        and step forward storing result in gTnm1, gSnm1, etc.  
          IF ( tempStepping ) THEN  
            CALL CALC_GT(  
      I         bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,  
      I         xA,yA,uTrans,vTrans,rTrans,maskUp,maskC,  
      I         KappaRT,  
      U         fVerT,  
      I         myTime, myThid)  
            CALL TIMESTEP_TRACER(  
      I         bi,bj,iMin,iMax,jMin,jMax,k,  
      I         theta, gT,  
      U         gTnm1,  
      I         myIter, myThid)  
          ENDIF  
          IF ( saltStepping ) THEN  
            CALL CALC_GS(  
      I         bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,  
      I         xA,yA,uTrans,vTrans,rTrans,maskUp,maskC,  
      I         KappaRS,  
      U         fVerS,  
      I         myTime, myThid)  
            CALL TIMESTEP_TRACER(  
      I         bi,bj,iMin,iMax,jMin,jMax,k,  
      I         salt, gS,  
      U         gSnm1,  
      I         myIter, myThid)  
          ENDIF  
   
 #ifdef   ALLOW_OBCS  
 C--      Apply open boundary conditions  
          IF (useOBCS) THEN  
            CALL OBCS_APPLY_TS( bi, bj, k, gTnm1, gSnm1, myThid )  
          END IF  
 #endif   /* ALLOW_OBCS */  
   
 C--      Freeze water  
          IF (allowFreezing) THEN  
328  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
329  CADJ STORE gTNm1(:,:,k,bi,bj) = comlev1_bibj_k  CADJ STORE KappaRU(:,:,:)
330  CADJ &   , key = kkey, byte = isbyte  CADJ &                 = comlev1_bibj, key=idynkey, byte=isbyte
331    CADJ STORE KappaRV(:,:,:)
332    CADJ &                 = comlev1_bibj, key=idynkey, byte=isbyte
333  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
             CALL FREEZE( bi, bj, iMin, iMax, jMin, jMax, k, myThid )  
          END IF  
   
 C--     end of thermodynamic k loop (Nr:1)  
         ENDDO  
   
   
 #ifdef ALLOW_AUTODIFF_TAMC  
 C? Patrick? What about this one?  
 cph Keys iikey and idkey don't seem to be needed  
 cph since storing occurs on different tape for each  
 cph impldiff call anyways.  
 cph Thus, common block comlev1_impl isn't needed either.  
 cph Storing below needed in the case useGMREDI.  
         iikey = (ikey-1)*maximpl  
 #endif /* ALLOW_AUTODIFF_TAMC */  
   
 C--     Implicit diffusion  
         IF (implicitDiffusion) THEN  
   
          IF (tempStepping) THEN  
 #ifdef ALLOW_AUTODIFF_TAMC  
             idkey = iikey + 1  
 CADJ STORE gTNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte  
 #endif /* ALLOW_AUTODIFF_TAMC */  
             CALL IMPLDIFF(  
      I         bi, bj, iMin, iMax, jMin, jMax,  
      I         deltaTtracer, KappaRT, recip_HFacC,  
      U         gTNm1,  
      I         myThid )  
          ENDIF  
   
          IF (saltStepping) THEN  
 #ifdef ALLOW_AUTODIFF_TAMC  
          idkey = iikey + 2  
 CADJ STORE gSNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte  
 #endif /* ALLOW_AUTODIFF_TAMC */  
             CALL IMPLDIFF(  
      I         bi, bj, iMin, iMax, jMin, jMax,  
      I         deltaTtracer, KappaRS, recip_HFacC,  
      U         gSNm1,  
      I         myThid )  
          ENDIF  
   
 #ifdef   ALLOW_OBCS  
 C--      Apply open boundary conditions  
          IF (useOBCS) THEN  
            DO K=1,Nr  
              CALL OBCS_APPLY_TS( bi, bj, k, gTnm1, gSnm1, myThid )  
            ENDDO  
          END IF  
 #endif   /* ALLOW_OBCS */  
   
 C--     End If implicitDiffusion  
         ENDIF  
   
 C--     Start computation of dynamics  
         iMin = 1-OLx+2  
         iMax = sNx+OLx-1  
         jMin = 1-OLy+2  
         jMax = sNy+OLy-1  
   
 C--     Explicit part of the Surface Potentiel Gradient (add in TIMESTEP)  
 C       (note: this loop will be replaced by CALL CALC_GRAD_ETA)  
         IF (implicSurfPress.NE.1.) THEN  
           CALL CALC_GRAD_PHI_SURF(  
      I         bi,bj,iMin,iMax,jMin,jMax,  
      I         etaN,  
      O         phiSurfX,phiSurfY,  
      I         myThid )                          
         ENDIF  
334    
335  C--     Start of dynamics loop  C--     Start of dynamics loop
336          DO k=1,Nr          DO k=1,Nr
# Line 582  C--       kup    Cycles through 1,2 to p Line 340  C--       kup    Cycles through 1,2 to p
340  C--       kDown  Cycles through 2,1 to point to current layer  C--       kDown  Cycles through 2,1 to point to current layer
341    
342            km1  = MAX(1,k-1)            km1  = MAX(1,k-1)
343              kp1  = MIN(k+1,Nr)
344            kup  = 1+MOD(k+1,2)            kup  = 1+MOD(k+1,2)
345            kDown= 1+MOD(k,2)            kDown= 1+MOD(k,2)
346    
347    #ifdef ALLOW_AUTODIFF_TAMC
348             kkey = (idynkey-1)*Nr + k
349    c
350    CADJ STORE totphihyd (:,:,k,bi,bj)
351    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
352    CADJ STORE theta (:,:,k,bi,bj)
353    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
354    CADJ STORE salt  (:,:,k,bi,bj)
355    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
356    #endif /* ALLOW_AUTODIFF_TAMC */
357    
358  C--      Integrate hydrostatic balance for phiHyd with BC of  C--      Integrate hydrostatic balance for phiHyd with BC of
359  C        phiHyd(z=0)=0  C        phiHyd(z=0)=0
360  C        distinguishe between Stagger and Non Stagger time stepping           CALL CALC_PHI_HYD(
          IF (staggerTimeStep) THEN  
            CALL CALC_PHI_HYD(  
      I        bi,bj,iMin,iMax,jMin,jMax,k,  
      I        gTnm1, gSnm1,  
      U        phiHyd,  
      I        myThid )  
          ELSE  
            CALL CALC_PHI_HYD(  
361       I        bi,bj,iMin,iMax,jMin,jMax,k,       I        bi,bj,iMin,iMax,jMin,jMax,k,
362       I        theta, salt,       I        theta, salt,
363       U        phiHyd,       U        phiHydF,
364       I        myThid )       O        phiHydC, dPhiHydX, dPhiHydY,
365           ENDIF       I        myTime, myIter, myThid )
366    
367  C--      Calculate accelerations in the momentum equations (gU, gV, ...)  C--      Calculate accelerations in the momentum equations (gU, gV, ...)
368  C        and step forward storing the result in gUnm1, gVnm1, etc...  C        and step forward storing the result in gU, gV, etc...
369           IF ( momStepping ) THEN           IF ( momStepping ) THEN
370             CALL CALC_MOM_RHS(  #ifdef ALLOW_MOM_FLUXFORM
371               IF (.NOT. vectorInvariantMomentum) CALL MOM_FLUXFORM(
372         I         bi,bj,iMin,iMax,jMin,jMax,k,kup,kDown,
373         I         KappaRU, KappaRV,
374         U         fVerU, fVerV,
375         O         guDissip, gvDissip,
376         I         myTime, myIter, myThid)
377    #endif
378    #ifdef ALLOW_MOM_VECINV
379               IF (vectorInvariantMomentum) CALL MOM_VECINV(
380       I         bi,bj,iMin,iMax,jMin,jMax,k,kup,kDown,       I         bi,bj,iMin,iMax,jMin,jMax,k,kup,kDown,
381       I         phiHyd,KappaRU,KappaRV,       I         KappaRU, KappaRV,
382       U         fVerU, fVerV,       U         fVerU, fVerV,
383       I         myTime, myThid)       O         guDissip, gvDissip,
384         I         myTime, myIter, myThid)
385    #endif
386             CALL TIMESTEP(             CALL TIMESTEP(
387       I         bi,bj,iMin,iMax,jMin,jMax,k,       I         bi,bj,iMin,iMax,jMin,jMax,k,
388       I         phiHyd, phiSurfX, phiSurfY,       I         dPhiHydX,dPhiHydY, phiSurfX, phiSurfY,
389       I         myIter, myThid)       I         guDissip, gvDissip,
390         I         myTime, myIter, myThid)
391    
392  #ifdef   ALLOW_OBCS  #ifdef   ALLOW_OBCS
393  C--      Apply open boundary conditions  C--      Apply open boundary conditions
394           IF (useOBCS) THEN             IF (useOBCS) THEN
395             CALL OBCS_APPLY_UV( bi, bj, k, gUnm1, gVnm1, myThid )               CALL OBCS_APPLY_UV( bi, bj, k, gU, gV, myThid )
396           END IF             ENDIF
397  #endif   /* ALLOW_OBCS */  #endif   /* ALLOW_OBCS */
398    
 #ifdef   ALLOW_AUTODIFF_TAMC  
 #ifdef   INCLUDE_CD_CODE  
          ELSE  
            DO j=1-OLy,sNy+OLy  
              DO i=1-OLx,sNx+OLx  
                guCD(i,j,k,bi,bj) = 0.0  
                gvCD(i,j,k,bi,bj) = 0.0  
              END DO  
            END DO  
 #endif   /* INCLUDE_CD_CODE */  
 #endif   /* ALLOW_AUTODIFF_TAMC */  
399           ENDIF           ENDIF
400    
401    
402  C--     end of dynamics k loop (1:Nr)  C--     end of dynamics k loop (1:Nr)
403          ENDDO          ENDDO
404    
405    C--     Implicit Vertical advection & viscosity
406    #ifdef INCLUDE_IMPLVERTADV_CODE
407  C--     Implicit viscosity          IF ( momImplVertAdv ) THEN
408          IF (implicitViscosity.AND.momStepping) THEN            CALL MOM_U_IMPLICIT_R( kappaRU,
409         I                           bi, bj, myTime, myIter, myThid )
410              CALL MOM_V_IMPLICIT_R( kappaRV,
411         I                           bi, bj, myTime, myIter, myThid )
412            ELSEIF ( implicitViscosity ) THEN
413    #else /* INCLUDE_IMPLVERTADV_CODE */
414            IF     ( implicitViscosity ) THEN
415    #endif /* INCLUDE_IMPLVERTADV_CODE */
416  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
417            idkey = iikey + 3  CADJ STORE KappaRU(:,:,:) = comlev1_bibj , key=idynkey, byte=isbyte
418  CADJ STORE gUNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte  CADJ STORE gU(:,:,:,bi,bj) = comlev1_bibj , key=idynkey, byte=isbyte
419  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
420            CALL IMPLDIFF(            CALL IMPLDIFF(
421       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
422       I         deltaTmom, KappaRU,recip_HFacW,       I         0, KappaRU,recip_HFacW,
423       U         gUNm1,       U         gU,
424       I         myThid )       I         myThid )
425  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
426            idkey = iikey + 4  CADJ STORE KappaRV(:,:,:) = comlev1_bibj , key=idynkey, byte=isbyte
427  CADJ STORE gVNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte  CADJ STORE gV(:,:,:,bi,bj) = comlev1_bibj , key=idynkey, byte=isbyte
428  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
429            CALL IMPLDIFF(            CALL IMPLDIFF(
430       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
431       I         deltaTmom, KappaRV,recip_HFacS,       I         0, KappaRV,recip_HFacS,
432       U         gVNm1,       U         gV,
433       I         myThid )       I         myThid )
434            ENDIF
435    
436  #ifdef   ALLOW_OBCS  #ifdef   ALLOW_OBCS
437  C--      Apply open boundary conditions  C--      Apply open boundary conditions
438           IF (useOBCS) THEN          IF ( useOBCS .AND.(implicitViscosity.OR.momImplVertAdv) ) THEN
439             DO K=1,Nr             DO K=1,Nr
440               CALL OBCS_APPLY_UV( bi, bj, k, gUnm1, gVnm1, myThid )               CALL OBCS_APPLY_UV( bi, bj, k, gU, gV, myThid )
441             ENDDO             ENDDO
442           END IF          ENDIF
443  #endif   /* ALLOW_OBCS */  #endif   /* ALLOW_OBCS */
444    
445  #ifdef    INCLUDE_CD_CODE  #ifdef    ALLOW_CD_CODE
446            IF (implicitViscosity.AND.useCDscheme) THEN
447  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
448            idkey = iikey + 5  CADJ STORE vVelD(:,:,:,bi,bj) = comlev1_bibj , key=idynkey, byte=isbyte
 CADJ STORE vVelD(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte  
449  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
450            CALL IMPLDIFF(            CALL IMPLDIFF(
451       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
452       I         deltaTmom, KappaRU,recip_HFacW,       I         0, KappaRU,recip_HFacW,
453       U         vVelD,       U         vVelD,
454       I         myThid )       I         myThid )
455  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
456            idkey = iikey + 6  CADJ STORE uVelD(:,:,:,bi,bj) = comlev1_bibj , key=idynkey, byte=isbyte
 CADJ STORE uVelD(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte  
457  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
458            CALL IMPLDIFF(            CALL IMPLDIFF(
459       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
460       I         deltaTmom, KappaRV,recip_HFacS,       I         0, KappaRV,recip_HFacS,
461       U         uVelD,       U         uVelD,
462       I         myThid )       I         myThid )
 #endif    /* INCLUDE_CD_CODE */  
 C--     End If implicitViscosity.AND.momStepping  
463          ENDIF          ENDIF
464    #endif    /* ALLOW_CD_CODE */
465    C--     End implicit Vertical advection & viscosity
466    
 Cjmc : add for phiHyd output <- but not working if multi tile per CPU  
 c       IF ( DIFFERENT_MULTIPLE(dumpFreq,myTime+deltaTClock,myTime)  
 c    &  .AND. buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN  
 c         WRITE(suff,'(I10.10)') myIter+1  
 c         CALL WRITE_FLD_XYZ_RL('PH.',suff,phiHyd,myIter+1,myThid)  
 c       ENDIF  
 Cjmc(end)  
   
 #ifdef ALLOW_TIMEAVE  
         IF (taveFreq.GT.0.) THEN  
           CALL TIMEAVE_CUMULATE(phiHydtave, phiHyd, Nr,  
      I                              deltaTclock, bi, bj, myThid)  
           IF (ivdc_kappa.NE.0.) THEN  
             CALL TIMEAVE_CUMULATE(ConvectCountTave, ConvectCount, Nr,  
      I                              deltaTclock, bi, bj, myThid)  
           ENDIF  
         ENDIF  
 #endif /* ALLOW_TIMEAVE */  
   
467         ENDDO         ENDDO
468        ENDDO        ENDDO
469    
470    #ifdef ALLOW_OBCS
471          IF (useOBCS) THEN
472           CALL OBCS_PRESCRIBE_EXCHANGES(myThid)
473          ENDIF
474    #endif
475    
476    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
477    
478    Cml(
479    C     In order to compare the variance of phiHydLow of a p/z-coordinate
480    C     run with etaH of a z/p-coordinate run the drift of phiHydLow
481    C     has to be removed by something like the following subroutine:
482    C      CALL REMOVE_MEAN_RL( 1, phiHydLow, maskH, maskH, rA, drF,
483    C     &                'phiHydLow', myThid )
484    Cml)
485    
486    #ifdef ALLOW_DIAGNOSTICS
487          IF ( usediagnostics ) THEN
488    
489           CALL DIAGNOSTICS_FILL(totPhihyd,'PHIHYD  ',0,Nr,0,1,1,myThid)
490           CALL DIAGNOSTICS_FILL(phiHydLow,'PHIBOT  ',0, 1,0,1,1,myThid)
491    
492           tmpFac = 1. _d 0
493           CALL DIAGNOSTICS_SCALE_FILL(totPhihyd,tmpFac,2,
494         &                                 'PHIHYDSQ',0,Nr,0,1,1,myThid)
495    
496           CALL DIAGNOSTICS_SCALE_FILL(phiHydLow,tmpFac,2,
497         &                                 'PHIBOTSQ',0, 1,0,1,1,myThid)
498    
499          ENDIF
500    #endif /* ALLOW_DIAGNOSTICS */
501          
502    #ifdef ALLOW_DEBUG
503          If ( debugLevel .GE. debLevB ) THEN
504           CALL DEBUG_STATS_RL(1,EtaN,'EtaN (DYNAMICS)',myThid)
505           CALL DEBUG_STATS_RL(Nr,uVel,'Uvel (DYNAMICS)',myThid)
506           CALL DEBUG_STATS_RL(Nr,vVel,'Vvel (DYNAMICS)',myThid)
507           CALL DEBUG_STATS_RL(Nr,wVel,'Wvel (DYNAMICS)',myThid)
508           CALL DEBUG_STATS_RL(Nr,theta,'Theta (DYNAMICS)',myThid)
509           CALL DEBUG_STATS_RL(Nr,salt,'Salt (DYNAMICS)',myThid)
510           CALL DEBUG_STATS_RL(Nr,gU,'Gu (DYNAMICS)',myThid)
511           CALL DEBUG_STATS_RL(Nr,gV,'Gv (DYNAMICS)',myThid)
512           CALL DEBUG_STATS_RL(Nr,gT,'Gt (DYNAMICS)',myThid)
513           CALL DEBUG_STATS_RL(Nr,gS,'Gs (DYNAMICS)',myThid)
514    #ifndef ALLOW_ADAMSBASHFORTH_3
515           CALL DEBUG_STATS_RL(Nr,guNm1,'GuNm1 (DYNAMICS)',myThid)
516           CALL DEBUG_STATS_RL(Nr,gvNm1,'GvNm1 (DYNAMICS)',myThid)
517           CALL DEBUG_STATS_RL(Nr,gtNm1,'GtNm1 (DYNAMICS)',myThid)
518           CALL DEBUG_STATS_RL(Nr,gsNm1,'GsNm1 (DYNAMICS)',myThid)
519    #endif
520          ENDIF
521    #endif
522    
523        RETURN        RETURN
524        END        END

Legend:
Removed from v.1.66  
changed lines
  Added in v.1.121

  ViewVC Help
Powered by ViewVC 1.1.22