sbcice_lim_2.F90 14 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288
  1. MODULE sbcice_lim_2
  2. !!======================================================================
  3. !! *** MODULE sbcice_lim_2 ***
  4. !! Surface module : update surface ocean boundary condition over ice covered area using LIM sea-ice model
  5. !! Sea-Ice model : LIM-2 Sea ice model time-stepping
  6. !!======================================================================
  7. !! History : 1.0 ! 06-2006 (G. Madec) from icestp_2.F90
  8. !! 3.0 ! 08-2008 (S. Masson, E. .... ) coupled interface
  9. !! 3.3 ! 05-2009 (G.Garric) addition of the lim2_evp case
  10. !!----------------------------------------------------------------------
  11. #if defined key_lim2
  12. !!----------------------------------------------------------------------
  13. !! 'key_lim2' : LIM-2 sea-ice model
  14. !!----------------------------------------------------------------------
  15. !! sbc_ice_lim_2 : sea-ice model time-stepping and update ocean sbc over ice-covered area
  16. !!----------------------------------------------------------------------
  17. USE oce ! ocean dynamics and tracers
  18. USE dom_oce ! ocean space and time domain
  19. USE ice_2
  20. USE par_ice_2
  21. USE iceini_2
  22. USE dom_ice_2
  23. USE sbc_oce ! Surface boundary condition: ocean fields
  24. USE sbc_ice ! Surface boundary condition: ice fields
  25. USE sbcblk_core ! Surface boundary condition: CORE bulk
  26. USE sbcblk_clio ! Surface boundary condition: CLIO bulk
  27. USE sbccpl ! Surface boundary condition: coupled interface
  28. USE albedo
  29. USE phycst ! Define parameters for the routines
  30. USE eosbn2 ! equation of state
  31. USE limdyn_2
  32. USE limtrp_2
  33. USE limdmp_2
  34. USE limthd_2
  35. USE limsbc_2 ! sea surface boundary condition
  36. USE limdia_2
  37. USE limwri_2
  38. USE limrst_2
  39. USE c1d ! 1D vertical configuration
  40. USE lbclnk ! lateral boundary condition - MPP link
  41. USE lib_mpp ! MPP library
  42. USE wrk_nemo ! work arrays
  43. USE iom ! I/O manager library
  44. USE in_out_manager ! I/O manager
  45. USE prtctl ! Print control
  46. # if defined key_agrif
  47. USE agrif_ice
  48. USE agrif_lim2_update
  49. # endif
  50. #if defined key_bdy
  51. USE bdyice_lim ! unstructured open boundary data (bdy_ice_lim routine)
  52. #endif
  53. IMPLICIT NONE
  54. PRIVATE
  55. PUBLIC sbc_ice_lim_2 ! routine called by sbcmod.F90
  56. !! * Substitutions
  57. # include "domzgr_substitute.h90"
  58. # include "vectopt_loop_substitute.h90"
  59. !!----------------------------------------------------------------------
  60. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  61. !! $Id: sbcice_lim_2.F90 5540 2015-07-02 15:11:23Z jchanut $
  62. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  63. !!----------------------------------------------------------------------
  64. CONTAINS
  65. SUBROUTINE sbc_ice_lim_2( kt, ksbc )
  66. !!---------------------------------------------------------------------
  67. !! *** ROUTINE sbc_ice_lim_2 ***
  68. !!
  69. !! ** Purpose : update the ocean surface boundary condition via the
  70. !! Louvain la Neuve Sea Ice Model time stepping
  71. !!
  72. !! ** Method : ice model time stepping
  73. !! - call the ice dynamics routine
  74. !! - call the ice advection/diffusion routine
  75. !! - call the ice thermodynamics routine
  76. !! - call the routine that computes mass and
  77. !! heat fluxes at the ice/ocean interface
  78. !! - save the outputs
  79. !! - save the outputs for restart when necessary
  80. !!
  81. !! ** Action : - time evolution of the LIM sea-ice model
  82. !! - update all sbc variables below sea-ice:
  83. !! utau, vtau, taum, wndm, qns , qsr, emp , sfx
  84. !!---------------------------------------------------------------------
  85. INTEGER, INTENT(in) :: kt ! ocean time step
  86. INTEGER, INTENT(in) :: ksbc ! type of sbc ( =3 CLIO bulk ; =4 CORE bulk ; =5 coupled )
  87. !!
  88. INTEGER :: ji, jj ! dummy loop indices
  89. REAL(wp), DIMENSION(:,:,:), POINTER :: zalb_os ! ice albedo under overcast sky
  90. REAL(wp), DIMENSION(:,:,:), POINTER :: zalb_cs ! ice albedo under clear sky
  91. REAL(wp), DIMENSION(:,:,:), POINTER :: zalb_ice ! mean ice albedo
  92. REAL(wp), DIMENSION(:,:,:), POINTER :: zsist ! ice surface temperature (K)
  93. REAL(wp), DIMENSION(:,: ), POINTER :: zutau_ice, zvtau_ice
  94. !!----------------------------------------------------------------------
  95. IF( kt == nit000 ) THEN
  96. IF(lwp) WRITE(numout,*)
  97. IF(lwp) WRITE(numout,*) 'sbc_ice_lim_2 : update ocean surface boudary condition'
  98. IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~ via Louvain la Neuve Ice Model (LIM) time stepping'
  99. !
  100. CALL ice_init_2
  101. !
  102. # if defined key_agrif
  103. IF( .NOT. Agrif_Root() ) CALL Agrif_InitValues_cont_lim2 ! AGRIF: set the meshes
  104. # endif
  105. ENDIF
  106. ! !----------------------!
  107. IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN ! Ice time-step only !
  108. ! !----------------------!
  109. # if defined key_agrif
  110. IF( .NOT. Agrif_Root() ) lim_nbstep = MOD(lim_nbstep,Agrif_rhot()&
  111. &*Agrif_PArent(nn_fsbc)/REAL(nn_fsbc)) + 1
  112. # endif
  113. CALL wrk_alloc( jpi,jpj , zutau_ice, zvtau_ice)
  114. CALL wrk_alloc( jpi,jpj,1, zalb_os, zalb_cs, zalb_ice, zsist )
  115. ! Bulk Formulea !
  116. !----------------!
  117. ! ... mean surface ocean current at ice dynamics point
  118. SELECT CASE( cp_ice_msh )
  119. CASE( 'I' ) !== B-grid ice dynamics : I-point (i.e. F-point with sea-ice indexation)
  120. DO jj = 2, jpj
  121. DO ji = 2, jpi ! NO vector opt. possible
  122. u_oce(ji,jj) = 0.5_wp * ( ssu_m(ji-1,jj ) * umask(ji-1,jj ,1) &
  123. & + ssu_m(ji-1,jj-1) * umask(ji-1,jj-1,1) ) * tmu(ji,jj)
  124. v_oce(ji,jj) = 0.5_wp * ( ssv_m(ji ,jj-1) * vmask(ji ,jj-1,1) &
  125. & + ssv_m(ji-1,jj-1) * vmask(ji-1,jj-1,1) ) * tmu(ji,jj)
  126. END DO
  127. END DO
  128. CALL lbc_lnk( u_oce, 'I', -1. ) ! I-point (i.e. F-point with ice indices)
  129. CALL lbc_lnk( v_oce, 'I', -1. ) ! I-point (i.e. F-point with ice indices)
  130. !
  131. CASE( 'C' ) !== C-grid ice dynamics : U & V-points (same as ocean)
  132. u_oce(:,:) = ssu_m(:,:) * umask(:,:,1) ! mean surface ocean current at ice velocity point
  133. v_oce(:,:) = ssv_m(:,:) * vmask(:,:,1)
  134. !
  135. END SELECT
  136. ! ... masked sea surface freezing temperature [Kelvin] (set to rt0 over land)
  137. CALL eos_fzp( sss_m(:,:), tfu(:,:) )
  138. tfu(:,:) = tfu(:,:) + rt0
  139. zsist (:,:,1) = sist (:,:) + rt0 * ( 1. - tmask(:,:,1) )
  140. ! Ice albedo
  141. CALL albedo_ice( zsist, reshape( hicif, (/jpi,jpj,1/) ), &
  142. reshape( hsnif, (/jpi,jpj,1/) ), &
  143. zalb_cs, zalb_os )
  144. SELECT CASE( ksbc )
  145. CASE( jp_core , jp_purecpl ) ! CORE and COUPLED bulk formulations
  146. ! albedo depends on cloud fraction because of non-linear spectral effects
  147. zalb_ice(:,:,:) = ( 1. - cldf_ice ) * zalb_cs(:,:,:) + cldf_ice * zalb_os(:,:,:)
  148. ! In CLIO the cloud fraction is read in the climatology and the all-sky albedo
  149. ! (zalb_ice) is computed within the bulk routine
  150. END SELECT
  151. ! ... Sea-ice surface boundary conditions output from bulk formulae :
  152. ! - utau_ice ! surface ice stress i-component (I-point) [N/m2]
  153. ! - vtau_ice ! surface ice stress j-component (I-point) [N/m2]
  154. ! - qns_ice ! non solar heat flux over ice (T-point) [W/m2]
  155. ! - qsr_ice ! solar heat flux over ice (T-point) [W/m2]
  156. ! - qla_ice ! latent heat flux over ice (T-point) [W/m2]
  157. ! - dqns_ice ! non solar heat sensistivity (T-point) [W/m2]
  158. ! - dqla_ice ! latent heat sensistivity (T-point) [W/m2]
  159. ! - tprecip ! total precipitation (T-point) [Kg/m2/s]
  160. ! - sprecip ! solid precipitation (T-point) [Kg/m2/s]
  161. ! - fr1_i0 ! 1sr fraction of qsr penetration in ice [%]
  162. ! - fr2_i0 ! 2nd fraction of qsr penetration in ice [%]
  163. !
  164. SELECT CASE( ksbc )
  165. CASE( jp_clio ) ! CLIO bulk formulation
  166. ! CALL blk_ice_clio( zsist, zalb_cs , zalb_os , zalb_ice , &
  167. ! & utau_ice , vtau_ice , qns_ice , qsr_ice, &
  168. ! & qla_ice , dqns_ice , dqla_ice , &
  169. ! & tprecip , sprecip , &
  170. ! & fr1_i0 , fr2_i0 , cp_ice_msh , jpl )
  171. CALL blk_ice_clio_tau
  172. CALL blk_ice_clio_flx( zsist, zalb_cs, zalb_os, zalb_ice )
  173. CASE( jp_core ) ! CORE bulk formulation
  174. CALL blk_ice_core_tau
  175. CALL blk_ice_core_flx( zsist, zalb_ice )
  176. CASE( jp_purecpl ) ! Coupled formulation : atmosphere-ice stress only (fluxes provided after ice dynamics)
  177. CALL sbc_cpl_ice_tau( utau_ice , vtau_ice )
  178. END SELECT
  179. IF( ln_mixcpl) THEN
  180. CALL sbc_cpl_ice_tau( zutau_ice , zvtau_ice )
  181. utau_ice(:,:) = utau_ice(:,:) * xcplmask(:,:,0) + zutau_ice(:,:) * ( 1. - xcplmask(:,:,0) )
  182. vtau_ice(:,:) = vtau_ice(:,:) * xcplmask(:,:,0) + zvtau_ice(:,:) * ( 1. - xcplmask(:,:,0) )
  183. ENDIF
  184. CALL iom_put( 'utau_ice', utau_ice ) ! Wind stress over ice along i-axis at I-point
  185. CALL iom_put( 'vtau_ice', vtau_ice ) ! Wind stress over ice along j-axis at I-point
  186. IF(ln_ctl) THEN ! print mean trends (used for debugging)
  187. CALL prt_ctl_info( 'Ice Forcings ' )
  188. CALL prt_ctl( tab2d_1=tprecip ,clinfo1=' sbc_ice_lim: precip : ', tab2d_2=sprecip , clinfo2=' Snow : ' )
  189. CALL prt_ctl( tab2d_1=utau_ice,clinfo1=' sbc_ice_lim: utau_ice: ', tab2d_2=vtau_ice, clinfo2=' vtau_ice: ' )
  190. CALL prt_ctl( tab2d_1=sst_m ,clinfo1=' sbc_ice_lim: sst : ', tab2d_2=sss_m , clinfo2=' sss : ' )
  191. CALL prt_ctl( tab2d_1=u_oce ,clinfo1=' sbc_ice_lim: u_io : ', tab2d_2=v_oce , clinfo2=' v_io : ' )
  192. CALL prt_ctl( tab2d_1=hsnif ,clinfo1=' sbc_ice_lim: hsnif 1: ', tab2d_2=hicif , clinfo2=' hicif : ' )
  193. CALL prt_ctl( tab2d_1=frld ,clinfo1=' sbc_ice_lim: frld 1: ', tab2d_2=sist , clinfo2=' sist : ' )
  194. ENDIF
  195. ! ---------------- !
  196. ! Ice model step !
  197. ! ---------------- !
  198. numit = numit + nn_fsbc ! Ice model time step
  199. CALL lim_rst_opn_2 ( kt ) ! Open Ice restart file
  200. IF( .NOT. lk_c1d ) THEN ! Ice dynamics & transport (except in 1D case)
  201. CALL lim_dyn_2 ( kt ) ! Ice dynamics ( rheology/dynamics )
  202. CALL lim_trp_2 ( kt ) ! Ice transport ( Advection/diffusion )
  203. IF( ln_limdmp ) CALL lim_dmp_2 ( kt ) ! Ice damping
  204. #if defined key_bdy
  205. CALL bdy_ice_lim( kt ) ! bdy ice thermo
  206. #endif
  207. END IF
  208. ! ! Ice surface fluxes in coupled mode
  209. IF( ln_cpl ) THEN ! pure coupled and mixed forced-coupled configurations
  210. a_i(:,:,1)=fr_i
  211. CALL sbc_cpl_ice_flx( frld, &
  212. ! optional arguments, used only in 'mixed oce-ice' case
  213. & palbi=zalb_ice, psst=sst_m, pist=zsist )
  214. sprecip(:,:) = - emp_ice(:,:) ! Ugly patch, WARNING, in coupled mode, sublimation included in snow (parsub = 0.)
  215. ENDIF
  216. CALL lim_thd_2 ( kt ) ! Ice thermodynamics
  217. CALL lim_sbc_flx_2 ( kt ) ! update surface ocean mass, heat & salt fluxes
  218. IF( .NOT. lk_mpp )THEN
  219. IF( MOD( kt+nn_fsbc-1, ninfo ) == 0 .OR. ntmoy == 1 ) &
  220. & CALL lim_dia_2 ( kt ) ! Ice Diagnostics
  221. ENDIF
  222. # if ! defined key_iomput
  223. CALL lim_wri_2 ( kt ) ! Ice outputs
  224. # endif
  225. IF( lrst_ice ) CALL lim_rst_write_2( kt ) ! Ice restart file
  226. !
  227. # if defined key_agrif && defined key_lim2
  228. IF( .NOT. Agrif_Root() ) CALL agrif_update_lim2( kt )
  229. # endif
  230. !
  231. CALL wrk_dealloc( jpi,jpj , zutau_ice, zvtau_ice)
  232. CALL wrk_dealloc( jpi,jpj,1, zalb_os, zalb_cs, zalb_ice, zsist )
  233. !
  234. ENDIF ! End sea-ice time step only
  235. !
  236. ! !--------------------------!
  237. ! ! at all ocean time step !
  238. ! !--------------------------!
  239. !
  240. ! ! Update surface ocean stresses (only in ice-dynamic case)
  241. ! ! otherwise the atm.-ocean stresses are used everywhere
  242. IF( ln_limdyn ) CALL lim_sbc_tau_2( kt, ub(:,:,1), vb(:,:,1) ) ! using before instantaneous surf. currents
  243. !
  244. END SUBROUTINE sbc_ice_lim_2
  245. #else
  246. !!----------------------------------------------------------------------
  247. !! Default option Dummy module NO LIM 2.0 sea-ice model
  248. !!----------------------------------------------------------------------
  249. CONTAINS
  250. SUBROUTINE sbc_ice_lim_2 ( kt, ksbc ) ! Dummy routine
  251. INTEGER, INTENT(in) :: kt, ksbc
  252. WRITE(*,*) 'sbc_ice_lim_2: You should not have seen this print! error?', kt, ksbc
  253. END SUBROUTINE sbc_ice_lim_2
  254. #endif
  255. !!======================================================================
  256. END MODULE sbcice_lim_2