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 branches/2017/dev_r7881_HPC09_ZDF/NEMOGCM/NEMO/OPA_SRC/ZDF – NEMO

source: branches/2017/dev_r7881_HPC09_ZDF/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfsh2.F90 @ 7991

Last change on this file since 7991 was 7991, checked in by gm, 7 years ago

#1880 (HPC-09) - step-5: OPA/ZDF shear production term computed outside closure schemes

File size: 4.6 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   !!----------------------------------------------------------------------
9
10   !!----------------------------------------------------------------------
11   !!   zdf_sh2       : compute mixing the shear production term of TKE
12   !!----------------------------------------------------------------------
13   USE oce            ! ocean: shared variables
14   USE dom_oce        ! domain: ocean
15   USE zdf_oce        ! vertical physics: variables
16   !
17   USE in_out_manager ! I/O manager
18   USE lib_mpp        ! MPP library
19   USE timing         ! Timing
20
21   IMPLICIT NONE
22   PRIVATE
23
24   PUBLIC   zdf_sh2        ! called by zdftke, zdfglf, and zdfric
25   
26   !!----------------------------------------------------------------------
27   !! NEMO/OPA 4.0 , NEMO Consortium (2017)
28   !! $Id: $
29   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
30   !!----------------------------------------------------------------------
31CONTAINS
32
33   SUBROUTINE zdf_sh2(  psh2  ) 
34      !!----------------------------------------------------------------------
35      !!                   ***  ROUTINE zdf_sh2  ***
36      !!
37      !! ** Purpose :   Compute the shear production term of a TKE equation
38      !!
39      !! ** Method  : - a stable discretization of this term is linked to the
40      !!                time-space discretization of the vertical diffusion
41      !!                of the OGCM. NEMO uses C-grid, a leap-frog environment
42      !!                and an implicit computation of vertical mixing term,
43      !!                so the shear production at w-point is given by:
44      !!                   sh2 = mi[   mi(avm) * dk[ub]/e3ub * dk[un]/e3un   ]
45      !!                       + mj[   mj(avm) * dk[vb]/e3vb * dk[vn]/e3vn   ]
46      !!                NB: wet-point only horizontal averaging of shear
47      !!
48      !! ** Action  : - psh2 shear prod. term at w-point (interior ocean domain only)
49      !!
50      !! References :   Bruchard, OM 2002
51      !! ---------------------------------------------------------------------
52      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(  out) ::   psh2   ! shear production of TKE (w-points)
53      !
54      INTEGER  ::   ji, jj, jk   ! dummy loop arguments
55      REAL(wp), DIMENSION(jpi,jpj) ::   zsh2u, zsh2v   ! 2D workspace
56      !!--------------------------------------------------------------------
57      IF( nn_timing == 1 )  CALL timing_start('zdf_sh2')
58      !
59      DO jk = 2, jpkm1
60         DO jj = 1, jpjm1        !* Shear production at uw- and vw-points (energy conserving form)
61            DO ji = 1, jpim1
62               zsh2u(ji,jj) = 0.5 * ( avm(ji+1,jj,jk) + avm(ji,jj,jk) ) * wumask(ji,jj,jk)  &
63                  &               * (  un(ji,jj,jk-1) -  un(ji,jj,jk) )   &
64                  &               * (  ub(ji,jj,jk-1) -  ub(ji,jj,jk) ) / ( e3uw_n(ji,jj,jk) * e3uw_b(ji,jj,jk) )
65               zsh2v(ji,jj) = 0.5 * ( avm(ji,jj+1,jk) + avm(ji,jj,jk) ) * wvmask(ji,jj,jk)  &
66                  &               * (  vn(ji,jj,jk-1) -  vn(ji,jj,jk) )   &
67                  &               * (  vb(ji,jj,jk-1) -  vb(ji,jj,jk) ) / ( e3vw_n(ji,jj,jk) * e3vw_b(ji,jj,jk) )
68            END DO
69         END DO
70         DO jj = 2, jpjm1        !* shear production at w-point
71            DO ji = 2, jpim1
72               !
73!!gm original type of coding
74!              psh2(ji,jj,jk) = ( zsh2u(ji-1,jj) + zsh2u(ji,jj) ) / MAX( 1._wp , umask(ji-1,jj,jk)+umask(ji,jj,jk) )   &
75!                 &           + ( zsh2v(ji,jj-1) + zsh2v(ji,jj) ) / MAX( 1._wp , vmask(ji,jj-1,jk)+vmask(ji,jj,jk) )   
76!
77!!gm optimized but it changes the last digits after 1 year of GYRE
78               !                       ! coast mask: =1 at the coast ; =2 otherwise
79               !                       ! no need of wmask as zsh2 are already masked
80               psh2(ji,jj,jk) = ( zsh2u(ji-1,jj) + zsh2u(ji,jj) ) * ( 2._wp - umask(ji-1,jj,jk) * umask(ji,jj,jk) )   &
81                  &           + ( zsh2v(ji,jj-1) + zsh2v(ji,jj) ) * ( 2._wp - vmask(ji,jj-1,jk) * vmask(ji,jj,jk) )
82            END DO
83         END DO
84      END DO 
85      !
86      IF( nn_timing == 1 )  CALL timing_stop('zdf_sh2')     
87      !
88   END SUBROUTINE zdf_sh2
89
90   !!======================================================================
91END MODULE zdfsh2
Note: See TracBrowser for help on using the repository browser.