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.
zdfmxl.F90 in NEMO/branches/UKMO/BPC_miniapp/OpenMP – NEMO

source: NEMO/branches/UKMO/BPC_miniapp/OpenMP/zdfmxl.F90 @ 10838

Last change on this file since 10838 was 10838, checked in by wayne_gaudin, 5 years ago

Ticket #2197 - extracted versions added

File size: 5.0 KB
RevLine 
[10838]1MODULE zdfmxl
2   !!======================================================================
3   !!                       ***  MODULE  zdfmxl  ***
4   !! Ocean physics: mixed layer depth
5   !!======================================================================
6   !! History :  1.0  ! 2003-08  (G. Madec)  original code
7   !!            3.2  ! 2009-07  (S. Masson, G. Madec)  IOM + merge of DO-loop
8   !!            3.7  ! 2012-03  (G. Madec)  make public the density criteria for trdmxl
9   !!             -   ! 2014-02  (F. Roquet)  mixed layer depth calculated using N2 instead of rhop
10   !!----------------------------------------------------------------------
11   !!   zdf_mxl      : Compute the turbocline and mixed layer depths.
12   !!----------------------------------------------------------------------
13   USE len_oce
14   !
15   USE in_out_manager ! I/O manager
16   USE phycst         ! physical constants
17
18   IMPLICIT NONE
19   PRIVATE
20
21   PUBLIC   zdf_mxl   ! called by zdfphy.F90
22
23   REAL(wp), PUBLIC ::   rho_c = 0.01_wp    !: density criterion for mixed layer depth
24   REAL(wp)         ::   avt_c = 5.e-4_wp   ! Kz criterion for the turbocline depth
25
26   !!----------------------------------------------------------------------
27   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
28   !! $Id$
29   !! Software governed by the CeCILL licence     (./LICENSE)
30   !!----------------------------------------------------------------------
31CONTAINS
32
33
34   SUBROUTINE zdf_mxl( rn2b, e3w_n, gdept_n, gdepw_n, avt, wmask, ssmask, mbkt, nlb10, nmln, hmld, hmlp, hmlpt )
35
36      !!----------------------------------------------------------------------
37      !!                  ***  ROUTINE zdfmxl  ***
38      !!                   
39      !! ** Purpose :   Compute the turbocline depth and the mixed layer depth
40      !!              with density criteria.
41      !!
42      !! ** Method  :   The mixed layer depth is the shallowest W depth with
43      !!      the density of the corresponding T point (just bellow) bellow a
44      !!      given value defined locally as rho(10m) + rho_c
45      !!               The turbocline depth is the depth at which the vertical
46      !!      eddy diffusivity coefficient (resulting from the vertical physics
47      !!      alone, not the isopycnal part, see trazdf.F) fall below a given
48      !!      value defined locally (avt_c here taken equal to 5 cm/s2 by default)
49      !!
50      !! ** Action  :   nmln, hmld, hmlp, hmlpt
51      !!----------------------------------------------------------------------
52      !
53      REAL(wp), INTENT(in), DIMENSION(:,:,:) ::   rn2b, e3w_n, gdept_n, gdepw_n, avt, wmask
54      REAL(wp), INTENT(in), DIMENSION(:,:)   ::   ssmask
55      INTEGER , INTENT(in), DIMENSION(:,:)   ::   mbkt
56      INTEGER , INTENT(in)                   ::   nlb10   ! index of shallowest W level Below ~10m
57      INTEGER , INTENT(out),DIMENSION(:,:)   ::   nmln
58      REAL(wp), INTENT(out),DIMENSION(:,:)   ::   hmld, hmlp, hmlpt 
59     
60
61      INTEGER  ::   ji, jj, jk      ! dummy loop indices
62      INTEGER  ::   iikn, iiki, ikt ! local integer
63      REAL(wp) ::   zN2_c           ! local scalar
64      INTEGER, ALLOCATABLE, DIMENSION(:,:) ::   imld   ! 2D workspace
65      ALLOCATE(imld(jpi,jpj)) ! Make this global at some point
66      !!----------------------------------------------------------------------
67      !
68      ! w-level of the mixing and mixed layers
69      nmln(:,:)  = nlb10               ! Initialization to the number of w ocean point
70      hmlp(:,:)  = 0._wp               ! here hmlp used as a dummy variable, integrating vertically N^2
71      zN2_c = grav * rho_c * r1_rau0   ! convert density criteria into N^2 criteria
72      DO jk = nlb10, jpkm1
73         DO jj = 1, jpj                ! Mixed layer level: w-level
74            DO ji = 1, jpi
75               ikt = mbkt(ji,jj)
76               hmlp(ji,jj) = hmlp(ji,jj) + MAX( rn2b(ji,jj,jk) , 0._wp ) * e3w_n(ji,jj,jk)
77               IF( hmlp(ji,jj) < zN2_c )   nmln(ji,jj) = MIN( jk , ikt ) + 1   ! Mixed layer level
78            END DO
79         END DO
80      END DO
81      !
82      ! w-level of the turbocline and mixing layer (iom_use)
83      imld(:,:) = mbkt(:,:) + 1        ! Initialization to the number of w ocean point
84      DO jk = jpkm1, nlb10, -1         ! from the bottom to nlb10
85         DO jj = 1, jpj
86            DO ji = 1, jpi
87               IF( avt (ji,jj,jk) < avt_c * wmask(ji,jj,jk) )   imld(ji,jj) = jk      ! Turbocline
88            END DO
89         END DO
90      END DO
91      ! depth of the mixing and mixed layers
92      DO jj = 1, jpj
93         DO ji = 1, jpi
94            iiki = imld(ji,jj)
95            iikn = nmln(ji,jj)
96            hmld (ji,jj) = gdepw_n(ji,jj,iiki  ) * ssmask(ji,jj)    ! Turbocline depth
97            hmlp (ji,jj) = gdepw_n(ji,jj,iikn  ) * ssmask(ji,jj)    ! Mixed layer depth
98            hmlpt(ji,jj) = gdept_n(ji,jj,iikn-1) * ssmask(ji,jj)    ! depth of the last T-point inside the mixed layer
99         END DO
100      END DO
101      !
102      !
103   END SUBROUTINE zdf_mxl
104
105   !!======================================================================
106END MODULE zdfmxl
Note: See TracBrowser for help on using the repository browser.