New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
icethd_dh.F90 in NEMO/trunk/src/ICE – NEMO

source: NEMO/trunk/src/ICE/icethd_dh.F90

Last change on this file was 14686, checked in by clem, 3 years ago

trunk: solve negative sublimation problems (ticket #2649)

  • Property svn:keywords set to Id
File size: 35.8 KB
Line 
1MODULE icethd_dh
2   !!======================================================================
3   !!                       ***  MODULE icethd_dh ***
4   !!   seaice : thermodynamic growth and melt
5   !!======================================================================
6   !! History :       !  2003-05  (M. Vancoppenolle) Original code in 1D
7   !!                 !  2005-06  (M. Vancoppenolle) 3D version
8   !!            4.0  !  2018     (many people)      SI3 [aka Sea Ice cube]
9   !!----------------------------------------------------------------------
10#if defined key_si3
11   !!----------------------------------------------------------------------
12   !!   'key_si3'                                       SI3 sea-ice model
13   !!----------------------------------------------------------------------
14   !!   ice_thd_dh        : vertical sea-ice growth and melt
15   !!----------------------------------------------------------------------
16   USE dom_oce        ! ocean space and time domain
17   USE phycst         ! physical constants
18   USE ice            ! sea-ice: variables
19   USE ice1D          ! sea-ice: thermodynamics variables
20   USE icethd_sal     ! sea-ice: salinity profiles
21   USE icevar         ! for CALL ice_var_snwblow
22   !
23   USE in_out_manager ! I/O manager
24   USE lib_mpp        ! MPP library
25   USE lib_fortran    ! fortran utilities (glob_sum + no signed zero)
26
27   IMPLICIT NONE
28   PRIVATE
29
30   PUBLIC   ice_thd_dh        ! called by ice_thd
31
32   !!----------------------------------------------------------------------
33   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
34   !! $Id$
35   !! Software governed by the CeCILL license (see ./LICENSE)
36   !!----------------------------------------------------------------------
37CONTAINS
38
39   SUBROUTINE ice_thd_dh
40      !!------------------------------------------------------------------
41      !!                ***  ROUTINE ice_thd_dh  ***
42      !!
43      !! ** Purpose :   compute ice and snow thickness changes due to growth/melting
44      !!
45      !! ** Method  :   Ice/Snow surface melting arises from imbalance in surface fluxes
46      !!                Bottom accretion/ablation arises from flux budget
47      !!                Snow thickness can increase by precipitation and decrease by sublimation
48      !!                If snow load excesses Archmiede limit, snow-ice is formed by
49      !!                the flooding of sea-water in the snow
50      !!
51      !!                - Compute available flux of heat for surface ablation
52      !!                - Compute snow and sea ice enthalpies
53      !!                - Surface ablation and sublimation
54      !!                - Bottom accretion/ablation
55      !!                - Snow ice formation
56      !!
57      !! ** Note     :  h=max(0,h+dh) are often used to ensure positivity of h.
58      !!                very small negative values can occur otherwise (e.g. -1.e-20)
59      !!
60      !! References : Bitz and Lipscomb, 1999, J. Geophys. Res.
61      !!              Fichefet T. and M. Maqueda 1997, J. Geophys. Res., 102(C6), 12609-12646
62      !!              Vancoppenolle, Fichefet and Bitz, 2005, Geophys. Res. Let.
63      !!              Vancoppenolle et al.,2009, Ocean Modelling
64      !!------------------------------------------------------------------
65      INTEGER  ::   ji, jk       ! dummy loop indices
66      INTEGER  ::   iter         ! local integer
67
68      REAL(wp) ::   ztmelts      ! local scalar
69      REAL(wp) ::   zdum
70      REAL(wp) ::   zfracs       ! fractionation coefficient for bottom salt entrapment
71      REAL(wp) ::   zswi1        ! switch for computation of bottom salinity
72      REAL(wp) ::   zswi12       ! switch for computation of bottom salinity
73      REAL(wp) ::   zswi2        ! switch for computation of bottom salinity
74      REAL(wp) ::   zgrr         ! bottom growth rate
75      REAL(wp) ::   zt_i_new     ! bottom formation temperature
76      REAL(wp) ::   z1_rho       ! 1/(rhos+rho0-rhoi)
77
78      REAL(wp) ::   zQm          ! enthalpy exchanged with the ocean (J/m2), >0 towards the ocean
79      REAL(wp) ::   zEi          ! specific enthalpy of sea ice (J/kg)
80      REAL(wp) ::   zEw          ! specific enthalpy of exchanged water (J/kg)
81      REAL(wp) ::   zdE          ! specific enthalpy difference (J/kg)
82      REAL(wp) ::   zfmdt        ! exchange mass flux x time step (J/m2), >0 towards the ocean
83
84      REAL(wp), DIMENSION(jpij) ::   zq_top      ! heat for surface ablation                   (J.m-2)
85      REAL(wp), DIMENSION(jpij) ::   zq_bot      ! heat for bottom ablation                    (J.m-2)
86      REAL(wp), DIMENSION(jpij) ::   zq_rema     ! remaining heat at the end of the routine    (J.m-2)
87      REAL(wp), DIMENSION(jpij) ::   zf_tt       ! Heat budget to determine melting or freezing(W.m-2)
88      REAL(wp), DIMENSION(jpij) ::   zevap_rema  ! remaining mass flux from sublimation        (kg.m-2)
89      REAL(wp), DIMENSION(jpij) ::   zdeltah
90      REAL(wp), DIMENSION(jpij) ::   zsnw        ! distribution of snow after wind blowing
91
92      INTEGER , DIMENSION(jpij,nlay_i)     ::   icount    ! number of layers vanishing by melting
93      REAL(wp), DIMENSION(jpij,0:nlay_i+1) ::   zh_i      ! ice layer thickness (m)
94      REAL(wp), DIMENSION(jpij,0:nlay_s  ) ::   zh_s      ! snw layer thickness (m)
95      REAL(wp), DIMENSION(jpij,0:nlay_s  ) ::   ze_s      ! snw layer enthalpy (J.m-3)
96
97      REAL(wp) ::   zswitch_sal
98
99      INTEGER  ::   num_iter_max      ! Heat conservation
100      !!------------------------------------------------------------------
101
102      ! Discriminate between time varying salinity and constant
103      SELECT CASE( nn_icesal )                  ! varying salinity or not
104         CASE( 1 , 3 )   ;   zswitch_sal = 0._wp   ! prescribed salinity profile
105         CASE( 2 )       ;   zswitch_sal = 1._wp   ! varying salinity profile
106      END SELECT
107
108      ! initialize ice layer thicknesses and enthalpies
109      eh_i_old(1:npti,0:nlay_i+1) = 0._wp
110      h_i_old (1:npti,0:nlay_i+1) = 0._wp
111      zh_i    (1:npti,0:nlay_i+1) = 0._wp
112      DO jk = 1, nlay_i
113         DO ji = 1, npti
114            eh_i_old(ji,jk) = h_i_1d(ji) * r1_nlay_i * e_i_1d(ji,jk)
115            h_i_old (ji,jk) = h_i_1d(ji) * r1_nlay_i
116            zh_i    (ji,jk) = h_i_1d(ji) * r1_nlay_i
117         END DO
118      END DO
119      !
120      ! initialize snw layer thicknesses and enthalpies
121      zh_s(1:npti,0) = 0._wp
122      ze_s(1:npti,0) = 0._wp
123      DO jk = 1, nlay_s
124         DO ji = 1, npti
125            zh_s(ji,jk) = h_s_1d(ji) * r1_nlay_s
126            ze_s(ji,jk) = e_s_1d(ji,jk)
127         END DO
128      END DO
129      !
130      !                       ! ============================================== !
131      !                       ! Available heat for surface and bottom ablation !
132      !                       ! ============================================== !
133      !
134      IF( ln_cndflx .AND. .NOT.ln_cndemulate ) THEN
135         !
136         DO ji = 1, npti
137            zq_top(ji)     = MAX( 0._wp, qml_ice_1d(ji) * rDt_ice )
138         END DO
139         !
140      ELSE
141         !
142         DO ji = 1, npti
143            zdum           = qns_ice_1d(ji) + qsr_ice_1d(ji) - qtr_ice_top_1d(ji) - qcn_ice_top_1d(ji)
144            qml_ice_1d(ji) = zdum * MAX( 0._wp , SIGN( 1._wp, t_su_1d(ji) - rt0 ) )
145            zq_top(ji)     = MAX( 0._wp, qml_ice_1d(ji) * rDt_ice )
146         END DO
147         !
148      ENDIF
149      !
150      DO ji = 1, npti
151         zf_tt(ji)         = qcn_ice_bot_1d(ji) + qsb_ice_bot_1d(ji) + fhld_1d(ji) + qtr_ice_bot_1d(ji) * frq_m_1d(ji)
152         zq_bot(ji)        = MAX( 0._wp, zf_tt(ji) * rDt_ice )
153      END DO
154
155      !                       ! ============ !
156      !                       !     Snow     !
157      !                       ! ============ !
158      !
159      ! Internal melting
160      ! ----------------
161      ! IF snow temperature is above freezing point, THEN snow melts (should not happen but sometimes it does)
162      DO jk = 1, nlay_s
163         DO ji = 1, npti
164            IF( t_s_1d(ji,jk) > rt0 ) THEN
165               hfx_res_1d    (ji) = hfx_res_1d    (ji) - ze_s(ji,jk) * zh_s(ji,jk) * a_i_1d(ji) * r1_Dt_ice   ! heat flux to the ocean [W.m-2], < 0
166               wfx_snw_sum_1d(ji) = wfx_snw_sum_1d(ji) + rhos        * zh_s(ji,jk) * a_i_1d(ji) * r1_Dt_ice   ! mass flux
167               ! updates
168               dh_s_mlt(ji)    =             dh_s_mlt(ji) - zh_s(ji,jk)
169               h_s_1d  (ji)    = MAX( 0._wp, h_s_1d  (ji) - zh_s(ji,jk) )
170               zh_s    (ji,jk) = 0._wp
171               ze_s    (ji,jk) = 0._wp
172            END IF
173         END DO
174      END DO
175
176      ! Snow precipitation
177      !-------------------
178      CALL ice_var_snwblow( 1._wp - at_i_1d(1:npti), zsnw(1:npti) )   ! snow distribution over ice after wind blowing
179
180      DO ji = 1, npti
181         IF( sprecip_1d(ji) > 0._wp ) THEN
182            zh_s(ji,0) = zsnw(ji) * sprecip_1d(ji) * rDt_ice * r1_rhos / at_i_1d(ji)   ! thickness of precip
183            ze_s(ji,0) = MAX( 0._wp, - qprec_ice_1d(ji) )                              ! enthalpy of the precip (>0, J.m-3)
184            !
185            hfx_spr_1d(ji) = hfx_spr_1d(ji) + ze_s(ji,0) * zh_s(ji,0) * a_i_1d(ji) * r1_Dt_ice   ! heat flux from snow precip (>0, W.m-2)
186            wfx_spr_1d(ji) = wfx_spr_1d(ji) - rhos       * zh_s(ji,0) * a_i_1d(ji) * r1_Dt_ice   ! mass flux, <0
187            !
188            ! update thickness
189            h_s_1d(ji) = h_s_1d(ji) + zh_s(ji,0)
190         ENDIF
191      END DO
192
193      ! Snow melting
194      ! ------------
195      ! If heat still available (zq_top > 0)
196      ! then all snw precip has been melted and we need to melt more snow
197      DO jk = 0, nlay_s
198         DO ji = 1, npti
199            IF( zh_s(ji,jk) > 0._wp .AND. zq_top(ji) > 0._wp ) THEN
200               !
201               rswitch = MAX( 0._wp , SIGN( 1._wp , ze_s(ji,jk) - epsi20 ) )
202               zdum    = - rswitch * zq_top(ji) / MAX( ze_s(ji,jk), epsi20 )   ! thickness change
203               zdum    = MAX( zdum , - zh_s(ji,jk) )                           ! bound melting
204
205               hfx_snw_1d    (ji) = hfx_snw_1d    (ji) - ze_s(ji,jk) * zdum * a_i_1d(ji) * r1_Dt_ice   ! heat used to melt snow(W.m-2, >0)
206               wfx_snw_sum_1d(ji) = wfx_snw_sum_1d(ji) - rhos        * zdum * a_i_1d(ji) * r1_Dt_ice   ! snow melting only = water into the ocean
207
208               ! updates available heat + thickness
209               dh_s_mlt(ji)    =              dh_s_mlt(ji)    + zdum
210               zq_top  (ji)    = MAX( 0._wp , zq_top  (ji)    + zdum * ze_s(ji,jk) )
211               h_s_1d  (ji)    = MAX( 0._wp , h_s_1d  (ji)    + zdum )
212               zh_s    (ji,jk) = MAX( 0._wp , zh_s    (ji,jk) + zdum )
213!!$               IF( zh_s(ji,jk) == 0._wp )   ze_s(ji,jk) = 0._wp
214               !
215            ENDIF
216         END DO
217      END DO
218
219      ! Snow sublimation
220      !-----------------
221      ! qla_ice is always >=0 (upwards), heat goes to the atmosphere, therefore snow sublimates
222      !    comment: not counted in mass/heat exchange in iceupdate.F90 since this is an exchange with atm. (not ocean)
223      zdeltah   (1:npti) = 0._wp ! total snow thickness that sublimates, < 0
224      zevap_rema(1:npti) = 0._wp
225      DO ji = 1, npti
226         zdeltah   (ji) = MAX( - evap_ice_1d(ji) * r1_rhos * rDt_ice, - h_s_1d(ji) )   ! amount of snw that sublimates, < 0
227         zevap_rema(ji) = evap_ice_1d(ji) * rDt_ice + zdeltah(ji) * rhos               ! remaining evap in kg.m-2 (used for ice sublimation later on)
228      END DO
229
230      DO jk = 0, nlay_s
231         DO ji = 1, npti
232            zdum = MAX( -zh_s(ji,jk), zdeltah(ji) ) ! snow layer thickness that sublimates, < 0
233            !
234            hfx_sub_1d    (ji) = hfx_sub_1d    (ji) + ze_s(ji,jk) * zdum * a_i_1d(ji) * r1_Dt_ice  ! Heat flux of snw that sublimates [W.m-2], < 0
235            wfx_snw_sub_1d(ji) = wfx_snw_sub_1d(ji) - rhos        * zdum * a_i_1d(ji) * r1_Dt_ice  ! Mass flux by sublimation
236
237            ! update thickness
238            h_s_1d(ji)    = MAX( 0._wp , h_s_1d(ji)    + zdum )
239            zh_s  (ji,jk) = MAX( 0._wp , zh_s  (ji,jk) + zdum )
240!!$            IF( zh_s(ji,jk) == 0._wp )   ze_s(ji,jk) = 0._wp
241
242            ! update sublimation left
243            zdeltah(ji) = MIN( zdeltah(ji) - zdum, 0._wp )
244         END DO
245      END DO
246
247      !
248      !                       ! ============ !
249      !                       !     Ice      !
250      !                       ! ============ !
251
252      ! Surface ice melting
253      !--------------------
254      DO jk = 1, nlay_i
255         DO ji = 1, npti
256            ztmelts = - rTmlt * sz_i_1d(ji,jk)   ! Melting point of layer k [C]
257
258            IF( t_i_1d(ji,jk) >= (ztmelts+rt0) ) THEN   !-- Internal melting
259
260               zEi            = - e_i_1d(ji,jk) * r1_rhoi             ! Specific enthalpy of layer k [J/kg, <0]
261               zdE            =   0._wp                               ! Specific enthalpy difference (J/kg, <0)
262               !                                                          set up at 0 since no energy is needed to melt water...(it is already melted)
263               zdum           = MIN( 0._wp , - zh_i(ji,jk) )          ! internal melting occurs when the internal temperature is above freezing
264               !                                                          this should normally not happen, but sometimes, heat diffusion leads to this
265               zfmdt          = - zdum * rhoi                         ! Recompute mass flux [kg/m2, >0]
266               !
267               dh_i_itm(ji)   = dh_i_itm(ji) + zdum                   ! Cumulate internal melting
268               !
269               hfx_res_1d(ji) = hfx_res_1d(ji) + zEi  * zfmdt             * a_i_1d(ji) * r1_Dt_ice    ! Heat flux to the ocean [W.m-2], <0
270               !                                                                                          ice enthalpy zEi is "sent" to the ocean
271               wfx_res_1d(ji) = wfx_res_1d(ji) - rhoi * zdum              * a_i_1d(ji) * r1_Dt_ice    ! Mass flux
272               sfx_res_1d(ji) = sfx_res_1d(ji) - rhoi * zdum * s_i_1d(ji) * a_i_1d(ji) * r1_Dt_ice    ! Salt flux
273               !                                                                                          using s_i_1d and not sz_i_1d(jk) is ok
274            ELSE                                        !-- Surface melting
275
276               zEi            = - e_i_1d(ji,jk) * r1_rhoi             ! Specific enthalpy of layer k [J/kg, <0]
277               zEw            =    rcp * ztmelts                      ! Specific enthalpy of resulting meltwater [J/kg, <0]
278               zdE            =    zEi - zEw                          ! Specific enthalpy difference < 0
279
280               zfmdt          = - zq_top(ji) / zdE                    ! Mass flux to the ocean [kg/m2, >0]
281
282               zdum           = - zfmdt * r1_rhoi                     ! Melt of layer jk [m, <0]
283
284               zdum           = MIN( 0._wp , MAX( zdum , - zh_i(ji,jk) ) )    ! Melt of layer jk cannot exceed the layer thickness [m, <0]
285
286               zq_top(ji)     = MAX( 0._wp , zq_top(ji) - zdum * rhoi * zdE ) ! update available heat
287
288               dh_i_sum(ji)   = dh_i_sum(ji) + zdum                   ! Cumulate surface melt
289
290               zfmdt          = - rhoi * zdum                         ! Recompute mass flux [kg/m2, >0]
291
292               zQm            = zfmdt * zEw                           ! Energy of the melt water sent to the ocean [J/m2, <0]
293
294               hfx_thd_1d(ji) = hfx_thd_1d(ji) + zEw  * zfmdt             * a_i_1d(ji) * r1_Dt_ice    ! Heat flux [W.m-2], < 0
295               hfx_sum_1d(ji) = hfx_sum_1d(ji) - zdE  * zfmdt             * a_i_1d(ji) * r1_Dt_ice    ! Heat flux used in this process [W.m-2], > 0
296               wfx_sum_1d(ji) = wfx_sum_1d(ji) - rhoi * zdum              * a_i_1d(ji) * r1_Dt_ice    ! Mass flux
297               sfx_sum_1d(ji) = sfx_sum_1d(ji) - rhoi * zdum * s_i_1d(ji) * a_i_1d(ji) * r1_Dt_ice    ! Salt flux >0
298               !                                                                                          using s_i_1d and not sz_i_1d(jk) is ok)
299            END IF
300            ! update thickness
301            zh_i(ji,jk) = MAX( 0._wp, zh_i(ji,jk) + zdum )
302            h_i_1d(ji)  = MAX( 0._wp, h_i_1d(ji)  + zdum )
303            !
304            ! update heat content (J.m-2) and layer thickness
305            eh_i_old(ji,jk) = eh_i_old(ji,jk) + zdum * e_i_1d(ji,jk)
306            h_i_old (ji,jk) = h_i_old (ji,jk) + zdum
307            !
308            !
309            ! Ice sublimation
310            ! ---------------
311            zdum               = MAX( - zh_i(ji,jk) , - zevap_rema(ji) * r1_rhoi )
312            !
313            hfx_sub_1d(ji)     = hfx_sub_1d(ji)     + e_i_1d(ji,jk) * zdum              * a_i_1d(ji) * r1_Dt_ice ! Heat flux [W.m-2], < 0
314            wfx_ice_sub_1d(ji) = wfx_ice_sub_1d(ji) - rhoi          * zdum              * a_i_1d(ji) * r1_Dt_ice ! Mass flux > 0
315            sfx_sub_1d(ji)     = sfx_sub_1d(ji)     - rhoi          * zdum * s_i_1d(ji) * a_i_1d(ji) * r1_Dt_ice ! Salt flux >0
316            !                                                                                                      clem: flux is sent to the ocean for simplicity
317            !                                                                                                            but salt should remain in the ice except
318            !                                                                                                            if all ice is melted. => must be corrected
319            ! update remaining mass flux and thickness
320            zevap_rema(ji) = zevap_rema(ji) + zdum * rhoi
321            zh_i(ji,jk)    = MAX( 0._wp, zh_i(ji,jk) + zdum )
322            h_i_1d(ji)     = MAX( 0._wp, h_i_1d(ji)  + zdum )
323            dh_i_sub(ji)   = dh_i_sub(ji) + zdum
324
325            ! update heat content (J.m-2) and layer thickness
326            eh_i_old(ji,jk) = eh_i_old(ji,jk) + zdum * e_i_1d(ji,jk)
327            h_i_old (ji,jk) = h_i_old (ji,jk) + zdum
328
329            ! record which layers have disappeared (for bottom melting)
330            !    => icount=0 : no layer has vanished
331            !    => icount=5 : 5 layers have vanished
332            rswitch       = MAX( 0._wp , SIGN( 1._wp , - zh_i(ji,jk) ) )
333            icount(ji,jk) = NINT( rswitch )
334
335         END DO
336      END DO
337
338      ! remaining "potential" evap is sent to ocean
339      DO ji = 1, npti
340         wfx_err_sub_1d(ji) = wfx_err_sub_1d(ji) - zevap_rema(ji) * a_i_1d(ji) * r1_Dt_ice  ! <=0 (net evap for the ocean in kg.m-2.s-1)
341      END DO
342
343
344      ! Ice Basal growth
345      !------------------
346      ! Basal growth is driven by heat imbalance at the ice-ocean interface,
347      ! between the inner conductive flux  (qcn_ice_bot), from the open water heat flux
348      ! (fhld) and the sensible ice-ocean flux (qsb_ice_bot).
349      ! qcn_ice_bot is positive downwards. qsb_ice_bot and fhld are positive to the ice
350
351      ! If salinity varies in time, an iterative procedure is required, because
352      ! the involved quantities are inter-dependent.
353      ! Basal growth (dh_i_bog) depends upon new ice specific enthalpy (zEi),
354      ! which depends on forming ice salinity (s_i_new), which depends on dh/dt (dh_i_bog)
355      ! -> need for an iterative procedure, which converges quickly
356
357      num_iter_max = 1
358      IF( nn_icesal == 2 )   num_iter_max = 5  ! salinity varying in time
359
360      DO ji = 1, npti
361         IF(  zf_tt(ji) < 0._wp  ) THEN
362            DO iter = 1, num_iter_max   ! iterations
363
364               ! New bottom ice salinity (Cox & Weeks, JGR88 )
365               !--- zswi1  if dh/dt < 2.0e-8
366               !--- zswi12 if 2.0e-8 < dh/dt < 3.6e-7
367               !--- zswi2  if dh/dt > 3.6e-7
368               zgrr     = MIN( 1.0e-3, MAX ( dh_i_bog(ji) * r1_Dt_ice , epsi10 ) )
369               zswi2    = MAX( 0._wp , SIGN( 1._wp , zgrr - 3.6e-7 ) )
370               zswi12   = MAX( 0._wp , SIGN( 1._wp , zgrr - 2.0e-8 ) ) * ( 1.0 - zswi2 )
371               zswi1    = 1. - zswi2 * zswi12
372               zfracs   = MIN( zswi1  * 0.12 + zswi12 * ( 0.8925 + 0.0568 * LOG( 100.0 * zgrr ) )   &
373                  &          + zswi2  * 0.26 / ( 0.26 + 0.74 * EXP ( - 724300.0 * zgrr ) )  , 0.5 )
374
375               s_i_new(ji)    = zswitch_sal * zfracs * sss_1d(ji) + ( 1. - zswitch_sal ) * s_i_1d(ji)  ! New ice salinity
376
377               ztmelts        = - rTmlt * s_i_new(ji)                                                  ! New ice melting point (C)
378
379               zt_i_new       = zswitch_sal * t_bo_1d(ji) + ( 1. - zswitch_sal) * t_i_1d(ji, nlay_i)
380
381               zEi            = rcpi * ( zt_i_new - (ztmelts+rt0) ) &                                  ! Specific enthalpy of forming ice (J/kg, <0)
382                  &             - rLfus * ( 1.0 - ztmelts / ( MIN( zt_i_new - rt0, -epsi10 ) ) ) + rcp * ztmelts
383
384               zEw            = rcp  * ( t_bo_1d(ji) - rt0 )                                           ! Specific enthalpy of seawater (J/kg, < 0)
385
386               zdE            = zEi - zEw                                                              ! Specific enthalpy difference (J/kg, <0)
387
388               dh_i_bog(ji)   = rDt_ice * MAX( 0._wp , zf_tt(ji) / ( zdE * rhoi ) )
389
390            END DO
391            ! Contribution to Energy and Salt Fluxes
392            zfmdt = - rhoi * dh_i_bog(ji)                                                              ! Mass flux x time step (kg/m2, < 0)
393
394            hfx_thd_1d(ji) = hfx_thd_1d(ji) + zEw  * zfmdt                      * a_i_1d(ji) * r1_Dt_ice   ! Heat flux to the ocean [W.m-2], >0
395            hfx_bog_1d(ji) = hfx_bog_1d(ji) - zdE  * zfmdt                      * a_i_1d(ji) * r1_Dt_ice   ! Heat flux used in this process [W.m-2], <0
396            wfx_bog_1d(ji) = wfx_bog_1d(ji) - rhoi * dh_i_bog(ji)               * a_i_1d(ji) * r1_Dt_ice   ! Mass flux, <0
397            sfx_bog_1d(ji) = sfx_bog_1d(ji) - rhoi * dh_i_bog(ji) * s_i_new(ji) * a_i_1d(ji) * r1_Dt_ice   ! Salt flux, <0
398
399            ! update thickness
400            zh_i(ji,nlay_i+1) = zh_i(ji,nlay_i+1) + dh_i_bog(ji)
401            h_i_1d(ji)        = h_i_1d(ji)        + dh_i_bog(ji)
402
403            ! update heat content (J.m-2) and layer thickness
404            eh_i_old(ji,nlay_i+1) = eh_i_old(ji,nlay_i+1) + dh_i_bog(ji) * (-zEi * rhoi)
405            h_i_old (ji,nlay_i+1) = h_i_old (ji,nlay_i+1) + dh_i_bog(ji)
406
407         ENDIF
408
409      END DO
410
411      ! Ice Basal melt
412      !---------------
413      DO jk = nlay_i, 1, -1
414         DO ji = 1, npti
415            IF(  zf_tt(ji)  >  0._wp  .AND. jk > icount(ji,jk) ) THEN   ! do not calculate where layer has already disappeared by surface melting
416
417               ztmelts = - rTmlt * sz_i_1d(ji,jk)  ! Melting point of layer jk (C)
418
419               IF( t_i_1d(ji,jk) >= (ztmelts+rt0) ) THEN   !-- Internal melting
420
421                  zEi            = - e_i_1d(ji,jk) * r1_rhoi     ! Specific enthalpy of melting ice (J/kg, <0)
422                  zdE            = 0._wp                         ! Specific enthalpy difference   (J/kg, <0)
423                  !                                                  set up at 0 since no energy is needed to melt water...(it is already melted)
424                  zdum           = MIN( 0._wp , - zh_i(ji,jk) )  ! internal melting occurs when the internal temperature is above freezing
425                  !                                                  this should normally not happen, but sometimes, heat diffusion leads to this
426                  dh_i_itm (ji)  = dh_i_itm(ji) + zdum
427                  !
428                  zfmdt          = - zdum * rhoi                 ! Mass flux x time step > 0
429                  !
430                  hfx_res_1d(ji) = hfx_res_1d(ji) + zEi  * zfmdt             * a_i_1d(ji) * r1_Dt_ice   ! Heat flux to the ocean [W.m-2], <0
431                  !                                                                                         ice enthalpy zEi is "sent" to the ocean
432                  wfx_res_1d(ji) = wfx_res_1d(ji) - rhoi * zdum              * a_i_1d(ji) * r1_Dt_ice   ! Mass flux
433                  sfx_res_1d(ji) = sfx_res_1d(ji) - rhoi * zdum * s_i_1d(ji) * a_i_1d(ji) * r1_Dt_ice   ! Salt flux
434                  !                                                                                         using s_i_1d and not sz_i_1d(jk) is ok
435               ELSE                                        !-- Basal melting
436
437                  zEi            = - e_i_1d(ji,jk) * r1_rhoi                       ! Specific enthalpy of melting ice (J/kg, <0)
438                  zEw            = rcp * ztmelts                                   ! Specific enthalpy of meltwater (J/kg, <0)
439                  zdE            = zEi - zEw                                       ! Specific enthalpy difference   (J/kg, <0)
440
441                  zfmdt          = - zq_bot(ji) / zdE                              ! Mass flux x time step (kg/m2, >0)
442
443                  zdum           = - zfmdt * r1_rhoi                               ! Gross thickness change
444
445                  zdum           = MIN( 0._wp , MAX( zdum, - zh_i(ji,jk) ) )       ! bound thickness change
446
447                  zq_bot(ji)     = MAX( 0._wp , zq_bot(ji) - zdum * rhoi * zdE )   ! update available heat. MAX is necessary for roundup errors
448
449                  dh_i_bom(ji)   = dh_i_bom(ji) + zdum                             ! Update basal melt
450
451                  zfmdt          = - zdum * rhoi                                   ! Mass flux x time step > 0
452
453                  zQm            = zfmdt * zEw                                     ! Heat exchanged with ocean
454
455                  hfx_thd_1d(ji) = hfx_thd_1d(ji) + zEw  * zfmdt             * a_i_1d(ji) * r1_Dt_ice   ! Heat flux to the ocean [W.m-2], <0
456                  hfx_bom_1d(ji) = hfx_bom_1d(ji) - zdE  * zfmdt             * a_i_1d(ji) * r1_Dt_ice   ! Heat used in this process [W.m-2], >0
457                  wfx_bom_1d(ji) = wfx_bom_1d(ji) - rhoi * zdum              * a_i_1d(ji) * r1_Dt_ice   ! Mass flux
458                  sfx_bom_1d(ji) = sfx_bom_1d(ji) - rhoi * zdum * s_i_1d(ji) * a_i_1d(ji) * r1_Dt_ice   ! Salt flux
459                  !                                                                                         using s_i_1d and not sz_i_1d(jk) is ok
460               ENDIF
461               ! update thickness
462               zh_i(ji,jk) = MAX( 0._wp, zh_i(ji,jk) + zdum )
463               h_i_1d(ji)  = MAX( 0._wp, h_i_1d(ji)  + zdum )
464               !
465               ! update heat content (J.m-2) and layer thickness
466               eh_i_old(ji,jk) = eh_i_old(ji,jk) + zdum * e_i_1d(ji,jk)
467               h_i_old (ji,jk) = h_i_old (ji,jk) + zdum
468            ENDIF
469         END DO
470      END DO
471
472      ! Remove snow if ice has melted entirely
473      ! --------------------------------------
474      DO jk = 0, nlay_s
475         DO ji = 1,npti
476            IF( h_i_1d(ji) == 0._wp ) THEN
477               ! mass & energy loss to the ocean
478               hfx_res_1d(ji) = hfx_res_1d(ji) - ze_s(ji,jk) * zh_s(ji,jk) * a_i_1d(ji) * r1_Dt_ice  ! heat flux to the ocean [W.m-2], < 0
479               wfx_res_1d(ji) = wfx_res_1d(ji) + rhos        * zh_s(ji,jk) * a_i_1d(ji) * r1_Dt_ice  ! mass flux
480
481               ! update thickness and energy
482               h_s_1d(ji)    = 0._wp
483               ze_s  (ji,jk) = 0._wp
484               zh_s  (ji,jk) = 0._wp
485            ENDIF
486         END DO
487      END DO
488
489      ! Snow load on ice
490      ! -----------------
491      ! When snow load exceeds Archimede's limit and sst is positive,
492      ! snow-ice formation (next bloc) can lead to negative ice enthalpy.
493      ! Therefore we consider here that this excess of snow falls into the ocean
494      zdeltah(1:npti) = h_s_1d(1:npti) + h_i_1d(1:npti) * (rhoi-rho0) * r1_rhos
495      DO jk = 0, nlay_s
496         DO ji = 1, npti
497            IF( zdeltah(ji) > 0._wp .AND. sst_1d(ji) > 0._wp ) THEN
498               ! snow layer thickness that falls into the ocean
499               zdum = MIN( zdeltah(ji) , zh_s(ji,jk) )
500               ! mass & energy loss to the ocean
501               hfx_res_1d(ji) = hfx_res_1d(ji) - ze_s(ji,jk) * zdum * a_i_1d(ji) * r1_Dt_ice  ! heat flux to the ocean [W.m-2], < 0
502               wfx_res_1d(ji) = wfx_res_1d(ji) + rhos        * zdum * a_i_1d(ji) * r1_Dt_ice  ! mass flux
503               ! update thickness and energy
504               h_s_1d(ji)    = MAX( 0._wp, h_s_1d(ji)  - zdum )
505               zh_s  (ji,jk) = MAX( 0._wp, zh_s(ji,jk) - zdum )
506               ! update snow thickness that still has to fall
507               zdeltah(ji)   = MAX( 0._wp, zdeltah(ji) - zdum )
508            ENDIF
509         END DO
510      END DO
511
512      ! Snow-Ice formation
513      ! ------------------
514      ! When snow load exceeds Archimede's limit, snow-ice interface goes down under sea-level,
515      ! flooding of seawater transforms snow into ice. Thickness that is transformed is dh_snowice (positive for the ice)
516      z1_rho = 1._wp / ( rhos+rho0-rhoi )
517      zdeltah(1:npti) = 0._wp
518      DO ji = 1, npti
519         !
520         dh_snowice(ji) = MAX( 0._wp , ( rhos * h_s_1d(ji) + (rhoi-rho0) * h_i_1d(ji) ) * z1_rho )
521
522         h_i_1d(ji)    = h_i_1d(ji) + dh_snowice(ji)
523         h_s_1d(ji)    = h_s_1d(ji) - dh_snowice(ji)
524
525         ! Contribution to energy flux to the ocean [J/m2], >0 (if sst<0)
526         zfmdt          = ( rhos - rhoi ) * dh_snowice(ji)    ! <0
527         zEw            = rcp * sst_1d(ji)
528         zQm            = zfmdt * zEw
529
530         hfx_thd_1d(ji) = hfx_thd_1d(ji) + zEw        * zfmdt * a_i_1d(ji) * r1_Dt_ice ! Heat flux
531         sfx_sni_1d(ji) = sfx_sni_1d(ji) + sss_1d(ji) * zfmdt * a_i_1d(ji) * r1_Dt_ice ! Salt flux
532
533         ! Case constant salinity in time: virtual salt flux to keep salinity constant
534         IF( nn_icesal /= 2 )  THEN
535            sfx_bri_1d(ji) = sfx_bri_1d(ji) - sss_1d(ji) * zfmdt                 * a_i_1d(ji) * r1_Dt_ice  &  ! put back sss_m     into the ocean
536               &                            - s_i_1d(ji) * dh_snowice(ji) * rhoi * a_i_1d(ji) * r1_Dt_ice     ! and get  rn_icesal from the ocean
537         ENDIF
538
539         ! Mass flux: All snow is thrown in the ocean, and seawater is taken to replace the volume
540         wfx_sni_1d    (ji) = wfx_sni_1d    (ji) - dh_snowice(ji) * rhoi * a_i_1d(ji) * r1_Dt_ice
541         wfx_snw_sni_1d(ji) = wfx_snw_sni_1d(ji) + dh_snowice(ji) * rhos * a_i_1d(ji) * r1_Dt_ice
542
543         ! update thickness
544         zh_i(ji,0)  = zh_i(ji,0) + dh_snowice(ji)
545         zdeltah(ji) =              dh_snowice(ji)
546
547         ! update heat content (J.m-2) and layer thickness
548         h_i_old (ji,0) = h_i_old (ji,0) + dh_snowice(ji)
549         eh_i_old(ji,0) = eh_i_old(ji,0) + zfmdt * zEw           ! 1st part (sea water enthalpy)
550
551      END DO
552      !
553      DO jk = nlay_s, 0, -1   ! flooding of snow starts from the base
554         DO ji = 1, npti
555            zdum           = MIN( zdeltah(ji), zh_s(ji,jk) )     ! amount of snw that floods, > 0
556            zh_s(ji,jk)    = MAX( 0._wp, zh_s(ji,jk) - zdum )    ! remove some snow thickness
557            eh_i_old(ji,0) = eh_i_old(ji,0) + zdum * ze_s(ji,jk) ! 2nd part (snow enthalpy)
558            ! update dh_snowice
559            zdeltah(ji)    = MAX( 0._wp, zdeltah(ji) - zdum )
560         END DO
561      END DO
562      !
563      !
564!!$      ! --- Update snow diags --- !
565!!$      !!clem: this is wrong. dh_s_tot is not used anyway
566!!$      DO ji = 1, npti
567!!$         dh_s_tot(ji) = dh_s_tot(ji) + dh_s_mlt(ji) + zdeltah(ji) + zdh_s_sub(ji) - dh_snowice(ji)
568!!$      END DO
569      !
570      !
571      ! Remapping of snw enthalpy on a regular grid
572      !--------------------------------------------
573      CALL snw_ent( zh_s, ze_s, e_s_1d )
574
575      ! recalculate t_s_1d from e_s_1d
576      DO jk = 1, nlay_s
577         DO ji = 1,npti
578            IF( h_s_1d(ji) > 0._wp ) THEN
579               t_s_1d(ji,jk) = rt0 + ( - e_s_1d(ji,jk) * r1_rhos * r1_rcpi + rLfus * r1_rcpi )
580            ELSE
581               t_s_1d(ji,jk) = rt0
582            ENDIF
583         END DO
584      END DO
585
586      ! Note: remapping of ice enthalpy is done in icethd.F90
587
588      ! --- ensure that a_i = 0 & h_s = 0 where h_i = 0 ---
589      WHERE( h_i_1d(1:npti) == 0._wp )
590         a_i_1d (1:npti) = 0._wp
591         h_s_1d (1:npti) = 0._wp
592         t_su_1d(1:npti) = rt0
593      END WHERE
594
595   END SUBROUTINE ice_thd_dh
596
597   SUBROUTINE snw_ent( ph_old, pe_old, pe_new )
598      !!-------------------------------------------------------------------
599      !!               ***   ROUTINE snw_ent  ***
600      !!
601      !! ** Purpose :
602      !!           This routine computes new vertical grids in the snow,
603      !!           and consistently redistributes temperatures.
604      !!           Redistribution is made so as to ensure to energy conservation
605      !!
606      !!
607      !! ** Method  : linear conservative remapping
608      !!
609      !! ** Steps : 1) cumulative integrals of old enthalpies/thicknesses
610      !!            2) linear remapping on the new layers
611      !!
612      !! ------------ cum0(0)                        ------------- cum1(0)
613      !!                                    NEW      -------------
614      !! ------------ cum0(1)               ==>      -------------
615      !!     ...                                     -------------
616      !! ------------                                -------------
617      !! ------------ cum0(nlay_s+1)                 ------------- cum1(nlay_s)
618      !!
619      !!
620      !! References : Bitz & Lipscomb, JGR 99; Vancoppenolle et al., GRL, 2005
621      !!-------------------------------------------------------------------
622      REAL(wp), DIMENSION(jpij,0:nlay_s), INTENT(in   ) ::   ph_old             ! old thicknesses (m)
623      REAL(wp), DIMENSION(jpij,0:nlay_s), INTENT(in   ) ::   pe_old             ! old enthlapies (J.m-3)
624      REAL(wp), DIMENSION(jpij,1:nlay_s), INTENT(inout) ::   pe_new             ! new enthlapies (J.m-3, remapped)
625      !
626      INTEGER  :: ji         !  dummy loop indices
627      INTEGER  :: jk0, jk1   !  old/new layer indices
628      !
629      REAL(wp), DIMENSION(jpij,0:nlay_s+1) ::   zeh_cum0, zh_cum0   ! old cumulative enthlapies and layers interfaces
630      REAL(wp), DIMENSION(jpij,0:nlay_s)   ::   zeh_cum1, zh_cum1   ! new cumulative enthlapies and layers interfaces
631      REAL(wp), DIMENSION(jpij)            ::   zhnew               ! new layers thicknesses
632      !!-------------------------------------------------------------------
633
634      !--------------------------------------------------------------------------
635      !  1) Cumulative integral of old enthalpy * thickness and layers interfaces
636      !--------------------------------------------------------------------------
637      zeh_cum0(1:npti,0) = 0._wp
638      zh_cum0 (1:npti,0) = 0._wp
639      DO jk0 = 1, nlay_s+1
640         DO ji = 1, npti
641            zeh_cum0(ji,jk0) = zeh_cum0(ji,jk0-1) + pe_old(ji,jk0-1) * ph_old(ji,jk0-1)
642            zh_cum0 (ji,jk0) = zh_cum0 (ji,jk0-1) + ph_old(ji,jk0-1)
643         END DO
644      END DO
645
646      !------------------------------------
647      !  2) Interpolation on the new layers
648      !------------------------------------
649      ! new layer thickesses
650      DO ji = 1, npti
651         zhnew(ji) = SUM( ph_old(ji,0:nlay_s) ) * r1_nlay_s
652      END DO
653
654      ! new layers interfaces
655      zh_cum1(1:npti,0) = 0._wp
656      DO jk1 = 1, nlay_s
657         DO ji = 1, npti
658            zh_cum1(ji,jk1) = zh_cum1(ji,jk1-1) + zhnew(ji)
659         END DO
660      END DO
661
662      zeh_cum1(1:npti,0:nlay_s) = 0._wp
663      ! new cumulative q*h => linear interpolation
664      DO jk0 = 1, nlay_s+1
665         DO jk1 = 1, nlay_s-1
666            DO ji = 1, npti
667               IF( zh_cum1(ji,jk1) <= zh_cum0(ji,jk0) .AND. zh_cum1(ji,jk1) > zh_cum0(ji,jk0-1) ) THEN
668                  zeh_cum1(ji,jk1) = ( zeh_cum0(ji,jk0-1) * ( zh_cum0(ji,jk0) - zh_cum1(ji,jk1  ) ) +  &
669                     &                 zeh_cum0(ji,jk0  ) * ( zh_cum1(ji,jk1) - zh_cum0(ji,jk0-1) ) )  &
670                     &             / ( zh_cum0(ji,jk0) - zh_cum0(ji,jk0-1) )
671               ENDIF
672            END DO
673         END DO
674      END DO
675      ! to ensure that total heat content is strictly conserved, set:
676      zeh_cum1(1:npti,nlay_s) = zeh_cum0(1:npti,nlay_s+1)
677
678      ! new enthalpies
679      DO jk1 = 1, nlay_s
680         DO ji = 1, npti
681            rswitch      = MAX( 0._wp , SIGN( 1._wp , zhnew(ji) - epsi20 ) )
682            pe_new(ji,jk1) = rswitch * ( zeh_cum1(ji,jk1) - zeh_cum1(ji,jk1-1) ) / MAX( zhnew(ji), epsi20 )
683         END DO
684      END DO
685
686   END SUBROUTINE snw_ent
687
688
689#else
690   !!----------------------------------------------------------------------
691   !!   Default option                                NO SI3 sea-ice model
692   !!----------------------------------------------------------------------
693#endif
694
695   !!======================================================================
696END MODULE icethd_dh
Note: See TracBrowser for help on using the repository browser.