/[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.139 by jmc, Mon Nov 5 18:52:21 2007 UTC revision 1.144 by jmc, Sat Jan 16 22:55:53 2010 UTC
# Line 15  C     !INTERFACE: Line 15  C     !INTERFACE:
15        SUBROUTINE DYNAMICS(myTime, myIter, myThid)        SUBROUTINE DYNAMICS(myTime, myIter, myThid)
16  C     !DESCRIPTION: \bv  C     !DESCRIPTION: \bv
17  C     *==========================================================*  C     *==========================================================*
18  C     | SUBROUTINE DYNAMICS                                        C     | SUBROUTINE DYNAMICS
19  C     | o Controlling routine for the explicit part of the model    C     | o Controlling routine for the explicit part of the model
20  C     |   dynamics.                                                C     |   dynamics.
21  C     *==========================================================*  C     *==========================================================*
22  C     | This routine evaluates the "dynamics" terms for each        C     | This routine evaluates the "dynamics" terms for each
23  C     | block of ocean in turn. Because the blocks of ocean have    C     | block of ocean in turn. Because the blocks of ocean have
24  C     | overlap regions they are independent of one another.        C     | overlap regions they are independent of one another.
25  C     | If terms involving lateral integrals are needed in this    C     | If terms involving lateral integrals are needed in this
26  C     | routine care will be needed. Similarly finite-difference    C     | routine care will be needed. Similarly finite-difference
27  C     | operations with stencils wider than the overlap region      C     | operations with stencils wider than the overlap region
28  C     | require special consideration.                              C     | require special consideration.
29  C     | The algorithm...  C     | The algorithm...
30  C     |  C     |
31  C     | "Correction Step"  C     | "Correction Step"
# Line 139  C      |-- DEBUG_STATS_RL Line 139  C      |-- DEBUG_STATS_RL
139    
140  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
141  C     == Routine arguments ==  C     == Routine arguments ==
142  C     myTime - Current time in simulation  C     myTime :: Current time in simulation
143  C     myIter - Current iteration number in simulation  C     myIter :: Current iteration number in simulation
144  C     myThid - Thread number for this instance of the routine.  C     myThid :: Thread number for this instance of the routine.
145        _RL myTime        _RL myTime
146        INTEGER myIter        INTEGER myIter
147        INTEGER myThid        INTEGER myThid
# Line 162  C     phiSurfX,  ::  gradient of Surface Line 162  C     phiSurfX,  ::  gradient of Surface
162  C     phiSurfY             or geopotential (atmos) in X and Y direction  C     phiSurfY             or geopotential (atmos) in X and Y direction
163  C     guDissip   :: dissipation tendency (all explicit terms), u component  C     guDissip   :: dissipation tendency (all explicit terms), u component
164  C     gvDissip   :: dissipation tendency (all explicit terms), v component  C     gvDissip   :: dissipation tendency (all explicit terms), v component
165  C     KappaRU:: vertical viscosity  C     KappaRU    :: vertical viscosity
166  C     KappaRV:: vertical viscosity  C     KappaRV    :: vertical viscosity
167  C     iMin, iMax     - Ranges and sub-block indices on which calculations  C     iMin, iMax     - Ranges and sub-block indices on which calculations
168  C     jMin, jMax       are applied.  C     jMin, jMax       are applied.
169  C     bi, bj  C     bi, bj
170  C     k, kup,        - Index for layer above and below. kup and kDown  C     k, kup,        - Index for layer above and below. kup and kDown
171  C     kDown, km1       are switched with layer to be the appropriate  C     kDown, km1       are switched with layer to be the appropriate
172  C                      index into fVerTerm.  C                      index into fVerTerm.
173        _RL fVerU   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerU   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
174        _RL fVerV   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerV   (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
# Line 287  C     just ensure that all memory refere Line 287  C     just ensure that all memory refere
287  C     point numbers. This prevents spurious hardware signals due to  C     point numbers. This prevents spurious hardware signals due to
288  C     uninitialised but inert locations.  C     uninitialised but inert locations.
289    
290    #ifdef ALLOW_AUTODIFF_TAMC
291          DO k=1,Nr          DO k=1,Nr
292           DO j=1-OLy,sNy+OLy           DO j=1-OLy,sNy+OLy
293            DO i=1-OLx,sNx+OLx            DO i=1-OLx,sNx+OLx
294             KappaRU(i,j,k) = 0. _d 0             KappaRU(i,j,k) = 0. _d 0
295             KappaRV(i,j,k) = 0. _d 0             KappaRV(i,j,k) = 0. _d 0
 #ifdef ALLOW_AUTODIFF_TAMC  
296  cph(  cph(
297  c--   need some re-initialisation here to break dependencies  c--   need some re-initialisation here to break dependencies
298  cph)  cph)
299             gU(i,j,k,bi,bj) = 0. _d 0             gU(i,j,k,bi,bj) = 0. _d 0
300             gV(i,j,k,bi,bj) = 0. _d 0             gV(i,j,k,bi,bj) = 0. _d 0
 #endif  
301            ENDDO            ENDDO
302           ENDDO           ENDDO
303          ENDDO          ENDDO
304    #endif /* ALLOW_AUTODIFF_TAMC */
305          DO j=1-OLy,sNy+OLy          DO j=1-OLy,sNy+OLy
306           DO i=1-OLx,sNx+OLx           DO i=1-OLx,sNx+OLx
307            fVerU  (i,j,1) = 0. _d 0            fVerU  (i,j,1) = 0. _d 0
# Line 317  cph) Line 317  cph)
317            guDissip(i,j)  = 0. _d 0            guDissip(i,j)  = 0. _d 0
318            gvDissip(i,j)  = 0. _d 0            gvDissip(i,j)  = 0. _d 0
319  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
320              phiHydLow(i,j,bi,bj) = 0. _d 0
321  # ifdef NONLIN_FRSURF  # ifdef NONLIN_FRSURF
322  #  ifndef DISABLE_RSTAR_CODE  #  ifndef DISABLE_RSTAR_CODE
323            dWtransC(i,j,bi,bj) = 0. _d 0            dWtransC(i,j,bi,bj) = 0. _d 0
# Line 336  C--     Start computation of dynamics Line 337  C--     Start computation of dynamics
337    
338  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
339  CADJ STORE wvel (:,:,:,bi,bj) =  CADJ STORE wvel (:,:,:,bi,bj) =
340  CADJ &     comlev1_bibj, key = idynkey, byte = isbyte  CADJ &     comlev1_bibj, key=idynkey, byte=isbyte
341  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
342    
343  C--     Explicit part of the Surface Potentiel Gradient (add in TIMESTEP)  C--     Explicit part of the Surface Potentiel Gradient (add in TIMESTEP)
# Line 359  CADJ &                 = comlev1_bibj, k Line 360  CADJ &                 = comlev1_bibj, k
360  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
361    
362  #ifdef  INCLUDE_CALC_DIFFUSIVITY_CALL  #ifdef  INCLUDE_CALC_DIFFUSIVITY_CALL
363  C--      Calculate the total vertical diffusivity  C--     Calculate the total vertical viscosity
364            CALL CALC_VISCOSITY(
365         I            bi,bj, iMin,iMax,jMin,jMax,
366         O            KappaRU, KappaRV,
367         I            myThid )
368    #else
369          DO k=1,Nr          DO k=1,Nr
370           CALL CALC_VISCOSITY(           DO j=1-OLy,sNy+OLy
371       I        bi,bj,iMin,iMax,jMin,jMax,k,            DO i=1-OLx,sNx+OLx
372       O        KappaRU,KappaRV,             KappaRU(i,j,k) = 0. _d 0
373       I        myThid)             KappaRV(i,j,k) = 0. _d 0
374         ENDDO            ENDDO
375             ENDDO
376            ENDDO
377  #endif  #endif
378    
379  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
# Line 387  C--       kDown  Cycles through 2,1 to p Line 395  C--       kDown  Cycles through 2,1 to p
395            kup  = 1+MOD(k+1,2)            kup  = 1+MOD(k+1,2)
396            kDown= 1+MOD(k,2)            kDown= 1+MOD(k,2)
397    
398  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
399           kkey = (idynkey-1)*Nr + k           kkey = (idynkey-1)*Nr + k
400  c  c
401  CADJ STORE totphihyd (:,:,k,bi,bj)  CADJ STORE totphihyd (:,:,k,bi,bj)
402  CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
403    CADJ STORE phihydlow (:,:,bi,bj)
404    CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
405  CADJ STORE theta (:,:,k,bi,bj)  CADJ STORE theta (:,:,k,bi,bj)
406  CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
407  CADJ STORE salt  (:,:,k,bi,bj)  CADJ STORE salt  (:,:,k,bi,bj)
# Line 441  CADJ &     = comlev1_bibj_k, key=kkey, b Line 451  CADJ &     = comlev1_bibj_k, key=kkey, b
451  # endif  # endif
452  #endif /* ALLOW_AUTODIFF_TAMC */  #endif /* ALLOW_AUTODIFF_TAMC */
453    
454  C--      Integrate hydrostatic balance for phiHyd with BC of  C--      Integrate hydrostatic balance for phiHyd with BC of
455  C        phiHyd(z=0)=0  C        phiHyd(z=0)=0
456           IF ( implicitIntGravWave ) THEN           IF ( implicitIntGravWave ) THEN
457             CALL CALC_PHI_HYD(             CALL CALC_PHI_HYD(
# Line 487  C Line 497  C
497             ELSE             ELSE
498  #ifdef ALLOW_MOM_VECINV  #ifdef ALLOW_MOM_VECINV
499  C  C
500  # ifdef ALLOW_AUTODIFF_TAMC  # ifdef ALLOW_AUTODIFF_TAMC
501  #  ifdef NONLIN_FRSURF  #  ifdef NONLIN_FRSURF
502  CADJ STORE fVerU(:,:,:)  CADJ STORE fVerU(:,:,:)
503  CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte  CADJ &     = comlev1_bibj_k, key=kkey, byte=isbyte
# Line 622  Cml( Line 632  Cml(
632  C     In order to compare the variance of phiHydLow of a p/z-coordinate  C     In order to compare the variance of phiHydLow of a p/z-coordinate
633  C     run with etaH of a z/p-coordinate run the drift of phiHydLow  C     run with etaH of a z/p-coordinate run the drift of phiHydLow
634  C     has to be removed by something like the following subroutine:  C     has to be removed by something like the following subroutine:
635  C      CALL REMOVE_MEAN_RL( 1, phiHydLow, maskH, maskH, rA, drF,  C      CALL REMOVE_MEAN_RL( 1, phiHydLow, maskInC, maskInC, rA, drF,
636  C     &                'phiHydLow', myThid )  C     &                     'phiHydLow', myTime, myThid )
637  Cml)  Cml)
638    
639  #ifdef ALLOW_DIAGNOSTICS  #ifdef ALLOW_DIAGNOSTICS
# Line 664  Cml) Line 674  Cml)
674  #endif  #endif
675    
676  #ifdef DYNAMICS_GUGV_EXCH_CHECK  #ifdef DYNAMICS_GUGV_EXCH_CHECK
677  C- jmc: For safety checking only: This Exchange here should not change  C- jmc: For safety checking only: This Exchange here should not change
678  C       the solution. If solution changes, it means something is wrong,  C       the solution. If solution changes, it means something is wrong,
679  C       but it does not mean that it is less wrong with this exchange.  C       but it does not mean that it is less wrong with this exchange.
680        IF ( debugLevel .GT. debLevB ) THEN        IF ( debugLevel .GT. debLevB ) THEN
681         CALL EXCH_UV_XYZ_RL(gU,gV,.TRUE.,myThid)         CALL EXCH_UV_XYZ_RL(gU,gV,.TRUE.,myThid)

Legend:
Removed from v.1.139  
changed lines
  Added in v.1.144

  ViewVC Help
Powered by ViewVC 1.1.22