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 branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/icethd_dh.F90 @ 8522

Last change on this file since 8522 was 8522, checked in by clem, 7 years ago

changes in style - part6 - ice diffusion (hope the scheme still converges)

File size: 35.5 KB
Line 
1MODULE icethd_dh
2   !!======================================================================
3   !!                       ***  MODULE icethd_dh ***
4   !!  LIM-3 :   thermodynamic growth and decay of the ice
5   !!======================================================================
6   !! History :  LIM  ! 2003-05 (M. Vancoppenolle) Original code in 1D
7   !!                 ! 2005-06 (M. Vancoppenolle) 3D version
8   !!            3.2  ! 2009-07 (M. Vancoppenolle, Y. Aksenov, G. Madec) bug correction in wfx_snw & wfx_ice
9   !!            3.4  ! 2011-02 (G. Madec) dynamical allocation
10   !!            3.5  ! 2012-10 (G. Madec & co) salt flux + bug fixes
11   !!----------------------------------------------------------------------
12#if defined key_lim3
13   !!----------------------------------------------------------------------
14   !!   'key_lim3'                                       LIM3 sea-ice model
15   !!----------------------------------------------------------------------
16   !!   ice_thd_dh    : vertical accr./abl. and lateral ablation of sea ice
17   !!----------------------------------------------------------------------
18   USE par_oce        ! ocean parameters
19   USE phycst         ! physical constants (OCE directory)
20   USE ice            ! LIM variables
21   USE ice1D          ! LIM thermodynamics
22   USE icethd_sal     ! sea-ice: salinity profiles
23   !
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   
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   ice_thd_dh      ! called by ice_thd
32   PUBLIC   ice_thd_snwblow ! called in sbcblk/sbcclio/sbccpl and here
33
34   INTERFACE ice_thd_snwblow
35      MODULE PROCEDURE ice_thd_snwblow_1d, ice_thd_snwblow_2d
36   END INTERFACE
37
38   !!----------------------------------------------------------------------
39   !! NEMO/ICE 4.0 , NEMO Consortium (2017)
40   !! $Id: icethd_dh.F90 8420 2017-08-08 12:18:46Z clem $
41   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
42   !!----------------------------------------------------------------------
43CONTAINS
44
45   SUBROUTINE ice_thd_dh
46      !!------------------------------------------------------------------
47      !!                ***  ROUTINE ice_thd_dh  ***
48      !!
49      !! ** Purpose :   determines variations of ice and snow thicknesses.
50      !!
51      !! ** Method  :   Ice/Snow surface melting arises from imbalance in surface fluxes
52      !!              Bottom accretion/ablation arises from flux budget
53      !!              Snow thickness can increase by precipitation and decrease by sublimation
54      !!              If snow load excesses Archmiede limit, snow-ice is formed by
55      !!              the flooding of sea-water in the snow
56      !!
57      !!                 1) Compute available flux of heat for surface ablation
58      !!                 2) Compute snow and sea ice enthalpies
59      !!                 3) Surface ablation and sublimation
60      !!                 4) Bottom accretion/ablation
61      !!                 5) Case of Total ablation
62      !!                 6) Snow ice formation
63      !!
64      !! References : Bitz and Lipscomb, 1999, J. Geophys. Res.
65      !!              Fichefet T. and M. Maqueda 1997, J. Geophys. Res., 102(C6), 12609-12646   
66      !!              Vancoppenolle, Fichefet and Bitz, 2005, Geophys. Res. Let.
67      !!              Vancoppenolle et al.,2009, Ocean Modelling
68      !!------------------------------------------------------------------
69      INTEGER  ::   ji, jk       ! dummy loop indices
70      INTEGER  ::   iter         ! local integer
71
72      REAL(wp) ::   ztmelts      ! local scalar
73      REAL(wp) ::   zdum       
74      REAL(wp) ::   zfracs       ! fractionation coefficient for bottom salt entrapment
75      REAL(wp) ::   zswi1        ! switch for computation of bottom salinity
76      REAL(wp) ::   zswi12       ! switch for computation of bottom salinity
77      REAL(wp) ::   zswi2        ! switch for computation of bottom salinity
78      REAL(wp) ::   zgrr         ! bottom growth rate
79      REAL(wp) ::   zt_i_new     ! bottom formation temperature
80      REAL(wp) ::   z1_rho       ! 1/(rhosn+rau0-rhoic)
81
82      REAL(wp) ::   zQm          ! enthalpy exchanged with the ocean (J/m2), >0 towards the ocean
83      REAL(wp) ::   zEi          ! specific enthalpy of sea ice (J/kg)
84      REAL(wp) ::   zEw          ! specific enthalpy of exchanged water (J/kg)
85      REAL(wp) ::   zdE          ! specific enthalpy difference (J/kg)
86      REAL(wp) ::   zfmdt        ! exchange mass flux x time step (J/m2), >0 towards the ocean
87
88      REAL(wp), DIMENSION(jpij) ::   zqprec      ! energy of fallen snow                       (J.m-3)
89      REAL(wp), DIMENSION(jpij) ::   zq_su       ! heat for surface ablation                   (J.m-2)
90      REAL(wp), DIMENSION(jpij) ::   zq_bo       ! heat for bottom ablation                    (J.m-2)
91      REAL(wp), DIMENSION(jpij) ::   zq_rema     ! remaining heat at the end of the routine    (J.m-2)
92      REAL(wp), DIMENSION(jpij) ::   zf_tt       ! Heat budget to determine melting or freezing(W.m-2)
93      REAL(wp), DIMENSION(jpij) ::   zevap_rema  ! remaining mass flux from sublimation        (kg.m-2)
94
95      REAL(wp), DIMENSION(jpij) ::   zdh_s_mel   ! snow melt
96      REAL(wp), DIMENSION(jpij) ::   zdh_s_pre   ! snow precipitation
97      REAL(wp), DIMENSION(jpij) ::   zdh_s_sub   ! snow sublimation
98
99      REAL(wp), DIMENSION(jpij,nlay_i) ::   zdeltah
100      REAL(wp), DIMENSION(jpij,nlay_i) ::   zh_i      ! ice layer thickness
101      INTEGER , DIMENSION(jpij,nlay_i) ::   icount    ! number of layers vanished by melting
102
103      REAL(wp), DIMENSION(jpij) ::   zeh_i       ! total ice heat content  (J.m-2)
104      REAL(wp), DIMENSION(jpij) ::   zsnw        ! distribution of snow after wind blowing
105
106      REAL(wp) ::   zswitch_sal
107
108      INTEGER  ::   num_iter_max      ! Heat conservation
109      !!------------------------------------------------------------------
110
111      ! Discriminate between time varying salinity and constant
112      SELECT CASE( nn_icesal )                  ! varying salinity or not
113         CASE( 1 , 3 )   ;   zswitch_sal = 0._wp   ! prescribed salinity profile
114         CASE( 2 )       ;   zswitch_sal = 1._wp   ! varying salinity profile
115      END SELECT
116
117      DO ji = 1, nidx
118         icount (ji,:) = 0
119         zdh_s_mel(ji) = 0._wp
120         e_i_1d(ji,nlay_i+1) = 0._wp ! Initialize enthalpy at nlay_i+1
121      END DO
122
123      ! initialize layer thicknesses and enthalpies
124      h_i_old (1:nidx,0:nlay_i+1) = 0._wp
125      eh_i_old(1:nidx,0:nlay_i+1) = 0._wp
126      DO jk = 1, nlay_i
127         DO ji = 1, nidx
128            h_i_old (ji,jk) = ht_i_1d(ji) * r1_nlay_i
129            eh_i_old(ji,jk) = e_i_1d(ji,jk) * h_i_old(ji,jk)
130         END DO
131      END DO
132      !
133      !------------------------------------------------------------------------------!
134      !  1) Calculate available heat for surface and bottom ablation                 !
135      !------------------------------------------------------------------------------!
136      !
137      DO ji = 1, nidx
138         zdum       = qns_ice_1d(ji) + ( 1._wp - i0(ji) ) * qsr_ice_1d(ji) - fc_su(ji) 
139         zf_tt(ji)  = fc_bo_i(ji) + fhtur_1d(ji) + fhld_1d(ji) 
140
141         zq_su (ji) = MAX( 0._wp, zdum      * rdt_ice ) * MAX( 0._wp , SIGN( 1._wp, t_su_1d(ji) - rt0 ) )
142         zq_bo (ji) = MAX( 0._wp, zf_tt(ji) * rdt_ice )
143      END DO
144
145      !------------------------------------------------------------------------------!
146      ! If snow temperature is above freezing point, then snow melts
147      ! (should not happen but sometimes it does)
148      !------------------------------------------------------------------------------!
149      DO ji = 1, nidx
150         IF( t_s_1d(ji,1) > rt0 ) THEN !!! Internal melting
151            ! Contribution to heat flux to the ocean [W.m-2], < 0 
152            hfx_res_1d(ji) = hfx_res_1d(ji) + e_s_1d(ji,1) * ht_s_1d(ji) * a_i_1d(ji) * r1_rdtice
153            ! Contribution to mass flux
154            wfx_snw_sum_1d(ji) = wfx_snw_sum_1d(ji) + rhosn * ht_s_1d(ji) * a_i_1d(ji) * r1_rdtice
155            ! updates
156            ht_s_1d(ji)   = 0._wp
157            e_s_1d (ji,1) = 0._wp
158            t_s_1d (ji,1) = rt0
159         END IF
160      END DO
161
162      !------------------------------------------------------------!
163      !  2) Computing layer thicknesses and enthalpies.            !
164      !------------------------------------------------------------!
165      DO jk = 1, nlay_i
166         DO ji = 1, nidx
167            zh_i(ji,jk) = ht_i_1d(ji) * r1_nlay_i
168            zeh_i(ji)   = zeh_i(ji) + e_i_1d(ji,jk) * zh_i(ji,jk)
169         END DO
170      END DO
171
172      !------------------------------------------------------------------------------|
173      !  3) Surface ablation and sublimation                                         |
174      !------------------------------------------------------------------------------|
175      !
176      !-------------------------
177      ! 3.1 Snow precips / melt
178      !-------------------------
179      ! Snow accumulation in one thermodynamic time step
180      ! snowfall is partitionned between leads and ice
181      ! if snow fall was uniform, a fraction (1-at_i) would fall into leads
182      ! but because of the winds, more snow falls on leads than on sea ice
183      ! and a greater fraction (1-at_i)^beta of the total mass of snow
184      ! (beta < 1) falls in leads.
185      ! In reality, beta depends on wind speed,
186      ! and should decrease with increasing wind speed but here, it is
187      ! considered as a constant. an average value is 0.66
188      ! Martin Vancoppenolle, December 2006
189
190      CALL ice_thd_snwblow( 1. - at_i_1d(1:nidx), zsnw(1:nidx) ) ! snow distribution over ice after wind blowing
191
192      zdeltah(1:nidx,:) = 0._wp
193      DO ji = 1, nidx
194         !-----------
195         ! Snow fall
196         !-----------
197         ! thickness change
198         zdh_s_pre(ji) = zsnw(ji) * sprecip_1d(ji) * rdt_ice * r1_rhosn / at_i_1d(ji)
199         ! enthalpy of the precip (>0, J.m-3)
200         zqprec   (ji) = - qprec_ice_1d(ji)   
201         IF( sprecip_1d(ji) == 0._wp ) zqprec(ji) = 0._wp
202         ! heat flux from snow precip (>0, W.m-2)
203         hfx_spr_1d(ji) = hfx_spr_1d(ji) + zdh_s_pre(ji) * a_i_1d(ji) * zqprec(ji) * r1_rdtice
204         ! mass flux, <0
205         wfx_spr_1d(ji) = wfx_spr_1d(ji) - rhosn * a_i_1d(ji) * zdh_s_pre(ji) * r1_rdtice
206
207         !---------------------
208         ! Melt of falling snow
209         !---------------------
210         ! thickness change
211         rswitch        = MAX( 0._wp , SIGN( 1._wp , zqprec(ji) - epsi20 ) )
212         zdeltah (ji,1) = - rswitch * zq_su(ji) / MAX( zqprec(ji) , epsi20 )
213         zdeltah (ji,1) = MAX( - zdh_s_pre(ji), zdeltah(ji,1) ) ! bound melting
214         ! heat used to melt snow (W.m-2, >0)
215         hfx_snw_1d(ji) = hfx_snw_1d(ji) - zdeltah(ji,1) * a_i_1d(ji) * zqprec(ji) * r1_rdtice
216         ! snow melting only = water into the ocean (then without snow precip), >0
217         wfx_snw_sum_1d(ji) = wfx_snw_sum_1d(ji) - rhosn * a_i_1d(ji) * zdeltah(ji,1) * r1_rdtice
218         ! updates available heat + precipitations after melting
219         zq_su     (ji) = MAX( 0._wp , zq_su (ji) + zdeltah(ji,1) * zqprec(ji) )     
220         zdh_s_pre (ji) = zdh_s_pre(ji) + zdeltah(ji,1)
221
222         ! update thickness
223         ht_s_1d(ji) = MAX( 0._wp , ht_s_1d(ji) + zdh_s_pre(ji) )
224      END DO
225
226      ! If heat still available (zq_su > 0), then melt more snow
227      zdeltah(1:nidx,:) = 0._wp
228      DO jk = 1, nlay_s
229         DO ji = 1, nidx
230            ! thickness change
231            rswitch          = 1._wp - MAX( 0._wp, SIGN( 1._wp, - ht_s_1d(ji) ) ) 
232            rswitch          = rswitch * ( MAX( 0._wp, SIGN( 1._wp, e_s_1d(ji,jk) - epsi20 ) ) ) 
233            zdeltah  (ji,jk) = - rswitch * zq_su(ji) / MAX( e_s_1d(ji,jk), epsi20 )
234            zdeltah  (ji,jk) = MAX( zdeltah(ji,jk) , - ht_s_1d(ji) ) ! bound melting
235            zdh_s_mel(ji)    = zdh_s_mel(ji) + zdeltah(ji,jk)   
236            ! heat used to melt snow(W.m-2, >0)
237            hfx_snw_1d(ji)   = hfx_snw_1d(ji) - zdeltah(ji,jk) * a_i_1d(ji) * e_s_1d(ji,jk) * r1_rdtice 
238            ! snow melting only = water into the ocean (then without snow precip)
239            wfx_snw_sum_1d(ji)   = wfx_snw_sum_1d(ji) - rhosn * a_i_1d(ji) * zdeltah(ji,jk) * r1_rdtice
240            ! updates available heat + thickness
241            zq_su (ji)  = MAX( 0._wp , zq_su (ji) + zdeltah(ji,jk) * e_s_1d(ji,jk) )
242            ht_s_1d(ji) = MAX( 0._wp , ht_s_1d(ji) + zdeltah(ji,jk) )
243         END DO
244      END DO
245
246      !------------------------------
247      ! 3.2 Sublimation (part1: snow)
248      !------------------------------
249      ! qla_ice is always >=0 (upwards), heat goes to the atmosphere, therefore snow sublimates
250      ! clem comment: not counted in mass/heat exchange in iceupdate.F90 since this is an exchange with atm. (not ocean)
251      zdeltah(1:nidx,:) = 0._wp
252      DO ji = 1, nidx
253         zdh_s_sub(ji)  = MAX( - ht_s_1d(ji) , - evap_ice_1d(ji) * r1_rhosn * rdt_ice )
254         ! remaining evap in kg.m-2 (used for ice melting later on)
255         zevap_rema(ji)  = evap_ice_1d(ji) * rdt_ice + zdh_s_sub(ji) * rhosn
256         ! Heat flux by sublimation [W.m-2], < 0 (sublimate first snow that had fallen, then pre-existing snow)
257         zdeltah(ji,1)  = MAX( zdh_s_sub(ji), - zdh_s_pre(ji) )
258         hfx_sub_1d(ji) = hfx_sub_1d(ji) + ( zdeltah(ji,1) * zqprec(ji) + ( zdh_s_sub(ji) - zdeltah(ji,1) ) * e_s_1d(ji,1)  &
259            &                              ) * a_i_1d(ji) * r1_rdtice
260         ! Mass flux by sublimation
261         wfx_snw_sub_1d(ji) = wfx_snw_sub_1d(ji) - rhosn * a_i_1d(ji) * zdh_s_sub(ji) * r1_rdtice
262
263         ! new snow thickness
264         ht_s_1d(ji)    =  MAX( 0._wp , ht_s_1d(ji) + zdh_s_sub(ji) )
265         ! update precipitations after sublimation and correct sublimation
266         zdh_s_pre(ji) = zdh_s_pre(ji) + zdeltah(ji,1)
267         zdh_s_sub(ji) = zdh_s_sub(ji) - zdeltah(ji,1)
268      END DO
269     
270      ! --- Update snow diags --- !
271      DO ji = 1, nidx
272         dh_s_tot(ji) = zdh_s_mel(ji) + zdh_s_pre(ji) + zdh_s_sub(ji)
273      END DO
274
275      !-------------------------------------------
276      ! 3.3 Update temperature, energy
277      !-------------------------------------------
278      ! new temp and enthalpy of the snow (remaining snow precip + remaining pre-existing snow)
279      DO jk = 1, nlay_s
280         DO ji = 1,nidx
281            rswitch       = MAX( 0._wp , SIGN( 1._wp, ht_s_1d(ji) - epsi20 ) )
282            e_s_1d(ji,jk) = rswitch / MAX( ht_s_1d(ji), epsi20 ) *           &
283              &            ( ( zdh_s_pre(ji)               ) * zqprec(ji) +  &
284              &              ( ht_s_1d(ji) - zdh_s_pre(ji) ) * rhosn * ( cpic * ( rt0 - t_s_1d(ji,jk) ) + lfus ) )
285         END DO
286      END DO
287
288      !--------------------------
289      ! 3.4 Surface ice ablation
290      !--------------------------
291      zdeltah(1:nidx,:) = 0._wp ! important
292      DO jk = 1, nlay_i
293         DO ji = 1, nidx
294            ztmelts           = - tmut * s_i_1d(ji,jk) + rt0          ! Melting point of layer k [K]
295           
296            IF( t_i_1d(ji,jk) >= ztmelts ) THEN !!! Internal melting
297
298               zEi            = - e_i_1d(ji,jk) * r1_rhoic            ! Specific enthalpy of layer k [J/kg, <0]       
299               zdE            = 0._wp                                 ! Specific enthalpy difference   (J/kg, <0)
300                                                                      ! set up at 0 since no energy is needed to melt water...(it is already melted)
301               zdeltah(ji,jk) = MIN( 0._wp , - zh_i(ji,jk) )          ! internal melting occurs when the internal temperature is above freezing     
302                                                                      ! this should normally not happen, but sometimes, heat diffusion leads to this
303               zfmdt          = - zdeltah(ji,jk) * rhoic              ! Mass flux x time step > 0
304                         
305               dh_i_surf(ji)  = dh_i_surf(ji) + zdeltah(ji,jk)        ! Cumulate surface melt
306               
307               zfmdt          = - rhoic * zdeltah(ji,jk)              ! Recompute mass flux [kg/m2, >0]
308
309               ! Contribution to heat flux to the ocean [W.m-2], <0 (ice enthalpy zEi is "sent" to the ocean)
310               hfx_res_1d(ji) = hfx_res_1d(ji) + zfmdt * a_i_1d(ji) * zEi * r1_rdtice
311               
312               ! Contribution to salt flux (clem: using sm_i_1d and not s_i_1d(jk) is ok)
313               sfx_res_1d(ji) = sfx_res_1d(ji) - rhoic * a_i_1d(ji) * zdeltah(ji,jk) * sm_i_1d(ji) * r1_rdtice
314               
315               ! Contribution to mass flux
316               wfx_res_1d(ji) =  wfx_res_1d(ji) - rhoic * a_i_1d(ji) * zdeltah(ji,jk) * r1_rdtice
317
318            ELSE                                !!! Surface melting
319               
320               zEi            = - e_i_1d(ji,jk) * r1_rhoic            ! Specific enthalpy of layer k [J/kg, <0]
321               zEw            =    rcp * ( ztmelts - rt0 )            ! Specific enthalpy of resulting meltwater [J/kg, <0]
322               zdE            =    zEi - zEw                          ! Specific enthalpy difference < 0
323               
324               zfmdt          = - zq_su(ji) / zdE                     ! Mass flux to the ocean [kg/m2, >0]
325               
326               zdeltah(ji,jk) = - zfmdt * r1_rhoic                    ! Melt of layer jk [m, <0]
327               
328               zdeltah(ji,jk) = MIN( 0._wp , MAX( zdeltah(ji,jk) , - zh_i(ji,jk) ) )    ! Melt of layer jk cannot exceed the layer thickness [m, <0]
329               
330               zq_su(ji)      = MAX( 0._wp , zq_su(ji) - zdeltah(ji,jk) * rhoic * zdE ) ! update available heat
331               
332               dh_i_surf(ji)  = dh_i_surf(ji) + zdeltah(ji,jk)        ! Cumulate surface melt
333               
334               zfmdt          = - rhoic * zdeltah(ji,jk)              ! Recompute mass flux [kg/m2, >0]
335               
336               zQm            = zfmdt * zEw                           ! Energy of the melt water sent to the ocean [J/m2, <0]
337               
338               ! Contribution to salt flux >0 (clem: using sm_i_1d and not s_i_1d(jk) is ok)
339               sfx_sum_1d(ji) = sfx_sum_1d(ji) - rhoic * a_i_1d(ji) * zdeltah(ji,jk) * sm_i_1d(ji) * r1_rdtice
340               
341               ! Contribution to heat flux [W.m-2], < 0
342               hfx_thd_1d(ji) = hfx_thd_1d(ji) + zfmdt * a_i_1d(ji) * zEw * r1_rdtice
343               
344               ! Total heat flux used in this process [W.m-2], > 0 
345               hfx_sum_1d(ji) = hfx_sum_1d(ji) - zfmdt * a_i_1d(ji) * zdE * r1_rdtice
346               
347               ! Contribution to mass flux
348               wfx_sum_1d(ji) =  wfx_sum_1d(ji) - rhoic * a_i_1d(ji) * zdeltah(ji,jk) * r1_rdtice
349               
350            END IF
351            ! ----------------------
352            ! Sublimation part2: ice
353            ! ----------------------
354            zdum      = MAX( - ( zh_i(ji,jk) + zdeltah(ji,jk) ) , - zevap_rema(ji) * r1_rhoic )
355            zdeltah(ji,jk) = zdeltah(ji,jk) + zdum
356            dh_i_sub(ji)  = dh_i_sub(ji) + zdum
357            ! Salt flux > 0 (clem2016: flux is sent to the ocean for simplicity but salt should remain in the ice except if all ice is melted.
358            !                          It must be corrected at some point)
359            sfx_sub_1d(ji) = sfx_sub_1d(ji) - rhoic * a_i_1d(ji) * zdum * sm_i_1d(ji) * r1_rdtice
360            ! Heat flux [W.m-2], < 0
361            hfx_sub_1d(ji) = hfx_sub_1d(ji) + zdum * e_i_1d(ji,jk) * a_i_1d(ji) * r1_rdtice
362            ! Mass flux > 0
363            wfx_ice_sub_1d(ji) =  wfx_ice_sub_1d(ji) - rhoic * a_i_1d(ji) * zdum * r1_rdtice
364
365            ! update remaining mass flux
366            zevap_rema(ji)  = zevap_rema(ji) + zdum * rhoic
367           
368            ! record which layers have disappeared (for bottom melting)
369            !    => icount=0 : no layer has vanished
370            !    => icount=5 : 5 layers have vanished
371            rswitch       = MAX( 0._wp , SIGN( 1._wp , - ( zh_i(ji,jk) + zdeltah(ji,jk) ) ) ) 
372            icount(ji,jk) = NINT( rswitch )
373            zh_i(ji,jk)   = MAX( 0._wp , zh_i(ji,jk) + zdeltah(ji,jk) )
374                       
375            ! update heat content (J.m-2) and layer thickness
376            eh_i_old(ji,jk) = eh_i_old(ji,jk) + zdeltah(ji,jk) * e_i_1d(ji,jk)
377            h_i_old (ji,jk) = h_i_old (ji,jk) + zdeltah(ji,jk)
378         END DO
379      END DO
380      ! update ice thickness
381      DO ji = 1, nidx
382         ht_i_1d(ji) =  MAX( 0._wp , ht_i_1d(ji) + dh_i_surf(ji) + dh_i_sub(ji) )
383      END DO
384
385      ! remaining "potential" evap is sent to ocean
386      DO ji = 1, nidx
387         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)
388      END DO
389
390
391      !------------------------------------------------------------------------------!
392      ! 4) Basal growth / melt                                                       !
393      !------------------------------------------------------------------------------!
394      !
395      !------------------
396      ! 4.1 Basal growth
397      !------------------
398      ! Basal growth is driven by heat imbalance at the ice-ocean interface,
399      ! between the inner conductive flux  (fc_bo_i), from the open water heat flux
400      ! (fhld) and the turbulent ocean flux (fhtur).
401      ! fc_bo_i is positive downwards. fhtur and fhld are positive to the ice
402
403      ! If salinity varies in time, an iterative procedure is required, because
404      ! the involved quantities are inter-dependent.
405      ! Basal growth (dh_i_bott) depends upon new ice specific enthalpy (zEi),
406      ! which depends on forming ice salinity (s_i_new), which depends on dh/dt (dh_i_bott)
407      ! -> need for an iterative procedure, which converges quickly
408
409      num_iter_max = 1
410      IF( nn_icesal == 2 )   num_iter_max = 5  ! salinity varying in time
411     
412      ! Iterative procedure
413      DO ji = 1, nidx
414         IF(  zf_tt(ji) < 0._wp  ) THEN
415            DO iter = 1, num_iter_max
416
417               ! New bottom ice salinity (Cox & Weeks, JGR88 )
418               !--- zswi1  if dh/dt < 2.0e-8
419               !--- zswi12 if 2.0e-8 < dh/dt < 3.6e-7
420               !--- zswi2  if dh/dt > 3.6e-7
421               zgrr               = MIN( 1.0e-3, MAX ( dh_i_bott(ji) * r1_rdtice , epsi10 ) )
422               zswi2              = MAX( 0._wp , SIGN( 1._wp , zgrr - 3.6e-7 ) )
423               zswi12             = MAX( 0._wp , SIGN( 1._wp , zgrr - 2.0e-8 ) ) * ( 1.0 - zswi2 )
424               zswi1              = 1. - zswi2 * zswi12
425               zfracs             = MIN ( zswi1  * 0.12 + zswi12 * ( 0.8925 + 0.0568 * LOG( 100.0 * zgrr ) )   &
426                  &               + zswi2  * 0.26 / ( 0.26 + 0.74 * EXP ( - 724300.0 * zgrr ) )  , 0.5 )
427
428               s_i_new(ji)        = zswitch_sal * zfracs * sss_1d(ji)  &  ! New ice salinity
429                                  + ( 1. - zswitch_sal ) * sm_i_1d(ji) 
430               ! New ice growth
431               ztmelts            = - tmut * s_i_new(ji) + rt0          ! New ice melting point (K)
432
433               zt_i_new           = zswitch_sal * t_bo_1d(ji) + ( 1. - zswitch_sal) * t_i_1d(ji, nlay_i)
434               
435               zEi                = cpic * ( zt_i_new - ztmelts ) &     ! Specific enthalpy of forming ice (J/kg, <0)     
436                  &               - lfus * ( 1.0 - ( ztmelts - rt0 ) / ( zt_i_new - rt0 ) )   &
437                  &               + rcp  * ( ztmelts-rt0 )         
438
439               zEw                = rcp  * ( t_bo_1d(ji) - rt0 )         ! Specific enthalpy of seawater (J/kg, < 0)
440
441               zdE                = zEi - zEw                           ! Specific enthalpy difference (J/kg, <0)
442
443               dh_i_bott(ji)      = rdt_ice * MAX( 0._wp , zf_tt(ji) / ( zdE * rhoic ) )
444
445               e_i_1d(ji,nlay_i+1) = -zEi * rhoic                        ! New ice energy of melting (J/m3, >0)
446               
447            END DO
448            ! Contribution to Energy and Salt Fluxes                                   
449            zfmdt          = - rhoic * dh_i_bott(ji)             ! Mass flux x time step (kg/m2, < 0)
450
451            ztmelts        = - tmut * s_i_new(ji) + rt0          ! New ice melting point (K)
452           
453            zt_i_new       = zswitch_sal * t_bo_1d(ji) + ( 1. - zswitch_sal) * t_i_1d(ji, nlay_i)
454           
455            zEi            = cpic * ( zt_i_new - ztmelts ) &     ! Specific enthalpy of forming ice (J/kg, <0)     
456               &               - lfus * ( 1.0 - ( ztmelts - rt0 ) / ( zt_i_new - rt0 ) )   &
457               &               + rcp  * ( ztmelts-rt0 )         
458           
459            zEw            = rcp  * ( t_bo_1d(ji) - rt0 )         ! Specific enthalpy of seawater (J/kg, < 0)
460           
461            zdE            = zEi - zEw                           ! Specific enthalpy difference (J/kg, <0)
462           
463            ! Contribution to heat flux to the ocean [W.m-2], >0 
464            hfx_thd_1d(ji) = hfx_thd_1d(ji) + zfmdt * a_i_1d(ji) * zEw * r1_rdtice
465
466            ! Total heat flux used in this process [W.m-2], <0 
467            hfx_bog_1d(ji) = hfx_bog_1d(ji) - zfmdt * a_i_1d(ji) * zdE * r1_rdtice
468           
469            ! Contribution to salt flux, <0
470            sfx_bog_1d(ji) = sfx_bog_1d(ji) - rhoic * a_i_1d(ji) * dh_i_bott(ji) * s_i_new(ji) * r1_rdtice
471
472            ! Contribution to mass flux, <0
473            wfx_bog_1d(ji) =  wfx_bog_1d(ji) - rhoic * a_i_1d(ji) * dh_i_bott(ji) * r1_rdtice
474
475            ! update heat content (J.m-2) and layer thickness
476            eh_i_old(ji,nlay_i+1) = eh_i_old(ji,nlay_i+1) + dh_i_bott(ji) * e_i_1d(ji,nlay_i+1)
477            h_i_old (ji,nlay_i+1) = h_i_old (ji,nlay_i+1) + dh_i_bott(ji)
478
479         ENDIF
480
481      END DO
482
483      !----------------
484      ! 4.2 Basal melt
485      !----------------
486      zdeltah(1:nidx,:) = 0._wp ! important
487      DO jk = nlay_i, 1, -1
488         DO ji = 1, nidx
489            IF(  zf_tt(ji)  >  0._wp  .AND. jk > icount(ji,jk) ) THEN   ! do not calculate where layer has already disappeared by surface melting
490
491               ztmelts = - tmut * s_i_1d(ji,jk) + rt0  ! Melting point of layer jk (K)
492
493               IF( t_i_1d(ji,jk) >= ztmelts ) THEN !!! Internal melting
494
495                  zEi               = - e_i_1d(ji,jk) * r1_rhoic    ! Specific enthalpy of melting ice (J/kg, <0)
496                  zdE               = 0._wp                         ! Specific enthalpy difference   (J/kg, <0)
497                                                                    ! set up at 0 since no energy is needed to melt water...(it is already melted)
498                  zdeltah   (ji,jk) = MIN( 0._wp , - zh_i(ji,jk) )  ! internal melting occurs when the internal temperature is above freezing     
499                                                                    ! this should normally not happen, but sometimes, heat diffusion leads to this
500
501                  dh_i_bott (ji)    = dh_i_bott(ji) + zdeltah(ji,jk)
502
503                  zfmdt             = - zdeltah(ji,jk) * rhoic      ! Mass flux x time step > 0
504
505                  ! Contribution to heat flux to the ocean [W.m-2], <0 (ice enthalpy zEi is "sent" to the ocean)
506                  hfx_res_1d(ji) = hfx_res_1d(ji) + zfmdt * a_i_1d(ji) * zEi * r1_rdtice
507
508                  ! Contribution to salt flux (clem: using sm_i_1d and not s_i_1d(jk) is ok)
509                  sfx_res_1d(ji) = sfx_res_1d(ji) - rhoic * a_i_1d(ji) * zdeltah(ji,jk) * sm_i_1d(ji) * r1_rdtice
510                                   
511                  ! Contribution to mass flux
512                  wfx_res_1d(ji) =  wfx_res_1d(ji) - rhoic * a_i_1d(ji) * zdeltah(ji,jk) * r1_rdtice
513
514                  ! update heat content (J.m-2) and layer thickness
515                  eh_i_old(ji,jk) = eh_i_old(ji,jk) + zdeltah(ji,jk) * e_i_1d(ji,jk)
516                  h_i_old (ji,jk) = h_i_old (ji,jk) + zdeltah(ji,jk)
517
518               ELSE                               !!! Basal melting
519
520                  zEi             = - e_i_1d(ji,jk) * r1_rhoic ! Specific enthalpy of melting ice (J/kg, <0)
521                  zEw             = rcp * ( ztmelts - rt0 )    ! Specific enthalpy of meltwater (J/kg, <0)
522                  zdE             = zEi - zEw                  ! Specific enthalpy difference   (J/kg, <0)
523
524                  zfmdt           = - zq_bo(ji) / zdE          ! Mass flux x time step (kg/m2, >0)
525
526                  zdeltah(ji,jk)  = - zfmdt * r1_rhoic         ! Gross thickness change
527
528                  zdeltah(ji,jk)  = MIN( 0._wp , MAX( zdeltah(ji,jk), - zh_i(ji,jk) ) ) ! bound thickness change
529                 
530                  zq_bo(ji)       = MAX( 0._wp , zq_bo(ji) - zdeltah(ji,jk) * rhoic * zdE ) ! update available heat. MAX is necessary for roundup errors
531
532                  dh_i_bott(ji)   = dh_i_bott(ji) + zdeltah(ji,jk)    ! Update basal melt
533
534                  zfmdt           = - zdeltah(ji,jk) * rhoic          ! Mass flux x time step > 0
535
536                  zQm             = zfmdt * zEw         ! Heat exchanged with ocean
537
538                  ! Contribution to heat flux to the ocean [W.m-2], <0 
539                  hfx_thd_1d(ji)  = hfx_thd_1d(ji) + zfmdt * a_i_1d(ji) * zEw * r1_rdtice
540
541                  ! Contribution to salt flux (clem: using sm_i_1d and not s_i_1d(jk) is ok)
542                  sfx_bom_1d(ji)  = sfx_bom_1d(ji) - rhoic *  a_i_1d(ji) * zdeltah(ji,jk) * sm_i_1d(ji) * r1_rdtice
543                 
544                  ! Total heat flux used in this process [W.m-2], >0 
545                  hfx_bom_1d(ji)  = hfx_bom_1d(ji) - zfmdt * a_i_1d(ji) * zdE * r1_rdtice
546                 
547                  ! Contribution to mass flux
548                  wfx_bom_1d(ji)  =  wfx_bom_1d(ji) - rhoic * a_i_1d(ji) * zdeltah(ji,jk) * r1_rdtice
549
550                  ! update heat content (J.m-2) and layer thickness
551                  eh_i_old(ji,jk) = eh_i_old(ji,jk) + zdeltah(ji,jk) * e_i_1d(ji,jk)
552                  h_i_old (ji,jk) = h_i_old (ji,jk) + zdeltah(ji,jk)
553               ENDIF
554           
555            ENDIF
556         END DO
557      END DO
558
559      !-------------------------------------------
560      ! Update temperature, energy
561      !-------------------------------------------
562      DO ji = 1, nidx
563         ht_i_1d(ji) =  MAX( 0._wp , ht_i_1d(ji) + dh_i_bott(ji) )
564      END DO 
565
566      !-------------------------------------------
567      ! 5. What to do with remaining energy
568      !-------------------------------------------
569      ! If heat still available for melting and snow remains, then melt more snow
570      !-------------------------------------------
571      zdeltah(1:nidx,:) = 0._wp ! important
572      DO ji = 1, nidx
573         zq_rema(ji)     = zq_su(ji) + zq_bo(ji) 
574         rswitch         = 1._wp - MAX( 0._wp, SIGN( 1._wp, - ht_s_1d(ji) ) )   ! =1 if snow
575         rswitch         = rswitch * MAX( 0._wp, SIGN( 1._wp, e_s_1d(ji,1) - epsi20 ) )
576         zdeltah  (ji,1) = - rswitch * zq_rema(ji) / MAX( e_s_1d(ji,1), epsi20 )
577         zdeltah  (ji,1) = MIN( 0._wp , MAX( zdeltah(ji,1) , - ht_s_1d(ji) ) ) ! bound melting
578         dh_s_tot (ji)   = dh_s_tot(ji)  + zdeltah(ji,1)
579         ht_s_1d   (ji)  = ht_s_1d(ji)   + zdeltah(ji,1)
580       
581         zq_rema(ji)     = zq_rema(ji) + zdeltah(ji,1) * e_s_1d(ji,1)                ! update available heat (J.m-2)
582         ! heat used to melt snow
583         hfx_snw_1d(ji)  = hfx_snw_1d(ji) - zdeltah(ji,1) * a_i_1d(ji) * e_s_1d(ji,1) * r1_rdtice ! W.m-2 (>0)
584         ! Contribution to mass flux
585         wfx_snw_sum_1d(ji)  =  wfx_snw_sum_1d(ji) - rhosn * a_i_1d(ji) * zdeltah(ji,1) * r1_rdtice
586         !   
587         ! Remaining heat flux (W.m-2) is sent to the ocean heat budget
588         hfx_out_1d(ji)  = hfx_out_1d(ji) + ( zq_rema(ji) * a_i_1d(ji) ) * r1_rdtice
589
590         IF( ln_icectl .AND. zq_rema(ji) < 0. .AND. lwp ) WRITE(numout,*) 'ALERTE zq_rema <0 = ', zq_rema(ji)
591      END DO
592
593      !
594      !------------------------------------------------------------------------------|
595      !  6) Snow-Ice formation                                                       |
596      !------------------------------------------------------------------------------|
597      ! When snow load excesses Archimede's limit, snow-ice interface goes down under sea-level,
598      ! flooding of seawater transforms snow into ice dh_snowice is positive for the ice
599      z1_rho = 1._wp / ( rhosn+rau0-rhoic )
600      DO ji = 1, nidx
601         !
602         dh_snowice(ji) = MAX(  0._wp , ( rhosn * ht_s_1d(ji) + (rhoic-rau0) * ht_i_1d(ji) ) * z1_rho )
603
604         ht_i_1d(ji)    = ht_i_1d(ji) + dh_snowice(ji)
605         ht_s_1d(ji)    = ht_s_1d(ji) - dh_snowice(ji)
606
607         ! Contribution to energy flux to the ocean [J/m2], >0 (if sst<0)
608         zfmdt          = ( rhosn - rhoic ) * dh_snowice(ji)    ! <0
609         zEw            = rcp * sst_1d(ji)
610         zQm            = zfmdt * zEw 
611         
612         ! Contribution to heat flux
613         hfx_thd_1d(ji) = hfx_thd_1d(ji) + zfmdt * a_i_1d(ji) * zEw * r1_rdtice 
614
615         ! Contribution to salt flux
616         sfx_sni_1d(ji) = sfx_sni_1d(ji) + sss_1d(ji) * a_i_1d(ji) * zfmdt * r1_rdtice 
617
618         ! Case constant salinity in time: virtual salt flux to keep salinity constant
619         IF( nn_icesal == 1 .OR. nn_icesal == 3 )  THEN
620            sfx_bri_1d(ji) = sfx_bri_1d(ji) - sss_1d (ji) * a_i_1d(ji) * zfmdt                  * r1_rdtice  & ! put back sss_m     into the ocean
621               &                            - sm_i_1d(ji) * a_i_1d(ji) * dh_snowice(ji) * rhoic * r1_rdtice    ! and get  rn_icesal from the ocean
622         ENDIF
623
624         ! Contribution to mass flux
625         ! All snow is thrown in the ocean, and seawater is taken to replace the volume
626         wfx_sni_1d(ji)     = wfx_sni_1d(ji)     - a_i_1d(ji) * dh_snowice(ji) * rhoic * r1_rdtice
627         wfx_snw_sni_1d(ji) = wfx_snw_sni_1d(ji) + a_i_1d(ji) * dh_snowice(ji) * rhosn * r1_rdtice
628
629         ! update heat content (J.m-2) and layer thickness
630         eh_i_old(ji,0) = eh_i_old(ji,0) + dh_snowice(ji) * e_s_1d(ji,1) + zfmdt * zEw
631         h_i_old (ji,0) = h_i_old (ji,0) + dh_snowice(ji)
632         
633      END DO
634
635      !
636      !-------------------------------------------
637      ! Update temperature, energy
638      !-------------------------------------------
639      DO ji = 1, nidx
640         rswitch     =  1.0 - MAX( 0._wp , SIGN( 1._wp , - ht_i_1d(ji) ) ) 
641         t_su_1d(ji) =  rswitch * t_su_1d(ji) + ( 1.0 - rswitch ) * rt0
642      END DO
643
644      DO jk = 1, nlay_s
645         DO ji = 1,nidx
646            ! mask enthalpy
647            rswitch       = 1._wp - MAX(  0._wp , SIGN( 1._wp, - ht_s_1d(ji) )  )
648            e_s_1d(ji,jk) = rswitch * e_s_1d(ji,jk)
649            ! recalculate t_s_1d from e_s_1d
650            t_s_1d(ji,jk) = rt0 + rswitch * ( - e_s_1d(ji,jk) * r1_rhosn * r1_cpic + lfus * r1_cpic )
651         END DO
652      END DO
653
654      ! --- ensure that a_i = 0 where ht_i = 0 ---
655      DO ji = 1, nidx
656         IF( ht_i_1d(ji) == 0._wp )   a_i_1d(ji) = 0._wp
657      END DO         
658      !
659   END SUBROUTINE ice_thd_dh
660
661
662   !!--------------------------------------------------------------------------
663   !! INTERFACE ice_thd_snwblow
664   !! ** Purpose :   Compute distribution of precip over the ice
665   !!--------------------------------------------------------------------------
666!!gm  I think it can be usefull to set this as a FUNCTION, not a SUBROUTINE....
667   SUBROUTINE ice_thd_snwblow_2d( pin, pout )
668      REAL(wp), DIMENSION(:,:), INTENT(in   ) :: pin   ! previous fraction lead ( 1. - a_i_b )
669      REAL(wp), DIMENSION(:,:), INTENT(inout) :: pout
670      pout = ( 1._wp - ( pin )**rn_blow_s )
671   END SUBROUTINE ice_thd_snwblow_2d
672
673   SUBROUTINE ice_thd_snwblow_1d( pin, pout )
674      REAL(wp), DIMENSION(:), INTENT(in   ) :: pin
675      REAL(wp), DIMENSION(:), INTENT(inout) :: pout
676      pout = ( 1._wp - ( pin )**rn_blow_s )
677   END SUBROUTINE ice_thd_snwblow_1d
678
679#else
680   !!----------------------------------------------------------------------
681   !!   Default option                               NO  LIM3 sea-ice model
682   !!----------------------------------------------------------------------
683#endif
684
685   !!======================================================================
686END MODULE icethd_dh
Note: See TracBrowser for help on using the repository browser.