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_lac_2.F90 in branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2 – NEMO

source: branches/DEV_r1837_mass_heat_salt_fluxes/NEMO/LIM_SRC_2/limthd_lac_2.F90 @ 1855

Last change on this file since 1855 was 1855, checked in by gm, 14 years ago

ticket:#665 style change only, with the suppression of thd_ice_2 (merged in ice_2)

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 12.2 KB
Line 
1MODULE limthd_lac_2
2   !!======================================================================
3   !!                       ***  MODULE limthd_lac_2   ***
4   !!   LIM 2 ice model :   thermodynamics -- lateral accretion of the ice
5   !!======================================================================
6   !! History :  LIM  !  2001-04 (UCL)  original code
7   !!            2.0  !  2002-08 (C. Ethe, G. Madec)  F90, mpp
8   !!----------------------------------------------------------------------
9#if defined key_lim2
10   !!----------------------------------------------------------------------
11   !!   'key_lim2' :                                  LIM 2.0 sea-ice model
12   !!----------------------------------------------------------------------
13   !!   lim_lat_acr_2   : lateral accretion of ice
14   !!----------------------------------------------------------------------
15   USE par_oce          ! ocean parameters
16   USE phycst           ! physical constants
17   USE ice_2            ! LIM 2 sea-ice variables
18   USE limistate_2      ! LIM 2 initial state
19     
20   IMPLICIT NONE
21   PRIVATE
22
23   PUBLIC   lim_thd_lac_2   ! called by lim_thd_2
24
25   REAL(wp) ::   epsi20 = 1.e-20   ! constant values
26   REAL(wp) ::   epsi13 = 1.e-13   !
27   REAL(wp) ::   rzero  = 0.e0     !
28   REAL(wp) ::   rone   = 1.e0     !
29
30   !!----------------------------------------------------------------------
31   !! NEMO/LIM 3.3,  UCL-LOCEAN-IPSL (2010)
32   !! $Id$
33   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
34   !!----------------------------------------------------------------------
35CONTAINS
36   
37   SUBROUTINE lim_thd_lac_2( kideb, kiut )
38      !!-------------------------------------------------------------------
39      !!               ***   ROUTINE lim_thd_lac_2  ***
40      !! 
41      !! ** Purpose : Computation of the evolution of the ice thickness and
42      !!      concentration as a function of the heat balance in the leads.
43      !!      It is only used for lateral accretion
44      !!       
45      !! ** Method  : Ice is formed in the open water when ocean lose heat
46      !!      (heat budget of open water Bl is negative) .
47      !!      Computation of the increase of 1-A (ice concentration) fol-
48      !!      lowing the law :
49      !!      (dA/dt)acc = F[ (1-A)/(1-a) ] * [ Bl / (Li*h0) ]
50      !!       where - h0 is the thickness of ice created in the lead
51      !!             - a is a minimum fraction for leads
52      !!             - F is a monotonic non-increasing function defined as:
53      !!                  F(X)=( 1 - X**exld )**(1.0/exld)
54      !!             - exld is the exponent closure rate (=2 default val.)
55      !!
56      !! ** Action : - Adjustment of snow and ice thicknesses and heat
57      !!                content in brine pockets
58      !!             - Updating ice internal temperature
59      !!             - Computation of variation of ice volume and mass
60      !!             - Computation of frldb after lateral accretion and
61      !!               update h_snow_1d, h_ice_1d and tbif_1d(:,:)     
62      !!
63      !! References :   M. Maqueda, 1995, PhD Thesis, Univesidad Complutense Madrid
64      !!                Fichefet T. and M. Maqueda 1997, J. Geo. Res., 102(C6), 12609 -12646   
65      !!-------------------------------------------------------------------
66      INTEGER, INTENT(in) ::   kideb   ! start point on which the the computation is applied
67      INTEGER, INTENT(in) ::   kiut    ! end point on which the the computation is applied
68      !!
69      INTEGER ::   ji         !  dummy loop indices
70      INTEGER ::   iicefr     !  1 = existing ice ; 0 = no ice
71      INTEGER ::   iiceform   !  1 = ice formed   ; 0 = no ice formed
72      INTEGER ::   ihemis     !  hemisphere indicator
73      REAL(wp), DIMENSION(jpij) ::   zqbgow      !  heat budget of the open water (negative)
74      REAL(wp), DIMENSION(jpij) ::   zfrl_old    !  previous sea/ice fraction
75      REAL(wp), DIMENSION(jpij) ::   zhice_old   !  previous ice thickness
76      REAL(wp), DIMENSION(jpij) ::   zhice0      !  thickness of newly formed ice in leads
77      REAL(wp), DIMENSION(jpij) ::   zfrlmin     !  minimum fraction for leads
78      REAL(wp), DIMENSION(jpij) ::   zdhicbot    !  part of thickness of newly formed ice in leads which
79      !                                          !  has been already used in transport for example
80      REAL(wp) ::   zhemis     !  hemisphere (0 = North, 1 = South)
81      REAL(wp) ::   zhicenew   !  new ice thickness
82      REAL(wp) ::   zholds2    !  ratio of previous ice thickness and 2
83      REAL(wp) ::   zhnews2    !  ratio of new ice thickness and 2
84      REAL(wp) ::   zfrlnew    !  new sea/ice fraction
85      REAL(wp) ::   zfrld      !  ratio of sea/ice fraction and minimum fraction for leads
86      REAL(wp) ::   zfrrate    !  leads-closure rate
87      REAL(wp) ::   zdfrl      !  sea-ice fraction increment
88      REAL(wp) ::   zdh1 , zdh2, zdh3, zdh4, zdh5   ! tempory scalars
89      REAL(wp) ::   ztint, zta1, zta2, zta3, zta4   !    -       -
90      REAL(wp) ::   zah, zalpha, zbeta              !    -       -
91      !!---------------------------------------------------------------------     
92                   
93      !--------------------------------------------------------------
94      !   Computation of the heat budget of the open water (negative)
95      !--------------------------------------------------------------
96      DO ji = kideb , kiut     
97         zqbgow(ji) = qldif_1d(ji) - qcmif_1d(ji)
98      END DO
99     
100      !-----------------------------------------------------------------
101      !   Taking the appropriate values for the corresponding hemisphere
102      !-----------------------------------------------------------------
103      DO ji = kideb , kiut
104         zhemis       = MAX( zzero , SIGN( zone , frld_1d(ji) - 2.0 ) ) 
105         ihemis       = INT( 1 + zhemis )
106         zhice0  (ji) = hiccrit( ihemis ) 
107         zfrlmin (ji) = acrit  ( ihemis )   
108         frld_1d (ji) = frld_1d(ji) - 2.0 * zhemis
109         zfrl_old(ji) = frld_1d(ji)
110      END DO
111     
112      !-------------------------------------------------------------------
113      !     Lateral Accretion (modification of the fraction of open water)
114      !     The ice formed in the leads has always a thickness zhice0, but
115      !     only a fraction zfrrate of the ice formed contributes to the
116      !     increase of the ice fraction. The remaining part (1-zfrrate)
117      !     is rather assumed to lead to an increase in the thickness of the
118      !     pre-existing ice (transport for example).
119      !     Morales Maqueda, 1995 - Fichefet and Morales Maqueda, 1997
120      !---------------------------------------------------------------------
121!CDIR NOVERRCHK
122      DO ji = kideb , kiut
123         iicefr       = 1 - MAX( 0, INT( SIGN( 1.5 * zone , zfrl_old(ji) - 1.0 + epsi13 ) ) )
124         !---computation of the leads-closure rate
125         zfrld        = MIN( zone , ( 1.0 - frld_1d(ji) ) / ( 1.0 - zfrlmin(ji) ) )
126         zfrrate      = ( 1.0 - zfrld**exld )**( 1.0 / exld )
127         !--computation of the sea-ice fraction increment and the new fraction
128         zdfrl        = ( zfrrate / zhice0(ji) )  * ( zqbgow(ji) / xlic )
129         zfrlnew      = zfrl_old(ji) + zdfrl
130         !--update the sea-ice fraction
131         frld_1d   (ji) = MAX( zfrlnew , zfrlmin(ji) )
132         !--computation of the remaining part of ice thickness which has been already used
133         zdhicbot(ji) =  ( frld_1d(ji) - zfrlnew ) * zhice0(ji) / ( 1.0 - zfrlmin(ji) ) & 
134            &         -  (  ( 1.0 - zfrrate ) / ( 1.0 - frld_1d(ji) ) )  * ( zqbgow(ji) / xlic ) 
135      END DO
136 
137      !----------------------------------------------------------------------------------------
138      !      Ajustement of snow and ice thicknesses and updating the total heat stored in brine pockets 
139      !      The thickness of newly formed ice is averaged with that of the pre-existing
140      !         (1-Anew) * hinew = (1-Aold) * hiold + ((1-Anew)-(1-Aold)) * h0
141      !      Snow is distributed over the new ice-covered area
142      !         (1-Anew) * hsnew = (1-Aold) * hsold           
143      !--------------------------------------------------------------------------------------------
144      DO ji = kideb , kiut
145         iicefr       = 1 - MAX( 0, INT( SIGN( 1.5 * zone , zfrl_old(ji) - 1.0 + epsi13 ) ) )
146         zhice_old(ji) = h_ice_1d(ji)
147         zhicenew      = iicefr * zhice_old(ji) + ( 1 - iicefr ) * zhice0(ji)
148         zalpha        = ( 1. - zfrl_old(ji) ) / ( 1.- frld_1d(ji) )
149         h_snow_1d(ji) = zalpha * h_snow_1d(ji)
150         h_ice_1d (ji) = zalpha * zhicenew + ( 1.0 - zalpha ) * zhice0(ji)
151         qstbif_1d(ji) = zalpha * qstbif_1d(ji) 
152      END DO
153     
154      !-------------------------------------------------------
155      !   Ajustement of ice internal temperatures
156      !-------------------------------------------------------
157      DO ji = kideb , kiut
158         iicefr      = 1 - MAX( 0, INT( SIGN( 1.5 * zone , zfrl_old(ji) - 1.0 + epsi13 ) ) )
159         iiceform    = 1 - MAX( 0 ,INT( SIGN( 1.5 * zone , zhice0(ji) - h_ice_1d(ji) ) ) )
160         zholds2     = zhice_old(ji)/ 2.
161         zhnews2     = h_ice_1d(ji) / 2.
162         zdh1        = MAX( zzero ,  zhice_old(ji)   - zhnews2 )
163         zdh2        = MAX( zzero , -zhice_old(ji)   + zhnews2 )
164         zdh3        = MAX( zzero ,  h_ice_1d(ji) - zholds2 )
165         zdh4        = MAX( zzero , -h_ice_1d(ji) + zholds2 )
166         zdh5        = MAX( zzero , zhice0(ji)      - zholds2 )
167         ztint       =       iiceform   * (  ( zholds2 - zdh3 ) * tbif_1d(ji,3) + zdh4 * tbif_1d(ji,2) )      &
168            &                           / MAX( epsi20 , h_ice_1d(ji) - zhice0(ji) )                           &
169            &                 + ( 1 - iiceform ) * tfu_1d(ji)
170         zta1        = iicefr * ( 1.  - zfrl_old(ji) ) * tbif_1d(ji,2) 
171         zta2        = iicefr * ( 1.  - zfrl_old(ji) ) * tbif_1d(ji,3)
172         zta3        = iicefr * ( 1.  - zfrl_old(ji) ) * ztint
173         zta4        = ( zfrl_old(ji) - frld_1d   (ji) ) * tfu_1d(ji)
174         zah         = ( 1. - frld_1d(ji) ) * zhnews2 
175
176         tbif_1d(ji,2) = (  MIN( zhnews2 , zholds2 )                                              * zta1   &
177            &          + ( 1 - iiceform ) * ( zholds2 - zdh1 )                                    * zta2   &
178            &          + ( iiceform * ( zhnews2 - zhice0(ji) + zdh5 ) + ( 1 - iiceform ) * zdh2 ) * zta3   & 
179            &          + MIN ( zhnews2 , zhice0(ji) )                                             * zta4   &
180            &          ) / zah
181         
182         tbif_1d(ji,3) =     (  iiceform * ( zhnews2 - zdh3 )                                          * zta1  &
183            &              + ( iiceform * zdh3 + ( 1 - iiceform ) * zdh1 )                             * zta2  &
184            &              + ( iiceform * ( zhnews2 - zdh5 ) + ( 1 - iiceform ) * ( zhnews2 - zdh1 ) ) * zta3  & 
185            &              + ( iiceform * zdh5 + ( 1 - iiceform ) * zhnews2 )                          * zta4  &
186            &            ) / zah
187         !---removing the remaining part of ice formed which has been already used
188         zbeta         = h_ice_1d(ji) / ( h_ice_1d(ji) + zdhicbot(ji) )
189         h_ice_1d(ji)  = h_ice_1d(ji) + zdhicbot(ji)
190         tbif_1d (ji,2)= zbeta * tbif_1d(ji,2) + ( 1.0 - zbeta ) * tbif_1d(ji,3)
191         tbif_1d (ji,3)= ( 2. * zbeta - 1.0 ) * tbif_1d(ji,3) + ( 2. * zdhicbot(ji) / h_ice_1d(ji) ) * tfu_1d(ji)
192         
193      END DO
194     
195      !-------------------------------------------------------------
196      !    Computation of variation of ice volume and ice mass
197      !           Vold = (1-Aold) * hiold ; Vnew = (1-Anew) * hinew
198      !           dV = Vnew - Vold
199      !-------------------------------------------------------------
200      DO ji = kideb , kiut
201         dvlbq_1d  (ji) = ( 1. - frld_1d(ji) ) * h_ice_1d(ji) - ( 1. - zfrl_old(ji) ) * zhice_old(ji)
202         rdmicif_1d(ji) = rdmicif_1d(ji) + rhoic * dvlbq_1d(ji)
203      END DO
204      !
205   END SUBROUTINE lim_thd_lac_2
206   
207#else
208   !!----------------------------------------------------------------------
209   !!   Default option          Dummy module       NO LIM 2.0 sea-ice model
210   !!----------------------------------------------------------------------
211#endif
212
213   !!======================================================================
214END MODULE limthd_lac_2
Note: See TracBrowser for help on using the repository browser.