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 tags/nemo_v3_2_2/NEMO/LIM_SRC_3 – NEMO

source: tags/nemo_v3_2_2/NEMO/LIM_SRC_3/ice.F90 @ 3532

Last change on this file since 3532 was 2778, checked in by smasson, 13 years ago

LIM3 compiling in v3_2_2, see ticket#817

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