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 NEMO/trunk/src/ICE – NEMO

source: NEMO/trunk/src/ICE/ice.F90

Last change on this file was 15388, checked in by clem, 3 years ago

slightly rearrange ice thermo. No change in sette

  • Property svn:keywords set to Id
File size: 45.2 KB
RevLine 
[825]1MODULE ice
[2528]2   !!======================================================================
[9019]3   !!                        ***  MODULE  ice  ***
4   !!   sea-ice:  ice variables defined in memory
5   !!======================================================================
[9604]6   !! History :  3.0  !  2008-03  (M. Vancoppenolle) Original code
7   !!            4.0  !  2018     (many people)      SI3 [aka Sea Ice cube]
[2528]8   !!----------------------------------------------------------------------
[9570]9#if defined key_si3
[825]10   !!----------------------------------------------------------------------
[9570]11   !!   'key_si3'                                       SI3 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
[9019]19   PUBLIC   ice_alloc   ! called by icestp.F90
[2715]20
[834]21   !!======================================================================
22   !!                                                                     |
[2528]23   !!              I C E   S T A T E   V A R I A B L E S                  |
[834]24   !!                                                                     |
25   !! Introduction :                                                      |
26   !! --------------                                                      |
27   !! Every ice-covered grid cell is characterized by a series of state   |
28   !! variables. To account for unresolved spatial variability in ice     |
29   !! thickness, the ice cover in divided in ice thickness categories.    |
30   !!                                                                     |
31   !! Sea ice state variables depend on the ice thickness category        |
32   !!                                                                     |
33   !! Those variables are divided into two groups                         |
34   !! * Extensive (or global) variables.                                  |
35   !!   These are the variables that are transported by all means         |
36   !! * Intensive (or equivalent) variables.                              |
37   !!   These are the variables that are either physically more           |
38   !!   meaningful and/or used in ice thermodynamics                      |
39   !!                                                                     |
40   !! List of ice state variables :                                       |
41   !! -----------------------------                                       |
42   !!                                                                     |
43   !!-------------|-------------|---------------------------------|-------|
44   !!   name in   |   name in   |              meaning            | units |
45   !! 2D routines | 1D routines |                                 |       |
46   !!-------------|-------------|---------------------------------|-------|
47   !!                                                                     |
48   !! ******************************************************************* |
49   !! ***         Dynamical variables (prognostic)                    *** |
50   !! ******************************************************************* |
51   !!                                                                     |
[10882]52   !! u_ice       |      -      |    ice velocity in i-direction  | m/s   |
53   !! v_ice       |      -      |    ice velocity in j-direction  | m/s   |
[834]54   !!                                                                     |
55   !! ******************************************************************* |
56   !! ***         Category dependent state variables (prognostic)     *** |
57   !! ******************************************************************* |
58   !!                                                                     |
59   !! ** Global variables                                                 |
60   !!-------------|-------------|---------------------------------|-------|
[10882]61   !! a_i         |   a_i_1d    |    Ice concentration            |       |
[834]62   !! v_i         |      -      |    Ice volume per unit area     | m     |
63   !! v_s         |      -      |    Snow volume per unit area    | m     |
[10882]64   !! sv_i        |      -      |    Sea ice salt content         | pss.m |
65   !! oa_i        |      -      |    Sea ice areal age content    | s     |
[14072]66   !! e_i         |             |    Ice enthalpy                 | J/m2  |
67   !!             |    e_i_1d   |    Ice enthalpy per unit vol.   | J/m3  |
68   !! e_s         |             |    Snow enthalpy                | J/m2  |
69   !!             |    e_s_1d   |    Snow enthalpy per unit vol.  | J/m3  |
[10882]70   !! a_ip        |      -      |    Ice pond concentration       |       |
71   !! v_ip        |      -      |    Ice pond volume per unit area| m     |
[13472]72   !! v_il        |    v_il_1d  |    Ice pond lid volume per area | m     |
[834]73   !!                                                                     |
74   !!-------------|-------------|---------------------------------|-------|
75   !!                                                                     |
76   !! ** Equivalent variables                                             |
77   !!-------------|-------------|---------------------------------|-------|
78   !!                                                                     |
[9019]79   !! h_i         | h_i_1d      |    Ice thickness                | m     |
80   !! h_s         ! h_s_1d      |    Snow depth                   | m     |
[10882]81   !! s_i         ! s_i_1d      |    Sea ice bulk salinity        ! pss   |
82   !! sz_i        ! sz_i_1d     |    Sea ice salinity profile     ! pss   |
[9019]83   !! o_i         !      -      |    Sea ice Age                  ! s     |
[4872]84   !! t_i         ! t_i_1d      |    Sea ice temperature          ! K     |
85   !! t_s         ! t_s_1d      |    Snow temperature             ! K     |
86   !! t_su        ! t_su_1d     |    Sea ice surface temperature  ! K     |
[10882]87   !! h_ip        | h_ip_1d     |    Ice pond thickness           | m     |
[13472]88   !! h_il        | h_il_1d     |    Ice pond lid thickness       | m     |
[834]89   !!                                                                     |
90   !! notes: the ice model only sees a bulk (i.e., vertically averaged)   |
91   !!        salinity, except in thermodynamic computations, for which    |
92   !!        the salinity profile is computed as a function of bulk       |
93   !!        salinity                                                     |
94   !!                                                                     |
95   !!        the sea ice surface temperature is not associated to any     |
96   !!        heat content. Therefore, it is not a state variable and      |
97   !!        does not have to be advected. Nevertheless, it has to be     |
98   !!        computed to determine whether the ice is melting or not      |
99   !!                                                                     |
100   !! ******************************************************************* |
101   !! ***         Category-summed state variables (diagnostic)        *** |
102   !! ******************************************************************* |
[4872]103   !! at_i        | at_i_1d     |    Total ice concentration      |       |
[834]104   !! vt_i        |      -      |    Total ice vol. per unit area | m     |
105   !! vt_s        |      -      |    Total snow vol. per unit ar. | m     |
[11536]106   !! st_i        |      -      |    Total Sea ice salt content   | pss.m |
[10882]107   !! sm_i        |      -      |    Mean sea ice salinity        | pss   |
[834]108   !! tm_i        |      -      |    Mean sea ice temperature     | K     |
[9433]109   !! tm_s        |      -      |    Mean snow    temperature     | K     |
[14072]110   !! et_i        |      -      |    Total ice enthalpy           | J/m2  |
111   !! et_s        |      -      |    Total snow enthalpy          | J/m2  |
112   !! bv_i        |      -      |    relative brine volume        | ???   |
[10882]113   !! at_ip       |      -      |    Total ice pond concentration |       |
[11536]114   !! hm_ip       |      -      |    Mean ice pond depth          | m     |
[10882]115   !! vt_ip       |      -      |    Total ice pond vol. per unit area| m |
[13472]116   !! hm_il       |      -      |    Mean ice pond lid depth      | m     |
117   !! vt_il       |      -      |    Total ice pond lid vol. per area | m |
[834]118   !!=====================================================================
[825]119
[9019]120   !!----------------------------------------------------------------------
[825]121   !! * Share Module variables
[9019]122   !!----------------------------------------------------------------------
123   !                                     !!** ice-generic parameters namelist (nampar) **
[14072]124   INTEGER           , PUBLIC ::   jpl              !: number of ice  categories
125   INTEGER           , PUBLIC ::   nlay_i           !: number of ice  layers
126   INTEGER           , PUBLIC ::   nlay_s           !: number of snow layers
[10531]127   LOGICAL           , PUBLIC ::   ln_virtual_itd   !: virtual ITD mono-category parameterization (T) or not (F)
[9019]128   LOGICAL           , PUBLIC ::   ln_icedyn        !: flag for ice dynamics (T) or not (F)
129   LOGICAL           , PUBLIC ::   ln_icethd        !: flag for ice thermo   (T) or not (F)
130   REAL(wp)          , PUBLIC ::   rn_amax_n        !: maximum ice concentration Northern hemisphere
131   REAL(wp)          , PUBLIC ::   rn_amax_s        !: maximum ice concentration Southern hemisphere
132   CHARACTER(len=256), PUBLIC ::   cn_icerst_in     !: suffix of ice restart name (input)
133   CHARACTER(len=256), PUBLIC ::   cn_icerst_out    !: suffix of ice restart name (output)
134   CHARACTER(len=256), PUBLIC ::   cn_icerst_indir  !: ice restart input directory
135   CHARACTER(len=256), PUBLIC ::   cn_icerst_outdir !: ice restart output directory
[1465]136
[9019]137   !                                     !!** ice-itd namelist (namitd) **
138   REAL(wp), PUBLIC ::   rn_himin         !: minimum ice thickness
[14072]139
[9019]140   !                                     !!** ice-dynamics namelist (namdyn) **
141   REAL(wp), PUBLIC ::   rn_ishlat        !: lateral boundary condition for sea-ice
[14072]142   LOGICAL , PUBLIC ::   ln_landfast_L16  !: landfast ice parameterizationfrom lemieux2016
[13472]143   REAL(wp), PUBLIC ::   rn_lf_depfra     !:    fraction of ocean depth that ice must reach to initiate landfast ice
[14072]144   REAL(wp), PUBLIC ::   rn_lf_bfr        !:    maximum bottom stress per unit area of contact (lemieux2016) or per unit volume (home)
[13472]145   REAL(wp), PUBLIC ::   rn_lf_relax      !:    relaxation time scale (s-1) to reach static friction
146   REAL(wp), PUBLIC ::   rn_lf_tensile    !:    isotropic tensile strength
[9019]147   !
[10413]148   !                                     !!** ice-ridging/rafting namelist (namdyn_rdgrft) **
[15334]149   LOGICAL,  PUBLIC ::   ln_str_H79       !: ice strength parameterization (Hibler79) (may be used in rheology)
[10413]150   REAL(wp), PUBLIC ::   rn_crhg          !: determines changes in ice strength (also used for landfast param)
[15334]151   REAL(wp), PUBLIC ::   rn_pstar         !: determines ice strength, Hibler JPO79 (may be used in rheology)
[10413]152   !
153   !                                     !!** ice-rheology namelist (namdyn_rhg) **
[14006]154   ! -- evp
[13999]155   LOGICAL , PUBLIC ::   ln_rhg_EVP       ! EVP rheology switch, used for rdgrft and rheology
156   LOGICAL , PUBLIC ::   ln_rhg_EAP       ! EAP rheology switch, used for rdgrft and rheology
[14072]157   LOGICAL , PUBLIC ::   ln_aEVP          !: using adaptive EVP (T or F)
[14006]158   REAL(wp), PUBLIC ::   rn_creepl        !: creep limit (has to be low enough, circa 10-9 m/s, depending on rheology)
[5123]159   REAL(wp), PUBLIC ::   rn_ecc           !: eccentricity of the elliptical yield curve
[7646]160   INTEGER , PUBLIC ::   nn_nevp          !: number of iterations for subcycling
[14072]161   REAL(wp), PUBLIC ::   rn_relast        !: ratio => telast/rDt_ice (1/3 or 1/9 depending on nb of subcycling nevp)
162   INTEGER , PUBLIC ::   nn_rhg_chkcvg    !: check ice rheology convergence
[14006]163   ! -- vp
164   LOGICAL , PUBLIC ::   ln_rhg_VP        !: VP rheology
165   INTEGER , PUBLIC ::   nn_vp_nout       !: Number of outer iterations
166   INTEGER , PUBLIC ::   nn_vp_ninn       !: Number of inner iterations (linear system solver)
167   INTEGER , PUBLIC ::   nn_vp_chkcvg     !: Number of iterations every each convergence is checked
[9019]168   !
[10413]169   !                                     !!** ice-advection namelist (namdyn_adv) **
170   LOGICAL , PUBLIC ::   ln_adv_Pra       !: Prather        advection scheme
171   LOGICAL , PUBLIC ::   ln_adv_UMx       !: Ultimate-Macho advection scheme
172   !
[10535]173   !                                     !!** ice-surface boundary conditions namelist (namsbc) **
[9019]174                                          ! -- icethd_dh -- !
[13472]175   REAL(wp), PUBLIC ::   rn_snwblow       !: coef. for partitioning of snowfall between leads and sea ice
176                                          ! -- icethd_zdf and icealb -- !
177   INTEGER , PUBLIC ::   nn_snwfra        !: calculate the fraction of ice covered by snow
178   !                                      !   = 0  fraction = 1 (if snow) or 0 (if no snow)
179   !                                      !   = 1  fraction = 1-exp(-0.2*rhos*hsnw) [MetO formulation]
180   !                                      !   = 2  fraction = hsnw / (hsnw+0.02)    [CICE formulation]
[9019]181                                          ! -- icethd -- !
182   REAL(wp), PUBLIC ::   rn_cio           !: drag coefficient for oceanic stress
183   INTEGER , PUBLIC ::   nn_flxdist       !: Redistribute heat flux over ice categories
184   !                                      !   =-1  Do nothing (needs N(cat) fluxes)
[14072]185   !                                      !   = 0  Average N(cat) fluxes then apply the average over the N(cat) ice
[9019]186   !                                      !   = 1  Average N(cat) fluxes then redistribute over the N(cat) ice using T-ice and albedo sensitivity
187   !                                      !   = 2  Redistribute a single flux over categories
[13472]188                                          ! -- icethd_zdf -- !
[14072]189   LOGICAL , PUBLIC ::   ln_cndflx        !: use conduction flux as surface boundary condition (instead of qsr and qns)
190   LOGICAL , PUBLIC ::   ln_cndemulate    !: emulate conduction flux (if not provided)
[10534]191   !                                      ! Conduction flux as surface forcing or not
192   INTEGER, PUBLIC, PARAMETER ::   np_cnd_OFF = 0  !: no forcing from conduction flux (ice thermodynamics forced via qsr and qns)
193   INTEGER, PUBLIC, PARAMETER ::   np_cnd_ON  = 1  !: forcing from conduction flux (SM0L) (compute qcn and qsr_tr via sbcblk.F90 or sbccpl.F90)
194   INTEGER, PUBLIC, PARAMETER ::   np_cnd_EMU = 2  !: emulate conduction flux via icethd_zdf.F90 (BL99) (1st round compute qcn and qsr_tr, 2nd round use it)
[13472]195   INTEGER, PUBLIC ::   nn_qtrice         !: Solar flux transmitted thru the surface scattering layer:
[14072]196   !                                      !   = 0  Grenfell and Maykut 1977 (depends on cloudiness and is 0 when there is snow)
[13472]197   !                                      !   = 1  Lebrun 2019 (equals 0.3 anytime with different melting/dry snw conductivities)
[15388]198
199   !                                     !!** namelist (namthd) **
200   LOGICAL , PUBLIC ::   ln_icedH         ! activate ice thickness change from growing/melting (T) or not (F)
201   LOGICAL , PUBLIC ::   ln_icedA         ! activate lateral melting param. (T) or not (F)
202   LOGICAL , PUBLIC ::   ln_icedO         ! activate ice growth in open-water (T) or not (F)
203   LOGICAL , PUBLIC ::   ln_icedS         ! activate gravity drainage and flushing (T) or not (F)
204   LOGICAL , PUBLIC ::   ln_leadhfx       ! heat in the leads is used to melt sea-ice before warming the ocean
[13472]205   !
[15388]206   !                                     !!** namelist (namthd_do) **
207   REAL(wp), PUBLIC ::   rn_hinew         ! thickness for new ice formation (m)
208   LOGICAL , PUBLIC ::   ln_frazil        ! use of frazil ice collection as function of wind (T) or not (F)
209   REAL(wp), PUBLIC ::   rn_maxfraz       ! maximum portion of frazil ice collecting at the ice bottom
210   REAL(wp), PUBLIC ::   rn_vfraz         ! threshold drift speed for collection of bottom frazil ice
211   REAL(wp), PUBLIC ::   rn_Cfraz         ! squeezing coefficient for collection of bottom frazil ice
212   !
[9019]213   !                                     !!** ice-vertical diffusion namelist (namthd_zdf) **
214   LOGICAL , PUBLIC ::   ln_cndi_U64      !: thermal conductivity: Untersteiner (1964)
215   LOGICAL , PUBLIC ::   ln_cndi_P07      !: thermal conductivity: Pringle et al (2007)
[14072]216   REAL(wp), PUBLIC ::   rn_cnd_s         !: thermal conductivity of the snow [W/m/K]
[13472]217   REAL(wp), PUBLIC ::   rn_kappa_i       !: coef. for the extinction of radiation in sea ice, Grenfell et al. (2006) [1/m]
218   REAL(wp), PUBLIC ::   rn_kappa_s       !: coef. for the extinction of radiation in snw (nn_qtrice=0) [1/m]
219   REAL(wp), PUBLIC ::   rn_kappa_smlt    !: coef. for the extinction of radiation in melt snw (nn_qtrice=1) [1/m]
220   REAL(wp), PUBLIC ::   rn_kappa_sdry    !: coef. for the extinction of radiation in dry  snw (nn_qtrice=1) [1/m]
221   LOGICAL , PUBLIC ::   ln_zdf_chkcvg    !: check convergence of heat diffusion scheme
[7646]222
[9019]223   !                                     !!** ice-salinity namelist (namthd_sal) **
[7646]224   INTEGER , PUBLIC ::   nn_icesal        !: salinity configuration used in the model
225   !                                      ! 1 - constant salinity in both space and time
226   !                                      ! 2 - prognostic salinity (s(z,t))
227   !                                      ! 3 - salinity profile, constant in time
228   REAL(wp), PUBLIC ::   rn_icesal        !: bulk salinity (ppt) in case of constant salinity
229   REAL(wp), PUBLIC ::   rn_simax         !: maximum ice salinity [PSU]
230   REAL(wp), PUBLIC ::   rn_simin         !: minimum ice salinity [PSU]
[825]231
[9019]232   !                                     !!** ice-ponds namelist (namthd_pnd)
[11536]233   LOGICAL , PUBLIC ::   ln_pnd           !: Melt ponds (T) or not (F)
[14005]234   LOGICAL , PUBLIC ::   ln_pnd_TOPO      !: Topographic Melt ponds scheme (Flocco et al 2007, 2010)
235   LOGICAL , PUBLIC ::   ln_pnd_LEV       !: Simple melt pond scheme
236   REAL(wp), PUBLIC ::   rn_apnd_min      !: Minimum fraction of melt water contributing to ponds
237   REAL(wp), PUBLIC ::   rn_apnd_max      !: Maximum fraction of melt water contributing to ponds
238   REAL(wp), PUBLIC ::   rn_pnd_flush     !: Pond flushing efficiency (tuning parameter)
[9019]239   LOGICAL , PUBLIC ::   ln_pnd_CST       !: Melt ponds scheme with constant fraction and depth
240   REAL(wp), PUBLIC ::   rn_apnd          !: prescribed pond fraction (0<rn_apnd<1)
241   REAL(wp), PUBLIC ::   rn_hpnd          !: prescribed pond depth    (0<rn_hpnd<1)
[13472]242   LOGICAL,  PUBLIC ::   ln_pnd_lids      !: Allow ponds to have frozen lids
[9019]243   LOGICAL , PUBLIC ::   ln_pnd_alb       !: melt ponds affect albedo
[825]244
[9019]245   !                                     !!** ice-diagnostics namelist (namdia) **
246   LOGICAL , PUBLIC ::   ln_icediachk     !: flag for ice diag (T) or not (F)
[11536]247   REAL(wp), PUBLIC ::   rn_icechk_cel    !: rate of ice spuriously gained/lost (at any gridcell)
248   REAL(wp), PUBLIC ::   rn_icechk_glo    !: rate of ice spuriously gained/lost (globally)
[9019]249   LOGICAL , PUBLIC ::   ln_icediahsb     !: flag for ice diag (T) or not (F)
250   LOGICAL , PUBLIC ::   ln_icectl        !: flag for sea-ice points output (T) or not (F)
251   INTEGER , PUBLIC ::   iiceprt          !: debug i-point
252   INTEGER , PUBLIC ::   jiceprt          !: debug j-point
253
[14072]254   !                                     !!** some other parameters
[9019]255   INTEGER , PUBLIC ::   kt_ice           !: iteration number
[12489]256   REAL(wp), PUBLIC ::   rDt_ice          !: ice time step
257   REAL(wp), PUBLIC ::   r1_Dt_ice        !: = 1. / rDt_ice
[5123]258   REAL(wp), PUBLIC ::   r1_nlay_i        !: 1 / nlay_i
[14072]259   REAL(wp), PUBLIC ::   r1_nlay_s        !: 1 / nlay_s
[7646]260   REAL(wp), PUBLIC ::   rswitch          !: switch for the presence of ice (1) or not (0)
[9019]261   REAL(wp), PUBLIC ::   rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft   !: conservation diagnostics
[14072]262   REAL(wp), PUBLIC, PARAMETER ::   epsi06 = 1.e-06_wp  !: small number
263   REAL(wp), PUBLIC, PARAMETER ::   epsi10 = 1.e-10_wp  !: small number
264   REAL(wp), PUBLIC, PARAMETER ::   epsi20 = 1.e-20_wp  !: small number
[4990]265
[7646]266   !                                     !!** define arrays
[13472]267   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   u_oce,v_oce     !: surface ocean velocity used in ice dynamics
268   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ht_i_new        !: ice collection thickness accreted in leads
[15334]269   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fraz_frac       !: fraction of frazil ice accreted at the ice bottom
[13472]270   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   strength        !: ice strength
271   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   stress1_i, stress2_i, stress12_i   !: 1st, 2nd & diagonal stress tensor element
272   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   delta_i         !: ice rheology elta factor (Flato & Hibler 95) [s-1]
273   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   divu_i          !: Divergence of the velocity field             [s-1]
274   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   shear_i         !: Shear of the velocity field                  [s-1]
[14103]275   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   aniso_11, aniso_12   !: structure tensor elements
276   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rdg_conv
[2715]277   !
[14072]278   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   t_bo            !: Sea-Ice bottom temperature [Kelvin]
[13472]279   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qlead           !: heat balance of the lead (or of the open ocean)
280   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qsb_ice_bot     !: net downward heat flux from the ice to the ocean
281   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   fhld            !: heat flux from the lead used for bottom melting
[4688]282
[13472]283   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_snw         !: mass flux from snow-ocean mass exchange             [kg.m-2.s-1]
284   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_snw_sni     !: mass flux from snow ice growth component of wfx_snw [kg.m-2.s-1]
285   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_snw_sum     !: mass flux from surface melt component of wfx_snw    [kg.m-2.s-1]
286   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_pnd         !: mass flux from melt pond-ocean mass exchange        [kg.m-2.s-1]
287   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_spr         !: mass flux from snow precipitation on ice            [kg.m-2.s-1]
288   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_sub         !: mass flux from sublimation of snow/ice              [kg.m-2.s-1]
289   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_snw_sub     !: mass flux from snow sublimation                     [kg.m-2.s-1]
290   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_ice_sub     !: mass flux from ice sublimation                      [kg.m-2.s-1]
[4688]291
[13472]292   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_snw_dyn     !: mass flux from dynamical component of wfx_snw       [kg.m-2.s-1]
[9019]293
[13472]294   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_ice         !: mass flux from ice-ocean mass exchange                   [kg.m-2.s-1]
295   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_sni         !: mass flux from snow ice growth component of wfx_ice      [kg.m-2.s-1]
296   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_opw         !: mass flux from lateral ice growth component of wfx_ice   [kg.m-2.s-1]
297   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_bog         !: mass flux from bottom ice growth component of wfx_ice    [kg.m-2.s-1]
298   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_dyn         !: mass flux from dynamical ice growth component of wfx_ice [kg.m-2.s-1]
299   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_bom         !: mass flux from bottom melt component of wfx_ice          [kg.m-2.s-1]
300   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_sum         !: mass flux from surface melt component of wfx_ice         [kg.m-2.s-1]
301   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_lam         !: mass flux from lateral melt component of wfx_ice         [kg.m-2.s-1]
302   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_res         !: mass flux from residual component of wfx_ice             [kg.m-2.s-1]
303   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   wfx_err_sub     !: mass flux error after sublimation                        [kg.m-2.s-1]
[4688]304
[13472]305   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sfx_bog         !: salt flux due to ice bottom growth                   [pss.kg.m-2.s-1 => g.m-2.s-1]
306   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sfx_bom         !: salt flux due to ice bottom melt                     [pss.kg.m-2.s-1 => g.m-2.s-1]
307   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sfx_lam         !: salt flux due to ice lateral melt                    [pss.kg.m-2.s-1 => g.m-2.s-1]
308   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sfx_sum         !: salt flux due to ice surface melt                    [pss.kg.m-2.s-1 => g.m-2.s-1]
309   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sfx_sni         !: salt flux due to snow-ice growth                     [pss.kg.m-2.s-1 => g.m-2.s-1]
310   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sfx_opw         !: salt flux due to growth in open water                [pss.kg.m-2.s-1 => g.m-2.s-1]
311   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sfx_bri         !: salt flux due to brine rejection                     [pss.kg.m-2.s-1 => g.m-2.s-1]
312   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sfx_dyn         !: salt flux due to porous ridged ice formation         [pss.kg.m-2.s-1 => g.m-2.s-1]
313   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sfx_res         !: salt flux due to correction on ice thick. (residual) [pss.kg.m-2.s-1 => g.m-2.s-1]
314   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   sfx_sub         !: salt flux due to ice sublimation                     [pss.kg.m-2.s-1 => g.m-2.s-1]
[825]315
[13472]316   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hfx_bog         !: total heat flux causing bottom ice growth           [W.m-2]
317   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hfx_bom         !: total heat flux causing bottom ice melt             [W.m-2]
318   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hfx_sum         !: total heat flux causing surface ice melt            [W.m-2]
319   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hfx_opw         !: total heat flux causing open water ice formation    [W.m-2]
320   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hfx_dif         !: total heat flux causing Temp change in the ice      [W.m-2]
321   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hfx_snw         !: heat flux for snow melt                             [W.m-2]
322   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hfx_err_dif     !: heat flux remaining due to change in non-solar flux [W.m-2]
323   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qt_atm_oi       !: heat flux at the interface atm-[oce+ice]            [W.m-2]
324   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   qt_oce_ai       !: heat flux at the interface oce-[atm+ice]            [W.m-2]
[14072]325
[4688]326   ! heat flux associated with ice-atmosphere mass exchange
[13472]327   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hfx_sub         !: heat flux for sublimation            [W.m-2]
328   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hfx_spr         !: heat flux of the snow precipitation  [W.m-2]
[4688]329
330   ! heat flux associated with ice-ocean mass exchange
[13472]331   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hfx_thd         !: ice-ocean heat flux from thermo processes (icethd_dh) [W.m-2]
332   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hfx_dyn         !: ice-ocean heat flux from ridging                      [W.m-2]
333   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hfx_res         !: heat flux due to correction on ice thick. (residual)  [W.m-2]
[4688]334
[13472]335   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rn_amax_2d      !: maximum ice concentration 2d array
336   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qtr_ice_bot     !: transmitted solar radiation under ice
337   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t1_ice          !: temperature of the first layer          (ln_cndflx=T) [K]
338   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   cnd_ice         !: effective conductivity of the 1st layer (ln_cndflx=T) [W.m-2.K-1]
[4688]339
[9019]340   !!----------------------------------------------------------------------
[834]341   !! * Ice global state variables
[9019]342   !!----------------------------------------------------------------------
[834]343   !! Variables defined for each ice category
[13472]344   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   h_i           !: Ice thickness                           (m)
345   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_i           !: Ice fractional areas (concentration)
346   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_i           !: Ice volume per unit area                (m)
347   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_s           !: Snow volume per unit area               (m)
348   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   h_s           !: Snow thickness                          (m)
349   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   t_su          !: Sea-Ice Surface Temperature             (K)
350   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   s_i           !: Sea-Ice Bulk salinity                   (pss)
351   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   sv_i          !: Sea-Ice Bulk salinity * volume per area (pss.m)
352   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   o_i           !: Sea-Ice Age                             (s)
353   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   oa_i          !: Sea-Ice Age times ice area              (s)
354   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   bv_i          !: brine volume
[825]355
[2715]356   !! Variables summed over all categories, or associated to all the ice in a single grid cell
[13472]357   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   u_ice, v_ice  !: components of the ice velocity                          (m/s)
358   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   vt_i , vt_s   !: ice and snow total volume per unit area                 (m)
359   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   st_i          !: Total ice salinity content                              (pss.m)
360   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   at_i          !: ice total fractional area (ice concentration)
361   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   ato_i         !: =1-at_i ; total open water fractional area
362   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   et_i , et_s   !: ice and snow total heat content                         (J/m2)
363   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   tm_i          !: mean ice temperature over all categories                (K)
364   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   tm_s          !: mean snw temperature over all categories                (K)
365   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   bvm_i         !: brine volume averaged over all categories
366   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   sm_i          !: mean sea ice salinity averaged over all categories      (pss)
367   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   tm_su         !: mean surface temperature over all categories            (K)
368   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   hm_i          !: mean ice  thickness over all categories                 (m)
369   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   hm_s          !: mean snow thickness over all categories                 (m)
370   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   om_i          !: mean ice age over all categories                        (s)
371   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   tau_icebfr    !: ice friction on ocean bottom (landfast param activated)
[14005]372   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   icb_mask      !: mask of grounded icebergs if landfast [0-1]
[825]373
[13472]374   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_s           !: Snow temperatures     [K]
375   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s           !: Snow enthalpy         [J/m2]
376   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_i           !: ice temperatures      [K]
377   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i           !: ice enthalpy          [J/m2]
378   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   sz_i          !: ice salinity          [PSS]
[825]379
[13472]380   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_ip          !: melt pond concentration
381   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_ip          !: melt pond volume per grid cell area      [m]
382   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_ip_frac     !: melt pond fraction (a_ip/a_i)
383   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_ip_eff      !: melt pond effective fraction (not covered up by lid) (a_ip/a_i)
384   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   h_ip          !: melt pond depth                          [m]
385   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_il          !: melt pond lid volume                     [m]
386   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   h_il          !: melt pond lid thickness                  [m]
[825]387
[13472]388   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   at_ip         !: total melt pond concentration
389   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   hm_ip         !: mean melt pond depth                     [m]
390   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   vt_ip         !: total melt pond volume per gridcell area [m]
391   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   hm_il         !: mean melt pond lid depth                     [m]
392   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   vt_il         !: total melt pond lid volume per gridcell area [m]
[9019]393
[14005]394   ! meltwater arrays to save for melt ponds (mv - could be grouped in a single meltwater volume array)
395   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   dh_i_sum_2d   !: surface melt (2d arrays for ponds)       [m]
396   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   dh_s_mlt_2d   !: snow surf melt (2d arrays for ponds)     [m]
397
[9019]398   !!----------------------------------------------------------------------
[13472]399   !! * Global variables at before time step
[9019]400   !!----------------------------------------------------------------------
[13472]401   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_s_b, v_i_b, h_s_b, h_i_b !: snow and ice volumes/thickness
[14005]402   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_ip_b, v_il_b             !: ponds and lids volumes
[13472]403   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_i_b, sv_i_b              !:
404   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s_b                      !: snow heat content
405   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i_b                      !: ice temperatures
406   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   u_ice_b, v_ice_b           !: ice velocity
407   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   at_i_b                     !: ice concentration (total)
[14072]408
[9019]409   !!----------------------------------------------------------------------
[834]410   !! * Ice thickness distribution variables
[9019]411   !!----------------------------------------------------------------------
[13472]412   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   hi_max            !: Boundary of ice thickness categories in thickness space
[14072]413   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:)   ::   hi_mean           !: Mean ice thickness in catgories
[4147]414   !
[9019]415   !!----------------------------------------------------------------------
[834]416   !! * Ice diagnostics
[9019]417   !!----------------------------------------------------------------------
[13472]418   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_vi       !: transport of ice volume
419   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_vs       !: transport of snw volume
420   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_ei       !: transport of ice enthalpy [W/m2]
421   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_es       !: transport of snw enthalpy [W/m2]
422   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_sv       !: transport of salt content
[4688]423   !
[14072]424   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_heat         !: snw/ice heat content variation   [W/m2]
425   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_sice         !: ice salt content variation   []
426   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_vice         !: ice volume variation   [m/s]
427   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_vsnw         !: snw volume variation   [m/s]
428   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_aice         !: ice conc.  variation   [s-1]
429   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_vpnd         !: pond volume variation  [m/s]
[13472]430   !
[13601]431   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_adv_mass     !: advection of mass (kg/m2/s)
432   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_adv_salt     !: advection of salt (g/m2/s)
433   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_adv_heat     !: advection of heat (W/m2)
434   !
[11536]435   !!----------------------------------------------------------------------
436   !! * Ice conservation
437   !!----------------------------------------------------------------------
[13472]438   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_v            !: conservation of ice volume
439   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_s            !: conservation of ice salt
440   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_t            !: conservation of ice heat
441   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_fv           !: conservation of ice volume
442   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_fs           !: conservation of ice salt
443   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_ft           !: conservation of ice heat
[4688]444   !
[2715]445   !!----------------------------------------------------------------------
[9019]446   !! * SIMIP extra diagnostics
447   !!----------------------------------------------------------------------
448   ! Extra sea ice diagnostics to address the data request
[14072]449   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t_si            !: Temperature at Snow-ice interface (K)
450   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   tm_si           !: mean temperature at the snow-ice interface (K)
[13472]451   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qcn_ice_bot     !: Bottom  conduction flux (W/m2)
452   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qcn_ice_top     !: Surface conduction flux (W/m2)
[9019]453   !
454   !!----------------------------------------------------------------------
[9598]455   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
[2715]456   !! $Id$
[10068]457   !! Software governed by the CeCILL license (see ./LICENSE)
[2715]458   !!----------------------------------------------------------------------
459CONTAINS
460
461   FUNCTION ice_alloc()
462      !!-----------------------------------------------------------------
[7813]463      !!               *** Routine ice_alloc ***
[2715]464      !!-----------------------------------------------------------------
465      INTEGER :: ice_alloc
466      !
[11536]467      INTEGER :: ierr(16), ii
[2715]468      !!-----------------------------------------------------------------
469      ierr(:) = 0
470
471      ii = 1
[15334]472      ALLOCATE( u_oce    (jpi,jpj) , v_oce    (jpi,jpj) , ht_i_new (jpi,jpj) , fraz_frac (jpi,jpj) ,  &
473         &      strength (jpi,jpj) , stress1_i(jpi,jpj) , stress2_i(jpi,jpj) , stress12_i(jpi,jpj) ,  &
474         &      delta_i  (jpi,jpj) , divu_i   (jpi,jpj) , shear_i  (jpi,jpj) ,                        &
475         &      aniso_11 (jpi,jpj) , aniso_12 (jpi,jpj) , rdg_conv (jpi,jpj) , STAT=ierr(ii) )
[2715]476
477      ii = ii + 1
[9913]478      ALLOCATE( t_bo       (jpi,jpj) , wfx_snw_sni(jpi,jpj) ,                                                &
479         &      wfx_snw    (jpi,jpj) , wfx_snw_dyn(jpi,jpj) , wfx_snw_sum(jpi,jpj) , wfx_snw_sub(jpi,jpj) ,  &
480         &      wfx_ice    (jpi,jpj) , wfx_sub    (jpi,jpj) , wfx_ice_sub(jpi,jpj) , wfx_lam    (jpi,jpj) ,  &
481         &      wfx_pnd    (jpi,jpj) ,                                                                       &
482         &      wfx_bog    (jpi,jpj) , wfx_dyn   (jpi,jpj) , wfx_bom(jpi,jpj) , wfx_sum(jpi,jpj) ,           &
483         &      wfx_res    (jpi,jpj) , wfx_sni   (jpi,jpj) , wfx_opw(jpi,jpj) , wfx_spr(jpi,jpj) ,           &
[11536]484         &      rn_amax_2d (jpi,jpj) ,                                                                       &
[9913]485         &      qsb_ice_bot(jpi,jpj) , qlead     (jpi,jpj) ,                                                 &
486         &      sfx_res    (jpi,jpj) , sfx_bri   (jpi,jpj) , sfx_dyn(jpi,jpj) , sfx_sub(jpi,jpj) , sfx_lam(jpi,jpj) ,  &
487         &      sfx_bog    (jpi,jpj) , sfx_bom   (jpi,jpj) , sfx_sum(jpi,jpj) , sfx_sni(jpi,jpj) , sfx_opw(jpi,jpj) ,  &
[14072]488         &      hfx_res    (jpi,jpj) , hfx_snw   (jpi,jpj) , hfx_sub(jpi,jpj) ,                        &
[9913]489         &      qt_atm_oi  (jpi,jpj) , qt_oce_ai (jpi,jpj) , fhld   (jpi,jpj) ,                        &
490         &      hfx_sum    (jpi,jpj) , hfx_bom   (jpi,jpj) , hfx_bog(jpi,jpj) , hfx_dif(jpi,jpj) ,     &
491         &      hfx_opw    (jpi,jpj) , hfx_thd   (jpi,jpj) , hfx_dyn(jpi,jpj) , hfx_spr(jpi,jpj) ,     &
[13472]492         &      hfx_err_dif(jpi,jpj) , wfx_err_sub(jpi,jpj)                   , STAT=ierr(ii) )
[2715]493
494      ! * Ice global state variables
495      ii = ii + 1
[9910]496      ALLOCATE( qtr_ice_bot(jpi,jpj,jpl) , cnd_ice(jpi,jpj,jpl) , t1_ice(jpi,jpj,jpl) ,  &
497         &      h_i        (jpi,jpj,jpl) , a_i    (jpi,jpj,jpl) , v_i   (jpi,jpj,jpl) ,  &
498         &      v_s        (jpi,jpj,jpl) , h_s    (jpi,jpj,jpl) , t_su  (jpi,jpj,jpl) ,  &
499         &      s_i        (jpi,jpj,jpl) , sv_i   (jpi,jpj,jpl) , o_i   (jpi,jpj,jpl) ,  &
500         &      oa_i       (jpi,jpj,jpl) , bv_i   (jpi,jpj,jpl) , STAT=ierr(ii) )
[9604]501
[2715]502      ii = ii + 1
[9604]503      ALLOCATE( u_ice(jpi,jpj) , v_ice(jpi,jpj) ,                                   &
[11536]504         &      vt_i (jpi,jpj) , vt_s (jpi,jpj) , st_i(jpi,jpj) , at_i(jpi,jpj) , ato_i(jpi,jpj) ,  &
505         &      et_i (jpi,jpj) , et_s (jpi,jpj) , tm_i(jpi,jpj) , tm_s(jpi,jpj) ,  &
506         &      sm_i (jpi,jpj) , tm_su(jpi,jpj) , hm_i(jpi,jpj) , hm_s(jpi,jpj) ,  &
[14005]507         &      om_i (jpi,jpj) , bvm_i(jpi,jpj) , tau_icebfr(jpi,jpj), icb_mask(jpi,jpj), STAT=ierr(ii) )
[9604]508
[2715]509      ii = ii + 1
[5123]510      ALLOCATE( t_s(jpi,jpj,nlay_s,jpl) , e_s(jpi,jpj,nlay_s,jpl) , STAT=ierr(ii) )
[9604]511
[2715]512      ii = ii + 1
[9019]513      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) )
[2715]514
515      ii = ii + 1
[13472]516      ALLOCATE( a_ip(jpi,jpj,jpl) , v_ip(jpi,jpj,jpl) , a_ip_frac(jpi,jpj,jpl) , h_ip(jpi,jpj,jpl),  &
[14005]517         &      v_il(jpi,jpj,jpl) , h_il(jpi,jpj,jpl) , a_ip_eff (jpi,jpj,jpl) ,                     &
518         &      dh_i_sum_2d(jpi,jpj,jpl) , dh_s_mlt_2d(jpi,jpj,jpl) , STAT = ierr(ii) )
[9604]519
[2715]520      ii = ii + 1
[13472]521      ALLOCATE( at_ip(jpi,jpj) , hm_ip(jpi,jpj) , vt_ip(jpi,jpj) , hm_il(jpi,jpj) , vt_il(jpi,jpj) , STAT = ierr(ii) )
[2715]522
523      ! * Old values of global variables
524      ii = ii + 1
[13472]525      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),         &
[14005]526         &      v_ip_b(jpi,jpj,jpl) , v_il_b(jpi,jpj,jpl) ,                                                         &
[13472]527         &      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) , &
528         &      STAT=ierr(ii) )
[9604]529
[7646]530      ii = ii + 1
531      ALLOCATE( u_ice_b(jpi,jpj) , v_ice_b(jpi,jpj) , at_i_b(jpi,jpj) , STAT=ierr(ii) )
[14072]532
[2715]533      ! * Ice thickness distribution variables
534      ii = ii + 1
[4869]535      ALLOCATE( hi_max(0:jpl), hi_mean(jpl),  STAT=ierr(ii) )
[2715]536
537      ! * Ice diagnostics
538      ii = ii + 1
[14072]539      ALLOCATE( diag_trp_vi(jpi,jpj) , diag_trp_vs (jpi,jpj) , diag_trp_ei(jpi,jpj),                      &
[13641]540         &      diag_trp_es(jpi,jpj) , diag_trp_sv (jpi,jpj) , diag_heat  (jpi,jpj),                      &
[14005]541         &      diag_sice  (jpi,jpj) , diag_vice   (jpi,jpj) , diag_vsnw  (jpi,jpj), diag_aice(jpi,jpj), diag_vpnd(jpi,jpj),  &
[13601]542         &      diag_adv_mass(jpi,jpj), diag_adv_salt(jpi,jpj), diag_adv_heat(jpi,jpj), STAT=ierr(ii) )
[2715]543
[11536]544      ! * Ice conservation
545      ii = ii + 1
[14072]546      ALLOCATE( diag_v (jpi,jpj) , diag_s (jpi,jpj) , diag_t (jpi,jpj),   &
[11536]547         &      diag_fv(jpi,jpj) , diag_fs(jpi,jpj) , diag_ft(jpi,jpj), STAT=ierr(ii) )
[14072]548
[9019]549      ! * SIMIP diagnostics
550      ii = ii + 1
[9916]551      ALLOCATE( t_si(jpi,jpj,jpl) , tm_si(jpi,jpj) , qcn_ice_bot(jpi,jpj,jpl) , qcn_ice_top(jpi,jpj,jpl) , STAT = ierr(ii) )
[9019]552
[2715]553      ice_alloc = MAXVAL( ierr(:) )
[10425]554      IF( ice_alloc /= 0 )   CALL ctl_stop( 'STOP', 'ice_alloc: failed to allocate arrays.' )
[2715]555      !
[13472]556
[2715]557   END FUNCTION ice_alloc
558
[825]559#else
560   !!----------------------------------------------------------------------
[9570]561   !!   Default option         Empty module           NO SI3 sea-ice model
[825]562   !!----------------------------------------------------------------------
563#endif
564
565   !!======================================================================
566END MODULE ice
Note: See TracBrowser for help on using the repository browser.