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 trunk/NEMO/OPA_SRC/ZDF – NEMO

source: trunk/NEMO/OPA_SRC/ZDF/zdfmxl.F90 @ 1577

Last change on this file since 1577 was 1577, checked in by smasson, 15 years ago

update diahth and zdfmxl, see ticket:468

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 3.7 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 + 10m ref.
8   !!----------------------------------------------------------------------
9   !!   zdf_mxl       : Compute mixed layer depth and level
10   !!----------------------------------------------------------------------
11   USE oce             ! ocean dynamics and tracers variables
12   USE dom_oce         ! ocean space and time domain variables
13   USE in_out_manager  ! I/O manager
14   USE prtctl          ! Print control
15   USE iom
16
17   IMPLICIT NONE
18   PRIVATE
19
20   PUBLIC   zdf_mxl    ! called by step.F90
21
22   INTEGER , PUBLIC, DIMENSION(jpi,jpj) ::   nmln    !: number of level in the mixed layer
23   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   hmlp    !: mixed layer depth  (rho=rho0+zdcrit) [m]
24   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   hmlpt   !: mixed layer depth at t-points        [m]
25
26   !! * Substitutions
27#  include "domzgr_substitute.h90"
28   !!----------------------------------------------------------------------
29   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)
30   !! $Id$
31   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33
34CONTAINS
35
36   SUBROUTINE zdf_mxl( kt )
37      !!----------------------------------------------------------------------
38      !!                  ***  ROUTINE zdfmxl  ***
39      !!                   
40      !! ** Purpose :   the mixed layer depth 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) + zrho_c
45      !!
46      !! ** Action  :   nmln, hmlp, hmlpt
47      !!----------------------------------------------------------------------
48      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
49      !!
50      INTEGER  ::   ji, jj, jk         ! dummy loop indices
51      INTEGER  ::   iikn               ! temporary integer within a do loop
52      REAL(wp) ::   zrho_c = 0.01_wp   ! density criterion for mixed layer depth
53      !!----------------------------------------------------------------------
54
55      IF( kt == nit000 ) THEN
56         IF(lwp) WRITE(numout,*)
57         IF(lwp) WRITE(numout,*) 'zdf_mxl : mixed layer depth'
58         IF(lwp) WRITE(numout,*) '~~~~~~~ '
59      ENDIF
60
61      ! w-level of the mixing and mixed layers
62      nmln(:,:) = mbathy(:,:)          ! Initialization to the number of w ocean point mbathy
63      DO jk = jpkm1, nlb10, -1         ! from the bottom to nlb10
64         DO jj = 1, jpj
65            DO ji = 1, jpi
66               IF( rhop(ji,jj,jk) > rhop(ji,jj,nla10) + zrho_c )   nmln(ji,jj) = jk      ! Mixed layer
67            END DO
68         END DO
69      END DO
70      ! depth of the mixing and mixed layers
71      DO jj = 1, jpj
72         DO ji = 1, jpi
73            iikn = nmln(ji,jj)
74            hmlp (ji,jj) = fsdepw(ji,jj,iikn  ) * tmask(ji,jj,1)    ! Mixed layer depth
75            hmlpt(ji,jj) = fsdept(ji,jj,iikn-1)                     ! depth of the last T-point inside the mixed layer
76         END DO
77      END DO
78      CALL iom_put( "mldr10_1" , hmlp )   ! mixed layer depth
79     
80      IF(ln_ctl)   CALL prt_ctl( tab2d_1=REAL(nmln,wp), clinfo1=' nmln : ', tab2d_2=hmlp, clinfo2=' hmlp : ', ovlap=1 )
81      !
82   END SUBROUTINE zdf_mxl
83
84   !!======================================================================
85END MODULE zdfmxl
Note: See TracBrowser for help on using the repository browser.