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/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3/ice.F90 @ 8518

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

changes in style - part6 - commits of the day

  • Property svn:keywords set to Id
File size: 41.1 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 by icestp.F90
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 icevar.F90 perform conversions                          |
66   !!  - ice_var_glo2eqv  : from global to equivalent variables           |
67   !!  - ice_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   !!  - ice_var_agg                                                      |
73   !!                                                                     |
74   !! in icestp.F90, the routines that compute the changes in the ice     |
75   !! state variables are called                                          |
76   !! - ice_rhg : ice dynamics                                            |
77   !! - ice_adv : ice advection                                           |
78   !! - ice_rdgrft : ice ridging and rafting                              |
79   !! - ice_thd : ice halo-thermodynamics and creation of new ice         |
80   !! - ice_itd : thermodynamic changes in ice thickness distribution     |
81   !!                                                                     |
82   !! See the associated routines for more information                    |
83   !!                                                                     |
84   !! List of ice state variables :                                       |
85   !! -----------------------------                                       |
86   !!                                                                     |
87   !!-------------|-------------|---------------------------------|-------|
88   !!   name in   |   name in   |              meaning            | units |
89   !! 2D routines | 1D routines |                                 |       |
90   !!-------------|-------------|---------------------------------|-------|
91   !!                                                                     |
92   !! ******************************************************************* |
93   !! ***         Dynamical variables (prognostic)                    *** |
94   !! ******************************************************************* |
95   !!                                                                     |
96   !! u_ice       |      -      |    Comp. U of the ice velocity  | m/s   |
97   !! v_ice       |      -      |    Comp. V of the ice velocity  | m/s   |
98   !!                                                                     |
99   !! ******************************************************************* |
100   !! ***         Category dependent state variables (prognostic)     *** |
101   !! ******************************************************************* |
102   !!                                                                     |
103   !! ** Global variables                                                 |
104   !!-------------|-------------|---------------------------------|-------|
105   !! a_i         | a_i_1d      |    Ice concentration            |       |
106   !! v_i         |      -      |    Ice volume per unit area     | m     |
107   !! v_s         |      -      |    Snow volume per unit area    | m     |
108   !! smv_i       |      -      |    Sea ice salt content         | ppt.m |
109   !! oa_i        !      -      !    Sea ice areal age content    | s     |
110   !! e_i         !      -      !    Ice enthalpy                 | J/m2  |
111   !!      -      ! e_i_1d      !    Ice enthalpy per unit vol.   | J/m3  |
112   !! e_s         !      -      !    Snow enthalpy                | J/m2  |
113   !!      -      ! e_s_1d      !    Snow enthalpy per unit vol.  | J/m3  |
114   !!                                                                     |
115   !!-------------|-------------|---------------------------------|-------|
116   !!                                                                     |
117   !! ** Equivalent variables                                             |
118   !!-------------|-------------|---------------------------------|-------|
119   !!                                                                     |
120   !! ht_i        | ht_i_1d     |    Ice thickness                | m     |
121   !! ht_s        ! ht_s_1d     |    Snow depth                   | m     |
122   !! sm_i        ! sm_i_1d     |    Sea ice bulk salinity        ! ppt   |
123   !! s_i         ! s_i_1d      |    Sea ice salinity profile     ! ppt   |
124   !! o_i         !      -      |    Sea ice Age                  ! s     |
125   !! t_i         ! t_i_1d      |    Sea ice temperature          ! K     |
126   !! t_s         ! t_s_1d      |    Snow temperature             ! K     |
127   !! t_su        ! t_su_1d     |    Sea ice surface temperature  ! K     |
128   !!                                                                     |
129   !! notes: the ice model only sees a bulk (i.e., vertically averaged)   |
130   !!        salinity, except in thermodynamic computations, for which    |
131   !!        the salinity profile is computed as a function of bulk       |
132   !!        salinity                                                     |
133   !!                                                                     |
134   !!        the sea ice surface temperature is not associated to any     |
135   !!        heat content. Therefore, it is not a state variable and      |
136   !!        does not have to be advected. Nevertheless, it has to be     |
137   !!        computed to determine whether the ice is melting or not      |
138   !!                                                                     |
139   !! ******************************************************************* |
140   !! ***         Category-summed state variables (diagnostic)        *** |
141   !! ******************************************************************* |
142   !! at_i        | at_i_1d     |    Total ice concentration      |       |
143   !! vt_i        |      -      |    Total ice vol. per unit area | m     |
144   !! vt_s        |      -      |    Total snow vol. per unit ar. | m     |
145   !! smt_i       |      -      |    Mean sea ice salinity        | ppt   |
146   !! tm_i        |      -      |    Mean sea ice temperature     | K     |
147   !! et_i        !      -      !    Total ice enthalpy           | J/m2  |
148   !! et_s        !      -      !    Total snow enthalpy          | J/m2  |
149   !! bv_i        !      -      !    relative brine volume        | ???   |
150   !!=====================================================================
151
152   !!--------------------------------------------------------------------------
153   !! * Share Module variables
154   !!--------------------------------------------------------------------------
155   !                                     !!** ice-generic parameters namelist (namice_run) **
156   INTEGER           , PUBLIC ::   jpl             !: number of ice  categories
157   INTEGER           , PUBLIC ::   nlay_i          !: number of ice  layers
158   INTEGER           , PUBLIC ::   nlay_s          !: number of snow layers
159   LOGICAL           , PUBLIC ::   ln_icedyn       !: flag for ice dynamics (T) or not (F)
160   LOGICAL           , PUBLIC ::   ln_icethd       !: flag for ice thermo   (T) or not (F)
161   REAL(wp)          , PUBLIC ::   rn_amax_n       !: maximum ice concentration Northern hemisphere
162   REAL(wp)          , PUBLIC ::   rn_amax_s       !: maximum ice concentration Southern hemisphere
163   CHARACTER(len=32) , PUBLIC ::   cn_icerst_in    !: suffix of ice restart name (input)
164   CHARACTER(len=32) , PUBLIC ::   cn_icerst_out   !: suffix of ice restart name (output)
165   CHARACTER(len=256), PUBLIC ::   cn_icerst_indir !: ice restart input directory
166   CHARACTER(len=256), PUBLIC ::   cn_icerst_outdir!: ice restart output directory
167
168   !                                     !!** ice-itd namelist (namice_itd) **
169   REAL(wp), PUBLIC ::   rn_himin         !: minimum ice thickness
170   
171   !                                     !!** ice-dynamics namelist (namice_dyn) **
172   REAL(wp), PUBLIC ::   rn_ishlat        !: lateral boundary condition for sea-ice
173   REAL(wp), PUBLIC ::   rn_cio           !: drag coefficient for oceanic stress
174   LOGICAL , PUBLIC ::   ln_landfast      !: landfast ice parameterization (T or F)
175   REAL(wp), PUBLIC ::   rn_gamma         !:    fraction of ocean depth that ice must reach to initiate landfast ice
176   REAL(wp), PUBLIC ::   rn_icebfr        !:    maximum bottom stress per unit area of contact (landfast ice)
177   REAL(wp), PUBLIC ::   rn_lfrelax       !:    relaxation time scale (s-1) to reach static friction (landfast ice)
178   !
179   !                                     !!** ice-rheology namelist (namice_rhg) **
180   REAL(wp), PUBLIC ::   rn_creepl        !: creep limit : has to be under 1.0e-9
181   REAL(wp), PUBLIC ::   rn_ecc           !: eccentricity of the elliptical yield curve
182   INTEGER , PUBLIC ::   nn_nevp          !: number of iterations for subcycling
183   REAL(wp), PUBLIC ::   rn_relast        !: ratio => telast/rdt_ice (1/3 or 1/9 depending on nb of subcycling nevp)
184   !
185   !                                     !!** ice-thermodynamics namelist (namice_thd) **
186                                          ! -- icethd_dif -- !
187   REAL(wp), PUBLIC ::   rn_kappa_i       !: coef. for the extinction of radiation Grenfell et al. (2006) [1/m]
188   LOGICAL , PUBLIC ::   ln_cndi_U64      !: thermal conductivity: Untersteiner (1964)
189   LOGICAL , PUBLIC ::   ln_cndi_P07      !: thermal conductivity: Pringle et al (2007)
190   LOGICAL , PUBLIC ::   ln_dqns_i        !: change non-solar surface flux with changing surface temperature (T) or not (F)
191   INTEGER , PUBLIC ::   nn_monocat       !: virtual ITD mono-category parameterizations (1-4) or not (0)
192   REAL(wp), PUBLIC ::   rn_cnd_s         !: thermal conductivity of the snow [W/m/K]
193                                          ! -- icethd_dh -- !
194   LOGICAL , PUBLIC ::   ln_icedH         !: activate ice thickness change from growing/melting (T) or not (F)
195   REAL(wp), PUBLIC ::   rn_blow_s        !: coef. for partitioning of snowfall between leads and sea ice
196                                          ! -- icethd_da -- !
197   LOGICAL , PUBLIC ::   ln_icedA         !: activate lateral melting param. (T) or not (F)
198   REAL(wp), PUBLIC ::   rn_beta          !: coef. beta for lateral melting param.
199   REAL(wp), PUBLIC ::   rn_dmin          !: minimum floe diameter for lateral melting param.
200                                          ! -- icethd_lac -- !
201   LOGICAL , PUBLIC ::   ln_icedO         !: activate ice growth in open-water (T) or not (F)
202   REAL(wp), PUBLIC ::   rn_hinew         !: thickness for new ice formation (m)
203   LOGICAL , PUBLIC ::   ln_frazil        !: use of frazil ice collection as function of wind (T) or not (F)
204   REAL(wp), PUBLIC ::   rn_maxfraz       !: maximum portion of frazil ice collecting at the ice bottom
205   REAL(wp), PUBLIC ::   rn_vfraz         !: threshold drift speed for collection of bottom frazil ice
206   REAL(wp), PUBLIC ::   rn_Cfraz         !: squeezing coefficient for collection of bottom frazil ice
207                                          ! -- icethd -- !
208   INTEGER , PUBLIC ::   nn_iceflx        !: Redistribute heat flux over ice categories
209   !                                      !   =-1  Do nothing (needs N(cat) fluxes)
210   !                                      !   = 0  Average N(cat) fluxes then apply the average over the N(cat) ice
211   !                                      !   = 1  Average N(cat) fluxes then redistribute over the N(cat) ice
212   !                                      !                                   using T-ice and albedo sensitivity
213   !                                      !   = 2  Redistribute a single flux over categories
214
215   !                                     !!** ice-salinity namelist (namice_sal) **
216   INTEGER , PUBLIC ::   nn_icesal        !: salinity configuration used in the model
217   !                                      ! 1 - constant salinity in both space and time
218   !                                      ! 2 - prognostic salinity (s(z,t))
219   !                                      ! 3 - salinity profile, constant in time
220   REAL(wp), PUBLIC ::   rn_icesal        !: bulk salinity (ppt) in case of constant salinity
221   REAL(wp), PUBLIC ::   rn_simax         !: maximum ice salinity [PSU]
222   REAL(wp), PUBLIC ::   rn_simin         !: minimum ice salinity [PSU]
223
224   ! MV MP 2016
225   !                                     !!** melt pond namelist (namicemp)
226   LOGICAL , PUBLIC ::   ln_pnd           !: activate ponds or not
227   LOGICAL , PUBLIC ::   ln_pnd_rad       !: ponds radiatively active or not
228   LOGICAL , PUBLIC ::   ln_pnd_fw        !: ponds active wrt meltwater or not
229   INTEGER , PUBLIC ::   nn_pnd_scheme    !: type of melt pond scheme:   =0 prescribed, =1 empirical, =2 topographic
230   REAL(wp), PUBLIC ::   rn_apnd          !: prescribed pond fraction (0<rn_apnd<1), only if nn_pnd_scheme = 0
231   REAL(wp), PUBLIC ::   rn_hpnd          !: prescribed pond depth    (0<rn_hpnd<1), only if nn_pnd_scheme = 0
232   ! END MV MP 2016
233   !                                     !!** ice-diagnostics namelist (namice_dia) **
234   LOGICAL , PUBLIC ::   ln_icediachk     !: flag for ice diag (T) or not (F)
235   LOGICAL , PUBLIC ::   ln_icediahsb     !: flag for ice diag (T) or not (F)
236   LOGICAL , PUBLIC ::   ln_icectl        !: flag for sea-ice points output (T) or not (F)
237   INTEGER , PUBLIC ::   iiceprt          !: debug i-point
238   INTEGER , PUBLIC ::   jiceprt          !: debug j-point
239
240   !                                     !!** some other parameters
241   INTEGER , PUBLIC ::   kt_ice           !: iteration number
242   REAL(wp), PUBLIC ::   rdt_ice          !: ice time step
243   REAL(wp), PUBLIC ::   r1_rdtice        !: = 1. / rdt_ice
244   REAL(wp), PUBLIC ::   r1_nlay_i        !: 1 / nlay_i
245   REAL(wp), PUBLIC ::   r1_nlay_s        !: 1 / nlay_s
246   REAL(wp), PUBLIC ::   rswitch          !: switch for the presence of ice (1) or not (0)
247   REAL(wp), PUBLIC ::   rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft   !: conservation diagnostics
248   REAL(wp), PUBLIC, PARAMETER ::   epsi06 = 1.e-06_wp  !: small number
249   REAL(wp), PUBLIC, PARAMETER ::   epsi10 = 1.e-10_wp  !: small number
250   REAL(wp), PUBLIC, PARAMETER ::   epsi20 = 1.e-20_wp  !: small number
251
252
253   !                                     !!** define arrays
254   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_oce,v_oce !: surface ocean velocity used in ice dynamics
255   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hicol       !: ice collection thickness accreted in leads
256   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   strength    !: ice strength
257   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   stress1_i, stress2_i, stress12_i   !: 1st, 2nd & diagonal stress tensor element
258   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   delta_i     !: ice rheology elta factor (Flato & Hibler 95) [s-1]
259   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   divu_i      !: Divergence of the velocity field [s-1]
260   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   shear_i     !: Shear of the velocity field [s-1]
261   !
262   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   t_bo        !: Sea-Ice bottom temperature [Kelvin]     
263   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qlead       !: heat balance of the lead (or of the open ocean)
264   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fhtur       !: net downward heat flux from the ice to the ocean
265   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fhld        !: heat flux from the lead used for bottom melting
266
267   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw     !: snow-ocean mass exchange   [kg.m-2.s-1]
268   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sni !: snow ice growth component of wfx_snw [kg.m-2.s-1]
269   ! MV MP 2016
270   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sum !: surface melt component of wfx_snw [kg.m-2.s-1]
271   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_pnd     !: melt pond-ocean mass exchange   [kg.m-2.s-1]
272   ! END MV MP 2016
273   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_spr     !: snow precipitation on ice  [kg.m-2.s-1]
274   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sub     !: sublimation of snow/ice    [kg.m-2.s-1]
275   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sub !: snow sublimation           [kg.m-2.s-1]
276   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_ice_sub !: ice sublimation            [kg.m-2.s-1]
277
278   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_dyn !: dynamical component of wfx_snw    [kg.m-2.s-1]
279
280   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_ice     !: ice-ocean mass exchange                   [kg.m-2.s-1]
281   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sni     !: snow ice growth component of wfx_ice      [kg.m-2.s-1]
282   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_opw     !: lateral ice growth component of wfx_ice   [kg.m-2.s-1]
283   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_bog     !: bottom ice growth component of wfx_ice    [kg.m-2.s-1]
284   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_dyn     !: dynamical ice growth component of wfx_ice [kg.m-2.s-1]
285   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_bom     !: bottom melt component of wfx_ice          [kg.m-2.s-1]
286   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sum     !: surface melt component of wfx_ice         [kg.m-2.s-1]
287   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_lam     !: lateral melt component of wfx_ice         [kg.m-2.s-1]
288   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_res     !: residual component of wfx_ice             [kg.m-2.s-1]
289
290   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   afx_tot     !: ice concentration tendency (total)          [s-1]
291
292   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bog     !: salt flux due to ice growth/melt                      [PSU/m2/s]
293   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bom     !: salt flux due to ice growth/melt                      [PSU/m2/s]
294   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_lam     !: salt flux due to ice growth/melt                      [PSU/m2/s]
295   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sum     !: salt flux due to ice growth/melt                      [PSU/m2/s]
296   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sni     !: salt flux due to ice growth/melt                      [PSU/m2/s]
297   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_opw     !: salt flux due to ice growth/melt                      [PSU/m2/s]
298   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bri     !: salt flux due to brine rejection                      [PSU/m2/s]
299   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_dyn     !: salt flux due to porous ridged ice formation          [PSU/m2/s]
300   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_res     !: residual salt flux due to correction of ice thickness [PSU/m2/s]
301
302   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sub     !: salt flux due to ice sublimation
303
304   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_bog     !: total heat flux causing bottom ice growth        [W.m-2]
305   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_bom     !: total heat flux causing bottom ice melt          [W.m-2]
306   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_sum     !: total heat flux causing surface ice melt         [W.m-2]
307   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_opw     !: total heat flux causing open water ice formation [W.m-2]
308   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_dif     !: total heat flux causing Temp change in the ice   [W.m-2]
309   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_snw     !: heat flux for snow melt                          [W.m-2]
310   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err_dif !: heat flux remaining due to change in non-solar flux [W.m-2]
311   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err_rem !: heat flux error after heat remapping             [W.m-2]
312   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_in      !: heat flux available for thermo transformations   [W.m-2]
313   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_out     !: heat flux remaining at the end of thermo transformations  [W.m-2]
314   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_err_sub !: mass flux error after sublimation [kg.m-2.s-1]
315   
316   ! heat flux associated with ice-atmosphere mass exchange
317   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_sub     !: heat flux for sublimation  [W.m-2]
318   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_spr     !: heat flux of the snow precipitation  [W.m-2]
319
320   ! heat flux associated with ice-ocean mass exchange
321   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_thd     !: ice-ocean heat flux from thermo processes (icethd_dh) [W.m-2]
322   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_dyn     !: ice-ocean heat flux from ridging                      [W.m-2]
323   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_res     !: residual heat flux due to correction of ice thickness [W.m-2]
324
325   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rn_amax_2d     !: maximum ice concentration 2d array
326   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ftr_ice        !: transmitted solar radiation under ice
327
328   !!--------------------------------------------------------------------------
329   !! * Ice global state variables
330   !!--------------------------------------------------------------------------
331   !! Variables defined for each ice category
332   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ht_i      !: Ice thickness (m)
333   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i       !: Ice fractional areas (concentration)
334   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_i       !: Ice volume per unit area (m)
335   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_s       !: Snow volume per unit area(m)
336   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ht_s      !: Snow thickness (m)
337   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t_su      !: Sea-Ice Surface Temperature (K)
338   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sm_i      !: Sea-Ice Bulk salinity (ppt)
339   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   smv_i     !: Sea-Ice Bulk salinity times volume per area (ppt.m)
340   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   o_i       !: Sea-Ice Age (s)
341   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   oa_i      !: Sea-Ice Age times ice area (s)
342   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   bv_i      !: brine volume
343
344   !! Variables summed over all categories, or associated to all the ice in a single grid cell
345   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_ice, v_ice !: components of the ice velocity (m/s)
346   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   vt_i , vt_s  !: ice and snow total volume per unit area (m)
347   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   at_i         !: ice total fractional area (ice concentration)
348   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ato_i        !: =1-at_i ; total open water fractional area
349   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   et_i , et_s  !: ice and snow total heat content
350   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tm_i         !: mean ice temperature over all categories
351   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bvm_i        !: brine volume averaged over all categories
352   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   smt_i        !: mean sea ice salinity averaged over all categories [PSU]
353   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tm_su        !: mean surface temperature over all categories
354   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   htm_i        !: mean ice  thickness over all categories
355   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   htm_s        !: mean snow thickness over all categories
356   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   om_i         !: mean ice age over all categories
357   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tau_icebfr   !: ice friction with bathy (landfast param activated)
358
359   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_s      !: Snow temperatures [K]
360   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s      !: Snow ...     
361     
362   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_i      !: ice temperatures          [K]
363   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i      !: ice thermal contents    [J/m2]
364   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   s_i      !: ice salinities          [PSU]
365
366   ! MV MP 2016
367   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_ip       !: melt pond fraction per grid cell area
368   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_ip       !: melt pond volume per grid cell area [m]
369   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_ip_frac  !: melt pond volume per ice area
370   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   h_ip       !: melt pond thickness [m]
371
372   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   at_ip      !: total melt pond fraction
373   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   vt_ip      !: total melt pond volume per unit area [m]
374   ! END MV MP 2016
375
376   !!--------------------------------------------------------------------------
377   !! * Moments for advection
378   !!--------------------------------------------------------------------------
379   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   sxopw, syopw, sxxopw, syyopw, sxyopw   !: open water in sea ice
380   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxice, syice, sxxice, syyice, sxyice   !: ice thickness
381   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxsn , sysn , sxxsn , syysn , sxysn    !: snow thickness
382   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxa  , sya  , sxxa  , syya  , sxya     !: lead fraction
383   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxc0 , syc0 , sxxc0 , syyc0 , sxyc0    !: snow thermal content
384   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxsal, sysal, sxxsal, syysal, sxysal   !: ice salinity
385   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxage, syage, sxxage, syyage, sxyage   !: ice age
386   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   sxe  , sye  , sxxe  , syye  , sxye     !: ice layers heat content
387   ! MV MP 2016
388   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxap , syap , sxxap , syyap , sxyap    !:  melt pond fraction
389   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxvp , syvp , sxxvp , syyvp , sxyvp    !:  melt pond volume
390   ! END MV MP 2016
391
392   !!--------------------------------------------------------------------------
393   !! * Old values of global variables
394   !!--------------------------------------------------------------------------
395   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_s_b, v_i_b, ht_s_b, ht_i_b  !: snow and ice volumes/thickness
396   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_i_b, smv_i_b, oa_i_b        !:
397   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s_b                         !: snow heat content
398   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i_b                         !: ice temperatures
399   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   u_ice_b, v_ice_b              !: ice velocity
400   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   at_i_b                        !: ice concentration (total)
401           
402   !!--------------------------------------------------------------------------
403   !! * Ice thickness distribution variables
404   !!--------------------------------------------------------------------------
405   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   hi_max         !: Boundary of ice thickness categories in thickness space
406   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   hi_mean        !: Mean ice thickness in catgories
407   !
408   !!--------------------------------------------------------------------------
409   !! * Ice diagnostics
410   !!--------------------------------------------------------------------------
411   ! thd refers to changes induced by thermodynamics
412   ! trp   ''         ''     ''       advection (transport of ice)
413   !
414   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_vi   !: transport of ice volume
415   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_vs   !: transport of snw volume
416   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_ei   !: transport of ice enthalpy (W/m2)
417   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_es   !: transport of snw enthalpy (W/m2)
418   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_smv  !: transport of salt content
419   !
420   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_heat     !: snw/ice heat content variation   [W/m2]
421   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_smvi     !: ice salt content variation   []
422   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_vice     !: ice volume variation   [m/s]
423   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_vsnw     !: snw volume variation   [m/s]
424
425   !
426   !!--------------------------------------------------------------------------
427   !! * SIMIP extra diagnostics
428   !!--------------------------------------------------------------------------
429   ! Extra sea ice diagnostics to address the data request
430   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   t_si          !: Temperature at Snow-ice interface (K)
431   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   tm_si         !: mean temperature at the snow-ice interface (K)
432   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_fc_bo    !: Bottom conduction flux (W/m2)
433   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_fc_su    !: Surface conduction flux (W/m2)
434
435   !
436   !!----------------------------------------------------------------------
437   !! NEMO/ICE 4.0 , NEMO Consortium (2017)
438   !! $Id$
439   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
440   !!----------------------------------------------------------------------
441CONTAINS
442
443   FUNCTION ice_alloc()
444      !!-----------------------------------------------------------------
445      !!               *** Routine ice_alloc ***
446      !!-----------------------------------------------------------------
447      INTEGER :: ice_alloc
448      !
449      INTEGER :: ierr(18), ii
450      !!-----------------------------------------------------------------
451
452      ierr(:) = 0
453
454      ! What could be one huge allocate statement is broken-up to try to
455      ! stay within Fortran's max-line length limit.
456      ii = 1
457      ALLOCATE( u_oce   (jpi,jpj) , v_oce    (jpi,jpj) , hicol    (jpi,jpj) ,                        &
458         &      strength(jpi,jpj) , stress1_i(jpi,jpj) , stress2_i(jpi,jpj) , stress12_i(jpi,jpj) ,  &
459         &      delta_i (jpi,jpj) , divu_i   (jpi,jpj) , shear_i  (jpi,jpj) , STAT=ierr(ii) )
460
461      ii = ii + 1
462      ALLOCATE( t_bo   (jpi,jpj) , wfx_snw_sni(jpi,jpj) ,                                                &
463         &      wfx_snw(jpi,jpj) , wfx_snw_dyn(jpi,jpj) , wfx_snw_sum(jpi,jpj) , wfx_snw_sub(jpi,jpj) ,  &
464         &      wfx_ice(jpi,jpj) , wfx_sub    (jpi,jpj) , wfx_ice_sub(jpi,jpj) , wfx_lam    (jpi,jpj) ,  &
465         ! MV MP 2016
466         &      wfx_pnd(jpi,jpj) ,                                                              &
467         ! END MV MP 2016
468         &      wfx_bog(jpi,jpj) , wfx_dyn(jpi,jpj) , wfx_bom(jpi,jpj) , wfx_sum(jpi,jpj) ,     &
469         &      wfx_res(jpi,jpj) , wfx_sni(jpi,jpj) , wfx_opw(jpi,jpj) , wfx_spr(jpi,jpj) ,     &
470         &      afx_tot(jpi,jpj) , rn_amax_2d(jpi,jpj),                                         &
471         &      fhtur  (jpi,jpj) , qlead  (jpi,jpj) ,                                           &
472         &      sfx_res(jpi,jpj) , sfx_bri(jpi,jpj) , sfx_dyn(jpi,jpj) , sfx_sub(jpi,jpj) , sfx_lam(jpi,jpj) ,  &
473         &      sfx_bog(jpi,jpj) , sfx_bom(jpi,jpj) , sfx_sum(jpi,jpj) , sfx_sni(jpi,jpj) , sfx_opw(jpi,jpj) ,  &
474         &      hfx_res(jpi,jpj) , hfx_snw(jpi,jpj) , hfx_sub(jpi,jpj) ,     & 
475         &      hfx_in (jpi,jpj) , hfx_out(jpi,jpj) , fhld   (jpi,jpj) ,                        &
476         &      hfx_sum(jpi,jpj) , hfx_bom(jpi,jpj) , hfx_bog(jpi,jpj) , hfx_dif(jpi,jpj) ,     &
477         &      hfx_opw(jpi,jpj) , hfx_thd(jpi,jpj) , hfx_dyn(jpi,jpj) , hfx_spr(jpi,jpj) ,     &
478         &      hfx_err_dif(jpi,jpj) , hfx_err_rem(jpi,jpj) , wfx_err_sub(jpi,jpj)        ,  STAT=ierr(ii) )
479
480      ! * Ice global state variables
481      ii = ii + 1
482      ALLOCATE( ftr_ice(jpi,jpj,jpl) ,                                                 &
483         &      ht_i   (jpi,jpj,jpl) , a_i   (jpi,jpj,jpl) , v_i   (jpi,jpj,jpl) ,     &
484         &      v_s    (jpi,jpj,jpl) , ht_s  (jpi,jpj,jpl) , t_su  (jpi,jpj,jpl) ,     &
485         &      sm_i   (jpi,jpj,jpl) , smv_i (jpi,jpj,jpl) , o_i   (jpi,jpj,jpl) ,     &
486         &      oa_i   (jpi,jpj,jpl) , bv_i  (jpi,jpj,jpl) ,  STAT=ierr(ii) )
487      ii = ii + 1
488      ALLOCATE( u_ice(jpi,jpj) , v_ice(jpi,jpj) ,                                       &
489         &      vt_i (jpi,jpj) , vt_s (jpi,jpj) , at_i (jpi,jpj) , ato_i(jpi,jpj) ,     &
490         &      et_i (jpi,jpj) , et_s (jpi,jpj) , tm_i (jpi,jpj) , bvm_i(jpi,jpj) ,     &
491         &      smt_i(jpi,jpj) , tm_su(jpi,jpj) , htm_i(jpi,jpj) , htm_s(jpi,jpj) ,     &
492         &      om_i (jpi,jpj) , tau_icebfr(jpi,jpj)                              , STAT=ierr(ii) )
493      ii = ii + 1
494      ALLOCATE( t_s(jpi,jpj,nlay_s,jpl) , e_s(jpi,jpj,nlay_s,jpl) , STAT=ierr(ii) )
495      ii = ii + 1
496      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) )
497
498      ! MV MP 2016
499      ii = ii + 1
500      ALLOCATE( a_ip(jpi,jpj,jpl) , v_ip(jpi,jpj,jpl) , a_ip_frac(jpi,jpj,jpl) , &
501         &      h_ip(jpi,jpj,jpl) , STAT = ierr(ii) )
502      ii = ii + 1
503      ALLOCATE( at_ip(jpi,jpj) , vt_ip(jpi,jpj) , STAT = ierr(ii) )
504      ! END MV MP 2016
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      ! MV MP 2016
524      ii = ii + 1
525      ALLOCATE( sxap(jpi,jpj,jpl) , syap(jpi,jpj,jpl) , sxxap(jpi,jpj,jpl) , syyap(jpi,jpj,jpl) , sxyap(jpi,jpj,jpl) ,   &
526         &      sxvp(jpi,jpj,jpl) , syvp(jpi,jpj,jpl) , sxxvp(jpi,jpj,jpl) , syyvp(jpi,jpj,jpl) , sxyvp(jpi,jpj,jpl) ,   &
527         &      STAT = ierr(ii) )
528      ! END MV MP 2016
529
530      ! * Old values of global variables
531      ii = ii + 1
532      ALLOCATE( v_s_b  (jpi,jpj,jpl) , v_i_b  (jpi,jpj,jpl) , ht_s_b(jpi,jpj,jpl)        , ht_i_b(jpi,jpj,jpl)        ,   &
533         &      a_i_b  (jpi,jpj,jpl) , smv_i_b(jpi,jpj,jpl) , e_i_b (jpi,jpj,nlay_i,jpl) , e_s_b (jpi,jpj,nlay_s,jpl) ,   &
534         &      oa_i_b (jpi,jpj,jpl)                                                     , STAT=ierr(ii) )
535      ii = ii + 1
536      ALLOCATE( u_ice_b(jpi,jpj) , v_ice_b(jpi,jpj) , at_i_b(jpi,jpj) , STAT=ierr(ii) )
537     
538      ! * Ice thickness distribution variables
539      ii = ii + 1
540      ALLOCATE( hi_max(0:jpl), hi_mean(jpl),  STAT=ierr(ii) )
541
542      ! * Ice diagnostics
543      ii = ii + 1
544      ALLOCATE( diag_trp_vi(jpi,jpj) , diag_trp_vs (jpi,jpj) , diag_trp_ei(jpi,jpj),   & 
545         &      diag_trp_es(jpi,jpj) , diag_trp_smv(jpi,jpj) , diag_heat  (jpi,jpj),   &
546         &      diag_smvi  (jpi,jpj) , diag_vice   (jpi,jpj) , diag_vsnw  (jpi,jpj), STAT=ierr(ii) )
547
548      ! * SIMIP diagnostics
549      ii = ii + 1
550      ALLOCATE( t_si (jpi,jpj,jpl)    , tm_si(jpi,jpj)        ,    & 
551                diag_fc_bo(jpi,jpj)   , diag_fc_su(jpi,jpj)   ,    &
552                STAT = ierr(ii) )
553
554      ice_alloc = MAXVAL( ierr(:) )
555      IF( ice_alloc /= 0 )   CALL ctl_warn('ice_alloc: failed to allocate arrays.')
556      !
557   END FUNCTION ice_alloc
558
559#else
560   !!----------------------------------------------------------------------
561   !!   Default option         Empty module            NO LIM sea-ice model
562   !!----------------------------------------------------------------------
563#endif
564
565   !!======================================================================
566END MODULE ice
Note: See TracBrowser for help on using the repository browser.