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.
ice.F90 in branches/2013/dev_r4028_CNRS_LIM3/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2013/dev_r4028_CNRS_LIM3/NEMOGCM/NEMO/LIM_SRC_3/ice.F90 @ 4634

Last change on this file since 4634 was 4634, checked in by clem, 10 years ago

major changes in heat budget

  • Property svn:keywords set to Id
File size: 40.2 KB
Line 
1MODULE ice
2   !!======================================================================
3   !!                        ***  MODULE ice  ***
4   !! LIM-3 Sea Ice physics:  diagnostics variables of ice defined in memory
5   !!=====================================================================
6   !! History :  3.0  ! 2008-03  (M. Vancoppenolle) original code LIM-3
7   !!            4.0  ! 2011-02  (G. Madec) dynamical allocation
8   !!----------------------------------------------------------------------
9#if defined key_lim3
10   !!----------------------------------------------------------------------
11   !!   'key_lim3'                                      LIM-3 sea-ice model
12   !!----------------------------------------------------------------------
13   USE par_ice        ! LIM sea-ice parameters
14   USE in_out_manager ! I/O manager
15   USE lib_mpp        ! MPP library
16
17   IMPLICIT NONE
18   PRIVATE
19
20   PUBLIC    ice_alloc  !  Called in iceini.F90
21
22   !!======================================================================
23   !! LIM3 by the use of sweat, agile fingers and sometimes brain juice,
24   !!  was developed in Louvain-la-Neuve by :
25   !!    * Martin Vancoppenolle (UCL-ASTR, Belgium)
26   !!    * Sylvain Bouillon (UCL-ASTR, Belgium)
27   !!    * Miguel Angel Morales Maqueda (NOC-L, UK)
28   !!
29   !! Based on extremely valuable earlier work by
30   !!    * Thierry Fichefet
31   !!    * Hugues Goosse
32   !!
33   !! The following persons also contributed to the code in various ways
34   !!    * Gurvan Madec, Claude Talandier, Christian Ethe (LOCEAN, France)
35   !!    * Xavier Fettweis (UCL-ASTR), Ralph Timmermann (AWI, Germany)
36   !!    * Bill Lipscomb (LANL), Cecilia Bitz (UWa)
37   !!      and Elisabeth Hunke (LANL), USA.
38   !!
39   !! For more info, the interested user is kindly invited to consult the following references
40   !!    For model description and validation :
41   !!    * Vancoppenolle et al., Ocean Modelling, 2008a.
42   !!    * Vancoppenolle et al., Ocean Modelling, 2008b.
43   !!    For a specific description of EVP :
44   !!    * Bouillon et al., Ocean Modelling 2009.
45   !!
46   !!    Or the reference manual, that should be available by 2011
47   !!======================================================================
48   !!                                                                     |
49   !!              I C E   S T A T E   V A R I A B L E S                  |
50   !!                                                                     |
51   !! Introduction :                                                      |
52   !! --------------                                                      |
53   !! Every ice-covered grid cell is characterized by a series of state   |
54   !! variables. To account for unresolved spatial variability in ice     |
55   !! thickness, the ice cover in divided in ice thickness categories.    |
56   !!                                                                     |
57   !! Sea ice state variables depend on the ice thickness category        |
58   !!                                                                     |
59   !! Those variables are divided into two groups                         |
60   !! * Extensive (or global) variables.                                  |
61   !!   These are the variables that are transported by all means         |
62   !! * Intensive (or equivalent) variables.                              |
63   !!   These are the variables that are either physically more           |
64   !!   meaningful and/or used in ice thermodynamics                      |
65   !!                                                                     |
66   !! Routines in limvar.F90 perform conversions                          |
67   !!  - lim_var_glo2eqv  : from global to equivalent variables           |
68   !!  - lim_var_eqv2glo  : from equivalent to global variables           |
69   !!                                                                     |
70   !! For various purposes, the sea ice state variables have sometimes    |
71   !! to be aggregated over all ice thickness categories. This operation  |
72   !! is done in :                                                        |
73   !!  - lim_var_agg                                                      |
74   !!                                                                     |
75   !! in icestp.F90, the routines that compute the changes in the ice     |
76   !! state variables are called                                          |
77   !! - lim_dyn : ice dynamics                                            |
78   !! - lim_trp : ice transport                                           |
79   !! - lim_itd_me : mechanical redistribution (ridging and rafting)      |
80   !! - lim_thd : ice halo-thermodynamics                                 |
81   !! - lim_itd_th : thermodynamic changes in ice thickness distribution  |
82   !!                and creation of new ice                              |
83   !!                                                                     |
84   !! See the associated routines for more information                    |
85   !!                                                                     |
86   !! List of ice state variables :                                       |
87   !! -----------------------------                                       |
88   !!                                                                     |
89   !!-------------|-------------|---------------------------------|-------|
90   !!   name in   |   name in   |              meaning            | units |
91   !! 2D routines | 1D routines |                                 |       |
92   !!-------------|-------------|---------------------------------|-------|
93   !!                                                                     |
94   !! ******************************************************************* |
95   !! ***         Dynamical variables (prognostic)                    *** |
96   !! ******************************************************************* |
97   !!                                                                     |
98   !! u_ice       |      -      |    Comp. U of the ice velocity  | m/s   |
99   !! v_ice       |      -      |    Comp. V of the ice velocity  | m/s   |
100   !!                                                                     |
101   !! ******************************************************************* |
102   !! ***         Category dependent state variables (prognostic)     *** |
103   !! ******************************************************************* |
104   !!                                                                     |
105   !! ** Global variables                                                 |
106   !!-------------|-------------|---------------------------------|-------|
107   !! a_i         | a_i_b       |    Ice concentration            |       |
108   !! v_i         |      -      |    Ice volume per unit area     | m     |
109   !! v_s         |      -      |    Snow volume per unit area    | m     |
110   !! smv_i       |      -      |    Sea ice salt content         | ppt.m |
111   !! oa_i        !      -      !    Sea ice areal age content    | day   |
112   !! e_i         !      -      !    Ice enthalpy                 | 10^9 J|
113   !!      -      ! q_i_b       !    Ice enthalpy per unit vol.   | J/m3  |
114   !! e_s         !      -      !    Snow enthalpy                | 10^9 J|
115   !!      -      ! q_s_b       !    Snow enthalpy per unit vol.  | J/m3  |
116   !!                                                                     |
117   !!-------------|-------------|---------------------------------|-------|
118   !!                                                                     |
119   !! ** Equivalent variables                                             |
120   !!-------------|-------------|---------------------------------|-------|
121   !!                                                                     |
122   !! ht_i        | ht_i_b      |    Ice thickness                | m     |
123   !! ht_s        ! ht_s_b      |    Snow depth                   | m     |
124   !! sm_i        ! sm_i_b      |    Sea ice bulk salinity        ! ppt   |
125   !! s_i         ! s_i_b       |    Sea ice salinity profile     ! ppt   |
126   !! o_i         !      -      |    Sea ice Age                  ! days  |
127   !! t_i         ! t_i_b       |    Sea ice temperature          ! K     |
128   !! t_s         ! t_s_b       |    Snow temperature             ! K     |
129   !! t_su        ! t_su_b      |    Sea ice surface temperature  ! K     |
130   !!                                                                     |
131   !! notes: the ice model only sees a bulk (i.e., vertically averaged)   |
132   !!        salinity, except in thermodynamic computations, for which    |
133   !!        the salinity profile is computed as a function of bulk       |
134   !!        salinity                                                     |
135   !!                                                                     |
136   !!        the sea ice surface temperature is not associated to any     |
137   !!        heat content. Therefore, it is not a state variable and      |
138   !!        does not have to be advected. Nevertheless, it has to be     |
139   !!        computed to determine whether the ice is melting or not      |
140   !!                                                                     |
141   !! ******************************************************************* |
142   !! ***         Category-summed state variables (diagnostic)        *** |
143   !! ******************************************************************* |
144   !! at_i        | at_i_b      |    Total ice concentration      |       |
145   !! vt_i        |      -      |    Total ice vol. per unit area | m     |
146   !! vt_s        |      -      |    Total snow vol. per unit ar. | m     |
147   !! smt_i       |      -      |    Mean sea ice salinity        | ppt   |
148   !! tm_i        |      -      |    Mean sea ice temperature     | K     |
149   !! ot_i        !      -      !    Sea ice areal age content    | day   |
150   !! et_i        !      -      !    Total ice enthalpy           | 10^9 J|
151   !! et_s        !      -      !    Total snow enthalpy          | 10^9 J|
152   !! bv_i        !      -      !    Mean relative brine volume   | ???   |
153   !!=====================================================================
154
155   LOGICAL, PUBLIC ::   con_i = .false.   ! switch for conservation test
156
157   !!--------------------------------------------------------------------------
158   !! * Share Module variables
159   !!--------------------------------------------------------------------------
160   INTEGER , PUBLIC ::   nstart      !: iteration number of the begining of the run
161   INTEGER , PUBLIC ::   nlast       !: iteration number of the end of the run
162   INTEGER , PUBLIC ::   nitrun      !: number of iteration
163   INTEGER , PUBLIC ::   numit       !: iteration number
164   REAL(wp), PUBLIC ::   rdt_ice     !: ice time step
165   REAL(wp), PUBLIC ::   r1_rdtice   !: = 1. / rdt_ice
166
167   !                                          !!** ice-dynamic namelist (namicedyn) **
168   INTEGER , PUBLIC ::   nbiter = 1            !: number of sub-time steps for relaxation
169   INTEGER , PUBLIC ::   nbitdr = 250          !: maximum number of iterations for relaxation
170   INTEGER , PUBLIC ::   nevp   = 400          !: number of iterations for subcycling
171   INTEGER , PUBLIC ::   nlay_i = 5            !: number of layers in the ice
172
173   !                                          !!** ice-dynamic namelist (namicedyn) **
174   REAL(wp), PUBLIC ::   epsd   = 1.0e-20_wp   !: tolerance parameter for dynamic
175   REAL(wp), PUBLIC ::   alpha  = 0.5_wp       !: coefficient for semi-implicit coriolis
176   REAL(wp), PUBLIC ::   dm     = 0.6e+03_wp   !: diffusion constant for dynamics
177   REAL(wp), PUBLIC ::   om     = 0.5_wp       !: relaxation constant
178   REAL(wp), PUBLIC ::   resl   = 5.0e-05_wp   !: maximum value for the residual of relaxation
179   REAL(wp), PUBLIC ::   cw     = 5.0e-03_wp   !: drag coefficient for oceanic stress
180   REAL(wp), PUBLIC ::   angvg  = 0._wp        !: turning angle for oceanic stress
181   REAL(wp), PUBLIC ::   pstar  = 1.0e+04_wp   !: determines ice strength (N/M), Hibler JPO79
182   REAL(wp), PUBLIC ::   c_rhg  = 20._wp       !: determines changes in ice strength
183   REAL(wp), PUBLIC ::   etamn  = 0.0e+07_wp   !: minimun value for viscosity : has to be 0
184   REAL(wp), PUBLIC ::   creepl = 2.0e-08_wp   !: creep limit : has to be under 1.0e-9
185   REAL(wp), PUBLIC ::   ecc    = 2._wp        !: eccentricity of the elliptical yield curve
186   REAL(wp), PUBLIC ::   ahi0   = 350._wp      !: sea-ice hor. eddy diffusivity coeff. (m2/s)
187   REAL(wp), PUBLIC ::   telast = 2880._wp     !: timescale for elastic waves (s) !SB
188   REAL(wp), PUBLIC ::   alphaevp = 1._wp      !: coeficient of the internal stresses !SB
189   REAL(wp), PUBLIC ::   unit_fac = 1.e+09_wp  !: conversion factor for ice / snow enthalpy
190   REAL(wp), PUBLIC ::   hminrhg = 0.001_wp    !: clem : ice volume (a*h, in m) below which ice velocity is set to ocean velocity
191
192   !                                              !!** ice-salinity namelist (namicesal) **
193   REAL(wp), PUBLIC ::   s_i_max  = 20.0_wp        !: maximum ice salinity [PSU]
194   REAL(wp), PUBLIC ::   s_i_min  =  0.1_wp        !: minimum ice salinity [PSU]
195   REAL(wp), PUBLIC ::   s_i_0    =  3.5_wp        !: 1st sal. value for the computation of sal .prof. [PSU]
196   REAL(wp), PUBLIC ::   s_i_1    =  4.5_wp        !: 2nd sal. value for the computation of sal .prof. [PSU]
197   REAL(wp), PUBLIC ::   sal_G    =  5.0_wp        !: restoring salinity for gravity drainage [PSU]
198   REAL(wp), PUBLIC ::   sal_F    =  2.5_wp        !: restoring salinity for flushing [PSU]
199   REAL(wp), PUBLIC ::   time_G   =  1.728e+06_wp  !: restoring time constant for gravity drainage (= 20 days) [s]
200   REAL(wp), PUBLIC ::   time_F   =  8.640e+05_wp  !: restoring time constant for gravity drainage (= 10 days) [s]
201   REAL(wp), PUBLIC ::   bulk_sal =  4.0_wp        !: bulk salinity (ppt) in case of constant salinity
202
203   !                                              !!** ice-salinity namelist (namicesal) **
204   INTEGER , PUBLIC ::   num_sal     = 1           !: salinity configuration used in the model
205   !                                               ! 1 - constant salinity in both space and time
206   !                                               ! 2 - prognostic salinity (s(z,t))
207   !                                               ! 3 - salinity profile, constant in time
208   INTEGER , PUBLIC ::   sal_prof    = 1           !: salinity profile or not
209   INTEGER , PUBLIC ::   thcon_i_swi = 1           !: thermal conductivity: =0 Untersteiner (1964) ; =1 Pringle et al (2007)
210
211   !                                              !!** ice-mechanical redistribution namelist (namiceitdme)
212   REAL(wp), PUBLIC ::   Cs        = 0.25_wp       !: fraction of shearing energy contributing to ridging           
213   REAL(wp), PUBLIC ::   Cf        = 17.0_wp       !: ratio of ridging work to PE loss
214   REAL(wp), PUBLIC ::   fsnowrdg  = 0.5_wp        !: fractional snow loss to the ocean during ridging
215   REAL(wp), PUBLIC ::   fsnowrft  = 0.5_wp        !: fractional snow loss to the ocean during ridging
216   REAL(wp), PUBLIC ::   Gstar     = 0.15_wp       !: fractional area of young ice contributing to ridging
217   REAL(wp), PUBLIC ::   astar     = 0.05_wp       !: equivalent of G* for an exponential participation function
218   REAL(wp), PUBLIC ::   Hstar     = 100.0_wp      !: thickness that determines the maximal thickness of ridged ice
219   REAL(wp), PUBLIC ::   hparmeter = 0.75_wp       !: threshold thickness (m) for rafting / ridging
220   REAL(wp), PUBLIC ::   Craft     = 5.0_wp        !: coefficient for smoothness of the hyperbolic tangent in rafting
221   REAL(wp), PUBLIC ::   ridge_por = 0.0_wp        !: initial porosity of ridges (0.3 regular value)
222   REAL(wp), PUBLIC ::   sal_max_ridge = 15.0_wp   !: maximum ridged ice salinity (ppt)
223   REAL(wp), PUBLIC ::   betas    = 1.0_wp         !: coef. for partitioning of snowfall between leads and sea ice
224   REAL(wp), PUBLIC ::   kappa_i  = 1.0_wp         !: coef. for the extinction of radiation Grenfell et al. (2006) [1/m]
225   REAL(wp), PUBLIC ::   nconv_i_thd = 50_wp       !: maximal number of iterations for heat diffusion
226   REAL(wp), PUBLIC ::   maxer_i_thd = 1.0e-4_wp   !: maximal tolerated error (C) for heat diffusion
227
228   !                                              !!** ice-mechanical redistribution namelist (namiceitdme)
229   INTEGER , PUBLIC ::   ridge_scheme_swi = 0      !: scheme used for ice ridging
230   INTEGER , PUBLIC ::   raftswi          = 1      !: rafting of ice or not                       
231   INTEGER , PUBLIC ::   partfun_swi      = 1      !: participation function: =0 Thorndike et al. (1975), =1 Lipscomb et al. (2007)
232   INTEGER , PUBLIC ::   transfun_swi     = 0      !: transfer function: =0 Hibler 1980, =1 Lipscomb et al. 2007
233   INTEGER , PUBLIC ::   brinstren_swi    = 0      !: use brine volume to diminish ice strength
234
235   REAL(wp), PUBLIC ::   usecc2           !:  = 1.0 / ( ecc * ecc )
236   REAL(wp), PUBLIC ::   rhoco            !: = rau0 * cw
237   REAL(wp), PUBLIC ::   sangvg, cangvg   !: sin and cos of the turning angle for ocean stress
238   REAL(wp), PUBLIC ::   pstarh           !: pstar / 2.0
239
240   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_oce, v_oce   !: surface ocean velocity used in ice dynamics
241   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ahiu , ahiv    !: hor. diffusivity coeff. at U- and V-points [m2/s]
242   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   pahu , pahv    !: ice hor. eddy diffusivity coef. at U- and V-points
243   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ust2s, hicol   !: friction velocity, ice collection thickness accreted in leads
244   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   strp1, strp2   !: strength at previous time steps
245   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   strength       !: ice strength
246   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   stress1_i, stress2_i, stress12_i   !: 1st, 2nd & diagonal stress tensor element
247   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   delta_i        !: ice rheology elta factor (Flato & Hibler 95) [s-1]
248   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   divu_i         !: Divergence of the velocity field [s-1]
249   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   shear_i        !: Shear of the velocity field [s-1]
250   !
251   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sist        !: Average Sea-Ice Surface Temperature [Kelvin]
252   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   icethi      !: total ice thickness (for all categories) (diag only)
253   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   t_bo        !: Sea-Ice bottom temperature [Kelvin]     
254   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   frld        !: Leads fraction = 1 - ice fraction
255   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   pfrld       !: Leads fraction at previous time 
256   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   phicif      !: Old ice thickness
257   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qlead       !: heat balance of the lead (or of the open ocean)
258   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fhtur       !: net downward heat flux from the ice to the ocean
259   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fhld        !: heat flux from the lead used for bottom melting
260
261   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw     !: Variation of snow mass over 1 time step     [Kg/m2]
262   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_ice     !: Variation of ice mass over 1 time step      [Kg/m2]
263   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sub     !: Variation of snow mass over 1 time step due to sublimation [Kg/m2]
264
265   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sni   ! snow ice growth
266   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_opw   ! lateral ice growth
267   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_bog   ! bottom ice growth
268   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_dyn   ! dynamical ice growth
269   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_bom   ! vertical bottom melt
270   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sum   ! vertical surface melt
271   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_res   ! production (growth+melt) due to limupdate
272
273   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bog     !: salt flux due to ice growth/melt                      [PSU/m2/s]
274   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bom     !: salt flux due to ice growth/melt                      [PSU/m2/s]
275   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sum     !: salt flux due to ice growth/melt                      [PSU/m2/s]
276   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sni     !: salt flux due to ice growth/melt                      [PSU/m2/s]
277   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_opw     !: salt flux due to ice growth/melt                      [PSU/m2/s]
278   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bri     !: salt flux due to brine rejection                      [PSU/m2/s]
279   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_dyn     !: salt flux due to porous ridged ice formation          [PSU/m2/s]
280   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_res     !: residual salt flux due to correction of ice thickness [PSU/m2/s]
281
282   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_thd     !: ice-ocean heat flux from thermo processes (limthd_dh)
283   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_dyn     !: ice-ocean heat flux from mecanical processes (limitd_me)
284   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_tot     !: total heat flux lost/gained by ice
285   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_spr     !: heat flux of the snow precipitation
286   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_res     !: residual heat flux due to correction of ice thickness
287   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_snw     !: heat flux for snow melt
288   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_sub     !: heat flux for sublimation
289   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err     !: heat flux error after heat diffusion
290   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err_rem !: heat flux error after heat remapping
291   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_in      !: heat flux available for thermo transformations
292   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_out     !: heat flux remaining at the end of thermo transformations
293
294   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ftr_ice     !: transmitted solar radiation under ice
295
296   ! temporary arrays for dummy version of the code
297   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   dh_i_surf2D, dh_i_bott2D, q_s
298
299   !!--------------------------------------------------------------------------
300   !! * Ice global state variables
301   !!--------------------------------------------------------------------------
302   !! Variables defined for each ice category
303   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ht_i    !: Ice thickness (m)
304   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i     !: Ice fractional areas (concentration)
305   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_i     !: Ice volume per unit area (m)
306   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_s     !: Snow volume per unit area(m)
307   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ht_s    !: Snow thickness (m)
308   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t_su    !: Sea-Ice Surface Temperature (K)
309   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sm_i    !: Sea-Ice Bulk salinity (ppt)
310   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   smv_i   !: Sea-Ice Bulk salinity times volume per area (ppt.m)
311   !                                                                  !  this is an extensive variable that has to be transported
312   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   o_i     !: Sea-Ice Age (days)
313   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ov_i    !: Sea-Ice Age times volume per area (days.m)
314   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   oa_i    !: Sea-Ice Age times ice area (days)
315
316   !! Variables summed over all categories, or associated to all the ice in a single grid cell
317   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_ice, v_ice   !: components of the ice velocity (m/s)
318   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tio_u, tio_v   !: components of the ice-ocean stress (N/m2)
319   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   vt_i , vt_s    !: ice and snow total volume per unit area (m)
320   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   at_i           !: ice total fractional area (ice concentration)
321   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ato_i          !: =1-at_i ; total open water fractional area
322   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   et_i , et_s    !: ice and snow total heat content
323   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ot_i           !: mean age over all categories
324   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tm_i           !: mean ice temperature over all categories
325   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bv_i           !: brine volume averaged over all categories
326   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   smt_i          !: mean sea ice salinity averaged over all categories [PSU]
327
328   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   at_i_typ     !: total area   contained in each ice type [m^2]
329   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   vt_i_typ     !: total volume contained in each ice type [m^3]
330
331   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_s        !: Snow temperatures [K]
332   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s        !: Snow ...     
333
334   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   e_i_cat    !: ! go to trash
335     
336   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_i        !: ice temperatures          [K]
337   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i        !: ice thermal contents [Giga J]
338   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   s_i        !: ice salinities          [PSU]
339
340   !!--------------------------------------------------------------------------
341   !! * Moments for advection
342   !!--------------------------------------------------------------------------
343   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   sxopw, syopw, sxxopw, syyopw, sxyopw   !: open water in sea ice
344   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxice, syice, sxxice, syyice, sxyice   !: ice thickness
345   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxsn , sysn , sxxsn , syysn , sxysn    !: snow thickness
346   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxa  , sya  , sxxa  , syya  , sxya     !: lead fraction
347   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxc0 , syc0 , sxxc0 , syyc0 , sxyc0    !: snow thermal content
348   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxsal, sysal, sxxsal, syysal, sxysal   !: ice salinity
349   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxage, syage, sxxage, syyage, sxyage   !: ice age
350   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   sxe  , sye  , sxxe  , syye  , sxye     !: ice layers heat content
351
352   !!--------------------------------------------------------------------------
353   !! * Old values of global variables
354   !!--------------------------------------------------------------------------
355   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   old_v_s, old_v_i               !: snow and ice volumes
356   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   old_a_i, old_smv_i, old_oa_i   !: ???
357   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   old_e_s                        !: snow heat content
358   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   old_e_i                        !: ice temperatures
359   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   old_u_ice, old_v_ice           !: ice velocity (gv6 and gv7)
360     
361
362   !!--------------------------------------------------------------------------
363   !! * Increment of global variables
364   !!--------------------------------------------------------------------------
365   ! thd refers to changes induced by thermodynamics
366   ! trp   ''         ''     ''       advection (transport of ice)
367   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   d_a_i_thd  , d_a_i_trp                 !: icefractions                 
368   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   d_v_s_thd  , d_v_s_trp                 !: snow volume
369   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   d_v_i_thd  , d_v_i_trp                 !: ice  volume
370   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   d_smv_i_thd, d_smv_i_trp               !:     
371   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   d_sm_i_fl  , d_sm_i_gd                 !:
372   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   d_sm_i_se  , d_sm_i_si  , d_sm_i_la    !:
373   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   d_oa_i_thd , d_oa_i_trp , s_i_newice   !:
374
375   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   d_e_s_thd  , d_e_s_trp     !:
376   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   d_e_i_thd  , d_e_i_trp     !:
377   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   d_u_ice_dyn, d_v_ice_dyn   !: ice velocity
378     
379   !!--------------------------------------------------------------------------
380   !! * Ice thickness distribution variables
381   !!--------------------------------------------------------------------------
382   ! REMOVE
383   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   ice_types      !: Vector connecting types and categories
384   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ice_cat_bounds !: Matrix containing the integer upper and
385   !                                                                       !  lower boundaries of ice thickness categories
386   ! REMOVE
387   INTEGER , PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   ice_ncat_types !: nb of thickness categories in each ice type
388   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   hi_max         !: Boundary of ice thickness categories in thickness space
389   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   hi_mean        !: Mean ice thickness in catgories
390   ! REMOVE
391   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hi_max_typ     !: Boundary of ice thickness categories in thickness space
392
393   !!--------------------------------------------------------------------------
394   !! * Ice Run
395   !!--------------------------------------------------------------------------
396   !                                                                     !!: ** Namelist namicerun read in iceini **
397   CHARACTER(len=32)     , PUBLIC ::   cn_icerst_in  = "restart_ice_in"   !: suffix of ice restart name (input)
398   CHARACTER(len=32)     , PUBLIC ::   cn_icerst_out = "restart_ice"      !: suffix of ice restart name (output)
399   LOGICAL               , PUBLIC ::   ln_limdyn     = .TRUE.             !: flag for ice dynamics (T) or not (F)
400   LOGICAL               , PUBLIC ::   ln_nicep      = .FALSE.             !: flag for sea-ice points output (T) or not (F)
401   REAL(wp)              , PUBLIC ::   cai           = 1.4e-3            !: atmospheric drag over sea ice
402   REAL(wp)              , PUBLIC ::   cao           = 1.0e-3            !: atmospheric drag over ocean
403   REAL(wp)              , PUBLIC ::   amax          = 0.99               !: maximum ice concentration
404   !
405   !!--------------------------------------------------------------------------
406   !! * Ice diagnostics
407   !!--------------------------------------------------------------------------
408   !! Check if everything down here is necessary
409   LOGICAL , PUBLIC                                      ::   ln_limdiahsb  = .FALSE. !: flag for ice diag (T) or not (F)
410   LOGICAL , PUBLIC                                      ::   ln_limdiaout  = .FALSE. !: flag for ice diag (T) or not (F)
411   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   dv_dt_thd  !: thermodynamic growth rates
412   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   izero
413   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   diag_trp_vi   ! transport of ice volume
414   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   diag_trp_vs   ! transport of snw volume
415   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   diag_trp_ei   ! transport of ice enthalpy (W/m2)
416   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   diag_trp_es   ! transport of snw enthalpy (W/m2)
417   !
418   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   diag_heat_dhc1    ! snw/ice heat content variation   [W/m2]
419   !
420   INTEGER , PUBLIC ::   jiindx, jjindx        !: indexes of the debugging point
421
422   !!----------------------------------------------------------------------
423   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2010)
424   !! $Id$
425   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
426   !!----------------------------------------------------------------------
427CONTAINS
428
429   FUNCTION ice_alloc()
430      !!-----------------------------------------------------------------
431      !!               *** Routine ice_alloc_2 ***
432      !!-----------------------------------------------------------------
433      INTEGER :: ice_alloc
434      !
435      INTEGER :: ierr(20), ii
436      !!-----------------------------------------------------------------
437
438      ierr(:) = 0
439
440      ! What could be one huge allocate statement is broken-up to try to
441      ! stay within Fortran's max-line length limit.
442      ii = 1
443      ALLOCATE( u_oce    (jpi,jpj) , v_oce    (jpi,jpj) ,                           &
444         &      ahiu     (jpi,jpj) , ahiv     (jpi,jpj) ,                           &
445         &      pahu     (jpi,jpj) , pahv     (jpi,jpj) ,                           &
446         &      ust2s    (jpi,jpj) , hicol    (jpi,jpj) ,                           &
447         &      strp1    (jpi,jpj) , strp2    (jpi,jpj) , strength  (jpi,jpj) ,     &
448         &      stress1_i(jpi,jpj) , stress2_i(jpi,jpj) , stress12_i(jpi,jpj) ,     &
449         &      delta_i  (jpi,jpj) , divu_i   (jpi,jpj) , shear_i   (jpi,jpj) , STAT=ierr(ii) )
450
451      ii = ii + 1
452      ALLOCATE( sist     (jpi,jpj) , icethi (jpi,jpj) , t_bo   (jpi,jpj) ,      &
453         &      frld     (jpi,jpj) , pfrld  (jpi,jpj) , phicif (jpi,jpj) ,      &
454         &      wfx_snw  (jpi,jpj) , wfx_ice(jpi,jpj) , wfx_sub(jpi,jpj) ,    &
455         &      wfx_bog(jpi,jpj)  , wfx_dyn(jpi,jpj) , wfx_bom(jpi,jpj) , wfx_sum(jpi,jpj) ,     &
456         &      wfx_res(jpi,jpj)  , wfx_sni(jpi,jpj) , wfx_opw(jpi,jpj) ,  qlead  (jpi,jpj) ,     &
457         &      fhtur    (jpi,jpj) , ftr_ice(jpi,jpj,jpl) ,      &
458         &      sfx_res  (jpi,jpj) , sfx_bri(jpi,jpj) , sfx_dyn(jpi,jpj) ,      &
459         &      sfx_bog  (jpi,jpj) , sfx_bom  (jpi,jpj) , sfx_sum  (jpi,jpj) ,  sfx_sni  (jpi,jpj) ,  sfx_opw  (jpi,jpj) ,   &
460         &      hfx_res  (jpi,jpj) , hfx_snw  (jpi,jpj) , hfx_sub(jpi,jpj) , hfx_err(jpi,jpj), hfx_err_rem(jpi,jpj), &
461         &      hfx_in   (jpi,jpj) , hfx_out(jpi,jpj) , fhld(jpi,jpj) ,  &
462         &      hfx_tot  (jpi,jpj) , hfx_thd  (jpi,jpj) , hfx_dyn(jpi,jpj) , hfx_spr(jpi,jpj),  STAT=ierr(ii) )
463
464      ii = ii + 1
465      ALLOCATE( dh_i_surf2D(jpi,jpj) , dh_i_bott2D(jpi,jpj) , q_s(jpi,jpj) , STAT=ierr(ii) )
466
467      ! * Ice global state variables
468      ii = ii + 1
469      ALLOCATE( ht_i (jpi,jpj,jpl) , a_i  (jpi,jpj,jpl) , v_i  (jpi,jpj,jpl) ,     &
470         &      v_s  (jpi,jpj,jpl) , ht_s (jpi,jpj,jpl) , t_su (jpi,jpj,jpl) ,     &
471         &      sm_i (jpi,jpj,jpl) , smv_i(jpi,jpj,jpl) , o_i  (jpi,jpj,jpl) ,     &
472         &      ov_i (jpi,jpj,jpl) , oa_i (jpi,jpj,jpl)                      , STAT=ierr(ii) )
473      ii = ii + 1
474      ALLOCATE( u_ice(jpi,jpj) , v_ice(jpi,jpj) , tio_u(jpi,jpj) , tio_v(jpi,jpj) ,     &
475         &      vt_i (jpi,jpj) , vt_s (jpi,jpj) , at_i (jpi,jpj) , ato_i(jpi,jpj) ,     &
476         &      et_i (jpi,jpj) , et_s (jpi,jpj) , ot_i (jpi,jpj) , tm_i (jpi,jpj) ,     &
477         &      bv_i (jpi,jpj) , smt_i(jpi,jpj)                                   , STAT=ierr(ii) )
478      ii = ii + 1
479      ALLOCATE( t_s(jpi,jpj,nlay_s,jpl) , at_i_typ(jpi,jpj,jpm) ,                            &
480         &      e_s(jpi,jpj,nlay_s,jpl) , vt_i_typ(jpi,jpj,jpm) , e_i_cat(jpi,jpj,jpl) , STAT=ierr(ii) )
481      ii = ii + 1
482      ALLOCATE( t_i(jpi,jpj,jkmax,jpl) , e_i(jpi,jpj,jkmax,jpl) , s_i(jpi,jpj,jkmax,jpl) , STAT=ierr(ii) )
483
484      ! * Moments for advection
485      ii = ii + 1
486      ALLOCATE( sxopw(jpi,jpj) , syopw(jpi,jpj) , sxxopw(jpi,jpj) , syyopw(jpi,jpj) , sxyopw(jpi,jpj) , STAT=ierr(ii) )
487      ii = ii + 1
488      ALLOCATE( sxice(jpi,jpj,jpl) , syice(jpi,jpj,jpl) , sxxice(jpi,jpj,jpl) , syyice(jpi,jpj,jpl) , sxyice(jpi,jpj,jpl) ,   &
489         &      sxsn (jpi,jpj,jpl) , sysn (jpi,jpj,jpl) , sxxsn (jpi,jpj,jpl) , syysn (jpi,jpj,jpl) , sxysn (jpi,jpj,jpl) ,   &
490         &      STAT=ierr(ii) )
491      ii = ii + 1
492      ALLOCATE( sxa  (jpi,jpj,jpl) , sya  (jpi,jpj,jpl) , sxxa  (jpi,jpj,jpl) , syya  (jpi,jpj,jpl) , sxya  (jpi,jpj,jpl) ,   &
493         &      sxc0 (jpi,jpj,jpl) , syc0 (jpi,jpj,jpl) , sxxc0 (jpi,jpj,jpl) , syyc0 (jpi,jpj,jpl) , sxyc0 (jpi,jpj,jpl) ,   &
494         &      sxsal(jpi,jpj,jpl) , sysal(jpi,jpj,jpl) , sxxsal(jpi,jpj,jpl) , syysal(jpi,jpj,jpl) , sxysal(jpi,jpj,jpl) ,   &
495         &      sxage(jpi,jpj,jpl) , syage(jpi,jpj,jpl) , sxxage(jpi,jpj,jpl) , syyage(jpi,jpj,jpl) , sxyage(jpi,jpj,jpl) ,   &
496         &      STAT=ierr(ii) )
497      ii = ii + 1
498      ALLOCATE( sxe (jpi,jpj,jkmax,jpl) , sye (jpi,jpj,jkmax,jpl) , sxxe(jpi,jpj,jkmax,jpl) ,     &
499         &      syye(jpi,jpj,jkmax,jpl) , sxye(jpi,jpj,jkmax,jpl)                           , STAT=ierr(ii) )
500
501      ! * Old values of global variables
502      ii = ii + 1
503      ALLOCATE( old_v_s  (jpi,jpj,jpl) , old_v_i  (jpi,jpj,jpl) , old_e_s(jpi,jpj,nlay_s,jpl) ,     &
504         &      old_a_i  (jpi,jpj,jpl) , old_smv_i(jpi,jpj,jpl) , old_e_i(jpi,jpj,jkmax ,jpl) ,     &
505         &      old_oa_i (jpi,jpj,jpl)                                                        ,     &
506         &      old_u_ice(jpi,jpj)     , old_v_ice(jpi,jpj)                                   , STAT=ierr(ii) )
507
508      ! * Increment of global variables
509      ii = ii + 1
510      ALLOCATE( d_a_i_thd(jpi,jpj,jpl) , d_a_i_trp (jpi,jpj,jpl) , d_v_s_thd  (jpi,jpj,jpl) , d_v_s_trp  (jpi,jpj,jpl) ,   &
511         &      d_v_i_thd(jpi,jpj,jpl) , d_v_i_trp (jpi,jpj,jpl) , d_smv_i_thd(jpi,jpj,jpl) , d_smv_i_trp(jpi,jpj,jpl) ,   &     
512         &      d_sm_i_fl(jpi,jpj,jpl) , d_sm_i_gd (jpi,jpj,jpl) , d_sm_i_se  (jpi,jpj,jpl) , d_sm_i_si  (jpi,jpj,jpl) ,   &
513         &      d_sm_i_la(jpi,jpj,jpl) , d_oa_i_thd(jpi,jpj,jpl) , d_oa_i_trp (jpi,jpj,jpl) , s_i_newice (jpi,jpj,jpl) ,   &
514         &     STAT=ierr(ii) )
515      ii = ii + 1
516      ALLOCATE( d_e_s_thd(jpi,jpj,nlay_s,jpl) , d_e_i_thd(jpi,jpj,jkmax,jpl) , d_u_ice_dyn(jpi,jpj) ,     &
517         &      d_e_s_trp(jpi,jpj,nlay_s,jpl) , d_e_i_trp(jpi,jpj,jkmax,jpl) , d_v_ice_dyn(jpi,jpj) , STAT=ierr(ii) )
518     
519      ! * Ice thickness distribution variables
520      ii = ii + 1
521      ALLOCATE( ice_types(jpl) , ice_cat_bounds(jpm,2) , ice_ncat_types  (jpm) ,     &
522         &      hi_max (0:jpl) , hi_mean(jpl)          , hi_max_typ(0:jpl,jpm) , STAT=ierr(ii) )
523
524      ! * Ice diagnostics
525      ii = ii + 1
526      ALLOCATE( dv_dt_thd(jpi,jpj,jpl) ,     &
527         &      izero    (jpi,jpj,jpl)  , diag_trp_vi(jpi,jpj) , diag_trp_vs(jpi,jpj), diag_trp_ei(jpi,jpj), diag_trp_es(jpi,jpj),     & 
528         &      diag_heat_dhc1(jpi,jpj) ,  STAT=ierr(ii) )
529
530      ice_alloc = MAXVAL( ierr(:) )
531      IF( ice_alloc /= 0 )   CALL ctl_warn('ice_alloc_2: failed to allocate arrays.')
532      !
533   END FUNCTION ice_alloc
534
535#else
536   !!----------------------------------------------------------------------
537   !!   Default option         Empty module            NO LIM sea-ice model
538   !!----------------------------------------------------------------------
539#endif
540
541   !!======================================================================
542END MODULE ice
Note: See TracBrowser for help on using the repository browser.