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.
limthd_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/limthd_dh.F90 @ 8373

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

remove most of wrk_alloc

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