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/2015/dev_r5044_CNRS_LIM3CLEAN/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

source: branches/2015/dev_r5044_CNRS_LIM3CLEAN/NEMOGCM/NEMO/LIM_SRC_3/ice.F90 @ 5047

Last change on this file since 5047 was 5047, checked in by clem, 9 years ago

LIM3 cleaning (1): namelist

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