/[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.54.2.7 by adcroft, Tue Jan 9 21:26:07 2001 UTC revision 1.74 by heimbach, Mon Jul 30 20:37:45 2001 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5    
# Line 25  C     \================================= Line 26  C     \=================================
26  C     == Global variables ===  C     == Global variables ===
27  #include "SIZE.h"  #include "SIZE.h"
28  #include "EEPARAMS.h"  #include "EEPARAMS.h"
 #include "CG2D.h"  
29  #include "PARAMS.h"  #include "PARAMS.h"
30  #include "DYNVARS.h"  #include "DYNVARS.h"
31  #include "GRID.h"  #include "GRID.h"
32    #ifdef ALLOW_PASSIVE_TRACER
33    #include "TR1.h"
34    #endif
35    
36  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
37  # include "tamc.h"  # include "tamc.h"
38  # include "tamc_keys.h"  # include "tamc_keys.h"
39    # include "FFIELDS.h"
40    # ifdef ALLOW_KPP
41    #  include "KPP.h"
42    # endif
43    # ifdef ALLOW_GMREDI
44    #  include "GMREDI.h"
45    # endif
46  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
47    
48  #ifdef ALLOW_KPP  #ifdef ALLOW_TIMEAVE
49  # include "KPP.h"  #include "TIMEAVE_STATV.h"
50  #endif  #endif
51    
52  C     == Routine arguments ==  C     == Routine arguments ==
# Line 51  C     == Local variables Line 61  C     == Local variables
61  C     xA, yA                 - Per block temporaries holding face areas  C     xA, yA                 - Per block temporaries holding face areas
62  C     uTrans, vTrans, rTrans - Per block temporaries holding flow  C     uTrans, vTrans, rTrans - Per block temporaries holding flow
63  C                              transport  C                              transport
64  C     rVel                     o uTrans: Zonal transport  C                              o uTrans: Zonal transport
65  C                              o vTrans: Meridional transport  C                              o vTrans: Meridional transport
66  C                              o rTrans: Vertical transport  C                              o rTrans: Vertical transport
67  C                              o rVel:   Vertical velocity at upper and  C     maskUp                   o maskUp: land/water mask for W points
 C                                        lower cell faces.  
 C     maskC,maskUp             o maskC: land/water mask for tracer cells  
 C                              o maskUp: land/water mask for W points  
68  C     fVer[STUV]               o fVer: Vertical flux term - note fVer  C     fVer[STUV]               o fVer: Vertical flux term - note fVer
69  C                                      is "pipelined" in the vertical  C                                      is "pipelined" in the vertical
70  C                                      so we need an fVer for each  C                                      so we need an fVer for each
71  C                                      variable.  C                                      variable.
72  C     rhoK, rhoKM1   - Density at current level, level above and level  C     rhoK, rhoKM1   - Density at current level, and level above
 C                      below.  
 C     rhoKP1                                                                    
 C     buoyK, buoyKM1 - Buoyancy at current level and level above.  
73  C     phiHyd         - Hydrostatic part of the potential phiHydi.  C     phiHyd         - Hydrostatic part of the potential phiHydi.
74  C                      In z coords phiHydiHyd is the hydrostatic  C                      In z coords phiHydiHyd is the hydrostatic
75  C                      pressure anomaly  C                      Potential (=pressure/rho0) anomaly
76  C                      In p coords phiHydiHyd is the geopotential  C                      In p coords phiHydiHyd is the geopotential
77  C                      surface height  C                      surface height anomaly.
78  C                      anomaly.  C     phiSurfX, - gradient of Surface potentiel (Pressure/rho, ocean)
79  C     etaSurfX,      - Holds surface elevation gradient in X and Y.  C     phiSurfY             or geopotentiel (atmos) in X and Y direction
 C     etaSurfY  
80  C     KappaRT,       - Total diffusion in vertical for T and S.  C     KappaRT,       - Total diffusion in vertical for T and S.
81  C     KappaRS          (background + spatially varying, isopycnal term).  C     KappaRS          (background + spatially varying, isopycnal term).
82  C     iMin, iMax     - Ranges and sub-block indices on which calculations  C     iMin, iMax     - Ranges and sub-block indices on which calculations
# Line 82  C     bi, bj Line 85  C     bi, bj
85  C     k, kup,        - Index for layer above and below. kup and kDown  C     k, kup,        - Index for layer above and below. kup and kDown
86  C     kDown, km1       are switched with layer to be the appropriate  C     kDown, km1       are switched with layer to be the appropriate
87  C                      index into fVerTerm.  C                      index into fVerTerm.
88    C     tauAB - Adams-Bashforth timestepping weight: 0=forward ; 1/2=Adams-Bashf.
89        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
91        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
92        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
93        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RL rVel    (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)  
       _RS maskC   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
94        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
95        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
96        _RL fVerS   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerS   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
97          _RL fVerTr1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
98        _RL fVerU   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerU   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
99        _RL fVerV   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerV   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
100        _RL phiHyd  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL phiHyd  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
101        _RL rhokm1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhokm1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RL rhokp1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
102        _RL rhok    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhok    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
103        _RL buoyKM1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
104        _RL buoyK   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RL rhotmp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
105        _RL KappaRT (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)        _RL KappaRT (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
106        _RL KappaRS (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)        _RL KappaRS (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
107        _RL KappaRU (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)        _RL KappaRU (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
# Line 108  C                      index into fVerTe Line 109  C                      index into fVerTe
109        _RL sigmaX  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaX  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
110        _RL sigmaY  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaY  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
111        _RL sigmaR  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaR  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
112          _RL tauAB
113    
114  C This is currently also used by IVDC and Diagnostics  C This is currently used by IVDC and Diagnostics
 C #ifdef INCLUDE_CONVECT_CALL  
115        _RL ConvectCount (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL ConvectCount (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
 C #endif  
116    
117        INTEGER iMin, iMax        INTEGER iMin, iMax
118        INTEGER jMin, jMax        INTEGER jMin, jMax
# Line 120  C #endif Line 120  C #endif
120        INTEGER i, j        INTEGER i, j
121        INTEGER k, km1, kup, kDown        INTEGER k, km1, kup, kDown
122    
123  #ifdef ALLOW_AUTODIFF_TAMC  Cjmc : add for phiHyd output <- but not working if multi tile per CPU
124        INTEGER    isbyte  c     CHARACTER*(MAX_LEN_MBUF) suff
125        PARAMETER( isbyte = 4 )  c     LOGICAL  DIFFERENT_MULTIPLE
126    c     EXTERNAL DIFFERENT_MULTIPLE
127        INTEGER act1, act2, act3, act4  Cjmc(end)
128        INTEGER max1, max2, max3  
       INTEGER iikey, kkey  
       INTEGER maximpl  
 #endif /* ALLOW_AUTODIFF_TAMC */  
   
129  C---    The algorithm...  C---    The algorithm...
130  C  C
131  C       "Correction Step"  C       "Correction Step"
# Line 144  C       "Calculation of Gs" Line 140  C       "Calculation of Gs"
140  C       ===================  C       ===================
141  C       This is where all the accelerations and tendencies (ie.  C       This is where all the accelerations and tendencies (ie.
142  C       physics, parameterizations etc...) are calculated  C       physics, parameterizations etc...) are calculated
 C         rVel = sum_r ( div. u[n] )  
143  C         rho = rho ( theta[n], salt[n] )  C         rho = rho ( theta[n], salt[n] )
144  C         b   = b(rho, theta)  C         b   = b(rho, theta)
145  C         K31 = K31 ( rho )  C         K31 = K31 ( rho )
146  C         Gu[n] = Gu( u[n], v[n], rVel, b, ... )  C         Gu[n] = Gu( u[n], v[n], wVel, b, ... )
147  C         Gv[n] = Gv( u[n], v[n], rVel, b, ... )  C         Gv[n] = Gv( u[n], v[n], wVel, b, ... )
148  C         Gt[n] = Gt( theta[n], u[n], v[n], rVel, K31, ... )  C         Gt[n] = Gt( theta[n], u[n], v[n], wVel, K31, ... )
149  C         Gs[n] = Gs( salt[n], u[n], v[n], rVel, K31, ... )  C         Gs[n] = Gs( salt[n], u[n], v[n], wVel, K31, ... )
150  C  C
151  C       "Time-stepping" or "Prediction"  C       "Time-stepping" or "Prediction"
152  C       ================================  C       ================================
# Line 192  C     uninitialised but inert locations. Line 187  C     uninitialised but inert locations.
187          uTrans(i,j)  = 0. _d 0          uTrans(i,j)  = 0. _d 0
188          vTrans(i,j)  = 0. _d 0          vTrans(i,j)  = 0. _d 0
189          DO k=1,Nr          DO k=1,Nr
190           phiHyd (i,j,k)  = 0. _d 0           phiHyd(i,j,k)  = 0. _d 0
191           KappaRU(i,j,k) = 0. _d 0           KappaRU(i,j,k) = 0. _d 0
192           KappaRV(i,j,k) = 0. _d 0           KappaRV(i,j,k) = 0. _d 0
193           sigmaX(i,j,k) = 0. _d 0           sigmaX(i,j,k) = 0. _d 0
# Line 201  C     uninitialised but inert locations. Line 196  C     uninitialised but inert locations.
196          ENDDO          ENDDO
197          rhoKM1 (i,j) = 0. _d 0          rhoKM1 (i,j) = 0. _d 0
198          rhok   (i,j) = 0. _d 0          rhok   (i,j) = 0. _d 0
199          rhoKP1 (i,j) = 0. _d 0          phiSurfX(i,j) = 0. _d 0
200          rhoTMP (i,j) = 0. _d 0          phiSurfY(i,j) = 0. _d 0
         buoyKM1(i,j) = 0. _d 0  
         buoyK  (i,j) = 0. _d 0  
         maskC  (i,j) = 0. _d 0  
201         ENDDO         ENDDO
202        ENDDO        ENDDO
203    
# Line 219  CHPF$ INDEPENDENT Line 211  CHPF$ INDEPENDENT
211    
212  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
213  C--    HPF directive to help TAMC  C--    HPF directive to help TAMC
214  CHPF$  INDEPENDENT, NEW (rTrans,rVel,fVerT,fVerS,fVerU,fVerV  CHPF$  INDEPENDENT, NEW (rTrans,fVerT,fVerS,fVerU,fVerV
215  CHPF$&                  ,phiHyd,utrans,vtrans,maskc,xA,yA  CHPF$&                  ,phiHyd,utrans,vtrans,xA,yA
216  CHPF$&                  ,KappaRT,KappaRS,KappaRU,KappaRV  CHPF$&                  ,KappaRT,KappaRS,KappaRU,KappaRV
217  CHPF$&                  )  CHPF$&                  )
218  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
# Line 247  CHPF$&                  ) Line 239  CHPF$&                  )
239  C--     Set up work arrays that need valid initial values  C--     Set up work arrays that need valid initial values
240          DO j=1-OLy,sNy+OLy          DO j=1-OLy,sNy+OLy
241           DO i=1-OLx,sNx+OLx           DO i=1-OLx,sNx+OLx
242            rTrans(i,j)   = 0. _d 0            rTrans (i,j)   = 0. _d 0
243            rVel  (i,j,1) = 0. _d 0            fVerT  (i,j,1) = 0. _d 0
244            rVel  (i,j,2) = 0. _d 0            fVerT  (i,j,2) = 0. _d 0
245            fVerT (i,j,1) = 0. _d 0            fVerS  (i,j,1) = 0. _d 0
246            fVerT (i,j,2) = 0. _d 0            fVerS  (i,j,2) = 0. _d 0
247            fVerS (i,j,1) = 0. _d 0            fVerTr1(i,j,1) = 0. _d 0
248            fVerS (i,j,2) = 0. _d 0            fVerTr1(i,j,2) = 0. _d 0
249            fVerU (i,j,1) = 0. _d 0            fVerU  (i,j,1) = 0. _d 0
250            fVerU (i,j,2) = 0. _d 0            fVerU  (i,j,2) = 0. _d 0
251            fVerV (i,j,1) = 0. _d 0            fVerV  (i,j,1) = 0. _d 0
252            fVerV (i,j,2) = 0. _d 0            fVerV  (i,j,2) = 0. _d 0
           phiHyd(i,j,1) = 0. _d 0  
253           ENDDO           ENDDO
254          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  #ifdef INCLUDE_CONVECT_CALL  C This is currently also used by IVDC and Diagnostics
260             ConvectCount(i,j,k) = 0.             ConvectCount(i,j,k) = 0.
 #endif  
261             KappaRT(i,j,k) = 0. _d 0             KappaRT(i,j,k) = 0. _d 0
262             KappaRS(i,j,k) = 0. _d 0             KappaRS(i,j,k) = 0. _d 0
263            ENDDO            ENDDO
# Line 280  C--     Set up work arrays that need val Line 270  C--     Set up work arrays that need val
270          jMax = sNy+OLy          jMax = sNy+OLy
271    
272    
273    #ifdef ALLOW_AUTODIFF_TAMC
274    CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
275    CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
276    CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
277    CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
278    #ifdef ALLOW_PASSIVE_TRACER
279    CADJ STORE tr1  (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
280    #endif
281    #endif /* ALLOW_AUTODIFF_TAMC */
282    
283  C--     Start of diagnostic loop  C--     Start of diagnostic loop
284          DO k=Nr,1,-1          DO k=Nr,1,-1
285    
286  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
287  C? Patrick, is this formula correct now that we change the loop range?  C? Patrick, is this formula correct now that we change the loop range?
288  C? Do we still need this?  C? Do we still need this?
289           kkey = (ikey-1)*(Nr-2+1) + (k-2) + 1  cph kkey formula corrected.
290    cph Needed for rhok, rhokm1, in the case useGMREDI.
291             kkey = (ikey-1)*Nr + k
292    CADJ STORE rhokm1(:,:) = comlev1_bibj_k ,       key=kkey, byte=isbyte
293    CADJ STORE rhok  (:,:) = comlev1_bibj_k ,       key=kkey, byte=isbyte
294  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
295    
296  C--       Integrate continuity vertically for vertical velocity  C--       Integrate continuity vertically for vertical velocity
# Line 296  C--       Integrate continuity verticall Line 300  C--       Integrate continuity verticall
300       I                         myThid )       I                         myThid )
301    
302  #ifdef    ALLOW_OBCS  #ifdef    ALLOW_OBCS
303  C--       Calculate future values on open boundaries  #ifdef    ALLOW_NONHYDROSTATIC
304            IF (openBoundaries) THEN  C--       Apply OBC to W if in N-H mode
305  #ifdef      ALLOW_NONHYDROSTATIC            IF (useOBCS.AND.nonHydrostatic) THEN
306              IF (nonHydrostatic) THEN              CALL OBCS_APPLY_W( bi, bj, k, wVel, myThid )
               CALL OBCS_APPLY_W( bi, bj, k, wVel, myThid )  
             ENDIF  
 #endif      /* ALLOW_NONHYDROSTATIC */  
             CALL OBCS_CALC( bi, bj, k, myTime+deltaT, myThid )  
307            ENDIF            ENDIF
308    #endif    /* ALLOW_NONHYDROSTATIC */
309  #endif    /* ALLOW_OBCS */  #endif    /* ALLOW_OBCS */
310    
311  C--       Calculate gradients of potential density for isoneutral  C--       Calculate gradients of potential density for isoneutral
312  C         slope terms (e.g. GM/Redi tensor or IVDC diffusivity)  C         slope terms (e.g. GM/Redi tensor or IVDC diffusivity)
313            IF ( k.GT.1 .AND. (useGMRedi.OR.ivdc_kappa.NE.0.) ) THEN  c         IF ( k.GT.1 .AND. (useGMRedi.OR.ivdc_kappa.NE.0.) ) THEN
314              IF ( useGMRedi .OR. (k.GT.1 .AND. ivdc_kappa.NE.0.) ) THEN
315    #ifdef ALLOW_AUTODIFF_TAMC
316    CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
317    CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
318    #endif /* ALLOW_AUTODIFF_TAMC */
319              CALL FIND_RHO(              CALL FIND_RHO(
320       I        bi, bj, iMin, iMax, jMin, jMax, k, k, eosType,       I        bi, bj, iMin, iMax, jMin, jMax, k, k, eosType,
321         I        theta, salt,
322       O        rhoK,       O        rhoK,
323       I        myThid )       I        myThid )
324              CALL FIND_RHO(              IF (k.GT.1) THEN
325    #ifdef ALLOW_AUTODIFF_TAMC
326    CADJ STORE theta(:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
327    CADJ STORE salt (:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
328    #endif /* ALLOW_AUTODIFF_TAMC */
329                 CALL FIND_RHO(
330       I        bi, bj, iMin, iMax, jMin, jMax, k-1, k, eosType,       I        bi, bj, iMin, iMax, jMin, jMax, k-1, k, eosType,
331         I        theta, salt,
332       O        rhoKm1,       O        rhoKm1,
333       I        myThid )       I        myThid )
334                ENDIF
335              CALL GRAD_SIGMA(              CALL GRAD_SIGMA(
336       I             bi, bj, iMin, iMax, jMin, jMax, k,       I             bi, bj, iMin, iMax, jMin, jMax, k,
337       I             rhoK, rhoKm1, rhoK,       I             rhoK, rhoKm1, rhoK,
# Line 326  C         slope terms (e.g. GM/Redi tens Line 340  C         slope terms (e.g. GM/Redi tens
340            ENDIF            ENDIF
341    
342  C--       Implicit Vertical Diffusion for Convection  C--       Implicit Vertical Diffusion for Convection
343    c ==> should use sigmaR !!!
344            IF (k.GT.1 .AND. ivdc_kappa.NE.0.) THEN            IF (k.GT.1 .AND. ivdc_kappa.NE.0.) THEN
345              CALL CALC_IVDC(              CALL CALC_IVDC(
346       I        bi, bj, iMin, iMax, jMin, jMax, k,       I        bi, bj, iMin, iMax, jMin, jMax, k,
347       I        rhoKm1, rhoK,       I        rhoKm1, rhoK,
 c should use sigmaR !!!  
348       U        ConvectCount, KappaRT, KappaRS,       U        ConvectCount, KappaRT, KappaRS,
349       I        myTime, myIter, myThid)       I        myTime, myIter, myThid)
350            END IF            ENDIF
351    
352  C--     end of diagnostic k loop (Nr:1)  C--     end of diagnostic k loop (Nr:1)
353          ENDDO          ENDDO
354    
355    #ifdef ALLOW_AUTODIFF_TAMC
356    cph avoids recomputation of integrate_for_w
357    CADJ STORE wvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
358    #endif /* ALLOW_AUTODIFF_TAMC */
359    
360    #ifdef  ALLOW_OBCS
361    C--     Calculate future values on open boundaries
362            IF (useOBCS) THEN
363              CALL OBCS_CALC( bi, bj, myTime+deltaT,
364         I            uVel, vVel, wVel, theta, salt,
365         I            myThid )
366            ENDIF
367    #endif  /* ALLOW_OBCS */
368    
369  C--     Determines forcing terms based on external fields  C--     Determines forcing terms based on external fields
370  C       relaxation terms, etc.  C       relaxation terms, etc.
371          CALL EXTERNAL_FORCING_SURF(          CALL EXTERNAL_FORCING_SURF(
372       I             bi, bj, iMin, iMax, jMin, jMax,       I             bi, bj, iMin, iMax, jMin, jMax,
373       I             myThid )       I             myThid )
374    #ifdef ALLOW_AUTODIFF_TAMC
375    cph needed for KPP
376    CADJ STORE surfacetendencyU(:,:,bi,bj)
377    CADJ &     = comlev1_bibj, key=ikey, byte=isbyte
378    CADJ STORE surfacetendencyV(:,:,bi,bj)
379    CADJ &     = comlev1_bibj, key=ikey, byte=isbyte
380    CADJ STORE surfacetendencyS(:,:,bi,bj)
381    CADJ &     = comlev1_bibj, key=ikey, byte=isbyte
382    CADJ STORE surfacetendencyT(:,:,bi,bj)
383    CADJ &     = comlev1_bibj, key=ikey, byte=isbyte
384    #endif /* ALLOW_AUTODIFF_TAMC */
385    
386  #ifdef  ALLOW_GMREDI  #ifdef  ALLOW_GMREDI
387    
388    #ifdef ALLOW_AUTODIFF_TAMC
389    CADJ STORE sigmaX(:,:,:) = comlev1, key=ikey, byte=isbyte
390    CADJ STORE sigmaY(:,:,:) = comlev1, key=ikey, byte=isbyte
391    CADJ STORE sigmaR(:,:,:) = comlev1, key=ikey, byte=isbyte
392    #endif /* ALLOW_AUTODIFF_TAMC */
393  C--     Calculate iso-neutral slopes for the GM/Redi parameterisation  C--     Calculate iso-neutral slopes for the GM/Redi parameterisation
394          IF (useGMRedi) THEN          IF (useGMRedi) THEN
395            DO k=1,Nr            DO k=1,Nr
# Line 353  C--     Calculate iso-neutral slopes for Line 398  C--     Calculate iso-neutral slopes for
398       I             sigmaX, sigmaY, sigmaR,       I             sigmaX, sigmaY, sigmaR,
399       I             myThid )       I             myThid )
400            ENDDO            ENDDO
401    #ifdef ALLOW_AUTODIFF_TAMC
402            ELSE
403              DO k=1, Nr
404                CALL GMREDI_CALC_TENSOR_DUMMY(
405         I             bi, bj, iMin, iMax, jMin, jMax, k,
406         I             sigmaX, sigmaY, sigmaR,
407         I             myThid )
408              ENDDO
409    #endif /* ALLOW_AUTODIFF_TAMC */
410          ENDIF          ENDIF
411    
412    #ifdef ALLOW_AUTODIFF_TAMC
413    CADJ STORE Kwx(:,:,:,bi,bj)   = comlev1_bibj, key=ikey, byte=isbyte
414    CADJ STORE Kwy(:,:,:,bi,bj)   = comlev1_bibj, key=ikey, byte=isbyte
415    CADJ STORE Kwz(:,:,:,bi,bj)   = comlev1_bibj, key=ikey, byte=isbyte
416    #endif /* ALLOW_AUTODIFF_TAMC */
417    
418  #endif  /* ALLOW_GMREDI */  #endif  /* ALLOW_GMREDI */
419    
420  #ifdef  ALLOW_KPP  #ifdef  ALLOW_KPP
# Line 361  C--     Compute KPP mixing coefficients Line 422  C--     Compute KPP mixing coefficients
422          IF (useKPP) THEN          IF (useKPP) THEN
423            CALL KPP_CALC(            CALL KPP_CALC(
424       I                  bi, bj, myTime, myThid )       I                  bi, bj, myTime, myThid )
425    #ifdef ALLOW_AUTODIFF_TAMC
426            ELSE
427              CALL KPP_CALC_DUMMY(
428         I                  bi, bj, myTime, myThid )
429    #endif /* ALLOW_AUTODIFF_TAMC */
430          ENDIF          ENDIF
431    
432    #ifdef ALLOW_AUTODIFF_TAMC
433    CADJ STORE KPPghat   (:,:,:,bi,bj)
434    CADJ &   , KPPviscAz (:,:,:,bi,bj)
435    CADJ &   , KPPdiffKzT(:,:,:,bi,bj)
436    CADJ &   , KPPdiffKzS(:,:,:,bi,bj)
437    CADJ &   , KPPfrac   (:,:  ,bi,bj)
438    CADJ &                 = comlev1_bibj, key=ikey, byte=isbyte
439    #endif /* ALLOW_AUTODIFF_TAMC */
440    
441  #endif  /* ALLOW_KPP */  #endif  /* ALLOW_KPP */
442    
443  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 371  CADJ STORE theta(:,:,:,bi,bj) = comlev1_ Line 447  CADJ STORE theta(:,:,:,bi,bj) = comlev1_
447  CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
448  CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
449  CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte  CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
450    #ifdef ALLOW_PASSIVE_TRACER
451    CADJ STORE tr1  (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
452    #endif
453  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
454    
455    #ifdef ALLOW_AIM
456    C       AIM - atmospheric intermediate model, physics package code.
457    C note(jmc) : phiHyd=0 at this point but is not really used in Molteni Physics
458            IF ( useAIM ) THEN
459             CALL TIMER_START('AIM_DO_ATMOS_PHYS      [DYNAMICS]', myThid)
460             CALL AIM_DO_ATMOS_PHYSICS( phiHyd, bi, bj, myTime, myThid )
461             CALL TIMER_STOP ('AIM_DO_ATMOS_PHYS      [DYNAMICS]', myThid)
462            ENDIF
463    #endif /* ALLOW_AIM */
464    
465    
466  C--     Start of thermodynamics loop  C--     Start of thermodynamics loop
467          DO k=Nr,1,-1          DO k=Nr,1,-1
468    #ifdef ALLOW_AUTODIFF_TAMC
469    C? Patrick Is this formula correct?
470    cph Yes, but I rewrote it.
471    cph Also, the KappaR? need the index and subscript k!
472             kkey = (ikey-1)*Nr + k
473    #endif /* ALLOW_AUTODIFF_TAMC */
474    
475  C--       km1    Points to level above k (=k-1)  C--       km1    Points to level above k (=k-1)
476  C--       kup    Cycles through 1,2 to point to layer above  C--       kup    Cycles through 1,2 to point to layer above
# Line 386  C--       kDown  Cycles through 2,1 to p Line 480  C--       kDown  Cycles through 2,1 to p
480            kup  = 1+MOD(k+1,2)            kup  = 1+MOD(k+1,2)
481            kDown= 1+MOD(k,2)            kDown= 1+MOD(k,2)
482    
483            iMin = 1-OLx+2            iMin = 1-OLx
484            iMax = sNx+OLx-1            iMax = sNx+OLx
485            jMin = 1-OLy+2            jMin = 1-OLy
486            jMax = sNy+OLy-1            jMax = sNy+OLy
487    
488    C--       Get temporary terms used by tendency routines
489              CALL CALC_COMMON_FACTORS (
490         I         bi,bj,iMin,iMax,jMin,jMax,k,
491         O         xA,yA,uTrans,vTrans,rTrans,maskUp,
492         I         myThid)
493    
494  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
495  CPatrick Is this formula correct?  CADJ STORE KappaRT(:,:,k)    = comlev1_bibj_k, key=kkey, byte=isbyte
496           kkey = (ikey-1)*(Nr-1+1) + (k-1) + 1  CADJ STORE KappaRS(:,:,k)    = comlev1_bibj_k, key=kkey, byte=isbyte
 CADJ STORE rvel  (:,:,kDown) = comlev1_bibj_k, key = kkey, byte = isbyte  
 CADJ STORE rTrans(:,:)       = comlev1_bibj_k, key = kkey, byte = isbyte  
 CADJ STORE KappaRT(:,:,:)    = comlev1_bibj_k, key = kkey, byte = isbyte  
 CADJ STORE KappaRS(:,:,:)    = comlev1_bibj_k, key = kkey, byte = isbyte  
497  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
498    
 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,rVel,maskC,maskUp,  
      I        myThid)  
   
499  #ifdef  INCLUDE_CALC_DIFFUSIVITY_CALL  #ifdef  INCLUDE_CALC_DIFFUSIVITY_CALL
500  C--      Calculate the total vertical diffusivity  C--      Calculate the total vertical diffusivity
501           CALL CALC_DIFFUSIVITY(           CALL CALC_DIFFUSIVITY(
502       I        bi,bj,iMin,iMax,jMin,jMax,k,       I        bi,bj,iMin,iMax,jMin,jMax,k,
503       I        maskC,maskup,       I        maskUp,
504       O        KappaRT,KappaRS,KappaRU,KappaRV,       O        KappaRT,KappaRS,KappaRU,KappaRV,
505       I        myThid)       I        myThid)
506  #endif  #endif
507    
508              iMin = 1-OLx+2
509              iMax = sNx+OLx-1
510              jMin = 1-OLy+2
511              jMax = sNy+OLy-1
512    
513  C--      Calculate active tracer tendencies (gT,gS,...)  C--      Calculate active tracer tendencies (gT,gS,...)
514  C        and step forward storing result in gTnm1, gSnm1, etc.  C        and step forward storing result in gTnm1, gSnm1, etc.
515           IF ( tempStepping ) THEN           IF ( tempStepping ) THEN
516             CALL CALC_GT(             CALL CALC_GT(
517       I         bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,       I         bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,
518       I         xA,yA,uTrans,vTrans,rTrans,maskUp,maskC,       I         xA,yA,uTrans,vTrans,rTrans,maskUp,
519       I         KappaRT,       I         KappaRT,
520       U         fVerT,       U         fVerT,
521       I         myTime, myThid)       I         myTime, myThid)
522               tauAB = 0.5d0 + abEps
523             CALL TIMESTEP_TRACER(             CALL TIMESTEP_TRACER(
524       I         bi,bj,iMin,iMax,jMin,jMax,k,       I         bi,bj,iMin,iMax,jMin,jMax,k,tauAB,
525       I         theta, gT,       I         theta, gT,
526       U         gTnm1,       U         gTnm1,
527       I         myIter, myThid)       I         myIter, myThid)
# Line 433  C        and step forward storing result Line 529  C        and step forward storing result
529           IF ( saltStepping ) THEN           IF ( saltStepping ) THEN
530             CALL CALC_GS(             CALL CALC_GS(
531       I         bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,       I         bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,
532       I         xA,yA,uTrans,vTrans,rTrans,maskUp,maskC,       I         xA,yA,uTrans,vTrans,rTrans,maskUp,
533       I         KappaRS,       I         KappaRS,
534       U         fVerS,       U         fVerS,
535       I         myTime, myThid)       I         myTime, myThid)
536               tauAB = 0.5d0 + abEps
537             CALL TIMESTEP_TRACER(             CALL TIMESTEP_TRACER(
538       I         bi,bj,iMin,iMax,jMin,jMax,k,       I         bi,bj,iMin,iMax,jMin,jMax,k,tauAB,
539       I         salt, gS,       I         salt, gS,
540       U         gSnm1,       U         gSnm1,
541       I         myIter, myThid)       I         myIter, myThid)
542           ENDIF           ENDIF
543    #ifdef ALLOW_PASSIVE_TRACER
544             IF ( tr1Stepping ) THEN
545               CALL CALC_GTR1(
546         I         bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,
547         I         xA,yA,uTrans,vTrans,rTrans,maskUp,
548         I         KappaRT,
549         U         fVerTr1,
550         I         myTime, myThid)
551               tauAB = 0.5d0 + abEps
552               CALL TIMESTEP_TRACER(
553         I         bi,bj,iMin,iMax,jMin,jMax,k,tauAB,
554         I         Tr1, gTr1,
555         U         gTr1NM1,
556         I         myIter, myThid)
557             ENDIF
558    #endif
559    
560  #ifdef   ALLOW_OBCS  #ifdef   ALLOW_OBCS
561  C--      Apply open boundary conditions  C--      Apply open boundary conditions
562           IF (openBoundaries) THEN           IF (useOBCS) THEN
563             CALL OBCS_APPLY_TS( bi, bj, k, gTnm1, gSnm1, myThid )             CALL OBCS_APPLY_TS( bi, bj, k, gTnm1, gSnm1, myThid )
564           END IF           END IF
565  #endif   /* ALLOW_OBCS */  #endif   /* ALLOW_OBCS */
# Line 465  C--     end of thermodynamic k loop (Nr: Line 578  C--     end of thermodynamic k loop (Nr:
578    
579    
580  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
581  CPatrick? What about this one?  C? Patrick? What about this one?
582             maximpl = 6  cph Keys iikey and idkey don't seem to be needed
583             iikey = (ikey-1)*maximpl  cph since storing occurs on different tape for each
584    cph impldiff call anyways.
585    cph Thus, common block comlev1_impl isn't needed either.
586    cph Storing below needed in the case useGMREDI.
587            iikey = (ikey-1)*maximpl
588  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
589    
590  C--     Implicit diffusion  C--     Implicit diffusion
591          IF (implicitDiffusion) THEN          IF (implicitDiffusion) THEN
592    
593            IF (tempStepping) THEN           IF (tempStepping) THEN
594  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
595              idkey = iikey + 1              idkey = iikey + 1
596    CADJ STORE gTNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
597  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
598              CALL IMPLDIFF(              CALL IMPLDIFF(
599       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 487  C--     Implicit diffusion Line 605  C--     Implicit diffusion
605           IF (saltStepping) THEN           IF (saltStepping) THEN
606  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
607           idkey = iikey + 2           idkey = iikey + 2
608    CADJ STORE gSNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, 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,
# Line 495  C--     Implicit diffusion Line 614  C--     Implicit diffusion
614       I         myThid )       I         myThid )
615           ENDIF           ENDIF
616    
617    #ifdef ALLOW_PASSIVE_TRACER
618             IF (tr1Stepping) THEN
619    #ifdef ALLOW_AUTODIFF_TAMC
620    CADJ STORE gTr1Nm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
621    #endif /* ALLOW_AUTODIFF_TAMC */
622              CALL IMPLDIFF(
623         I      bi, bj, iMin, iMax, jMin, jMax,
624         I      deltaTtracer, KappaRT, recip_HFacC,
625         U      gTr1Nm1,
626         I      myThid )
627             ENDIF
628    #endif
629    
630  #ifdef   ALLOW_OBCS  #ifdef   ALLOW_OBCS
631  C--      Apply open boundary conditions  C--      Apply open boundary conditions
632           IF (openBoundaries) THEN           IF (useOBCS) THEN
633             DO K=1,Nr             DO K=1,Nr
634               CALL OBCS_APPLY_TS( bi, bj, k, gTnm1, gSnm1, myThid )               CALL OBCS_APPLY_TS( bi, bj, k, gTnm1, gSnm1, myThid )
635             ENDDO             ENDDO
# Line 507  C--      Apply open boundary conditions Line 639  C--      Apply open boundary conditions
639  C--     End If implicitDiffusion  C--     End If implicitDiffusion
640          ENDIF          ENDIF
641    
642    C--     Start computation of dynamics
643            iMin = 1-OLx+2
644            iMax = sNx+OLx-1
645            jMin = 1-OLy+2
646            jMax = sNy+OLy-1
647    
648    C--     Explicit part of the Surface Potentiel Gradient (add in TIMESTEP)
649    C       (note: this loop will be replaced by CALL CALC_GRAD_ETA)
650            IF (implicSurfPress.NE.1.) THEN
651              CALL CALC_GRAD_PHI_SURF(
652         I         bi,bj,iMin,iMax,jMin,jMax,
653         I         etaN,
654         O         phiSurfX,phiSurfY,
655         I         myThid )                        
656            ENDIF
657    
658  C--     Start of dynamics loop  C--     Start of dynamics loop
659          DO k=1,Nr          DO k=1,Nr
# Line 520  C--       kDown  Cycles through 2,1 to p Line 666  C--       kDown  Cycles through 2,1 to p
666            kup  = 1+MOD(k+1,2)            kup  = 1+MOD(k+1,2)
667            kDown= 1+MOD(k,2)            kDown= 1+MOD(k,2)
668    
           iMin = 1-OLx+2  
           iMax = sNx+OLx-1  
           jMin = 1-OLy+2  
           jMax = sNy+OLy-1  
   
 C--      Calculate buoyancy  
          CALL FIND_RHO(  
      I        bi, bj, iMin, iMax, jMin, jMax, km1, km1, eosType,  
      O        rhoKm1,  
      I        myThid )  
          CALL CALC_BUOYANCY(  
      I        bi,bj,iMin,iMax,jMin,jMax,k,rhoKm1,  
      O        buoyKm1,  
      I        myThid )  
          CALL FIND_RHO(  
      I        bi, bj, iMin, iMax, jMin, jMax, k, k, eosType,  
      O        rhoK,  
      I        myThid )  
          CALL CALC_BUOYANCY(  
      I        bi,bj,iMin,iMax,jMin,jMax,k,rhoK,  
      O        buoyK,  
      I        myThid )  
   
669  C--      Integrate hydrostatic balance for phiHyd with BC of  C--      Integrate hydrostatic balance for phiHyd with BC of
670  C--      phiHyd(z=0)=0  C        phiHyd(z=0)=0
671           CALL CALC_PHI_HYD(  C        distinguishe between Stagger and Non Stagger time stepping
672       I        bi,bj,iMin,iMax,jMin,jMax,k,buoyKm1,buoyK,           IF (staggerTimeStep) THEN
673               CALL CALC_PHI_HYD(
674         I        bi,bj,iMin,iMax,jMin,jMax,k,
675         I        gTnm1, gSnm1,
676       U        phiHyd,       U        phiHyd,
677       I        myThid )       I        myThid )
678             ELSE
679               CALL CALC_PHI_HYD(
680         I        bi,bj,iMin,iMax,jMin,jMax,k,
681         I        theta, salt,
682         U        phiHyd,
683         I        myThid )
684             ENDIF
685    
686  C--      Calculate accelerations in the momentum equations (gU, gV, ...)  C--      Calculate accelerations in the momentum equations (gU, gV, ...)
687  C        and step forward storing the result in gUnm1, gVnm1, etc...  C        and step forward storing the result in gUnm1, gVnm1, etc...
# Line 560  C        and step forward storing the re Line 693  C        and step forward storing the re
693       I         myTime, myThid)       I         myTime, myThid)
694             CALL TIMESTEP(             CALL TIMESTEP(
695       I         bi,bj,iMin,iMax,jMin,jMax,k,       I         bi,bj,iMin,iMax,jMin,jMax,k,
696         I         phiHyd, phiSurfX, phiSurfY,
697       I         myIter, myThid)       I         myIter, myThid)
698    
699  #ifdef   ALLOW_OBCS  #ifdef   ALLOW_OBCS
700  C--      Apply open boundary conditions  C--      Apply open boundary conditions
701           IF (openBoundaries) THEN           IF (useOBCS) THEN
702             CALL OBCS_APPLY_UV( bi, bj, k, gUnm1, gVnm1, myThid )             CALL OBCS_APPLY_UV( bi, bj, k, gUnm1, gVnm1, myThid )
703           END IF           END IF
704  #endif   /* ALLOW_OBCS */  #endif   /* ALLOW_OBCS */
# Line 592  C--     Implicit viscosity Line 726  C--     Implicit viscosity
726          IF (implicitViscosity.AND.momStepping) THEN          IF (implicitViscosity.AND.momStepping) THEN
727  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
728            idkey = iikey + 3            idkey = iikey + 3
729    CADJ STORE gUNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
730  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
731            CALL IMPLDIFF(            CALL IMPLDIFF(
732       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 600  C--     Implicit viscosity Line 735  C--     Implicit viscosity
735       I         myThid )       I         myThid )
736  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
737            idkey = iikey + 4            idkey = iikey + 4
738    CADJ STORE gVNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
739  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
740            CALL IMPLDIFF(            CALL IMPLDIFF(
741       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 609  C--     Implicit viscosity Line 745  C--     Implicit viscosity
745    
746  #ifdef   ALLOW_OBCS  #ifdef   ALLOW_OBCS
747  C--      Apply open boundary conditions  C--      Apply open boundary conditions
748           IF (openBoundaries) THEN           IF (useOBCS) THEN
749             DO K=1,Nr             DO K=1,Nr
750               CALL OBCS_APPLY_UV( bi, bj, k, gUnm1, gVnm1, myThid )               CALL OBCS_APPLY_UV( bi, bj, k, gUnm1, gVnm1, myThid )
751             ENDDO             ENDDO
# Line 619  C--      Apply open boundary conditions Line 755  C--      Apply open boundary conditions
755  #ifdef    INCLUDE_CD_CODE  #ifdef    INCLUDE_CD_CODE
756  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
757            idkey = iikey + 5            idkey = iikey + 5
758    CADJ STORE vVelD(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
759  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
760            CALL IMPLDIFF(            CALL IMPLDIFF(
761       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 627  C--      Apply open boundary conditions Line 764  C--      Apply open boundary conditions
764       I         myThid )       I         myThid )
765  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
766            idkey = iikey + 6            idkey = iikey + 6
767    CADJ STORE uVelD(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
768  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
769            CALL IMPLDIFF(            CALL IMPLDIFF(
770       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 637  C--      Apply open boundary conditions Line 775  C--      Apply open boundary conditions
775  C--     End If implicitViscosity.AND.momStepping  C--     End If implicitViscosity.AND.momStepping
776          ENDIF          ENDIF
777    
778    Cjmc : add for phiHyd output <- but not working if multi tile per CPU
779    c       IF ( DIFFERENT_MULTIPLE(dumpFreq,myTime+deltaTClock,myTime)
780    c    &  .AND. buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
781    c         WRITE(suff,'(I10.10)') myIter+1
782    c         CALL WRITE_FLD_XYZ_RL('PH.',suff,phiHyd,myIter+1,myThid)
783    c       ENDIF
784    Cjmc(end)
785    
786    #ifdef ALLOW_TIMEAVE
787            IF (taveFreq.GT.0.) THEN
788              CALL TIMEAVE_CUMUL_1T(phiHydtave, phiHyd, Nr,
789         I                              deltaTclock, bi, bj, myThid)
790              IF (ivdc_kappa.NE.0.) THEN
791                CALL TIMEAVE_CUMULATE(ConvectCountTave, ConvectCount, Nr,
792         I                              deltaTclock, bi, bj, myThid)
793              ENDIF
794            ENDIF
795    #endif /* ALLOW_TIMEAVE */
796    
797         ENDDO         ENDDO
798        ENDDO        ENDDO
799    
800        RETURN  #ifndef EXCLUDE_DEBUGMODE
801        END        If (debugMode) THEN
802           CALL DEBUG_STATS_RL(1,EtaN,'EtaN (DYNAMICS)',myThid)
803           CALL DEBUG_STATS_RL(Nr,uVel,'Uvel (DYNAMICS)',myThid)
804  C--      Cumulative diagnostic calculations (ie. time-averaging)         CALL DEBUG_STATS_RL(Nr,vVel,'Vvel (DYNAMICS)',myThid)
805  #ifdef INCLUDE_DIAGNOSTICS_INTERFACE_CODE         CALL DEBUG_STATS_RL(Nr,wVel,'Wvel (DYNAMICS)',myThid)
806  c        IF (taveFreq.GT.0.) THEN         CALL DEBUG_STATS_RL(Nr,theta,'Theta (DYNAMICS)',myThid)
807  c         CALL DO_TIME_AVERAGES(         CALL DEBUG_STATS_RL(Nr,salt,'Salt (DYNAMICS)',myThid)
808  c    I                           myTime, myIter, bi, bj, k, kup, kDown,         CALL DEBUG_STATS_RL(Nr,Gu,'Gu (DYNAMICS)',myThid)
809  c    I                           ConvectCount,         CALL DEBUG_STATS_RL(Nr,Gv,'Gv (DYNAMICS)',myThid)
810  c    I                           myThid )         CALL DEBUG_STATS_RL(Nr,Gt,'Gt (DYNAMICS)',myThid)
811  c        ENDIF         CALL DEBUG_STATS_RL(Nr,Gs,'Gs (DYNAMICS)',myThid)
812           CALL DEBUG_STATS_RL(Nr,GuNm1,'GuNm1 (DYNAMICS)',myThid)
813           CALL DEBUG_STATS_RL(Nr,GvNm1,'GvNm1 (DYNAMICS)',myThid)
814           CALL DEBUG_STATS_RL(Nr,GtNm1,'GtNm1 (DYNAMICS)',myThid)
815           CALL DEBUG_STATS_RL(Nr,GsNm1,'GsNm1 (DYNAMICS)',myThid)
816          ENDIF
817  #endif  #endif
818    
819          RETURN
820          END

Legend:
Removed from v.1.54.2.7  
changed lines
  Added in v.1.74

  ViewVC Help
Powered by ViewVC 1.1.22