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_crs.F90 in branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/OPA_SRC/ZDF – NEMO

source: branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfmxl_crs.F90 @ 6101

Last change on this file since 6101 was 6101, checked in by cbricaud, 8 years ago

correction of bugs from last update and improvments for CRS

  • Property svn:executable set to *
File size: 4.9 KB
Line 
1MODULE zdfmxl_crs
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 oce             ! ocean dynamics and tracers variables
14   !USE dom_oce         ! ocean space and time domain variables
15   !USE oce_trc
16   USE zdf_oce         ! ocean vertical physics
17   USE in_out_manager  ! I/O manager
18   USE prtctl          ! Print control
19   USE phycst          ! physical constants
20   USE iom             ! I/O library
21   USE lib_mpp         ! MPP library
22   USE wrk_nemo        ! work arrays
23   USE timing          ! Timing
24   USE trc_oce, ONLY : lk_offline ! offline flag
25   USE crs
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   zdf_mxl_crs       ! called by step.F90
31
32   REAL(wp)         ::   avt_c = 5.e-4_wp   ! Kz criterion for the turbocline depth
33
34   !! * Substitutions
35#  include "domzgr_substitute.h90"
36   !!----------------------------------------------------------------------
37   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
38   !! $Id: zdfmxl.F90 4990 2014-12-15 16:42:49Z timgraham $
39   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
40   !!----------------------------------------------------------------------
41CONTAINS
42
43   SUBROUTINE zdf_mxl_crs( kt )
44      !!----------------------------------------------------------------------
45      !!                  ***  ROUTINE zdfmxl  ***
46      !!                   
47      !! ** Purpose :   Compute the turbocline depth and the mixed layer depth
48      !!              with density criteria.
49      !!
50      !! ** Method  :   The mixed layer depth is the shallowest W depth with
51      !!      the density of the corresponding T point (just bellow) bellow a
52      !!      given value defined locally as rho(10m) + rho_c
53      !!               The turbocline depth is the depth at which the vertical
54      !!      eddy diffusivity coefficient (resulting from the vertical physics
55      !!      alone, not the isopycnal part, see trazdf.F) fall below a given
56      !!      value defined locally (avt_c here taken equal to 5 cm/s2 by default)
57      !!
58      !! ** Action  :   nmln, hmld, hmlp, hmlpt
59      !!----------------------------------------------------------------------
60      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
61      !
62      INTEGER  ::   ji, jj, jk   ! dummy loop indices
63      INTEGER  ::   iiki,iikn   ! local integer
64      REAL(wp) ::   zN2_c        ! local scalar
65      INTEGER, POINTER, DIMENSION(:,:) ::   imld   ! 2D workspace
66      REAL(wp), POINTER, DIMENSION(:,:) ::  z2d   ! 2D workspace
67      !!----------------------------------------------------------------------
68      !
69      IF( nn_timing == 1 )  CALL timing_start('zdf_mxl_crs')
70      !
71      CALL wrk_alloc( jpi_crs,jpj_crs, imld )
72      CALL wrk_alloc( jpi_crs,jpj_crs, z2d )
73
74      IF( kt == nit000 ) THEN
75         IF(lwp) WRITE(numout,*)
76         IF(lwp) WRITE(numout,*) 'zdf_mxl_crs : mixed layer depth'
77         IF(lwp) WRITE(numout,*) '~~~~~~~ '
78      ENDIF
79
80      ! w-level of the turbocline
81      imld(:,:)=0
82      DO jk = jpkm1, nlb10, -1         ! from the bottom to nlb10
83         DO jj = 1, jpj_crs
84            DO ji = 1, jpi_crs
85               IF( avt_crs (ji,jj,jk) < avt_c )   imld(ji,jj) = MAX( jk, 1 )      ! Turbocline
86            END DO
87         END DO
88      END DO
89
90      ! depth of the mixing and mixed layers
91      hmld_crs(:,:) = 0._wp
92      hmlpt_crs(:,:) = 0._wp
93      DO jj = 1, jpj_crs
94         DO ji = 1, jpi_crs
95            iiki = imld(ji,jj)
96            iikn = nmln_crs(ji,jj)
97            IF( iiki .NE. 0 ) hmld_crs (ji,jj) = ( gdepw_crs(ji,jj,iiki  ) - gdepw_crs(ji,jj,1 )            )   * tmask_crs(ji,jj,1)  ! Turbocline depth
98            IF( iiki .NE. 0 ) hmlpt_crs(ji,jj) = ( gdept_crs(ji,jj,iikn-1) - gdepw_crs(ji,jj,1 )            )   * tmask_crs(ji,jj,1)  ! depth of the last T-point inside the mixed layer
99         END DO
100      END DO
101      !
102      z2d=REAL(nmln_crs,wp)
103      CALL iom_put("nmln_crs",z2d)
104      CALL iom_put("hmlpt_crs",hmlpt_crs)
105      !
106      CALL wrk_dealloc( jpi_crs,jpj_crs, imld )
107      CALL wrk_dealloc( jpi_crs,jpj_crs, z2d )
108      !
109      IF( nn_timing == 1 )  CALL timing_stop('zdf_mxl_crs')
110      !
111   END SUBROUTINE zdf_mxl_crs
112
113   !!======================================================================
114END MODULE zdfmxl_crs
Note: See TracBrowser for help on using the repository browser.