1 | MODULE 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 | |
---|
30 | INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: nmln !: number of level in the mixed layer (used by TOP) |
---|
31 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: hmld !: mixing layer depth (turbocline) [m] |
---|
32 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: hmlp !: mixed layer depth (rho=rho0+zdcrit) [m] |
---|
33 | REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) :: hmlpt !: mixed layer depth at t-points [m] |
---|
34 | |
---|
35 | REAL(wp), PUBLIC :: rho_c = 0.01_wp !: density criterion for mixed layer depth |
---|
36 | REAL(wp) :: avt_c = 5.e-4_wp ! Kz criterion for the turbocline depth |
---|
37 | |
---|
38 | !! * Substitutions |
---|
39 | # include "domzgr_substitute.h90" |
---|
40 | !!---------------------------------------------------------------------- |
---|
41 | !! NEMO/OPA 4.0 , NEMO Consortium (2011) |
---|
42 | !! $Id$ |
---|
43 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
44 | !!---------------------------------------------------------------------- |
---|
45 | CONTAINS |
---|
46 | |
---|
47 | INTEGER FUNCTION zdf_mxl_alloc() |
---|
48 | !!---------------------------------------------------------------------- |
---|
49 | !! *** FUNCTION zdf_mxl_alloc *** |
---|
50 | !!---------------------------------------------------------------------- |
---|
51 | zdf_mxl_alloc = 0 ! set to zero if no array to be allocated |
---|
52 | IF( .NOT. ALLOCATED( nmln ) ) THEN |
---|
53 | ALLOCATE( nmln(jpi,jpj), hmld(jpi,jpj), hmlp(jpi,jpj), hmlpt(jpi,jpj), STAT= zdf_mxl_alloc ) |
---|
54 | ! |
---|
55 | IF( lk_mpp ) CALL mpp_sum ( zdf_mxl_alloc ) |
---|
56 | IF( zdf_mxl_alloc /= 0 ) CALL ctl_warn('zdf_mxl_alloc: failed to allocate arrays.') |
---|
57 | ! |
---|
58 | ENDIF |
---|
59 | END FUNCTION zdf_mxl_alloc |
---|
60 | |
---|
61 | |
---|
62 | SUBROUTINE zdf_mxl( kt ) |
---|
63 | !!---------------------------------------------------------------------- |
---|
64 | !! *** ROUTINE zdfmxl *** |
---|
65 | !! |
---|
66 | !! ** Purpose : Compute the turbocline depth and the mixed layer depth |
---|
67 | !! with density criteria. |
---|
68 | !! |
---|
69 | !! ** Method : The mixed layer depth is the shallowest W depth with |
---|
70 | !! the density of the corresponding T point (just bellow) bellow a |
---|
71 | !! given value defined locally as rho(10m) + rho_c |
---|
72 | !! The turbocline depth is the depth at which the vertical |
---|
73 | !! eddy diffusivity coefficient (resulting from the vertical physics |
---|
74 | !! alone, not the isopycnal part, see trazdf.F) fall below a given |
---|
75 | !! value defined locally (avt_c here taken equal to 5 cm/s2 by default) |
---|
76 | !! |
---|
77 | !! ** Action : nmln, hmld, hmlp, hmlpt |
---|
78 | !!---------------------------------------------------------------------- |
---|
79 | INTEGER, INTENT(in) :: kt ! ocean time-step index |
---|
80 | ! |
---|
81 | INTEGER :: ji, jj, jk ! dummy loop indices |
---|
82 | INTEGER :: iikn, iiki, ikt, imkt ! local integer |
---|
83 | REAL(wp) :: zN2_c ! local scalar |
---|
84 | INTEGER, POINTER, DIMENSION(:,:) :: imld ! 2D workspace |
---|
85 | !!---------------------------------------------------------------------- |
---|
86 | ! |
---|
87 | IF( nn_timing == 1 ) CALL timing_start('zdf_mxl') |
---|
88 | ! |
---|
89 | CALL wrk_alloc( jpi,jpj, imld ) |
---|
90 | |
---|
91 | IF( kt == nit000 ) THEN |
---|
92 | IF(lwp) WRITE(numout,*) |
---|
93 | IF(lwp) WRITE(numout,*) 'zdf_mxl : mixed layer depth' |
---|
94 | IF(lwp) WRITE(numout,*) '~~~~~~~ ' |
---|
95 | ! ! allocate zdfmxl arrays |
---|
96 | IF( zdf_mxl_alloc() /= 0 ) CALL ctl_stop( 'STOP', 'zdf_mxl : unable to allocate arrays' ) |
---|
97 | ENDIF |
---|
98 | |
---|
99 | ! w-level of the mixing and mixed layers |
---|
100 | nmln(:,:) = nlb10 ! Initialization to the number of w ocean point |
---|
101 | hmlp(:,:) = 0._wp ! here hmlp used as a dummy variable, integrating vertically N^2 |
---|
102 | zN2_c = grav * rho_c * r1_rau0 ! convert density criteria into N^2 criteria |
---|
103 | DO jk = nlb10, jpkm1 |
---|
104 | DO jj = 1, jpj ! Mixed layer level: w-level |
---|
105 | DO ji = 1, jpi |
---|
106 | ikt = mbkt(ji,jj) |
---|
107 | hmlp(ji,jj) = hmlp(ji,jj) + MAX( rn2b(ji,jj,jk) , 0._wp ) * fse3w(ji,jj,jk) |
---|
108 | IF( hmlp(ji,jj) < zN2_c ) nmln(ji,jj) = MIN( jk , ikt ) + 1 ! Mixed layer level |
---|
109 | END DO |
---|
110 | END DO |
---|
111 | END DO |
---|
112 | ! |
---|
113 | ! w-level of the turbocline |
---|
114 | imld(:,:) = mbkt(:,:) + 1 ! Initialization to the number of w ocean point |
---|
115 | DO jk = jpkm1, nlb10, -1 ! from the bottom to nlb10 |
---|
116 | DO jj = 1, jpj |
---|
117 | DO ji = 1, jpi |
---|
118 | imkt = mikt(ji,jj) |
---|
119 | IF( avt (ji,jj,jk) < avt_c ) imld(ji,jj) = MAX( imkt, jk ) ! Turbocline |
---|
120 | END DO |
---|
121 | END DO |
---|
122 | END DO |
---|
123 | ! depth of the mixing and mixed layers |
---|
124 | DO jj = 1, jpj |
---|
125 | DO ji = 1, jpi |
---|
126 | iiki = imld(ji,jj) |
---|
127 | iikn = nmln(ji,jj) |
---|
128 | imkt = mikt(ji,jj) |
---|
129 | hmld (ji,jj) = ( fsdepw(ji,jj,iiki ) - fsdepw(ji,jj,imkt ) ) * ssmask(ji,jj) ! Turbocline depth |
---|
130 | hmlp (ji,jj) = ( fsdepw(ji,jj,iikn ) - fsdepw(ji,jj,MAX( imkt,nla10 ) ) ) * ssmask(ji,jj) ! Mixed layer depth |
---|
131 | 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 |
---|
132 | END DO |
---|
133 | END DO |
---|
134 | IF( .NOT.lk_offline ) THEN ! no need to output in offline mode |
---|
135 | CALL iom_put( "mldr10_1", hmlp ) ! mixed layer depth |
---|
136 | CALL iom_put( "mldkz5" , hmld ) ! turbocline depth |
---|
137 | ENDIF |
---|
138 | |
---|
139 | IF(ln_ctl) CALL prt_ctl( tab2d_1=REAL(nmln,wp), clinfo1=' nmln : ', tab2d_2=hmlp, clinfo2=' hmlp : ', ovlap=1 ) |
---|
140 | ! |
---|
141 | CALL wrk_dealloc( jpi,jpj, imld ) |
---|
142 | ! |
---|
143 | IF( nn_timing == 1 ) CALL timing_stop('zdf_mxl') |
---|
144 | ! |
---|
145 | END SUBROUTINE zdf_mxl |
---|
146 | |
---|
147 | !!====================================================================== |
---|
148 | END MODULE zdfmxl |
---|