New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
ice.F90 in branches/2017/dev_r8183_ICEMODEL/NEMOGCM/NEMO/LIM_SRC_3 – NEMO

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

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

continue changing names (again)

  • Property svn:keywords set to Id
File size: 48.0 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
[8321]19   PUBLIC    ice_alloc  !  Called in ice_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                                          |
[8407]76   !! - ice_rhg : ice dynamics                                            |
[8409]77   !! - ice_adv : ice advection                                           |
78   !! - ice_rdgrft : ice ridging and rafting                              |
[834]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 |
[8239]110   !! oa_i        !      -      !    Sea ice areal age content    | s     |
[5123]111   !! e_i         !      -      !    Ice enthalpy                 | J/m2  |
[8325]112   !!      -      ! e_i_1d      !    Ice enthalpy per unit vol.   | J/m3  |
[5123]113   !! e_s         !      -      !    Snow enthalpy                | J/m2  |
[8325]114   !!      -      ! e_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   |
[8239]125   !! o_i         !      -      |    Sea ice Age                  ! s     |
[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     |
[5123]148   !! et_i        !      -      !    Total ice enthalpy           | J/m2  |
149   !! et_s        !      -      !    Total snow enthalpy          | J/m2  |
[7646]150   !! bv_i        !      -      !    relative brine volume        | ???   |
[834]151   !!=====================================================================
[825]152
[2528]153   LOGICAL, PUBLIC ::   con_i = .false.   ! switch for conservation test
[825]154
[834]155   !!--------------------------------------------------------------------------
[825]156   !! * Share Module variables
[834]157   !!--------------------------------------------------------------------------
[7646]158   !                                     !!** ice-generic parameters namelist (namicerun) **
159   INTEGER           , PUBLIC ::   jpl             !: number of ice  categories
160   INTEGER           , PUBLIC ::   nlay_i          !: number of ice  layers
161   INTEGER           , PUBLIC ::   nlay_s          !: number of snow layers
162   REAL(wp)          , PUBLIC ::   rn_amax_n       !: maximum ice concentration Northern hemisphere
163   REAL(wp)          , PUBLIC ::   rn_amax_s       !: maximum ice concentration Southern hemisphere
164   CHARACTER(len=32) , PUBLIC ::   cn_icerst_in    !: suffix of ice restart name (input)
165   CHARACTER(len=32) , PUBLIC ::   cn_icerst_out   !: suffix of ice restart name (output)
166   CHARACTER(len=256), PUBLIC ::   cn_icerst_indir !: ice restart input directory
167   CHARACTER(len=256), PUBLIC ::   cn_icerst_outdir!: ice restart output directory
168   LOGICAL           , PUBLIC ::   ln_limthd       !: flag for ice thermo (T) or not (F)
169   LOGICAL           , PUBLIC ::   ln_limdyn       !: flag for ice dynamics (T) or not (F)
170   INTEGER           , PUBLIC ::   nn_limdyn       !: flag for ice dynamics
171   REAL(wp)          , PUBLIC ::   rn_uice         !: prescribed u-vel (case nn_limdyn=0)
172   REAL(wp)          , PUBLIC ::   rn_vice         !: prescribed v-vel (case nn_limdyn=0)
173   
174   !                                     !!** ice-diagnostics namelist (namicediag) **
175   LOGICAL , PUBLIC ::   ln_limdiachk     !: flag for ice diag (T) or not (F)
176   LOGICAL , PUBLIC ::   ln_limdiahsb     !: flag for ice diag (T) or not (F)
177   LOGICAL , PUBLIC ::   ln_limctl        !: flag for sea-ice points output (T) or not (F)
178   INTEGER , PUBLIC ::   iiceprt          !: debug i-point
179   INTEGER , PUBLIC ::   jiceprt          !: debug j-point
[1465]180
[7646]181   !                                     !!** ice-init namelist (namiceini) **
[8413]182                                          ! -- iceistate -- !
[7646]183   LOGICAL , PUBLIC ::   ln_limini        ! initialization or not
184   LOGICAL , PUBLIC ::   ln_limini_file   ! Ice initialization state from 2D netcdf file
185   REAL(wp), PUBLIC ::   rn_thres_sst     ! threshold water temperature for initial sea ice
186   REAL(wp), PUBLIC ::   rn_hts_ini_n     ! initial snow thickness in the north
187   REAL(wp), PUBLIC ::   rn_hts_ini_s     ! initial snow thickness in the south
188   REAL(wp), PUBLIC ::   rn_hti_ini_n     ! initial ice thickness in the north
189   REAL(wp), PUBLIC ::   rn_hti_ini_s     ! initial ice thickness in the south
190   REAL(wp), PUBLIC ::   rn_ati_ini_n     ! initial leads area in the north
191   REAL(wp), PUBLIC ::   rn_ati_ini_s     ! initial leads area in the south
192   REAL(wp), PUBLIC ::   rn_smi_ini_n     ! initial salinity
193   REAL(wp), PUBLIC ::   rn_smi_ini_s     ! initial salinity
194   REAL(wp), PUBLIC ::   rn_tmi_ini_n     ! initial temperature
195   REAL(wp), PUBLIC ::   rn_tmi_ini_s     ! initial temperature
196   
[5123]197   !                                     !!** ice-thickness distribution namelist (namiceitd) **
198   REAL(wp), PUBLIC ::   rn_himean        !: mean thickness of the domain (used to compute the distribution, nn_itdshp = 2 only)
[825]199
[5123]200   !                                     !!** ice-dynamics namelist (namicedyn) **
[8409]201                                          ! -- iceadv -- !
[7646]202   INTEGER , PUBLIC ::   nn_limadv        !: choose the advection scheme (-1=Prather ; 0=Ultimate-Macho)
203   INTEGER , PUBLIC ::   nn_limadv_ord    !: choose the order of the advection scheme (if Ultimate-Macho)   
[8409]204                                          ! -- icerdgrft -- !
[5123]205   INTEGER , PUBLIC ::   nn_icestr        !: ice strength parameterization (0=Hibler79 1=Rothrock75)
206   REAL(wp), PUBLIC ::   rn_pe_rdg        !: ridging work divided by pot. energy change in ridging, nn_icestr = 1
[7646]207   REAL(wp), PUBLIC ::   rn_pstar         !: determines ice strength, Hibler JPO79
208   REAL(wp), PUBLIC ::   rn_crhg          !: determines changes in ice strength
209   LOGICAL , PUBLIC ::   ln_icestr_bvf    !: use brine volume to diminish ice strength
[8409]210                                          ! -- icerhg -- !
[8313]211   REAL(wp), PUBLIC ::   rn_ishlat        !: lateral boundary condition for sea-ice
[5123]212   REAL(wp), PUBLIC ::   rn_cio           !: drag coefficient for oceanic stress
213   REAL(wp), PUBLIC ::   rn_creepl        !: creep limit : has to be under 1.0e-9
214   REAL(wp), PUBLIC ::   rn_ecc           !: eccentricity of the elliptical yield curve
[7646]215   INTEGER , PUBLIC ::   nn_nevp          !: number of iterations for subcycling
[5123]216   REAL(wp), PUBLIC ::   rn_relast        !: ratio => telast/rdt_ice (1/3 or 1/9 depending on nb of subcycling nevp)
[7646]217   LOGICAL , PUBLIC ::   ln_landfast      !: landfast ice parameterization (T or F)
218   REAL(wp), PUBLIC ::   rn_gamma         !: fraction of ocean depth that ice must reach to initiate landfast ice
219   REAL(wp), PUBLIC ::   rn_icebfr        !: maximum bottom stress per unit area of contact (landfast ice)
220   REAL(wp), PUBLIC ::   rn_lfrelax       !: relaxation time scale (s-1) to reach static friction (landfast ice)
[5123]221
[7646]222   !                                     !!** ice-thermodynamics namelist (namicethd) **
223                                          ! -- limthd_dif -- !
224   REAL(wp), PUBLIC ::   rn_kappa_i       !: coef. for the extinction of radiation Grenfell et al. (2006) [1/m]
225   INTEGER , PUBLIC ::   nn_ice_thcon     !: thermal conductivity: =0 Untersteiner (1964) ; =1 Pringle et al (2007)
[8313]226   LOGICAL , PUBLIC ::   ln_dqnsice       !: change non-solar surface flux with changing surface temperature (T) or not (F)
227   INTEGER , PUBLIC ::   nn_monocat       !: virtual ITD mono-category parameterizations (1-4) or not (0)
[7813]228   REAL(wp), PUBLIC ::   rn_cdsn          !: thermal conductivity of the snow [W/m/K]
[7646]229                                          ! -- limthd_dh -- !
230   LOGICAL , PUBLIC ::   ln_limdH         !: activate ice thickness change from growing/melting (T) or not (F)
231   REAL(wp), PUBLIC ::   rn_betas         !: coef. for partitioning of snowfall between leads and sea ice
232                                          ! -- limthd_da -- !
233   LOGICAL , PUBLIC ::   ln_limdA         !: activate lateral melting param. (T) or not (F)
234   REAL(wp), PUBLIC ::   rn_beta          !: coef. beta for lateral melting param.
235   REAL(wp), PUBLIC ::   rn_dmin          !: minimum floe diameter for lateral melting param.
236                                          ! -- limthd_lac -- !
237   LOGICAL , PUBLIC ::   ln_limdO         !: activate ice growth in open-water (T) or not (F)
238   REAL(wp), PUBLIC ::   rn_hnewice       !: thickness for new ice formation (m)
239   LOGICAL , PUBLIC ::   ln_frazil        !: use of frazil ice collection as function of wind (T) or not (F)
240   REAL(wp), PUBLIC ::   rn_maxfrazb      !: maximum portion of frazil ice collecting at the ice bottom
241   REAL(wp), PUBLIC ::   rn_vfrazb        !: threshold drift speed for collection of bottom frazil ice
242   REAL(wp), PUBLIC ::   rn_Cfrazb        !: squeezing coefficient for collection of bottom frazil ice
243                                          ! -- limitd_th -- !
244   REAL(wp), PUBLIC ::   rn_himin         !: minimum ice thickness
245
[4147]246   !                                     !!** ice-salinity namelist (namicesal) **
[7646]247   LOGICAL , PUBLIC ::   ln_limdS         !: activate gravity drainage and flushing (T) or not (F)
248   INTEGER , PUBLIC ::   nn_icesal        !: salinity configuration used in the model
249   !                                      ! 1 - constant salinity in both space and time
250   !                                      ! 2 - prognostic salinity (s(z,t))
251   !                                      ! 3 - salinity profile, constant in time
252   REAL(wp), PUBLIC ::   rn_icesal        !: bulk salinity (ppt) in case of constant salinity
[5123]253   REAL(wp), PUBLIC ::   rn_sal_gd        !: restoring salinity for gravity drainage [PSU]
[7646]254   REAL(wp), PUBLIC ::   rn_time_gd       !: restoring time constant for gravity drainage (= 20 days) [s]
[5123]255   REAL(wp), PUBLIC ::   rn_sal_fl        !: restoring salinity for flushing [PSU]
256   REAL(wp), PUBLIC ::   rn_time_fl       !: restoring time constant for gravity drainage (= 10 days) [s]
[7646]257   REAL(wp), PUBLIC ::   rn_simax         !: maximum ice salinity [PSU]
258   REAL(wp), PUBLIC ::   rn_simin         !: minimum ice salinity [PSU]
[825]259
[4147]260   !                                     !!** ice-mechanical redistribution namelist (namiceitdme)
[5123]261   REAL(wp), PUBLIC ::   rn_cs            !: fraction of shearing energy contributing to ridging           
[7646]262   INTEGER , PUBLIC ::   nn_partfun       !: participation function: =0 Thorndike et al. (1975), =1 Lipscomb et al. (2007)
[5123]263   REAL(wp), PUBLIC ::   rn_gstar         !: fractional area of young ice contributing to ridging
264   REAL(wp), PUBLIC ::   rn_astar         !: equivalent of G* for an exponential participation function
[7646]265   LOGICAL , PUBLIC ::   ln_ridging       !: ridging of ice or not                       
[5123]266   REAL(wp), PUBLIC ::   rn_hstar         !: thickness that determines the maximal thickness of ridged ice
[7646]267   REAL(wp), PUBLIC ::   rn_por_rdg       !: initial porosity of ridges (0.3 regular value)
268   REAL(wp), PUBLIC ::   rn_fsnowrdg      !: fractional snow loss to the ocean during ridging
[8233]269   REAL(wp), PUBLIC ::   rn_fpondrdg      !: fractional melt pond loss to the ocean during ridging
[7646]270   LOGICAL , PUBLIC ::   ln_rafting       !: rafting of ice or not                       
[5123]271   REAL(wp), PUBLIC ::   rn_hraft         !: threshold thickness (m) for rafting / ridging
272   REAL(wp), PUBLIC ::   rn_craft         !: coefficient for smoothness of the hyperbolic tangent in rafting
[7646]273   REAL(wp), PUBLIC ::   rn_fsnowrft      !: fractional snow loss to the ocean during ridging
[8233]274   REAL(wp), PUBLIC ::   rn_fpondrft      !: fractional snow loss to the ocean during rafting
[825]275
[8233]276   ! MV MP 2016
277   !                                     !!** melt pond namelist (namicemp)
278   LOGICAL , PUBLIC ::   ln_pnd           !: activate ponds or not
279   LOGICAL , PUBLIC ::   ln_pnd_rad       !: ponds radiatively active or not
280   LOGICAL , PUBLIC ::   ln_pnd_fw        !: ponds active wrt meltwater or not
281   INTEGER , PUBLIC ::   nn_pnd_scheme    !: type of melt pond scheme:   =0 prescribed, =1 empirical, =2 topographic
282   REAL(wp), PUBLIC ::   rn_apnd          !: prescribed pond fraction (0<rn_apnd<1), only if nn_pnd_scheme = 0
283   REAL(wp), PUBLIC ::   rn_hpnd          !: prescribed pond depth    (0<rn_hpnd<1), only if nn_pnd_scheme = 0
284   ! END MV MP 2016
285
[7646]286   !                                     !!** some other parameters
[8319]287   INTEGER , PUBLIC ::   kt_ice           !: iteration number
[7646]288   REAL(wp), PUBLIC ::   rdt_ice          !: ice time step
289   REAL(wp), PUBLIC ::   r1_rdtice        !: = 1. / rdt_ice
[5123]290   REAL(wp), PUBLIC ::   r1_nlay_i        !: 1 / nlay_i
291   REAL(wp), PUBLIC ::   r1_nlay_s        !: 1 / nlay_s
[7646]292   REAL(wp), PUBLIC ::   rswitch          !: switch for the presence of ice (1) or not (0)
[4990]293   REAL(wp), PUBLIC, PARAMETER ::   epsi06   = 1.e-06_wp  !: small number
294   REAL(wp), PUBLIC, PARAMETER ::   epsi10   = 1.e-10_wp  !: small number
295   REAL(wp), PUBLIC, PARAMETER ::   epsi20   = 1.e-20_wp  !: small number
296
[7646]297   !                                     !!** define arrays
298   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_oce, v_oce !: surface ocean velocity used in ice dynamics
299   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hicol       !: ice collection thickness accreted in leads
300   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   strength    !: ice strength
[2715]301   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   stress1_i, stress2_i, stress12_i   !: 1st, 2nd & diagonal stress tensor element
[7646]302   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   delta_i     !: ice rheology elta factor (Flato & Hibler 95) [s-1]
303   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   divu_i      !: Divergence of the velocity field [s-1]
304   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   shear_i     !: Shear of the velocity field [s-1]
[2715]305   !
306   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   t_bo        !: Sea-Ice bottom temperature [Kelvin]     
[4688]307   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qlead       !: heat balance of the lead (or of the open ocean)
308   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fhtur       !: net downward heat flux from the ice to the ocean
309   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fhld        !: heat flux from the lead used for bottom melting
310
[7646]311   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw     !: snow-ocean mass exchange   [kg.m-2.s-1]
[8341]312   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sni !: snow ice growth component of wfx_snw [kg.m-2.s-1]
[8233]313   ! MV MP 2016
314   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sum !: surface melt component of wfx_snw [kg.m-2.s-1]
315   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_pnd     !: melt pond-ocean mass exchange   [kg.m-2.s-1]
316   ! END MV MP 2016
[7646]317   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_spr     !: snow precipitation on ice  [kg.m-2.s-1]
[8239]318   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sub     !: sublimation of snow/ice    [kg.m-2.s-1]
319   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sub !: snow sublimation           [kg.m-2.s-1]
320   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_ice_sub !: ice sublimation            [kg.m-2.s-1]
[4688]321
[8239]322   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_dyn !: dynamical component of wfx_snw    [kg.m-2.s-1]
323
[7646]324   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_ice     !: ice-ocean mass exchange                   [kg.m-2.s-1]
325   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sni     !: snow ice growth component of wfx_ice      [kg.m-2.s-1]
326   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_opw     !: lateral ice growth component of wfx_ice   [kg.m-2.s-1]
327   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_bog     !: bottom ice growth component of wfx_ice    [kg.m-2.s-1]
328   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_dyn     !: dynamical ice growth component of wfx_ice [kg.m-2.s-1]
329   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_bom     !: bottom melt component of wfx_ice          [kg.m-2.s-1]
330   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sum     !: surface melt component of wfx_ice         [kg.m-2.s-1]
331   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_lam     !: lateral melt component of wfx_ice         [kg.m-2.s-1]
332   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_res     !: residual component of wfx_ice             [kg.m-2.s-1]
[4688]333
[6416]334   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   afx_tot     !: ice concentration tendency (total)          [s-1]
[5123]335   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   afx_thd     !: ice concentration tendency (thermodynamics) [s-1]
[6416]336   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   afx_dyn     !: ice concentration tendency (dynamics)       [s-1]
[5123]337
[4688]338   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bog     !: salt flux due to ice growth/melt                      [PSU/m2/s]
339   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bom     !: salt flux due to ice growth/melt                      [PSU/m2/s]
[7646]340   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_lam     !: salt flux due to ice growth/melt                      [PSU/m2/s]
[4688]341   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sum     !: salt flux due to ice growth/melt                      [PSU/m2/s]
342   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sni     !: salt flux due to ice growth/melt                      [PSU/m2/s]
343   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_opw     !: salt flux due to ice growth/melt                      [PSU/m2/s]
[3625]344   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bri     !: salt flux due to brine rejection                      [PSU/m2/s]
[4688]345   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_dyn     !: salt flux due to porous ridged ice formation          [PSU/m2/s]
[3625]346   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_res     !: residual salt flux due to correction of ice thickness [PSU/m2/s]
[825]347
[6416]348   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sub     !: salt flux due to ice sublimation
[4688]349
[6416]350   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_bog     !: total heat flux causing bottom ice growth        [W.m-2]
351   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_bom     !: total heat flux causing bottom ice melt          [W.m-2]
352   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_sum     !: total heat flux causing surface ice melt         [W.m-2]
353   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_opw     !: total heat flux causing open water ice formation [W.m-2]
354   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_dif     !: total heat flux causing Temp change in the ice   [W.m-2]
355   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_snw     !: heat flux for snow melt                          [W.m-2]
356   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err     !: heat flux error after heat diffusion             [W.m-2]
357   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err_dif !: heat flux remaining due to change in non-solar flux [W.m-2]
358   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err_rem !: heat flux error after heat remapping             [W.m-2]
359   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_in      !: heat flux available for thermo transformations   [W.m-2]
360   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_out     !: heat flux remaining at the end of thermo transformations  [W.m-2]
361   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_err_sub !: mass flux error after sublimation [kg.m-2.s-1]
362   
[4688]363   ! heat flux associated with ice-atmosphere mass exchange
[6416]364   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_sub     !: heat flux for sublimation  [W.m-2]
365   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_spr     !: heat flux of the snow precipitation  [W.m-2]
[4688]366
367   ! heat flux associated with ice-ocean mass exchange
[8409]368   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_thd     !: ice-ocean heat flux from thermo processes (limthd_dh) [W.m-2]
369   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_dyn     !: ice-ocean heat flux from ridging                      [W.m-2]
[6416]370   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_res     !: residual heat flux due to correction of ice thickness [W.m-2]
[4688]371
[7646]372   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rn_amax_2d     !: maximum ice concentration 2d array
373   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ftr_ice        !: transmitted solar radiation under ice
[4688]374
[834]375   !!--------------------------------------------------------------------------
376   !! * Ice global state variables
377   !!--------------------------------------------------------------------------
378   !! Variables defined for each ice category
[7646]379   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ht_i      !: Ice thickness (m)
380   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i       !: Ice fractional areas (concentration)
381   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_i       !: Ice volume per unit area (m)
382   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_s       !: Snow volume per unit area(m)
383   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ht_s      !: Snow thickness (m)
384   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t_su      !: Sea-Ice Surface Temperature (K)
385   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sm_i      !: Sea-Ice Bulk salinity (ppt)
386   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   smv_i     !: Sea-Ice Bulk salinity times volume per area (ppt.m)
387   !                                                                    !  this is an extensive variable that has to be transported
[8239]388   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   o_i       !: Sea-Ice Age (s)
389   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   oa_i      !: Sea-Ice Age times ice area (s)
[7646]390   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   bv_i      !: brine volume
[825]391
[2715]392   !! Variables summed over all categories, or associated to all the ice in a single grid cell
[7646]393   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_ice, v_ice !: components of the ice velocity (m/s)
394   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   vt_i , vt_s  !: ice and snow total volume per unit area (m)
395   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   at_i         !: ice total fractional area (ice concentration)
396   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ato_i        !: =1-at_i ; total open water fractional area
397   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   et_i , et_s  !: ice and snow total heat content
398   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tm_i         !: mean ice temperature over all categories
399   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bvm_i        !: brine volume averaged over all categories
400   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   smt_i        !: mean sea ice salinity averaged over all categories [PSU]
401   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tm_su        !: mean surface temperature over all categories
402   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   htm_i        !: mean ice  thickness over all categories
403   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   htm_s        !: mean snow thickness over all categories
404   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   om_i         !: mean ice age over all categories
405   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tau_icebfr   !: ice friction with bathy (landfast param activated)
[825]406
[7646]407   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_s      !: Snow temperatures [K]
408   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s      !: Snow ...     
[2715]409     
[7646]410   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_i      !: ice temperatures          [K]
411   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i      !: ice thermal contents    [J/m2]
412   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   s_i      !: ice salinities          [PSU]
[825]413
[8233]414   ! MV MP 2016
415   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_ip       !: melt pond fraction per grid cell area
416   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_ip       !: melt pond volume per grid cell area [m]
417   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_ip_frac  !: melt pond volume per ice area
418   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   h_ip       !: melt pond thickness [m]
419
420   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   at_ip      !: total melt pond fraction
421   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   vt_ip      !: total melt pond volume per unit area [m]
422   ! END MV MP 2016
423
[834]424   !!--------------------------------------------------------------------------
425   !! * Moments for advection
426   !!--------------------------------------------------------------------------
[2715]427   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   sxopw, syopw, sxxopw, syyopw, sxyopw   !: open water in sea ice
428   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxice, syice, sxxice, syyice, sxyice   !: ice thickness
429   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxsn , sysn , sxxsn , syysn , sxysn    !: snow thickness
430   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxa  , sya  , sxxa  , syya  , sxya     !: lead fraction
431   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxc0 , syc0 , sxxc0 , syyc0 , sxyc0    !: snow thermal content
432   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxsal, sysal, sxxsal, syysal, sxysal   !: ice salinity
433   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxage, syage, sxxage, syyage, sxyage   !: ice age
434   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   sxe  , sye  , sxxe  , syye  , sxye     !: ice layers heat content
[8233]435   ! MV MP 2016
436   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxap , syap , sxxap , syyap , sxyap    !:  melt pond fraction
437   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sxvp , syvp , sxxvp , syyvp , sxyvp    !:  melt pond volume
438   ! END MV MP 2016
[825]439
[834]440   !!--------------------------------------------------------------------------
441   !! * Old values of global variables
442   !!--------------------------------------------------------------------------
[8360]443   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_s_b, v_i_b, ht_s_b, ht_i_b  !: snow and ice volumes/thickness
444   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_i_b, smv_i_b, oa_i_b        !:
445   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s_b                         !: snow heat content
446   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i_b                         !: ice temperatures
447   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   u_ice_b, v_ice_b              !: ice velocity
448   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   at_i_b                        !: ice concentration (total)
[5123]449           
[834]450   !!--------------------------------------------------------------------------
451   !! * Ice thickness distribution variables
452   !!--------------------------------------------------------------------------
[2715]453   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   hi_max         !: Boundary of ice thickness categories in thickness space
454   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   hi_mean        !: Mean ice thickness in catgories
[4147]455   !
[921]456   !!--------------------------------------------------------------------------
[834]457   !! * Ice diagnostics
458   !!--------------------------------------------------------------------------
[5123]459   ! thd refers to changes induced by thermodynamics
460   ! trp   ''         ''     ''       advection (transport of ice)
[7646]461   !
[5123]462   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_vi   !: transport of ice volume
463   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_vs   !: transport of snw volume
464   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_ei   !: transport of ice enthalpy (W/m2)
465   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_es   !: transport of snw enthalpy (W/m2)
466   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_trp_smv  !: transport of salt content
[4688]467   !
[5167]468   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_heat     !: snw/ice heat content variation   [W/m2]
469   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_smvi     !: ice salt content variation   []
470   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_vice     !: ice volume variation   [m/s]
471   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_vsnw     !: snw volume variation   [m/s]
[8239]472
[4688]473   !
[8239]474   !!--------------------------------------------------------------------------
475   !! * SIMIP extra diagnostics
476   !!--------------------------------------------------------------------------
477   ! Extra sea ice diagnostics to address the data request
478   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   t_si          !: Temperature at Snow-ice interface (K)
479   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   tm_si         !: mean temperature at the snow-ice interface (K)
480   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_dmi_dyn  !: Change in ice mass due to ice dynamics (kg/m2/s)
481   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_dms_dyn  !: Change in snow mass due to ice dynamics (kg/m2/s)
482   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_xmtrp_ice !: X-component of ice mass transport (kg/s)
483   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_ymtrp_ice !: Y-component of ice mass transport (kg/s)
484   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_xmtrp_snw !: X-component of snow mass transport (kg/s)
485   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_ymtrp_snw !: Y-component of snow mass transport (kg/s)
486   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_xatrp    !: X-component of area transport (m2/s)
487   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_yatrp    !: Y-component of area transport (m2/s)
488   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_fc_bo    !: Bottom conduction flux (W/m2)
489   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_fc_su    !: Surface conduction flux (W/m2)
490   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_utau_oi  !: X-direction ocean-ice stress
491   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_vtau_oi  !: Y-direction ocean-ice stress 
492   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_dssh_dx  !: X-direction sea-surface tilt term (N/m2)
493   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_dssh_dy  !: X-direction sea-surface tilt term (N/m2)
494   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_corstrx  !: X-direction coriolis stress (N/m2)
495   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_corstry  !: Y-direction coriolis stress (N/m2)
496   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_intstrx  !: X-direction internal stress (N/m2)
497   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_intstry  !: Y-direction internal stress (N/m2)
498   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_sig1     !: Average normal stress in sea ice   
499   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_sig2     !: Maximum shear stress in sea ice
500   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   diag_shear    !: Maximum shear of sea-ice velocity field
501
502   !
[2715]503   !!----------------------------------------------------------------------
[4161]504   !! NEMO/LIM3 4.0 , UCL - NEMO Consortium (2010)
[2715]505   !! $Id$
506   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
507   !!----------------------------------------------------------------------
508CONTAINS
509
510   FUNCTION ice_alloc()
511      !!-----------------------------------------------------------------
[7813]512      !!               *** Routine ice_alloc ***
[2715]513      !!-----------------------------------------------------------------
514      INTEGER :: ice_alloc
515      !
[8239]516      INTEGER :: ierr(18), ii
[2715]517      !!-----------------------------------------------------------------
518
519      ierr(:) = 0
520
521      ! What could be one huge allocate statement is broken-up to try to
522      ! stay within Fortran's max-line length limit.
523      ii = 1
[8312]524      ALLOCATE( u_oce   (jpi,jpj) , v_oce    (jpi,jpj) , hicol    (jpi,jpj) ,                        &
[7646]525         &      strength(jpi,jpj) , stress1_i(jpi,jpj) , stress2_i(jpi,jpj) , stress12_i(jpi,jpj) ,  &
526         &      delta_i (jpi,jpj) , divu_i   (jpi,jpj) , shear_i  (jpi,jpj) , STAT=ierr(ii) )
[2715]527
528      ii = ii + 1
[8341]529      ALLOCATE( t_bo   (jpi,jpj) , wfx_snw_sni(jpi,jpj) ,                                                &
[8239]530         &      wfx_snw(jpi,jpj) , wfx_snw_dyn(jpi,jpj) , wfx_snw_sum(jpi,jpj) , wfx_snw_sub(jpi,jpj) ,  &
531         &      wfx_ice(jpi,jpj) , wfx_sub    (jpi,jpj) , wfx_ice_sub(jpi,jpj) , wfx_lam    (jpi,jpj) ,  &
[8233]532         ! MV MP 2016
[8240]533         &      wfx_pnd(jpi,jpj) ,                                                              &
[8233]534         ! END MV MP 2016
[4688]535         &      wfx_bog(jpi,jpj) , wfx_dyn(jpi,jpj) , wfx_bom(jpi,jpj) , wfx_sum(jpi,jpj) ,     &
[5123]536         &      wfx_res(jpi,jpj) , wfx_sni(jpi,jpj) , wfx_opw(jpi,jpj) , wfx_spr(jpi,jpj) ,     &
[7646]537         &      afx_tot(jpi,jpj) , afx_thd(jpi,jpj),  afx_dyn(jpi,jpj) , rn_amax_2d(jpi,jpj),   &
538         &      fhtur  (jpi,jpj) , qlead  (jpi,jpj) ,                                           &
539         &      sfx_res(jpi,jpj) , sfx_bri(jpi,jpj) , sfx_dyn(jpi,jpj) , sfx_sub(jpi,jpj) , sfx_lam(jpi,jpj) ,  &
540         &      sfx_bog(jpi,jpj) , sfx_bom(jpi,jpj) , sfx_sum(jpi,jpj) , sfx_sni(jpi,jpj) , sfx_opw(jpi,jpj) ,  &
[5146]541         &      hfx_res(jpi,jpj) , hfx_snw(jpi,jpj) , hfx_sub(jpi,jpj) , hfx_err(jpi,jpj) ,     & 
[7646]542         &      hfx_in (jpi,jpj) , hfx_out(jpi,jpj) , fhld   (jpi,jpj) ,                        &
543         &      hfx_sum(jpi,jpj) , hfx_bom(jpi,jpj) , hfx_bog(jpi,jpj) , hfx_dif(jpi,jpj) ,     &
544         &      hfx_opw(jpi,jpj) , hfx_thd(jpi,jpj) , hfx_dyn(jpi,jpj) , hfx_spr(jpi,jpj) ,     &
545         &      hfx_err_dif(jpi,jpj) , hfx_err_rem(jpi,jpj) , wfx_err_sub(jpi,jpj)        ,  STAT=ierr(ii) )
[2715]546
547      ! * Ice global state variables
548      ii = ii + 1
[8312]549      ALLOCATE( ftr_ice(jpi,jpj,jpl) ,                                                 &
[7646]550         &      ht_i   (jpi,jpj,jpl) , a_i   (jpi,jpj,jpl) , v_i   (jpi,jpj,jpl) ,     &
551         &      v_s    (jpi,jpj,jpl) , ht_s  (jpi,jpj,jpl) , t_su  (jpi,jpj,jpl) ,     &
552         &      sm_i   (jpi,jpj,jpl) , smv_i (jpi,jpj,jpl) , o_i   (jpi,jpj,jpl) ,     &
553         &      oa_i   (jpi,jpj,jpl) , bv_i  (jpi,jpj,jpl) ,  STAT=ierr(ii) )
[2715]554      ii = ii + 1
[7646]555      ALLOCATE( u_ice(jpi,jpj) , v_ice(jpi,jpj) ,                                       &
[2715]556         &      vt_i (jpi,jpj) , vt_s (jpi,jpj) , at_i (jpi,jpj) , ato_i(jpi,jpj) ,     &
[7646]557         &      et_i (jpi,jpj) , et_s (jpi,jpj) , tm_i (jpi,jpj) , bvm_i(jpi,jpj) ,     &
558         &      smt_i(jpi,jpj) , tm_su(jpi,jpj) , htm_i(jpi,jpj) , htm_s(jpi,jpj) ,     &
559         &      om_i (jpi,jpj) , tau_icebfr(jpi,jpj)                              , STAT=ierr(ii) )
[2715]560      ii = ii + 1
[5123]561      ALLOCATE( t_s(jpi,jpj,nlay_s,jpl) , e_s(jpi,jpj,nlay_s,jpl) , STAT=ierr(ii) )
[2715]562      ii = ii + 1
[5167]563      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]564
[8233]565      ! MV MP 2016
566      ii = ii + 1
567      ALLOCATE( a_ip(jpi,jpj,jpl) , v_ip(jpi,jpj,jpl) , a_ip_frac(jpi,jpj,jpl) , &
568         &      h_ip(jpi,jpj,jpl) , STAT = ierr(ii) )
569      ii = ii + 1
570      ALLOCATE( at_ip(jpi,jpj) , vt_ip(jpi,jpj) , STAT = ierr(ii) )
571      ! END MV MP 2016
572
[2715]573      ! * Moments for advection
574      ii = ii + 1
575      ALLOCATE( sxopw(jpi,jpj) , syopw(jpi,jpj) , sxxopw(jpi,jpj) , syyopw(jpi,jpj) , sxyopw(jpi,jpj) , STAT=ierr(ii) )
576      ii = ii + 1
577      ALLOCATE( sxice(jpi,jpj,jpl) , syice(jpi,jpj,jpl) , sxxice(jpi,jpj,jpl) , syyice(jpi,jpj,jpl) , sxyice(jpi,jpj,jpl) ,   &
578         &      sxsn (jpi,jpj,jpl) , sysn (jpi,jpj,jpl) , sxxsn (jpi,jpj,jpl) , syysn (jpi,jpj,jpl) , sxysn (jpi,jpj,jpl) ,   &
579         &      STAT=ierr(ii) )
580      ii = ii + 1
581      ALLOCATE( sxa  (jpi,jpj,jpl) , sya  (jpi,jpj,jpl) , sxxa  (jpi,jpj,jpl) , syya  (jpi,jpj,jpl) , sxya  (jpi,jpj,jpl) ,   &
582         &      sxc0 (jpi,jpj,jpl) , syc0 (jpi,jpj,jpl) , sxxc0 (jpi,jpj,jpl) , syyc0 (jpi,jpj,jpl) , sxyc0 (jpi,jpj,jpl) ,   &
583         &      sxsal(jpi,jpj,jpl) , sysal(jpi,jpj,jpl) , sxxsal(jpi,jpj,jpl) , syysal(jpi,jpj,jpl) , sxysal(jpi,jpj,jpl) ,   &
584         &      sxage(jpi,jpj,jpl) , syage(jpi,jpj,jpl) , sxxage(jpi,jpj,jpl) , syyage(jpi,jpj,jpl) , sxyage(jpi,jpj,jpl) ,   &
585         &      STAT=ierr(ii) )
586      ii = ii + 1
[5167]587      ALLOCATE( sxe (jpi,jpj,nlay_i,jpl) , sye (jpi,jpj,nlay_i,jpl) , sxxe(jpi,jpj,nlay_i,jpl) ,     &
588         &      syye(jpi,jpj,nlay_i,jpl) , sxye(jpi,jpj,nlay_i,jpl)                            , STAT=ierr(ii) )
[2715]589
[8233]590      ! MV MP 2016
[8239]591      ii = ii + 1
[8233]592      ALLOCATE( sxap(jpi,jpj,jpl) , syap(jpi,jpj,jpl) , sxxap(jpi,jpj,jpl) , syyap(jpi,jpj,jpl) , sxyap(jpi,jpj,jpl) ,   &
593         &      sxvp(jpi,jpj,jpl) , syvp(jpi,jpj,jpl) , sxxvp(jpi,jpj,jpl) , syyvp(jpi,jpj,jpl) , sxyvp(jpi,jpj,jpl) ,   &
594         &      STAT = ierr(ii) )
595      ! END MV MP 2016
596
[2715]597      ! * Old values of global variables
598      ii = ii + 1
[8360]599      ALLOCATE( v_s_b  (jpi,jpj,jpl) , v_i_b  (jpi,jpj,jpl) , ht_s_b(jpi,jpj,jpl)        , ht_i_b(jpi,jpj,jpl)        ,   &
600         &      a_i_b  (jpi,jpj,jpl) , smv_i_b(jpi,jpj,jpl) , e_i_b (jpi,jpj,nlay_i,jpl) , e_s_b (jpi,jpj,nlay_s,jpl) ,   &
601         &      oa_i_b (jpi,jpj,jpl)                                                     , STAT=ierr(ii) )
[7646]602      ii = ii + 1
603      ALLOCATE( u_ice_b(jpi,jpj) , v_ice_b(jpi,jpj) , at_i_b(jpi,jpj) , STAT=ierr(ii) )
[2715]604     
605      ! * Ice thickness distribution variables
606      ii = ii + 1
[4869]607      ALLOCATE( hi_max(0:jpl), hi_mean(jpl),  STAT=ierr(ii) )
[2715]608
609      ! * Ice diagnostics
610      ii = ii + 1
[7646]611      ALLOCATE( diag_trp_vi(jpi,jpj) , diag_trp_vs (jpi,jpj) , diag_trp_ei(jpi,jpj),   & 
612         &      diag_trp_es(jpi,jpj) , diag_trp_smv(jpi,jpj) , diag_heat  (jpi,jpj),   &
613         &      diag_smvi  (jpi,jpj) , diag_vice   (jpi,jpj) , diag_vsnw  (jpi,jpj), STAT=ierr(ii) )
[2715]614
[8239]615      ! * SIMIP diagnostics
616      ii = ii + 1
617      ALLOCATE( t_si (jpi,jpj,jpl)    , tm_si(jpi,jpj)        ,    & 
618                diag_dmi_dyn(jpi,jpj) , diag_dms_dyn(jpi,jpj) ,    &
619                diag_xmtrp_ice(jpi,jpj), diag_ymtrp_ice(jpi,jpj),  &
620                diag_xmtrp_snw(jpi,jpj), diag_ymtrp_snw(jpi,jpj),  &
621                diag_xatrp(jpi,jpj)    , diag_yatrp(jpi,jpj)    ,  &
622                diag_fc_bo(jpi,jpj)   , diag_fc_su(jpi,jpj)   ,    &
623                diag_utau_oi(jpi,jpj) , diag_vtau_oi(jpi,jpj) ,    &
624                diag_dssh_dx(jpi,jpj) , diag_dssh_dy(jpi,jpj) ,    &
625                diag_corstrx(jpi,jpj) , diag_corstry(jpi,jpj) ,    &
626                diag_intstrx(jpi,jpj) , diag_intstry(jpi,jpj) ,    &
627                diag_sig1(jpi,jpj)    , diag_sig2(jpi,jpj)    ,    &
[8291]628                diag_shear(jpi,jpj)   , STAT = ierr(ii) )
[8239]629
[2715]630      ice_alloc = MAXVAL( ierr(:) )
[7646]631      IF( ice_alloc /= 0 )   CALL ctl_warn('ice_alloc: failed to allocate arrays.')
[2715]632      !
633   END FUNCTION ice_alloc
634
[825]635#else
636   !!----------------------------------------------------------------------
637   !!   Default option         Empty module            NO LIM sea-ice model
638   !!----------------------------------------------------------------------
639#endif
640
641   !!======================================================================
642END MODULE ice
Note: See TracBrowser for help on using the repository browser.