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_merge_2017/NEMOGCM/NEMO/ICE_SRC – NEMO

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/ICE_SRC/ice.F90 @ 9570

Last change on this file since 9570 was 9570, checked in by nicolasmartin, 6 years ago

Global renaming for core routines (./NEMO)

  • Folders
    • LIM_SRC_3 -> ICE_SRC
    • OPA_SRC -> OCE_SRC
  • CPP key: key_lim3 -> key_si3
  • Modules, (sub)routines and variables names
    • MPI: mpi_comm_opa -> mpi_comm_oce, MPI_COMM_OPA -> MPI_COMM_OCE, mpi_init_opa -> mpi_init_oce
    • AGRIF: agrif_opa_* -> agrif_oce_*, agrif_lim3_* -> agrif_si3_* and few more
    • TOP-PISCES: p.zlim -> p.zice, namp.zlim -> namp.zice
  • Comments
    • NEMO/OPA -> NEMO/OCE
    • ESIM|LIM3 -> SI3
  • Property svn:keywords set to Id
File size: 37.4 KB
Line 
1MODULE ice
2   !!======================================================================
3   !!                        ***  MODULE  ice  ***
4   !!   sea-ice:  ice variables defined in memory
5   !!======================================================================
6   !! History :  3.0  ! 2008-03  (M. Vancoppenolle) original code LIM-3
7   !!            4.0  ! 2011-02  (G. Madec) dynamical allocation
8   !!----------------------------------------------------------------------
9#if defined key_si3
10   !!----------------------------------------------------------------------
11   !!   'key_si3'                                       SI3 sea-ice model
12   !!----------------------------------------------------------------------
13   USE in_out_manager ! I/O manager
14   USE lib_mpp        ! MPP library
15
16   IMPLICIT NONE
17   PRIVATE
18
19   PUBLIC   ice_alloc   ! called by icestp.F90
20
21   !!======================================================================
22   !! LIM3 by the use of sweat, agile fingers and sometimes brain juice,
23   !!  was developed in Louvain-la-Neuve by :
24   !!    * Martin Vancoppenolle (UCL-ASTR, Belgium)
25   !!    * Sylvain Bouillon (UCL-ASTR, Belgium)
26   !!    * Miguel Angel Morales Maqueda (NOC-L, UK)
27   !!
28   !! Based on extremely valuable earlier work by
29   !!    * Thierry Fichefet
30   !!    * Hugues Goosse
31   !!
32   !! The following persons also contributed to the code in various ways
33   !!    * Gurvan Madec, Claude Talandier, Christian Ethe (LOCEAN, France)
34   !!    * Xavier Fettweis (UCL-ASTR), Ralph Timmermann (AWI, Germany)
35   !!    * Bill Lipscomb (LANL), Cecilia Bitz (UWa)
36   !!      and Elisabeth Hunke (LANL), USA.
37   !!
38   !! For more info, the interested user is kindly invited to consult the following references
39   !!    For model description and validation :
40   !!    * Vancoppenolle et al., Ocean Modelling, 2008a.
41   !!    * Vancoppenolle et al., Ocean Modelling, 2008b.
42   !!    For a specific description of EVP :
43   !!    * Bouillon et al., Ocean Modelling 2009.
44   !!
45   !!    Or the reference manual, that should be available by 2011
46   !!======================================================================
47   !!                                                                     |
48   !!              I C E   S T A T E   V A R I A B L E S                  |
49   !!                                                                     |
50   !! Introduction :                                                      |
51   !! --------------                                                      |
52   !! Every ice-covered grid cell is characterized by a series of state   |
53   !! variables. To account for unresolved spatial variability in ice     |
54   !! thickness, the ice cover in divided in ice thickness categories.    |
55   !!                                                                     |
56   !! Sea ice state variables depend on the ice thickness category        |
57   !!                                                                     |
58   !! Those variables are divided into two groups                         |
59   !! * Extensive (or global) variables.                                  |
60   !!   These are the variables that are transported by all means         |
61   !! * Intensive (or equivalent) variables.                              |
62   !!   These are the variables that are either physically more           |
63   !!   meaningful and/or used in ice thermodynamics                      |
64   !!                                                                     |
65   !! Routines in icevar.F90 perform conversions                          |
66   !!  - ice_var_glo2eqv  : from global to equivalent variables           |
67   !!  - ice_var_eqv2glo  : from equivalent to global variables           |
68   !!                                                                     |
69   !! For various purposes, the sea ice state variables have sometimes    |
70   !! to be aggregated over all ice thickness categories. This operation  |
71   !! is done in :                                                        |
72   !!  - ice_var_agg                                                      |
73   !!                                                                     |
74   !! in icestp.F90, the routines that compute the changes in the ice     |
75   !! state variables are called                                          |
76   !! - ice_rhg : ice dynamics                                            |
77   !! - ice_adv : ice advection                                           |
78   !! - ice_rdgrft : ice ridging and rafting                              |
79   !! - ice_thd : ice halo-thermodynamics and creation of new ice         |
80   !! - ice_itd : thermodynamic changes in ice thickness distribution     |
81   !!                                                                     |
82   !! See the associated routines for more information                    |
83   !!                                                                     |
84   !! List of ice state variables :                                       |
85   !! -----------------------------                                       |
86   !!                                                                     |
87   !!-------------|-------------|---------------------------------|-------|
88   !!   name in   |   name in   |              meaning            | units |
89   !! 2D routines | 1D routines |                                 |       |
90   !!-------------|-------------|---------------------------------|-------|
91   !!                                                                     |
92   !! ******************************************************************* |
93   !! ***         Dynamical variables (prognostic)                    *** |
94   !! ******************************************************************* |
95   !!                                                                     |
96   !! u_ice       |      -      |    Comp. U of the ice velocity  | m/s   |
97   !! v_ice       |      -      |    Comp. V of the ice velocity  | m/s   |
98   !!                                                                     |
99   !! ******************************************************************* |
100   !! ***         Category dependent state variables (prognostic)     *** |
101   !! ******************************************************************* |
102   !!                                                                     |
103   !! ** Global variables                                                 |
104   !!-------------|-------------|---------------------------------|-------|
105   !! a_i         | a_i_1d      |    Ice concentration            |       |
106   !! v_i         |      -      |    Ice volume per unit area     | m     |
107   !! v_s         |      -      |    Snow volume per unit area    | m     |
108   !! sv_i        |      -      |    Sea ice salt content         | ppt.m |
109   !! oa_i        !      -      !    Sea ice areal age content    | s     |
110   !! e_i         !      -      !    Ice enthalpy                 | J/m2  |
111   !!      -      ! e_i_1d      !    Ice enthalpy per unit vol.   | J/m3  |
112   !! e_s         !      -      !    Snow enthalpy                | J/m2  |
113   !!      -      ! e_s_1d      !    Snow enthalpy per unit vol.  | J/m3  |
114   !!                                                                     |
115   !!-------------|-------------|---------------------------------|-------|
116   !!                                                                     |
117   !! ** Equivalent variables                                             |
118   !!-------------|-------------|---------------------------------|-------|
119   !!                                                                     |
120   !! h_i         | h_i_1d      |    Ice thickness                | m     |
121   !! h_s         ! h_s_1d      |    Snow depth                   | m     |
122   !! s_i         ! s_i_1d      |    Sea ice bulk salinity        ! ppt   |
123   !! sz_i        ! sz_i_1d     |    Sea ice salinity profile     ! ppt   |
124   !! o_i         !      -      |    Sea ice Age                  ! s     |
125   !! t_i         ! t_i_1d      |    Sea ice temperature          ! K     |
126   !! t_s         ! t_s_1d      |    Snow temperature             ! K     |
127   !! t_su        ! t_su_1d     |    Sea ice surface temperature  ! K     |
128   !!                                                                     |
129   !! notes: the ice model only sees a bulk (i.e., vertically averaged)   |
130   !!        salinity, except in thermodynamic computations, for which    |
131   !!        the salinity profile is computed as a function of bulk       |
132   !!        salinity                                                     |
133   !!                                                                     |
134   !!        the sea ice surface temperature is not associated to any     |
135   !!        heat content. Therefore, it is not a state variable and      |
136   !!        does not have to be advected. Nevertheless, it has to be     |
137   !!        computed to determine whether the ice is melting or not      |
138   !!                                                                     |
139   !! ******************************************************************* |
140   !! ***         Category-summed state variables (diagnostic)        *** |
141   !! ******************************************************************* |
142   !! at_i        | at_i_1d     |    Total ice concentration      |       |
143   !! vt_i        |      -      |    Total ice vol. per unit area | m     |
144   !! vt_s        |      -      |    Total snow vol. per unit ar. | m     |
145   !! sm_i        |      -      |    Mean sea ice salinity        | ppt   |
146   !! tm_i        |      -      |    Mean sea ice temperature     | K     |
147   !! tm_s        |      -      |    Mean snow    temperature     | K     |
148   !! et_i        !      -      !    Total ice enthalpy           | J/m2  |
149   !! et_s        !      -      !    Total snow enthalpy          | J/m2  |
150   !! bv_i        !      -      !    relative brine volume        | ???   |
151   !!=====================================================================
152
153   !!----------------------------------------------------------------------
154   !! * Share Module variables
155   !!----------------------------------------------------------------------
156   !                                     !!** ice-generic parameters namelist (nampar) **
157   INTEGER           , PUBLIC ::   jpl              !: number of ice  categories
158   INTEGER           , PUBLIC ::   nlay_i           !: number of ice  layers
159   INTEGER           , PUBLIC ::   nlay_s           !: number of snow layers
160   INTEGER           , PUBLIC ::   nn_virtual_itd   !: virtual ITD mono-category parameterizations (1-3) or not (0)
161   LOGICAL           , PUBLIC ::   ln_icedyn        !: flag for ice dynamics (T) or not (F)
162   LOGICAL           , PUBLIC ::   ln_icethd        !: flag for ice thermo   (T) or not (F)
163   REAL(wp)          , PUBLIC ::   rn_amax_n        !: maximum ice concentration Northern hemisphere
164   REAL(wp)          , PUBLIC ::   rn_amax_s        !: maximum ice concentration Southern hemisphere
165   CHARACTER(len=256), PUBLIC ::   cn_icerst_in     !: suffix of ice restart name (input)
166   CHARACTER(len=256), PUBLIC ::   cn_icerst_out    !: suffix of ice restart name (output)
167   CHARACTER(len=256), PUBLIC ::   cn_icerst_indir  !: ice restart input directory
168   CHARACTER(len=256), PUBLIC ::   cn_icerst_outdir !: ice restart output directory
169
170   !                                     !!** ice-itd namelist (namitd) **
171   REAL(wp), PUBLIC ::   rn_himin         !: minimum ice thickness
172   
173   !                                     !!** ice-dynamics namelist (namdyn) **
174   REAL(wp), PUBLIC ::   rn_ishlat        !: lateral boundary condition for sea-ice
175   LOGICAL , PUBLIC ::   ln_landfast      !: landfast ice parameterization (T or F)
176   REAL(wp), PUBLIC ::   rn_gamma         !:    fraction of ocean depth that ice must reach to initiate landfast ice
177   REAL(wp), PUBLIC ::   rn_icebfr        !:    maximum bottom stress per unit area of contact (landfast ice)
178   REAL(wp), PUBLIC ::   rn_lfrelax       !:    relaxation time scale (s-1) to reach static friction (landfast ice)
179   !
180   !                                     !!** ice-rheology namelist (namrhg) **
181   LOGICAL , PUBLIC ::   ln_aEVP          !: using adaptive EVP (T or F)
182   REAL(wp), PUBLIC ::   rn_creepl        !: creep limit : has to be under 1.0e-9
183   REAL(wp), PUBLIC ::   rn_ecc           !: eccentricity of the elliptical yield curve
184   INTEGER , PUBLIC ::   nn_nevp          !: number of iterations for subcycling
185   REAL(wp), PUBLIC ::   rn_relast        !: ratio => telast/rdt_ice (1/3 or 1/9 depending on nb of subcycling nevp)
186   !
187   !                                     !!** ice-surface forcing namelist (namforcing) **
188                                          ! -- icethd_dh -- !
189   REAL(wp), PUBLIC ::   rn_blow_s        !: coef. for partitioning of snowfall between leads and sea ice
190                                          ! -- icethd -- !
191   REAL(wp), PUBLIC ::   rn_cio           !: drag coefficient for oceanic stress
192   INTEGER , PUBLIC ::   nn_flxdist       !: Redistribute heat flux over ice categories
193   !                                      !   =-1  Do nothing (needs N(cat) fluxes)
194   !                                      !   = 0  Average N(cat) fluxes then apply the average over the N(cat) ice
195   !                                      !   = 1  Average N(cat) fluxes then redistribute over the N(cat) ice using T-ice and albedo sensitivity
196   !                                      !   = 2  Redistribute a single flux over categories
197   INTEGER , PUBLIC            ::   nice_jules           !: Choice of jules coupling
198   INTEGER , PUBLIC, PARAMETER ::   np_jules_OFF    = 0  !: no Jules coupling (ice thermodynamics forced via qsr and qns)
199   INTEGER , PUBLIC, PARAMETER ::   np_jules_EMULE  = 1  !: emulated Jules coupling via icethd_zdf.F90 (BL99) (1st round compute qcn and qsr_tr, 2nd round use it)
200   INTEGER , PUBLIC, PARAMETER ::   np_jules_ACTIVE = 2  !: active Jules coupling                      (SM0L) (compute qcn and qsr_tr via sbcblk.F90 or sbccpl.F90)
201
202   !                                     !!** ice-vertical diffusion namelist (namthd_zdf) **
203   LOGICAL , PUBLIC ::   ln_cndi_U64      !: thermal conductivity: Untersteiner (1964)
204   LOGICAL , PUBLIC ::   ln_cndi_P07      !: thermal conductivity: Pringle et al (2007)
205   REAL(wp), PUBLIC ::   rn_kappa_i       !: coef. for the extinction of radiation Grenfell et al. (2006) [1/m]
206   REAL(wp), PUBLIC ::   rn_cnd_s         !: thermal conductivity of the snow [W/m/K]   
207
208   !                                     !!** ice-salinity namelist (namthd_sal) **
209   INTEGER , PUBLIC ::   nn_icesal        !: salinity configuration used in the model
210   !                                      ! 1 - constant salinity in both space and time
211   !                                      ! 2 - prognostic salinity (s(z,t))
212   !                                      ! 3 - salinity profile, constant in time
213   REAL(wp), PUBLIC ::   rn_icesal        !: bulk salinity (ppt) in case of constant salinity
214   REAL(wp), PUBLIC ::   rn_simax         !: maximum ice salinity [PSU]
215   REAL(wp), PUBLIC ::   rn_simin         !: minimum ice salinity [PSU]
216
217   !                                     !!** ice-ponds namelist (namthd_pnd)
218   LOGICAL , PUBLIC ::   ln_pnd_H12       !: Melt ponds scheme from Holland et al 2012
219   LOGICAL , PUBLIC ::   ln_pnd_fwb       !: melt ponds store freshwater
220   LOGICAL , PUBLIC ::   ln_pnd_CST       !: Melt ponds scheme with constant fraction and depth
221   REAL(wp), PUBLIC ::   rn_apnd          !: prescribed pond fraction (0<rn_apnd<1)
222   REAL(wp), PUBLIC ::   rn_hpnd          !: prescribed pond depth    (0<rn_hpnd<1)
223   LOGICAL , PUBLIC ::   ln_pnd_alb       !: melt ponds affect albedo
224
225   !                                     !!** ice-diagnostics namelist (namdia) **
226   LOGICAL , PUBLIC ::   ln_icediachk     !: flag for ice diag (T) or not (F)
227   LOGICAL , PUBLIC ::   ln_icediahsb     !: flag for ice diag (T) or not (F)
228   LOGICAL , PUBLIC ::   ln_icectl        !: flag for sea-ice points output (T) or not (F)
229   INTEGER , PUBLIC ::   iiceprt          !: debug i-point
230   INTEGER , PUBLIC ::   jiceprt          !: debug j-point
231
232   !                                     !!** some other parameters
233   INTEGER , PUBLIC ::   kt_ice           !: iteration number
234   REAL(wp), PUBLIC ::   rdt_ice          !: ice time step
235   REAL(wp), PUBLIC ::   r1_rdtice        !: = 1. / rdt_ice
236   REAL(wp), PUBLIC ::   r1_nlay_i        !: 1 / nlay_i
237   REAL(wp), PUBLIC ::   r1_nlay_s        !: 1 / nlay_s
238   REAL(wp), PUBLIC ::   rswitch          !: switch for the presence of ice (1) or not (0)
239   REAL(wp), PUBLIC ::   rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft   !: conservation diagnostics
240   REAL(wp), PUBLIC, PARAMETER ::   epsi06 = 1.e-06_wp  !: small number
241   REAL(wp), PUBLIC, PARAMETER ::   epsi10 = 1.e-10_wp  !: small number
242   REAL(wp), PUBLIC, PARAMETER ::   epsi20 = 1.e-20_wp  !: small number
243
244
245   !                                     !!** define arrays
246   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_oce,v_oce !: surface ocean velocity used in ice dynamics
247   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ht_i_new    !: ice collection thickness accreted in leads
248   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   strength    !: ice strength
249   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   stress1_i, stress2_i, stress12_i   !: 1st, 2nd & diagonal stress tensor element
250   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   delta_i     !: ice rheology elta factor (Flato & Hibler 95) [s-1]
251   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   divu_i      !: Divergence of the velocity field [s-1]
252   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   shear_i     !: Shear of the velocity field [s-1]
253   !
254   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   t_bo        !: Sea-Ice bottom temperature [Kelvin]     
255   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qlead       !: heat balance of the lead (or of the open ocean)
256   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fhtur       !: net downward heat flux from the ice to the ocean
257   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fhld        !: heat flux from the lead used for bottom melting
258
259   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw     !: snow-ocean mass exchange   [kg.m-2.s-1]
260   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sni !: snow ice growth component of wfx_snw [kg.m-2.s-1]
261   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sum !: surface melt component of wfx_snw [kg.m-2.s-1]
262   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_pnd     !: melt pond-ocean mass exchange   [kg.m-2.s-1]
263   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_spr     !: snow precipitation on ice  [kg.m-2.s-1]
264   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sub     !: sublimation of snow/ice    [kg.m-2.s-1]
265   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sub !: snow sublimation           [kg.m-2.s-1]
266   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_ice_sub !: ice sublimation            [kg.m-2.s-1]
267
268   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_dyn !: dynamical component of wfx_snw    [kg.m-2.s-1]
269
270   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_ice     !: ice-ocean mass exchange                   [kg.m-2.s-1]
271   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sni     !: snow ice growth component of wfx_ice      [kg.m-2.s-1]
272   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_opw     !: lateral ice growth component of wfx_ice   [kg.m-2.s-1]
273   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_bog     !: bottom ice growth component of wfx_ice    [kg.m-2.s-1]
274   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_dyn     !: dynamical ice growth component of wfx_ice [kg.m-2.s-1]
275   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_bom     !: bottom melt component of wfx_ice          [kg.m-2.s-1]
276   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sum     !: surface melt component of wfx_ice         [kg.m-2.s-1]
277   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_lam     !: lateral melt component of wfx_ice         [kg.m-2.s-1]
278   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_res     !: residual component of wfx_ice             [kg.m-2.s-1]
279
280   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   afx_tot     !: ice concentration tendency (total)          [s-1]
281
282   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bog     !: salt flux due to ice growth/melt                      [PSU/m2/s]
283   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bom     !: salt flux due to ice growth/melt                      [PSU/m2/s]
284   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_lam     !: salt flux due to ice growth/melt                      [PSU/m2/s]
285   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sum     !: salt flux due to ice growth/melt                      [PSU/m2/s]
286   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sni     !: salt flux due to ice growth/melt                      [PSU/m2/s]
287   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_opw     !: salt flux due to ice growth/melt                      [PSU/m2/s]
288   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_bri     !: salt flux due to brine rejection                      [PSU/m2/s]
289   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_dyn     !: salt flux due to porous ridged ice formation          [PSU/m2/s]
290   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_res     !: residual salt flux due to correction of ice thickness [PSU/m2/s]
291
292   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_sub     !: salt flux due to ice sublimation
293
294   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_bog     !: total heat flux causing bottom ice growth        [W.m-2]
295   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_bom     !: total heat flux causing bottom ice melt          [W.m-2]
296   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_sum     !: total heat flux causing surface ice melt         [W.m-2]
297   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_opw     !: total heat flux causing open water ice formation [W.m-2]
298   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_dif     !: total heat flux causing Temp change in the ice   [W.m-2]
299   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_snw     !: heat flux for snow melt                          [W.m-2]
300   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err_dif !: heat flux remaining due to change in non-solar flux [W.m-2]
301   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err_rem !: heat flux error after heat remapping             [W.m-2]
302   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_in      !: heat flux available for thermo transformations   [W.m-2]
303   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_out     !: heat flux remaining at the end of thermo transformations  [W.m-2]
304   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_err_sub !: mass flux error after sublimation [kg.m-2.s-1]
305   
306   ! heat flux associated with ice-atmosphere mass exchange
307   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_sub     !: heat flux for sublimation  [W.m-2]
308   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_spr     !: heat flux of the snow precipitation  [W.m-2]
309
310   ! heat flux associated with ice-ocean mass exchange
311   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_thd     !: ice-ocean heat flux from thermo processes (icethd_dh) [W.m-2]
312   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_dyn     !: ice-ocean heat flux from ridging                      [W.m-2]
313   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_res     !: residual heat flux due to correction of ice thickness [W.m-2]
314
315   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rn_amax_2d     !: maximum ice concentration 2d array
316   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ftr_ice        !: transmitted solar radiation under ice
317   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t1_ice         !: temperature of the first layer (Jules coupling) [K]
318   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   cnd_ice        !: effective conductivity at the top of ice/snow (Jules coupling) [W.m-2.K-1]
319
320   !!----------------------------------------------------------------------
321   !! * Ice global state variables
322   !!----------------------------------------------------------------------
323   !! Variables defined for each ice category
324   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   h_i       !: Ice thickness (m)
325   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i       !: Ice fractional areas (concentration)
326   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_i       !: Ice volume per unit area (m)
327   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_s       !: Snow volume per unit area(m)
328   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   h_s       !: Snow thickness (m)
329   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t_su      !: Sea-Ice Surface Temperature (K)
330   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   s_i       !: Sea-Ice Bulk salinity (ppt)
331   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sv_i      !: Sea-Ice Bulk salinity times volume per area (ppt.m)
332   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   o_i       !: Sea-Ice Age (s)
333   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   oa_i      !: Sea-Ice Age times ice area (s)
334   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   bv_i      !: brine volume
335
336   !! Variables summed over all categories, or associated to all the ice in a single grid cell
337   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_ice, v_ice !: components of the ice velocity (m/s)
338   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   vt_i , vt_s  !: ice and snow total volume per unit area (m)
339   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   at_i         !: ice total fractional area (ice concentration)
340   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ato_i        !: =1-at_i ; total open water fractional area
341   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   et_i , et_s  !: ice and snow total heat content
342   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tm_i         !: mean ice temperature over all categories
343   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tm_s         !: mean snw temperature over all categories
344   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bvm_i        !: brine volume averaged over all categories
345   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sm_i         !: mean sea ice salinity averaged over all categories [PSU]
346   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tm_su        !: mean surface temperature over all categories
347   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hm_i         !: mean ice  thickness over all categories
348   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hm_s         !: mean snow thickness over all categories
349   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   om_i         !: mean ice age over all categories
350   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tau_icebfr   !: ice friction with bathy (landfast param activated)
351
352   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_s      !: Snow temperatures     [K]
353   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s      !: Snow enthalpy         [J/m2]
354   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_i      !: ice temperatures      [K]
355   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i      !: ice enthalpy          [J/m2]
356   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   sz_i     !: ice salinity          [PSU]
357
358   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_ip       !: melt pond fraction per grid cell area
359   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_ip       !: melt pond volume per grid cell area [m]
360   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_ip_frac  !: melt pond volume per ice area
361   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   h_ip       !: melt pond thickness [m]
362
363   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   at_ip      !: total melt pond fraction
364   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   vt_ip      !: total melt pond volume per unit area [m]
365
366   !!----------------------------------------------------------------------
367   !! * Old values of global variables
368   !!----------------------------------------------------------------------
369   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_s_b, v_i_b, h_s_b, h_i_b    !: snow and ice volumes/thickness
370   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_i_b, sv_i_b, oa_i_b         !:
371   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s_b                         !: snow heat content
372   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i_b                         !: ice temperatures
373   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   u_ice_b, v_ice_b              !: ice velocity
374   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   at_i_b                        !: ice concentration (total)
375           
376   !!----------------------------------------------------------------------
377   !! * Ice thickness distribution variables
378   !!----------------------------------------------------------------------
379   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   hi_max         !: Boundary of ice thickness categories in thickness space
380   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   hi_mean        !: Mean ice thickness in catgories
381   !
382   !!----------------------------------------------------------------------
383   !! * Ice diagnostics
384   !!----------------------------------------------------------------------
385   ! thd refers to changes induced by thermodynamics
386   ! trp   ''         ''     ''       advection (transport of ice)
387   !
388   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_vi   !: transport of ice volume
389   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_vs   !: transport of snw volume
390   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_ei   !: transport of ice enthalpy (W/m2)
391   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_es   !: transport of snw enthalpy (W/m2)
392   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_sv   !: transport of salt content
393   !
394   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_heat     !: snw/ice heat content variation   [W/m2]
395   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_sice     !: ice salt content variation   []
396   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_vice     !: ice volume variation   [m/s]
397   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_vsnw     !: snw volume variation   [m/s]
398
399   !
400   !!----------------------------------------------------------------------
401   !! * SIMIP extra diagnostics
402   !!----------------------------------------------------------------------
403   ! Extra sea ice diagnostics to address the data request
404   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t_si          !: Temperature at Snow-ice interface (K)
405   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   tm_si         !: mean temperature at the snow-ice interface (K)
406   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   diag_fc_bo    !: Bottom conduction flux (W/m2)
407   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   diag_fc_su    !: Surface conduction flux (W/m2)
408
409   !
410   !!----------------------------------------------------------------------
411   !! NEMO/ICE 4.0 , NEMO Consortium (2017)
412   !! $Id$
413   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
414   !!----------------------------------------------------------------------
415CONTAINS
416
417   FUNCTION ice_alloc()
418      !!-----------------------------------------------------------------
419      !!               *** Routine ice_alloc ***
420      !!-----------------------------------------------------------------
421      INTEGER :: ice_alloc
422      !
423      INTEGER :: ierr(18), ii
424      !!-----------------------------------------------------------------
425
426      ierr(:) = 0
427
428      ! What could be one huge allocate statement is broken-up to try to
429      ! stay within Fortran's max-line length limit.
430      ii = 1
431      ALLOCATE( u_oce   (jpi,jpj) , v_oce    (jpi,jpj) , ht_i_new (jpi,jpj) ,                        &
432         &      strength(jpi,jpj) , stress1_i(jpi,jpj) , stress2_i(jpi,jpj) , stress12_i(jpi,jpj) ,  &
433         &      delta_i (jpi,jpj) , divu_i   (jpi,jpj) , shear_i  (jpi,jpj) , STAT=ierr(ii) )
434
435      ii = ii + 1
436      ALLOCATE( t_bo   (jpi,jpj) , wfx_snw_sni(jpi,jpj) ,                                                &
437         &      wfx_snw(jpi,jpj) , wfx_snw_dyn(jpi,jpj) , wfx_snw_sum(jpi,jpj) , wfx_snw_sub(jpi,jpj) ,  &
438         &      wfx_ice(jpi,jpj) , wfx_sub    (jpi,jpj) , wfx_ice_sub(jpi,jpj) , wfx_lam    (jpi,jpj) ,  &
439         &      wfx_pnd(jpi,jpj) ,                                                              &
440         &      wfx_bog(jpi,jpj) , wfx_dyn(jpi,jpj) , wfx_bom(jpi,jpj) , wfx_sum(jpi,jpj) ,     &
441         &      wfx_res(jpi,jpj) , wfx_sni(jpi,jpj) , wfx_opw(jpi,jpj) , wfx_spr(jpi,jpj) ,     &
442         &      afx_tot(jpi,jpj) , rn_amax_2d(jpi,jpj),                                         &
443         &      fhtur  (jpi,jpj) , qlead  (jpi,jpj) ,                                           &
444         &      sfx_res(jpi,jpj) , sfx_bri(jpi,jpj) , sfx_dyn(jpi,jpj) , sfx_sub(jpi,jpj) , sfx_lam(jpi,jpj) ,  &
445         &      sfx_bog(jpi,jpj) , sfx_bom(jpi,jpj) , sfx_sum(jpi,jpj) , sfx_sni(jpi,jpj) , sfx_opw(jpi,jpj) ,  &
446         &      hfx_res(jpi,jpj) , hfx_snw(jpi,jpj) , hfx_sub(jpi,jpj) ,     & 
447         &      hfx_in (jpi,jpj) , hfx_out(jpi,jpj) , fhld   (jpi,jpj) ,                        &
448         &      hfx_sum(jpi,jpj) , hfx_bom(jpi,jpj) , hfx_bog(jpi,jpj) , hfx_dif(jpi,jpj) ,     &
449         &      hfx_opw(jpi,jpj) , hfx_thd(jpi,jpj) , hfx_dyn(jpi,jpj) , hfx_spr(jpi,jpj) ,     &
450         &      hfx_err_dif(jpi,jpj) , hfx_err_rem(jpi,jpj) , wfx_err_sub(jpi,jpj)        ,  STAT=ierr(ii) )
451
452      ! * Ice global state variables
453      ii = ii + 1
454      ALLOCATE( ftr_ice(jpi,jpj,jpl) , cnd_ice(jpi,jpj,jpl) , t1_ice(jpi,jpj,jpl) , &
455         &      h_i (jpi,jpj,jpl) , a_i (jpi,jpj,jpl) , v_i (jpi,jpj,jpl) ,     &
456         &      v_s (jpi,jpj,jpl) , h_s (jpi,jpj,jpl) , t_su(jpi,jpj,jpl) ,     &
457         &      s_i (jpi,jpj,jpl) , sv_i(jpi,jpj,jpl) , o_i (jpi,jpj,jpl) ,     &
458         &      oa_i(jpi,jpj,jpl) , bv_i(jpi,jpj,jpl) ,  STAT=ierr(ii) )
459      ii = ii + 1
460      ALLOCATE( u_ice(jpi,jpj) , v_ice(jpi,jpj) ,                                      &
461         &      vt_i (jpi,jpj) , vt_s (jpi,jpj) , at_i(jpi,jpj) , ato_i(jpi,jpj) ,     &
462         &      et_i (jpi,jpj) , et_s (jpi,jpj) , tm_i(jpi,jpj) , tm_s (jpi,jpj) , bvm_i(jpi,jpj) ,  &
463         &      sm_i (jpi,jpj) , tm_su(jpi,jpj) , hm_i(jpi,jpj) , hm_s (jpi,jpj) ,     &
464         &      om_i (jpi,jpj) , tau_icebfr(jpi,jpj)                             , STAT=ierr(ii) )
465      ii = ii + 1
466      ALLOCATE( t_s(jpi,jpj,nlay_s,jpl) , e_s(jpi,jpj,nlay_s,jpl) , STAT=ierr(ii) )
467      ii = ii + 1
468      ALLOCATE( t_i(jpi,jpj,nlay_i,jpl) , e_i(jpi,jpj,nlay_i,jpl) , sz_i(jpi,jpj,nlay_i,jpl) , STAT=ierr(ii) )
469
470      ii = ii + 1
471      ALLOCATE( a_ip(jpi,jpj,jpl) , v_ip(jpi,jpj,jpl) , a_ip_frac(jpi,jpj,jpl) , h_ip(jpi,jpj,jpl) , STAT = ierr(ii) )
472      ii = ii + 1
473      ALLOCATE( at_ip(jpi,jpj) , vt_ip(jpi,jpj) , STAT = ierr(ii) )
474
475      ! * Old values of global variables
476      ii = ii + 1
477      ALLOCATE( v_s_b  (jpi,jpj,jpl) , v_i_b (jpi,jpj,jpl) , h_s_b(jpi,jpj,jpl)        , h_i_b(jpi,jpj,jpl)        ,   &
478         &      a_i_b  (jpi,jpj,jpl) , sv_i_b(jpi,jpj,jpl) , e_i_b(jpi,jpj,nlay_i,jpl) , e_s_b(jpi,jpj,nlay_s,jpl) ,   &
479         &      oa_i_b (jpi,jpj,jpl)                                                   , STAT=ierr(ii) )
480      ii = ii + 1
481      ALLOCATE( u_ice_b(jpi,jpj) , v_ice_b(jpi,jpj) , at_i_b(jpi,jpj) , STAT=ierr(ii) )
482     
483      ! * Ice thickness distribution variables
484      ii = ii + 1
485      ALLOCATE( hi_max(0:jpl), hi_mean(jpl),  STAT=ierr(ii) )
486
487      ! * Ice diagnostics
488      ii = ii + 1
489      ALLOCATE( diag_trp_vi(jpi,jpj) , diag_trp_vs (jpi,jpj) , diag_trp_ei(jpi,jpj),   & 
490         &      diag_trp_es(jpi,jpj) , diag_trp_sv (jpi,jpj) , diag_heat  (jpi,jpj),   &
491         &      diag_sice  (jpi,jpj) , diag_vice   (jpi,jpj) , diag_vsnw  (jpi,jpj), STAT=ierr(ii) )
492
493      ! * SIMIP diagnostics
494      ii = ii + 1
495      ALLOCATE( t_si (jpi,jpj,jpl) , tm_si(jpi,jpj) , diag_fc_bo(jpi,jpj) , diag_fc_su(jpi,jpj) , STAT = ierr(ii) )
496
497      ice_alloc = MAXVAL( ierr(:) )
498      IF( ice_alloc /= 0 )   CALL ctl_warn('ice_alloc: failed to allocate arrays.')
499      !
500   END FUNCTION ice_alloc
501
502#else
503   !!----------------------------------------------------------------------
504   !!   Default option         Empty module           NO SI3 sea-ice model
505   !!----------------------------------------------------------------------
506#endif
507
508   !!======================================================================
509END MODULE ice
Note: See TracBrowser for help on using the repository browser.