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 branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/DIA – NEMO

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/OPA_SRC/DIA/diahth.F90 @ 11738

Last change on this file since 11738 was 11738, checked in by marc, 4 years ago

The Dr Hook changes from my perl code.

File size: 18.7 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   !!            8.5  !  2002-06  (G. Madec)  F90: Free form and module
11   !!   NEMO     3.2  !  2009-07  (S. Masson) hc300 bugfix + cleaning + add new diag
12   !!----------------------------------------------------------------------
13#if   defined key_diahth   ||   defined key_esopa
14   !!----------------------------------------------------------------------
15   !!   'key_diahth' :                              thermocline depth diag.
16   !!----------------------------------------------------------------------
17   !!   dia_hth      : Compute varius diagnostics associated with the mixed layer
18   !!----------------------------------------------------------------------
19   USE oce             ! ocean dynamics and tracers
20   USE dom_oce         ! ocean space and time domain
21   USE phycst          ! physical constants
22   USE in_out_manager  ! I/O manager
23   USE lib_mpp         ! MPP library
24   USE iom             ! I/O library
25   USE timing          ! preformance summary
26
27   USE yomhook, ONLY: lhook, dr_hook
28   USE parkind1, ONLY: jprb, jpim
29
30   IMPLICIT NONE
31   PRIVATE
32
33   PUBLIC   dia_hth       ! routine called by step.F90
34   PUBLIC   dia_hth_alloc ! routine called by nemogcm.F90
35
36   LOGICAL , PUBLIC, PARAMETER          ::   lk_diahth = .TRUE.    !: thermocline-20d depths flag
37   ! note: following variables should move to local variables once iom_put is always used
38   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hth    !: depth of the max vertical temperature gradient [m]
39   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hd20   !: depth of 20 C isotherm                         [m]
40   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hd28   !: depth of 28 C isotherm                         [m]
41   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   htc3   !: heat content of first 300 m                    [W]
42
43   !! * Substitutions
44#  include "domzgr_substitute.h90"
45   !!----------------------------------------------------------------------
46   !! NEMO/OPA 4.0 , NEMO Consortium (2011)
47   !! $Id$
48   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
49   !!----------------------------------------------------------------------
50CONTAINS
51
52   FUNCTION dia_hth_alloc()
53      !!---------------------------------------------------------------------
54      INTEGER :: dia_hth_alloc
55      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
56      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
57      REAL(KIND=jprb)               :: zhook_handle
58
59      CHARACTER(LEN=*), PARAMETER :: RoutineName='DIA_HTH_ALLOC'
60
61      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
62
63      !!---------------------------------------------------------------------
64      !
65      ALLOCATE(hth(jpi,jpj), hd20(jpi,jpj), hd28(jpi,jpj), htc3(jpi,jpj), STAT=dia_hth_alloc)
66      !
67      IF( lk_mpp           )   CALL mpp_sum ( dia_hth_alloc )
68      IF(dia_hth_alloc /= 0)   CALL ctl_warn('dia_hth_alloc: failed to allocate arrays.')
69      !
70      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
71   END FUNCTION dia_hth_alloc
72
73
74   SUBROUTINE dia_hth( kt )
75      !!---------------------------------------------------------------------
76      !!                  ***  ROUTINE dia_hth  ***
77      !!
78      !! ** Purpose : Computes
79      !!      the mixing layer depth (turbocline): avt = 5.e-4
80      !!      the depth of strongest vertical temperature gradient
81      !!      the mixed layer depth with density     criteria: rho = rho(10m or surf) + 0.03(or 0.01)
82      !!      the mixed layer depth with temperature criteria: abs( tn - tn(10m) ) = 0.2       
83      !!      the top of the thermochine: tn = tn(10m) - ztem2
84      !!      the pycnocline depth with density criteria equivalent to a temperature variation
85      !!                rho = rho10m + (dr/dT)(T,S,10m)*(-0.2 degC)
86      !!      the barrier layer thickness
87      !!      the maximal verical inversion of temperature and its depth max( 0, max of tn - tn(10m) )
88      !!      the depth of the 20 degree isotherm (linear interpolation)
89      !!      the depth of the 28 degree isotherm (linear interpolation)
90      !!      the heat content of first 300 m
91      !!
92      !! ** Method :
93      !!-------------------------------------------------------------------
94      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
95      !!
96      INTEGER                          ::   ji, jj, jk            ! dummy loop arguments
97      INTEGER                          ::   iid, ilevel           ! temporary integers
98      INTEGER, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ik20, ik28  ! levels
99      REAL(wp)                         ::   zavt5 = 5.e-4_wp      ! Kz criterion for the turbocline depth
100      REAL(wp)                         ::   zrho3 = 0.03_wp       ! density     criterion for mixed layer depth
101      REAL(wp)                         ::   zrho1 = 0.01_wp       ! density     criterion for mixed layer depth
102      REAL(wp)                         ::   ztem2 = 0.2_wp        ! temperature criterion for mixed layer depth
103      REAL(wp)                         ::   zthick_0, zcoef       ! temporary scalars
104      REAL(wp)                         ::   zztmp, zzdep          ! temporary scalars inside do loop
105      REAL(wp)                         ::   zu, zv, zw, zut, zvt  ! temporary workspace
106      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zabs2      ! MLD: abs( tn - tn(10m) ) = ztem2
107      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ztm2       ! Top of thermocline: tn = tn(10m) - ztem2     
108      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zrho10_3   ! MLD: rho = rho10m + zrho3     
109      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zpycn      ! pycnocline: rho = rho10m + (dr/dT)(T,S,10m)*(-0.2 degC)
110      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ztinv      ! max of temperature inversion
111      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zdepinv    ! depth of temperature inversion
112      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zrho0_3    ! MLD rho = rho(surf) = 0.03
113      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zrho0_1    ! MLD rho = rho(surf) = 0.01
114      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zmaxdzT    ! max of dT/dz
115      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zthick     ! vertical integration thickness
116      REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   zdelr      ! delta rho equivalent to deltaT = 0.2
117      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
118      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
119      REAL(KIND=jprb)               :: zhook_handle
120
121      CHARACTER(LEN=*), PARAMETER :: RoutineName='DIA_HTH'
122
123      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
124
125      !!----------------------------------------------------------------------
126      IF( nn_timing == 1 )   CALL timing_start('dia_hth')
127
128      IF( kt == nit000 ) THEN
129         !                                      ! allocate dia_hth array
130         IF( dia_hth_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'lim_sbc_init : unable to allocate standard arrays' )
131
132         IF(.not. ALLOCATED(ik20))THEN
133            ALLOCATE(ik20(jpi,jpj), ik28(jpi,jpj), &
134               &      zabs2(jpi,jpj),   &
135               &      ztm2(jpi,jpj),    &
136               &      zrho10_3(jpi,jpj),&
137               &      zpycn(jpi,jpj),   &
138               &      ztinv(jpi,jpj),   &
139               &      zdepinv(jpi,jpj), &
140               &      zrho0_3(jpi,jpj), &
141               &      zrho0_1(jpi,jpj), &
142               &      zmaxdzT(jpi,jpj), &
143               &      zthick(jpi,jpj),  &
144               &      zdelr(jpi,jpj), STAT=ji)
145            IF( lk_mpp  )   CALL mpp_sum(ji)
146            IF( ji /= 0 )   CALL ctl_stop( 'STOP', 'dia_hth : unable to allocate standard ocean arrays' )
147         END IF
148
149         IF(lwp) WRITE(numout,*)
150         IF(lwp) WRITE(numout,*) 'dia_hth : diagnostics of the thermocline depth'
151         IF(lwp) WRITE(numout,*) '~~~~~~~ '
152         IF(lwp) WRITE(numout,*)
153      ENDIF
154
155      ! initialization
156      ztinv  (:,:) = 0._wp 
157      zdepinv(:,:) = 0._wp 
158      zmaxdzT(:,:) = 0._wp 
159      DO jj = 1, jpj
160         DO ji = 1, jpi
161            zztmp = bathy(ji,jj)
162            hth     (ji,jj) = zztmp
163            zabs2   (ji,jj) = zztmp
164            ztm2    (ji,jj) = zztmp
165            zrho10_3(ji,jj) = zztmp
166            zpycn   (ji,jj) = zztmp
167        END DO
168      END DO
169      IF( nla10 > 1 ) THEN
170         DO jj = 1, jpj
171            DO ji = 1, jpi
172               zztmp = bathy(ji,jj)
173               zrho0_3(ji,jj) = zztmp
174               zrho0_1(ji,jj) = zztmp
175            END DO
176         END DO
177      ENDIF
178     
179      ! Preliminary computation
180      ! computation of zdelr = (dr/dT)(T,S,10m)*(-0.2 degC)
181      DO jj = 1, jpj
182         DO ji = 1, jpi
183            IF( tmask(ji,jj,nla10) == 1. ) THEN
184               zu  =  1779.50 + 11.250 * tsn(ji,jj,nla10,jp_tem) - 3.80   * tsn(ji,jj,nla10,jp_sal)                             &
185                  &                                              - 0.0745 * tsn(ji,jj,nla10,jp_tem) * tsn(ji,jj,nla10,jp_tem)   &
186                  &                                              - 0.0100 * tsn(ji,jj,nla10,jp_tem) * tsn(ji,jj,nla10,jp_sal)
187               zv  =  5891.00 + 38.000 * tsn(ji,jj,nla10,jp_tem) + 3.00   * tsn(ji,jj,nla10,jp_sal)                             &
188                  &                                              - 0.3750 * tsn(ji,jj,nla10,jp_tem) * tsn(ji,jj,nla10,jp_tem)
189               zut =    11.25 -  0.149 * tsn(ji,jj,nla10,jp_tem) - 0.01   * tsn(ji,jj,nla10,jp_sal)
190               zvt =    38.00 -  0.750 * tsn(ji,jj,nla10,jp_tem)
191               zw  = (zu + 0.698*zv) * (zu + 0.698*zv)
192               zdelr(ji,jj) = ztem2 * (1000.*(zut*zv - zvt*zu)/zw)
193            ELSE
194               zdelr(ji,jj) = 0._wp
195            ENDIF
196         END DO
197      END DO
198
199      ! ------------------------------------------------------------- !
200      ! thermocline depth: strongest vertical gradient of temperature !
201      ! turbocline depth (mixing layer depth): avt = zavt5            !
202      ! MLD: rho = rho(1) + zrho3                                     !
203      ! MLD: rho = rho(1) + zrho1                                     !
204      ! ------------------------------------------------------------- !
205      DO jk = jpkm1, 2, -1   ! loop from bottom to 2
206         DO jj = 1, jpj
207            DO ji = 1, jpi
208               !
209               zzdep = fsdepw(ji,jj,jk)
210               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)
211               zzdep = zzdep * tmask(ji,jj,1)
212
213               IF( zztmp > zmaxdzT(ji,jj) ) THEN                       
214                  zmaxdzT(ji,jj) = zztmp   ;   hth    (ji,jj) = zzdep                ! max and depth of dT/dz
215               ENDIF
216               
217               IF( nla10 > 1 ) THEN
218                  zztmp = rhop(ji,jj,jk) - rhop(ji,jj,1)                             ! delta rho(1)
219                  IF( zztmp > zrho3 )          zrho0_3(ji,jj) = zzdep                ! > 0.03
220                  IF( zztmp > zrho1 )          zrho0_1(ji,jj) = zzdep                ! > 0.01
221               ENDIF
222
223            END DO
224         END DO
225      END DO
226     
227      CALL iom_put( "mlddzt", hth )            ! depth of the thermocline
228      IF( nla10 > 1 ) THEN
229         CALL iom_put( "mldr0_3", zrho0_3 )   ! MLD delta rho(surf) = 0.03
230         CALL iom_put( "mldr0_1", zrho0_1 )   ! MLD delta rho(surf) = 0.01
231      ENDIF
232
233      ! ------------------------------------------------------------- !
234      ! MLD: abs( tn - tn(10m) ) = ztem2                              !
235      ! Top of thermocline: tn = tn(10m) - ztem2                      !
236      ! MLD: rho = rho10m + zrho3                                     !
237      ! pycnocline: rho = rho10m + (dr/dT)(T,S,10m)*(-0.2 degC)       !
238      ! temperature inversion: max( 0, max of tn - tn(10m) )          !
239      ! depth of temperature inversion                                !
240      ! ------------------------------------------------------------- !
241      DO jk = jpkm1, nlb10, -1   ! loop from bottom to nlb10
242         DO jj = 1, jpj
243            DO ji = 1, jpi
244               !
245               zzdep = fsdepw(ji,jj,jk) * tmask(ji,jj,1)
246               !
247               zztmp = tsn(ji,jj,nla10,jp_tem) - tsn(ji,jj,jk,jp_tem)  ! - delta T(10m)
248               IF( ABS(zztmp) > ztem2 )      zabs2   (ji,jj) = zzdep   ! abs > 0.2
249               IF(     zztmp  > ztem2 )      ztm2    (ji,jj) = zzdep   ! > 0.2
250               zztmp = -zztmp                                          ! delta T(10m)
251               IF( zztmp >  ztinv(ji,jj) ) THEN                        ! temperature inversion
252                  ztinv(ji,jj) = zztmp   ;   zdepinv (ji,jj) = zzdep   ! max value and depth
253               ENDIF
254
255               zztmp = rhop(ji,jj,jk) - rhop(ji,jj,nla10)              ! delta rho(10m)
256               IF( zztmp > zrho3        )    zrho10_3(ji,jj) = zzdep   ! > 0.03
257               IF( zztmp > zdelr(ji,jj) )    zpycn   (ji,jj) = zzdep   ! > equi. delta T(10m) - 0.2
258               !
259            END DO
260         END DO
261      END DO
262
263      CALL iom_put( "mld_dt02", zabs2        )   ! MLD abs(delta t) - 0.2
264      CALL iom_put( "topthdep", ztm2         )   ! T(10) - 0.2
265      CALL iom_put( "mldr10_3", zrho10_3     )   ! MLD delta rho(10m) = 0.03
266      CALL iom_put( "pycndep" , zpycn        )   ! MLD delta rho equi. delta T(10m) = 0.2
267      CALL iom_put( "tinv"    , ztinv        )   ! max. temp. inv. (t10 ref)
268      CALL iom_put( "depti"   , zdepinv      )   ! depth of max. temp. inv. (t10 ref)
269
270
271      ! ----------------------------------- !
272      ! search deepest level above 20C/28C  !
273      ! ----------------------------------- !
274      ik20(:,:) = 1
275      ik28(:,:) = 1
276      DO jk = 1, jpkm1   ! beware temperature is not always decreasing with depth => loop from top to bottom
277         DO jj = 1, jpj
278            DO ji = 1, jpi
279               zztmp = tsn(ji,jj,jk,jp_tem)
280               IF( zztmp >= 20. )   ik20(ji,jj) = jk
281               IF( zztmp >= 28. )   ik28(ji,jj) = jk
282            END DO
283         END DO
284      END DO
285
286      ! --------------------------- !
287      !  Depth of 20C/28C isotherm  !
288      ! --------------------------- !
289      DO jj = 1, jpj
290         DO ji = 1, jpi
291            !
292            zzdep = fsdepw(ji,jj,mbkt(ji,jj)+1)       ! depth of the oean bottom
293            !
294            iid = ik20(ji,jj)
295            IF( iid /= 1 ) THEN
296               zztmp =      fsdept(ji,jj,iid  )   &                     ! linear interpolation
297                  &  + (    fsdept(ji,jj,iid+1) - fsdept(ji,jj,iid)                       )   &
298                  &  * ( 20.*tmask(ji,jj,iid+1) - tsn(ji,jj,iid,jp_tem)                       )   &
299                  &  / ( tsn(ji,jj,iid+1,jp_tem) - tsn(ji,jj,iid,jp_tem) + (1.-tmask(ji,jj,1)) )
300               hd20(ji,jj) = MIN( zztmp , zzdep) * tmask(ji,jj,1)       ! bound by the ocean depth
301            ELSE
302               hd20(ji,jj) = 0._wp
303            ENDIF
304            !
305            iid = ik28(ji,jj)
306            IF( iid /= 1 ) THEN
307               zztmp =      fsdept(ji,jj,iid  )   &                     ! linear interpolation
308                  &  + (    fsdept(ji,jj,iid+1) - fsdept(ji,jj,iid)                       )   &
309                  &  * ( 28.*tmask(ji,jj,iid+1) -    tsn(ji,jj,iid,jp_tem)                       )   &
310                  &  / (  tsn(ji,jj,iid+1,jp_tem) -    tsn(ji,jj,iid,jp_tem) + (1.-tmask(ji,jj,1)) )
311               hd28(ji,jj) = MIN( zztmp , zzdep ) * tmask(ji,jj,1)      ! bound by the ocean depth
312            ELSE
313               hd28(ji,jj) = 0._wp
314            ENDIF
315
316         END DO
317      END DO
318      CALL iom_put( "20d", hd20 )   ! depth of the 20 isotherm
319      CALL iom_put( "28d", hd28 )   ! depth of the 28 isotherm
320
321      ! ----------------------------- !
322      !  Heat content of first 300 m  !
323      ! ----------------------------- !
324
325      ! find ilevel with (ilevel+1) the deepest W-level above 300m (we assume we can use e3t_1d to do this search...)
326      ilevel   = 0
327      zthick_0 = 0._wp
328      DO jk = 1, jpkm1                     
329         zthick_0 = zthick_0 + e3t_1d(jk)
330         IF( zthick_0 < 300. )   ilevel = jk
331      END DO
332      ! surface boundary condition
333      IF( lk_vvl ) THEN   ;   zthick(:,:) = 0._wp       ;   htc3(:,:) = 0._wp                                   
334      ELSE                ;   zthick(:,:) = sshn(:,:)   ;   htc3(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:) * tmask(:,:,1)   
335      ENDIF
336      ! integration down to ilevel
337      DO jk = 1, ilevel
338         zthick(:,:) = zthick(:,:) + fse3t(:,:,jk)
339         htc3  (:,:) = htc3  (:,:) + fse3t(:,:,jk) * tsn(:,:,jk,jp_tem) * tmask(:,:,jk)
340      END DO
341      ! deepest layer
342      zthick(:,:) = 300. - zthick(:,:)   !   remaining thickness to reach 300m
343      DO jj = 1, jpj
344         DO ji = 1, jpi
345            htc3(ji,jj) = htc3(ji,jj) + tsn(ji,jj,ilevel+1,jp_tem) * MIN( fse3t(ji,jj,ilevel+1), zthick(ji,jj) )  &
346                                                                   * tmask(ji,jj,ilevel+1)
347         END DO
348      END DO
349      ! from temperature to heat contain
350      zcoef = rau0 * rcp
351      htc3(:,:) = zcoef * htc3(:,:)
352      CALL iom_put( "hc300", htc3 )      ! first 300m heat content
353      !
354      IF( nn_timing == 1 )   CALL timing_stop('dia_hth')
355      !
356      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
357   END SUBROUTINE dia_hth
358
359#else
360   !!----------------------------------------------------------------------
361   !!   Default option :                                       Empty module
362   !!----------------------------------------------------------------------
363   LOGICAL , PUBLIC, PARAMETER ::   lk_diahth = .FALSE.  !: thermocline-20d depths flag
364CONTAINS
365   SUBROUTINE dia_hth( kt )         ! Empty routine
366   USE yomhook, ONLY: lhook, dr_hook
367   USE parkind1, ONLY: jprb, jpim
368
369   IMPLICIT NONE
370    INTEGER, INTENT( in ) ::   kt      ! ocean time-step index
371    INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
372    INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
373    REAL(KIND=jprb)               :: zhook_handle
374
375    CHARACTER(LEN=*), PARAMETER :: RoutineName='DIA_HTH'
376
377    IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
378
379    WRITE(*,*) 'dia_hth: You should not have seen this print! error?', kt
380    IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
381   END SUBROUTINE dia_hth
382#endif
383
384   !!======================================================================
385END MODULE diahth
Note: See TracBrowser for help on using the repository browser.