New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
zdfsh2.F90 in NEMO/trunk/src/OCE/ZDF – NEMO

source: NEMO/trunk/src/OCE/ZDF/zdfsh2.F90

Last change on this file was 15293, checked in by clem, 3 years ago

try to pass debug mode with outputs activated. One issue was that the shear was not calculated at the top and bottom levels. Another issue is that the shear is not defined in the haloes but solving this one probably requires to wait for the new xios to be released

  • Property svn:keywords set to Id
File size: 5.9 KB
Line 
1MODULE zdfsh2
2   !!======================================================================
3   !!                       ***  MODULE  zdfsh2  ***
4   !! Ocean physics:  shear production term of TKE
5   !!=====================================================================
6   !! History :   -   !  2014-10  (A. Barthelemy, G. Madec)  original code
7   !!   NEMO     4.0  !  2017-04  (G. Madec)  remove u-,v-pts avm
8   !!   NEMO     4.2  !  2020-12  (G. Madec, E. Clementi) add Stokes Drift Shear
9   !                  !           for wave coupling
10   !!----------------------------------------------------------------------
11
12   !!----------------------------------------------------------------------
13   !!   zdf_sh2       : compute mixing the shear production term of TKE
14   !!----------------------------------------------------------------------
15   USE oce
16   USE dom_oce        ! domain: ocean
17   USE sbcwave        ! Surface Waves (add Stokes shear)
18   USE sbc_oce , ONLY: ln_stshear  !Stoked Drift shear contribution
19   !
20   USE in_out_manager ! I/O manager
21   USE lib_mpp        ! MPP library
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   zdf_sh2        ! called by zdftke, zdfglf, and zdfric
27
28   !! * Substitutions
29#  include "do_loop_substitute.h90"
30#  include "domzgr_substitute.h90"
31   !!----------------------------------------------------------------------
32   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
33   !! $Id$
34   !! Software governed by the CeCILL license (see ./LICENSE)
35   !!----------------------------------------------------------------------
36CONTAINS
37
38   SUBROUTINE zdf_sh2( Kbb, Kmm, p_avm, p_sh2  )
39      !!----------------------------------------------------------------------
40      !!                   ***  ROUTINE zdf_sh2  ***
41      !!
42      !! ** Purpose :   Compute the shear production term of a TKE equation
43      !!
44      !! ** Method  : - a stable discretization of this term is linked to the
45      !!                time-space discretization of the vertical diffusion
46      !!                of the OGCM. NEMO uses C-grid, a leap-frog environment
47      !!                and an implicit computation of vertical mixing term,
48      !!                so the shear production at w-point is given by:
49      !!                   sh2 = mi[   mi(avm) * dk[ub]/e3ub * dk[un]/e3un   ]
50      !!                       + mj[   mj(avm) * dk[vb]/e3vb * dk[vn]/e3vn   ]
51      !!                NB: wet-point only horizontal averaging of shear
52      !!
53      !! ** Action  : - p_sh2 shear prod. term at w-point (inner domain only)
54      !!                                                   *****
55      !! References :   Bruchard, OM 2002
56      !! ---------------------------------------------------------------------
57      INTEGER                              , INTENT(in   ) ::   Kbb, Kmm             ! ocean time level indices
58      REAL(wp), DIMENSION(:,:,:)           , INTENT(in   ) ::   p_avm                ! vertical eddy viscosity (w-points)
59      REAL(wp), DIMENSION(A2D(nn_hls),jpk) , INTENT(  out) ::   p_sh2                ! shear production of TKE (w-points)
60      !
61      INTEGER  ::   ji, jj, jk   ! dummy loop arguments
62      REAL(wp), DIMENSION(A2D(nn_hls)) ::   zsh2u, zsh2v   ! 2D workspace
63      !!--------------------------------------------------------------------
64      !
65      DO jk = 2, jpkm1                 !* Shear production at uw- and vw-points (energy conserving form)
66         IF ( cpl_sdrftx .AND. ln_stshear )  THEN       ! Surface Stokes Drift available  ===>>>  shear + stokes drift contibution
67            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 )
68               zsh2u(ji,jj) = ( p_avm(ji+1,jj,jk) + p_avm(ji,jj,jk) )        &
69                  &         * ( uu (ji,jj,jk-1,Kmm) -   uu (ji,jj,jk,Kmm)    &
70                  &           + usd(ji,jj,jk-1) -   usd(ji,jj,jk) )  &
71                  &         * ( uu (ji,jj,jk-1,Kbb) -   uu (ji,jj,jk,Kbb) )  &
72                  &         / ( e3uw(ji,jj,jk,Kmm) * e3uw(ji,jj,jk,Kbb) ) * wumask(ji,jj,jk)
73               zsh2v(ji,jj) = ( p_avm(ji,jj+1,jk) + p_avm(ji,jj,jk) )         &
74                  &         * ( vv (ji,jj,jk-1,Kmm) -   vv (ji,jj,jk,Kmm)     &
75                  &           + vsd(ji,jj,jk-1) -   vsd(ji,jj,jk) )   &
76                  &         * ( vv (ji,jj,jk-1,Kbb) -   vv (ji,jj,jk,Kbb) )   &
77                  &/ ( e3vw(ji,jj,jk,Kmm) * e3vw(ji,jj,jk,Kbb) ) * wvmask(ji,jj,jk)
78            END_2D
79         ELSE
80            DO_2D( nn_hls, nn_hls-1, nn_hls, nn_hls-1 )     !* 2 x shear production at uw- and vw-points (energy conserving form)
81               zsh2u(ji,jj) = ( p_avm(ji+1,jj,jk) + p_avm(ji,jj,jk) ) &
82                  &         * (   uu(ji,jj,jk-1,Kmm) -   uu(ji,jj,jk,Kmm) ) &
83                  &         * (   uu(ji,jj,jk-1,Kbb) -   uu(ji,jj,jk,Kbb) ) &
84                  &         / ( e3uw(ji,jj,jk  ,Kmm) * e3uw(ji,jj,jk,Kbb) ) &
85                  &         * wumask(ji,jj,jk)
86               zsh2v(ji,jj) = ( p_avm(ji,jj+1,jk) + p_avm(ji,jj,jk) ) &
87                  &         * (   vv(ji,jj,jk-1,Kmm) -   vv(ji,jj,jk,Kmm) ) &
88                  &         * (   vv(ji,jj,jk-1,Kbb) -   vv(ji,jj,jk,Kbb) ) &
89                  &         / ( e3vw(ji,jj,jk  ,Kmm) * e3vw(ji,jj,jk,Kbb) ) &
90                  &         * wvmask(ji,jj,jk)
91            END_2D
92         ENDIF
93         DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 )     !* shear production at w-point ! coast mask: =2 at the coast ; =1 otherwise (NB: wmask useless as zsh2 are masked)
94            p_sh2(ji,jj,jk) = 0.25 * (   ( zsh2u(ji-1,jj) + zsh2u(ji,jj) ) * ( 2. - umask(ji-1,jj,jk) * umask(ji,jj,jk) )   &
95               &                       + ( zsh2v(ji,jj-1) + zsh2v(ji,jj) ) * ( 2. - vmask(ji,jj-1,jk) * vmask(ji,jj,jk) )   )
96         END_2D
97      END DO
98      DO_2D( nn_hls-1, nn_hls-1, nn_hls-1, nn_hls-1 ) ! set p_sh2 to 0 at the surface and bottom for output purpose
99         p_sh2(ji,jj,1)   = 0._wp
100         p_sh2(ji,jj,jpk) = 0._wp
101      END_2D
102      !
103   END SUBROUTINE zdf_sh2
104
105   !!======================================================================
106END MODULE zdfsh2
Note: See TracBrowser for help on using the repository browser.