MODULE zdfmxl !!====================================================================== !! *** MODULE zdfmxl *** !! Ocean physics: mixed layer depth !!====================================================================== !! History : 1.0 ! 2003-08 (G. Madec) original code !! 3.2 ! 2009-07 (S. Masson, G. Madec) IOM + merge of DO-loop !! 3.7 ! 2012-03 (G. Madec) make public the density criteria for trdmxl !! - ! 2014-02 (F. Roquet) mixed layer depth calculated using N2 instead of rhop !!---------------------------------------------------------------------- !! zdf_mxl : Compute the turbocline and mixed layer depths. !!---------------------------------------------------------------------- USE len_oce ! USE in_out_manager ! I/O manager USE phycst ! physical constants IMPLICIT NONE PRIVATE PUBLIC zdf_mxl ! called by zdfphy.F90 REAL(wp), PUBLIC :: rho_c = 0.01_wp !: density criterion for mixed layer depth REAL(wp) :: avt_c = 5.e-4_wp ! Kz criterion for the turbocline depth !!---------------------------------------------------------------------- !! NEMO/OCE 4.0 , NEMO Consortium (2018) !! $Id$ !! Software governed by the CeCILL licence (./LICENSE) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE zdf_mxl( rn2b, e3w_n, gdept_n, gdepw_n, avt, wmask, ssmask, mbkt, nlb10, nmln, hmld, hmlp, hmlpt ) !!---------------------------------------------------------------------- !! *** ROUTINE zdfmxl *** !! !! ** Purpose : Compute the turbocline depth and the mixed layer depth !! with density criteria. !! !! ** Method : The mixed layer depth is the shallowest W depth with !! the density of the corresponding T point (just bellow) bellow a !! given value defined locally as rho(10m) + rho_c !! The turbocline depth is the depth at which the vertical !! eddy diffusivity coefficient (resulting from the vertical physics !! alone, not the isopycnal part, see trazdf.F) fall below a given !! value defined locally (avt_c here taken equal to 5 cm/s2 by default) !! !! ** Action : nmln, hmld, hmlp, hmlpt !!---------------------------------------------------------------------- ! REAL(wp), INTENT(in), DIMENSION(:,:,:) :: rn2b, e3w_n, gdept_n, gdepw_n, avt, wmask REAL(wp), INTENT(in), DIMENSION(:,:) :: ssmask INTEGER , INTENT(in), DIMENSION(:,:) :: mbkt INTEGER , INTENT(in) :: nlb10 ! index of shallowest W level Below ~10m INTEGER , INTENT(out),DIMENSION(:,:) :: nmln REAL(wp), INTENT(out),DIMENSION(:,:) :: hmld, hmlp, hmlpt INTEGER :: ji, jj, jk ! dummy loop indices INTEGER :: iikn, iiki, ikt ! local integer REAL(wp) :: zN2_c ! local scalar INTEGER, ALLOCATABLE, DIMENSION(:,:) :: imld ! 2D workspace ALLOCATE(imld(jpi,jpj)) ! Make this global at some point !!---------------------------------------------------------------------- ! ! w-level of the mixing and mixed layers nmln(:,:) = nlb10 ! Initialization to the number of w ocean point hmlp(:,:) = 0._wp ! here hmlp used as a dummy variable, integrating vertically N^2 zN2_c = grav * rho_c * r1_rau0 ! convert density criteria into N^2 criteria DO jk = nlb10, jpkm1 DO jj = 1, jpj ! Mixed layer level: w-level DO ji = 1, jpi ikt = mbkt(ji,jj) hmlp(ji,jj) = hmlp(ji,jj) + MAX( rn2b(ji,jj,jk) , 0._wp ) * e3w_n(ji,jj,jk) IF( hmlp(ji,jj) < zN2_c ) nmln(ji,jj) = MIN( jk , ikt ) + 1 ! Mixed layer level END DO END DO END DO ! ! w-level of the turbocline and mixing layer (iom_use) imld(:,:) = mbkt(:,:) + 1 ! Initialization to the number of w ocean point DO jk = jpkm1, nlb10, -1 ! from the bottom to nlb10 DO jj = 1, jpj DO ji = 1, jpi IF( avt (ji,jj,jk) < avt_c * wmask(ji,jj,jk) ) imld(ji,jj) = jk ! Turbocline END DO END DO END DO ! depth of the mixing and mixed layers DO jj = 1, jpj DO ji = 1, jpi iiki = imld(ji,jj) iikn = nmln(ji,jj) hmld (ji,jj) = gdepw_n(ji,jj,iiki ) * ssmask(ji,jj) ! Turbocline depth hmlp (ji,jj) = gdepw_n(ji,jj,iikn ) * ssmask(ji,jj) ! Mixed layer depth hmlpt(ji,jj) = gdept_n(ji,jj,iikn-1) * ssmask(ji,jj) ! depth of the last T-point inside the mixed layer END DO END DO ! ! END SUBROUTINE zdf_mxl !!====================================================================== END MODULE zdfmxl