sbcice_if.F90 7.5 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150
  1. MODULE sbcice_if
  2. !!======================================================================
  3. !! *** MODULE sbcice ***
  4. !! Surface module : update surface ocean boundary condition over ice
  5. !! covered area using ice-if model
  6. !!======================================================================
  7. !! History : 3.0 ! 2006-06 (G. Madec) Original code
  8. !!----------------------------------------------------------------------
  9. !!----------------------------------------------------------------------
  10. !! sbc_ice_if : update sbc in ice-covered area
  11. !!----------------------------------------------------------------------
  12. USE oce ! ocean dynamics and tracers
  13. USE dom_oce ! ocean space and time domain
  14. USE phycst ! physical constants
  15. USE eosbn2 ! equation of state
  16. USE sbc_oce ! surface boundary condition: ocean fields
  17. #if defined key_lim3
  18. USE ice , ONLY : a_i
  19. #else
  20. USE sbc_ice, ONLY : a_i
  21. #endif
  22. USE fldread ! read input field
  23. USE iom ! I/O manager library
  24. USE in_out_manager ! I/O manager
  25. USE lib_mpp ! MPP library
  26. USE lib_fortran ! Fortran utilities (allows no signed zero when 'key_nosignedzero' defined)
  27. IMPLICIT NONE
  28. PRIVATE
  29. PUBLIC sbc_ice_if ! routine called in sbcmod
  30. TYPE(FLD), ALLOCATABLE, DIMENSION(:) :: sf_ice ! structure of input ice-cover (file informations, fields read)
  31. !! * Substitutions
  32. # include "domzgr_substitute.h90"
  33. !!----------------------------------------------------------------------
  34. !! NEMO/OPA 3.3 , NEMO Consortium (2010)
  35. !! $Id: sbcice_if.F90 5540 2015-07-02 15:11:23Z jchanut $
  36. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  37. !!----------------------------------------------------------------------
  38. CONTAINS
  39. SUBROUTINE sbc_ice_if( kt )
  40. !!---------------------------------------------------------------------
  41. !! *** ROUTINE sbc_ice_if ***
  42. !!
  43. !! ** Purpose : handle surface boundary condition over ice cover area
  44. !! when sea-ice model are not used
  45. !!
  46. !! ** Method : - read sea-ice cover climatology
  47. !! - blah blah blah, ...
  48. !!
  49. !! ** Action : utau, vtau : remain unchanged
  50. !! taum, wndm : remain unchanged
  51. !! qns, qsr : update heat flux below sea-ice
  52. !! emp, sfx : update freshwater flux below sea-ice
  53. !! fr_i : update the ice fraction
  54. !!---------------------------------------------------------------------
  55. INTEGER, INTENT(in) :: kt ! ocean time step
  56. !
  57. INTEGER :: ji, jj ! dummy loop indices
  58. INTEGER :: ierror ! return error code
  59. INTEGER :: ios ! Local integer output status for namelist read
  60. REAL(wp) :: ztrp, zsice, zt_fzp, zfr_obs
  61. REAL(wp) :: zqri, zqrj, zqrp, zqi
  62. !!
  63. CHARACTER(len=100) :: cn_dir ! Root directory for location of ice-if files
  64. TYPE(FLD_N) :: sn_ice ! informations about the fields to be read
  65. NAMELIST/namsbc_iif/ cn_dir, sn_ice
  66. !!---------------------------------------------------------------------
  67. ! ! ====================== !
  68. IF( kt == nit000 ) THEN ! First call kt=nit000 !
  69. ! ! ====================== !
  70. ! set file information
  71. REWIND( numnam_ref ) ! Namelist namsbc_iif in reference namelist : Ice if file
  72. READ ( numnam_ref, namsbc_iif, IOSTAT = ios, ERR = 901)
  73. 901 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_iif in reference namelist', lwp )
  74. REWIND( numnam_cfg ) ! Namelist Namelist namsbc_iif in configuration namelist : Ice if file
  75. READ ( numnam_cfg, namsbc_iif, IOSTAT = ios, ERR = 902 )
  76. 902 IF( ios /= 0 ) CALL ctl_nam ( ios , 'namsbc_iif in configuration namelist', lwp )
  77. IF(lwm) WRITE ( numond, namsbc_iif )
  78. ALLOCATE( sf_ice(1), STAT=ierror )
  79. IF( ierror > 0 ) CALL ctl_stop( 'STOP', 'sbc_ice_if: unable to allocate sf_ice structure' )
  80. ALLOCATE( sf_ice(1)%fnow(jpi,jpj,1) )
  81. IF( sn_ice%ln_tint ) ALLOCATE( sf_ice(1)%fdta(jpi,jpj,1,2) )
  82. ! fill sf_ice with sn_ice and control print
  83. CALL fld_fill( sf_ice, (/ sn_ice /), cn_dir, 'sbc_ice_if', 'ice-if sea-ice model', 'namsbc_iif' )
  84. !
  85. ENDIF
  86. CALL fld_read( kt, nn_fsbc, sf_ice ) ! Read input fields and provides the
  87. ! ! input fields at the current time-step
  88. IF( MOD( kt-1, nn_fsbc) == 0 ) THEN
  89. !
  90. ztrp = -40. ! restoring terme for temperature (w/m2/k)
  91. zsice = - 0.04 / 0.8 ! ratio of isohaline compressibility over isotherme compressibility
  92. ! ( d rho / dt ) / ( d rho / ds ) ( s = 34, t = -1.8 )
  93. CALL eos_fzp( sss_m(:,:), fr_i(:,:) ) ! sea surface freezing temperature [Celcius]
  94. fr_i(:,:) = fr_i(:,:) * tmask(:,:,1)
  95. IF( ln_cpl ) a_i(:,:,1) = fr_i(:,:)
  96. ! Flux and ice fraction computation
  97. DO jj = 1, jpj
  98. DO ji = 1, jpi
  99. !
  100. zt_fzp = fr_i(ji,jj) ! freezing point temperature
  101. zfr_obs = sf_ice(1)%fnow(ji,jj,1) ! observed ice cover
  102. ! ! ocean ice fraction (0/1) from the freezing point temperature
  103. IF( sst_m(ji,jj) <= zt_fzp ) THEN ; fr_i(ji,jj) = 1.e0
  104. ELSE ; fr_i(ji,jj) = 0.e0
  105. ENDIF
  106. tsn(ji,jj,1,jp_tem) = MAX( tsn(ji,jj,1,jp_tem), zt_fzp ) ! avoid over-freezing point temperature
  107. qsr(ji,jj) = ( 1. - zfr_obs ) * qsr(ji,jj) ! solar heat flux : zero below observed ice cover
  108. ! ! non solar heat flux : add a damping term
  109. ! # ztrp*(t-(tgel-1.)) if observed ice and no opa ice (zfr_obs=1 fr_i=0)
  110. ! # ztrp*min(0,t-tgel) if observed ice and opa ice (zfr_obs=1 fr_i=1)
  111. zqri = ztrp * ( tsb(ji,jj,1,jp_tem) - ( zt_fzp - 1.) )
  112. zqrj = ztrp * MIN( 0., tsb(ji,jj,1,jp_tem) - zt_fzp )
  113. zqrp = ( zfr_obs * ( (1. - fr_i(ji,jj) ) * zqri &
  114. & + fr_i(ji,jj) * zqrj ) ) * tmask(ji,jj,1)
  115. ! ! non-solar heat flux
  116. ! # qns unchanged if no climatological ice (zfr_obs=0)
  117. ! # qns = zqrp if climatological ice and no opa ice (zfr_obs=1, fr_i=0)
  118. ! # qns = zqrp -2(-4) watt/m2 if climatological ice and opa ice (zfr_obs=1, fr_i=1)
  119. ! (-2=arctic, -4=antarctic)
  120. zqi = -3. + SIGN( 1.e0, ff(ji,jj) )
  121. qns(ji,jj) = ( ( 1.- zfr_obs ) * qns(ji,jj) &
  122. & + zfr_obs * fr_i(ji,jj) * zqi ) * tmask(ji,jj,1) &
  123. & + zqrp
  124. END DO
  125. END DO
  126. !
  127. ENDIF
  128. !
  129. END SUBROUTINE sbc_ice_if
  130. !!======================================================================
  131. END MODULE sbcice_if