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

source: branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/LIM_SRC_3/ice.F90 @ 5602

Last change on this file since 5602 was 5602, checked in by cbricaud, 9 years ago

merge change from trunk rev 5003 to 5519 ( rev where branche 3.6_stable were created )

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