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.
diahth.F90 in NEMO/releases/release-4.0/src/OCE/DIA – NEMO

source: NEMO/releases/release-4.0/src/OCE/DIA/diahth.F90 @ 11093

Last change on this file since 11093 was 11093, checked in by agn, 5 years ago

original lot of changes to diahth.F90

  • Property svn:keywords set to Id
File size: 19.2 KB
Line 
1MODULE diahth
2   !!======================================================================
3   !!                       ***  MODULE  diahth  ***
4   !! Ocean diagnostics: thermocline and 20 degree depth
5   !!======================================================================
6   !! History :  OPA  !  1994-09  (J.-P. Boulanger)  Original code
7   !!                 !  1996-11  (E. Guilyardi)  OPA8
8   !!                 !  1997-08  (G. Madec)  optimization
9   !!                 !  1999-07  (E. Guilyardi)  hd28 + heat content
10   !!   NEMO     1.0  !  2002-06  (G. Madec)  F90: Free form and module
11   !!            3.2  !  2009-07  (S. Masson) hc300 bugfix + cleaning + add new diag
12   !!----------------------------------------------------------------------
13   !!----------------------------------------------------------------------
14   !!   'key_diahth' :                              thermocline depth diag.
15   !!----------------------------------------------------------------------
16   !!   dia_hth      : Compute varius diagnostics associated with the mixed layer
17   !!----------------------------------------------------------------------
18   USE oce             ! ocean dynamics and tracers
19   USE dom_oce         ! ocean space and time domain
20   USE phycst          ! physical constants
21   !
22   USE in_out_manager  ! I/O manager
23   USE lib_mpp         ! MPP library
24   USE iom             ! I/O library
25
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC   dia_hth       ! routine called by step.F90
30   PUBLIC   dia_hth_init  ! routine called by nemogcm.F90
31
32   LOGICAL, PUBLIC ::   ln_diahth   !: Compute further diagnostics of ML and thermocline depth
33
34   !!----------------------------------------------------------------------
35   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
36   !! $Id$
37   !! Software governed by the CeCILL license (see ./LICENSE)
38   !!----------------------------------------------------------------------
39CONTAINS
40
41
42   SUBROUTINE dia_hth( kt )
43     !!---------------------------------------------------------------------
44     !!                  ***  ROUTINE dia_hth  ***
45     !!
46     !! ** Purpose : Computes
47     !!      the mixing layer depth (turbocline): avt = 5.e-4
48     !!      the depth of strongest vertical temperature gradient
49     !!      the mixed layer depth with density     criteria: rho = rho(10m or surf) + 0.03(or 0.01)
50     !!      the mixed layer depth with temperature criteria: abs( tn - tn(10m) ) = 0.2
51     !!      the top of the thermochine: tn = tn(10m) - ztem2
52     !!      the pycnocline depth with density criteria equivalent to a temperature variation
53     !!                rho = rho10m + (dr/dT)(T,S,10m)*(-0.2 degC)
54     !!      the barrier layer thickness
55     !!      the maximal verical inversion of temperature and its depth max( 0, max of tn - tn(10m) )
56     !!      the depth of the 20 degree isotherm (linear interpolation)
57     !!      the depth of the 28 degree isotherm (linear interpolation)
58     !!      the heat content of first 300 m
59     !!
60     !! ** Method :
61     !!-------------------------------------------------------------------
62     INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
63     !!
64     INTEGER                          ::   ji, jj, jk            ! dummy loop arguments
65     INTEGER                          ::   iid, ilevel           ! temporary integers
66     INTEGER, DIMENSION(jpi,jpj) ::   ik20, ik28  ! levels
67     REAL(wp)                         ::   zavt5 = 5.e-4_wp      ! Kz criterion for the turbocline depth
68     REAL(wp)                         ::   zrho3 = 0.03_wp       ! density     criterion for mixed layer depth
69     REAL(wp)                         ::   zrho1 = 0.01_wp       ! density     criterion for mixed layer depth
70     REAL(wp)                         ::   ztem2 = 0.2_wp        ! temperature criterion for mixed layer depth
71     REAL(wp)                         ::   zthick_0, zcoef       ! temporary scalars
72     REAL(wp)                         ::   zztmp, zzdep          ! temporary scalars inside do loop
73     REAL(wp)                         ::   zu, zv, zw, zut, zvt  ! temporary workspace
74     REAL(wp), DIMENSION(jpi,jpj) ::   zabs2      ! MLD: abs( tn - tn(10m) ) = ztem2
75     REAL(wp), DIMENSION(jpi,jpj) ::   ztm2       ! Top of thermocline: tn = tn(10m) - ztem2
76     REAL(wp), DIMENSION(jpi,jpj) ::   zrho10_3   ! MLD: rho = rho10m + zrho3
77     REAL(wp), DIMENSION(jpi,jpj) ::   zpycn      ! pycnocline: rho = rho10m + (dr/dT)(T,S,10m)*(-0.2 degC)
78     REAL(wp), DIMENSION(jpi,jpj) ::   ztinv      ! max of temperature inversion
79     REAL(wp), DIMENSION(jpi,jpj) ::   zdepinv    ! depth of temperature inversion
80     REAL(wp), DIMENSION(jpi,jpj) ::   zrho0_3    ! MLD rho = rho(surf) = 0.03
81     REAL(wp), DIMENSION(jpi,jpj) ::   zrho0_1    ! MLD rho = rho(surf) = 0.01
82     REAL(wp), DIMENSION(jpi,jpj) ::   zmaxdzT    ! max of dT/dz
83     REAL(wp), DIMENSION(jpi,jpj) ::   zthick     ! vertical integration thickness
84     REAL(wp), DIMENSION(jpi,jpj) ::   zdelr      ! delta rho equivalent to deltaT = 0.2
85   ! note: following variables should move to local variables once iom_put is always used
86     REAL(wp), DIMENSION(jpi,jpj) ::   zhth    !: depth of the max vertical temperature gradient [m]
87     REAL(wp), DIMENSION(jpi,jpj) ::   zhd20   !: depth of 20 C isotherm                         [m]
88     REAL(wp), DIMENSION(jpi,jpj) ::   zhd28   !: depth of 28 C isotherm                         [m]
89     REAL(wp), DIMENSION(jpi,jpj) ::   zhtc3   !: heat content of first 300 m                    [W]
90
91<<<<<<< variant A
92     IF (iom_use("mlddzt").OR.iom_use("mldr0_3").OR.iom_use("mldr0_1")) THEN
93        ! ------------------------------------------------------------- !
94        ! thermocline depth: strongest vertical gradient of temperature !
95        ! turbocline depth (mixing layer depth): avt = zavt5            !
96        ! MLD: rho = rho(1) + zrho3                                     !
97        ! MLD: rho = rho(1) + zrho1                                     !
98        ! ------------------------------------------------------------- !
99        zmaxdzT(:,:) = 0._wp
100        IF( nla10 > 1 ) THEN
101>>>>>>> variant B
102     IF(iom_use("mlddzt").OR.iom_use("mldr0_3").OR.iom_use("mldr0_1").OR.iom_use("mld_dt02") &
103          & .OR.iom_use("topthdep").OR.iom_use("mldr10_3").OR.iom_use("pycndep").OR.iom_use("tinv").OR.iom_use("depti")) THEN
104        ! initialization
105        ztinv  (:,:) = 0._wp 
106        zdepinv(:,:) = 0._wp 
107        zmaxdzT(:,:) = 0._wp 
108        DO jj = 1, jpj
109           DO ji = 1, jpi
110              zztmp = gdepw_n(ji,jj,mbkt(ji,jj)+1) 
111              zhth     (ji,jj) = zztmp
112              zabs2   (ji,jj) = zztmp
113              ztm2    (ji,jj) = zztmp
114              zrho10_3(ji,jj) = zztmp
115              zpycn   (ji,jj) = zztmp
116           END DO
117        END DO
118        IF( nla10 > 1 ) THEN 
119======= end
120           DO jj = 1, jpj
121              DO ji = 1, jpi
122                 zztmp = gdepw_n(ji,jj,mbkt(ji,jj)+1)
123                 zrho0_3(ji,jj) = zztmp
124                 zrho0_1(ji,jj) = zztmp
125<<<<<<< variant A
126                 zhth(ji,jj) = zztmp
127>>>>>>> variant B
128======= end
129              END DO
130           END DO
131<<<<<<< variant A
132        ELSE IF (iom_use("mlddzt")) THEN
133           DO jj = 1, jpj
134              DO ji = 1, jpi
135                 zztmp = gdepw_n(ji,jj,mbkt(ji,jj)+1)
136                 zhth(ji,jj) = zztmp
137              END DO
138           END DO
139        ELSE
140           zhth(:,:) = 0._wp
141>>>>>>> variant B
142======= end
143        ENDIF
144<<<<<<< variant A
145>>>>>>> variant B
146     ENDIF
147======= end
148
149<<<<<<< variant A
150>>>>>>> variant B
151     IF (iom_use("mlddzt").OR.iom_use("mldr0_3").OR.iom_use("mldr0_1")) THEN
152        ! ------------------------------------------------------------- !
153        ! thermocline depth: strongest vertical gradient of temperature !
154        ! turbocline depth (mixing layer depth): avt = zavt5            !
155        ! MLD: rho = rho(1) + zrho3                                     !
156        ! MLD: rho = rho(1) + zrho1                                     !
157        ! ------------------------------------------------------------- !
158======= end
159        DO jk = jpkm1, 2, -1   ! loop from bottom to 2
160           DO jj = 1, jpj
161              DO ji = 1, jpi
162                 !
163                 zzdep = gdepw_n(ji,jj,jk)
164                 zztmp = ( tsn(ji,jj,jk-1,jp_tem) - tsn(ji,jj,jk,jp_tem) ) / zzdep * tmask(ji,jj,jk)   ! vertical gradient of temperature (dT/dz)
165                 zzdep = zzdep * tmask(ji,jj,1)
166
167<<<<<<< variant A
168                 IF( zztmp > zmaxdzT(ji,jj) ) THEN
169>>>>>>> variant B
170                 IF( zztmp > zmaxdzT(ji,jj) ) THEN                       
171======= end
172                    zmaxdzT(ji,jj) = zztmp   ;   zhth    (ji,jj) = zzdep                ! max and depth of dT/dz
173                 ENDIF
174
175<<<<<<< variant A
176                 IF( nla10 > 1 ) THEN
177>>>>>>> variant B
178                 IF( nla10 > 1 ) THEN 
179======= end
180                    zztmp = rhop(ji,jj,jk) - rhop(ji,jj,1)                             ! delta rho(1)
181                    IF( zztmp > zrho3 )          zrho0_3(ji,jj) = zzdep                ! > 0.03
182                    IF( zztmp > zrho1 )          zrho0_1(ji,jj) = zzdep                ! > 0.01
183                 ENDIF
184
185              END DO
186           END DO
187        END DO
188
189        IF (iom_use("mlddzt")) CALL iom_put( "mlddzt", zhth*tmask(:,:,1) )            ! depth of the thermocline
190<<<<<<< variant A
191        IF( nla10 > 1 ) THEN
192>>>>>>> variant B
193        IF( nla10 > 1 ) THEN 
194======= end
195           IF (iom_use("mldr0_3")) CALL iom_put( "mldr0_3", zrho0_3*tmask(:,:,1) )   ! MLD delta rho(surf) = 0.03
196           IF (iom_use("mldr0_1")) CALL iom_put( "mldr0_1", zrho0_1*tmask(:,:,1) )   ! MLD delta rho(surf) = 0.01
197        ENDIF
198     ENDIF
199
200     IF (iom_use("mld_dt02").OR.iom_use("topthdep").OR.iom_use("mldr10_3").OR. &
201          & iom_use("pycndep").OR.iom_use("tinv").OR.iom_use("depti")) THEN
202        DO jj = 1, jpj
203           DO ji = 1, jpi
204              zztmp = gdepw_n(ji,jj,mbkt(ji,jj)+1)
205              zabs2   (ji,jj) = zztmp
206              ztm2    (ji,jj) = zztmp
207              zrho10_3(ji,jj) = zztmp
208              zpycn   (ji,jj) = zztmp
209           END DO
210        END DO
211        ztinv  (:,:) = 0._wp
212        zdepinv(:,:) = 0._wp
213
214        IF (iom_use("pycndep")) THEN
215           ! Preliminary computation
216           ! computation of zdelr = (dr/dT)(T,S,10m)*(-0.2 degC)
217           DO jj = 1, jpj
218              DO ji = 1, jpi
219                 IF( tmask(ji,jj,nla10) == 1. ) THEN
220                    zu  =  1779.50 + 11.250 * tsn(ji,jj,nla10,jp_tem) - 3.80   * tsn(ji,jj,nla10,jp_sal)                             &
221                         &                                              - 0.0745 * tsn(ji,jj,nla10,jp_tem) * tsn(ji,jj,nla10,jp_tem)   &
222                         &                                              - 0.0100 * tsn(ji,jj,nla10,jp_tem) * tsn(ji,jj,nla10,jp_sal)
223                    zv  =  5891.00 + 38.000 * tsn(ji,jj,nla10,jp_tem) + 3.00   * tsn(ji,jj,nla10,jp_sal)                             &
224                         &                                              - 0.3750 * tsn(ji,jj,nla10,jp_tem) * tsn(ji,jj,nla10,jp_tem)
225                    zut =    11.25 -  0.149 * tsn(ji,jj,nla10,jp_tem) - 0.01   * tsn(ji,jj,nla10,jp_sal)
226                    zvt =    38.00 -  0.750 * tsn(ji,jj,nla10,jp_tem)
227                    zw  = (zu + 0.698*zv) * (zu + 0.698*zv)
228                    zdelr(ji,jj) = ztem2 * (1000.*(zut*zv - zvt*zu)/zw)
229                 ELSE
230                    zdelr(ji,jj) = 0._wp
231                 ENDIF
232              END DO
233           END DO
234        ELSE
235           zdelr(:,:) = 0._wp
236        ENDIF
237
238        ! ------------------------------------------------------------- !
239        ! MLD: abs( tn - tn(10m) ) = ztem2                              !
240        ! Top of thermocline: tn = tn(10m) - ztem2                      !
241        ! MLD: rho = rho10m + zrho3                                     !
242        ! pycnocline: rho = rho10m + (dr/dT)(T,S,10m)*(-0.2 degC)       !
243        ! temperature inversion: max( 0, max of tn - tn(10m) )          !
244        ! depth of temperature inversion                                !
245        ! ------------------------------------------------------------- !
246        DO jk = jpkm1, nlb10, -1   ! loop from bottom to nlb10
247           DO jj = 1, jpj
248              DO ji = 1, jpi
249                 !
250                 zzdep = gdepw_n(ji,jj,jk) * tmask(ji,jj,1)
251                 !
252                 zztmp = tsn(ji,jj,nla10,jp_tem) - tsn(ji,jj,jk,jp_tem)  ! - delta T(10m)
253                 IF( ABS(zztmp) > ztem2 )      zabs2   (ji,jj) = zzdep   ! abs > 0.2
254                 IF(     zztmp  > ztem2 )      ztm2    (ji,jj) = zzdep   ! > 0.2
255                 zztmp = -zztmp                                          ! delta T(10m)
256                 IF( zztmp >  ztinv(ji,jj) ) THEN                        ! temperature inversion
257                    ztinv(ji,jj) = zztmp   ;   zdepinv (ji,jj) = zzdep   ! max value and depth
258                 ENDIF
259
260                 zztmp = rhop(ji,jj,jk) - rhop(ji,jj,nla10)              ! delta rho(10m)
261                 IF( zztmp > zrho3        )    zrho10_3(ji,jj) = zzdep   ! > 0.03
262                 IF( zztmp > zdelr(ji,jj) )    zpycn   (ji,jj) = zzdep   ! > equi. delta T(10m) - 0.2
263                 !
264              END DO
265           END DO
266        END DO
267
268        IF (iom_use("mld_dt02")) CALL iom_put( "mld_dt02", zabs2*tmask(:,:,1)        )   ! MLD abs(delta t) - 0.2
269        IF (iom_use("topthdep")) CALL iom_put( "topthdep", ztm2*tmask(:,:,1)         )   ! T(10) - 0.2
270        IF (iom_use("mldr10_3")) CALL iom_put( "mldr10_3", zrho10_3*tmask(:,:,1)     )   ! MLD delta rho(10m) = 0.03
271        IF (iom_use("pycndep")) CALL iom_put( "pycndep" , zpycn*tmask(:,:,1)        )   ! MLD delta rho equi. delta T(10m) = 0.2
272        IF (iom_use("tinv")) CALL iom_put( "tinv"    , ztinv*tmask(:,:,1)        )   ! max. temp. inv. (t10 ref)
273        IF (iom_use("depti")) CALL iom_put( "depti"   , zdepinv*tmask(:,:,1)      )   ! depth of max. temp. inv. (t10 ref)
274     ENDIF
275
276     IF(iom_use("20d").OR.iom_use("28d")) THEN
277        ! ----------------------------------- !
278        ! search deepest level above 20C/28C  !
279        ! ----------------------------------- !
280        ik20(:,:) = 1
281        ik28(:,:) = 1
282        DO jk = 1, jpkm1   ! beware temperature is not always decreasing with depth => loop from top to bottom
283           DO jj = 1, jpj
284              DO ji = 1, jpi
285                 zztmp = tsn(ji,jj,jk,jp_tem)
286                 IF( zztmp >= 20. )   ik20(ji,jj) = jk
287                 IF( zztmp >= 28. )   ik28(ji,jj) = jk
288              END DO
289           END DO
290        END DO
291
292        ! --------------------------- !
293        !  Depth of 20C/28C isotherm  !
294        ! --------------------------- !
295        DO jj = 1, jpj
296           DO ji = 1, jpi
297              !
298              zzdep = gdepw_n(ji,jj,mbkt(ji,jj)+1)       ! depth of the oean bottom
299              !
300              iid = ik20(ji,jj)
301              IF( iid /= 1 ) THEN
302                 zztmp =      gdept_n(ji,jj,iid  )   &                     ! linear interpolation
303                      &  + (    gdept_n(ji,jj,iid+1) - gdept_n(ji,jj,iid)                       )   &
304                      &  * ( 20.*tmask(ji,jj,iid+1) - tsn(ji,jj,iid,jp_tem)                       )   &
305                      &  / ( tsn(ji,jj,iid+1,jp_tem) - tsn(ji,jj,iid,jp_tem) + (1.-tmask(ji,jj,1)) )
306                 zhd20(ji,jj) = MIN( zztmp , zzdep) * tmask(ji,jj,1)       ! bound by the ocean depth
307              ELSE
308                 zhd20(ji,jj) = 0._wp
309              ENDIF
310              !
311              iid = ik28(ji,jj)
312              IF( iid /= 1 ) THEN
313                 zztmp =      gdept_n(ji,jj,iid  )   &                     ! linear interpolation
314                      &  + (    gdept_n(ji,jj,iid+1) - gdept_n(ji,jj,iid)                       )   &
315                      &  * ( 28.*tmask(ji,jj,iid+1) -    tsn(ji,jj,iid,jp_tem)                       )   &
316                      &  / (  tsn(ji,jj,iid+1,jp_tem) -    tsn(ji,jj,iid,jp_tem) + (1.-tmask(ji,jj,1)) )
317                 zhd28(ji,jj) = MIN( zztmp , zzdep ) * tmask(ji,jj,1)      ! bound by the ocean depth
318              ELSE
319                 zhd28(ji,jj) = 0._wp
320              ENDIF
321
322           END DO
323        END DO
324        CALL iom_put( "20d", zhd20 )   ! depth of the 20 isotherm
325        CALL iom_put( "28d", zhd28 )   ! depth of the 28 isotherm
326     ENDIF
327
328     ! ----------------------------- !
329     !  Heat content of first 300 m  !
330     ! ----------------------------- !
331     IF (iom_use("hc300")) THEN
332        ! find ilevel with (ilevel+1) the deepest W-level above 300m (we assume we can use e3t_1d to do this search...)
333        ilevel   = 0
334        zthick_0 = 0._wp
335        DO jk = 1, jpkm1
336           zthick_0 = zthick_0 + e3t_1d(jk)
337           IF( zthick_0 < 300. )   ilevel = jk
338        END DO
339        ! surface boundary condition
340        IF( ln_linssh ) THEN   ;   zthick(:,:) = sshn(:,:)   ;   zhtc3(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:) * tmask(:,:,1)
341        ELSE                   ;   zthick(:,:) = 0._wp       ;   zhtc3(:,:) = 0._wp
342        ENDIF
343        ! integration down to ilevel
344        DO jk = 1, ilevel
345           zthick(:,:) = zthick(:,:) + e3t_n(:,:,jk)
346           zhtc3  (:,:) = zhtc3  (:,:) + e3t_n(:,:,jk) * tsn(:,:,jk,jp_tem) * tmask(:,:,jk)
347        END DO
348        ! deepest layer
349        zthick(:,:) = 300. - zthick(:,:)   !   remaining thickness to reach 300m
350        DO jj = 1, jpj
351           DO ji = 1, jpi
352              zhtc3(ji,jj) = zhtc3(ji,jj) + tsn(ji,jj,ilevel+1,jp_tem)                  &
353                   &                      * MIN( e3t_n(ji,jj,ilevel+1), zthick(ji,jj) ) * tmask(ji,jj,ilevel+1)
354           END DO
355        END DO
356        ! from temperature to heat contain
357        zcoef = rau0 * rcp
358        zhtc3(:,:) = zcoef * zhtc3(:,:)
359        CALL iom_put( "hc300", zhtc3*tmask(:,:,1) )      ! first 300m heat content
360     ENDIF
361     !
362      IF( ln_timing )   CALL timing_stop('dia_hth')
363     !
364   END SUBROUTINE dia_hth
365
366
367   SUBROUTINE dia_hth_init
368      !!---------------------------------------------------------------------------
369      !!                  ***  ROUTINE dia_hth_init  ***
370      !!
371      !! ** Purpose: Initialization for ML and thermocline depths
372      !!
373      !! ** Action : Read namelist flag to permit or not extra Ml depths and thermocline depths
374      !!---------------------------------------------------------------------------
375      INTEGER ::   ierror, ios   ! local integer
376      !!
377      NAMELIST/namhth/ ln_diahth
378      !!---------------------------------------------------------------------------
379       !
380      IF(lwp) THEN
381         WRITE(numout,*)
382         WRITE(numout,*) 'dia_hth_init : heat and salt budgets diagnostics'
383         WRITE(numout,*) '~~~~~~~~~~~~ '
384      ENDIF
385      REWIND( numnam_ref )              ! Namelist namhth in reference namelist
386      READ  ( numnam_ref, namhth, IOSTAT = ios, ERR = 901)
387901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namhth in reference namelist', lwp )
388      REWIND( numnam_cfg )              ! Namelist namhth in configuration namelist
389      READ  ( numnam_cfg, namhth, IOSTAT = ios, ERR = 902 )
390902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namhth in configuration namelist', lwp )
391      IF(lwm) WRITE( numond, namhth )
392
393      IF(lwp) THEN
394         WRITE(numout,*) '   Namelist  namhth :'
395         WRITE(numout,*) '      check the heat and salt budgets (T) or not (F)       ln_diahth = ', ln_diahth
396      ENDIF
397      !
398   END SUBROUTINE dia_hth_init
399END MODULE diahth
Note: See TracBrowser for help on using the repository browser.