limdmp_2.F90 9.1 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185
  1. MODULE limdmp_2
  2. !!======================================================================
  3. !! *** MODULE limdmp_2 ***
  4. !! LIM-2 ice model : restoring Ice thickness and Fraction leads
  5. !!======================================================================
  6. !! History : 2.0 ! 2004-04 (S. Theetten) Original code
  7. !! 3.3 ! 2010-06 (J.-M. Molines) use of fldread
  8. !!----------------------------------------------------------------------
  9. #if defined key_lim2
  10. !!----------------------------------------------------------------------
  11. !! 'key_lim2' LIM 2.0 sea-ice model
  12. !!----------------------------------------------------------------------
  13. !! lim_dmp_2 : ice model damping
  14. !!----------------------------------------------------------------------
  15. USE ice_2 ! ice variables
  16. USE sbc_oce, ONLY : nn_fsbc ! for fldread
  17. USE dom_oce ! for mi0; mi1 etc ...
  18. USE fldread ! read input fields
  19. USE in_out_manager ! I/O manager
  20. USE lib_mpp ! MPP library
  21. USE lib_fortran ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)
  22. IMPLICIT NONE
  23. PRIVATE
  24. PUBLIC lim_dmp_2 ! called by sbc_ice_lim2
  25. INTEGER , PARAMETER :: jp_hicif = 1 , jp_frld = 2
  26. REAL(wp) , ALLOCATABLE, DIMENSION(:,:,:) :: resto_ice ! restoring coeff. on ICE [s-1]
  27. TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_icedmp ! structure of ice damping input
  28. !! * Substitution
  29. # include "vectopt_loop_substitute.h90"
  30. !!----------------------------------------------------------------------
  31. !! NEMO/LIM 3.3 , UCL-NEMO-consortium (2010)
  32. !! $Id: limdmp_2.F90 4624 2014-04-28 12:09:03Z acc $
  33. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  34. !!----------------------------------------------------------------------
  35. CONTAINS
  36. SUBROUTINE lim_dmp_2( kt )
  37. !!-------------------------------------------------------------------
  38. !! *** ROUTINE lim_dmp_2 ***
  39. !!
  40. !! ** purpose : restore ice thickness and lead fraction
  41. !!
  42. !! ** method : restore ice thickness and lead fraction using a restoring
  43. !! coefficient defined by the user in lim_dmp_init
  44. !!
  45. !! ** Action : - update hicif and frld
  46. !!
  47. !!---------------------------------------------------------------------
  48. INTEGER, INTENT(in) :: kt ! ocean time-step
  49. !
  50. INTEGER :: ji, jj ! dummy loop indices
  51. REAL(wp) :: zfrld, zhice ! local scalars
  52. !!---------------------------------------------------------------------
  53. !
  54. IF( kt == nit000 ) THEN
  55. IF(lwp) WRITE(numout,*)
  56. IF(lwp) WRITE(numout,*) 'lim_dmp_2 : Ice thickness and ice concentration restoring'
  57. IF(lwp) WRITE(numout,*) '~~~~~~~~~~'
  58. !
  59. ! ice_resto_init create resto_ice (in 1/s) for restoring ice parameters near open boundaries.
  60. ! Double check this routine to verify if it corresponds to your config
  61. CALL lim_dmp_init
  62. ENDIF
  63. !
  64. IF( ln_limdmp ) THEN ! ice restoring in this case
  65. !
  66. CALL fld_read( kt, nn_fsbc, sf_icedmp )
  67. !
  68. !CDIR COLLAPSE
  69. hicif(:,:) = MAX( 0._wp, & ! h >= 0 avoid spurious out of physical range
  70. & hicif(:,:) - rdt_ice * resto_ice(:,:,1) * ( hicif(:,:) - sf_icedmp(jp_hicif)%fnow(:,:,1) ) )
  71. !CDIR COLLAPSE
  72. frld (:,:) = MAX( 0._wp, MIN( 1._wp, & ! 0<= frld<=1 values which blow the run up
  73. & frld (:,:) - rdt_ice * resto_ice(:,:,1) * ( frld (:,:) - sf_icedmp(jp_frld )%fnow(:,:,1) ) ) )
  74. !
  75. ENDIF
  76. !
  77. END SUBROUTINE lim_dmp_2
  78. SUBROUTINE lim_dmp_init
  79. !!----------------------------------------------------------------------
  80. !! *** ROUTINE lim_dmp_init ***
  81. !!
  82. !! ** Purpose : set the coefficient for the ice thickness and lead fraction restoring
  83. !!
  84. !! ** Method : restoring is used to mimic ice open boundaries.
  85. !! the restoring coef. (a 2D array) has to be defined by the user.
  86. !! here is given as an example a restoring along north and south boundaries
  87. !!
  88. !! ** Action : define resto_ice(:,:,1)
  89. !!----------------------------------------------------------------------
  90. INTEGER :: ji, jj, jk ! dummy loop indices
  91. INTEGER :: irelax, ierror ! error flag for allocation
  92. INTEGER :: ios ! Local integer output status for namelist read
  93. !
  94. REAL(wp) :: zdmpmax, zdmpmin, zfactor, zreltim ! temporary scalar
  95. !
  96. CHARACTER(len=100) :: cn_dir ! Root directory for location of ssr files
  97. TYPE(FLD_N), DIMENSION (2) :: sl_icedmp ! informations about the icedmp field to be read
  98. TYPE(FLD_N) :: sn_hicif !
  99. TYPE(FLD_N) :: sn_frld !
  100. NAMELIST/namice_dmp/ cn_dir, ln_limdmp, sn_hicif, sn_frld
  101. !!----------------------------------------------------------------------
  102. !
  103. ! 1) initialize fld read structure for input data
  104. ! --------------------------------------------
  105. REWIND( numnam_ice_ref ) ! Namelist namice_dmp in reference namelist : Ice restoring
  106. READ ( numnam_ice_ref, namice_dmp, IOSTAT = ios, ERR = 901)
  107. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_dmp in reference namelist', lwp )
  108. REWIND( numnam_ice_cfg ) ! Namelist namice_dmp in configuration namelist : Ice restoring
  109. READ ( numnam_ice_cfg, namice_dmp, IOSTAT = ios, ERR = 902 )
  110. 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namice_dmp in configuration namelist', lwp )
  111. IF(lwm) WRITE ( numoni, namice_dmp )
  112. !
  113. IF ( lwp ) THEN !* control print
  114. WRITE (numout,*)' lim_dmp_init : lim_dmp initialization '
  115. WRITE (numout,*)' Namelist namicedmp read '
  116. WRITE (numout,*)' Ice restoring (T) or not (F) ln_limdmp =', ln_limdmp
  117. WRITE (numout,*)
  118. WRITE (numout,*)' CAUTION : here hard coded ice restoring along northern and southern boundaries'
  119. WRITE (numout,*)' adapt the lim_dmp_init routine to your needs'
  120. ENDIF
  121. ! 2) initialise resto_ice ==> config dependant !
  122. ! -------------------- ++++++++++++++++
  123. !
  124. IF( ln_limdmp ) THEN !* ice restoring is used, follow initialization
  125. !
  126. sl_icedmp ( jp_hicif ) = sn_hicif
  127. sl_icedmp ( jp_frld ) = sn_frld
  128. ALLOCATE ( sf_icedmp (2) , resto_ice(jpi,jpj,1), STAT=ierror )
  129. IF( ierror > 0 ) THEN
  130. CALL ctl_stop( 'lim_dmp_init: unable to allocate sf_icedmp structure or resto_ice array' ) ; RETURN
  131. ENDIF
  132. ALLOCATE( sf_icedmp(jp_hicif)%fnow(jpi,jpj,1) , sf_icedmp(jp_hicif)%fdta(jpi,jpj,1,2) )
  133. ALLOCATE( sf_icedmp(jp_frld )%fnow(jpi,jpj,1) , sf_icedmp(jp_frld )%fdta(jpi,jpj,1,2) )
  134. ! ! fill sf_icedmp with sn_icedmp and control print
  135. CALL fld_fill( sf_icedmp, sl_icedmp, cn_dir, 'lim_dmp_init', 'Ice restoring input data', 'namicedmp' )
  136. resto_ice(:,:,:) = 0._wp
  137. ! Re-calculate the North and South boundary restoring term
  138. ! because those boundaries may change with the prescribed zoom area.
  139. !
  140. irelax = 16 ! width of buffer zone with respect to close boundary
  141. zdmpmax = 10._wp ! max restoring time scale (days) (low restoring)
  142. zdmpmin = rdt_ice / 86400._wp ! min restoring time scale (days) (high restoring)
  143. ! ! days / grid-point
  144. zfactor = ( zdmpmax - zdmpmin ) / REAL( irelax, wp )
  145. ! South boundary restoring term
  146. ! REM: if there is no ice in the model and in the data,
  147. ! no restoring even with non zero resto_ice
  148. DO jj = mj0(jpjzoom - 1 + 1), mj1(jpjzoom -1 + irelax)
  149. zreltim = zdmpmin + zfactor * ( mjg(jj) - jpjzoom + 1 )
  150. resto_ice(:,jj,:) = 1._wp / ( zreltim * 86400._wp )
  151. END DO
  152. ! North boundary restoring term
  153. DO jj = mj0(jpjzoom -1 + jpjglo - irelax), mj1(jpjzoom - 1 + jpjglo)
  154. zreltim = zdmpmin + zfactor * (jpjglo - ( mjg(jj) - jpjzoom + 1 ))
  155. resto_ice(:,jj,:) = 1.e0 / ( zreltim * 86400 )
  156. END DO
  157. ENDIF
  158. !
  159. END SUBROUTINE lim_dmp_init
  160. #else
  161. !!----------------------------------------------------------------------
  162. !! Default option Empty Module No ice damping
  163. !!----------------------------------------------------------------------
  164. CONTAINS
  165. SUBROUTINE lim_dmp_2( kt ) ! Dummy routine
  166. WRITE(*,*) 'lim_dmp_2: You should not see this print! error? ', kt
  167. END SUBROUTINE lim_dmp_2
  168. #endif
  169. !!======================================================================
  170. END MODULE limdmp_2