icesbc.F90 25 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436
  1. MODULE icesbc
  2. !!======================================================================
  3. !! *** MODULE icesbc ***
  4. !! Sea-Ice : air-ice sbc fields
  5. !!=====================================================================
  6. !! History : 4.0 ! 2017-08 (C. Rousset) Original code
  7. !! 4.0 ! 2018 (many people) SI3 [aka Sea Ice cube]
  8. !!----------------------------------------------------------------------
  9. #if defined key_si3
  10. !!----------------------------------------------------------------------
  11. !! 'key_si3' : SI3 sea-ice model
  12. !!----------------------------------------------------------------------
  13. USE oce ! ocean dynamics and tracers
  14. USE dom_oce ! ocean space and time domain
  15. USE ice ! sea-ice: variables
  16. USE sbc_oce ! Surface boundary condition: ocean fields
  17. USE sbc_ice ! Surface boundary condition: ice fields
  18. USE usrdef_sbc ! Surface boundary condition: user defined
  19. USE sbcblk ! Surface boundary condition: bulk
  20. USE sbccpl ! Surface boundary condition: coupled interface
  21. USE icealb ! sea-ice: albedo
  22. !
  23. USE in_out_manager ! I/O manager
  24. USE iom ! I/O manager library
  25. USE lib_mpp ! MPP library
  26. USE lib_fortran ! fortran utilities (glob_sum + no signed zero)
  27. USE lbclnk ! lateral boundary conditions (or mpp links)
  28. USE timing ! Timing
  29. USE fldread !!GS: needed by agrif
  30. IMPLICIT NONE
  31. PRIVATE
  32. PUBLIC ice_sbc_tau ! called by icestp.F90
  33. PUBLIC ice_sbc_flx ! called by icestp.F90
  34. PUBLIC ice_sbc_init ! called by icestp.F90
  35. !! * Substitutions
  36. # include "do_loop_substitute.h90"
  37. !!----------------------------------------------------------------------
  38. !! NEMO/ICE 4.0 , NEMO Consortium (2018)
  39. !! $Id: icesbc.F90 15388 2021-10-17 11:33:47Z clem $
  40. !! Software governed by the CeCILL license (see ./LICENSE)
  41. !!----------------------------------------------------------------------
  42. CONTAINS
  43. SUBROUTINE ice_sbc_tau( kt, ksbc, utau_ice, vtau_ice )
  44. !!-------------------------------------------------------------------
  45. !! *** ROUTINE ice_sbc_tau ***
  46. !!
  47. !! ** Purpose : provide surface boundary condition for sea ice (momentum)
  48. !!
  49. !! ** Action : It provides the following fields:
  50. !! utau_ice, vtau_ice : surface ice stress (U- & V-points) [N/m2]
  51. !!-------------------------------------------------------------------
  52. INTEGER , INTENT(in ) :: kt ! ocean time step
  53. INTEGER , INTENT(in ) :: ksbc ! type of sbc flux
  54. REAL(wp), DIMENSION(jpi,jpj), INTENT( out) :: utau_ice, vtau_ice ! air-ice stress [N/m2]
  55. !!
  56. INTEGER :: ji, jj ! dummy loop index
  57. REAL(wp), DIMENSION(jpi,jpj) :: zutau_ice, zvtau_ice
  58. !!-------------------------------------------------------------------
  59. !
  60. IF( ln_timing ) CALL timing_start('icesbc')
  61. !
  62. IF( kt == nit000 .AND. lwp ) THEN
  63. WRITE(numout,*)
  64. WRITE(numout,*)'ice_sbc_tau: Surface boundary condition for sea ice (momentum)'
  65. WRITE(numout,*)'~~~~~~~~~~~~~~~'
  66. ENDIF
  67. !
  68. SELECT CASE( ksbc )
  69. CASE( jp_usr ) ; CALL usrdef_sbc_ice_tau( kt ) ! user defined formulation
  70. CASE( jp_blk )
  71. CALL blk_ice_1( sf(jp_wndi)%fnow(:,:,1), sf(jp_wndj)%fnow(:,:,1), &
  72. & theta_air_zt(:,:), q_air_zt(:,:), & ! #LB: known from "sbc_oce" module...
  73. & sf(jp_slp )%fnow(:,:,1), u_ice, v_ice, tm_su , & ! inputs
  74. & putaui = utau_ice, pvtaui = vtau_ice ) ! outputs
  75. ! CASE( jp_abl ) utau_ice & vtau_ice are computed in ablmod
  76. CASE( jp_purecpl ) ; CALL sbc_cpl_ice_tau( utau_ice , vtau_ice ) ! Coupled formulation
  77. END SELECT
  78. !
  79. IF( ln_mixcpl) THEN ! Case of a mixed Bulk/Coupled formulation
  80. CALL sbc_cpl_ice_tau( zutau_ice , zvtau_ice )
  81. DO_2D( 0, 0, 0, 0 )
  82. utau_ice(ji,jj) = utau_ice(ji,jj) * xcplmask(ji,jj,0) + zutau_ice(ji,jj) * ( 1. - xcplmask(ji,jj,0) )
  83. vtau_ice(ji,jj) = vtau_ice(ji,jj) * xcplmask(ji,jj,0) + zvtau_ice(ji,jj) * ( 1. - xcplmask(ji,jj,0) )
  84. END_2D
  85. CALL lbc_lnk( 'icesbc', utau_ice, 'U', -1.0_wp, vtau_ice, 'V', -1.0_wp )
  86. ENDIF
  87. !
  88. IF( ln_timing ) CALL timing_stop('icesbc')
  89. !
  90. END SUBROUTINE ice_sbc_tau
  91. SUBROUTINE ice_sbc_flx( kt, ksbc )
  92. !!-------------------------------------------------------------------
  93. !! *** ROUTINE ice_sbc_flx ***
  94. !!
  95. !! ** Purpose : provide surface boundary condition for sea ice (flux)
  96. !!
  97. !! ** Action : It provides the following fields used in sea ice model:
  98. !! emp_oce , emp_ice = E-P over ocean and sea ice [Kg/m2/s]
  99. !! sprecip = solid precipitation [Kg/m2/s]
  100. !! evap_ice = sublimation [Kg/m2/s]
  101. !! qsr_tot , qns_tot = solar & non solar heat flux (total) [W/m2]
  102. !! qsr_ice , qns_ice = solar & non solar heat flux over ice [W/m2]
  103. !! dqns_ice = non solar heat sensistivity [W/m2]
  104. !! qemp_oce, qemp_ice, qprec_ice, qevap_ice = sensible heat (associated with evap & precip) [W/m2]
  105. !! + these fields
  106. !! qsb_ice_bot = sensible heat at the ice bottom [W/m2]
  107. !! fhld, qlead = heat budget in the leads [W/m2]
  108. !! + some fields that are not used outside this module:
  109. !! qla_ice = latent heat flux over ice [W/m2]
  110. !! dqla_ice = latent heat sensistivity [W/m2]
  111. !! tprecip = total precipitation [Kg/m2/s]
  112. !! alb_ice = albedo above sea ice
  113. !!-------------------------------------------------------------------
  114. INTEGER, INTENT(in) :: kt ! ocean time step
  115. INTEGER, INTENT(in) :: ksbc ! flux formulation (user defined, bulk or Pure Coupled)
  116. !!--------------------------------------------------------------------
  117. !
  118. IF( ln_timing ) CALL timing_start('icesbc')
  119. IF( kt == nit000 .AND. lwp ) THEN
  120. WRITE(numout,*)
  121. WRITE(numout,*)'ice_sbc_flx: Surface boundary condition for sea ice (flux)'
  122. WRITE(numout,*)'~~~~~~~~~~~~~~~'
  123. ENDIF
  124. ! !== ice albedo ==!
  125. CALL ice_alb( t_su, h_i, h_s, ln_pnd_alb, a_ip_eff, h_ip, cloud_fra, alb_ice )
  126. !
  127. SELECT CASE( ksbc ) !== fluxes over sea ice ==!
  128. !
  129. CASE( jp_usr ) !--- user defined formulation
  130. CALL usrdef_sbc_ice_flx( kt, h_s, h_i )
  131. CASE( jp_blk, jp_abl ) !--- bulk formulation & ABL formulation
  132. CALL blk_ice_2 ( t_su, h_s, h_i, alb_ice, &
  133. & theta_air_zt(:,:), q_air_zt(:,:), & ! #LB: known from "sbc_oce" module...
  134. & sf(jp_slp)%fnow(:,:,1), sf(jp_qlw)%fnow(:,:,1), &
  135. & sf(jp_prec)%fnow(:,:,1), sf(jp_snow)%fnow(:,:,1) )
  136. IF( ln_mixcpl ) CALL sbc_cpl_ice_flx( kt, picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su, phs=h_s, phi=h_i )
  137. IF( nn_flxdist /= -1 ) CALL ice_flx_dist ( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_flxdist )
  138. ! ! compute conduction flux and surface temperature (as in Jules surface module)
  139. IF( ln_cndflx .AND. .NOT.ln_cndemulate ) &
  140. & CALL blk_ice_qcn ( ln_virtual_itd, t_su, t_bo, h_s, h_i )
  141. CASE ( jp_purecpl ) !--- coupled formulation
  142. CALL sbc_cpl_ice_flx( kt, picefr=at_i_b, palbi=alb_ice, psst=sst_m, pist=t_su, phs=h_s, phi=h_i )
  143. IF( nn_flxdist /= -1 ) CALL ice_flx_dist ( t_su, alb_ice, qns_ice, qsr_ice, dqns_ice, evap_ice, devap_ice, nn_flxdist )
  144. END SELECT
  145. ! !== some fluxes at the ice-ocean interface and in the leads
  146. CALL ice_flx_other
  147. !
  148. IF( ln_timing ) CALL timing_stop('icesbc')
  149. !
  150. END SUBROUTINE ice_sbc_flx
  151. SUBROUTINE ice_flx_dist( ptn_ice, palb_ice, pqns_ice, pqsr_ice, pdqn_ice, pevap_ice, pdevap_ice, k_flxdist )
  152. !!-------------------------------------------------------------------
  153. !! *** ROUTINE ice_flx_dist ***
  154. !!
  155. !! ** Purpose : update the ice surface boundary condition by averaging
  156. !! and/or redistributing fluxes on ice categories
  157. !!
  158. !! ** Method : average then redistribute
  159. !!
  160. !! ** Action : depends on k_flxdist
  161. !! = -1 Do nothing (needs N(cat) fluxes)
  162. !! = 0 Average N(cat) fluxes then apply the average over the N(cat) ice
  163. !! = 1 Average N(cat) fluxes then redistribute over the N(cat) ice
  164. !! using T-ice and albedo sensitivity
  165. !! = 2 Redistribute a single flux over categories
  166. !!-------------------------------------------------------------------
  167. INTEGER , INTENT(in ) :: k_flxdist ! redistributor
  168. REAL(wp), DIMENSION(:,:,:), INTENT(in ) :: ptn_ice ! ice surface temperature
  169. REAL(wp), DIMENSION(:,:,:), INTENT(in ) :: palb_ice ! ice albedo
  170. REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pqns_ice ! non solar flux
  171. REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pqsr_ice ! net solar flux
  172. REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pdqn_ice ! non solar flux sensitivity
  173. REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pevap_ice ! sublimation
  174. REAL(wp), DIMENSION(:,:,:), INTENT(inout) :: pdevap_ice ! sublimation sensitivity
  175. !
  176. INTEGER :: jl ! dummy loop index
  177. !
  178. REAL(wp), DIMENSION(jpi,jpj) :: z1_at_i ! inverse of concentration
  179. !
  180. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_qsr_m ! Mean solar heat flux over all categories
  181. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_qns_m ! Mean non solar heat flux over all categories
  182. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_evap_m ! Mean sublimation over all categories
  183. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_dqn_m ! Mean d(qns)/dT over all categories
  184. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_devap_m ! Mean d(evap)/dT over all categories
  185. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: zalb_m ! Mean albedo over all categories
  186. REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: ztem_m ! Mean temperature over all categories
  187. !!----------------------------------------------------------------------
  188. !
  189. WHERE ( at_i (:,:) > 0._wp ) ; z1_at_i(:,:) = 1._wp / at_i (:,:)
  190. ELSEWHERE ; z1_at_i(:,:) = 0._wp
  191. END WHERE
  192. SELECT CASE( k_flxdist ) !== averaged on all ice categories ==!
  193. !
  194. CASE( 0 , 1 )
  195. !
  196. ALLOCATE( z_qns_m(jpi,jpj), z_qsr_m(jpi,jpj), z_dqn_m(jpi,jpj), z_evap_m(jpi,jpj), z_devap_m(jpi,jpj) )
  197. !
  198. z_qns_m (:,:) = SUM( a_i(:,:,:) * pqns_ice (:,:,:) , dim=3 ) * z1_at_i(:,:)
  199. z_qsr_m (:,:) = SUM( a_i(:,:,:) * pqsr_ice (:,:,:) , dim=3 ) * z1_at_i(:,:)
  200. z_dqn_m (:,:) = SUM( a_i(:,:,:) * pdqn_ice (:,:,:) , dim=3 ) * z1_at_i(:,:)
  201. z_evap_m (:,:) = SUM( a_i(:,:,:) * pevap_ice (:,:,:) , dim=3 ) * z1_at_i(:,:)
  202. z_devap_m(:,:) = SUM( a_i(:,:,:) * pdevap_ice(:,:,:) , dim=3 ) * z1_at_i(:,:)
  203. DO jl = 1, jpl
  204. pqns_ice (:,:,jl) = z_qns_m (:,:)
  205. pqsr_ice (:,:,jl) = z_qsr_m (:,:)
  206. pdqn_ice (:,:,jl) = z_dqn_m (:,:)
  207. pevap_ice (:,:,jl) = z_evap_m(:,:)
  208. pdevap_ice(:,:,jl) = z_devap_m(:,:)
  209. END DO
  210. !
  211. DEALLOCATE( z_qns_m, z_qsr_m, z_dqn_m, z_evap_m, z_devap_m )
  212. !
  213. END SELECT
  214. !
  215. SELECT CASE( k_flxdist ) !== redistribution on all ice categories ==!
  216. !
  217. CASE( 1 , 2 )
  218. !
  219. ALLOCATE( zalb_m(jpi,jpj), ztem_m(jpi,jpj) )
  220. !
  221. zalb_m(:,:) = SUM( a_i(:,:,:) * palb_ice(:,:,:) , dim=3 ) * z1_at_i(:,:)
  222. ztem_m(:,:) = SUM( a_i(:,:,:) * ptn_ice (:,:,:) , dim=3 ) * z1_at_i(:,:)
  223. DO jl = 1, jpl
  224. pqns_ice (:,:,jl) = pqns_ice (:,:,jl) + pdqn_ice (:,:,jl) * ( ptn_ice(:,:,jl) - ztem_m(:,:) )
  225. pevap_ice(:,:,jl) = pevap_ice(:,:,jl) + pdevap_ice(:,:,jl) * ( ptn_ice(:,:,jl) - ztem_m(:,:) )
  226. pqsr_ice (:,:,jl) = pqsr_ice (:,:,jl) * ( 1._wp - palb_ice(:,:,jl) ) / ( 1._wp - zalb_m(:,:) )
  227. END DO
  228. !
  229. DEALLOCATE( zalb_m, ztem_m )
  230. !
  231. END SELECT
  232. !
  233. END SUBROUTINE ice_flx_dist
  234. SUBROUTINE ice_flx_other
  235. !!-----------------------------------------------------------------------
  236. !! *** ROUTINE ice_flx_other ***
  237. !!
  238. !! ** Purpose : prepare necessary fields for thermo calculations
  239. !!
  240. !! ** Inputs : u_ice, v_ice, ssu_m, ssv_m, utau, vtau
  241. !! frq_m, qsr_oce, qns_oce, qemp_oce, e3t_m, sst_m
  242. !! ** Outputs : qsb_ice_bot, fhld, qlead
  243. !!-----------------------------------------------------------------------
  244. INTEGER :: ji, jj ! dummy loop indices
  245. REAL(wp) :: zfric_u, zqld, zqfr, zqfr_neg, zqfr_pos, zu_io, zv_io, zu_iom1, zv_iom1
  246. REAL(wp), PARAMETER :: zfric_umin = 0._wp ! lower bound for the friction velocity (cice value=5.e-04)
  247. REAL(wp), PARAMETER :: zch = 0.0057_wp ! heat transfer coefficient
  248. REAL(wp), DIMENSION(jpi,jpj) :: zfric, zvel ! ice-ocean velocity (m/s) and frictional velocity (m2/s2)
  249. !!-----------------------------------------------------------------------
  250. !
  251. ! computation of friction velocity at T points
  252. IF( ln_icedyn ) THEN
  253. DO_2D( 0, 0, 0, 0 )
  254. zu_io = u_ice(ji ,jj ) - ssu_m(ji ,jj )
  255. zu_iom1 = u_ice(ji-1,jj ) - ssu_m(ji-1,jj )
  256. zv_io = v_ice(ji ,jj ) - ssv_m(ji ,jj )
  257. zv_iom1 = v_ice(ji ,jj-1) - ssv_m(ji ,jj-1)
  258. !
  259. zfric(ji,jj) = rn_cio * ( 0.5_wp * ( zu_io*zu_io + zu_iom1*zu_iom1 + zv_io*zv_io + zv_iom1*zv_iom1 ) ) * tmask(ji,jj,1)
  260. zvel (ji,jj) = 0.5_wp * SQRT( ( u_ice(ji-1,jj ) + u_ice(ji,jj) ) * ( u_ice(ji-1,jj ) + u_ice(ji,jj) ) + &
  261. & ( v_ice(ji ,jj-1) + v_ice(ji,jj) ) * ( v_ice(ji ,jj-1) + v_ice(ji,jj) ) )
  262. END_2D
  263. ELSE ! if no ice dynamics => transfer directly the atmospheric stress to the ocean
  264. DO_2D( 0, 0, 0, 0 )
  265. zfric(ji,jj) = r1_rho0 * SQRT( 0.5_wp * &
  266. & ( utau(ji,jj) * utau(ji,jj) + utau(ji-1,jj) * utau(ji-1,jj) &
  267. & + vtau(ji,jj) * vtau(ji,jj) + vtau(ji,jj-1) * vtau(ji,jj-1) ) ) * tmask(ji,jj,1)
  268. zvel(ji,jj) = 0._wp
  269. END_2D
  270. ENDIF
  271. CALL lbc_lnk( 'icesbc', zfric, 'T', 1.0_wp, zvel, 'T', 1.0_wp )
  272. !
  273. !--------------------------------------------------------------------!
  274. ! Partial computation of forcing for the thermodynamic sea ice model
  275. !--------------------------------------------------------------------!
  276. DO_2D( nn_hls, nn_hls, nn_hls, nn_hls ) ! needed for qlead
  277. rswitch = tmask(ji,jj,1) * MAX( 0._wp , SIGN( 1._wp , at_i(ji,jj) - epsi10 ) ) ! 0 if no ice
  278. !
  279. ! --- Energy received in the lead from atm-oce exchanges, zqld is defined everywhere (J.m-2) --- !
  280. zqld = tmask(ji,jj,1) * rDt_ice * &
  281. & ( ( 1._wp - at_i_b(ji,jj) ) * qsr_oce(ji,jj) * frq_m(ji,jj) + &
  282. & ( 1._wp - at_i_b(ji,jj) ) * qns_oce(ji,jj) + qemp_oce(ji,jj) )
  283. ! --- Energy needed to bring ocean surface layer until its freezing, zqfr is defined everywhere (J.m-2) --- !
  284. ! (mostly<0 but >0 if supercooling)
  285. zqfr = rho0 * rcp * e3t_m(ji,jj) * ( t_bo(ji,jj) - ( sst_m(ji,jj) + rt0 ) ) * tmask(ji,jj,1) ! both < 0 (t_bo < sst) and > 0 (t_bo > sst)
  286. zqfr_neg = MIN( zqfr , 0._wp ) ! only < 0
  287. zqfr_pos = MAX( zqfr , 0._wp ) ! only > 0
  288. ! --- Sensible ocean-to-ice heat flux (W/m2) --- !
  289. ! (mostly>0 but <0 if supercooling)
  290. zfric_u = MAX( SQRT( zfric(ji,jj) ), zfric_umin )
  291. qsb_ice_bot(ji,jj) = rswitch * rho0 * rcp * zch * zfric_u * ( ( sst_m(ji,jj) + rt0 ) - t_bo(ji,jj) )
  292. ! upper bound for qsb_ice_bot: the heat retrieved from the ocean must be smaller than the heat necessary to reach
  293. ! the freezing point, so that we do not have SST < T_freeze
  294. ! This implies: qsb_ice_bot(ji,jj) * at_i(ji,jj) * rtdice <= - zqfr_neg
  295. ! The following formulation is ok for both normal conditions and supercooling
  296. qsb_ice_bot(ji,jj) = rswitch * MIN( qsb_ice_bot(ji,jj), - zqfr_neg * r1_Dt_ice / MAX( at_i(ji,jj), epsi10 ) )
  297. ! If conditions are always supercooled (such as at the mouth of ice-shelves), then ice grows continuously
  298. ! ==> stop ice formation by artificially setting up the turbulent fluxes to 0 when volume > 20m (arbitrary)
  299. IF( ( t_bo(ji,jj) - ( sst_m(ji,jj) + rt0 ) ) > 0._wp .AND. vt_i(ji,jj) >= 20._wp ) THEN
  300. zqfr = 0._wp
  301. zqfr_pos = 0._wp
  302. qsb_ice_bot(ji,jj) = 0._wp
  303. ENDIF
  304. !
  305. ! --- Energy Budget of the leads (qlead, J.m-2) --- !
  306. ! qlead is the energy received from the atm. in the leads.
  307. ! If warming (zqld >= 0), then the energy in the leads is used to melt ice (bottom melting) => fhld (W/m2)
  308. ! If cooling (zqld < 0), then the energy in the leads is used to grow ice in open water => qlead (J.m-2)
  309. IF( ( zqld - zqfr ) < 0._wp .OR. at_i(ji,jj) < epsi10 ) THEN
  310. fhld (ji,jj) = 0._wp
  311. ! upper bound for qlead: qlead should be equal to zqld
  312. ! but before using this heat for ice formation, we suppose that the ocean cools down till the freezing point.
  313. ! The energy for this cooling down is zqfr and freezing point is reached if zqfr = zqld
  314. ! so the max heat that can be pulled out of the ocean is zqld - zqfr
  315. ! The following formulation is ok for both normal conditions and supercooling
  316. qlead(ji,jj) = MIN( 0._wp , zqld - zqfr )
  317. ELSE
  318. ! upper bound for fhld: fhld should be equal to zqld
  319. ! but we have to make sure that this heat will not make the sst drop below the freezing point
  320. ! so the max heat that can be pulled out of the ocean is zqld - zqfr_pos
  321. ! The following formulation is ok for both normal conditions and supercooling
  322. fhld (ji,jj) = rswitch * MAX( 0._wp, ( zqld - zqfr_pos ) * r1_Dt_ice / MAX( at_i(ji,jj), epsi10 ) ) ! divided by at_i since this is (re)multiplied by a_i in icethd_dh.F90
  323. qlead(ji,jj) = 0._wp
  324. ENDIF
  325. !
  326. ! If ice is landfast and ice concentration reaches its max
  327. ! => stop ice formation in open water
  328. ! ELIC change
  329. ! - this change prevents more efficiently the formation of ice in open water for landfast ice
  330. ! - it helps avoiding large ice accumulations in small embayments along the Antarctic coast
  331. ! - it was recommended by Clement Rousset in an email to Noe Pirlet
  332. !
  333. IF( zvel(ji,jj) <= 5.e-04_wp .AND. at_i(ji,jj) >= rn_amax_2d(ji,jj)-0.01_wp ) qlead(ji,jj) = 0._wp
  334. ! end ELIC change
  335. !
  336. ! If the grid cell is almost fully covered by ice (no leads)
  337. ! => stop ice formation in open water
  338. IF( at_i(ji,jj) >= (1._wp - epsi10) ) qlead(ji,jj) = 0._wp
  339. !
  340. ! If ln_leadhfx is false
  341. ! => do not use energy of the leads to melt sea-ice
  342. IF( .NOT.ln_leadhfx ) fhld(ji,jj) = 0._wp
  343. !
  344. END_2D
  345. ! In case we bypass open-water ice formation
  346. IF( .NOT. ln_icedO ) qlead(:,:) = 0._wp
  347. ! In case we bypass growing/melting from top and bottom
  348. IF( .NOT. ln_icedH ) THEN
  349. qsb_ice_bot(:,:) = 0._wp
  350. fhld (:,:) = 0._wp
  351. ENDIF
  352. END SUBROUTINE ice_flx_other
  353. SUBROUTINE ice_sbc_init
  354. !!-------------------------------------------------------------------
  355. !! *** ROUTINE ice_sbc_init ***
  356. !!
  357. !! ** Purpose : Physical constants and parameters linked to the ice dynamics
  358. !!
  359. !! ** Method : Read the namsbc namelist and check the ice-dynamic
  360. !! parameter values called at the first timestep (nit000)
  361. !!
  362. !! ** input : Namelist namsbc
  363. !!-------------------------------------------------------------------
  364. INTEGER :: ios, ioptio ! Local integer
  365. !!
  366. NAMELIST/namsbc/ rn_cio, nn_snwfra, rn_snwblow, nn_flxdist, ln_cndflx, ln_cndemulate, nn_qtrice
  367. !!-------------------------------------------------------------------
  368. !
  369. READ ( numnam_ice_ref, namsbc, IOSTAT = ios, ERR = 901)
  370. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc in reference namelist' )
  371. READ ( numnam_ice_cfg, namsbc, IOSTAT = ios, ERR = 902 )
  372. 902 IF( ios > 0 ) CALL ctl_nam ( ios , 'namsbc in configuration namelist' )
  373. IF(lwm) WRITE( numoni, namsbc )
  374. !
  375. IF(lwp) THEN ! control print
  376. WRITE(numout,*)
  377. WRITE(numout,*) 'ice_sbc_init: ice parameters for ice dynamics '
  378. WRITE(numout,*) '~~~~~~~~~~~~~~~~'
  379. WRITE(numout,*) ' Namelist namsbc:'
  380. WRITE(numout,*) ' drag coefficient for oceanic stress rn_cio = ', rn_cio
  381. WRITE(numout,*) ' fraction of ice covered by snow (options 0,1,2) nn_snwfra = ', nn_snwfra
  382. WRITE(numout,*) ' coefficient for ice-lead partition of snowfall rn_snwblow = ', rn_snwblow
  383. WRITE(numout,*) ' Multicategory heat flux formulation nn_flxdist = ', nn_flxdist
  384. WRITE(numout,*) ' Use conduction flux as surface condition ln_cndflx = ', ln_cndflx
  385. WRITE(numout,*) ' emulate conduction flux ln_cndemulate = ', ln_cndemulate
  386. WRITE(numout,*) ' solar flux transmitted thru the surface scattering layer nn_qtrice = ', nn_qtrice
  387. WRITE(numout,*) ' = 0 Grenfell and Maykut 1977'
  388. WRITE(numout,*) ' = 1 Lebrun 2019'
  389. ENDIF
  390. !
  391. IF(lwp) WRITE(numout,*)
  392. SELECT CASE( nn_flxdist ) ! SI3 Multi-category heat flux formulation
  393. CASE( -1 )
  394. IF(lwp) WRITE(numout,*) ' SI3: use per-category fluxes (nn_flxdist = -1) '
  395. CASE( 0 )
  396. IF(lwp) WRITE(numout,*) ' SI3: use average per-category fluxes (nn_flxdist = 0) '
  397. CASE( 1 )
  398. IF(lwp) WRITE(numout,*) ' SI3: use average then redistribute per-category fluxes (nn_flxdist = 1) '
  399. IF( ln_cpl ) CALL ctl_stop( 'ice_thd_init: the chosen nn_flxdist for SI3 in coupled mode must be /=1' )
  400. CASE( 2 )
  401. IF(lwp) WRITE(numout,*) ' SI3: Redistribute a single flux over categories (nn_flxdist = 2) '
  402. IF( .NOT. ln_cpl ) CALL ctl_stop( 'ice_thd_init: the chosen nn_flxdist for SI3 in forced mode must be /=2' )
  403. CASE DEFAULT
  404. CALL ctl_stop( 'ice_thd_init: SI3 option, nn_flxdist, should be between -1 and 2' )
  405. END SELECT
  406. !
  407. END SUBROUTINE ice_sbc_init
  408. #else
  409. !!----------------------------------------------------------------------
  410. !! Default option : Empty module NO SI3 sea-ice model
  411. !!----------------------------------------------------------------------
  412. #endif
  413. !!======================================================================
  414. END MODULE icesbc