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/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2016/dev_v3_6_STABLE_r6506_AGRIF_LIM3/NEMOGCM/NEMO/LIM_SRC_3/ice.F90 @ 6629

Last change on this file since 6629 was 6629, checked in by clem, 8 years ago

debug thickness diffusion

  • Property svn:keywords set to Id
File size: 41.6 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 in_out_manager ! I/O manager
14   USE lib_mpp        ! MPP library
15
16   IMPLICIT NONE
17   PRIVATE
18
19   PUBLIC    ice_alloc  !  Called in sbc_lim_init
20
21   !!======================================================================
22   !! LIM3 by the use of sweat, agile fingers and sometimes brain juice,
23   !!  was developed in Louvain-la-Neuve by :
24   !!    * Martin Vancoppenolle (UCL-ASTR, Belgium)
25   !!    * Sylvain Bouillon (UCL-ASTR, Belgium)
26   !!    * Miguel Angel Morales Maqueda (NOC-L, UK)
27   !!
28   !! Based on extremely valuable earlier work by
29   !!    * Thierry Fichefet
30   !!    * Hugues Goosse
31   !!
32   !! The following persons also contributed to the code in various ways
33   !!    * Gurvan Madec, Claude Talandier, Christian Ethe (LOCEAN, France)
34   !!    * Xavier Fettweis (UCL-ASTR), Ralph Timmermann (AWI, Germany)
35   !!    * Bill Lipscomb (LANL), Cecilia Bitz (UWa)
36   !!      and Elisabeth Hunke (LANL), USA.
37   !!
38   !! For more info, the interested user is kindly invited to consult the following references
39   !!    For model description and validation :
40   !!    * Vancoppenolle et al., Ocean Modelling, 2008a.
41   !!    * Vancoppenolle et al., Ocean Modelling, 2008b.
42   !!    For a specific description of EVP :
43   !!    * Bouillon et al., Ocean Modelling 2009.
44   !!
45   !!    Or the reference manual, that should be available by 2011
46   !!======================================================================
47   !!                                                                     |
48   !!              I C E   S T A T E   V A R I A B L E S                  |
49   !!                                                                     |
50   !! Introduction :                                                      |
51   !! --------------                                                      |
52   !! Every ice-covered grid cell is characterized by a series of state   |
53   !! variables. To account for unresolved spatial variability in ice     |
54   !! thickness, the ice cover in divided in ice thickness categories.    |
55   !!                                                                     |
56   !! Sea ice state variables depend on the ice thickness category        |
57   !!                                                                     |
58   !! Those variables are divided into two groups                         |
59   !! * Extensive (or global) variables.                                  |
60   !!   These are the variables that are transported by all means         |
61   !! * Intensive (or equivalent) variables.                              |
62   !!   These are the variables that are either physically more           |
63   !!   meaningful and/or used in ice thermodynamics                      |
64   !!                                                                     |
65   !! Routines in limvar.F90 perform conversions                          |
66   !!  - lim_var_glo2eqv  : from global to equivalent variables           |
67   !!  - lim_var_eqv2glo  : from equivalent to global variables           |
68   !!                                                                     |
69   !! For various purposes, the sea ice state variables have sometimes    |
70   !! to be aggregated over all ice thickness categories. This operation  |
71   !! is done in :                                                        |
72   !!  - lim_var_agg                                                      |
73   !!                                                                     |
74   !! in icestp.F90, the routines that compute the changes in the ice     |
75   !! state variables are called                                          |
76   !! - lim_dyn : ice dynamics                                            |
77   !! - lim_trp : ice transport                                           |
78   !! - lim_itd_me : mechanical redistribution (ridging and rafting)      |
79   !! - lim_thd : ice halo-thermodynamics                                 |
80   !! - lim_itd_th : thermodynamic changes in ice thickness distribution  |
81   !!                and creation of new ice                              |
82   !!                                                                     |
83   !! See the associated routines for more information                    |
84   !!                                                                     |
85   !! List of ice state variables :                                       |
86   !! -----------------------------                                       |
87   !!                                                                     |
88   !!-------------|-------------|---------------------------------|-------|
89   !!   name in   |   name in   |              meaning            | units |
90   !! 2D routines | 1D routines |                                 |       |
91   !!-------------|-------------|---------------------------------|-------|
92   !!                                                                     |
93   !! ******************************************************************* |
94   !! ***         Dynamical variables (prognostic)                    *** |
95   !! ******************************************************************* |
96   !!                                                                     |
97   !! u_ice       |      -      |    Comp. U of the ice velocity  | m/s   |
98   !! v_ice       |      -      |    Comp. V of the ice velocity  | m/s   |
99   !!                                                                     |
100   !! ******************************************************************* |
101   !! ***         Category dependent state variables (prognostic)     *** |
102   !! ******************************************************************* |
103   !!                                                                     |
104   !! ** Global variables                                                 |
105   !!-------------|-------------|---------------------------------|-------|
106   !! a_i         | a_i_1d      |    Ice concentration            |       |
107   !! v_i         |      -      |    Ice volume per unit area     | m     |
108   !! v_s         |      -      |    Snow volume per unit area    | m     |
109   !! smv_i       |      -      |    Sea ice salt content         | ppt.m |
110   !! oa_i        !      -      !    Sea ice areal age content    | day   |
111   !! e_i         !      -      !    Ice enthalpy                 | J/m2  |
112   !!      -      ! q_i_1d      !    Ice enthalpy per unit vol.   | J/m3  |
113   !! e_s         !      -      !    Snow enthalpy                | J/m2  |
114   !!      -      ! q_s_1d      !    Snow enthalpy per unit vol.  | J/m3  |
115   !!                                                                     |
116   !!-------------|-------------|---------------------------------|-------|
117   !!                                                                     |
118   !! ** Equivalent variables                                             |
119   !!-------------|-------------|---------------------------------|-------|
120   !!                                                                     |
121   !! ht_i        | ht_i_1d     |    Ice thickness                | m     |
122   !! ht_s        ! ht_s_1d     |    Snow depth                   | m     |
123   !! sm_i        ! sm_i_1d     |    Sea ice bulk salinity        ! ppt   |
124   !! s_i         ! s_i_1d      |    Sea ice salinity profile     ! ppt   |
125   !! o_i         !      -      |    Sea ice Age                  ! days  |
126   !! t_i         ! t_i_1d      |    Sea ice temperature          ! K     |
127   !! t_s         ! t_s_1d      |    Snow temperature             ! K     |
128   !! t_su        ! t_su_1d     |    Sea ice surface temperature  ! K     |
129   !!                                                                     |
130   !! notes: the ice model only sees a bulk (i.e., vertically averaged)   |
131   !!        salinity, except in thermodynamic computations, for which    |
132   !!        the salinity profile is computed as a function of bulk       |
133   !!        salinity                                                     |
134   !!                                                                     |
135   !!        the sea ice surface temperature is not associated to any     |
136   !!        heat content. Therefore, it is not a state variable and      |
137   !!        does not have to be advected. Nevertheless, it has to be     |
138   !!        computed to determine whether the ice is melting or not      |
139   !!                                                                     |
140   !! ******************************************************************* |
141   !! ***         Category-summed state variables (diagnostic)        *** |
142   !! ******************************************************************* |
143   !! at_i        | at_i_1d     |    Total ice concentration      |       |
144   !! vt_i        |      -      |    Total ice vol. per unit area | m     |
145   !! vt_s        |      -      |    Total snow vol. per unit ar. | m     |
146   !! smt_i       |      -      |    Mean sea ice salinity        | ppt   |
147   !! tm_i        |      -      |    Mean sea ice temperature     | K     |
148   !! et_i        !      -      !    Total ice enthalpy           | J/m2  |
149   !! et_s        !      -      !    Total snow enthalpy          | J/m2  |
150   !! bv_i        !      -      !    relative brine volume        | ???   |
151   !!=====================================================================
152
153   LOGICAL, PUBLIC ::   con_i = .false.   ! switch for conservation test
154
155   !!--------------------------------------------------------------------------
156   !! * Share Module variables
157   !!--------------------------------------------------------------------------
158   !                                     !!** ice-generic parameters namelist (namicerun) **
159   INTEGER           , PUBLIC ::   jpl             !: number of ice  categories
160   INTEGER           , PUBLIC ::   nlay_i          !: number of ice  layers
161   INTEGER           , PUBLIC ::   nlay_s          !: number of snow layers
162   REAL(wp)          , PUBLIC ::   rn_amax_n       !: maximum ice concentration Northern hemisphere
163   REAL(wp)          , PUBLIC ::   rn_amax_s       !: maximum ice concentration Southern hemisphere
164   CHARACTER(len=32) , PUBLIC ::   cn_icerst_in    !: suffix of ice restart name (input)
165   CHARACTER(len=32) , PUBLIC ::   cn_icerst_out   !: suffix of ice restart name (output)
166   CHARACTER(len=256), PUBLIC ::   cn_icerst_indir !: ice restart input directory
167   CHARACTER(len=256), PUBLIC ::   cn_icerst_outdir!: ice restart output directory
168   LOGICAL           , PUBLIC ::   ln_limthd       !: flag for ice thermo (T) or not (F)
169   LOGICAL           , PUBLIC ::   ln_limdyn       !: flag for ice dynamics (T) or not (F)
170   INTEGER           , PUBLIC ::   nn_limdyn       !: flag for ice dynamics
171   REAL(wp)          , PUBLIC ::   rn_uice         !: prescribed u-vel (case nn_limdyn=0)
172   REAL(wp)          , PUBLIC ::   rn_vice         !: prescribed v-vel (case nn_limdyn=0)
173   
174   !                                     !!** ice-diagnostics namelist (namicediag) **
175   LOGICAL , PUBLIC ::   ln_limdiahsb     !: flag for ice diag (T) or not (F)
176   LOGICAL , PUBLIC ::   ln_limdiaout     !: flag for ice diag (T) or not (F)
177   LOGICAL , PUBLIC ::   ln_icectl        !: flag for sea-ice points output (T) or not (F)
178   INTEGER , PUBLIC ::   iiceprt          !: debug i-point
179   INTEGER , PUBLIC ::   jiceprt          !: debug j-point
180
181   !                                     !!** ice-init namelist (namiceini) **
182                                          ! -- limistate -- !
183   LOGICAL , PUBLIC ::   ln_limini        ! initialization or not
184   LOGICAL , PUBLIC ::   ln_limini_file   ! Ice initialization state from 2D netcdf file
185   REAL(wp), PUBLIC ::   rn_thres_sst     ! threshold water temperature for initial sea ice
186   REAL(wp), PUBLIC ::   rn_hts_ini_n     ! initial snow thickness in the north
187   REAL(wp), PUBLIC ::   rn_hts_ini_s     ! initial snow thickness in the south
188   REAL(wp), PUBLIC ::   rn_hti_ini_n     ! initial ice thickness in the north
189   REAL(wp), PUBLIC ::   rn_hti_ini_s     ! initial ice thickness in the south
190   REAL(wp), PUBLIC ::   rn_ati_ini_n     ! initial leads area in the north
191   REAL(wp), PUBLIC ::   rn_ati_ini_s     ! initial leads area in the south
192   REAL(wp), PUBLIC ::   rn_smi_ini_n     ! initial salinity
193   REAL(wp), PUBLIC ::   rn_smi_ini_s     ! initial salinity
194   REAL(wp), PUBLIC ::   rn_tmi_ini_n     ! initial temperature
195   REAL(wp), PUBLIC ::   rn_tmi_ini_s     ! initial temperature
196   
197   !                                     !!** ice-thickness distribution namelist (namiceitd) **
198   INTEGER , PUBLIC ::   nn_catbnd        !: categories distribution following: tanh function (1), or h^(-alpha) function (2)
199   REAL(wp), PUBLIC ::   rn_himean        !: mean thickness of the domain (used to compute the distribution, nn_itdshp = 2 only)
200
201   !                                     !!** ice-dynamics namelist (namicedyn) **
202                                          ! -- limitd_me -- !
203   INTEGER , PUBLIC ::   nn_icestr        !: ice strength parameterization (0=Hibler79 1=Rothrock75)
204   REAL(wp), PUBLIC ::   rn_pe_rdg        !: ridging work divided by pot. energy change in ridging, nn_icestr = 1
205   REAL(wp), PUBLIC ::   rn_pstar         !: determines ice strength (N/M), Hibler JPO79
206   REAL(wp), PUBLIC ::   rn_crhg          !: determines changes in ice strength
207   LOGICAL , PUBLIC ::   ln_icestr_bvf    !: use brine volume to diminish ice strength
208                                          ! -- limdyn & limrhg -- !
209   REAL(wp), PUBLIC ::   rn_cio           !: drag coefficient for oceanic stress
210   REAL(wp), PUBLIC ::   rn_creepl        !: creep limit : has to be under 1.0e-9
211   REAL(wp), PUBLIC ::   rn_ecc           !: eccentricity of the elliptical yield curve
212   INTEGER , PUBLIC ::   nn_nevp          !: number of iterations for subcycling
213   REAL(wp), PUBLIC ::   rn_relast        !: ratio => telast/rdt_ice (1/3 or 1/9 depending on nb of subcycling nevp)
214
215   !                                     !!** ice-diffusion namelist (namicehdf) **
216   INTEGER , PUBLIC ::   nn_ahi0          !: sea-ice hor. eddy diffusivity coeff. (3 ways of calculation)
217   REAL(wp), PUBLIC ::   rn_ahi0_ref      !: sea-ice hor. eddy diffusivity coeff. (m2/s)
218
219   !                                     !!** ice-thermodynamics namelist (namicethd) **
220                                          ! -- limthd_dif -- !
221   REAL(wp), PUBLIC ::   rn_kappa_i       !: coef. for the extinction of radiation Grenfell et al. (2006) [1/m]
222   REAL(wp), PUBLIC ::   nn_conv_dif      !: maximal number of iterations for heat diffusion
223   REAL(wp), PUBLIC ::   rn_terr_dif      !: maximal tolerated error (C) for heat diffusion
224   INTEGER , PUBLIC ::   nn_ice_thcon     !: thermal conductivity: =0 Untersteiner (1964) ; =1 Pringle et al (2007)
225   LOGICAL , PUBLIC ::   ln_it_qnsice     !: iterate surface flux with changing surface temperature or not (F)
226   INTEGER , PUBLIC ::   nn_monocat       !: virtual ITD mono-category parameterizations (1) or not (0)
227                                          ! -- limthd_dh -- !
228   LOGICAL , PUBLIC ::   ln_limdH         !: activate ice thickness change from growing/melting (T) or not (F)
229   REAL(wp), PUBLIC ::   rn_betas         !: coef. for partitioning of snowfall between leads and sea ice
230                                          ! -- limthd_da -- !
231   LOGICAL , PUBLIC ::   ln_limdA         !: activate lateral melting param. (T) or not (F)
232   REAL(wp), PUBLIC ::   rn_beta          !: coef. beta for lateral melting param.
233   REAL(wp), PUBLIC ::   rn_dmin          !: minimum floe diameter for lateral melting param.
234                                          ! -- limthd_lac -- !
235   LOGICAL , PUBLIC ::   ln_limdO         !: activate ice growth in open-water (T) or not (F)
236   REAL(wp), PUBLIC ::   rn_hnewice       !: thickness for new ice formation (m)
237   LOGICAL , PUBLIC ::   ln_frazil        !: use of frazil ice collection as function of wind (T) or not (F)
238   REAL(wp), PUBLIC ::   rn_maxfrazb      !: maximum portion of frazil ice collecting at the ice bottom
239   REAL(wp), PUBLIC ::   rn_vfrazb        !: threshold drift speed for collection of bottom frazil ice
240   REAL(wp), PUBLIC ::   rn_Cfrazb        !: squeezing coefficient for collection of bottom frazil ice
241                                          ! -- limitd_th -- !
242   REAL(wp), PUBLIC ::   rn_himin         !: minimum ice thickness
243
244   !                                     !!** ice-salinity namelist (namicesal) **
245   LOGICAL , PUBLIC ::   ln_limdS         !: activate gravity drainage and flushing (T) or not (F)
246   INTEGER , PUBLIC ::   nn_icesal        !: salinity configuration used in the model
247   !                                      ! 1 - constant salinity in both space and time
248   !                                      ! 2 - prognostic salinity (s(z,t))
249   !                                      ! 3 - salinity profile, constant in time
250   REAL(wp), PUBLIC ::   rn_icesal        !: bulk salinity (ppt) in case of constant salinity
251   REAL(wp), PUBLIC ::   rn_sal_gd        !: restoring salinity for gravity drainage [PSU]
252   REAL(wp), PUBLIC ::   rn_time_gd       !: restoring time constant for gravity drainage (= 20 days) [s]
253   REAL(wp), PUBLIC ::   rn_sal_fl        !: restoring salinity for flushing [PSU]
254   REAL(wp), PUBLIC ::   rn_time_fl       !: restoring time constant for gravity drainage (= 10 days) [s]
255   REAL(wp), PUBLIC ::   rn_simax         !: maximum ice salinity [PSU]
256   REAL(wp), PUBLIC ::   rn_simin         !: minimum ice salinity [PSU]
257
258   !                                     !!** ice-mechanical redistribution namelist (namiceitdme)
259   REAL(wp), PUBLIC ::   rn_cs            !: fraction of shearing energy contributing to ridging           
260   INTEGER , PUBLIC ::   nn_partfun       !: participation function: =0 Thorndike et al. (1975), =1 Lipscomb et al. (2007)
261   REAL(wp), PUBLIC ::   rn_gstar         !: fractional area of young ice contributing to ridging
262   REAL(wp), PUBLIC ::   rn_astar         !: equivalent of G* for an exponential participation function
263   LOGICAL , PUBLIC ::   ln_ridging       !: ridging of ice or not                       
264   REAL(wp), PUBLIC ::   rn_hstar         !: thickness that determines the maximal thickness of ridged ice
265   REAL(wp), PUBLIC ::   rn_por_rdg       !: initial porosity of ridges (0.3 regular value)
266   REAL(wp), PUBLIC ::   rn_fsnowrdg      !: fractional snow loss to the ocean during ridging
267   LOGICAL , PUBLIC ::   ln_rafting       !: rafting of ice or not                       
268   REAL(wp), PUBLIC ::   rn_hraft         !: threshold thickness (m) for rafting / ridging
269   REAL(wp), PUBLIC ::   rn_craft         !: coefficient for smoothness of the hyperbolic tangent in rafting
270   REAL(wp), PUBLIC ::   rn_fsnowrft      !: fractional snow loss to the ocean during ridging
271
272   !                                     !!** some other parameters
273   INTEGER , PUBLIC ::   nstart           !: iteration number of the begining of the run
274   INTEGER , PUBLIC ::   nlast            !: iteration number of the end of the run
275   INTEGER , PUBLIC ::   nitrun           !: number of iteration
276   INTEGER , PUBLIC ::   numit            !: iteration number
277   REAL(wp), PUBLIC ::   rdt_ice          !: ice time step
278   REAL(wp), PUBLIC ::   r1_rdtice        !: = 1. / rdt_ice
279   REAL(wp), PUBLIC ::   usecc2           !:  = 1.0 / ( rn_ecc * rn_ecc )
280   REAL(wp), PUBLIC ::   rhoco            !: = rau0 * cio
281   REAL(wp), PUBLIC ::   r1_nlay_i        !: 1 / nlay_i
282   REAL(wp), PUBLIC ::   r1_nlay_s        !: 1 / nlay_s
283   REAL(wp), PUBLIC ::   rswitch          !: switch for the presence of ice (1) or not (0)
284   REAL(wp), PUBLIC, PARAMETER ::   epsi06   = 1.e-06_wp  !: small number
285   REAL(wp), PUBLIC, PARAMETER ::   epsi10   = 1.e-10_wp  !: small number
286   REAL(wp), PUBLIC, PARAMETER ::   epsi20   = 1.e-20_wp  !: small number
287
288   !                                     !!** define arrays
289   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_oce, v_oce !: surface ocean velocity used in ice dynamics
290   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ahiu , ahiv !: hor. diffusivity coeff. at U- and V-points [m2/s]
291   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hicol       !: ice collection thickness accreted in leads
292   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   strength    !: ice strength
293   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   stress1_i, stress2_i, stress12_i   !: 1st, 2nd & diagonal stress tensor element
294   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   delta_i     !: ice rheology elta factor (Flato & Hibler 95) [s-1]
295   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   divu_i      !: Divergence of the velocity field [s-1]
296   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   shear_i     !: Shear of the velocity field [s-1]
297   !
298   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sist        !: Average Sea-Ice Surface Temperature [Kelvin]
299   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   t_bo        !: Sea-Ice bottom temperature [Kelvin]     
300   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   frld        !: Leads fraction = 1 - ice fraction
301   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   pfrld       !: Leads fraction at previous time 
302   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   phicif      !: Old ice thickness
303   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qlead       !: heat balance of the lead (or of the open ocean)
304   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fhtur       !: net downward heat flux from the ice to the ocean
305   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fhld        !: heat flux from the lead used for bottom melting
306
307   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw     !: snow-ocean mass exchange   [kg.m-2.s-1]
308   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_spr     !: snow precipitation on ice  [kg.m-2.s-1]
309   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sub     !: snow/ice sublimation       [kg.m-2.s-1]
310
311   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_ice     !: ice-ocean mass exchange                   [kg.m-2.s-1]
312   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sni     !: snow ice growth component of wfx_ice      [kg.m-2.s-1]
313   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_opw     !: lateral ice growth component of wfx_ice   [kg.m-2.s-1]
314   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_bog     !: bottom ice growth component of wfx_ice    [kg.m-2.s-1]
315   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_dyn     !: dynamical ice growth component of wfx_ice [kg.m-2.s-1]
316   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_bom     !: bottom melt component of wfx_ice          [kg.m-2.s-1]
317   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sum     !: surface melt component of wfx_ice         [kg.m-2.s-1]
318   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_lam     !: lateral melt component of wfx_ice         [kg.m-2.s-1]
319   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_res     !: residual component of wfx_ice             [kg.m-2.s-1]
320
321   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   afx_tot     !: ice concentration tendency (total)          [s-1]
322   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   afx_thd     !: ice concentration tendency (thermodynamics) [s-1]
323   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   afx_dyn     !: ice concentration tendency (dynamics)       [s-1]
324
325   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bog     !: salt flux due to ice growth/melt                      [PSU/m2/s]
326   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bom     !: salt flux due to ice growth/melt                      [PSU/m2/s]
327   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_lam     !: salt flux due to ice growth/melt                      [PSU/m2/s]
328   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sum     !: salt flux due to ice growth/melt                      [PSU/m2/s]
329   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sni     !: salt flux due to ice growth/melt                      [PSU/m2/s]
330   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_opw     !: salt flux due to ice growth/melt                      [PSU/m2/s]
331   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bri     !: salt flux due to brine rejection                      [PSU/m2/s]
332   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_dyn     !: salt flux due to porous ridged ice formation          [PSU/m2/s]
333   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_res     !: residual salt flux due to correction of ice thickness [PSU/m2/s]
334
335   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sub     !: salt flux due to ice sublimation
336
337   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_bog     !: total heat flux causing bottom ice growth        [W.m-2]
338   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_bom     !: total heat flux causing bottom ice melt          [W.m-2]
339   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_sum     !: total heat flux causing surface ice melt         [W.m-2]
340   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_opw     !: total heat flux causing open water ice formation [W.m-2]
341   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_dif     !: total heat flux causing Temp change in the ice   [W.m-2]
342   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_snw     !: heat flux for snow melt                          [W.m-2]
343   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err     !: heat flux error after heat diffusion             [W.m-2]
344   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err_dif !: heat flux remaining due to change in non-solar flux [W.m-2]
345   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err_rem !: heat flux error after heat remapping             [W.m-2]
346   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_in      !: heat flux available for thermo transformations   [W.m-2]
347   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_out     !: heat flux remaining at the end of thermo transformations  [W.m-2]
348   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_err_sub !: mass flux error after sublimation [kg.m-2.s-1]
349   
350   ! heat flux associated with ice-atmosphere mass exchange
351   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_sub     !: heat flux for sublimation  [W.m-2]
352   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_spr     !: heat flux of the snow precipitation  [W.m-2]
353
354   ! heat flux associated with ice-ocean mass exchange
355   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_thd     !: ice-ocean heat flux from thermo processes (limthd_dh)  [W.m-2]
356   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_dyn     !: ice-ocean heat flux from mecanical processes (limitd_me)  [W.m-2]
357   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_res     !: residual heat flux due to correction of ice thickness [W.m-2]
358
359   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rn_amax_2d     !: maximum ice concentration 2d array
360   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ftr_ice        !: transmitted solar radiation under ice
361   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   pahu3D, pahv3D !: ice hor. eddy diffusivity coef. at U- and V-points
362
363   !!--------------------------------------------------------------------------
364   !! * Ice global state variables
365   !!--------------------------------------------------------------------------
366   !! Variables defined for each ice category
367   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ht_i      !: Ice thickness (m)
368   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i       !: Ice fractional areas (concentration)
369   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_i       !: Ice volume per unit area (m)
370   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_s       !: Snow volume per unit area(m)
371   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ht_s      !: Snow thickness (m)
372   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t_su      !: Sea-Ice Surface Temperature (K)
373   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sm_i      !: Sea-Ice Bulk salinity (ppt)
374   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   smv_i     !: Sea-Ice Bulk salinity times volume per area (ppt.m)
375   !                                                                    !  this is an extensive variable that has to be transported
376   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   o_i       !: Sea-Ice Age (days)
377   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ov_i      !: Sea-Ice Age times volume per area (days.m)
378   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   oa_i      !: Sea-Ice Age times ice area (days)
379   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   bv_i      !: brine volume
380
381   !! Variables summed over all categories, or associated to all the ice in a single grid cell
382   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_ice, v_ice !: components of the ice velocity (m/s)
383   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tio_u, tio_v !: components of the ice-ocean stress (N/m2)
384   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   vt_i , vt_s  !: ice and snow total volume per unit area (m)
385   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   at_i         !: ice total fractional area (ice concentration)
386   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ato_i        !: =1-at_i ; total open water fractional area
387   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   et_i , et_s  !: ice and snow total heat content
388   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tm_i         !: mean ice temperature over all categories
389   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bvm_i        !: brine volume averaged over all categories
390   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   smt_i        !: mean sea ice salinity averaged over all categories [PSU]
391   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tm_su        !: mean surface temperature over all categories
392   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   htm_i        !: mean ice  thickness over all categories
393   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   htm_s        !: mean snow thickness over all categories
394   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   om_i         !: mean ice age over all categories
395
396   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_s      !: Snow temperatures [K]
397   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s      !: Snow ...     
398     
399   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_i      !: ice temperatures          [K]
400   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i      !: ice thermal contents    [J/m2]
401   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   s_i      !: ice salinities          [PSU]
402
403   !!--------------------------------------------------------------------------
404   !! * Moments for advection
405   !!--------------------------------------------------------------------------
406   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   sxopw, syopw, sxxopw, syyopw, sxyopw   !: open water in sea ice
407   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxice, syice, sxxice, syyice, sxyice   !: ice thickness
408   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxsn , sysn , sxxsn , syysn , sxysn    !: snow thickness
409   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxa  , sya  , sxxa  , syya  , sxya     !: lead fraction
410   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxc0 , syc0 , sxxc0 , syyc0 , sxyc0    !: snow thermal content
411   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxsal, sysal, sxxsal, syysal, sxysal   !: ice salinity
412   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxage, syage, sxxage, syyage, sxyage   !: ice age
413   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   sxe  , sye  , sxxe  , syye  , sxye     !: ice layers heat content
414
415   !!--------------------------------------------------------------------------
416   !! * Old values of global variables
417   !!--------------------------------------------------------------------------
418   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_s_b, v_i_b               !: snow and ice volumes
419   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_i_b, smv_i_b, oa_i_b     !:
420   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s_b                      !: snow heat content
421   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i_b                      !: ice temperatures
422   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   u_ice_b, v_ice_b           !: ice velocity
423           
424   !!--------------------------------------------------------------------------
425   !! * Ice thickness distribution variables
426   !!--------------------------------------------------------------------------
427   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   hi_max         !: Boundary of ice thickness categories in thickness space
428   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   hi_mean        !: Mean ice thickness in catgories
429   !
430   !!--------------------------------------------------------------------------
431   !! * Ice diagnostics
432   !!--------------------------------------------------------------------------
433   ! thd refers to changes induced by thermodynamics
434   ! trp   ''         ''     ''       advection (transport of ice)
435   !
436   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_vi   !: transport of ice volume
437   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_vs   !: transport of snw volume
438   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_ei   !: transport of ice enthalpy (W/m2)
439   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_es   !: transport of snw enthalpy (W/m2)
440   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_smv  !: transport of salt content
441   !
442   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_heat     !: snw/ice heat content variation   [W/m2]
443   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_smvi     !: ice salt content variation   []
444   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_vice     !: ice volume variation   [m/s]
445   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_vsnw     !: snw volume variation   [m/s]
446   !
447   !!----------------------------------------------------------------------
448   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2010)
449   !! $Id$
450   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
451   !!----------------------------------------------------------------------
452CONTAINS
453
454   FUNCTION ice_alloc()
455      !!-----------------------------------------------------------------
456      !!               *** Routine ice_alloc_2 ***
457      !!-----------------------------------------------------------------
458      INTEGER :: ice_alloc
459      !
460      INTEGER :: ierr(15), ii
461      !!-----------------------------------------------------------------
462
463      ierr(:) = 0
464
465      ! What could be one huge allocate statement is broken-up to try to
466      ! stay within Fortran's max-line length limit.
467      ii = 1
468      ALLOCATE( u_oce    (jpi,jpj) , v_oce    (jpi,jpj) , ahiu      (jpi,jpj) , ahiv     (jpi,jpj) ,  &
469         &      hicol    (jpi,jpj) , strength (jpi,jpj) ,                                             &
470         &      stress1_i(jpi,jpj) , stress2_i(jpi,jpj) , stress12_i(jpi,jpj) ,                       &
471         &      delta_i  (jpi,jpj) , divu_i   (jpi,jpj) , shear_i   (jpi,jpj) , STAT=ierr(ii) )
472
473      ii = ii + 1
474      ALLOCATE( sist   (jpi,jpj) , t_bo   (jpi,jpj) ,                                           &
475         &      frld   (jpi,jpj) , pfrld  (jpi,jpj) , phicif (jpi,jpj) ,                        &
476         &      wfx_snw(jpi,jpj) , wfx_ice(jpi,jpj) , wfx_sub(jpi,jpj) , wfx_lam(jpi,jpj) ,     &
477         &      wfx_bog(jpi,jpj) , wfx_dyn(jpi,jpj) , wfx_bom(jpi,jpj) , wfx_sum(jpi,jpj) ,     &
478         &      wfx_res(jpi,jpj) , wfx_sni(jpi,jpj) , wfx_opw(jpi,jpj) , wfx_spr(jpi,jpj) ,     &
479         &      afx_tot(jpi,jpj) , afx_thd(jpi,jpj),  afx_dyn(jpi,jpj) , rn_amax_2d(jpi,jpj),   &
480         &      fhtur  (jpi,jpj) , qlead  (jpi,jpj) ,                                           &
481         &      sfx_res(jpi,jpj) , sfx_bri(jpi,jpj) , sfx_dyn(jpi,jpj) , sfx_sub(jpi,jpj) , sfx_lam(jpi,jpj) ,  &
482         &      sfx_bog(jpi,jpj) , sfx_bom(jpi,jpj) , sfx_sum(jpi,jpj) , sfx_sni(jpi,jpj) , sfx_opw(jpi,jpj) ,  &
483         &      hfx_res(jpi,jpj) , hfx_snw(jpi,jpj) , hfx_sub(jpi,jpj) , hfx_err(jpi,jpj) ,     & 
484         &      hfx_in (jpi,jpj) , hfx_out(jpi,jpj) , fhld   (jpi,jpj) ,                        &
485         &      hfx_sum(jpi,jpj) , hfx_bom(jpi,jpj) , hfx_bog(jpi,jpj) , hfx_dif(jpi,jpj) ,     &
486         &      hfx_opw(jpi,jpj) , hfx_thd(jpi,jpj) , hfx_dyn(jpi,jpj) , hfx_spr(jpi,jpj) ,     &
487         &      hfx_err_dif(jpi,jpj) , hfx_err_rem(jpi,jpj) , wfx_err_sub(jpi,jpj)        ,  STAT=ierr(ii) )
488
489      ! * Ice global state variables
490      ii = ii + 1
491      ALLOCATE( ftr_ice(jpi,jpj,jpl) , pahu3D(jpi,jpj,jpl+1) , pahv3D(jpi,jpj,jpl+1) , &
492         &      ht_i   (jpi,jpj,jpl) , a_i   (jpi,jpj,jpl) , v_i   (jpi,jpj,jpl) ,     &
493         &      v_s    (jpi,jpj,jpl) , ht_s  (jpi,jpj,jpl) , t_su  (jpi,jpj,jpl) ,     &
494         &      sm_i   (jpi,jpj,jpl) , smv_i (jpi,jpj,jpl) , o_i   (jpi,jpj,jpl) ,     &
495         &      ov_i   (jpi,jpj,jpl) , oa_i  (jpi,jpj,jpl) , bv_i  (jpi,jpj,jpl) ,  STAT=ierr(ii) )
496      ii = ii + 1
497      ALLOCATE( u_ice(jpi,jpj) , v_ice(jpi,jpj) , tio_u(jpi,jpj) , tio_v(jpi,jpj) ,     &
498         &      vt_i (jpi,jpj) , vt_s (jpi,jpj) , at_i (jpi,jpj) , ato_i(jpi,jpj) ,     &
499         &      et_i (jpi,jpj) , et_s (jpi,jpj) , tm_i (jpi,jpj) , bvm_i(jpi,jpj) ,     &
500         &      smt_i(jpi,jpj) , tm_su(jpi,jpj) , htm_i(jpi,jpj) , htm_s(jpi,jpj) , om_i(jpi,jpj) , STAT=ierr(ii) )
501      ii = ii + 1
502      ALLOCATE( t_s(jpi,jpj,nlay_s,jpl) , e_s(jpi,jpj,nlay_s,jpl) , STAT=ierr(ii) )
503      ii = ii + 1
504      ALLOCATE( t_i(jpi,jpj,nlay_i,jpl) , e_i(jpi,jpj,nlay_i,jpl) , s_i(jpi,jpj,nlay_i,jpl) , STAT=ierr(ii) )
505
506      ! * Moments for advection
507      ii = ii + 1
508      ALLOCATE( sxopw(jpi,jpj) , syopw(jpi,jpj) , sxxopw(jpi,jpj) , syyopw(jpi,jpj) , sxyopw(jpi,jpj) , STAT=ierr(ii) )
509      ii = ii + 1
510      ALLOCATE( sxice(jpi,jpj,jpl) , syice(jpi,jpj,jpl) , sxxice(jpi,jpj,jpl) , syyice(jpi,jpj,jpl) , sxyice(jpi,jpj,jpl) ,   &
511         &      sxsn (jpi,jpj,jpl) , sysn (jpi,jpj,jpl) , sxxsn (jpi,jpj,jpl) , syysn (jpi,jpj,jpl) , sxysn (jpi,jpj,jpl) ,   &
512         &      STAT=ierr(ii) )
513      ii = ii + 1
514      ALLOCATE( sxa  (jpi,jpj,jpl) , sya  (jpi,jpj,jpl) , sxxa  (jpi,jpj,jpl) , syya  (jpi,jpj,jpl) , sxya  (jpi,jpj,jpl) ,   &
515         &      sxc0 (jpi,jpj,jpl) , syc0 (jpi,jpj,jpl) , sxxc0 (jpi,jpj,jpl) , syyc0 (jpi,jpj,jpl) , sxyc0 (jpi,jpj,jpl) ,   &
516         &      sxsal(jpi,jpj,jpl) , sysal(jpi,jpj,jpl) , sxxsal(jpi,jpj,jpl) , syysal(jpi,jpj,jpl) , sxysal(jpi,jpj,jpl) ,   &
517         &      sxage(jpi,jpj,jpl) , syage(jpi,jpj,jpl) , sxxage(jpi,jpj,jpl) , syyage(jpi,jpj,jpl) , sxyage(jpi,jpj,jpl) ,   &
518         &      STAT=ierr(ii) )
519      ii = ii + 1
520      ALLOCATE( sxe (jpi,jpj,nlay_i,jpl) , sye (jpi,jpj,nlay_i,jpl) , sxxe(jpi,jpj,nlay_i,jpl) ,     &
521         &      syye(jpi,jpj,nlay_i,jpl) , sxye(jpi,jpj,nlay_i,jpl)                            , STAT=ierr(ii) )
522
523      ! * Old values of global variables
524      ii = ii + 1
525      ALLOCATE( v_s_b  (jpi,jpj,jpl) , v_i_b  (jpi,jpj,jpl) , e_s_b(jpi,jpj,nlay_s,jpl) ,     &
526         &      a_i_b  (jpi,jpj,jpl) , smv_i_b(jpi,jpj,jpl) , e_i_b(jpi,jpj,nlay_i,jpl) ,     &
527         &      oa_i_b (jpi,jpj,jpl)                                                    , STAT=ierr(ii) )
528      ii = ii + 1
529      ALLOCATE( u_ice_b(jpi,jpj) , v_ice_b(jpi,jpj) , STAT=ierr(ii) )
530     
531      ! * Ice thickness distribution variables
532      ii = ii + 1
533      ALLOCATE( hi_max(0:jpl), hi_mean(jpl),  STAT=ierr(ii) )
534
535      ! * Ice diagnostics
536      ii = ii + 1
537      ALLOCATE( diag_trp_vi(jpi,jpj) , diag_trp_vs (jpi,jpj) , diag_trp_ei(jpi,jpj),   & 
538         &      diag_trp_es(jpi,jpj) , diag_trp_smv(jpi,jpj) , diag_heat  (jpi,jpj),   &
539         &      diag_smvi  (jpi,jpj) , diag_vice   (jpi,jpj) , diag_vsnw  (jpi,jpj), STAT=ierr(ii) )
540
541      ice_alloc = MAXVAL( ierr(:) )
542      IF( ice_alloc /= 0 )   CALL ctl_warn('ice_alloc_2: failed to allocate arrays.')
543      !
544   END FUNCTION ice_alloc
545
546#else
547   !!----------------------------------------------------------------------
548   !!   Default option         Empty module            NO LIM sea-ice model
549   !!----------------------------------------------------------------------
550#endif
551
552   !!======================================================================
553END MODULE ice
Note: See TracBrowser for help on using the repository browser.