/[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.63 by jmc, Tue Feb 20 15:06:21 2001 UTC revision 1.70 by adcroft, Wed Jun 6 15:14:06 2001 UTC
# Line 26  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"
# Line 34  C     == Global variables === Line 33  C     == Global variables ===
33  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
34  # include "tamc.h"  # include "tamc.h"
35  # include "tamc_keys.h"  # include "tamc_keys.h"
36    # include "FFIELDS.h"
37    # ifdef ALLOW_KPP
38    #  include "KPP.h"
39    # endif
40    # ifdef ALLOW_GMREDI
41    #  include "GMREDI.h"
42    # endif
43  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
44    
45  #ifdef ALLOW_KPP  #ifdef ALLOW_TIMEAVE
46  # include "KPP.h"  #include "TIMEAVE_STATV.h"
 #endif  
   
 #ifdef INCLUDE_DIAGNOSTICS_INTERFACE_CODE  
 #include "AVER.h"  
47  #endif  #endif
48    
49  C     == Routine arguments ==  C     == Routine arguments ==
# Line 59  C                              transport Line 61  C                              transport
61  C                              o uTrans: Zonal transport  C                              o uTrans: Zonal transport
62  C                              o vTrans: Meridional transport  C                              o vTrans: Meridional transport
63  C                              o rTrans: Vertical transport  C                              o rTrans: Vertical transport
64  C     maskC,maskUp             o maskC: land/water mask for tracer cells  C     maskUp                   o maskUp: land/water mask for W points
 C                              o maskUp: land/water mask for W points  
65  C     fVer[STUV]               o fVer: Vertical flux term - note fVer  C     fVer[STUV]               o fVer: Vertical flux term - note fVer
66  C                                      is "pipelined" in the vertical  C                                      is "pipelined" in the vertical
67  C                                      so we need an fVer for each  C                                      so we need an fVer for each
# Line 68  C                                      v Line 69  C                                      v
69  C     rhoK, rhoKM1   - Density at current level, and level above  C     rhoK, rhoKM1   - Density at current level, and level above
70  C     phiHyd         - Hydrostatic part of the potential phiHydi.  C     phiHyd         - Hydrostatic part of the potential phiHydi.
71  C                      In z coords phiHydiHyd is the hydrostatic  C                      In z coords phiHydiHyd is the hydrostatic
72  C                      pressure anomaly  C                      Potential (=pressure/rho0) anomaly
73  C                      In p coords phiHydiHyd is the geopotential  C                      In p coords phiHydiHyd is the geopotential
74  C                      surface height  C                      surface height anomaly.
 C                      anomaly.  
75  C     phiSurfX, - gradient of Surface potentiel (Pressure/rho, ocean)  C     phiSurfX, - gradient of Surface potentiel (Pressure/rho, ocean)
76  C     phiSurfY             or geopotentiel (atmos) in X and Y direction  C     phiSurfY             or geopotentiel (atmos) in X and Y direction
77  C     KappaRT,       - Total diffusion in vertical for T and S.  C     KappaRT,       - Total diffusion in vertical for T and S.
# Line 82  C     bi, bj Line 82  C     bi, bj
82  C     k, kup,        - Index for layer above and below. kup and kDown  C     k, kup,        - Index for layer above and below. kup and kDown
83  C     kDown, km1       are switched with layer to be the appropriate  C     kDown, km1       are switched with layer to be the appropriate
84  C                      index into fVerTerm.  C                      index into fVerTerm.
85    C     tauAB - Adams-Bashforth timestepping weight: 0=forward ; 1/2=Adams-Bashf.
86        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA      (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
88        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
89        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
       _RS maskC   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
91        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
92        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
93        _RL fVerS   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerS   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
# Line 105  C                      index into fVerTe Line 105  C                      index into fVerTe
105        _RL sigmaX  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaX  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
106        _RL sigmaY  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaY  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
107        _RL sigmaR  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaR  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
108          _RL tauAB
109    
110  C This is currently used by IVDC and Diagnostics  C This is currently used by IVDC and Diagnostics
111        _RL ConvectCount (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL ConvectCount (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
# Line 121  c     LOGICAL  DIFFERENT_MULTIPLE Line 122  c     LOGICAL  DIFFERENT_MULTIPLE
122  c     EXTERNAL DIFFERENT_MULTIPLE  c     EXTERNAL DIFFERENT_MULTIPLE
123  Cjmc(end)  Cjmc(end)
124    
 #ifdef ALLOW_AUTODIFF_TAMC  
       INTEGER    isbyte  
       PARAMETER( isbyte = 4 )  
   
       INTEGER act1, act2, act3, act4  
       INTEGER max1, max2, max3  
       INTEGER iikey, kkey  
       INTEGER maximpl  
 #endif /* ALLOW_AUTODIFF_TAMC */  
   
125  C---    The algorithm...  C---    The algorithm...
126  C  C
127  C       "Correction Step"  C       "Correction Step"
# Line 201  C     uninitialised but inert locations. Line 192  C     uninitialised but inert locations.
192          ENDDO          ENDDO
193          rhoKM1 (i,j) = 0. _d 0          rhoKM1 (i,j) = 0. _d 0
194          rhok   (i,j) = 0. _d 0          rhok   (i,j) = 0. _d 0
         maskC  (i,j) = 0. _d 0  
195          phiSurfX(i,j) = 0. _d 0          phiSurfX(i,j) = 0. _d 0
196          phiSurfY(i,j) = 0. _d 0          phiSurfY(i,j) = 0. _d 0
197         ENDDO         ENDDO
# Line 218  CHPF$ INDEPENDENT Line 208  CHPF$ INDEPENDENT
208  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
209  C--    HPF directive to help TAMC  C--    HPF directive to help TAMC
210  CHPF$  INDEPENDENT, NEW (rTrans,fVerT,fVerS,fVerU,fVerV  CHPF$  INDEPENDENT, NEW (rTrans,fVerT,fVerS,fVerU,fVerV
211  CHPF$&                  ,phiHyd,utrans,vtrans,maskc,xA,yA  CHPF$&                  ,phiHyd,utrans,vtrans,xA,yA
212  CHPF$&                  ,KappaRT,KappaRS,KappaRU,KappaRV  CHPF$&                  ,KappaRT,KappaRS,KappaRU,KappaRV
213  CHPF$&                  )  CHPF$&                  )
214  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
# Line 274  C This is currently also used by IVDC an Line 264  C This is currently also used by IVDC an
264          jMax = sNy+OLy          jMax = sNy+OLy
265    
266    
267    #ifdef ALLOW_AUTODIFF_TAMC
268    CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
269    CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
270    CADJ STORE uvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
271    CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
272    #endif /* ALLOW_AUTODIFF_TAMC */
273    
274  C--     Start of diagnostic loop  C--     Start of diagnostic loop
275          DO k=Nr,1,-1          DO k=Nr,1,-1
276    
277  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
278  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?
279  C? Do we still need this?  C? Do we still need this?
280           kkey = (ikey-1)*(Nr-2+1) + (k-2) + 1  cph kkey formula corrected.
281    cph Needed for rhok, rhokm1, in the case useGMREDI.
282             kkey = (ikey-1)*Nr + k
283    CADJ STORE rhokm1(:,:) = comlev1_bibj_k ,       key=kkey, byte=isbyte
284    CADJ STORE rhok  (:,:) = comlev1_bibj_k ,       key=kkey, byte=isbyte
285  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
286    
287  C--       Integrate continuity vertically for vertical velocity  C--       Integrate continuity vertically for vertical velocity
# Line 302  C--       Calculate gradients of potenti Line 303  C--       Calculate gradients of potenti
303  C         slope terms (e.g. GM/Redi tensor or IVDC diffusivity)  C         slope terms (e.g. GM/Redi tensor or IVDC diffusivity)
304  c         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
305            IF ( useGMRedi .OR. (k.GT.1 .AND. ivdc_kappa.NE.0.) ) THEN            IF ( useGMRedi .OR. (k.GT.1 .AND. ivdc_kappa.NE.0.) ) THEN
306    #ifdef ALLOW_AUTODIFF_TAMC
307    CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
308    CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
309    #endif /* ALLOW_AUTODIFF_TAMC */
310              CALL FIND_RHO(              CALL FIND_RHO(
311       I        bi, bj, iMin, iMax, jMin, jMax, k, k, eosType,       I        bi, bj, iMin, iMax, jMin, jMax, k, k, eosType,
312       I        theta, salt,       I        theta, salt,
313       O        rhoK,       O        rhoK,
314       I        myThid )       I        myThid )
315              IF (k.GT.1) CALL FIND_RHO(              IF (k.GT.1) THEN
316    #ifdef ALLOW_AUTODIFF_TAMC
317    CADJ STORE theta(:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
318    CADJ STORE salt (:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
319    #endif /* ALLOW_AUTODIFF_TAMC */
320                 CALL FIND_RHO(
321       I        bi, bj, iMin, iMax, jMin, jMax, k-1, k, eosType,       I        bi, bj, iMin, iMax, jMin, jMax, k-1, k, eosType,
322       I        theta, salt,       I        theta, salt,
323       O        rhoKm1,       O        rhoKm1,
324       I        myThid )       I        myThid )
325                ENDIF
326              CALL GRAD_SIGMA(              CALL GRAD_SIGMA(
327       I             bi, bj, iMin, iMax, jMin, jMax, k,       I             bi, bj, iMin, iMax, jMin, jMax, k,
328       I             rhoK, rhoKm1, rhoK,       I             rhoK, rhoKm1, rhoK,
# Line 332  c ==> should use sigmaR !!! Line 343  c ==> should use sigmaR !!!
343  C--     end of diagnostic k loop (Nr:1)  C--     end of diagnostic k loop (Nr:1)
344          ENDDO          ENDDO
345    
346    #ifdef ALLOW_AUTODIFF_TAMC
347    cph avoids recomputation of integrate_for_w
348    CADJ STORE wvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
349    #endif /* ALLOW_AUTODIFF_TAMC */
350    
351  #ifdef  ALLOW_OBCS  #ifdef  ALLOW_OBCS
352  C--     Calculate future values on open boundaries  C--     Calculate future values on open boundaries
353          IF (useOBCS) THEN          IF (useOBCS) THEN
# Line 346  C       relaxation terms, etc. Line 362  C       relaxation terms, etc.
362          CALL EXTERNAL_FORCING_SURF(          CALL EXTERNAL_FORCING_SURF(
363       I             bi, bj, iMin, iMax, jMin, jMax,       I             bi, bj, iMin, iMax, jMin, jMax,
364       I             myThid )       I             myThid )
365    #ifdef ALLOW_AUTODIFF_TAMC
366    cph needed for KPP
367    CADJ STORE surfacetendencyU(:,:,bi,bj)
368    CADJ &     = comlev1_bibj, key=ikey, byte=isbyte
369    CADJ STORE surfacetendencyV(:,:,bi,bj)
370    CADJ &     = comlev1_bibj, key=ikey, byte=isbyte
371    CADJ STORE surfacetendencyS(:,:,bi,bj)
372    CADJ &     = comlev1_bibj, key=ikey, byte=isbyte
373    CADJ STORE surfacetendencyT(:,:,bi,bj)
374    CADJ &     = comlev1_bibj, key=ikey, byte=isbyte
375    #endif /* ALLOW_AUTODIFF_TAMC */
376    
377  #ifdef  ALLOW_GMREDI  #ifdef  ALLOW_GMREDI
378    
379    #ifdef ALLOW_AUTODIFF_TAMC
380    CADJ STORE sigmaX(:,:,:) = comlev1, key=ikey, byte=isbyte
381    CADJ STORE sigmaY(:,:,:) = comlev1, key=ikey, byte=isbyte
382    CADJ STORE sigmaR(:,:,:) = comlev1, key=ikey, byte=isbyte
383    #endif /* ALLOW_AUTODIFF_TAMC */
384  C--     Calculate iso-neutral slopes for the GM/Redi parameterisation  C--     Calculate iso-neutral slopes for the GM/Redi parameterisation
385          IF (useGMRedi) THEN          IF (useGMRedi) THEN
386            DO k=1,Nr            DO k=1,Nr
# Line 366  C--     Calculate iso-neutral slopes for Line 399  C--     Calculate iso-neutral slopes for
399            ENDDO            ENDDO
400  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
401          ENDIF          ENDIF
402    
403    #ifdef ALLOW_AUTODIFF_TAMC
404    CADJ STORE Kwx(:,:,:,bi,bj)   = comlev1_bibj, key=ikey, byte=isbyte
405    CADJ STORE Kwy(:,:,:,bi,bj)   = comlev1_bibj, key=ikey, byte=isbyte
406    CADJ STORE Kwz(:,:,:,bi,bj)   = comlev1_bibj, key=ikey, byte=isbyte
407    #endif /* ALLOW_AUTODIFF_TAMC */
408    
409  #endif  /* ALLOW_GMREDI */  #endif  /* ALLOW_GMREDI */
410    
411  #ifdef  ALLOW_KPP  #ifdef  ALLOW_KPP
# Line 373  C--     Compute KPP mixing coefficients Line 413  C--     Compute KPP mixing coefficients
413          IF (useKPP) THEN          IF (useKPP) THEN
414            CALL KPP_CALC(            CALL KPP_CALC(
415       I                  bi, bj, myTime, myThid )       I                  bi, bj, myTime, myThid )
416    #ifdef ALLOW_AUTODIFF_TAMC
417            ELSE
418              CALL KPP_CALC_DUMMY(
419         I                  bi, bj, myTime, myThid )
420    #endif /* ALLOW_AUTODIFF_TAMC */
421          ENDIF          ENDIF
422    
423    #ifdef ALLOW_AUTODIFF_TAMC
424    CADJ STORE KPPghat   (:,:,:,bi,bj)
425    CADJ &   , KPPviscAz (:,:,:,bi,bj)
426    CADJ &   , KPPdiffKzT(:,:,:,bi,bj)
427    CADJ &   , KPPdiffKzS(:,:,:,bi,bj)
428    CADJ &   , KPPfrac   (:,:  ,bi,bj)
429    CADJ &                 = comlev1_bibj, key=ikey, byte=isbyte
430    #endif /* ALLOW_AUTODIFF_TAMC */
431    
432  #endif  /* ALLOW_KPP */  #endif  /* ALLOW_KPP */
433    
434  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 398  C note(jmc) : phiHyd=0 at this point but Line 453  C note(jmc) : phiHyd=0 at this point but
453    
454  C--     Start of thermodynamics loop  C--     Start of thermodynamics loop
455          DO k=Nr,1,-1          DO k=Nr,1,-1
456    #ifdef ALLOW_AUTODIFF_TAMC
457    C? Patrick Is this formula correct?
458    cph Yes, but I rewrote it.
459    cph Also, the KappaR? need the index and subscript k!
460             kkey = (ikey-1)*Nr + k
461    #endif /* ALLOW_AUTODIFF_TAMC */
462    
463  C--       km1    Points to level above k (=k-1)  C--       km1    Points to level above k (=k-1)
464  C--       kup    Cycles through 1,2 to point to layer above  C--       kup    Cycles through 1,2 to point to layer above
# Line 412  C--       kDown  Cycles through 2,1 to p Line 473  C--       kDown  Cycles through 2,1 to p
473            jMin = 1-OLy+2            jMin = 1-OLy+2
474            jMax = sNy+OLy-1            jMax = sNy+OLy-1
475    
 #ifdef ALLOW_AUTODIFF_TAMC  
 CPatrick Is this formula correct?  
          kkey = (ikey-1)*(Nr-1+1) + (k-1) + 1  
 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  
 #endif /* ALLOW_AUTODIFF_TAMC */  
   
476  C--      Get temporary terms used by tendency routines  C--      Get temporary terms used by tendency routines
477           CALL CALC_COMMON_FACTORS (           CALL CALC_COMMON_FACTORS (
478       I        bi,bj,iMin,iMax,jMin,jMax,k,km1,kup,kDown,       I        bi,bj,iMin,iMax,jMin,jMax,k,
479       O        xA,yA,uTrans,vTrans,rTrans,maskC,maskUp,       O        xA,yA,uTrans,vTrans,rTrans,maskUp,
480       I        myThid)       I        myThid)
481    
482    #ifdef ALLOW_AUTODIFF_TAMC
483    CADJ STORE KappaRT(:,:,k)    = comlev1_bibj_k, key=kkey, byte=isbyte
484    CADJ STORE KappaRS(:,:,k)    = comlev1_bibj_k, key=kkey, byte=isbyte
485    #endif /* ALLOW_AUTODIFF_TAMC */
486    
487  #ifdef  INCLUDE_CALC_DIFFUSIVITY_CALL  #ifdef  INCLUDE_CALC_DIFFUSIVITY_CALL
488  C--      Calculate the total vertical diffusivity  C--      Calculate the total vertical diffusivity
489           CALL CALC_DIFFUSIVITY(           CALL CALC_DIFFUSIVITY(
490       I        bi,bj,iMin,iMax,jMin,jMax,k,       I        bi,bj,iMin,iMax,jMin,jMax,k,
491       I        maskC,maskup,       I        maskUp,
492       O        KappaRT,KappaRS,KappaRU,KappaRV,       O        KappaRT,KappaRS,KappaRU,KappaRV,
493       I        myThid)       I        myThid)
494  #endif  #endif
# Line 440  C        and step forward storing result Line 498  C        and step forward storing result
498           IF ( tempStepping ) THEN           IF ( tempStepping ) THEN
499             CALL CALC_GT(             CALL CALC_GT(
500       I         bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,       I         bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,
501       I         xA,yA,uTrans,vTrans,rTrans,maskUp,maskC,       I         xA,yA,uTrans,vTrans,rTrans,maskUp,
502       I         KappaRT,       I         KappaRT,
503       U         fVerT,       U         fVerT,
504       I         myTime, myThid)       I         myTime, myThid)
505               tauAB = 0.5d0 + abEps
506             CALL TIMESTEP_TRACER(             CALL TIMESTEP_TRACER(
507       I         bi,bj,iMin,iMax,jMin,jMax,k,       I         bi,bj,iMin,iMax,jMin,jMax,k,tauAB,
508       I         theta, gT,       I         theta, gT,
509       U         gTnm1,       U         gTnm1,
510       I         myIter, myThid)       I         myIter, myThid)
# Line 453  C        and step forward storing result Line 512  C        and step forward storing result
512           IF ( saltStepping ) THEN           IF ( saltStepping ) THEN
513             CALL CALC_GS(             CALL CALC_GS(
514       I         bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,       I         bi,bj,iMin,iMax,jMin,jMax, k,km1,kup,kDown,
515       I         xA,yA,uTrans,vTrans,rTrans,maskUp,maskC,       I         xA,yA,uTrans,vTrans,rTrans,maskUp,
516       I         KappaRS,       I         KappaRS,
517       U         fVerS,       U         fVerS,
518       I         myTime, myThid)       I         myTime, myThid)
519               tauAB = 0.5d0 + abEps
520             CALL TIMESTEP_TRACER(             CALL TIMESTEP_TRACER(
521       I         bi,bj,iMin,iMax,jMin,jMax,k,       I         bi,bj,iMin,iMax,jMin,jMax,k,tauAB,
522       I         salt, gS,       I         salt, gS,
523       U         gSnm1,       U         gSnm1,
524       I         myIter, myThid)       I         myIter, myThid)
# Line 485  C--     end of thermodynamic k loop (Nr: Line 545  C--     end of thermodynamic k loop (Nr:
545    
546    
547  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
548  CPatrick? What about this one?  C? Patrick? What about this one?
549             maximpl = 6  cph Keys iikey and idkey don't seem to be needed
550             iikey = (ikey-1)*maximpl  cph since storing occurs on different tape for each
551    cph impldiff call anyways.
552    cph Thus, common block comlev1_impl isn't needed either.
553    cph Storing below needed in the case useGMREDI.
554            iikey = (ikey-1)*maximpl
555  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
556    
557  C--     Implicit diffusion  C--     Implicit diffusion
# Line 496  C--     Implicit diffusion Line 560  C--     Implicit diffusion
560           IF (tempStepping) THEN           IF (tempStepping) THEN
561  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
562              idkey = iikey + 1              idkey = iikey + 1
563    CADJ STORE gTNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
564  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
565              CALL IMPLDIFF(              CALL IMPLDIFF(
566       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 507  C--     Implicit diffusion Line 572  C--     Implicit diffusion
572           IF (saltStepping) THEN           IF (saltStepping) THEN
573  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
574           idkey = iikey + 2           idkey = iikey + 2
575    CADJ STORE gSNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
576  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
577              CALL IMPLDIFF(              CALL IMPLDIFF(
578       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 533  C--     Start computation of dynamics Line 599  C--     Start computation of dynamics
599          jMin = 1-OLy+2          jMin = 1-OLy+2
600          jMax = sNy+OLy-1          jMax = sNy+OLy-1
601    
602  C--     Explicit part of the Surface Pressure Gradient (add in TIMESTEP)  C--     Explicit part of the Surface Potentiel Gradient (add in TIMESTEP)
603  C       (note: this loop will be replaced by CALL CALC_GRAD_ETA)  C       (note: this loop will be replaced by CALL CALC_GRAD_ETA)
604          IF (implicSurfPress.NE.1.) THEN          IF (implicSurfPress.NE.1.) THEN
605            DO j=jMin,jMax            CALL CALC_GRAD_PHI_SURF(
606              DO i=iMin,iMax       I         bi,bj,iMin,iMax,jMin,jMax,
607                phiSurfX(i,j) = _recip_dxC(i,j,bi,bj)*gBaro       I         etaN,
608       &           *(cg2d_x(i,j,bi,bj)-cg2d_x(i-1,j,bi,bj))       O         phiSurfX,phiSurfY,
609                phiSurfY(i,j) = _recip_dyC(i,j,bi,bj)*gBaro       I         myThid )                        
      &           *(cg2d_x(i,j,bi,bj)-cg2d_x(i,j-1,bi,bj))  
             ENDDO  
           ENDDO  
610          ENDIF          ENDIF
611    
612  C--     Start of dynamics loop  C--     Start of dynamics loop
# Line 617  C--     Implicit viscosity Line 680  C--     Implicit viscosity
680          IF (implicitViscosity.AND.momStepping) THEN          IF (implicitViscosity.AND.momStepping) THEN
681  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
682            idkey = iikey + 3            idkey = iikey + 3
683    CADJ STORE gUNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
684  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
685            CALL IMPLDIFF(            CALL IMPLDIFF(
686       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 625  C--     Implicit viscosity Line 689  C--     Implicit viscosity
689       I         myThid )       I         myThid )
690  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
691            idkey = iikey + 4            idkey = iikey + 4
692    CADJ STORE gVNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
693  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
694            CALL IMPLDIFF(            CALL IMPLDIFF(
695       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 644  C--      Apply open boundary conditions Line 709  C--      Apply open boundary conditions
709  #ifdef    INCLUDE_CD_CODE  #ifdef    INCLUDE_CD_CODE
710  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
711            idkey = iikey + 5            idkey = iikey + 5
712    CADJ STORE vVelD(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
713  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
714            CALL IMPLDIFF(            CALL IMPLDIFF(
715       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 652  C--      Apply open boundary conditions Line 718  C--      Apply open boundary conditions
718       I         myThid )       I         myThid )
719  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
720            idkey = iikey + 6            idkey = iikey + 6
721    CADJ STORE uVelD(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
722  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
723            CALL IMPLDIFF(            CALL IMPLDIFF(
724       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 670  c         CALL WRITE_FLD_XYZ_RL('PH.',su Line 737  c         CALL WRITE_FLD_XYZ_RL('PH.',su
737  c       ENDIF  c       ENDIF
738  Cjmc(end)  Cjmc(end)
739    
740  #ifdef INCLUDE_DIAGNOSTICS_INTERFACE_CODE  #ifdef ALLOW_TIMEAVE
741          IF (taveFreq.GT.0.) THEN          IF (taveFreq.GT.0.) THEN
742           DO K=1,Nr            CALL TIMEAVE_CUMUL_1T(phiHydtave, phiHyd, Nr,
743            CALL TIMEAVER_1FLD_XYZ(phiHyd, phiHydtave,       I                              deltaTclock, bi, bj, myThid)
      I                              deltaTclock, bi, bj, K, myThid)  
744            IF (ivdc_kappa.NE.0.) THEN            IF (ivdc_kappa.NE.0.) THEN
745              CALL TIMEAVER_1FLD_XYZ(ConvectCount, ConvectCountTave,              CALL TIMEAVE_CUMULATE(ConvectCountTave, ConvectCount, Nr,
746       I                              deltaTclock, bi, bj, K, myThid)       I                              deltaTclock, bi, bj, myThid)
747            ENDIF            ENDIF
          ENDDO  
748          ENDIF          ENDIF
749  #endif /* INCLUDE_DIAGNOSTICS_INTERFACE_CODE */  #endif /* ALLOW_TIMEAVE */
750    
751         ENDDO         ENDDO
752        ENDDO        ENDDO
753    
754    #ifndef EXCLUDE_DEBUGMODE
755          If (debugMode) THEN
756           CALL DEBUG_STATS_RL(1,EtaN,'EtaN (DYNAMICS)',myThid)
757           CALL DEBUG_STATS_RL(Nr,vVel,'Vvel (DYNAMICS)',myThid)
758           CALL DEBUG_STATS_RL(Nr,wVel,'Wvel (DYNAMICS)',myThid)
759           CALL DEBUG_STATS_RL(Nr,theta,'Theta (DYNAMICS)',myThid)
760           CALL DEBUG_STATS_RL(Nr,salt,'Salt (DYNAMICS)',myThid)
761           CALL DEBUG_STATS_RL(Nr,Gu,'Gu (DYNAMICS)',myThid)
762           CALL DEBUG_STATS_RL(Nr,Gv,'Gv (DYNAMICS)',myThid)
763           CALL DEBUG_STATS_RL(Nr,Gt,'Gt (DYNAMICS)',myThid)
764           CALL DEBUG_STATS_RL(Nr,Gs,'Gs (DYNAMICS)',myThid)
765           CALL DEBUG_STATS_RL(Nr,GuNm1,'GuNm1 (DYNAMICS)',myThid)
766           CALL DEBUG_STATS_RL(Nr,GvNm1,'GvNm1 (DYNAMICS)',myThid)
767           CALL DEBUG_STATS_RL(Nr,GtNm1,'GtNm1 (DYNAMICS)',myThid)
768           CALL DEBUG_STATS_RL(Nr,GsNm1,'GsNm1 (DYNAMICS)',myThid)
769          ENDIF
770    #endif
771    
772        RETURN        RETURN
773        END        END

Legend:
Removed from v.1.63  
changed lines
  Added in v.1.70

  ViewVC Help
Powered by ViewVC 1.1.22