/[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.69 by adcroft, Wed Jun 6 14:55:45 2001 UTC revision 1.166 by m_bates, Sun Sep 15 14:28:31 2013 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    #ifdef ALLOW_OBCS
7    # include "OBCS_OPTIONS.h"
8    #endif
9    
10    #undef DYNAMICS_GUGV_EXCH_CHECK
11    
12    CBOP
13    C     !ROUTINE: DYNAMICS
14    C     !INTERFACE:
15        SUBROUTINE DYNAMICS(myTime, myIter, myThid)        SUBROUTINE DYNAMICS(myTime, myIter, myThid)
16  C     /==========================================================\  C     !DESCRIPTION: \bv
17  C     | SUBROUTINE DYNAMICS                                      |  C     *==========================================================*
18  C     | o Controlling routine for the explicit part of the model |  C     | SUBROUTINE DYNAMICS
19  C     |   dynamics.                                              |  C     | o Controlling routine for the explicit part of the model
20  C     |==========================================================|  C     |   dynamics.
21  C     | This routine evaluates the "dynamics" terms for each     |  C     *==========================================================*
22  C     | block of ocean in turn. Because the blocks of ocean have |  C     | This routine evaluates the "dynamics" terms for each
23  C     | overlap regions they are independent of one another.     |  C     | block of ocean in turn. Because the blocks of ocean have
24  C     | If terms involving lateral integrals are needed in this  |  C     | overlap regions they are independent of one another.
25  C     | routine care will be needed. Similarly finite-difference |  C     | If terms involving lateral integrals are needed in this
26  C     | operations with stencils wider than the overlap region   |  C     | routine care will be needed. Similarly finite-difference
27  C     | require special consideration.                           |  C     | operations with stencils wider than the overlap region
28  C     | Notes                                                    |  C     | require special consideration.
29  C     | =====                                                    |  C     | The algorithm...
30  C     | C*P* comments indicating place holders for which code is |  C     |
31  C     |      presently being developed.                          |  C     | "Correction Step"
32  C     \==========================================================/  C     | =================
33    C     | Here we update the horizontal velocities with the surface
34    C     | pressure such that the resulting flow is either consistent
35    C     | with the free-surface evolution or the rigid-lid:
36    C     |   U[n] = U* + dt x d/dx P
37    C     |   V[n] = V* + dt x d/dy P
38    C     |   W[n] = W* + dt x d/dz P  (NH mode)
39    C     |
40    C     | "Calculation of Gs"
41    C     | ===================
42    C     | This is where all the accelerations and tendencies (ie.
43    C     | physics, parameterizations etc...) are calculated
44    C     |   rho = rho ( theta[n], salt[n] )
45    C     |   b   = b(rho, theta)
46    C     |   K31 = K31 ( rho )
47    C     |   Gu[n] = Gu( u[n], v[n], wVel, b, ... )
48    C     |   Gv[n] = Gv( u[n], v[n], wVel, b, ... )
49    C     |   Gt[n] = Gt( theta[n], u[n], v[n], wVel, K31, ... )
50    C     |   Gs[n] = Gs( salt[n], u[n], v[n], wVel, K31, ... )
51    C     |
52    C     | "Time-stepping" or "Prediction"
53    C     | ================================
54    C     | The models variables are stepped forward with the appropriate
55    C     | time-stepping scheme (currently we use Adams-Bashforth II)
56    C     | - For momentum, the result is always *only* a "prediction"
57    C     | in that the flow may be divergent and will be "corrected"
58    C     | later with a surface pressure gradient.
59    C     | - Normally for tracers the result is the new field at time
60    C     | level [n+1} *BUT* in the case of implicit diffusion the result
61    C     | is also *only* a prediction.
62    C     | - We denote "predictors" with an asterisk (*).
63    C     |   U* = U[n] + dt x ( 3/2 Gu[n] - 1/2 Gu[n-1] )
64    C     |   V* = V[n] + dt x ( 3/2 Gv[n] - 1/2 Gv[n-1] )
65    C     |   theta[n+1] = theta[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
66    C     |   salt[n+1] = salt[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
67    C     | With implicit diffusion:
68    C     |   theta* = theta[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
69    C     |   salt* = salt[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )
70    C     |   (1 + dt * K * d_zz) theta[n] = theta*
71    C     |   (1 + dt * K * d_zz) salt[n] = salt*
72    C     |
73    C     *==========================================================*
74    C     \ev
75    C     !USES:
76        IMPLICIT NONE        IMPLICIT NONE
   
77  C     == Global variables ===  C     == Global variables ===
78  #include "SIZE.h"  #include "SIZE.h"
79  #include "EEPARAMS.h"  #include "EEPARAMS.h"
80  #include "PARAMS.h"  #include "PARAMS.h"
 #include "DYNVARS.h"  
81  #include "GRID.h"  #include "GRID.h"
82    #include "DYNVARS.h"
83    #ifdef ALLOW_CD_CODE
84    # include "CD_CODE_VARS.h"
85    #endif
86  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
87  # include "tamc.h"  # include "tamc.h"
88  # include "tamc_keys.h"  # include "tamc_keys.h"
89  # include "FFIELDS.h"  # include "FFIELDS.h"
90    # include "EOS.h"
91  # ifdef ALLOW_KPP  # ifdef ALLOW_KPP
92  #  include "KPP.h"  #  include "KPP.h"
93  # endif  # endif
94  # ifdef ALLOW_GMREDI  # ifdef ALLOW_PTRACERS
95  #  include "GMREDI.h"  #  include "PTRACERS_SIZE.h"
96    #  include "PTRACERS_FIELDS.h"
97    # endif
98    # ifdef ALLOW_OBCS
99    #  include "OBCS_PARAMS.h"
100    #  include "OBCS_FIELDS.h"
101    #  ifdef ALLOW_PTRACERS
102    #   include "OBCS_PTRACERS.h"
103    #  endif
104    # endif
105    # ifdef ALLOW_MOM_FLUXFORM
106    #  include "MOM_FLUXFORM.h"
107  # endif  # endif
108  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
109    
110  #ifdef ALLOW_TIMEAVE  C     !CALLING SEQUENCE:
111  #include "TIMEAVE_STATV.h"  C     DYNAMICS()
112  #endif  C      |
113    C      |-- CALC_EP_FORCING
114    C      |
115    C      |-- CALC_GRAD_PHI_SURF
116    C      |
117    C      |-- CALC_VISCOSITY
118    C      |
119    C      |-- CALC_EDDY_STRESS
120    C      |
121    C      |-- CALC_PHI_HYD
122    C      |
123    C      |-- MOM_FLUXFORM
124    C      |
125    C      |-- MOM_VECINV
126    C      |
127    C      |-- TIMESTEP
128    C      |
129    C      |-- MOM_U_IMPLICIT_R
130    C      |-- MOM_V_IMPLICIT_R
131    C      |
132    C      |-- IMPLDIFF
133    C      |
134    C      |-- OBCS_APPLY_UV
135    C      |
136    C      |-- CALC_GW
137    C      |
138    C      |-- DIAGNOSTICS_FILL
139    C      |-- DEBUG_STATS_RL
140    
141    C     !INPUT/OUTPUT PARAMETERS:
142  C     == Routine arguments ==  C     == Routine arguments ==
143  C     myTime - Current time in simulation  C     myTime :: Current time in simulation
144  C     myIter - Current iteration number in simulation  C     myIter :: Current iteration number in simulation
145  C     myThid - Thread number for this instance of the routine.  C     myThid :: Thread number for this instance of the routine.
146        _RL myTime        _RL myTime
147        INTEGER myIter        INTEGER myIter
148        INTEGER myThid        INTEGER myThid
149    
150    C     !FUNCTIONS:
151    #ifdef ALLOW_DIAGNOSTICS
152          LOGICAL  DIAGNOSTICS_IS_ON
153          EXTERNAL DIAGNOSTICS_IS_ON
154    #endif
155    
156    C     !LOCAL VARIABLES:
157  C     == Local variables  C     == Local variables
158  C     xA, yA                 - Per block temporaries holding face areas  C     fVer[UV]               o fVer: Vertical flux term - note fVer
159  C     uTrans, vTrans, rTrans - Per block temporaries holding flow  C                                    is "pipelined" in the vertical
160  C                              transport  C                                    so we need an fVer for each
161  C                              o uTrans: Zonal transport  C                                    variable.
162  C                              o vTrans: Meridional transport  C     phiHydC    :: hydrostatic potential anomaly at cell center
163  C                              o rTrans: Vertical transport  C                   In z coords phiHyd is the hydrostatic potential
164  C     maskUp                   o maskUp: land/water mask for W points  C                      (=pressure/rho0) anomaly
165  C     fVer[STUV]               o fVer: Vertical flux term - note fVer  C                   In p coords phiHyd is the geopotential height anomaly.
166  C                                      is "pipelined" in the vertical  C     phiHydF    :: hydrostatic potential anomaly at middle between 2 centers
167  C                                      so we need an fVer for each  C     dPhiHydX,Y :: Gradient (X & Y directions) of hydrostatic potential anom.
168  C                                      variable.  C     phiSurfX,  ::  gradient of Surface potential (Pressure/rho, ocean)
169  C     rhoK, rhoKM1   - Density at current level, and level above  C     phiSurfY             or geopotential (atmos) in X and Y direction
170  C     phiHyd         - Hydrostatic part of the potential phiHydi.  C     guDissip   :: dissipation tendency (all explicit terms), u component
171  C                      In z coords phiHydiHyd is the hydrostatic  C     gvDissip   :: dissipation tendency (all explicit terms), v component
172  C                      Potential (=pressure/rho0) anomaly  C     KappaRU    :: vertical viscosity for velocity U-component
173  C                      In p coords phiHydiHyd is the geopotential  C     KappaRV    :: vertical viscosity for velocity V-component
174  C                      surface height anomaly.  C     iMin, iMax :: Ranges and sub-block indices on which calculations
175  C     phiSurfX, - gradient of Surface potentiel (Pressure/rho, ocean)  C     jMin, jMax    are applied.
176  C     phiSurfY             or geopotentiel (atmos) in X and Y direction  C     bi, bj     :: tile indices
177  C     KappaRT,       - Total diffusion in vertical for T and S.  C     k          :: current level index
178  C     KappaRS          (background + spatially varying, isopycnal term).  C     km1, kp1   :: index of level above (k-1) and below (k+1)
179  C     iMin, iMax     - Ranges and sub-block indices on which calculations  C     kUp, kDown :: Index for interface above and below. kUp and kDown are
180  C     jMin, jMax       are applied.  C                   are switched with k to be the appropriate index into fVerU,V
 C     bi, bj  
 C     k, kup,        - Index for layer above and below. kup and kDown  
 C     kDown, km1       are switched with layer to be the appropriate  
 C                      index into fVerTerm.  
 C     tauAB - Adams-Bashforth timestepping weight: 0=forward ; 1/2=Adams-Bashf.  
       _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 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)  
181        _RL fVerU   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerU   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
182        _RL fVerV   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerV   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
183        _RL phiHyd  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL phiHydF (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
184        _RL rhokm1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL phiHydC (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
185        _RL rhok    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL dPhiHydX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
186          _RL dPhiHydY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
187        _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
188        _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
189        _RL KappaRT (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)        _RL guDissip(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
190        _RL KappaRS (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)        _RL gvDissip(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
191        _RL KappaRU (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)        _RL KappaRU (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
192        _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)  
       _RL tauAB  
   
 C This is currently used by IVDC and Diagnostics  
       _RL ConvectCount (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)  
193    
194        INTEGER iMin, iMax        INTEGER iMin, iMax
195        INTEGER jMin, jMax        INTEGER jMin, jMax
196        INTEGER bi, bj        INTEGER bi, bj
197        INTEGER i, j        INTEGER i, j
198        INTEGER k, km1, kup, kDown        INTEGER k, km1, kp1, kUp, kDown
199    
200    #ifdef ALLOW_DIAGNOSTICS
201          LOGICAL dPhiHydDiagIsOn
202          _RL tmpFac
203    #endif /* ALLOW_DIAGNOSTICS */
204    
 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)  
   
205  C---    The algorithm...  C---    The algorithm...
206  C  C
207  C       "Correction Step"  C       "Correction Step"
# Line 165  C         salt* = salt[n] + dt x ( 3/2 G Line 245  C         salt* = salt[n] + dt x ( 3/2 G
245  C         (1 + dt * K * d_zz) theta[n] = theta*  C         (1 + dt * K * d_zz) theta[n] = theta*
246  C         (1 + dt * K * d_zz) salt[n] = salt*  C         (1 + dt * K * d_zz) salt[n] = salt*
247  C---  C---
248    CEOP
249    
250  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_DEBUG
251  C--   dummy statement to end declaration part        IF (debugMode) CALL DEBUG_ENTER( 'DYNAMICS', myThid )
252        ikey = 1  #endif
 #endif /* ALLOW_AUTODIFF_TAMC */  
253    
254  C--   Set up work arrays with valid (i.e. not NaN) values  #ifdef ALLOW_DIAGNOSTICS
255  C     These inital values do not alter the numerical results. They        dPhiHydDiagIsOn = .FALSE.
256  C     just ensure that all memory references are to valid floating        IF ( useDiagnostics )
257  C     point numbers. This prevents spurious hardware signals due to       &  dPhiHydDiagIsOn = DIAGNOSTICS_IS_ON( 'Um_dPHdx', myThid )
258  C     uninitialised but inert locations.       &               .OR. DIAGNOSTICS_IS_ON( 'Vm_dPHdy', myThid )
259        DO j=1-OLy,sNy+OLy  #endif
260         DO i=1-OLx,sNx+OLx  
261          xA(i,j)      = 0. _d 0  C-- Call to routine for calculation of Eliassen-Palm-flux-forced
262          yA(i,j)      = 0. _d 0  C    U-tendency, if desired:
263          uTrans(i,j)  = 0. _d 0  #ifdef INCLUDE_EP_FORCING_CODE
264          vTrans(i,j)  = 0. _d 0        CALL CALC_EP_FORCING(myThid)
265          DO k=1,Nr  #endif
          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  
         phiSurfX(i,j) = 0. _d 0  
         phiSurfY(i,j) = 0. _d 0  
        ENDDO  
       ENDDO  
266    
267    #ifdef ALLOW_AUTODIFF_MONITOR_DIAG
268          CALL DUMMY_IN_DYNAMICS( myTime, myIter, myThid )
269    #endif
270    
271  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
272  C--   HPF directive to help TAMC  C--   HPF directive to help TAMC
# Line 207  CHPF$ INDEPENDENT Line 277  CHPF$ INDEPENDENT
277    
278  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
279  C--    HPF directive to help TAMC  C--    HPF directive to help TAMC
280  CHPF$  INDEPENDENT, NEW (rTrans,fVerT,fVerS,fVerU,fVerV  CHPF$  INDEPENDENT, NEW (fVerU,fVerV
281  CHPF$&                  ,phiHyd,utrans,vtrans,xA,yA  CHPF$&                  ,phiHydF
282  CHPF$&                  ,KappaRT,KappaRS,KappaRU,KappaRV  CHPF$&                  ,KappaRU,KappaRV
283  CHPF$&                  )  CHPF$&                  )
284  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
285    
# Line 218  CHPF$&                  ) Line 288  CHPF$&                  )
288  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
289            act1 = bi - myBxLo(myThid)            act1 = bi - myBxLo(myThid)
290            max1 = myBxHi(myThid) - myBxLo(myThid) + 1            max1 = myBxHi(myThid) - myBxLo(myThid) + 1
   
291            act2 = bj - myByLo(myThid)            act2 = bj - myByLo(myThid)
292            max2 = myByHi(myThid) - myByLo(myThid) + 1            max2 = myByHi(myThid) - myByLo(myThid) + 1
   
293            act3 = myThid - 1            act3 = myThid - 1
294            max3 = nTx*nTy            max3 = nTx*nTy
   
295            act4 = ikey_dynamics - 1            act4 = ikey_dynamics - 1
296              idynkey = (act1 + 1) + act2*max1
           ikey = (act1 + 1) + act2*max1  
297       &                      + act3*max1*max2       &                      + act3*max1*max2
298       &                      + act4*max1*max2*max3       &                      + act4*max1*max2*max3
299  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
300    
301  C--     Set up work arrays that need valid initial values  C--   Set up work arrays with valid (i.e. not NaN) values
302          DO j=1-OLy,sNy+OLy  C     These initial values do not alter the numerical results. They
303           DO i=1-OLx,sNx+OLx  C     just ensure that all memory references are to valid floating
304            rTrans(i,j)   = 0. _d 0  C     point numbers. This prevents spurious hardware signals due to
305            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  
306    
307    #ifdef ALLOW_AUTODIFF_TAMC
308          DO k=1,Nr          DO k=1,Nr
309           DO j=1-OLy,sNy+OLy           DO j=1-OLy,sNy+OLy
310            DO i=1-OLx,sNx+OLx            DO i=1-OLx,sNx+OLx
311  C This is currently also used by IVDC and Diagnostics  cph(
312             ConvectCount(i,j,k) = 0.  c--   need some re-initialisation here to break dependencies
313             KappaRT(i,j,k) = 0. _d 0  cph)
314             KappaRS(i,j,k) = 0. _d 0             gU(i,j,k,bi,bj) = 0. _d 0
315               gV(i,j,k,bi,bj) = 0. _d 0
316            ENDDO            ENDDO
317           ENDDO           ENDDO
318          ENDDO          ENDDO
   
         iMin = 1-OLx+1  
         iMax = sNx+OLx  
         jMin = 1-OLy+1  
         jMax = sNy+OLy  
   
   
 #ifdef ALLOW_AUTODIFF_TAMC  
 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 */  
   
 C--     Start of diagnostic loop  
         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  
 #ifdef ALLOW_AUTODIFF_TAMC  
 CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte  
 CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte  
 #endif /* ALLOW_AUTODIFF_TAMC */  
             CALL FIND_RHO(  
      I        bi, bj, iMin, iMax, jMin, jMax, k, k, eosType,  
      I        theta, salt,  
      O        rhoK,  
      I        myThid )  
             IF (k.GT.1) THEN  
 #ifdef ALLOW_AUTODIFF_TAMC  
 CADJ STORE theta(:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte  
 CADJ STORE salt (:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte  
319  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
320               CALL FIND_RHO(          DO j=1-OLy,sNy+OLy
321       I        bi, bj, iMin, iMax, jMin, jMax, k-1, k, eosType,           DO i=1-OLx,sNx+OLx
322       I        theta, salt,            fVerU  (i,j,1) = 0. _d 0
323       O        rhoKm1,            fVerU  (i,j,2) = 0. _d 0
324       I        myThid )            fVerV  (i,j,1) = 0. _d 0
325              ENDIF            fVerV  (i,j,2) = 0. _d 0
326              CALL GRAD_SIGMA(            phiHydF (i,j)  = 0. _d 0
327       I             bi, bj, iMin, iMax, jMin, jMax, k,            phiHydC (i,j)  = 0. _d 0
328       I             rhoK, rhoKm1, rhoK,  #ifndef INCLUDE_PHIHYD_CALCULATION_CODE
329       O             sigmaX, sigmaY, sigmaR,            dPhiHydX(i,j)  = 0. _d 0
330       I             myThid )            dPhiHydY(i,j)  = 0. _d 0
331            ENDIF  #endif
332              phiSurfX(i,j)  = 0. _d 0
333  C--       Implicit Vertical Diffusion for Convection            phiSurfY(i,j)  = 0. _d 0
334  c ==> should use sigmaR !!!            guDissip(i,j)  = 0. _d 0
335            IF (k.GT.1 .AND. ivdc_kappa.NE.0.) THEN            gvDissip(i,j)  = 0. _d 0
336              CALL CALC_IVDC(  #ifdef ALLOW_AUTODIFF_TAMC
337       I        bi, bj, iMin, iMax, jMin, jMax, k,            phiHydLow(i,j,bi,bj) = 0. _d 0
338       I        rhoKm1, rhoK,  # if (defined NONLIN_FRSURF) && (defined ALLOW_MOM_FLUXFORM)
339       U        ConvectCount, KappaRT, KappaRS,  #  ifndef DISABLE_RSTAR_CODE
340       I        myTime, myIter, myThid)  #   ifndef ALLOW_AUTODIFF_OPENAD
341            ENDIF            dWtransC(i,j,bi,bj) = 0. _d 0
342              dWtransU(i,j,bi,bj) = 0. _d 0
343  C--     end of diagnostic k loop (Nr:1)            dWtransV(i,j,bi,bj) = 0. _d 0
344    #   endif
345    #  endif
346    # endif
347    #endif
348             ENDDO
349          ENDDO          ENDDO
350    
351    C--     Start computation of dynamics
352            iMin = 0
353            iMax = sNx+1
354            jMin = 0
355            jMax = sNy+1
356    
357  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
358  cph avoids recomputation of integrate_for_w  CADJ STORE wVel (:,:,:,bi,bj) =
359  CADJ STORE wvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  CADJ &     comlev1_bibj, key=idynkey, byte=isbyte
360  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
361    
362  #ifdef  ALLOW_OBCS  C--     Explicit part of the Surface Potential Gradient (add in TIMESTEP)
363  C--     Calculate future values on open boundaries  C       (note: this loop will be replaced by CALL CALC_GRAD_ETA)
364          IF (useOBCS) THEN          IF (implicSurfPress.NE.1.) THEN
365            CALL OBCS_CALC( bi, bj, myTime+deltaT,            CALL CALC_GRAD_PHI_SURF(
366       I            uVel, vVel, wVel, theta, salt,       I         bi,bj,iMin,iMax,jMin,jMax,
367       I            myThid )       I         etaN,
368         O         phiSurfX,phiSurfY,
369         I         myThid )
370          ENDIF          ENDIF
 #endif  /* ALLOW_OBCS */  
   
 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_AUTODIFF_TAMC  
 cph needed for KPP  
 CADJ STORE surfacetendencyU(:,:,bi,bj)  
 CADJ &     = comlev1_bibj, key=ikey, byte=isbyte  
 CADJ STORE surfacetendencyV(:,:,bi,bj)  
 CADJ &     = comlev1_bibj, key=ikey, byte=isbyte  
 CADJ STORE surfacetendencyS(:,:,bi,bj)  
 CADJ &     = comlev1_bibj, key=ikey, byte=isbyte  
 CADJ STORE surfacetendencyT(:,:,bi,bj)  
 CADJ &     = comlev1_bibj, key=ikey, byte=isbyte  
 #endif /* ALLOW_AUTODIFF_TAMC */  
   
 #ifdef  ALLOW_GMREDI  
371    
372  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
373  CADJ STORE sigmaX(:,:,:) = comlev1, key=ikey, byte=isbyte  CADJ STORE uVel (:,:,:,bi,bj) = comlev1_bibj, key=idynkey, byte=isbyte
374  CADJ STORE sigmaY(:,:,:) = comlev1, key=ikey, byte=isbyte  CADJ STORE vVel (:,:,:,bi,bj) = comlev1_bibj, key=idynkey, byte=isbyte
375  CADJ STORE sigmaR(:,:,:) = comlev1, key=ikey, byte=isbyte  #ifdef ALLOW_KPP
376    CADJ STORE KPPviscAz (:,:,:,bi,bj)
377    CADJ &                 = comlev1_bibj, key=idynkey, byte=isbyte
378    #endif /* ALLOW_KPP */
379  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
380  C--     Calculate iso-neutral slopes for the GM/Redi parameterisation  
381          IF (useGMRedi) THEN  #if (defined INCLUDE_CALC_DIFFUSIVITY_CALL) && !(defined ALLOW_AUTODIFF)
382            IF ( .NOT.momViscosity ) THEN
383    #endif /* INCLUDE_CALC_DIFFUSIVITY_CALL and not ALLOW_AUTODIFF */
384            DO k=1,Nr            DO k=1,Nr
385              CALL GMREDI_CALC_TENSOR(             DO j=1-OLy,sNy+OLy
386       I             bi, bj, iMin, iMax, jMin, jMax, k,              DO i=1-OLx,sNx+OLx
387       I             sigmaX, sigmaY, sigmaR,               KappaRU(i,j,k) = 0. _d 0
388       I             myThid )               KappaRV(i,j,k) = 0. _d 0
389            ENDDO              ENDDO
390  #ifdef ALLOW_AUTODIFF_TAMC             ENDDO
         ELSE  
           DO k=1, Nr  
             CALL GMREDI_CALC_TENSOR_DUMMY(  
      I             bi, bj, iMin, iMax, jMin, jMax, k,  
      I             sigmaX, sigmaY, sigmaR,  
      I             myThid )  
391            ENDDO            ENDDO
392  #endif /* ALLOW_AUTODIFF_TAMC */  #ifdef INCLUDE_CALC_DIFFUSIVITY_CALL
393          ENDIF  C--     Calculate the total vertical viscosity
394    #ifdef ALLOW_AUTODIFF
395  #ifdef ALLOW_AUTODIFF_TAMC          IF ( momViscosity ) THEN
396  CADJ STORE Kwx(:,:,:,bi,bj)   = comlev1_bibj, key=ikey, byte=isbyte  #else
 CADJ STORE Kwy(:,:,:,bi,bj)   = comlev1_bibj, key=ikey, byte=isbyte  
 CADJ STORE Kwz(:,:,:,bi,bj)   = comlev1_bibj, key=ikey, byte=isbyte  
 #endif /* ALLOW_AUTODIFF_TAMC */  
   
 #endif  /* ALLOW_GMREDI */  
   
 #ifdef  ALLOW_KPP  
 C--     Compute KPP mixing coefficients  
         IF (useKPP) THEN  
           CALL KPP_CALC(  
      I                  bi, bj, myTime, myThid )  
 #ifdef ALLOW_AUTODIFF_TAMC  
397          ELSE          ELSE
398            CALL KPP_CALC_DUMMY(  #endif
399       I                  bi, bj, myTime, myThid )            CALL CALC_VISCOSITY(
400  #endif /* ALLOW_AUTODIFF_TAMC */       I            bi,bj, iMin,iMax,jMin,jMax,
401         O            KappaRU, KappaRV,
402         I            myThid )
403          ENDIF          ENDIF
404    #endif /* INCLUDE_CALC_DIFFUSIVITY_CALL */
405    
406  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
407  CADJ STORE KPPghat   (:,:,:,bi,bj)  CADJ STORE KappaRU(:,:,:)
408  CADJ &   , KPPviscAz (:,:,:,bi,bj)  CADJ &     = comlev1_bibj, key=idynkey, byte=isbyte
409  CADJ &   , KPPdiffKzT(:,:,:,bi,bj)  CADJ STORE KappaRV(:,:,:)
410  CADJ &   , KPPdiffKzS(:,:,:,bi,bj)  CADJ &     = comlev1_bibj, key=idynkey, byte=isbyte
411  CADJ &   , KPPfrac   (:,:  ,bi,bj)  #endif /* ALLOW_AUTODIFF_TAMC */
412  CADJ &                 = comlev1_bibj, key=ikey, byte=isbyte  
413  #endif /* ALLOW_AUTODIFF_TAMC */  #ifdef ALLOW_OBCS
414    C--   For Stevens boundary conditions velocities need to be extrapolated
415  #endif  /* ALLOW_KPP */  C     (copied) to a narrow strip outside the domain
416            IF ( useOBCS ) THEN
417  #ifdef ALLOW_AUTODIFF_TAMC            CALL OBCS_COPY_UV_N(
418  CADJ STORE KappaRT(:,:,:)     = comlev1_bibj, key = ikey, byte = isbyte       U         uVel(1-OLx,1-OLy,1,bi,bj),
419  CADJ STORE KappaRS(:,:,:)     = comlev1_bibj, key = ikey, byte = isbyte       U         vVel(1-OLx,1-OLy,1,bi,bj),
420  CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte       I         Nr, bi, bj, myThid )
 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)  
421          ENDIF          ENDIF
422  #endif /* ALLOW_AIM */  #endif /* ALLOW_OBCS */
423    
424    #ifdef ALLOW_EDDYPSI
425            CALL CALC_EDDY_STRESS(bi,bj,myThid)
426    #endif
427    
428  C--     Start of thermodynamics loop  C--     Start of dynamics loop
429          DO k=Nr,1,-1          DO k=1,Nr
 #ifdef ALLOW_AUTODIFF_TAMC  
 C? Patrick Is this formula correct?  
 cph Yes, but I rewrote it.  
 cph Also, the KappaR? need the index and subscript k!  
          kkey = (ikey-1)*Nr + k  
 #endif /* ALLOW_AUTODIFF_TAMC */  
430    
431  C--       km1    Points to level above k (=k-1)  C--       km1    Points to level above k (=k-1)
432  C--       kup    Cycles through 1,2 to point to layer above  C--       kup    Cycles through 1,2 to point to layer above
433  C--       kDown  Cycles through 2,1 to point to current layer  C--       kDown  Cycles through 2,1 to point to current layer
434    
435            km1  = MAX(1,k-1)            km1  = MAX(1,k-1)
436              kp1  = MIN(k+1,Nr)
437            kup  = 1+MOD(k+1,2)            kup  = 1+MOD(k+1,2)
438            kDown= 1+MOD(k,2)            kDown= 1+MOD(k,2)
439    
           iMin = 1-OLx+2  
           iMax = sNx+OLx-1  
           jMin = 1-OLy+2  
           jMax = sNy+OLy-1  
   
 C--      Get temporary terms used by tendency routines  
          CALL CALC_COMMON_FACTORS (  
      I        bi,bj,iMin,iMax,jMin,jMax,k,  
      O        xA,yA,uTrans,vTrans,rTrans,maskUp,  
      I        myThid)  
   
 #ifdef ALLOW_AUTODIFF_TAMC  
 CADJ STORE KappaRT(:,:,k)    = comlev1_bibj_k, key=kkey, byte=isbyte  
 CADJ STORE KappaRS(:,:,k)    = comlev1_bibj_k, key=kkey, byte=isbyte  
 #endif /* ALLOW_AUTODIFF_TAMC */  
   
 #ifdef  INCLUDE_CALC_DIFFUSIVITY_CALL  
 C--      Calculate the total vertical diffusivity  
          CALL CALC_DIFFUSIVITY(  
      I        bi,bj,iMin,iMax,jMin,jMax,k,  
      I        maskUp,  
      O        KappaRT,KappaRS,KappaRU,KappaRV,  
      I        myThid)  
 #endif  
   
 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,  
      I         KappaRT,  
      U         fVerT,  
      I         myTime, myThid)  
            tauAB = 0.5d0 + abEps  
            CALL TIMESTEP_TRACER(  
      I         bi,bj,iMin,iMax,jMin,jMax,k,tauAB,  
      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,  
      I         KappaRS,  
      U         fVerS,  
      I         myTime, myThid)  
            tauAB = 0.5d0 + abEps  
            CALL TIMESTEP_TRACER(  
      I         bi,bj,iMin,iMax,jMin,jMax,k,tauAB,  
      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  
 #ifdef ALLOW_AUTODIFF_TAMC  
 CADJ STORE gTNm1(:,:,k,bi,bj) = comlev1_bibj_k  
 CADJ &   , key = kkey, byte = isbyte  
 #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  
440  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
441           idkey = iikey + 2           kkey = (idynkey-1)*Nr + k
442  CADJ STORE gSNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte  c
443    CADJ STORE totPhiHyd (:,:,k,bi,bj)
444    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
445    CADJ STORE phiHydLow (:,:,bi,bj)
446    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
447    CADJ STORE theta (:,:,k,bi,bj)
448    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
449    CADJ STORE salt  (:,:,k,bi,bj)
450    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
451    CADJ STORE gT(:,:,k,bi,bj)
452    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
453    CADJ STORE gS(:,:,k,bi,bj)
454    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
455    # ifdef NONLIN_FRSURF
456    cph-test
457    CADJ STORE  phiHydC (:,:)
458    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
459    CADJ STORE  phiHydF (:,:)
460    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
461    CADJ STORE  guDissip (:,:)
462    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
463    CADJ STORE  gvDissip (:,:)
464    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
465    CADJ STORE  fVerU (:,:,:)
466    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
467    CADJ STORE  fVerV (:,:,:)
468    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
469    CADJ STORE gU(:,:,k,bi,bj)
470    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
471    CADJ STORE gV(:,:,k,bi,bj)
472    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
473    #  ifndef ALLOW_ADAMSBASHFORTH_3
474    CADJ STORE guNm1(:,:,k,bi,bj)
475    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
476    CADJ STORE gvNm1(:,:,k,bi,bj)
477    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
478    #  else
479    CADJ STORE guNm(:,:,k,bi,bj,1)
480    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
481    CADJ STORE guNm(:,:,k,bi,bj,2)
482    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
483    CADJ STORE gvNm(:,:,k,bi,bj,1)
484    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
485    CADJ STORE gvNm(:,:,k,bi,bj,2)
486    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
487    #  endif
488    #  ifdef ALLOW_CD_CODE
489    CADJ STORE uNM1(:,:,k,bi,bj)
490    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
491    CADJ STORE vNM1(:,:,k,bi,bj)
492    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
493    CADJ STORE uVelD(:,:,k,bi,bj)
494    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
495    CADJ STORE vVelD(:,:,k,bi,bj)
496    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
497    #  endif
498    # endif
499    # ifdef ALLOW_DEPTH_CONTROL
500    CADJ STORE  fVerU (:,:,:)
501    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
502    CADJ STORE  fVerV (:,:,:)
503    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
504    # endif
505  #endif /* ALLOW_AUTODIFF_TAMC */  #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  
   
 C--     Start of dynamics loop  
         DO k=1,Nr  
   
 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)  
506    
507  C--      Integrate hydrostatic balance for phiHyd with BC of  C--      Integrate hydrostatic balance for phiHyd with BC of phiHyd(z=0)=0
508  C        phiHyd(z=0)=0           IF ( implicitIntGravWave ) THEN
 C        distinguishe between Stagger and Non Stagger time stepping  
          IF (staggerTimeStep) THEN  
509             CALL CALC_PHI_HYD(             CALL CALC_PHI_HYD(
510       I        bi,bj,iMin,iMax,jMin,jMax,k,       I        bi,bj,iMin,iMax,jMin,jMax,k,
511       I        gTnm1, gSnm1,       I        gT, gS,
512       U        phiHyd,       U        phiHydF,
513       I        myThid )       O        phiHydC, dPhiHydX, dPhiHydY,
514         I        myTime, myIter, myThid )
515           ELSE           ELSE
516             CALL CALC_PHI_HYD(             CALL CALC_PHI_HYD(
517       I        bi,bj,iMin,iMax,jMin,jMax,k,       I        bi,bj,iMin,iMax,jMin,jMax,k,
518       I        theta, salt,       I        theta, salt,
519       U        phiHyd,       U        phiHydF,
520       I        myThid )       O        phiHydC, dPhiHydX, dPhiHydY,
521         I        myTime, myIter, myThid )
522           ENDIF           ENDIF
523    #ifdef ALLOW_DIAGNOSTICS
524             IF ( dPhiHydDiagIsOn ) THEN
525               tmpFac = -1. _d 0
526               CALL DIAGNOSTICS_SCALE_FILL( dPhiHydX, tmpFac, 1,
527         &                           'Um_dPHdx', k, 1, 2, bi, bj, myThid )
528               CALL DIAGNOSTICS_SCALE_FILL( dPhiHydY, tmpFac, 1,
529         &                           'Vm_dPHdy', k, 1, 2, bi, bj, myThid )
530             ENDIF
531    #endif /* ALLOW_DIAGNOSTICS */
532    
533  C--      Calculate accelerations in the momentum equations (gU, gV, ...)  C--      Calculate accelerations in the momentum equations (gU, gV, ...)
534  C        and step forward storing the result in gUnm1, gVnm1, etc...  C        and step forward storing the result in gU, gV, etc...
535           IF ( momStepping ) THEN           IF ( momStepping ) THEN
536             CALL CALC_MOM_RHS(  #ifdef ALLOW_AUTODIFF_TAMC
537       I         bi,bj,iMin,iMax,jMin,jMax,k,kup,kDown,  # ifdef NONLIN_FRSURF
538       I         phiHyd,KappaRU,KappaRV,  #  if (defined ALLOW_MOM_FLUXFORM) && !(defined DISABLE_RSTAR_CODE)
539       U         fVerU, fVerV,  CADJ STORE dWtransC(:,:,bi,bj)
540       I         myTime, myThid)  CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
541    CADJ STORE dWtransU(:,:,bi,bj)
542    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
543    CADJ STORE dWtransV(:,:,bi,bj)
544    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
545    #  endif
546    CADJ STORE fVerU(:,:,:)
547    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
548    CADJ STORE fVerV(:,:,:)
549    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
550    # endif /* NONLIN_FRSURF */
551    #endif /* ALLOW_AUTODIFF_TAMC */
552               IF (.NOT. vectorInvariantMomentum) THEN
553    #ifdef ALLOW_MOM_FLUXFORM
554                  CALL MOM_FLUXFORM(
555         I         bi,bj,k,iMin,iMax,jMin,jMax,
556         I         KappaRU, KappaRV,
557         U         fVerU(1-OLx,1-OLy,kUp),   fVerV(1-OLx,1-OLy,kUp),
558         O         fVerU(1-OLx,1-OLy,kDown), fVerV(1-OLx,1-OLy,kDown),
559         O         guDissip, gvDissip,
560         I         myTime, myIter, myThid)
561    #endif
562               ELSE
563    #ifdef ALLOW_MOM_VECINV
564                 CALL MOM_VECINV(
565         I         bi,bj,k,iMin,iMax,jMin,jMax,
566         I         KappaRU, KappaRV,
567         I         fVerU(1-OLx,1-OLy,kUp),   fVerV(1-OLx,1-OLy,kUp),
568         O         fVerU(1-OLx,1-OLy,kDown), fVerV(1-OLx,1-OLy,kDown),
569         O         guDissip, gvDissip,
570         I         myTime, myIter, myThid)
571    #endif
572               ENDIF
573    
574             CALL TIMESTEP(             CALL TIMESTEP(
575       I         bi,bj,iMin,iMax,jMin,jMax,k,       I         bi,bj,iMin,iMax,jMin,jMax,k,
576       I         phiHyd, phiSurfX, phiSurfY,       I         dPhiHydX,dPhiHydY, phiSurfX, phiSurfY,
577       I         myIter, myThid)       I         guDissip, gvDissip,
578         I         myTime, myIter, myThid)
 #ifdef   ALLOW_OBCS  
 C--      Apply open boundary conditions  
          IF (useOBCS) THEN  
            CALL OBCS_APPLY_UV( bi, bj, k, gUnm1, gVnm1, myThid )  
          END IF  
 #endif   /* ALLOW_OBCS */  
579    
 #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 */  
580           ENDIF           ENDIF
581    
   
582  C--     end of dynamics k loop (1:Nr)  C--     end of dynamics k loop (1:Nr)
583          ENDDO          ENDDO
584    
585    C--     Implicit Vertical advection & viscosity
586    #if (defined (INCLUDE_IMPLVERTADV_CODE) && \
587  C--     Implicit viscosity       defined (ALLOW_MOM_COMMON) && !(defined ALLOW_AUTODIFF_TAMC))
588          IF (implicitViscosity.AND.momStepping) THEN          IF ( momImplVertAdv ) THEN
589              CALL MOM_U_IMPLICIT_R( kappaRU,
590         I                           bi, bj, myTime, myIter, myThid )
591              CALL MOM_V_IMPLICIT_R( kappaRV,
592         I                           bi, bj, myTime, myIter, myThid )
593            ELSEIF ( implicitViscosity ) THEN
594    #else /* INCLUDE_IMPLVERTADV_CODE */
595            IF     ( implicitViscosity ) THEN
596    #endif /* INCLUDE_IMPLVERTADV_CODE */
597  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
598            idkey = iikey + 3  CADJ STORE KappaRU(:,:,:) = comlev1_bibj , key=idynkey, byte=isbyte
599  CADJ STORE gUNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte  CADJ STORE gU(:,:,:,bi,bj) = comlev1_bibj , key=idynkey, byte=isbyte
600  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
601            CALL IMPLDIFF(            CALL IMPLDIFF(
602       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
603       I         deltaTmom, KappaRU,recip_HFacW,       I         -1, KappaRU, recip_hFacW(1-OLx,1-OLy,1,bi,bj),
604       U         gUNm1,       U         gU,
605       I         myThid )       I         myThid )
606  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
607            idkey = iikey + 4  CADJ STORE KappaRV(:,:,:) = comlev1_bibj , key=idynkey, byte=isbyte
608  CADJ STORE gVNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte  CADJ STORE gV(:,:,:,bi,bj) = comlev1_bibj , key=idynkey, byte=isbyte
609  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
610            CALL IMPLDIFF(            CALL IMPLDIFF(
611       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
612       I         deltaTmom, KappaRV,recip_HFacS,       I         -2, KappaRV, recip_hFacS(1-OLx,1-OLy,1,bi,bj),
613       U         gVNm1,       U         gV,
614       I         myThid )       I         myThid )
615            ENDIF
616    
617  #ifdef   ALLOW_OBCS  #ifdef ALLOW_OBCS
618  C--      Apply open boundary conditions  C--      Apply open boundary conditions
619           IF (useOBCS) THEN          IF ( useOBCS ) THEN
620             DO K=1,Nr  C--      but first save intermediate velocities to be used in the
621               CALL OBCS_APPLY_UV( bi, bj, k, gUnm1, gVnm1, myThid )  C        next time step for the Stevens boundary conditions
622             ENDDO            CALL OBCS_SAVE_UV_N(
623           END IF       I        bi, bj, iMin, iMax, jMin, jMax, 0,
624  #endif   /* ALLOW_OBCS */       I        gU, gV, myThid )
625              CALL OBCS_APPLY_UV( bi, bj, 0, gU, gV, myThid )
626            ENDIF
627    #endif /* ALLOW_OBCS */
628    
629  #ifdef    INCLUDE_CD_CODE  #ifdef    ALLOW_CD_CODE
630            IF (implicitViscosity.AND.useCDscheme) THEN
631  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
632            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  
633  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
634            CALL IMPLDIFF(            CALL IMPLDIFF(
635       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
636       I         deltaTmom, KappaRU,recip_HFacW,       I         0, KappaRU, recip_hFacW(1-OLx,1-OLy,1,bi,bj),
637       U         vVelD,       U         vVelD,
638       I         myThid )       I         myThid )
639  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
640            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  
641  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
642            CALL IMPLDIFF(            CALL IMPLDIFF(
643       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
644       I         deltaTmom, KappaRV,recip_HFacS,       I         0, KappaRV, recip_hFacS(1-OLx,1-OLy,1,bi,bj),
645       U         uVelD,       U         uVelD,
646       I         myThid )       I         myThid )
 #endif    /* INCLUDE_CD_CODE */  
 C--     End If implicitViscosity.AND.momStepping  
647          ENDIF          ENDIF
648    #endif    /* ALLOW_CD_CODE */
649  Cjmc : add for phiHyd output <- but not working if multi tile per CPU  C--     End implicit Vertical advection & viscosity
650  c       IF ( DIFFERENT_MULTIPLE(dumpFreq,myTime+deltaTClock,myTime)  
651  c    &  .AND. buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
652  c         WRITE(suff,'(I10.10)') myIter+1  
653  c         CALL WRITE_FLD_XYZ_RL('PH.',suff,phiHyd,myIter+1,myThid)  #ifdef ALLOW_NONHYDROSTATIC
654  c       ENDIF  C--   Step forward W field in N-H algorithm
655  Cjmc(end)          IF ( nonHydrostatic ) THEN
656    #ifdef ALLOW_DEBUG
657  #ifdef ALLOW_TIMEAVE           IF (debugMode) CALL DEBUG_CALL('CALC_GW', myThid )
658          IF (taveFreq.GT.0.) THEN  #endif
659            CALL TIMEAVE_CUMUL_1T(phiHydtave, phiHyd, Nr,           CALL TIMER_START('CALC_GW          [DYNAMICS]',myThid)
660       I                              deltaTclock, bi, bj, myThid)           CALL CALC_GW(
661            IF (ivdc_kappa.NE.0.) THEN       I                 bi,bj, KappaRU, KappaRV,
662              CALL TIMEAVE_CUMULATE(ConvectCountTave, ConvectCount, Nr,       I                 myTime, myIter, myThid )
      I                              deltaTclock, bi, bj, myThid)  
           ENDIF  
663          ENDIF          ENDIF
664  #endif /* ALLOW_TIMEAVE */          IF ( nonHydrostatic.OR.implicitIntGravWave )
665         &   CALL TIMESTEP_WVEL( bi,bj, myTime, myIter, myThid )
666            IF ( nonHydrostatic )
667         &   CALL TIMER_STOP ('CALC_GW          [DYNAMICS]',myThid)
668    #endif
669    
670    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
671    
672    C-    end of bi,bj loops
673         ENDDO         ENDDO
674        ENDDO        ENDDO
675    
676  #ifndef EXCLUDE_DEBUGMODE  #ifdef ALLOW_OBCS
677          IF (useOBCS) THEN
678            CALL OBCS_EXCHANGES( myThid )
679          ENDIF
680    #endif
681    
682    Cml(
683    C     In order to compare the variance of phiHydLow of a p/z-coordinate
684    C     run with etaH of a z/p-coordinate run the drift of phiHydLow
685    C     has to be removed by something like the following subroutine:
686    C      CALL REMOVE_MEAN_RL( 1, phiHydLow, maskInC, maskInC, rA, drF,
687    C     &                     'phiHydLow', myTime, myThid )
688    Cml)
689    
690    #ifdef ALLOW_DIAGNOSTICS
691          IF ( useDiagnostics ) THEN
692    
693           CALL DIAGNOSTICS_FILL(totPhihyd,'PHIHYD  ',0,Nr,0,1,1,myThid)
694           CALL DIAGNOSTICS_FILL(phiHydLow,'PHIBOT  ',0, 1,0,1,1,myThid)
695    
696           tmpFac = 1. _d 0
697           CALL DIAGNOSTICS_SCALE_FILL(totPhihyd,tmpFac,2,
698         &                                 'PHIHYDSQ',0,Nr,0,1,1,myThid)
699    
700           CALL DIAGNOSTICS_SCALE_FILL(phiHydLow,tmpFac,2,
701         &                                 'PHIBOTSQ',0, 1,0,1,1,myThid)
702    
703          ENDIF
704    #endif /* ALLOW_DIAGNOSTICS */
705    
706    #ifdef ALLOW_DEBUG
707          IF ( debugLevel .GE. debLevD ) THEN
708         CALL DEBUG_STATS_RL(1,EtaN,'EtaN (DYNAMICS)',myThid)         CALL DEBUG_STATS_RL(1,EtaN,'EtaN (DYNAMICS)',myThid)
709           CALL DEBUG_STATS_RL(Nr,uVel,'Uvel (DYNAMICS)',myThid)
710         CALL DEBUG_STATS_RL(Nr,vVel,'Vvel (DYNAMICS)',myThid)         CALL DEBUG_STATS_RL(Nr,vVel,'Vvel (DYNAMICS)',myThid)
711         CALL DEBUG_STATS_RL(Nr,wVel,'Wvel (DYNAMICS)',myThid)         CALL DEBUG_STATS_RL(Nr,wVel,'Wvel (DYNAMICS)',myThid)
712         CALL DEBUG_STATS_RL(Nr,theta,'Theta (DYNAMICS)',myThid)         CALL DEBUG_STATS_RL(Nr,theta,'Theta (DYNAMICS)',myThid)
713         CALL DEBUG_STATS_RL(Nr,salt,'Salt (DYNAMICS)',myThid)         CALL DEBUG_STATS_RL(Nr,salt,'Salt (DYNAMICS)',myThid)
714         CALL DEBUG_STATS_RL(Nr,Gu,'Gu (DYNAMICS)',myThid)         CALL DEBUG_STATS_RL(Nr,gU,'Gu (DYNAMICS)',myThid)
715         CALL DEBUG_STATS_RL(Nr,Gv,'Gv (DYNAMICS)',myThid)         CALL DEBUG_STATS_RL(Nr,gV,'Gv (DYNAMICS)',myThid)
716         CALL DEBUG_STATS_RL(Nr,Gt,'Gt (DYNAMICS)',myThid)         CALL DEBUG_STATS_RL(Nr,gT,'Gt (DYNAMICS)',myThid)
717         CALL DEBUG_STATS_RL(Nr,Gs,'Gs (DYNAMICS)',myThid)         CALL DEBUG_STATS_RL(Nr,gS,'Gs (DYNAMICS)',myThid)
718         CALL DEBUG_STATS_RL(Nr,GuNm1,'GuNm1 (DYNAMICS)',myThid)  #ifndef ALLOW_ADAMSBASHFORTH_3
719         CALL DEBUG_STATS_RL(Nr,GvNm1,'GvNm1 (DYNAMICS)',myThid)         CALL DEBUG_STATS_RL(Nr,guNm1,'GuNm1 (DYNAMICS)',myThid)
720         CALL DEBUG_STATS_RL(Nr,GtNm1,'GtNm1 (DYNAMICS)',myThid)         CALL DEBUG_STATS_RL(Nr,gvNm1,'GvNm1 (DYNAMICS)',myThid)
721         CALL DEBUG_STATS_RL(Nr,GsNm1,'GsNm1 (DYNAMICS)',myThid)         CALL DEBUG_STATS_RL(Nr,gtNm1,'GtNm1 (DYNAMICS)',myThid)
722           CALL DEBUG_STATS_RL(Nr,gsNm1,'GsNm1 (DYNAMICS)',myThid)
723    #endif
724          ENDIF
725    #endif
726    
727    #ifdef DYNAMICS_GUGV_EXCH_CHECK
728    C- jmc: For safety checking only: This Exchange here should not change
729    C       the solution. If solution changes, it means something is wrong,
730    C       but it does not mean that it is less wrong with this exchange.
731          IF ( debugLevel .GE. debLevE ) THEN
732           CALL EXCH_UV_XYZ_RL(gU,gV,.TRUE.,myThid)
733          ENDIF
734    #endif
735    
736    #ifdef ALLOW_DEBUG
737          IF (debugMode) CALL DEBUG_LEAVE( 'DYNAMICS', myThid )
738  #endif  #endif
739    
740        RETURN        RETURN

Legend:
Removed from v.1.69  
changed lines
  Added in v.1.166

  ViewVC Help
Powered by ViewVC 1.1.22