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

source: tags/nemo_v3_2/nemo_v3_2/NEMO/OPA_SRC/ZDF/zdfmxl.F90 @ 1878

Last change on this file since 1878 was 1878, checked in by flavoni, 14 years ago

initial test for nemogcm

File size: 4.8 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   !!----------------------------------------------------------------------
9   !!   zdf_mxl      : Compute the turbocline and mixed layer depths.
10   !!----------------------------------------------------------------------
11   USE oce             ! ocean dynamics and tracers variables
12   USE dom_oce         ! ocean space and time domain variables
13   USE zdf_oce         ! ocean vertical physics
14   USE in_out_manager  ! I/O manager
15   USE prtctl          ! Print control
16   USE iom
17
18   IMPLICIT NONE
19   PRIVATE
20
21   PUBLIC   zdf_mxl    ! called by step.F90
22
23   INTEGER , PUBLIC, DIMENSION(jpi,jpj) ::   nmln    !: number of level in the mixed layer (used by TOP)
24   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   hmld    !: mixing layer depth (turbocline)      [m]
25   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   hmlp    !: mixed layer depth  (rho=rho0+zdcrit) [m]
26   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   hmlpt   !: mixed layer depth at t-points        [m]
27
28   !! * Substitutions
29#  include "domzgr_substitute.h90"
30   !!----------------------------------------------------------------------
31   !! NEMO/OPA 3.2 , LOCEAN-IPSL (2009)
32   !! $Id: zdfmxl.F90 1585 2009-08-06 07:29:43Z smasson $
33   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
34   !!----------------------------------------------------------------------
35
36CONTAINS
37
38   SUBROUTINE zdf_mxl( kt )
39      !!----------------------------------------------------------------------
40      !!                  ***  ROUTINE zdfmxl  ***
41      !!                   
42      !! ** Purpose :   Compute the turbocline depth and the mixed layer depth
43      !!              with density criteria.
44      !!
45      !! ** Method  :   The mixed layer depth is the shallowest W depth with
46      !!      the density of the corresponding T point (just bellow) bellow a
47      !!      given value defined locally as rho(10m) + zrho_c
48      !!               The turbocline depth is the depth at which the vertical
49      !!      eddy diffusivity coefficient (resulting from the vertical physics
50      !!      alone, not the isopycnal part, see trazdf.F) fall below a given
51      !!      value defined locally (avt_c here taken equal to 5 cm/s2)
52      !!
53      !! ** Action  :   nmln, hmld, hmlp, hmlpt
54      !!----------------------------------------------------------------------
55      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
56      !!
57      INTEGER                     ::   ji, jj, jk          ! dummy loop indices
58      INTEGER                     ::   iikn, iiki          ! temporary integer within a do loop
59      INTEGER, DIMENSION(jpi,jpj) ::   imld                ! temporary workspace
60      REAL(wp)                    ::   zrho_c = 0.01_wp    ! density criterion for mixed layer depth
61      REAL(wp)                    ::   zavt_c = 5.e-4_wp   ! Kz criterion for the turbocline depth
62      !!----------------------------------------------------------------------
63
64      IF( kt == nit000 ) THEN
65         IF(lwp) WRITE(numout,*)
66         IF(lwp) WRITE(numout,*) 'zdf_mxl : mixed layer depth'
67         IF(lwp) WRITE(numout,*) '~~~~~~~ '
68      ENDIF
69
70      ! w-level of the mixing and mixed layers
71      nmln(:,:) = mbathy(:,:)          ! Initialization to the number of w ocean point mbathy
72      imld(:,:) = mbathy(:,:)
73      DO jk = jpkm1, nlb10, -1         ! from the bottom to nlb10
74         DO jj = 1, jpj
75            DO ji = 1, jpi
76               IF( rhop(ji,jj,jk) > rhop(ji,jj,nla10) + zrho_c )   nmln(ji,jj) = jk      ! Mixed layer
77               IF( avt (ji,jj,jk) < zavt_c                     )   imld(ji,jj) = jk      ! Turbocline
78            END DO
79         END DO
80      END DO
81      ! depth of the mixing and mixed layers
82      DO jj = 1, jpj
83         DO ji = 1, jpi
84            iiki = imld(ji,jj)
85            iikn = nmln(ji,jj)
86            hmld (ji,jj) = fsdepw(ji,jj,iiki  ) * tmask(ji,jj,1)    ! Turbocline depth
87            hmlp (ji,jj) = fsdepw(ji,jj,iikn  ) * tmask(ji,jj,1)    ! Mixed layer depth
88            hmlpt(ji,jj) = fsdept(ji,jj,iikn-1)                     ! depth of the last T-point inside the mixed layer
89         END DO
90      END DO
91      CALL iom_put( "mldr10_1", hmlp )   ! mixed layer depth
92      CALL iom_put( "mldkz5"  , hmld )   ! turbocline depth
93     
94      IF(ln_ctl)   CALL prt_ctl( tab2d_1=REAL(nmln,wp), clinfo1=' nmln : ', tab2d_2=hmlp, clinfo2=' hmlp : ', ovlap=1 )
95      !
96   END SUBROUTINE zdf_mxl
97
98   !!======================================================================
99END MODULE zdfmxl
Note: See TracBrowser for help on using the repository browser.