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 @ 5105

Last change on this file since 5105 was 5105, checked in by cbricaud, 9 years ago

bug correction

  • Property svn:executable set to *
File size: 6.7 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   !!----------------------------------------------------------------------
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             ! I/O library
17   USE lib_mpp         ! MPP library
18   USE wrk_nemo        ! work arrays
19   USE timing          ! Timing
20   USE trc_oce, ONLY : lk_offline ! offline flag
21   USE crs
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   zdf_mxl_crs       ! called by step.F90
27
28   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   nmln    !: number of level in the mixed layer (used by TOP)
29   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmld    !: mixing layer depth (turbocline)      [m]
30   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmlp    !: mixed layer depth  (rho=rho0+zdcrit) [m]
31   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmlpt   !: mixed layer depth at t-points        [m]
32
33   !! * Substitutions
34#  include "domzgr_substitute.h90"
35   !!----------------------------------------------------------------------
36   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
37   !! $Id: zdfmxl.F90 3294 2012-01-28 16:44:18Z rblod $
38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
39   !!----------------------------------------------------------------------
40CONTAINS
41
42   INTEGER FUNCTION zdf_mxl_alloc_crs()
43      !!----------------------------------------------------------------------
44      !!               ***  FUNCTION zdf_mxl_alloc  ***
45      !!----------------------------------------------------------------------
46      zdf_mxl_alloc_crs = 0      ! set to zero if no array to be allocated
47      IF( .NOT. ALLOCATED( nmln_crs ) ) THEN
48         ALLOCATE( nmln_crs(jpi_crs,jpj_crs), hmld_crs(jpi_crs,jpj_crs), hmlp_crs(jpi_crs,jpj_crs) & !! declaration in crs.F90
49         &       , hmlpt_crs(jpi_crs,jpj_crs), STAT= zdf_mxl_alloc_crs )
50         !
51         IF( lk_mpp             )   CALL mpp_sum ( zdf_mxl_alloc_crs )
52         IF( zdf_mxl_alloc_crs /= 0 )   CALL ctl_warn('zdf_mxl_alloc: failed to allocate arrays.')
53         !
54      ENDIF
55   END FUNCTION zdf_mxl_alloc_crs
56
57
58   SUBROUTINE zdf_mxl_crs( kt )
59      !!----------------------------------------------------------------------
60      !!                  ***  ROUTINE zdfmxl  ***
61      !!                   
62      !! ** Purpose :   Compute the turbocline depth and the mixed layer depth
63      !!              with density criteria.
64      !!
65      !! ** Method  :   The mixed layer depth is the shallowest W depth with
66      !!      the density of the corresponding T point (just bellow) bellow a
67      !!      given value defined locally as rho(10m) + zrho_c
68      !!               The turbocline depth is the depth at which the vertical
69      !!      eddy diffusivity coefficient (resulting from the vertical physics
70      !!      alone, not the isopycnal part, see trazdf.F) fall below a given
71      !!      value defined locally (avt_c here taken equal to 5 cm/s2)
72      !!
73      !! ** Action  :   nmln, hmld, hmlp, hmlpt
74      !!----------------------------------------------------------------------
75      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
76      !!
77      INTEGER  ::   ji, jj, jk          ! dummy loop indices
78      INTEGER  ::   iikn, iiki          ! temporary integer within a do loop
79      INTEGER, POINTER, DIMENSION(:,:) ::   imld                ! temporary workspace
80      REAL(wp) ::   zrho_c = 0.01_wp    ! density criterion for mixed layer depth
81      REAL(wp) ::   zavt_c = 5.e-4_wp   ! Kz criterion for the turbocline depth
82      !!----------------------------------------------------------------------
83      !
84      IF( nn_timing == 1 )  CALL timing_start('zdf_mxl')
85      !
86      CALL wrk_alloc( jpi_crs,jpj_crs, imld )
87
88      IF( kt == nit000 ) THEN
89         IF(lwp) WRITE(numout,*)
90         IF(lwp) WRITE(numout,*) 'zdf_mxl : mixed layer depth'
91         IF(lwp) WRITE(numout,*) '~~~~~~~ '
92         !                             ! allocate zdfmxl arrays
93         IF( zdf_mxl_alloc_crs() /= 0 )   CALL ctl_stop( 'STOP', 'zdf_mxl : unable to allocate arrays' )
94      ENDIF
95
96      ! w-level of the mixing and mixed layers
97      nmln_crs(:,:) = mbkt_crs(:,:) + 1        ! Initialization to the number of w ocean point
98      imld(:,:)     = mbkt_crs(:,:) + 1
99      DO jk = jpkm1, nlb10, -1         ! from the bottom to nlb10
100         DO jj = 1, jpj_crs
101            DO ji = 1, jpi_crs
102               IF( rhop_crs(ji,jj,jk) > rhop_crs(ji,jj,nla10) + zrho_c )   nmln_crs(ji,jj) = jk      ! Mixed layer
103        !       IF( avt (ji,jj,jk) < zavt_c                     )   imld(ji,jj) = jk      ! Turbocline
104            END DO
105         END DO
106      END DO
107      ! depth of the mixing and mixed layers
108      !write(narea+2000,*)"nlb10 ",nlb10,SHAPE(hmlpt_crs),SHAPE(gdepw_crs) ; call flush(narea+2000)
109      DO jj = 1, jpj_crs
110         DO ji = 1, jpi_crs
111           ! iiki = imld(ji,jj)
112            iikn = nmln_crs(ji,jj)
113            ! write(narea+2000,*)ji,jj,iikn,gdept_crs(ji,jj,iikn-1) ; call flush(narea+2000)
114       !     hmld (ji,jj) = gdepw_crs(ji,jj,iiki  ) * tmask_crs(ji,jj,1)    ! Turbocline depth
115            !IF( iikn .LT. 2 .OR. iikn .GT. jpk )write(narea+2000,*)"iikn ",ji,jj,iikn ; call flush(narea+2000)
116            hmlp_crs (ji,jj) = gdepw_crs(ji,jj,iikn  ) * tmask_crs(ji,jj,1)    ! Mixed layer depth
117            hmlpt_crs(ji,jj) = gdept_crs(ji,jj,iikn-1)                     ! depth of the last T-point inside the mixed layer
118         END DO
119      END DO
120      IF( .NOT.lk_offline ) THEN            ! no need to output in offline mode
121  !       CALL iom_put( "mldr10_1", hmlp )   ! mixed layer depth
122   !      CALL iom_put( "mldkz5"  , hmld )   ! turbocline depth
123      ENDIF
124     
125    !  IF(ln_ctl)   CALL prt_ctl( tab2d_1=REAL(nmln,wp), clinfo1=' nmln : ', tab2d_2=hmlp, clinfo2=' hmlp : ', ovlap=1 )
126      !
127      CALL wrk_dealloc( jpi_crs,jpj_crs, imld )
128      !
129      IF( nn_timing == 1 )  CALL timing_stop('zdf_mxl')
130      !
131   END SUBROUTINE zdf_mxl_crs
132
133   !!======================================================================
134END MODULE zdfmxl_crs
Note: See TracBrowser for help on using the repository browser.