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_zdf.F90 in branches/nemo/NEMO/LIM_SRC – NEMO

source: branches/nemo/NEMO/LIM_SRC/limthd_zdf.F90 @ 4

Last change on this file since 4 was 3, checked in by opalod, 20 years ago

Initial revision

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 42.8 KB
Line 
1MODULE limthd_zdf
2#if defined key_ice_lim
3   !!======================================================================
4   !!                       ***  MODULE limthd_zdf ***
5   !!                thermodynamic growth and decay of the ice
6   !!======================================================================
7
8   !!----------------------------------------------------------------------
9   !!   lim_thd_zdf  : vertical accr./abl. and lateral ablation of sea ice
10   !! * Modules used
11   USE phycst
12   USE ice_oce         ! ice variables
13   USE thd_ice
14   USE iceini
15   USE limistate
16   USE in_out_manager
17     
18   IMPLICIT NONE
19   PRIVATE
20
21   !! * Routine accessibility
22   PUBLIC lim_thd_zdf        ! called by lim_thd
23
24   !! * Module variables
25   REAL(wp)  ::           &  ! constant values
26      epsi20 = 1e-20   ,  &
27      epsi13 = 1e-13   ,  &
28      zzero  = 0.0     ,  &
29      zone   = 1.0
30   !!----------------------------------------------------------------------
31   !!   LIM 2.0 , UCL-LODYC-IPSL  (2003)
32   !!----------------------------------------------------------------------
33CONTAINS
34
35   SUBROUTINE lim_thd_zdf( kideb , kiut )
36       !!------------------------------------------------------------------
37       !!                ***  ROUTINE lim_thd_zdf  ***
38       !!             
39       !! ** Purpose : This routine determines the time evolution of snow
40       !!      and sea-ice thicknesses, concentration and heat content
41       !!      due to the vertical and lateral thermodynamic accretion-
42       !!      ablation processes. One only treats the case of lat. abl.
43       !!      For lateral accretion, see routine lim_lat_accr
44       !!
45       !! ** Method  : The representation of vertical growth and decay of
46       !!      the sea-ice model is based upon the diffusion of heat
47       !!      through the external and internal boundaries of a
48       !!      three-layer system (two layers of ice and one layer and
49       !!      one layer of snow, if present, on top of the ice).
50       !!
51       !! ** Action  : - Calculation of some intermediates variables
52       !!              - Calculation of surface temperature
53       !!              - Calculation of available heat for surface ablation
54       !!              - Calculation of the changes in internal temperature
55       !!                of the three-layer system, due to vertical diffusion
56       !!                processes
57       !!              - Performs surface ablation and bottom accretion-ablation
58       !!              - Performs snow-ice formation
59       !!              - Performs lateral ablation
60       !!
61       !! References :
62       !!   Fichefet T. and M. Maqueda 1997, J. Geophys. Res., 102(C6), 12609-12646   
63       !!   Fichefet T. and M. Maqueda 1999, Clim. Dyn, 15(4), 251-268 
64       !!
65       !! History :
66       !!   original    : 01-04 (LIM)
67       !!   addition    : 02-08 (C. Ethe, G. Madec)
68       !!------------------------------------------------------------------
69       !! * Arguments
70       INTEGER , INTENT (in) ::  &
71          kideb ,  &  ! Start point on which the  the computation is applied
72          kiut        ! End point on which the  the computation is applied
73
74       !! * Local variables
75       INTEGER ::   ji       ! dummy loop indices
76
77       REAL(wp) , DIMENSION(jpij,2) ::  &
78          zqcmlt        ! energy due to surface( /1 ) and bottom melting( /2 )
79
80       REAL(wp), DIMENSION(jpij) ::  &
81          ztsmlt      &    ! snow/ice surface melting temperature
82          ,ztbif      &    ! int. temp. at the mid-point of the 1st layer of the snow/ice sys.
83          ,zksn       &    ! effective conductivity of snow
84          ,zkic       &    ! effective conductivity of ice
85          ,zksndh     &    ! thermal cond. at the mid-point of the 1st layer of the snow/ice sys.
86          , zfcsu     &    ! conductive heat flux at the surface of the snow/ice system
87          , zfcsudt   &    ! = zfcsu * dt
88          , zi0       &    ! frac. of the net SW rad. which is not absorbed at the surface
89          , z1mi0     &    ! fraction of the net SW radiation absorbed at the surface
90          , zqmax     &    ! maximum energy stored in brine pockets
91          , zrcpdt    &    ! h_su*rho_su*cp_su/dt(h_su being the thick. of surf. layer)
92          , zts_old   &    ! previous surface temperature
93          , zidsn , z1midsn , zidsnic ! tempory variables
94
95       REAL(wp), DIMENSION(jpij) :: &
96          zfnet       &  ! net heat flux at the top surface( incl. conductive heat flux)
97          , zsprecip  &    ! snow accumulation
98          , zhsnw_old &    ! previous snow thickness
99          , zdhictop  &    ! change in ice thickness due to top surf ablation/accretion
100          , zdhicbot  &    ! change in ice thickness due to bottom surf abl/acc
101          , zqsup     &    ! energy transmitted to ocean (coming from top surf abl/acc)
102          , zqocea    &    ! energy transmitted to ocean (coming from bottom sur abl/acc)
103          , zfrl_old  &    ! previous sea/ice fraction
104          , zfrld_1d    &    ! new sea/ice fraction
105          , zep            ! internal temperature of the 2nd layer of the snow/ice system
106
107       REAL(wp), DIMENSION(3) :: & 
108          zplediag  &    ! principle diagonal, subdiag. and supdiag. of the
109          , zsubdiag  &    ! tri-diagonal matrix coming from the computation
110          , zsupdiag  &    ! of the temperatures inside the snow-ice system
111          , zsmbr          ! second member
112
113       REAL(wp) :: & 
114          zhsu     &     ! thickness of surface layer
115          , zhe      &     ! effective thickness for compu. of equ. thermal conductivity
116          , zheshth  &     ! = zhe / thth
117          , zghe     &     ! correction factor of the thermal conductivity
118          , zumsb    &     ! parameter for numerical method to solve heat-diffusion eq.
119          , zkhsn    &     ! conductivity at the snow layer
120          , zkhic    &     ! conductivity at the ice layers
121          , zkint    &     ! equivalent conductivity at the snow-ice interface
122          , zkhsnint &     ! = zkint*dt / (hsn*rhosn*cpsn) 
123          , zkhicint &     ! = 2*zkint*dt / (hic*rhoic*cpic)
124          , zpiv1 , zpiv2  &       ! tempory scalars used to solve the tri-diagonal system
125          , zb2 , zd2 , zb3 , zd3 &
126          , ztint          ! equivalent temperature at the snow-ice interface
127
128       REAL(wp) :: & 
129          zexp      &     ! exponential function of the ice thickness
130          , zfsab     &     ! part of solar radiation stored in brine pockets
131          , zfts      &     ! value of energy balance function when the temp. equal surf. temp.
132          , zdfts     &     ! value of derivative of ztfs when the temp. equal surf. temp.
133          , zdts      &     ! surface temperature increment
134          , zqsnw_mlt &     ! energy needed to melt snow
135          , zdhsmlt   &     ! change in snow thickness due to melt
136          , zhsn      &     ! snow thickness (previous+accumulation-melt)
137          , zqsn_mlt_rem &  ! remaining heat coming from snow melting
138          , zqice_top_mlt & ! energy used to melt ice at top surface
139          , zdhssub      &  ! change in snow thick. due to sublimation or evaporation
140          , zdhisub      &  ! change in ice thick. due to sublimation or evaporation   
141          , zdhsn        &  ! snow ice thickness increment
142          , zdtsn        &  ! snow internal temp. increment
143          , zdtic        &  ! ice internal temp. increment
144          , zqnes          ! conductive energy due to ice melting in the first ice layer
145
146       REAL(wp) :: & 
147          ztbot     &      ! temperature at the bottom surface
148          , zfcbot    &      ! conductive heat flux at bottom surface
149          , zqice_bot &      ! energy used for bottom melting/growing
150          , zqice_bot_mlt &  ! energy used for bottom melting
151          , zqstbif_bot  &  ! part of energy stored in brine pockets used for bottom melting
152          , zqstbif_old  &  ! tempory var. for zqstbif_bot
153          , zdhicmlt      &  ! change in ice thickness due to bottom melting
154          , zdhicm        &  ! change in ice thickness var.
155          , zdhsnm        &  ! change in snow thickness var.
156          , zhsnfi        &  ! snow thickness var.
157          , zc1, zpc1, zc2, zpc2, zp1, zp2 & ! tempory variables
158          , ztb2, ztb3
159
160       REAL(wp) :: & 
161          zdrmh         &   ! change in snow/ice thick. after snow-ice formation
162          , zhicnew       &   ! new ice thickness
163          , zhsnnew       &   ! new snow thickness
164          , zquot , ztneq &   ! tempory temp. variables
165          , zqice, zqicetot & ! total heat inside the snow/ice system
166          , zdfrl         &   ! change in ice concentration
167          , zdvsnvol      &   ! change in snow volume
168          , zdrfrl1, zdrfrl2 &  ! tempory scalars
169          , zihsn, zidhb, zihic, zihe, zihq, ziexp, ziqf, zihnf, zibmlt, ziqr, zihgnew, zind
170       !!----------------------------------------------------------------------
171
172       !-----------------------------------------------------------------------
173       !  1. Boundaries conditions for snow/ice system internal temperature
174       !       - If tbif_1d(ji,1) > rt0_snow, tbif_1d(ji,1) = rt0_snow
175       !       - If tbif_1d(ji,2/3) > rt0_ice, tbif_1d(ji,2/3) = rt0_ice
176       !     Computation of energies due to surface and bottom melting
177       !-----------------------------------------------------------------------
178       
179       
180       DO ji = kideb , kiut
181          zihsn = MAX( zzero , SIGN( zone , hsndif - h_snow_1d(ji) ) )
182          zihic = MAX( zzero , SIGN( zone , hicdif - h_ice_1d(ji) ) )
183          !--computation of energy due to surface melting
184          zqcmlt(ji,1) = ( MAX ( zzero ,  &
185             &                   rcpsn * h_snow_1d(ji) * ( tbif_1d(ji,1) - rt0_snow ) ) ) * ( 1.0 - zihsn )
186          !--computation of energy due to bottom melting
187          zqcmlt(ji,2) = ( MAX( zzero , &
188             &                  rcpic * ( tbif_1d(ji,2) - rt0_ice ) * ( h_ice_1d(ji) / 2. ) ) &
189             &           + MAX( zzero , &
190             &                  rcpic * ( tbif_1d(ji,3) - rt0_ice ) * ( h_ice_1d(ji) / 2. ) ) &
191             &           ) * ( 1.0 - zihic  )
192          !--limitation of  snow/ice system internal temperature
193          tbif_1d(ji,1)   = MIN( rt0_snow, tbif_1d(ji,1) )
194          tbif_1d(ji,2)   = MIN( rt0_ice , tbif_1d(ji,2) )
195          tbif_1d(ji,3)   = MIN( rt0_ice , tbif_1d(ji,3) )
196       END DO
197
198
199       !-------------------------------------------
200       !  2. Calculate some intermediate variables. 
201       !-------------------------------------------
202       
203       ! initialisation of the thickness of surface layer
204       zhsu = hnzst 
205
206       DO ji = kideb , kiut
207          zind   = MAX( zzero , SIGN( zone , zhsu - h_snow_1d(ji) ) )
208          zihsn  = MAX( zzero , SIGN( zone , hsndif - h_snow_1d(ji) ) )
209          zihsn  = MAX( zihsn , zind )
210          zihic  = MAX( zzero , sign( zone , hicdif - h_ice_1d(ji) ) )
211          !     2.1. Computation of surface melting temperature
212          !----------------------------------------------------
213          zind  = MAX( zzero , SIGN( zone , -h_snow_1d(ji) ) )
214          ztsmlt(ji) = ( 1.0 - zind ) * rt0_snow + zind * rt0_ice
215          !
216          !     2.2. Effective conductivity of snow and ice
217          !-----------------------------------------------
218
219          !---computation of the correction factor on the thermal conductivity
220          !-- (Morales Maqueda, 1995 ; Fichefet and Morales Maqueda, 1997)
221          zhe      =  ( rcdsn / ( rcdsn + rcdic ) ) * h_ice_1d(ji)   &
222             &     + ( rcdic / ( rcdsn + rcdic ) ) * h_snow_1d(ji) 
223          zihe     = MAX( zzero , SIGN( zone , 2.0 * zhe - thth ) )
224          zheshth  = zhe / thth
225          zghe     = ( 1.0 - zihe ) * zheshth * ( 2.0 - zheshth )   &
226             &     +         zihe   * 0.5 * ( 1.5 + LOG( 2.0 * zheshth ) )
227#if defined key_lim_cp3
228          zghe = 1.0
229#endif 
230
231          !---effective conductivities
232          zksn(ji)  = zghe * rcdsn 
233          zkic(ji)  = zghe * rcdic
234
235          !
236          !     2.3. Computation of the conductive heat flux from the snow/ice
237          !          system interior toward the top surface
238          !------------------------------------------------------------------
239
240          !---Thermal conductivity at the mid-point of the first snow/ice system layer
241          zksndh(ji) =   ( ( 1.0 - zihsn ) * 2.0 * zksn(ji) + zihsn * 4.0 * zkic(ji) )   &
242             &         / ( ( 1.0 - zihsn ) *  h_snow_1d(ji)                              &
243             &           +        zihsn   *  ( ( 1.0 + 3.0 * zihic ) * h_ice_1d(ji)      &
244             &           + 4.0 * zkic(ji)/zksn(ji) * h_snow_1d(ji) ) )
245
246          !---internal temperature at the mid-point of the first snow/ice system layer
247          ztbif(ji)  = ( 1.0 - zihsn ) * tbif_1d(ji,1)                       &
248             &       +         zihsn   * ( ( 1.0 - zihic ) * tbif_1d(ji,2)   &
249             &       +         zihic   * tfu_1d(ji)   )
250          !---conductive heat flux
251          zfcsu(ji) = zksndh(ji) * ( ztbif(ji) - sist_1d(ji) )
252
253       END DO
254
255       !--------------------------------------------------------------------
256       !  3. Calculate :
257       !     - fstbif_1d, part of solar radiation absorbing inside the ice
258       !       assuming an exponential absorption (Grenfell and Maykut, 1977)
259       !     - zqmax,  maximum energy stored in brine pockets
260       !     - qstbif_1d, total energy stored in brine pockets (updating)
261       !-------------------------------------------------------------------
262
263
264       DO ji = kideb , kiut
265          zihsn  = MAX( zzero , SIGN (zone , -h_snow_1d(ji) ) )
266          zihic  = MAX( zzero , 1.0 - ( h_ice_1d(ji) / zhsu ) )     
267          zind   = MAX( zzero , SIGN (zone , hicdif - h_ice_1d(ji) ) )
268          !--Computation of the fraction of the net shortwave radiation which
269          !--penetrates inside the ice cover ( See Forcat)
270          zi0(ji)  = zihsn * ( fr1_i0_1d(ji) + zihic * fr2_i0_1d(ji) )
271          zexp     = MIN( zone , EXP( -1.5 * ( h_ice_1d(ji) - zhsu ) ) )
272          fstbif_1d(ji) = zi0(ji) * qsr_ice_1d(ji) * zexp
273          !--Computation of maximum energy stored in brine pockets zqmax and update
274          !--the total energy stored in brine pockets, if less than zqmax
275          zqmax(ji) = MAX( zzero , 0.5 * xlic * ( h_ice_1d(ji) - hicmin ) )
276          zfsab   = zi0(ji) * qsr_ice_1d(ji) * ( 1.0 - zexp )
277          zihq    = ( 1.0 - zind ) * MAX(zzero, SIGN( zone , qstbif_1d(ji) - zqmax(ji) ) ) &
278             &    +         zind   * zone
279          qstbif_1d(ji) = ( qstbif_1d(ji) + ( 1.0 - zihq ) * zfsab * rdt_ice ) * swiqst
280          !--fraction of shortwave radiation absorbed at surface
281          ziexp = zihq * zexp + ( 1.0 - zihq ) * ( swiqst + ( 1.0 - swiqst ) * zexp )
282          z1mi0(ji) = 1.0 - zi0(ji) * ziexp
283       END DO
284
285
286       !--------------------------------------------------------------------------------
287       !  4. Computation of the surface temperature : determined by considering the
288       !     budget of a thin layer of thick. zhsu at the top surface (H. Grenier, 1995)
289       !     and based on a surface energy balance :
290       !     hsu * rcp * dT/dt = Fsr + Fnsr(T) + Fcs(T),
291       !     where - Fsr is the net absorbed solar radiation,
292       !           - Fnsr is the total non solar radiation (incoming and outgoing long-wave,
293       !             sensible and latent heat fluxes)
294       !           - Fcs the conductive heat flux at the top of surface
295       !------------------------------------------------------------------------------
296
297       !     4.1. Computation of intermediate values
298       !---------------------------------------------
299       DO ji = kideb, kiut
300          zrcpdt(ji) = ( rcpsn * MIN( h_snow_1d(ji) , zhsu )    &
301             &       + rcpic * MAX( zhsu - h_snow_1d(ji) , zzero ) ) / rdt_ice
302          zts_old(ji) =  sist_1d(ji)
303       END DO
304
305       !     4.2. Computation of surface temperature by expanding the eq. of energy balance
306       !          with Ts = Tp + DT. One obtain , F(Tp) + DT * DF(Tp) = 0
307       !          where  - F(Tp) = Fsr + Fnsr(Tp) + Fcs(Tp)
308       !                 - DF(Tp)= (dFnsr(Tp)/dT) + (dFcs(Tp)/dT) - hsu*rcp/dt
309       !---------------------------------------------------------------------------------
310
311       DO ji = kideb, kiut
312          !---computation of the derivative of energy balance function
313#if defined key_coupled
314#   if defined key_lim_cp2
315          zdfts   =   zksndh(ji)   & ! contribution of the conductive heat flux
316             &      + zrcpdt(ji)   & ! contribution of hsu * rcp / dt
317             &      - dqns_ice_1d(ji)      ! contribution of the total non solar radiation
318#   else
319          zdfts   =   zksndh(ji)   & ! contribution of the conductive heat flux
320             &      + zrcpdt(ji)    ! contribution of hsu * rcp / dt
321#   endif
322
323#else
324          zdfts    =  zksndh(ji)   & ! contribution of the conductive heat flux
325             &      + zrcpdt(ji)   & ! contribution of hsu * rcp / dt
326             &      - dqns_ice_1d (ji)     ! contribution of the total non solar radiation
327#endif
328          !---computation of the energy balance function
329          zfts    = - z1mi0 (ji) * qsr_ice_1d(ji)   & ! net absorbed solar radiation
330             &      - qnsr_ice_1d(ji)                & ! total non solar radiation
331             &      - zfcsu (ji)                  ! conductive heat flux from the surface
332          !---computation of surface temperature increment 
333          zdts    = -zfts / zdfts
334#if defined key_lim_cp3
335          zdts = zdts / 3.0
336#endif
337          !---computation of the new surface temperature
338          sist_1d(ji) = sist_1d(ji) + zdts
339
340       END DO
341
342       !----------------------------------------------------------------------------
343       !  5. Boundary condition at the top surface
344       !--    IF Tsb < Tmelt, Fnet = Fcs (the net heat flux equal the conductive heat flux)
345       !      Otherwise Tsb = Tmelt and Qnet(Tmelt) > 0
346       !      Fnet(Tmelt) is therefore the net surface flux needed for melting
347       !----------------------------------------------------------------------------
348       
349       
350       !     5.1.  Limitation of surface temperature and update total non solar fluxes,
351       !          latent heat flux and conductive flux at the top surface
352       !---------------------------------------------------------------------- 
353                     
354       DO ji = kideb, kiut
355          sist_1d(ji) = MIN( ztsmlt(ji) , sist_1d(ji) )
356#if defined key_coupled
357          qnsr_ice_1d(ji) =  qnsr_ice_1d(ji) - ( emic * stefan * sist_1d(ji) * sist_1d(ji) * sist_1d(ji) * sist_1d(ji) )
358#else         
359          qnsr_ice_1d(ji) = qnsr_ice_1d(ji) + dqns_ice_1d(ji) * ( sist_1d(ji) - zts_old(ji) )
360          qla_ice_1d (ji) = qla_ice_1d (ji) + dqla_ice_1d(ji) * ( sist_1d(ji) - zts_old(ji) )
361#endif
362          zfcsu(ji)  = zksndh(ji) * ( ztbif(ji) - sist_1d(ji) )
363       END DO
364
365     
366
367       !     5.2. Calculate available heat for surface ablation.
368       !---------------------------------------------------------------------
369
370       DO ji = kideb, kiut
371          zfnet(ji) = qnsr_ice_1d(ji) + z1mi0(ji) * qsr_ice_1d(ji) + zfcsu(ji)         
372          zfnet(ji) = MAX( zzero , zfnet(ji) )
373          zfnet(ji) = zfnet(ji) * MAX( zzero , SIGN( zone , sist_1d(ji) - ztsmlt(ji) ) )
374       END DO
375
376       !-------------------------------------------------------------------------
377       !  6. Calculate changes in internal temperature due to vertical diffusion   
378       !     processes. The evolution of this temperature is governed by the one-
379       !     dimensionnal heat-diffusion equation.
380       !     Given the temperature tbif(1/2/3), at time m we solve a set
381       !     of finite difference equations to obtain new tempe. Each tempe is coupled
382       !     to the temp. immediatly above and below by heat conduction terms. Thus
383       !     we have a set of equations of the form A * T = B, where A is a tridiagonal
384       !     matrix, T a vector whose components are the unknown new temp.
385       !-------------------------------------------------------------------------
386       
387       !--parameter for the numerical methode use to solve the heat-diffusion equation
388       !- implicit, explicit or Crank-Nicholson
389       zumsb = 1.0 - sbeta 
390       DO ji = kideb, kiut
391          zidsn(ji)   = MAX ( zzero, SIGN( zone, hsndif - h_snow_1d(ji) ) ) 
392          z1midsn(ji) = 1.0 - zidsn(ji)
393          zihic       = MAX ( zzero, SIGN( zone, hicdif - h_ice_1d(ji) ) ) 
394          zidsnic(ji) = zidsn(ji) *  zihic 
395          zfcsudt(ji) = zfcsu(ji) * rdt_ice 
396       END DO
397   
398       DO ji = kideb, kiut
399
400          !     6.1 Calculate intermediate variables.
401          !----------------------------------------
402
403          !--conductivity at the snow surface
404          zkhsn = 2.0 * zksn(ji) * rdt_ice / rcpsn
405          !--conductivity at the ice surface
406          zkhic = 4.0 * zkic(ji) * rdt_ice / MAX( h_ice_1d(ji) * h_ice_1d(ji) * rcpic , epsi20 )
407          !--conductivity at the snow/ice interface
408          zkint = 4.0 * zksn(ji) * zkic(ji)  &
409             &        / ( zksn(ji) * h_ice_1d(ji) + 2.0 * zkic(ji) * h_snow_1d(ji) * z1midsn(ji)) 
410          zkhsnint = zkint * rdt_ice / rcpsn
411          zkhicint = zkint * 2.0 * rdt_ice / MAX( h_ice_1d(ji) * rcpic , epsi20 )
412         
413          !     6.2. Fulfill the linear system matrix.
414          !-----------------------------------------
415!$$$          zplediag(1) = 1 + sbeta * z1midsn(ji) * ( zkhsn + zkhsnint )       
416          zplediag(1) =   zidsn(ji) + z1midsn(ji) * h_snow_1d(ji)   &
417             &          + sbeta * z1midsn(ji) * zkhsnint 
418          zplediag(2) = 1 + sbeta * ( z1midsn(ji) * zkhicint + zkhic ) 
419          zplediag(3) = 1 + 3.0 * sbeta * zkhic   
420
421          zsubdiag(1) = 0.0             
422          zsubdiag(2) = -1.0 * z1midsn(ji) * sbeta * zkhicint
423          zsubdiag(3) = -1.0 * sbeta * zkhic 
424
425          zsupdiag(1) =  -1.0 * z1midsn(ji) * sbeta * zkhsnint 
426          zsupdiag(2) = zsubdiag(3)
427          zsupdiag(3) = 0.0
428         
429          !     6.3. Fulfill the idependent term vector.
430          !-------------------------------------------
431         
432!$$$          zsmbr(1) = zidsn(ji) * sist_1d(ji) + z1midsn(ji) *   &
433!$$$             &         ( tbif_1d(ji,1) + zkhsn * sist_1d(ji)
434!$$$             &         - zumsb * ( zkhsn * tbif_1d(ji,1)
435!$$$             &                   + zkhsnint * ( tbif_1d(ji,1) - tbif_1d(ji,2) ) ) )
436          zsmbr(1) = zidsn(ji) * sist_1d(ji) + z1midsn(ji) *    &
437             &       ( h_snow_1d(ji) * tbif_1d(ji,1) - ( zfcsudt(ji) / rcpsn )  &
438             &       - zumsb * zkhsnint * ( tbif_1d(ji,1) - tbif_1d(ji,2) ) )
439
440          zsmbr(2) =  tbif_1d(ji,2)  &
441             &      - zidsn(ji) * ( 1.0 - zidsnic(ji) ) &
442             &        * ( zfcsudt(ji) / MAX( h_ice_1d(ji) * rcpic , epsi20 ) ) &
443             &      + zumsb * ( zkhicint * ( tbif_1d(ji,1) - tbif_1d(ji,2) ) &
444             &                   - zkhic * ( tbif_1d(ji,2) - tbif_1d(ji,3) )  )
445
446          zsmbr(3) =  tbif_1d(ji,3)  &
447             &      + zkhic * ( 2.0 * tfu_1d(ji) &
448             &                + zumsb * ( tbif_1d(ji,2) - 3.0 * tbif_1d(ji,3) ) )
449         
450          !     6.4. Solve the system (Gauss elimination method).
451          !----------------------------------------------------
452         
453          zpiv1 = zsubdiag(2) / zplediag(1) 
454          zb2   = zplediag(2) - zpiv1 * zsupdiag(1)
455          zd2   = zsmbr(2) - zpiv1 * zsmbr(1)
456
457          zpiv2 = zsubdiag(3) / zb2
458          zb3   = zplediag(3) - zpiv2 * zsupdiag(2)
459          zd3   = zsmbr(3) - zpiv2 * zd2
460
461          tbif_1d(ji,3) = zd3 / zb3
462          tbif_1d(ji,2) = ( zd2 - zsupdiag(2) * tbif_1d(ji,3) ) / zb2
463          tbif_1d(ji,1) = ( zsmbr(1) - zsupdiag(1) * tbif_1d(ji,2) ) / zplediag(1)           
464
465          !--- taking into account the particular case of  zidsnic(ji) = 1
466          ztint =  (  zkic(ji) * h_snow_1d(ji) * tfu_1d (ji)    &
467             &      + zksn(ji) * h_ice_1d(ji) * sist_1d(ji) )   &
468             &   / ( zkic(ji) * h_snow_1d(ji) + zksn(ji) * h_ice_1d(ji) ) 
469
470          tbif_1d(ji,1) = ( 1.0 - zidsnic(ji) ) * tbif_1d(ji,1)   &
471             &                + zidsnic(ji)   * ( ztint + sist_1d(ji) ) / 2.0
472          tbif_1d(ji,2) = ( 1.0 - zidsnic(ji) ) * tbif_1d(ji,2)   &
473             &                + zidsnic(ji)   * ( 3.0 * ztint + tfu_1d(ji) ) / 4.0
474          tbif_1d(ji,3) = ( 1.0 - zidsnic(ji) ) * tbif_1d(ji,3)   &
475             &                + zidsnic(ji)   * ( ztint + 3.0 * tfu_1d(ji) ) / 4.0     
476       END DO
477 
478       !----------------------------------------------------------------------
479       !  9. Take into account surface ablation and bottom accretion-ablation.|
480       !----------------------------------------------------------------------
481       
482       !---Snow accumulation in one thermodynamic time step
483       zsprecip(kideb:kiut) = sprecip_1d(kideb:kiut) * rdt_ice / rhosn
484
485
486       DO ji = kideb, kiut
487         
488          !      9.1. Surface ablation and update of snow thickness and qstbif_1d
489          !--------------------------------------------------------------------
490         
491          !--------------------------------------------------------------------------
492          !--      Melting snow processes :
493          !--      Melt at the upper surface is computed from the difference between
494          !--      the net heat flux (including the conductive heat flux) at the upper
495          !--      surface and the pre-existing energy due to surface melting
496          !------------------------------------------------------------------------------
497         
498          !-- store the snow thickness
499          zhsnw_old(ji) =  h_snow_1d(ji)
500          !--computation of the energy needed to melt snow
501          zqsnw_mlt  = zfnet(ji) * rdt_ice - zqcmlt(ji,1)
502          !--change in snow thickness due to melt
503          zdhsmlt = - zqsnw_mlt / xlsn
504         
505          !-- compute new snow thickness, taking into account the part of snow accumulation
506          !   (as snow precipitation) and the part of snow lost due to melt
507          zhsn =  h_snow_1d(ji) + zsprecip(ji) + zdhsmlt
508          h_snow_1d(ji) = MAX( zzero , zhsn )
509          !-- compute the volume of snow lost after surface melting and the associated mass
510          dvsbq_1d(ji) =  ( 1.0 - frld_1d(ji) ) * ( h_snow_1d(ji) - zhsnw_old(ji) - zsprecip(ji) )
511          dvsbq_1d(ji) =  MIN( zzero , dvsbq_1d(ji) )
512          rdmsnif_1d(ji) =  rhosn * dvsbq_1d(ji)
513          !-- If the snow is completely melted the remaining heat is used to melt ice
514          zqsn_mlt_rem  = MAX( zzero , -zhsn ) * xlsn
515          zqice_top_mlt = zqsn_mlt_rem 
516          zqstbif_old   = qstbif_1d(ji)
517
518          !--------------------------------------------------------------------------
519          !--      Melting ice processes at the top surface :
520          !--      The energy used to melt ice, zqice_top_mlt, is taken from the energy
521          !--      stored in brine pockets qstbif_1d and the remaining energy coming
522          !--      from the melting snow process zqsn_mlt_rem.
523          !--      If qstbif_1d > zqsn_mlt_rem then, one uses only a zqsn_mlt_rem part
524          !--      of qstbif_1d to melt ice,
525          !--         zqice_top_mlt = zqice_top_mlt + zqsn_mlt_rem
526          !--         qstbif_1d = qstbif_1d - zqsn_mlt_rem
527          !--      Otherwise one uses all qstbif_1d to melt ice
528          !--         zqice_top_mlt = zqice_top_mlt + qstbif_1d
529          !--         qstbif_1d = 0
530          !------------------------------------------------------
531         
532          ziqf =  MAX ( zzero , SIGN( zone , qstbif_1d(ji) - zqsn_mlt_rem  ) )
533          zqice_top_mlt =         ziqf   * ( zqice_top_mlt + zqsn_mlt_rem )   &
534             &          + ( 1.0 - ziqf ) * ( zqice_top_mlt + qstbif_1d(ji)  )
535
536          qstbif_1d(ji) =         ziqf   * ( qstbif_1d(ji) - zqsn_mlt_rem )   &
537             &        + ( 1.0 - ziqf ) * ( qstbif_1d(ji) - qstbif_1d(ji)  )
538
539          !--    The contribution of the energy stored in brine pockets qstbif_1d to melt
540          !--    ice is taking into account only when qstbif_1d is less than zqmax.
541          !--    Otherwise, only the remaining energy coming from the melting snow
542          !--    process is used
543          zihq =  MAX ( zzero , SIGN( zone , qstbif_1d(ji) - zqmax(ji) ) )
544
545          zqice_top_mlt =         zihq   * zqice_top_mlt   &
546             &          + ( 1.0 - zihq ) * zqsn_mlt_rem
547
548          qstbif_1d(ji) =         zihq   * qstbif_1d(ji)   &
549             &        + ( 1.0 - zihq ) * zqstbif_old
550
551          !--change in ice thickness due to melt at the top surface
552          zdhictop(ji) = -zqice_top_mlt / xlic
553          !--compute the volume formed after surface melting
554          dvsbq_1d(ji) =  zdhictop(ji) * ( 1.0 - frld_1d(ji) )
555
556          !-------------------------------------------------------------------------
557          !--      A small variation at the surface also occurs because of sublimation
558          !--      associated with the latent flux. If qla_ice_1d is negative, snow condensates at
559          !        the surface. Otherwise, snow evaporates
560          !-----------------------------------------------------------------------
561          !----change in snow and ice thicknesses due to sublimation or evaporation
562          zdhssub  = parsub * ( qla_ice_1d(ji) / ( rhosn * xsn ) ) * rdt_ice 
563          zhsn     = h_snow_1d(ji) - zdhssub
564          zdhisub  = MAX( zzero , -zhsn ) * rhosn/rhoic
565          zdhictop(ji) =  zdhictop(ji) - zdhisub
566          h_snow_1d(ji)  =  MAX( zzero , zhsn )
567          !-------------------------------------------------
568          !--  Update Internal temperature and qstbif_1d.
569          !-------------------------------------------
570          zihsn  =  MAX( zzero , SIGN( zone, -h_snow_1d(ji) ) )
571          tbif_1d(ji,1) = ( 1.0 - zihsn ) * tbif_1d(ji,1) + zihsn   * tfu_1d(ji)
572          !--change in snow internal temperature if snow has increased
573          zihnf = MAX( zzero , SIGN( zone , h_snow_1d(ji) - zhsnw_old(ji) ) )
574          zdhsn = 1.0 - zhsnw_old(ji) / MAX( h_snow_1d(ji) , epsi20 )
575          zdtsn = zdhsn * ( sist_1d(ji) - tbif_1d(ji,1) )
576          tbif_1d(ji,1) = tbif_1d(ji,1) + z1midsn(ji) * zihnf * zdtsn
577          !--energy created due to ice melting in the first ice layer
578          zqnes  = ( rt0_ice - tbif_1d(ji,2) ) * rcpic * ( h_ice_1d(ji) / 2. )
579          !--change in first ice layer internal temperature
580          ziqr  = MAX( zzero , SIGN( zone , qstbif_1d(ji) - zqnes ) )
581          zdtic = qstbif_1d(ji) / ( rcpic * ( h_ice_1d(ji) / 2. ) )
582          tbif_1d(ji,2) =  ziqr * rt0_ice + ( 1 - ziqr ) * ( tbif_1d(ji,2) + zdtic )
583          !--update qstbif_1d
584          qstbif_1d(ji) = ziqr * ( qstbif_1d(ji) - zqnes ) * swiqst
585
586
587          !--      9.2. Calculate bottom accretion-ablation and update qstbif_1d.
588          !             Growth and melting at bottom ice surface are governed by 
589          !                 -xlic * Dh = (Fcb - Fbot ) * Dt
590          !             where Fbot is the net downward heat flux from ice to the ocean
591          !            and Fcb is the conductive heat flux at the bottom surface
592          !---------------------------------------------------------------------------
593          ztbot = ( 1.0 - zidsnic(ji) ) * tbif_1d(ji,3) + zidsnic(ji) * sist_1d(ji)
594          !---computes conductive heat flux at bottom surface
595          zfcbot =  4.0 * zkic(ji) * ( tfu_1d(ji) - ztbot )   &
596             &   / ( h_ice_1d(ji) + zidsnic(ji) * ( 3. * h_ice_1d(ji) &
597             &   + 4.0 * zkic(ji)/zksn(ji) * h_snow_1d(ji) ) )
598          !---computation of net energy needed for bottom melting/growing
599          zqice_bot = ( zfcbot - ( fbif_1d(ji) + qlbbq_1d(ji) ) ) * rdt_ice
600          zqstbif_bot = qstbif_1d(ji)
601          !---switch to know if bottom surface melts ( = 1 ) or grows ( = 0 )occurs
602          zibmlt = MAX( zzero , SIGN( zone , -zqice_bot ) )
603          !--particular case of melting (in the same way as the top surface)
604          zqice_bot_mlt = zqice_bot 
605          zqstbif_old = zqstbif_bot
606
607          ziqf =  MAX ( zzero , SIGN( zone , qstbif_1d(ji) + zqice_bot_mlt  ) )
608          zqice_bot_mlt =         ziqf   * ( zqice_bot_mlt + zqice_bot_mlt ) &
609             &          + ( 1.0 - ziqf ) * ( zqice_bot_mlt + qstbif_1d(ji)  )         
610          qstbif_1d(ji)   =         ziqf   * ( qstbif_1d(ji) + zqice_bot_mlt ) &
611             &          + ( 1.0 - ziqf ) * ( qstbif_1d(ji) - qstbif_1d(ji)  )
612          !--    The contribution of the energy stored in brine pockets qstbif_1d to melt
613          !--    ice is taking into account only when qstbif_1d is less than zqmax.
614          zihq =  MAX ( zzero , SIGN( zone , qstbif_1d(ji) - zqmax(ji) ) )
615          zqice_bot_mlt =         zihq   * zqice_bot_mlt   &
616             &          + ( 1.0 - zihq ) * zqice_bot
617          qstbif_1d(ji)   =         zihq   * qstbif_1d(ji)   &
618             &             + ( 1.0 - zihq ) * zqstbif_old
619
620          !---treatment of the case of melting/growing
621          zqice_bot   =         zibmlt   * ( zqice_bot_mlt - zqcmlt(ji,2) )   &
622             &        + ( 1.0 - zibmlt ) * ( zqice_bot - zqcmlt(ji,2)  )
623          qstbif_1d(ji) =         zibmlt   * qstbif_1d(ji)   &
624             &           + ( 1.0 - zibmlt ) * zqstbif_bot
625
626          !--computes change in ice thickness due to melt or growth
627          zdhicbot(ji) = zqice_bot / xlic
628          !--limitation of bottom melting if so : hmelt maximum melting at bottom
629          zdhicmlt  = MAX( hmelt , zdhicbot(ji) ) 
630          !--energy after bottom melting/growing
631          zqsup(ji) = ( 1.0 - frld_1d(ji) ) * xlic * ( zdhicmlt - zdhicbot(ji) )
632          !-- compute the new thickness and the newly formed volume after bottom melting/growing
633          zdhicbot(ji)  = zdhicmlt
634          dvbbq_1d(ji) = ( 1.0 - frld_1d(ji) ) * zdhicbot(ji)
635
636
637          !        9.3.  Updating ice thickness after top surface ablation
638          !              and bottom surface accretion/ablation
639          !---------------------------------------------------------------
640          zhicnew  = h_ice_1d(ji) + zdhictop(ji) + zdhicbot(ji)
641
642          !
643          !        9.4. Case of total ablation (ice is gone but snow may be left)
644          !-------------------------------------------------------------------
645          zhsn  = h_snow_1d(ji)
646          zihgnew = 1.0 - MAX( zzero , SIGN( zone , -zhicnew ) )
647          zihsn   = MAX( zzero , SIGN( zone , -zhsn ) )
648          !---convert
649          zdhicm  = ( 1.0 - zihgnew ) * ( zhicnew - qstbif_1d(ji) / xlic )
650          zdhsnm  = ( 1.0 - zihsn ) * zdhicm * rhoic / rhosn
651          !---updating new ice thickness and computing the newly formed ice mass
652          zhicnew   =  zihgnew * zhicnew
653          rdmicif_1d(ji) =  rdmicif_1d(ji) + ( 1.0 - frld_1d(ji) ) * ( zhicnew - h_ice_1d(ji) ) * rhoic
654          !---updating new snow thickness and computing the newly formed snow mass
655          zhsnfi   = zhsn + zdhsnm
656          h_snow_1d(ji) = MAX( zzero , zhsnfi )
657          rdmsnif_1d(ji) =  rdmsnif_1d(ji) + ( 1.0 - frld_1d(ji) ) * ( h_snow_1d(ji) - zhsn ) * rhosn
658          !--remaining energy in case of total ablation
659          zqocea(ji) = - ( zihsn * xlic * zdhicm + xlsn * ( zhsnfi - h_snow_1d(ji) ) ) * ( 1.0 - frld_1d(ji) )
660          qstbif_1d(ji) = zihgnew * qstbif_1d(ji)
661
662          !
663          !        9.5. Update internal temperature and ice thickness.
664          !-------------------------------------------------------
665          !
666          sist_1d(ji) = zihgnew * sist_1d(ji) + ( 1.0 - zihgnew ) * tfu_1d(ji)
667          zidhb  = MAX( zzero , SIGN( zone , - zdhicbot(ji) ) )
668          zc1    = - zhicnew * 0.5
669          zpc1   = MIN( 0.5 * zone , - h_ice_1d(ji) * 0.5 - zdhictop(ji) )
670          zc2    = - zhicnew
671          zpc2   =  zidhb * zc2 + ( 1.0 - zidhb ) * ( - h_ice_1d(ji) - zdhictop(ji) )
672          zp1    =  MAX( zpc1 , zc1 )
673          zp2    =  MAX( zpc2 , zc1 )
674          zep(ji) =  tbif_1d(ji,2)
675          ztb2  = 2.0 * (         - zp1   * tbif_1d(ji,2)  &
676             &  + ( zp1 - zp2 ) * tbif_1d(ji,3)  &
677             &  + ( zp2 - zc1 ) * tfu_1d(ji) ) / MAX( zhicnew , epsi20 ) 
678          tbif_1d(ji,2) = zihgnew * ztb2 + ( 1.0 - zihgnew ) * tfu_1d(ji)
679          !---
680          zp1  =  MIN( zpc1 , zc1 )
681          zp2  =  MIN( zpc2 , zc1 )
682          zp1  =  MAX( zc2  , zp1 )
683          ztb3 =  2.0 * (   ( 1.0 - zidhb ) * (  ( zc1 - zp2 ) * tbif_1d(ji,3)  &
684             &                                 + ( zp2 - zc2 ) * tfu_1d(ji) )   &
685             &               +      zidhb   * (  ( zc1 - zp1 ) * zep(ji)      &
686             &                                 + ( zp1 - zc2 ) * tbif_1d(ji,3))  ) / MAX( zhicnew , epsi20 )
687          tbif_1d(ji,3) =  zihgnew * ztb3 + ( 1.0 - zihgnew ) * tfu_1d(ji)
688          h_ice_1d(ji)  =  zhicnew
689       END DO
690
691
692       !----------------------------------------------------------------------------
693       !  10. Surface accretion.
694       !      The change of ice thickness after snow/ice formation is such that
695       !      the interface between snow and ice is located at the same height
696       !      as the ocean surface. It is given by (Fichefet and Morales Maqueda 1999)
697       !          D(h_ice) = (- D(hsn)/alph) =  [rhosn*hsn - (rau0 - rhoic)*hic]
698       !                                     / [alph*rhosn+rau0 - rhoic]
699       !----------------------------------------------------------------------------
700       !
701       DO ji = kideb , kiut
702
703          !--  Computation of the change of ice thickness after snow-ice formation
704          zdrmh =  ( rhosn * h_snow_1d(ji) + ( rhoic - rau0 ) * h_ice_1d(ji) )  &
705             &  / ( alphs * rhosn + rau0 - rhoic )
706          zdrmh = MAX( zzero , zdrmh )
707
708          !--New ice and snow thicknesses Fichefet and Morales Maqueda (1999)
709          zhicnew  = MAX( h_ice_1d(ji) , h_ice_1d(ji) + zdrmh )
710          zhsnnew  = MIN( h_snow_1d(ji) , h_snow_1d(ji) - alphs * zdrmh )
711          !---Compute new ice temperatures. snow temperature remains unchanged
712          !   Lepparanta (1983):
713          zihic = 1.0 - MAX( zzero , SIGN( zone , -zhicnew ) )
714          zquot  = ( 1.0 - zihic ) &
715             &   +         zihic * MIN( zone , h_ice_1d(ji) / MAX( zhicnew , epsi20 ) ) 
716          ztneq  =         alphs * cnscg * tbif_1d(ji,1)    &
717             &   + ( 1.0 - alphs * ( rhosn/rhoic ) ) * tfu_1d(ji)
718          zep(ji) = tbif_1d(ji,2)
719          tbif_1d(ji,2) = ztneq - zquot * zquot * ( ztneq - tbif_1d(ji,2) )
720          tbif_1d(ji,3) = 2.0 * ztneq &
721             &        + zquot * ( tbif_1d(ji,3) + zep(ji) - 2.0 * ztneq ) - tbif_1d(ji,2)
722
723          !---  Lepparanta (1983) (latent heat released during white ice formation
724          !     goes to the ocean -for lateral ablation-)
725          qldif_1d(ji)  = qldif_1d(ji) + zdrmh * ( 1.0 - alphs * ( rhosn/rhoic ) ) * xlic * ( 1.0 - frld_1d(ji) )
726          !--   Changes in ice volume and ice mass Lepparanta (1983):
727          dvnbq_1d(ji) = ( 1.0 - frld_1d(ji) ) * ( zhicnew - h_ice_1d(ji) )
728          dmgwi_1d(ji) = dmgwi_1d(ji) + ( 1.0 -frld_1d(ji) ) * ( h_snow_1d(ji) - zhsnnew ) * rhosn
729          !  case of natural freshwater flux
730#if defined key_lim_fdd 
731          rdmicif_1d(ji) = rdmicif_1d(ji) + ( 1.0 - frld_1d(ji) )   * ( zhicnew - h_ice_1d(ji) )  * rhoic
732          rdmsnif_1d(ji) = rdmsnif_1d(ji) + ( 1.0 - frld_1d(ji) )   * ( zhsnnew - h_snow_1d(ji) ) * rhosn
733
734#else
735          rdmicif_1d(ji) = rdmicif_1d(ji) + ( 1.0 - frld_1d(ji) ) * (  ( zhicnew - h_ice_1d(ji) ) * rhoic   &
736             &                                                    + ( zhsnnew - h_snow_1d(ji) ) * rhosn )
737#endif
738
739          !---  Actualize new snow and ice thickness.
740
741          h_snow_1d(ji)  = zhsnnew
742          h_ice_1d(ji)  = zhicnew
743
744       END DO
745
746       !----------------------------------------------------
747       !  11. Lateral ablation (Changes in sea/ice fraction)
748       !----------------------------------------------------
749       DO ji = kideb , kiut
750          zfrl_old(ji)  = frld_1d(ji)
751          zihic   = 1.0 - MAX( zzero , SIGN( zone , -h_ice_1d(ji) ) )
752          zihsn   = 1.0 - MAX( zzero , SIGN( zone , -h_snow_1d(ji) ) )
753          !--In the case of total ablation (all the ice ice has melted) frld = 1
754          frld_1d(ji)  = ( 1.0 - zihic ) + zihic * zfrl_old(ji)
755          !--Part of solar radiation absorbing inside the ice and going
756          !--through the ocean
757          fscbq_1d(ji) = ( 1.0 - zfrl_old(ji) ) * ( 1.0 - thcm_1d(ji) ) * fstbif_1d(ji)
758          !--Total remaining energy after bottom melting/growing
759          qfvbq_1d(ji) = zqsup(ji) + ( 1.0 - zihic ) * zqocea(ji)
760          !--Updating of total heat from the ocean
761          qldif_1d(ji)  = qldif_1d(ji) + qfvbq_1d(ji) + ( 1.0 - zihic ) * fscbq_1d(ji) * rdt_ice
762          !--Computation of total heat inside the snow/ice system
763          zqice  = h_snow_1d(ji) * xlsn + h_ice_1d(ji) * xlic
764          zqicetot  = ( 1.0 - frld_1d(ji) ) * zqice
765          !--The concentration of ice is reduced (frld increases) if the heat
766          !--exchange between ice and ocean is positive
767          ziqf = MAX( zzero , SIGN( zone ,  zqicetot - qldif_1d(ji) ) )
768          zdfrl = qldif_1d(ji) / MAX( epsi20 , zqice ) 
769          frld_1d(ji)  = ( 1.0 - ziqf )    &
770             &       +         ziqf * ( frld_1d(ji) + MAX( zzero , zdfrl ) ) 
771          fltbif_1d(ji) = ( ( 1.0 - zfrl_old(ji) ) * qstbif_1d(ji) - zqicetot  ) / rdt_ice
772          !--  Opening of leads: Hakkinen & Mellor, 1992.
773          zdfrl = - ( zdhictop(ji) + zdhicbot(ji) ) * hakspl * ( 1.0 - zfrl_old(ji) ) &
774             &  / MAX( epsi13 , h_ice_1d(ji) + h_snow_1d(ji) * rhosn/rhoic ) 
775          zfrld_1d(ji) =  frld_1d(ji) + MAX( zzero , zdfrl )
776          !--Limitation of sea-ice fraction <= 1
777          zfrld_1d(ji) = ziqf * MIN( 0.99 * zone , zfrld_1d(ji) ) + ( 1 - ziqf )
778          !---Update surface and internal temperature and snow/ice thicknesses.
779          sist_1d(ji)   = sist_1d(ji)   + ( 1.0 - ziqf ) * ( tfu_1d(ji) - sist_1d(ji)   )
780          tbif_1d(ji,1) = tbif_1d(ji,1) + ( 1.0 - ziqf ) * ( tfu_1d(ji) - tbif_1d(ji,1) )
781          tbif_1d(ji,2) = tbif_1d(ji,2) + ( 1.0 - ziqf ) * ( tfu_1d(ji) - tbif_1d(ji,2) )
782          tbif_1d(ji,3) = tbif_1d(ji,3) + ( 1.0 - ziqf ) * ( tfu_1d(ji) - tbif_1d(ji,3) )
783          !--variation of ice volume and ice mass
784          dvlbq_1d(ji)   = zihic * ( zfrl_old(ji) - frld_1d(ji) ) * h_ice_1d(ji)
785          rdmicif_1d(ji) = rdmicif_1d(ji) + dvlbq_1d(ji) * rhoic
786          !--variation of snow volume and snow mass
787          zdvsnvol    = zihsn * ( zfrl_old(ji) - frld_1d(ji) ) * h_snow_1d(ji)
788          rdmsnif_1d(ji) = rdmsnif_1d(ji) + zdvsnvol * rhosn
789          h_snow_1d(ji)  = ziqf * h_snow_1d(ji)
790
791          zdrfrl1 = ziqf * ( 1.0 -  frld_1d(ji) ) / MAX( epsi20 , 1.0 - zfrld_1d(ji) )
792          zdrfrl2 = ziqf * ( 1.0 - zfrl_old(ji) ) / MAX( epsi20 , 1.0 - zfrld_1d(ji) )
793
794          h_snow_1d (ji) = zdrfrl1 * h_snow_1d(ji)
795          h_ice_1d  (ji) = zdrfrl1 * h_ice_1d(ji)
796          qstbif_1d(ji) = zdrfrl2 * qstbif_1d(ji)
797          frld_1d(ji)    = zfrld_1d(ji)
798
799       END DO
800       
801    END SUBROUTINE lim_thd_zdf
802#else
803   !!======================================================================
804   !!                       ***  MODULE limthd_zdf   ***
805   !!                              no sea ice model 
806   !!======================================================================
807CONTAINS
808   SUBROUTINE lim_thd_zdf          ! Empty routine
809   END SUBROUTINE lim_thd_zdf
810#endif
811 END MODULE limthd_zdf
Note: See TracBrowser for help on using the repository browser.