/[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.60 by adcroft, Wed Feb 7 16:28:54 2001 UTC revision 1.66 by heimbach, Sun Mar 25 22:33:52 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 40  C     == Global variables === Line 39  C     == Global variables ===
39  # include "KPP.h"  # include "KPP.h"
40  #endif  #endif
41    
42    #ifdef ALLOW_TIMEAVE
43    #include "TIMEAVE_STATV.h"
44    #endif
45    
46  C     == Routine arguments ==  C     == Routine arguments ==
47  C     myTime - Current time in simulation  C     myTime - Current time in simulation
48  C     myIter - Current iteration number in simulation  C     myIter - Current iteration number in simulation
# Line 52  C     == Local variables Line 55  C     == Local variables
55  C     xA, yA                 - Per block temporaries holding face areas  C     xA, yA                 - Per block temporaries holding face areas
56  C     uTrans, vTrans, rTrans - Per block temporaries holding flow  C     uTrans, vTrans, rTrans - Per block temporaries holding flow
57  C                              transport  C                              transport
58  C     rVel                     o uTrans: Zonal transport  C                              o uTrans: Zonal transport
59  C                              o vTrans: Meridional transport  C                              o vTrans: Meridional transport
60  C                              o rTrans: Vertical transport  C                              o rTrans: Vertical transport
 C                              o rVel:   Vertical velocity at upper and  
 C                                        lower cell faces.  
61  C     maskC,maskUp             o maskC: land/water mask for tracer cells  C     maskC,maskUp             o maskC: land/water mask for tracer cells
62  C                              o maskUp: land/water mask for W points  C                              o maskUp: land/water mask for W points
63  C     fVer[STUV]               o fVer: Vertical flux term - note fVer  C     fVer[STUV]               o fVer: Vertical flux term - note fVer
# Line 66  C                                      v Line 67  C                                      v
67  C     rhoK, rhoKM1   - Density at current level, and level above  C     rhoK, rhoKM1   - Density at current level, and level above
68  C     phiHyd         - Hydrostatic part of the potential phiHydi.  C     phiHyd         - Hydrostatic part of the potential phiHydi.
69  C                      In z coords phiHydiHyd is the hydrostatic  C                      In z coords phiHydiHyd is the hydrostatic
70  C                      pressure anomaly  C                      Potential (=pressure/rho0) anomaly
71  C                      In p coords phiHydiHyd is the geopotential  C                      In p coords phiHydiHyd is the geopotential
72  C                      surface height  C                      surface height anomaly.
73  C                      anomaly.  C     phiSurfX, - gradient of Surface potentiel (Pressure/rho, ocean)
74  C     etaSurfX,      - Holds surface elevation gradient in X and Y.  C     phiSurfY             or geopotentiel (atmos) in X and Y direction
 C     etaSurfY  
75  C     KappaRT,       - Total diffusion in vertical for T and S.  C     KappaRT,       - Total diffusion in vertical for T and S.
76  C     KappaRS          (background + spatially varying, isopycnal term).  C     KappaRS          (background + spatially varying, isopycnal term).
77  C     iMin, iMax     - Ranges and sub-block indices on which calculations  C     iMin, iMax     - Ranges and sub-block indices on which calculations
# Line 85  C                      index into fVerTe Line 85  C                      index into fVerTe
85        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
86        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
87        _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)  
88        _RS maskC   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskC   (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
89        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
90        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerT   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
# Line 95  C                      index into fVerTe Line 94  C                      index into fVerTe
94        _RL phiHyd  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL phiHyd  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
95        _RL rhokm1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhokm1  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96        _RL rhok    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rhok    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
97          _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98          _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
99        _RL KappaRT (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)        _RL KappaRT (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
100        _RL KappaRS (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)        _RL KappaRS (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
101        _RL KappaRU (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)        _RL KappaRU (1-Olx:sNx+Olx,1-Oly:sNy+Oly,Nr)
# Line 103  C                      index into fVerTe Line 104  C                      index into fVerTe
104        _RL sigmaY  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaY  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
105        _RL sigmaR  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL sigmaR  (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
106    
107  C This is currently also used by IVDC and Diagnostics  C This is currently used by IVDC and Diagnostics
 C #ifdef INCLUDE_CONVECT_CALL  
108        _RL ConvectCount (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL ConvectCount (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
 C #endif  
109    
110        INTEGER iMin, iMax        INTEGER iMin, iMax
111        INTEGER jMin, jMax        INTEGER jMin, jMax
# Line 114  C #endif Line 113  C #endif
113        INTEGER i, j        INTEGER i, j
114        INTEGER k, km1, kup, kDown        INTEGER k, km1, kup, kDown
115    
116  #ifdef ALLOW_AUTODIFF_TAMC  Cjmc : add for phiHyd output <- but not working if multi tile per CPU
117        INTEGER    isbyte  c     CHARACTER*(MAX_LEN_MBUF) suff
118        PARAMETER( isbyte = 4 )  c     LOGICAL  DIFFERENT_MULTIPLE
119    c     EXTERNAL DIFFERENT_MULTIPLE
120        INTEGER act1, act2, act3, act4  Cjmc(end)
121        INTEGER max1, max2, max3  
       INTEGER iikey, kkey  
       INTEGER maximpl  
 #endif /* ALLOW_AUTODIFF_TAMC */  
   
122  C---    The algorithm...  C---    The algorithm...
123  C  C
124  C       "Correction Step"  C       "Correction Step"
# Line 138  C       "Calculation of Gs" Line 133  C       "Calculation of Gs"
133  C       ===================  C       ===================
134  C       This is where all the accelerations and tendencies (ie.  C       This is where all the accelerations and tendencies (ie.
135  C       physics, parameterizations etc...) are calculated  C       physics, parameterizations etc...) are calculated
 C         rVel = sum_r ( div. u[n] )  
136  C         rho = rho ( theta[n], salt[n] )  C         rho = rho ( theta[n], salt[n] )
137  C         b   = b(rho, theta)  C         b   = b(rho, theta)
138  C         K31 = K31 ( rho )  C         K31 = K31 ( rho )
139  C         Gu[n] = Gu( u[n], v[n], rVel, b, ... )  C         Gu[n] = Gu( u[n], v[n], wVel, b, ... )
140  C         Gv[n] = Gv( u[n], v[n], rVel, b, ... )  C         Gv[n] = Gv( u[n], v[n], wVel, b, ... )
141  C         Gt[n] = Gt( theta[n], u[n], v[n], rVel, K31, ... )  C         Gt[n] = Gt( theta[n], u[n], v[n], wVel, K31, ... )
142  C         Gs[n] = Gs( salt[n], u[n], v[n], rVel, K31, ... )  C         Gs[n] = Gs( salt[n], u[n], v[n], wVel, K31, ... )
143  C  C
144  C       "Time-stepping" or "Prediction"  C       "Time-stepping" or "Prediction"
145  C       ================================  C       ================================
# Line 196  C     uninitialised but inert locations. Line 190  C     uninitialised but inert locations.
190          rhoKM1 (i,j) = 0. _d 0          rhoKM1 (i,j) = 0. _d 0
191          rhok   (i,j) = 0. _d 0          rhok   (i,j) = 0. _d 0
192          maskC  (i,j) = 0. _d 0          maskC  (i,j) = 0. _d 0
193            phiSurfX(i,j) = 0. _d 0
194            phiSurfY(i,j) = 0. _d 0
195         ENDDO         ENDDO
196        ENDDO        ENDDO
197    
# Line 209  CHPF$ INDEPENDENT Line 205  CHPF$ INDEPENDENT
205    
206  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
207  C--    HPF directive to help TAMC  C--    HPF directive to help TAMC
208  CHPF$  INDEPENDENT, NEW (rTrans,rVel,fVerT,fVerS,fVerU,fVerV  CHPF$  INDEPENDENT, NEW (rTrans,fVerT,fVerS,fVerU,fVerV
209  CHPF$&                  ,phiHyd,utrans,vtrans,maskc,xA,yA  CHPF$&                  ,phiHyd,utrans,vtrans,maskc,xA,yA
210  CHPF$&                  ,KappaRT,KappaRS,KappaRU,KappaRV  CHPF$&                  ,KappaRT,KappaRS,KappaRU,KappaRV
211  CHPF$&                  )  CHPF$&                  )
# Line 238  C--     Set up work arrays that need val Line 234  C--     Set up work arrays that need val
234          DO j=1-OLy,sNy+OLy          DO j=1-OLy,sNy+OLy
235           DO i=1-OLx,sNx+OLx           DO i=1-OLx,sNx+OLx
236            rTrans(i,j)   = 0. _d 0            rTrans(i,j)   = 0. _d 0
           rVel  (i,j,1) = 0. _d 0  
           rVel  (i,j,2) = 0. _d 0  
237            fVerT (i,j,1) = 0. _d 0            fVerT (i,j,1) = 0. _d 0
238            fVerT (i,j,2) = 0. _d 0            fVerT (i,j,2) = 0. _d 0
239            fVerS (i,j,1) = 0. _d 0            fVerS (i,j,1) = 0. _d 0
# Line 254  C--     Set up work arrays that need val Line 248  C--     Set up work arrays that need val
248          DO k=1,Nr          DO k=1,Nr
249           DO j=1-OLy,sNy+OLy           DO j=1-OLy,sNy+OLy
250            DO i=1-OLx,sNx+OLx            DO i=1-OLx,sNx+OLx
251  #ifdef INCLUDE_CONVECT_CALL  C This is currently also used by IVDC and Diagnostics
252             ConvectCount(i,j,k) = 0.             ConvectCount(i,j,k) = 0.
 #endif  
253             KappaRT(i,j,k) = 0. _d 0             KappaRT(i,j,k) = 0. _d 0
254             KappaRS(i,j,k) = 0. _d 0             KappaRS(i,j,k) = 0. _d 0
255            ENDDO            ENDDO
# Line 269  C--     Set up work arrays that need val Line 262  C--     Set up work arrays that need val
262          jMax = sNy+OLy          jMax = sNy+OLy
263    
264    
265    #ifdef ALLOW_AUTODIFF_TAMC
266    CADJ STORE theta(:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
267    CADJ STORE salt (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
268    CADJ STORE uvel(:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
269    CADJ STORE vvel (:,:,:,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
270    #endif /* ALLOW_AUTODIFF_TAMC */
271    
272  C--     Start of diagnostic loop  C--     Start of diagnostic loop
273          DO k=Nr,1,-1          DO k=Nr,1,-1
274    
275  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
276  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?
277  C? Do we still need this?  C? Do we still need this?
278           kkey = (ikey-1)*(Nr-2+1) + (k-2) + 1  cph kkey formula corrected.
279    cph Needed for rhok, rhokm1, in the case useGMREDI.
280             kkey = (ikey-1)*Nr + k
281    CADJ STORE rhokm1(:,:) = comlev1_bibj_k , key = kkey, byte = isbyte
282    CADJ STORE rhok  (:,:) = comlev1_bibj_k , key = kkey, byte = isbyte
283  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
284    
285  C--       Integrate continuity vertically for vertical velocity  C--       Integrate continuity vertically for vertical velocity
# Line 322  c ==> should use sigmaR !!! Line 326  c ==> should use sigmaR !!!
326       I        rhoKm1, rhoK,       I        rhoKm1, rhoK,
327       U        ConvectCount, KappaRT, KappaRS,       U        ConvectCount, KappaRT, KappaRS,
328       I        myTime, myIter, myThid)       I        myTime, myIter, myThid)
329            END IF            ENDIF
330    
331  C--     end of diagnostic k loop (Nr:1)  C--     end of diagnostic k loop (Nr:1)
332          ENDDO          ENDDO
# Line 368  C--     Compute KPP mixing coefficients Line 372  C--     Compute KPP mixing coefficients
372          IF (useKPP) THEN          IF (useKPP) THEN
373            CALL KPP_CALC(            CALL KPP_CALC(
374       I                  bi, bj, myTime, myThid )       I                  bi, bj, myTime, myThid )
375    #ifdef ALLOW_AUTODIFF_TAMC
376            ELSE
377              DO j=1-OLy,sNy+OLy
378                DO i=1-OLx,sNx+OLx
379                  KPPhbl (i,j,bi,bj) = 1.0
380                  KPPfrac(i,j,bi,bj) = 0.0
381                  DO k = 1,Nr
382                     KPPghat   (i,j,k,bi,bj) = 0.0
383                     KPPviscAz (i,j,k,bi,bj) = viscAz
384                     KPPdiffKzT(i,j,k,bi,bj) = diffKzT
385                     KPPdiffKzS(i,j,k,bi,bj) = diffKzS
386                  ENDDO
387                ENDDO
388              ENDDO
389    #endif /* ALLOW_AUTODIFF_TAMC */
390          ENDIF          ENDIF
391    
392    #ifdef ALLOW_AUTODIFF_TAMC
393    CADJ STORE KPPghat   (:,:,:,bi,bj)
394    CADJ &   , KPPviscAz (:,:,:,bi,bj)
395    CADJ &   , KPPdiffKzT(:,:,:,bi,bj)
396    CADJ &   , KPPdiffKzS(:,:,:,bi,bj)
397    CADJ &   , KPPfrac   (:,:  ,bi,bj)
398    CADJ &                 = comlev1_bibj, key=ikey, byte=isbyte
399    #endif /* ALLOW_AUTODIFF_TAMC */
400    
401  #endif  /* ALLOW_KPP */  #endif  /* ALLOW_KPP */
402    
403  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 408  C--       kDown  Cycles through 2,1 to p Line 437  C--       kDown  Cycles through 2,1 to p
437            jMax = sNy+OLy-1            jMax = sNy+OLy-1
438    
439  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
440  CPatrick Is this formula correct?  C? Patrick Is this formula correct?
441           kkey = (ikey-1)*(Nr-1+1) + (k-1) + 1  cph Yes, but I rewrote it.
442  CADJ STORE rvel  (:,:,kDown) = comlev1_bibj_k, key = kkey, byte = isbyte  cph Also, the KappaR? need the index k!
443  CADJ STORE rTrans(:,:)       = comlev1_bibj_k, key = kkey, byte = isbyte           kkey = (ikey-1)*Nr + k
444  CADJ STORE KappaRT(:,:,:)    = comlev1_bibj_k, key = kkey, byte = isbyte  CADJ STORE KappaRT(:,:,k)    = comlev1_bibj_k, key = kkey, byte = isbyte
445  CADJ STORE KappaRS(:,:,:)    = comlev1_bibj_k, key = kkey, byte = isbyte  CADJ STORE KappaRS(:,:,k)    = comlev1_bibj_k, key = kkey, byte = isbyte
446  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
447    
448  C--      Get temporary terms used by tendency routines  C--      Get temporary terms used by tendency routines
449           CALL CALC_COMMON_FACTORS (           CALL CALC_COMMON_FACTORS (
450       I        bi,bj,iMin,iMax,jMin,jMax,k,km1,kup,kDown,       I        bi,bj,iMin,iMax,jMin,jMax,k,km1,kup,kDown,
451       O        xA,yA,uTrans,vTrans,rTrans,rVel,maskC,maskUp,       O        xA,yA,uTrans,vTrans,rTrans,maskC,maskUp,
452       I        myThid)       I        myThid)
453    
454  #ifdef  INCLUDE_CALC_DIFFUSIVITY_CALL  #ifdef  INCLUDE_CALC_DIFFUSIVITY_CALL
# Line 481  C--     end of thermodynamic k loop (Nr: Line 510  C--     end of thermodynamic k loop (Nr:
510    
511    
512  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
513  CPatrick? What about this one?  C? Patrick? What about this one?
514             maximpl = 6  cph Keys iikey and idkey don't seem to be needed
515             iikey = (ikey-1)*maximpl  cph since storing occurs on different tape for each
516    cph impldiff call anyways.
517    cph Thus, common block comlev1_impl isn't needed either.
518    cph Storing below needed in the case useGMREDI.
519            iikey = (ikey-1)*maximpl
520  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
521    
522  C--     Implicit diffusion  C--     Implicit diffusion
523          IF (implicitDiffusion) THEN          IF (implicitDiffusion) THEN
524    
525            IF (tempStepping) THEN           IF (tempStepping) THEN
526  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
527              idkey = iikey + 1              idkey = iikey + 1
528    CADJ STORE gTNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
529  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
530              CALL IMPLDIFF(              CALL IMPLDIFF(
531       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 503  C--     Implicit diffusion Line 537  C--     Implicit diffusion
537           IF (saltStepping) THEN           IF (saltStepping) THEN
538  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
539           idkey = iikey + 2           idkey = iikey + 2
540    CADJ STORE gSNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
541  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
542              CALL IMPLDIFF(              CALL IMPLDIFF(
543       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 523  C--      Apply open boundary conditions Line 558  C--      Apply open boundary conditions
558  C--     End If implicitDiffusion  C--     End If implicitDiffusion
559          ENDIF          ENDIF
560    
561    C--     Start computation of dynamics
562            iMin = 1-OLx+2
563            iMax = sNx+OLx-1
564            jMin = 1-OLy+2
565            jMax = sNy+OLy-1
566    
567    C--     Explicit part of the Surface Potentiel Gradient (add in TIMESTEP)
568    C       (note: this loop will be replaced by CALL CALC_GRAD_ETA)
569            IF (implicSurfPress.NE.1.) THEN
570              CALL CALC_GRAD_PHI_SURF(
571         I         bi,bj,iMin,iMax,jMin,jMax,
572         I         etaN,
573         O         phiSurfX,phiSurfY,
574         I         myThid )                        
575            ENDIF
576    
577  C--     Start of dynamics loop  C--     Start of dynamics loop
578          DO k=1,Nr          DO k=1,Nr
# Line 536  C--       kDown  Cycles through 2,1 to p Line 585  C--       kDown  Cycles through 2,1 to p
585            kup  = 1+MOD(k+1,2)            kup  = 1+MOD(k+1,2)
586            kDown= 1+MOD(k,2)            kDown= 1+MOD(k,2)
587    
           iMin = 1-OLx+2  
           iMax = sNx+OLx-1  
           jMin = 1-OLy+2  
           jMax = sNy+OLy-1  
   
588  C--      Integrate hydrostatic balance for phiHyd with BC of  C--      Integrate hydrostatic balance for phiHyd with BC of
589  C        phiHyd(z=0)=0  C        phiHyd(z=0)=0
590  C        distinguishe between Stagger and Non Stagger time stepping  C        distinguishe between Stagger and Non Stagger time stepping
# Line 567  C        and step forward storing the re Line 611  C        and step forward storing the re
611       U         fVerU, fVerV,       U         fVerU, fVerV,
612       I         myTime, myThid)       I         myTime, myThid)
613             CALL TIMESTEP(             CALL TIMESTEP(
614       I         bi,bj,iMin,iMax,jMin,jMax,k,phiHyd,       I         bi,bj,iMin,iMax,jMin,jMax,k,
615         I         phiHyd, phiSurfX, phiSurfY,
616       I         myIter, myThid)       I         myIter, myThid)
617    
618  #ifdef   ALLOW_OBCS  #ifdef   ALLOW_OBCS
# Line 600  C--     Implicit viscosity Line 645  C--     Implicit viscosity
645          IF (implicitViscosity.AND.momStepping) THEN          IF (implicitViscosity.AND.momStepping) THEN
646  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
647            idkey = iikey + 3            idkey = iikey + 3
648    CADJ STORE gUNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
649  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
650            CALL IMPLDIFF(            CALL IMPLDIFF(
651       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 608  C--     Implicit viscosity Line 654  C--     Implicit viscosity
654       I         myThid )       I         myThid )
655  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
656            idkey = iikey + 4            idkey = iikey + 4
657    CADJ STORE gVNm1(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
658  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
659            CALL IMPLDIFF(            CALL IMPLDIFF(
660       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 627  C--      Apply open boundary conditions Line 674  C--      Apply open boundary conditions
674  #ifdef    INCLUDE_CD_CODE  #ifdef    INCLUDE_CD_CODE
675  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
676            idkey = iikey + 5            idkey = iikey + 5
677    CADJ STORE vVelD(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
678  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
679            CALL IMPLDIFF(            CALL IMPLDIFF(
680       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 635  C--      Apply open boundary conditions Line 683  C--      Apply open boundary conditions
683       I         myThid )       I         myThid )
684  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
685            idkey = iikey + 6            idkey = iikey + 6
686    CADJ STORE uVelD(:,:,:,bi,bj) = comlev1_bibj , key=ikey, byte=isbyte
687  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
688            CALL IMPLDIFF(            CALL IMPLDIFF(
689       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
# Line 645  C--      Apply open boundary conditions Line 694  C--      Apply open boundary conditions
694  C--     End If implicitViscosity.AND.momStepping  C--     End If implicitViscosity.AND.momStepping
695          ENDIF          ENDIF
696    
697    Cjmc : add for phiHyd output <- but not working if multi tile per CPU
698    c       IF ( DIFFERENT_MULTIPLE(dumpFreq,myTime+deltaTClock,myTime)
699    c    &  .AND. buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
700    c         WRITE(suff,'(I10.10)') myIter+1
701    c         CALL WRITE_FLD_XYZ_RL('PH.',suff,phiHyd,myIter+1,myThid)
702    c       ENDIF
703    Cjmc(end)
704    
705    #ifdef ALLOW_TIMEAVE
706            IF (taveFreq.GT.0.) THEN
707              CALL TIMEAVE_CUMULATE(phiHydtave, phiHyd, Nr,
708         I                              deltaTclock, bi, bj, myThid)
709              IF (ivdc_kappa.NE.0.) THEN
710                CALL TIMEAVE_CUMULATE(ConvectCountTave, ConvectCount, Nr,
711         I                              deltaTclock, bi, bj, myThid)
712              ENDIF
713            ENDIF
714    #endif /* ALLOW_TIMEAVE */
715    
716         ENDDO         ENDDO
717        ENDDO        ENDDO
718    

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

  ViewVC Help
Powered by ViewVC 1.1.22