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/releases/r4.0/r4.0-HEAD/src/ICE – NEMO

source: NEMO/releases/r4.0/r4.0-HEAD/src/ICE/icethd_dh.F90

Last change on this file was 15814, checked in by clem, 6 months ago

authorized snow-ice formation eventhough SST is above 0deg. Snow was supposed to melt when temperature is above 0deg but it is actually a bug, and we should let snow-ice formation to occur

  • Property svn:keywords set to Id
File size: 35.1 KB
RevLine 
[8586]1MODULE icethd_dh
2   !!======================================================================
3   !!                       ***  MODULE icethd_dh ***
4   !!   seaice : thermodynamic growth and melt
5   !!======================================================================
[9604]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]
[8586]9   !!----------------------------------------------------------------------
[9570]10#if defined key_si3
[8586]11   !!----------------------------------------------------------------------
[9570]12   !!   'key_si3'                                       SI3 sea-ice model
[8586]13   !!----------------------------------------------------------------------
14   !!   ice_thd_dh        : vertical sea-ice growth and melt
[13284]15   !!----------------------------------------------------------------------
[8586]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
[13284]21   USE icevar         ! for CALL ice_var_snwblow
[8586]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   !!----------------------------------------------------------------------
[9598]33   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
[10069]34   !! $Id$
[10068]35   !! Software governed by the CeCILL license (see ./LICENSE)
[8586]36   !!----------------------------------------------------------------------
37CONTAINS
38
39   SUBROUTINE ice_thd_dh
40      !!------------------------------------------------------------------
41      !!                ***  ROUTINE ice_thd_dh  ***
42      !!
[9274]43      !! ** Purpose :   compute ice and snow thickness changes due to growth/melting
[8586]44      !!
45      !! ** Method  :   Ice/Snow surface melting arises from imbalance in surface fluxes
[9274]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
[8586]50      !!
[9274]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
[8586]56      !!
[14026]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      !!
[8586]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
[9935]76      REAL(wp) ::   z1_rho       ! 1/(rhos+rau0-rhoi)
[8586]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
[9922]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)
[8586]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)
[14026]89      REAL(wp), DIMENSION(jpij) ::   zdeltah     
90      REAL(wp), DIMENSION(jpij) ::   zsnw        ! distribution of snow after wind blowing
[8586]91
[14026]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)
[8586]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
[14026]108      ! initialize ice layer thicknesses and enthalpies
109      eh_i_old(1:npti,0:nlay_i+1) = 0._wp
[8586]110      h_i_old (1:npti,0:nlay_i+1) = 0._wp
[14026]111      zh_i    (1:npti,0:nlay_i+1) = 0._wp
[8586]112      DO jk = 1, nlay_i
113         DO ji = 1, npti
[14026]114            eh_i_old(ji,jk) = h_i_1d(ji) * r1_nlay_i * e_i_1d(ji,jk)
[8586]115            h_i_old (ji,jk) = h_i_1d(ji) * r1_nlay_i
[14026]116            zh_i    (ji,jk) = h_i_1d(ji) * r1_nlay_i
[8586]117         END DO
118      END DO
119      !
[14026]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      !
[9604]130      !                       ! ============================================== !
131      !                       ! Available heat for surface and bottom ablation !
132      !                       ! ============================================== !
[8813]133      !
[10534]134      IF( ln_cndflx .AND. .NOT.ln_cndemulate ) THEN
[8813]135         !
136         DO ji = 1, npti
[9922]137            zq_top(ji)     = MAX( 0._wp, qml_ice_1d(ji) * rdt_ice )
[8813]138         END DO
139         !
[10534]140      ELSE
[8813]141         !
142         DO ji = 1, npti
[9916]143            zdum           = qns_ice_1d(ji) + qsr_ice_1d(ji) - qtr_ice_top_1d(ji) - qcn_ice_top_1d(ji)
[9274]144            qml_ice_1d(ji) = zdum * MAX( 0._wp , SIGN( 1._wp, t_su_1d(ji) - rt0 ) )
[9922]145            zq_top(ji)     = MAX( 0._wp, qml_ice_1d(ji) * rdt_ice )
[8813]146         END DO
147         !
[10534]148      ENDIF
[8813]149      !
[8586]150      DO ji = 1, npti
[13642]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) 
[9922]152         zq_bot(ji)        = MAX( 0._wp, zf_tt(ji) * rdt_ice )
[8586]153      END DO
154
[9274]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)
[9271]162      DO jk = 1, nlay_s
[8586]163         DO ji = 1, npti
[9274]164            IF( t_s_1d(ji,jk) > rt0 ) THEN
[14026]165               hfx_res_1d    (ji) = hfx_res_1d    (ji) - ze_s(ji,jk) * zh_s(ji,jk) * a_i_1d(ji) * r1_rdtice   ! 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_rdtice   ! mass flux
[9271]167               ! updates
[14026]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) )
[9274]170               zh_s    (ji,jk) = 0._wp
[14026]171               ze_s    (ji,jk) = 0._wp
[9271]172            END IF
[8586]173         END DO
[9274]174      END DO         
[8586]175
[9274]176      ! Snow precipitation
177      !-------------------
[14026]178      CALL ice_var_snwblow( 1._wp - at_i_1d(1:npti), zsnw(1:npti) )   ! snow distribution over ice after wind blowing
[8586]179
180      DO ji = 1, npti
[9274]181         IF( sprecip_1d(ji) > 0._wp ) THEN
[14026]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)
[9274]184            !
[14026]185            hfx_spr_1d(ji) = hfx_spr_1d(ji) + ze_s(ji,0) * zh_s(ji,0) * a_i_1d(ji) * r1_rdtice   ! 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_rdtice   ! mass flux, <0
[9274]187            !
188            ! update thickness
[14026]189            h_s_1d(ji) = h_s_1d(ji) + zh_s(ji,0)
[9274]190         ENDIF
[8586]191      END DO
192
[9274]193      ! Snow melting
194      ! ------------
[14026]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
[8586]198         DO ji = 1, npti
[9922]199            IF( zh_s(ji,jk) > 0._wp .AND. zq_top(ji) > 0._wp ) THEN
[9274]200               !
[14026]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
[9274]204               
[14026]205               hfx_snw_1d    (ji) = hfx_snw_1d    (ji) - ze_s(ji,jk) * zdum * a_i_1d(ji) * r1_rdtice   ! 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_rdtice   ! snow melting only = water into the ocean
[9274]207               
208               ! updates available heat + thickness
[14026]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
[9274]214               !
215            ENDIF
[8586]216         END DO
217      END DO
218
[9274]219      ! Snow sublimation
220      !-----------------
[8586]221      ! qla_ice is always >=0 (upwards), heat goes to the atmosphere, therefore snow sublimates
[8885]222      !    comment: not counted in mass/heat exchange in iceupdate.F90 since this is an exchange with atm. (not ocean)
[14026]223      zdeltah   (1:npti) = 0._wp ! total snow thickness that sublimates, < 0
224      zevap_rema(1:npti) = 0._wp
[8586]225      DO ji = 1, npti
[14685]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)
[8586]228      END DO
229     
[14026]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_rdtice  ! 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_rdtice  ! Mass flux by sublimation
[8586]236
[14026]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 )
[8586]244         END DO
245      END DO
[14026]246
247      !     
[9274]248      !                       ! ============ !
249      !                       !     Ice      !
250      !                       ! ============ !
[8586]251
[9274]252      ! Surface ice melting
253      !--------------------
[8586]254      DO jk = 1, nlay_i
255         DO ji = 1, npti
[9935]256            ztmelts = - rTmlt * sz_i_1d(ji,jk)   ! Melting point of layer k [C]
[8586]257           
[9274]258            IF( t_i_1d(ji,jk) >= (ztmelts+rt0) ) THEN   !-- Internal melting
[8586]259
[9935]260               zEi            = - e_i_1d(ji,jk) * r1_rhoi             ! Specific enthalpy of layer k [J/kg, <0]       
[14026]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_rdtice    ! 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_rdtice    ! Mass flux
272               sfx_res_1d(ji) = sfx_res_1d(ji) - rhoi * zdum * s_i_1d(ji) * a_i_1d(ji) * r1_rdtice    ! Salt flux
273               !                                                                                          using s_i_1d and not sz_i_1d(jk) is ok
[9274]274            ELSE                                        !-- Surface melting
[8586]275               
[9935]276               zEi            = - e_i_1d(ji,jk) * r1_rhoi             ! Specific enthalpy of layer k [J/kg, <0]
[8586]277               zEw            =    rcp * ztmelts                      ! Specific enthalpy of resulting meltwater [J/kg, <0]
278               zdE            =    zEi - zEw                          ! Specific enthalpy difference < 0
279               
[9922]280               zfmdt          = - zq_top(ji) / zdE                    ! Mass flux to the ocean [kg/m2, >0]
[8586]281               
[14026]282               zdum           = - zfmdt * r1_rhoi                     ! Melt of layer jk [m, <0]
[8586]283               
[14026]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
[8586]287               
[14026]288               dh_i_sum(ji)   = dh_i_sum(ji) + zdum                   ! Cumulate surface melt
[8586]289               
[14026]290               zfmdt          = - rhoi * zdum                         ! Recompute mass flux [kg/m2, >0]
[8586]291               
292               zQm            = zfmdt * zEw                           ! Energy of the melt water sent to the ocean [J/m2, <0]
293               
[14026]294               hfx_thd_1d(ji) = hfx_thd_1d(ji) + zEw  * zfmdt             * a_i_1d(ji) * r1_rdtice    ! Heat flux [W.m-2], < 0
295               hfx_sum_1d(ji) = hfx_sum_1d(ji) - zdE  * zfmdt             * a_i_1d(ji) * r1_rdtice    ! 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_rdtice    ! Mass flux
297               sfx_sum_1d(ji) = sfx_sum_1d(ji) - rhoi * zdum * s_i_1d(ji) * a_i_1d(ji) * r1_rdtice    ! Salt flux >0
298               !                                                                                          using s_i_1d and not sz_i_1d(jk) is ok)
[8586]299            END IF
[14026]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            !
[9274]309            ! Ice sublimation
310            ! ---------------
[14026]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_rdtice ! Heat flux [W.m-2], < 0
314            wfx_ice_sub_1d(ji) = wfx_ice_sub_1d(ji) - rhoi          * zdum              * a_i_1d(ji) * r1_rdtice ! Mass flux > 0
315            sfx_sub_1d(ji)     = sfx_sub_1d(ji)     - rhoi          * zdum * s_i_1d(ji) * a_i_1d(ji) * r1_rdtice ! 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
[8586]324
[14026]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
[9274]328
[8586]329            ! record which layers have disappeared (for bottom melting)
330            !    => icount=0 : no layer has vanished
331            !    => icount=5 : 5 layers have vanished
[14026]332            rswitch       = MAX( 0._wp , SIGN( 1._wp , - zh_i(ji,jk) ) ) 
[8586]333            icount(ji,jk) = NINT( rswitch )
334                       
335         END DO
336      END DO
[9274]337     
[8586]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_rdtice  ! <=0 (net evap for the ocean in kg.m-2.s-1)
341      END DO
342
343
[9274]344      ! Ice Basal growth
[8586]345      !------------------
346      ! Basal growth is driven by heat imbalance at the ice-ocean interface,
[9916]347      ! between the inner conductive flux  (qcn_ice_bot), from the open water heat flux
[9913]348      ! (fhld) and the sensible ice-ocean flux (qsb_ice_bot).
[9916]349      ! qcn_ice_bot is positive downwards. qsb_ice_bot and fhld are positive to the ice
[8586]350
351      ! If salinity varies in time, an iterative procedure is required, because
352      ! the involved quantities are inter-dependent.
[9750]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)
[8586]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
[9274]362            DO iter = 1, num_iter_max   ! iterations
[8586]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
[9750]368               zgrr     = MIN( 1.0e-3, MAX ( dh_i_bog(ji) * r1_rdtice , epsi10 ) )
[9274]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 )
[8586]374
[14026]375               s_i_new(ji)    = zswitch_sal * zfracs * sss_1d(ji) + ( 1. - zswitch_sal ) * s_i_1d(ji)  ! New ice salinity
[8586]376
[14026]377               ztmelts        = - rTmlt * s_i_new(ji)                                                  ! New ice melting point (C)
[9274]378
[14026]379               zt_i_new       = zswitch_sal * t_bo_1d(ji) + ( 1. - zswitch_sal) * t_i_1d(ji, nlay_i)
[8586]380               
[14026]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
[8586]383
[14026]384               zEw            = rcp  * ( t_bo_1d(ji) - rt0 )                                           ! Specific enthalpy of seawater (J/kg, < 0)
[8586]385
[14026]386               zdE            = zEi - zEw                                                              ! Specific enthalpy difference (J/kg, <0)
[8586]387
[14026]388               dh_i_bog(ji)   = rdt_ice * MAX( 0._wp , zf_tt(ji) / ( zdE * rhoi ) )
[8586]389               
390            END DO
391            ! Contribution to Energy and Salt Fluxes                                   
[14026]392            zfmdt = - rhoi * dh_i_bog(ji)                                                              ! Mass flux x time step (kg/m2, < 0)
[8586]393           
[14026]394            hfx_thd_1d(ji) = hfx_thd_1d(ji) + zEw  * zfmdt                      * a_i_1d(ji) * r1_rdtice   ! 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_rdtice   ! 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_rdtice   ! 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_rdtice   ! Salt flux, <0
[8586]398
[14026]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)
[8586]402
403            ! update heat content (J.m-2) and layer thickness
[9935]404            eh_i_old(ji,nlay_i+1) = eh_i_old(ji,nlay_i+1) + dh_i_bog(ji) * (-zEi * rhoi)
[9750]405            h_i_old (ji,nlay_i+1) = h_i_old (ji,nlay_i+1) + dh_i_bog(ji)
[8586]406
407         ENDIF
408
409      END DO
410
[9274]411      ! Ice Basal melt
412      !---------------
[8586]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
[9935]417               ztmelts = - rTmlt * sz_i_1d(ji,jk)  ! Melting point of layer jk (C)
[8586]418
[9274]419               IF( t_i_1d(ji,jk) >= (ztmelts+rt0) ) THEN   !-- Internal melting
[8586]420
[14026]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_rdtice   ! 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_rdtice   ! Mass flux
433                  sfx_res_1d(ji) = sfx_res_1d(ji) - rhoi * zdum * s_i_1d(ji) * a_i_1d(ji) * r1_rdtice   ! Salt flux
434                  !                                                                                         using s_i_1d and not sz_i_1d(jk) is ok
[9274]435               ELSE                                        !-- Basal melting
[8586]436
[14026]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)
[8586]440
[14026]441                  zfmdt          = - zq_bot(ji) / zdE                              ! Mass flux x time step (kg/m2, >0)
[8586]442
[14026]443                  zdum           = - zfmdt * r1_rhoi                               ! Gross thickness change
[8586]444
[14026]445                  zdum           = MIN( 0._wp , MAX( zdum, - zh_i(ji,jk) ) )       ! bound thickness change
[8586]446                 
[14026]447                  zq_bot(ji)     = MAX( 0._wp , zq_bot(ji) - zdum * rhoi * zdE )   ! update available heat. MAX is necessary for roundup errors
[8586]448
[14026]449                  dh_i_bom(ji)   = dh_i_bom(ji) + zdum                             ! Update basal melt
[8586]450
[14026]451                  zfmdt          = - zdum * rhoi                                   ! Mass flux x time step > 0
[8586]452
[14026]453                  zQm            = zfmdt * zEw                                     ! Heat exchanged with ocean
[8586]454
[14026]455                  hfx_thd_1d(ji) = hfx_thd_1d(ji) + zEw  * zfmdt             * a_i_1d(ji) * r1_rdtice   ! 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_rdtice   ! 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_rdtice   ! Mass flux
458                  sfx_bom_1d(ji) = sfx_bom_1d(ji) - rhoi * zdum * s_i_1d(ji) * a_i_1d(ji) * r1_rdtice   ! Salt flux
459                  !                                                                                         using s_i_1d and not sz_i_1d(jk) is ok
[8586]460               ENDIF
[14026]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
[8586]468            ENDIF
469         END DO
470      END DO
471
[14026]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_rdtice  ! 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_rdtice  ! mass flux
[8586]480
[14026]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
[8586]487      END DO
[14026]488     
[9274]489      ! Snow-Ice formation
490      ! ------------------
[14026]491      ! When snow load exceeds Archimede's limit, snow-ice interface goes down under sea-level,
492      ! flooding of seawater transforms snow into ice. Thickness that is transformed is dh_snowice (positive for the ice)
[9935]493      z1_rho = 1._wp / ( rhos+rau0-rhoi )
[14026]494      zdeltah(1:npti) = 0._wp
[8586]495      DO ji = 1, npti
496         !
[14026]497         dh_snowice(ji) = MAX( 0._wp , ( rhos * h_s_1d(ji) + (rhoi-rau0) * h_i_1d(ji) ) * z1_rho )
[8586]498
499         h_i_1d(ji)    = h_i_1d(ji) + dh_snowice(ji)
500         h_s_1d(ji)    = h_s_1d(ji) - dh_snowice(ji)
501
502         ! Contribution to energy flux to the ocean [J/m2], >0 (if sst<0)
[9935]503         zfmdt          = ( rhos - rhoi ) * dh_snowice(ji)    ! <0
[8586]504         zEw            = rcp * sst_1d(ji)
505         zQm            = zfmdt * zEw 
506         
[14026]507         hfx_thd_1d(ji) = hfx_thd_1d(ji) + zEw        * zfmdt * a_i_1d(ji) * r1_rdtice ! Heat flux
508         sfx_sni_1d(ji) = sfx_sni_1d(ji) + sss_1d(ji) * zfmdt * a_i_1d(ji) * r1_rdtice ! Salt flux
[8586]509
510         ! Case constant salinity in time: virtual salt flux to keep salinity constant
[8637]511         IF( nn_icesal /= 2 )  THEN
[14026]512            sfx_bri_1d(ji) = sfx_bri_1d(ji) - sss_1d(ji) * zfmdt                 * a_i_1d(ji) * r1_rdtice  &  ! put back sss_m     into the ocean
513               &                            - s_i_1d(ji) * dh_snowice(ji) * rhoi * a_i_1d(ji) * r1_rdtice     ! and get  rn_icesal from the ocean
[8586]514         ENDIF
515
[9274]516         ! Mass flux: All snow is thrown in the ocean, and seawater is taken to replace the volume
[14026]517         wfx_sni_1d    (ji) = wfx_sni_1d    (ji) - dh_snowice(ji) * rhoi * a_i_1d(ji) * r1_rdtice
518         wfx_snw_sni_1d(ji) = wfx_snw_sni_1d(ji) + dh_snowice(ji) * rhos * a_i_1d(ji) * r1_rdtice
[8586]519
[14026]520         ! update thickness
521         zh_i(ji,0)  = zh_i(ji,0) + dh_snowice(ji)
522         zdeltah(ji) =              dh_snowice(ji)
523
[8586]524         ! update heat content (J.m-2) and layer thickness
525         h_i_old (ji,0) = h_i_old (ji,0) + dh_snowice(ji)
[14026]526         eh_i_old(ji,0) = eh_i_old(ji,0) + zfmdt * zEw           ! 1st part (sea water enthalpy)
527
[8586]528      END DO
529      !
[14026]530      DO jk = nlay_s, 0, -1   ! flooding of snow starts from the base
531         DO ji = 1, npti
532            zdum           = MIN( zdeltah(ji), zh_s(ji,jk) )     ! amount of snw that floods, > 0
533            zh_s(ji,jk)    = MAX( 0._wp, zh_s(ji,jk) - zdum )    ! remove some snow thickness
534            eh_i_old(ji,0) = eh_i_old(ji,0) + zdum * ze_s(ji,jk) ! 2nd part (snow enthalpy)
535            ! update dh_snowice
536            zdeltah(ji)    = MAX( 0._wp, zdeltah(ji) - zdum )
537         END DO
[8586]538      END DO
[14026]539      !
540      !
541!!$      ! --- Update snow diags --- !
542!!$      !!clem: this is wrong. dh_s_tot is not used anyway
543!!$      DO ji = 1, npti
544!!$         dh_s_tot(ji) = dh_s_tot(ji) + dh_s_mlt(ji) + zdeltah(ji) + zdh_s_sub(ji) - dh_snowice(ji)
545!!$      END DO
546      !
547      !
548      ! Remapping of snw enthalpy on a regular grid
549      !--------------------------------------------
550      CALL snw_ent( zh_s, ze_s, e_s_1d )
551     
552      ! recalculate t_s_1d from e_s_1d
[8586]553      DO jk = 1, nlay_s
554         DO ji = 1,npti
[14026]555            IF( h_s_1d(ji) > 0._wp ) THEN
556               t_s_1d(ji,jk) = rt0 + ( - e_s_1d(ji,jk) * r1_rhos * r1_rcpi + rLfus * r1_rcpi )
557            ELSE
558               t_s_1d(ji,jk) = rt0
559            ENDIF
[8586]560         END DO
561      END DO
562
[14026]563      ! Note: remapping of ice enthalpy is done in icethd.F90
564
[10786]565      ! --- ensure that a_i = 0 & h_s = 0 where h_i = 0 ---
566      WHERE( h_i_1d(1:npti) == 0._wp )   
[14026]567         a_i_1d (1:npti) = 0._wp
568         h_s_1d (1:npti) = 0._wp
569         t_su_1d(1:npti) = rt0
[10786]570      END WHERE
[14026]571     
[8586]572   END SUBROUTINE ice_thd_dh
573
[14026]574   SUBROUTINE snw_ent( ph_old, pe_old, pe_new )
575      !!-------------------------------------------------------------------
576      !!               ***   ROUTINE snw_ent  ***
577      !!
578      !! ** Purpose :
579      !!           This routine computes new vertical grids in the snow,
580      !!           and consistently redistributes temperatures.
581      !!           Redistribution is made so as to ensure to energy conservation
582      !!
583      !!
584      !! ** Method  : linear conservative remapping
585      !!           
586      !! ** Steps : 1) cumulative integrals of old enthalpies/thicknesses
587      !!            2) linear remapping on the new layers
588      !!
589      !! ------------ cum0(0)                        ------------- cum1(0)
590      !!                                    NEW      -------------
591      !! ------------ cum0(1)               ==>      -------------
592      !!     ...                                     -------------
593      !! ------------                                -------------
594      !! ------------ cum0(nlay_s+1)                 ------------- cum1(nlay_s)
595      !!
596      !!
597      !! References : Bitz & Lipscomb, JGR 99; Vancoppenolle et al., GRL, 2005
598      !!-------------------------------------------------------------------
599      REAL(wp), DIMENSION(jpij,0:nlay_s), INTENT(in   ) ::   ph_old             ! old thicknesses (m)
600      REAL(wp), DIMENSION(jpij,0:nlay_s), INTENT(in   ) ::   pe_old             ! old enthlapies (J.m-3)
601      REAL(wp), DIMENSION(jpij,1:nlay_s), INTENT(inout) ::   pe_new             ! new enthlapies (J.m-3, remapped)
602      !
603      INTEGER  :: ji         !  dummy loop indices
604      INTEGER  :: jk0, jk1   !  old/new layer indices
605      !
606      REAL(wp), DIMENSION(jpij,0:nlay_s+1) ::   zeh_cum0, zh_cum0   ! old cumulative enthlapies and layers interfaces
607      REAL(wp), DIMENSION(jpij,0:nlay_s)   ::   zeh_cum1, zh_cum1   ! new cumulative enthlapies and layers interfaces
608      REAL(wp), DIMENSION(jpij)            ::   zhnew               ! new layers thicknesses
609      !!-------------------------------------------------------------------
610
611      !--------------------------------------------------------------------------
612      !  1) Cumulative integral of old enthalpy * thickness and layers interfaces
613      !--------------------------------------------------------------------------
614      zeh_cum0(1:npti,0) = 0._wp 
615      zh_cum0 (1:npti,0) = 0._wp
616      DO jk0 = 1, nlay_s+1
617         DO ji = 1, npti
618            zeh_cum0(ji,jk0) = zeh_cum0(ji,jk0-1) + pe_old(ji,jk0-1) * ph_old(ji,jk0-1)
619            zh_cum0 (ji,jk0) = zh_cum0 (ji,jk0-1) + ph_old(ji,jk0-1)
620         END DO
621      END DO
622
623      !------------------------------------
624      !  2) Interpolation on the new layers
625      !------------------------------------
626      ! new layer thickesses
627      DO ji = 1, npti
628         zhnew(ji) = SUM( ph_old(ji,0:nlay_s) ) * r1_nlay_s 
629      END DO
630
631      ! new layers interfaces
632      zh_cum1(1:npti,0) = 0._wp
633      DO jk1 = 1, nlay_s
634         DO ji = 1, npti
635            zh_cum1(ji,jk1) = zh_cum1(ji,jk1-1) + zhnew(ji)
636         END DO
637      END DO
638
639      zeh_cum1(1:npti,0:nlay_s) = 0._wp 
640      ! new cumulative q*h => linear interpolation
641      DO jk0 = 1, nlay_s+1
642         DO jk1 = 1, nlay_s-1
643            DO ji = 1, npti
644               IF( zh_cum1(ji,jk1) <= zh_cum0(ji,jk0) .AND. zh_cum1(ji,jk1) > zh_cum0(ji,jk0-1) ) THEN
645                  zeh_cum1(ji,jk1) = ( zeh_cum0(ji,jk0-1) * ( zh_cum0(ji,jk0) - zh_cum1(ji,jk1  ) ) +  &
646                     &                 zeh_cum0(ji,jk0  ) * ( zh_cum1(ji,jk1) - zh_cum0(ji,jk0-1) ) )  &
647                     &             / ( zh_cum0(ji,jk0) - zh_cum0(ji,jk0-1) )
648               ENDIF
649            END DO
650         END DO
651      END DO
652      ! to ensure that total heat content is strictly conserved, set:
653      zeh_cum1(1:npti,nlay_s) = zeh_cum0(1:npti,nlay_s+1) 
654
655      ! new enthalpies
656      DO jk1 = 1, nlay_s
657         DO ji = 1, npti
658            rswitch      = MAX( 0._wp , SIGN( 1._wp , zhnew(ji) - epsi20 ) ) 
659            pe_new(ji,jk1) = rswitch * ( zeh_cum1(ji,jk1) - zeh_cum1(ji,jk1-1) ) / MAX( zhnew(ji), epsi20 )
660         END DO
661      END DO
662     
663   END SUBROUTINE snw_ent
664
665   
[8586]666#else
667   !!----------------------------------------------------------------------
[9570]668   !!   Default option                                NO SI3 sea-ice model
[8586]669   !!----------------------------------------------------------------------
670#endif
671
672   !!======================================================================
673END MODULE icethd_dh
Note: See TracBrowser for help on using the repository browser.