icbclv.F90 9.0 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183
  1. MODULE icbclv
  2. !!======================================================================
  3. !! *** MODULE icbclv ***
  4. !! Icebergs: calving routines for iceberg calving
  5. !!======================================================================
  6. !! History : 3.3.1 ! 2010-01 (Martin&Adcroft) Original code
  7. !! - ! 2011-03 (Madec) Part conversion to NEMO form
  8. !! - ! Removal of mapping from another grid
  9. !! - ! 2011-04 (Alderson) Split into separate modules
  10. !! - ! 2011-05 (Alderson) budgets into separate module
  11. !!----------------------------------------------------------------------
  12. !!----------------------------------------------------------------------
  13. !! icb_clv_flx : transfer input flux of ice into iceberg classes
  14. !! icb_clv : calve icebergs from stored ice
  15. !!----------------------------------------------------------------------
  16. USE par_oce ! NEMO parameters
  17. USE dom_oce ! NEMO ocean domain
  18. USE phycst ! NEMO physical constants
  19. USE lib_mpp ! NEMO MPI library, lk_mpp in particular
  20. USE lbclnk ! NEMO boundary exchanges for gridded data
  21. USE icb_oce ! iceberg variables
  22. USE icbdia ! iceberg diagnostics
  23. USE icbutl ! iceberg utility routines
  24. IMPLICIT NONE
  25. PRIVATE
  26. PUBLIC icb_clv_flx ! routine called in icbstp.F90 module
  27. PUBLIC icb_clv ! routine called in icbstp.F90 module
  28. !!----------------------------------------------------------------------
  29. !! NEMO/OPA 3.3 , NEMO Consortium (2011)
  30. !! $Id: icbclv.F90 2355 2015-05-20 07:11:50Z ufla $
  31. !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
  32. !!----------------------------------------------------------------------
  33. CONTAINS
  34. SUBROUTINE icb_clv_flx( kt )
  35. !!----------------------------------------------------------------------
  36. !! *** ROUTINE icb_clv_flx ***
  37. !!
  38. !! ** Purpose : accumulate ice available for calving into class arrays
  39. !!
  40. !!----------------------------------------------------------------------
  41. INTEGER, INTENT(in) :: kt
  42. !
  43. REAL(wp) :: zcalving_used, zdist, zfact
  44. INTEGER :: jn, ji, jj ! loop counters
  45. INTEGER :: imx ! temporary integer for max berg class
  46. LOGICAL, SAVE :: ll_first_call = .TRUE.
  47. !!----------------------------------------------------------------------
  48. !
  49. ! Adapt calving flux and calving heat flux from coupler for use here
  50. ! Use interior mask: so no bergs in overlap areas and convert from km^3/year to kg/s
  51. ! this assumes that input is given as equivalent water flux so that pure water density is appropriate
  52. zfact = ( (1000._wp)**3 / ( NINT(rday) * nyear_len(1) ) ) * 850._wp
  53. berg_grid%calving(:,:) = src_calving(:,:) * tmask_i(:,:) * zfact
  54. ! Heat in units of W/m2, and mask (just in case)
  55. berg_grid%calving_hflx(:,:) = src_calving_hflx(:,:) * tmask_i(:,:)
  56. IF( ll_first_call .AND. .NOT. l_restarted_bergs) THEN ! This is a hack to simplify initialization
  57. ll_first_call = .FALSE.
  58. !do jn=1, nclasses
  59. ! where (berg_grid%calving==0.) berg_grid%stored_ice(:,:,jn)=0.
  60. !end do
  61. DO jj = 2, jpjm1
  62. DO ji = 2, jpim1
  63. IF( berg_grid%calving(ji,jj) /= 0._wp ) & ! Need units of J
  64. berg_grid%stored_heat(ji,jj) = SUM( berg_grid%stored_ice(ji,jj,:) ) * & ! initial stored ice in kg
  65. berg_grid%calving_hflx(ji,jj) * e1e2t(ji,jj) / & ! J/s/m2 x m^2 = J/s
  66. berg_grid%calving(ji,jj) ! /calving in kg/s
  67. END DO
  68. END DO
  69. ENDIF
  70. ! assume that all calving flux must be distributed even if distribution array does not sum
  71. ! to one - this may not be what is intended, but it's what you've got
  72. DO jj = 1,jpj
  73. DO ji = 1,jpi
  74. imx = berg_grid%maxclass(ji,jj)
  75. zdist = SUM( rn_distribution(1:nclasses) ) / SUM( rn_distribution(1:imx) )
  76. DO jn = 1, imx
  77. berg_grid%stored_ice(ji,jj,jn) = berg_grid%stored_ice(ji,jj,jn) + &
  78. berg_dt * berg_grid%calving(ji,jj) * rn_distribution(jn) * zdist
  79. END DO
  80. END DO
  81. END DO
  82. ! before changing the calving, save the amount we're about to use and do budget
  83. zcalving_used = SUM( berg_grid%calving(:,:) )
  84. berg_grid%tmp(:,:) = berg_dt * berg_grid%calving_hflx(:,:) * e1e2t(:,:) * tmask_i(:,:)
  85. berg_grid%stored_heat (:,:) = berg_grid%stored_heat (:,:) + berg_grid%tmp(:,:)
  86. CALL icb_dia_income( kt, zcalving_used, berg_grid%tmp )
  87. !
  88. END SUBROUTINE icb_clv_flx
  89. SUBROUTINE icb_clv()
  90. !!----------------------------------------------------------------------
  91. !! *** ROUTINE icb_clv ***
  92. !!
  93. !! ** Purpose : This routine takes a stored ice field and calves to the ocean,
  94. !! so the gridded array stored_ice has only non-zero entries at selected
  95. !! wet points adjacent to known land based calving points
  96. !!
  97. !! ** method : - Look at each grid point and see if there's enough for each size class to calve
  98. !! If there is, a new iceberg is calved. This happens in the order determined by
  99. !! the class definition arrays (which in the default case is smallest first)
  100. !! Note that only the non-overlapping part of the processor where icebergs are allowed
  101. !! is considered
  102. !!----------------------------------------------------------------------
  103. INTEGER :: ji, jj, jn ! dummy loop indices
  104. INTEGER :: icnt, icntmax
  105. TYPE(iceberg) :: newberg
  106. TYPE(point) :: newpt
  107. REAL(wp) :: zday, zcalved_to_berg, zheat_to_berg
  108. !!----------------------------------------------------------------------
  109. !
  110. icntmax = 0
  111. zday = REAL(nday_year,wp) + REAL(nsec_day,wp)/86400.0_wp
  112. !
  113. DO jn = 1, nclasses
  114. DO jj = nicbdj, nicbej
  115. DO ji = nicbdi, nicbei
  116. !
  117. icnt = 0
  118. !
  119. DO WHILE (berg_grid%stored_ice(ji,jj,jn) >= rn_initial_mass(jn) * rn_mass_scaling(jn) )
  120. !
  121. newpt%lon = glamt(ji,jj) ! at t-point (centre of the cell)
  122. newpt%lat = gphit(ji,jj)
  123. newpt%xi = REAL( mig(ji), wp )
  124. newpt%yj = REAL( mjg(jj), wp )
  125. !
  126. newpt%uvel = 0._wp ! initially at rest
  127. newpt%vvel = 0._wp
  128. ! ! set berg characteristics
  129. newpt%mass = rn_initial_mass (jn)
  130. newpt%thickness = rn_initial_thickness(jn)
  131. newpt%width = first_width (jn)
  132. newpt%length = first_length (jn)
  133. newberg%mass_scaling = rn_mass_scaling (jn)
  134. newpt%mass_of_bits = 0._wp ! no bergy
  135. !
  136. newpt%year = nyear
  137. newpt%day = zday
  138. newpt%heat_density = berg_grid%stored_heat(ji,jj) / berg_grid%stored_ice(ji,jj,jn) ! This is in J/kg
  139. !
  140. CALL icb_utl_incr()
  141. newberg%number(:) = num_bergs(:)
  142. !
  143. CALL icb_utl_add( newberg, newpt )
  144. !
  145. zcalved_to_berg = rn_initial_mass(jn) * rn_mass_scaling(jn) ! Units of kg
  146. ! ! Heat content
  147. zheat_to_berg = zcalved_to_berg * newpt%heat_density ! Units of J
  148. berg_grid%stored_heat(ji,jj) = berg_grid%stored_heat(ji,jj) - zheat_to_berg
  149. ! ! Stored mass
  150. berg_grid%stored_ice(ji,jj,jn) = berg_grid%stored_ice(ji,jj,jn) - zcalved_to_berg
  151. !
  152. icnt = icnt + 1
  153. !
  154. CALL icb_dia_calve(ji, jj, jn, zcalved_to_berg, zheat_to_berg )
  155. END DO
  156. icntmax = MAX( icntmax, icnt )
  157. END DO
  158. END DO
  159. END DO
  160. !
  161. DO jn = 1,nclasses
  162. CALL lbc_lnk( berg_grid%stored_ice(:,:,jn), 'T', 1._wp )
  163. END DO
  164. CALL lbc_lnk( berg_grid%stored_heat, 'T', 1._wp )
  165. !
  166. IF( nn_verbose_level > 0 .AND. icntmax > 1 ) WRITE(numicb,*) 'icb_clv: icnt=', icnt,' on', narea
  167. !
  168. END SUBROUTINE icb_clv
  169. !!======================================================================
  170. END MODULE icbclv