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/Master – NEMO

source: NEMO/branches/UKMO/BPC_miniapp/Master/zdfmxl.F90 @ 10831

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

Ticket #2197 - added the Master directory with code and makefile

File size: 5.0 KB
Line 
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!$ACC KERNELS
69      ! w-level of the mixing and mixed layers
70      nmln(:,:)  = nlb10               ! Initialization to the number of w ocean point
71      hmlp(:,:)  = 0._wp               ! here hmlp used as a dummy variable, integrating vertically N^2
72      zN2_c = grav * rho_c * r1_rau0   ! convert density criteria into N^2 criteria
73      DO jk = nlb10, jpkm1
74         DO jj = 1, jpj                ! Mixed layer level: w-level
75            DO ji = 1, jpi
76               ikt = mbkt(ji,jj)
77               hmlp(ji,jj) = hmlp(ji,jj) + MAX( rn2b(ji,jj,jk) , 0._wp ) * e3w_n(ji,jj,jk)
78               IF( hmlp(ji,jj) < zN2_c )   nmln(ji,jj) = MIN( jk , ikt ) + 1   ! Mixed layer level
79            END DO
80         END DO
81      END DO
82      !
83      ! w-level of the turbocline and mixing layer (iom_use)
84      imld(:,:) = mbkt(:,:) + 1        ! Initialization to the number of w ocean point
85      DO jk = jpkm1, nlb10, -1         ! from the bottom to nlb10
86         DO jj = 1, jpj
87            DO ji = 1, jpi
88               IF( avt (ji,jj,jk) < avt_c * wmask(ji,jj,jk) )   imld(ji,jj) = jk      ! Turbocline
89            END DO
90         END DO
91      END DO
92      ! depth of the mixing and mixed layers
93      DO jj = 1, jpj
94         DO ji = 1, jpi
95            iiki = imld(ji,jj)
96            iikn = nmln(ji,jj)
97            hmld (ji,jj) = gdepw_n(ji,jj,iiki  ) * ssmask(ji,jj)    ! Turbocline depth
98            hmlp (ji,jj) = gdepw_n(ji,jj,iikn  ) * ssmask(ji,jj)    ! Mixed layer depth
99            hmlpt(ji,jj) = gdept_n(ji,jj,iikn-1) * ssmask(ji,jj)    ! depth of the last T-point inside the mixed layer
100         END DO
101      END DO
102!$ACC END KERNELS
103      !
104      !
105   END SUBROUTINE zdf_mxl
106
107   !!======================================================================
108END MODULE zdfmxl
Note: See TracBrowser for help on using the repository browser.