diahth.F90 17 KB

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