limistate_2.F90 10 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228
  1. MODULE limistate_2
  2. !!======================================================================
  3. !! *** MODULE limistate_2 ***
  4. !! Initialisation of diagnostics ice variables
  5. !!======================================================================
  6. !! History : 1.0 ! 01-04 (C. Ethe, G. Madec) Original code
  7. !! 2.0 ! 03-08 (G. Madec) add lim_istate_init
  8. !! ! 04-04 (S. Theetten) initialization from a file
  9. !! ! 06-07 (S. Masson) IOM to read the restart
  10. !! ! 07-10 (G. Madec) surface module
  11. !!--------------------------------------------------------------------
  12. #if defined key_lim2
  13. !!----------------------------------------------------------------------
  14. !! 'key_lim2' : LIM 2.0 sea-ice model
  15. !!----------------------------------------------------------------------
  16. !! lim_istate_2 : Initialisation of diagnostics ice variables
  17. !! lim_istate_init_2 : initialization of ice state and namelist read
  18. !!----------------------------------------------------------------------
  19. USE phycst
  20. USE par_ice_2 ! ice parameters
  21. USE dom_ice_2
  22. USE eosbn2 ! equation of state
  23. USE lbclnk
  24. USE oce
  25. USE ice_2
  26. USE iom
  27. USE in_out_manager
  28. USE lib_fortran ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)
  29. IMPLICIT NONE
  30. PRIVATE
  31. PUBLIC lim_istate_2 ! routine called by lim_init_2.F90
  32. ! !! ** namelist (namiceini) **
  33. LOGICAL :: ln_limini ! Ice initialization state
  34. REAL(wp) :: ttest ! threshold water temperature for initial sea ice
  35. REAL(wp) :: hninn ! initial snow thickness in the north
  36. REAL(wp) :: hginn ! initial ice thickness in the north
  37. REAL(wp) :: alinn ! initial leads area in the north
  38. REAL(wp) :: hnins ! initial snow thickness in the south
  39. REAL(wp) :: hgins ! initial ice thickness in the south
  40. REAL(wp) :: alins ! initial leads area in the south
  41. REAL(wp) :: zero = 0.e0 ! constant value = 0
  42. REAL(wp) :: zone = 1.e0 ! constant value = 1
  43. !!----------------------------------------------------------------------
  44. !! NEMO/LIM2 3.3 , UCL - NEMO Consortium (2010)
  45. !! $Id: limistate_2.F90 5540 2015-07-02 15:11:23Z jchanut $
  46. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  47. !!----------------------------------------------------------------------
  48. CONTAINS
  49. SUBROUTINE lim_istate_2
  50. !!-------------------------------------------------------------------
  51. !! *** ROUTINE lim_istate_2 ***
  52. !!
  53. !! ** Purpose : defined the sea-ice initial state
  54. !!
  55. !! ** Method : restart from a state defined in a binary file
  56. !! or from arbitrary sea-ice conditions
  57. !!--------------------------------------------------------------------
  58. INTEGER :: ji, jj, jk ! dummy loop indices
  59. REAL(wp) :: zidto ! temporary scalar
  60. !--------------------------------------------------------------------
  61. CALL lim_istate_init_2 ! reading the initials parameters of the ice
  62. IF( .NOT. ln_limini ) THEN
  63. CALL eos_fzp( tsn(:,:,1,jp_sal), tfu(:,:) ) ! freezing/melting point of sea water [Celcius]
  64. tfu(:,:) = tfu(:,:) * tmask(:,:,1)
  65. DO jj = 1, jpj
  66. DO ji = 1, jpi
  67. ! ! ice if sst <= t-freez + ttest
  68. IF( tsn(ji,jj,1,jp_tem) - tfu(ji,jj) >= ttest ) THEN ; zidto = 0.e0 ! no ice
  69. ELSE ; zidto = 1.e0 ! ice
  70. ENDIF
  71. !
  72. IF( fcor(ji,jj) >= 0.e0 ) THEN !-- Northern hemisphere.
  73. hicif(ji,jj) = zidto * hginn
  74. frld(ji,jj) = zidto * alinn + ( 1.0 - zidto ) * 1.0
  75. hsnif(ji,jj) = zidto * hninn
  76. ELSE !--- Southern hemisphere.
  77. hicif(ji,jj) = zidto * hgins
  78. frld(ji,jj) = zidto * alins + ( 1.0 - zidto ) * 1.0
  79. hsnif(ji,jj) = zidto * hnins
  80. ENDIF
  81. END DO
  82. END DO
  83. tfu(:,:) = tfu(:,:) + rt0 ! ftu converted from Celsius to Kelvin (rt0 over land)
  84. sist (:,:) = tfu(:,:)
  85. tbif (:,:,1) = tfu(:,:)
  86. tbif (:,:,2) = tfu(:,:)
  87. tbif (:,:,3) = tfu(:,:)
  88. ENDIF
  89. fsbbq (:,:) = 0.e0
  90. qstoif(:,:) = 0.e0
  91. u_ice (:,:) = 0.e0
  92. v_ice (:,:) = 0.e0
  93. !--- Moments for advection.
  94. sxice (:,:) = 0.e0 ; sxsn (:,:) = 0.e0 ; sxa (:,:) = 0.e0
  95. syice (:,:) = 0.e0 ; sysn (:,:) = 0.e0 ; sya (:,:) = 0.e0
  96. sxxice(:,:) = 0.e0 ; sxxsn(:,:) = 0.e0 ; sxxa (:,:) = 0.e0
  97. syyice(:,:) = 0.e0 ; syysn(:,:) = 0.e0 ; syya (:,:) = 0.e0
  98. sxyice(:,:) = 0.e0 ; sxysn(:,:) = 0.e0 ; sxya (:,:) = 0.e0
  99. sxc0 (:,:) = 0.e0 ; sxc1 (:,:) = 0.e0 ; sxc2 (:,:) = 0.e0
  100. syc0 (:,:) = 0.e0 ; syc1 (:,:) = 0.e0 ; syc2 (:,:) = 0.e0
  101. sxxc0 (:,:) = 0.e0 ; sxxc1(:,:) = 0.e0 ; sxxc2(:,:) = 0.e0
  102. syyc0 (:,:) = 0.e0 ; syyc1(:,:) = 0.e0 ; syyc2(:,:) = 0.e0
  103. sxyc0 (:,:) = 0.e0 ; sxyc1(:,:) = 0.e0 ; sxyc2(:,:) = 0.e0
  104. sxst (:,:) = 0.e0
  105. syst (:,:) = 0.e0
  106. sxxst (:,:) = 0.e0
  107. syyst (:,:) = 0.e0
  108. sxyst (:,:) = 0.e0
  109. #if ! defined key_lim2_vp
  110. stress1_i (:,:) = 0._wp ! EVP rheology
  111. stress2_i (:,:) = 0._wp
  112. stress12_i(:,:) = 0._wp
  113. #endif
  114. !-- lateral boundary conditions
  115. CALL lbc_lnk( hicif, 'T', 1. )
  116. CALL lbc_lnk( frld , 'T', 1. )
  117. ! C A U T I O N frld = 1 over land and lbc_lnk put zero along
  118. ! ************* closed boundaries herefore we force to one over land
  119. frld(:,:) = tms(:,:) * frld(:,:) + ( 1. - tms(:,:) )
  120. CALL lbc_lnk( hsnif, 'T', 1. )
  121. CALL lbc_lnk( sist , 'T', 1. , pval = rt0 ) ! set rt0 on closed boundary (required by bulk formulation)
  122. DO jk = 1, jplayersp1
  123. CALL lbc_lnk(tbif(:,:,jk), 'T', 1. )
  124. END DO
  125. CALL lbc_lnk( fsbbq , 'T', 1. )
  126. CALL lbc_lnk( qstoif , 'T', 1. )
  127. END SUBROUTINE lim_istate_2
  128. SUBROUTINE lim_istate_init_2
  129. !!-------------------------------------------------------------------
  130. !! *** ROUTINE lim_istate_init_2 ***
  131. !!
  132. !! ** Purpose : Definition of initial state of the ice
  133. !!
  134. !! ** Method : Read the namiceini namelist and check the parameter
  135. !! values called at the first timestep (nit000)
  136. !!
  137. !! ** input : Namelist namiceini
  138. !!-------------------------------------------------------------------
  139. INTEGER :: inum_ice
  140. INTEGER :: ji,jj
  141. INTEGER :: ios ! Local integer output status for namelist read
  142. NAMELIST/namiceini/ ln_limini, ttest, hninn, hginn, alinn, &
  143. & hnins, hgins, alins
  144. !!-------------------------------------------------------------------
  145. REWIND( numnam_ice_ref ) ! Namelist namiceini in reference namelist : Ice initial state
  146. READ ( numnam_ice_ref, namiceini, IOSTAT = ios, ERR = 901)
  147. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namiceini in reference namelist', lwp )
  148. REWIND( numnam_ice_cfg ) ! Namelist namiceini in configuration namelist : Ice initial state
  149. READ ( numnam_ice_cfg, namiceini, IOSTAT = ios, ERR = 902 )
  150. 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namiceini in configuration namelist', lwp )
  151. IF(lwm) WRITE ( numoni, namiceini )
  152. !
  153. IF(lwp) THEN
  154. WRITE(numout,*)
  155. WRITE(numout,*) 'lim_istate_init_2 : ice parameters inititialisation '
  156. WRITE(numout,*) '~~~~~~~~~~~~~~~~~'
  157. WRITE(numout,*) ' threshold water temp. for initial sea-ice ttest = ', ttest
  158. WRITE(numout,*) ' initial snow thickness in the north hninn = ', hninn
  159. WRITE(numout,*) ' initial ice thickness in the north hginn = ', hginn
  160. WRITE(numout,*) ' initial leads area in the north alinn = ', alinn
  161. WRITE(numout,*) ' initial snow thickness in the south hnins = ', hnins
  162. WRITE(numout,*) ' initial ice thickness in the south hgins = ', hgins
  163. WRITE(numout,*) ' initial leads area in the south alins = ', alins
  164. WRITE(numout,*) ' Ice state initialization using input file ln_limini = ', ln_limini
  165. ENDIF
  166. IF( ln_limini ) THEN ! Ice initialization using input file
  167. !
  168. CALL iom_open( 'Ice_initialization.nc', inum_ice )
  169. !
  170. IF( inum_ice > 0 ) THEN
  171. IF(lwp) WRITE(numout,*)
  172. IF(lwp) WRITE(numout,*) ' ice state initialization with : Ice_initialization.nc'
  173. CALL iom_get( inum_ice, jpdom_data, 'hicif', hicif )
  174. CALL iom_get( inum_ice, jpdom_data, 'hsnif', hsnif )
  175. CALL iom_get( inum_ice, jpdom_data, 'frld' , frld )
  176. CALL iom_get( inum_ice, jpdom_data, 'ts' , sist )
  177. CALL iom_get( inum_ice, jpdom_unknown, 'tbif', tbif(1:nlci,1:nlcj,:), &
  178. & kstart = (/ mig(1),mjg(1),1 /), kcount = (/ nlci,nlcj,jplayersp1 /) )
  179. ! put some values in the extra-halo...
  180. DO jj = nlcj+1, jpj ; tbif(1:nlci,jj,:) = tbif(1:nlci,nlej,:) ; END DO
  181. DO ji = nlci+1, jpi ; tbif(ji ,: ,:) = tbif(nlei ,: ,:) ; END DO
  182. CALL iom_close( inum_ice)
  183. !
  184. ENDIF
  185. ENDIF
  186. !
  187. END SUBROUTINE lim_istate_init_2
  188. #else
  189. !!----------------------------------------------------------------------
  190. !! Default option : Empty module NO LIM 2.0 sea-ice model
  191. !!----------------------------------------------------------------------
  192. CONTAINS
  193. SUBROUTINE lim_istate_2 ! Empty routine
  194. END SUBROUTINE lim_istate_2
  195. #endif
  196. !!======================================================================
  197. END MODULE limistate_2