/[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.173 by jmc, Fri Aug 15 19:22:06 2014 UTC revision 1.178 by jmc, Mon Nov 28 23:05:05 2016 UTC
# Line 25  C     | SUBROUTINE DYNAMICS Line 25  C     | SUBROUTINE DYNAMICS
25  C     | o Controlling routine for the explicit part of the model  C     | o Controlling routine for the explicit part of the model
26  C     |   dynamics.  C     |   dynamics.
27  C     *==========================================================*  C     *==========================================================*
 C     | This routine evaluates the "dynamics" terms for each  
 C     | block of ocean in turn. Because the blocks of ocean have  
 C     | overlap regions they are independent of one another.  
 C     | If terms involving lateral integrals are needed in this  
 C     | routine care will be needed. Similarly finite-difference  
 C     | operations with stencils wider than the overlap region  
 C     | require special consideration.  
 C     | The algorithm...  
 C     |  
 C     | "Correction Step"  
 C     | =================  
 C     | Here we update the horizontal velocities with the surface  
 C     | pressure such that the resulting flow is either consistent  
 C     | with the free-surface evolution or the rigid-lid:  
 C     |   U[n] = U* + dt x d/dx P  
 C     |   V[n] = V* + dt x d/dy P  
 C     |   W[n] = W* + dt x d/dz P  (NH mode)  
 C     |  
 C     | "Calculation of Gs"  
 C     | ===================  
 C     | This is where all the accelerations and tendencies (ie.  
 C     | physics, parameterizations etc...) are calculated  
 C     |   rho = rho ( theta[n], salt[n] )  
 C     |   b   = b(rho, theta)  
 C     |   K31 = K31 ( rho )  
 C     |   Gu[n] = Gu( u[n], v[n], wVel, b, ... )  
 C     |   Gv[n] = Gv( u[n], v[n], wVel, b, ... )  
 C     |   Gt[n] = Gt( theta[n], u[n], v[n], wVel, K31, ... )  
 C     |   Gs[n] = Gs( salt[n], u[n], v[n], wVel, K31, ... )  
 C     |  
 C     | "Time-stepping" or "Prediction"  
 C     | ================================  
 C     | The models variables are stepped forward with the appropriate  
 C     | time-stepping scheme (currently we use Adams-Bashforth II)  
 C     | - For momentum, the result is always *only* a "prediction"  
 C     | in that the flow may be divergent and will be "corrected"  
 C     | later with a surface pressure gradient.  
 C     | - Normally for tracers the result is the new field at time  
 C     | level [n+1} *BUT* in the case of implicit diffusion the result  
 C     | is also *only* a prediction.  
 C     | - We denote "predictors" with an asterisk (*).  
 C     |   U* = U[n] + dt x ( 3/2 Gu[n] - 1/2 Gu[n-1] )  
 C     |   V* = V[n] + dt x ( 3/2 Gv[n] - 1/2 Gv[n-1] )  
 C     |   theta[n+1] = theta[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )  
 C     |   salt[n+1] = salt[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )  
 C     | With implicit diffusion:  
 C     |   theta* = theta[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )  
 C     |   salt* = salt[n] + dt x ( 3/2 Gt[n] - 1/2 atG[n-1] )  
 C     |   (1 + dt * K * d_zz) theta[n] = theta*  
 C     |   (1 + dt * K * d_zz) salt[n] = salt*  
 C     |  
 C     *==========================================================*  
28  C     \ev  C     \ev
29  C     !USES:  C     !USES:
30        IMPLICIT NONE        IMPLICIT NONE
# Line 183  C     phiSurfX,  ::  gradient of Surface Line 131  C     phiSurfX,  ::  gradient of Surface
131  C     phiSurfY             or geopotential (atmos) in X and Y direction  C     phiSurfY             or geopotential (atmos) in X and Y direction
132  C     guDissip   :: dissipation tendency (all explicit terms), u component  C     guDissip   :: dissipation tendency (all explicit terms), u component
133  C     gvDissip   :: dissipation tendency (all explicit terms), v component  C     gvDissip   :: dissipation tendency (all explicit terms), v component
134  C     KappaRU    :: vertical viscosity for velocity U-component  C     kappaRU    :: vertical viscosity for velocity U-component
135  C     KappaRV    :: vertical viscosity for velocity V-component  C     kappaRV    :: vertical viscosity for velocity V-component
136  C     iMin, iMax :: Ranges and sub-block indices on which calculations  C     iMin, iMax :: Ranges and sub-block indices on which calculations
137  C     jMin, jMax    are applied.  C     jMin, jMax    are applied.
138  C     bi, bj     :: tile indices  C     bi, bj     :: tile indices
# Line 202  C                   are switched with k Line 150  C                   are switched with k
150        _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
151        _RL guDissip(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL guDissip(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
152        _RL gvDissip(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL gvDissip(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
153        _RL KappaRU (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL kappaRU (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr+1)
154        _RL KappaRV (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL kappaRV (1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr+1)
155  #ifdef ALLOW_SMAG_3D  #ifdef ALLOW_SMAG_3D
156  C     str11       :: strain component Vxx @ grid-cell center  C     str11       :: strain component Vxx @ grid-cell center
157  C     str22       :: strain component Vyy @ grid-cell center  C     str22       :: strain component Vyy @ grid-cell center
# Line 324  CHPF$ INDEPENDENT Line 272  CHPF$ INDEPENDENT
272  C--    HPF directive to help TAMC  C--    HPF directive to help TAMC
273  CHPF$  INDEPENDENT, NEW (fVerU,fVerV  CHPF$  INDEPENDENT, NEW (fVerU,fVerV
274  CHPF$&                  ,phiHydF  CHPF$&                  ,phiHydF
275  CHPF$&                  ,KappaRU,KappaRV  CHPF$&                  ,kappaRU,kappaRV
276  CHPF$&                  )  CHPF$&                  )
277  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
278    
# Line 418  CADJ &                 = comlev1_bibj, k Line 366  CADJ &                 = comlev1_bibj, k
366  #ifndef ALLOW_AUTODIFF  #ifndef ALLOW_AUTODIFF
367          IF ( .NOT.momViscosity ) THEN          IF ( .NOT.momViscosity ) THEN
368  #endif  #endif
369            DO k=1,Nr            DO k=1,Nr+1
370             DO j=1-OLy,sNy+OLy             DO j=1-OLy,sNy+OLy
371              DO i=1-OLx,sNx+OLx              DO i=1-OLx,sNx+OLx
372               KappaRU(i,j,k) = 0. _d 0               kappaRU(i,j,k) = 0. _d 0
373               KappaRV(i,j,k) = 0. _d 0               kappaRV(i,j,k) = 0. _d 0
374              ENDDO              ENDDO
375             ENDDO             ENDDO
376            ENDDO            ENDDO
# Line 434  C--     Calculate the total vertical vis Line 382  C--     Calculate the total vertical vis
382          IF ( momViscosity ) THEN          IF ( momViscosity ) THEN
383            CALL CALC_VISCOSITY(            CALL CALC_VISCOSITY(
384       I            bi,bj, iMin,iMax,jMin,jMax,       I            bi,bj, iMin,iMax,jMin,jMax,
385       O            KappaRU, KappaRV,       O            kappaRU, kappaRV,
386       I            myThid )       I            myThid )
387          ENDIF          ENDIF
388  #endif /* INCLUDE_CALC_DIFFUSIVITY_CALL */  #endif /* INCLUDE_CALC_DIFFUSIVITY_CALL */
# Line 448  C--     Calculate the total vertical vis Line 396  C--     Calculate the total vertical vis
396  #endif /* ALLOW_SMAG_3D */  #endif /* ALLOW_SMAG_3D */
397    
398  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
399  CADJ STORE KappaRU(:,:,:)  CADJ STORE kappaRU(:,:,:)
400  CADJ &     = comlev1_bibj, key=idynkey, byte=isbyte  CADJ &     = comlev1_bibj, key=idynkey, byte=isbyte
401  CADJ STORE KappaRV(:,:,:)  CADJ STORE kappaRV(:,:,:)
402  CADJ &     = comlev1_bibj, key=idynkey, byte=isbyte  CADJ &     = comlev1_bibj, key=idynkey, byte=isbyte
403  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
404    
# Line 577  CADJ STORE fVerV(:,:,:) = comlev1_bibj_k Line 525  CADJ STORE fVerV(:,:,:) = comlev1_bibj_k
525  #ifdef ALLOW_MOM_FLUXFORM  #ifdef ALLOW_MOM_FLUXFORM
526                CALL MOM_FLUXFORM(                CALL MOM_FLUXFORM(
527       I         bi,bj,k,iMin,iMax,jMin,jMax,       I         bi,bj,k,iMin,iMax,jMin,jMax,
528       I         KappaRU, KappaRV,       I         kappaRU, kappaRV,
529       U         fVerU(1-OLx,1-OLy,kUp),   fVerV(1-OLx,1-OLy,kUp),       U         fVerU(1-OLx,1-OLy,kUp),   fVerV(1-OLx,1-OLy,kUp),
530       O         fVerU(1-OLx,1-OLy,kDown), fVerV(1-OLx,1-OLy,kDown),       O         fVerU(1-OLx,1-OLy,kDown), fVerV(1-OLx,1-OLy,kDown),
531       O         guDissip, gvDissip,       O         guDissip, gvDissip,
# Line 587  CADJ STORE fVerV(:,:,:) = comlev1_bibj_k Line 535  CADJ STORE fVerV(:,:,:) = comlev1_bibj_k
535  #ifdef ALLOW_MOM_VECINV  #ifdef ALLOW_MOM_VECINV
536               CALL MOM_VECINV(               CALL MOM_VECINV(
537       I         bi,bj,k,iMin,iMax,jMin,jMax,       I         bi,bj,k,iMin,iMax,jMin,jMax,
538       I         KappaRU, KappaRV,       I         kappaRU, kappaRV,
539       I         fVerU(1-OLx,1-OLy,kUp),   fVerV(1-OLx,1-OLy,kUp),       I         fVerU(1-OLx,1-OLy,kUp),   fVerV(1-OLx,1-OLy,kUp),
540       O         fVerU(1-OLx,1-OLy,kDown), fVerV(1-OLx,1-OLy,kDown),       O         fVerU(1-OLx,1-OLy,kDown), fVerV(1-OLx,1-OLy,kDown),
541       O         guDissip, gvDissip,       O         guDissip, gvDissip,
# Line 629  C--     end of dynamics k loop (1:Nr) Line 577  C--     end of dynamics k loop (1:Nr)
577    
578  C--     Implicit Vertical advection & viscosity  C--     Implicit Vertical advection & viscosity
579  #if (defined (INCLUDE_IMPLVERTADV_CODE) && \  #if (defined (INCLUDE_IMPLVERTADV_CODE) && \
580       defined (ALLOW_MOM_COMMON) && !(defined ALLOW_AUTODIFF_TAMC))       defined (ALLOW_MOM_COMMON) && !(defined ALLOW_AUTODIFF))
581          IF ( momImplVertAdv ) THEN          IF ( momImplVertAdv .OR. implicitViscosity
582         &                      .OR. selectImplicitDrag.GE.1 ) THEN
583    C      to recover older (prior to 2016-10-05) results:
584    c       IF ( momImplVertAdv ) THEN
585            CALL MOM_U_IMPLICIT_R( kappaRU,            CALL MOM_U_IMPLICIT_R( kappaRU,
586       I                           bi, bj, myTime, myIter, myThid )       I                           bi, bj, myTime, myIter, myThid )
587            CALL MOM_V_IMPLICIT_R( kappaRV,            CALL MOM_V_IMPLICIT_R( kappaRV,
# Line 644  CADJ STORE gU(:,:,:,bi,bj) = comlev1_bib Line 595  CADJ STORE gU(:,:,:,bi,bj) = comlev1_bib
595  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
596            CALL IMPLDIFF(            CALL IMPLDIFF(
597       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
598       I         -1, KappaRU, recip_hFacW(1-OLx,1-OLy,1,bi,bj),       I         -1, kappaRU, recip_hFacW(1-OLx,1-OLy,1,bi,bj),
599       U         gU(1-OLx,1-OLy,1,bi,bj),       U         gU(1-OLx,1-OLy,1,bi,bj),
600       I         myThid )       I         myThid )
601  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
# Line 652  CADJ STORE gV(:,:,:,bi,bj) = comlev1_bib Line 603  CADJ STORE gV(:,:,:,bi,bj) = comlev1_bib
603  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
604            CALL IMPLDIFF(            CALL IMPLDIFF(
605       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
606       I         -2, KappaRV, recip_hFacS(1-OLx,1-OLy,1,bi,bj),       I         -2, kappaRV, recip_hFacS(1-OLx,1-OLy,1,bi,bj),
607       U         gV(1-OLx,1-OLy,1,bi,bj),       U         gV(1-OLx,1-OLy,1,bi,bj),
608       I         myThid )       I         myThid )
609          ENDIF          ENDIF
# Line 676  CADJ STORE vVelD(:,:,:,bi,bj) = comlev1_ Line 627  CADJ STORE vVelD(:,:,:,bi,bj) = comlev1_
627  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
628            CALL IMPLDIFF(            CALL IMPLDIFF(
629       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
630       I         0, KappaRU, recip_hFacW(1-OLx,1-OLy,1,bi,bj),       I         0, kappaRU, recip_hFacW(1-OLx,1-OLy,1,bi,bj),
631       U         vVelD(1-OLx,1-OLy,1,bi,bj),       U         vVelD(1-OLx,1-OLy,1,bi,bj),
632       I         myThid )       I         myThid )
633  #ifdef    ALLOW_AUTODIFF_TAMC  #ifdef    ALLOW_AUTODIFF_TAMC
# Line 684  CADJ STORE uVelD(:,:,:,bi,bj) = comlev1_ Line 635  CADJ STORE uVelD(:,:,:,bi,bj) = comlev1_
635  #endif    /* ALLOW_AUTODIFF_TAMC */  #endif    /* ALLOW_AUTODIFF_TAMC */
636            CALL IMPLDIFF(            CALL IMPLDIFF(
637       I         bi, bj, iMin, iMax, jMin, jMax,       I         bi, bj, iMin, iMax, jMin, jMax,
638       I         0, KappaRV, recip_hFacS(1-OLx,1-OLy,1,bi,bj),       I         0, kappaRV, recip_hFacS(1-OLx,1-OLy,1,bi,bj),
639       U         uVelD(1-OLx,1-OLy,1,bi,bj),       U         uVelD(1-OLx,1-OLy,1,bi,bj),
640       I         myThid )       I         myThid )
641          ENDIF          ENDIF
# Line 701  C--   Step forward W field in N-H algori Line 652  C--   Step forward W field in N-H algori
652  #endif  #endif
653           CALL TIMER_START('CALC_GW          [DYNAMICS]',myThid)           CALL TIMER_START('CALC_GW          [DYNAMICS]',myThid)
654           CALL CALC_GW(           CALL CALC_GW(
655       I                 bi,bj, KappaRU, KappaRV,       I                 bi,bj, kappaRU, kappaRV,
656       I                 str13, str23, str33,       I                 str13, str23, str33,
657       I                 viscAh3d_00, viscAh3d_13, viscAh3d_23,       I                 viscAh3d_00, viscAh3d_13, viscAh3d_23,
658       I                 myTime, myIter, myThid )       I                 myTime, myIter, myThid )

Legend:
Removed from v.1.173  
changed lines
  Added in v.1.178

  ViewVC Help
Powered by ViewVC 1.1.22