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 branches/UKMO/dev_r5518_v3.4_asm_nemovar_community/NEMOGCM/NEMO/OPA_SRC/ZDF – NEMO

source: branches/UKMO/dev_r5518_v3.4_asm_nemovar_community/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfmxl.F90 @ 6661

Last change on this file since 6661 was 6661, checked in by kingr, 8 years ago

Made changes to code to fix bug in appplying 2D assimilation increments.

File size: 9.0 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   !!            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 zdf_oce         ! ocean vertical physics
16   USE in_out_manager  ! I/O manager
17   USE prtctl          ! Print control
18   USE phycst          ! physical constants
19   USE iom             ! I/O library
20   USE lib_mpp         ! MPP library
21   USE wrk_nemo        ! work arrays
22   USE timing          ! Timing
23   USE trc_oce, ONLY : lk_offline ! offline flag
24
25   IMPLICIT NONE
26   PRIVATE
27
28   PUBLIC   zdf_mxl       ! called by step.F90
29   PUBLIC   zdf_mxl_tref  ! called by asminc.F90
30   PUBLIC   zdf_mxl_alloc ! Used in zdf_tke_init
31
32   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   nmln    !: number of level in the mixed layer (used by TOP)
33   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmld    !: mixing layer depth (turbocline)      [m]
34   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmlp    !: mixed layer depth  (rho=rho0+zdcrit) [m]
35   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmlpt   !: mixed layer depth at t-points        [m]
36   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hmld_tref  !: mixed layer depth at t-points - temperature criterion [m]
37
38   REAL(wp), PUBLIC ::   rho_c = 0.01_wp    !: density criterion for mixed layer depth
39   REAL(wp)         ::   avt_c = 5.e-4_wp   ! Kz criterion for the turbocline depth
40
41   !! * Substitutions
42#  include "domzgr_substitute.h90"
43   !!----------------------------------------------------------------------
44   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
45   !! $Id$
46   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
47   !!----------------------------------------------------------------------
48CONTAINS
49
50   INTEGER FUNCTION zdf_mxl_alloc()
51      !!----------------------------------------------------------------------
52      !!               ***  FUNCTION zdf_mxl_alloc  ***
53      !!----------------------------------------------------------------------
54      zdf_mxl_alloc = 0      ! set to zero if no array to be allocated
55      IF( .NOT. ALLOCATED( nmln ) ) THEN
56         ALLOCATE( nmln(jpi,jpj), hmld(jpi,jpj), hmlp(jpi,jpj), hmlpt(jpi,jpj), &
57         &                           hmld_tref(jpi,jpj), STAT= zdf_mxl_alloc )
58         !
59         IF( lk_mpp             )   CALL mpp_sum ( zdf_mxl_alloc )
60         IF( zdf_mxl_alloc /= 0 )   CALL ctl_warn('zdf_mxl_alloc: failed to allocate arrays.')
61         !
62      ENDIF
63   END FUNCTION zdf_mxl_alloc
64
65
66   SUBROUTINE zdf_mxl( kt )
67      !!----------------------------------------------------------------------
68      !!                  ***  ROUTINE zdfmxl  ***
69      !!                   
70      !! ** Purpose :   Compute the turbocline depth and the mixed layer depth
71      !!              with density criteria.
72      !!
73      !! ** Method  :   The mixed layer depth is the shallowest W depth with
74      !!      the density of the corresponding T point (just bellow) bellow a
75      !!      given value defined locally as rho(10m) + rho_c
76      !!               The turbocline depth is the depth at which the vertical
77      !!      eddy diffusivity coefficient (resulting from the vertical physics
78      !!      alone, not the isopycnal part, see trazdf.F) fall below a given
79      !!      value defined locally (avt_c here taken equal to 5 cm/s2 by default)
80      !!
81      !! ** Action  :   nmln, hmld, hmlp, hmlpt
82      !!----------------------------------------------------------------------
83      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
84      !
85      INTEGER  ::   ji, jj, jk   ! dummy loop indices
86      INTEGER  ::   iikn, iiki, ikt, imkt   ! local integer
87      REAL(wp) ::   zN2_c        ! local scalar
88      INTEGER, POINTER, DIMENSION(:,:) ::   imld   ! 2D workspace
89      !!----------------------------------------------------------------------
90      !
91      IF( nn_timing == 1 )  CALL timing_start('zdf_mxl')
92      !
93      CALL wrk_alloc( jpi,jpj, imld )
94
95      IF( kt == nit000 ) THEN
96         IF(lwp) WRITE(numout,*)
97         IF(lwp) WRITE(numout,*) 'zdf_mxl : mixed layer depth'
98         IF(lwp) WRITE(numout,*) '~~~~~~~ '
99         !                             ! allocate zdfmxl arrays
100         IF( zdf_mxl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'zdf_mxl : unable to allocate arrays' )
101      ENDIF
102
103      ! w-level of the mixing and mixed layers
104      nmln(:,:)  = nlb10               ! Initialization to the number of w ocean point
105      hmlp(:,:)  = 0._wp               ! here hmlp used as a dummy variable, integrating vertically N^2
106      zN2_c = grav * rho_c * r1_rau0   ! convert density criteria into N^2 criteria
107      DO jk = nlb10, jpkm1
108         DO jj = 1, jpj                ! Mixed layer level: w-level
109            DO ji = 1, jpi
110               ikt = mbkt(ji,jj)
111               hmlp(ji,jj) = hmlp(ji,jj) + MAX( rn2b(ji,jj,jk) , 0._wp ) * fse3w(ji,jj,jk)
112               IF( hmlp(ji,jj) < zN2_c )   nmln(ji,jj) = MIN( jk , ikt ) + 1   ! Mixed layer level
113            END DO
114         END DO
115      END DO
116      !
117      ! w-level of the turbocline
118      imld(:,:) = mbkt(:,:) + 1        ! Initialization to the number of w ocean point
119      DO jk = jpkm1, nlb10, -1         ! from the bottom to nlb10
120         DO jj = 1, jpj
121            DO ji = 1, jpi
122               imkt = mikt(ji,jj)
123               IF( avt (ji,jj,jk) < avt_c )   imld(ji,jj) = MAX( imkt, jk )      ! Turbocline
124            END DO
125         END DO
126      END DO
127      ! depth of the mixing and mixed layers
128      DO jj = 1, jpj
129         DO ji = 1, jpi
130            iiki = imld(ji,jj)
131            iikn = nmln(ji,jj)
132            imkt = mikt(ji,jj)
133            hmld (ji,jj) = ( fsdepw(ji,jj,iiki  ) - fsdepw(ji,jj,imkt ) ) * ssmask(ji,jj)    ! Turbocline depth
134            hmlp (ji,jj) = ( fsdepw(ji,jj,iikn  ) - fsdepw(ji,jj,imkt ) ) * ssmask(ji,jj)    ! Mixed layer depth
135            hmlpt(ji,jj) = ( fsdept(ji,jj,iikn-1) - fsdepw(ji,jj,imkt ) ) * ssmask(ji,jj)    ! depth of the last T-point inside the mixed layer
136         END DO
137      END DO
138      IF( .NOT.lk_offline ) THEN            ! no need to output in offline mode
139         CALL iom_put( "mldr10_1", hmlp )   ! mixed layer depth
140         CALL iom_put( "mldkz5"  , hmld )   ! turbocline depth
141      ENDIF
142     
143      IF(ln_ctl)   CALL prt_ctl( tab2d_1=REAL(nmln,wp), clinfo1=' nmln : ', tab2d_2=hmlp, clinfo2=' hmlp : ', ovlap=1 )
144      !
145      CALL wrk_dealloc( jpi,jpj, imld )
146      !
147      IF( nn_timing == 1 )  CALL timing_stop('zdf_mxl')
148      !
149   END SUBROUTINE zdf_mxl
150
151
152   SUBROUTINE zdf_mxl_tref()
153      !!----------------------------------------------------------------------
154      !!                  ***  ROUTINE zdf_mxl_tref  ***
155      !!                   
156      !! ** Purpose :   Compute the mixed layer depth with temperature criteria.
157      !!
158      !! ** Method  :   The temperature-defined mixed layer depth is required
159      !!                   when assimilating SST in a 2D analysis.
160      !!
161      !! ** Action  :   hmld_tref
162      !!----------------------------------------------------------------------
163      !
164      INTEGER  ::   ji, jj, jk   ! dummy loop indices
165      REAL(wp) ::   t_ref               ! Reference temperature 
166      REAL(wp) ::   temp_c = 0.2        ! temperature criterion for mixed layer depth 
167      !!----------------------------------------------------------------------
168      !
169      ! Initialise array
170      IF( zdf_mxl_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'zdf_mxl_tref : unable to allocate arrays' )
171     
172      !For the AMM model assimiation uses a temperature based mixed layer depth 
173      !This is defined here 
174      DO jj = 1, jpj 
175         DO ji = 1, jpi 
176           hmld_tref(ji,jj)=fsdept(ji,jj,1  )   
177           IF(ssmask(ji,jj) > 0.)THEN 
178             t_ref=tsn(ji,jj,1,jp_tem) 
179             DO jk=2,jpk 
180               IF(ssmask(ji,jj)==0.)THEN 
181                  hmld_tref(ji,jj)=fsdept(ji,jj,jk ) 
182                  EXIT 
183               ELSEIF( ABS(tsn(ji,jj,jk,jp_tem)-t_ref) < temp_c)THEN 
184                  hmld_tref(ji,jj)=fsdept(ji,jj,jk ) 
185               ELSE 
186                  EXIT 
187               ENDIF 
188             ENDDO 
189           ENDIF 
190         ENDDO 
191      ENDDO
192
193   END SUBROUTINE zdf_mxl_tref
194
195   !!======================================================================
196END MODULE zdfmxl
Note: See TracBrowser for help on using the repository browser.