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/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE – NEMO

source: NEMO/branches/UKMO/NEMO_4.0_add_pond_lids_prints/src/ICE/ice.F90 @ 12475

Last change on this file since 12475 was 12475, checked in by dancopsey, 4 years ago
  • Add more print statements.
  • Move away from using snow to ice diagnostics and use a new snow to pond one instead.
File size: 38.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   !!                                                                     |
[10881]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   !!-------------|-------------|---------------------------------|-------|
[10881]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     |
[10881]64   !! sv_i        |      -      |    Sea ice salt content         | pss.m |
65   !! oa_i        |      -      |    Sea ice areal age content    | s     |
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  |
70   !! a_ip        |      -      |    Ice pond concentration       |       |
71   !! v_ip        |      -      |    Ice pond volume per unit area| m     |
[12379]72   !! lh_ip       !    lh_ip_1d !    Ice pond lid thickness       ! 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     |
[10881]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     |
[10881]87   !! h_ip        | h_ip_1d     |    Ice pond thickness           | m     |
[834]88   !!                                                                     |
89   !! notes: the ice model only sees a bulk (i.e., vertically averaged)   |
90   !!        salinity, except in thermodynamic computations, for which    |
91   !!        the salinity profile is computed as a function of bulk       |
92   !!        salinity                                                     |
93   !!                                                                     |
94   !!        the sea ice surface temperature is not associated to any     |
95   !!        heat content. Therefore, it is not a state variable and      |
96   !!        does not have to be advected. Nevertheless, it has to be     |
97   !!        computed to determine whether the ice is melting or not      |
98   !!                                                                     |
99   !! ******************************************************************* |
100   !! ***         Category-summed state variables (diagnostic)        *** |
101   !! ******************************************************************* |
[4872]102   !! at_i        | at_i_1d     |    Total ice concentration      |       |
[834]103   !! vt_i        |      -      |    Total ice vol. per unit area | m     |
104   !! vt_s        |      -      |    Total snow vol. per unit ar. | m     |
[10881]105   !! sm_i        |      -      |    Mean sea ice salinity        | pss   |
[834]106   !! tm_i        |      -      |    Mean sea ice temperature     | K     |
[9433]107   !! tm_s        |      -      |    Mean snow    temperature     | K     |
[10881]108   !! et_i        |      -      |    Total ice enthalpy           | J/m2  |
109   !! et_s        |      -      |    Total snow enthalpy          | J/m2  |
110   !! bv_i        |      -      |    relative brine volume        | ???   |
111   !! at_ip       |      -      |    Total ice pond concentration |       |
112   !! vt_ip       |      -      |    Total ice pond vol. per unit area| m |
[834]113   !!=====================================================================
[825]114
[9019]115   !!----------------------------------------------------------------------
[825]116   !! * Share Module variables
[9019]117   !!----------------------------------------------------------------------
118   !                                     !!** ice-generic parameters namelist (nampar) **
119   INTEGER           , PUBLIC ::   jpl              !: number of ice  categories
120   INTEGER           , PUBLIC ::   nlay_i           !: number of ice  layers
121   INTEGER           , PUBLIC ::   nlay_s           !: number of snow layers
[10531]122   LOGICAL           , PUBLIC ::   ln_virtual_itd   !: virtual ITD mono-category parameterization (T) or not (F)
[9019]123   LOGICAL           , PUBLIC ::   ln_icedyn        !: flag for ice dynamics (T) or not (F)
124   LOGICAL           , PUBLIC ::   ln_icethd        !: flag for ice thermo   (T) or not (F)
125   REAL(wp)          , PUBLIC ::   rn_amax_n        !: maximum ice concentration Northern hemisphere
126   REAL(wp)          , PUBLIC ::   rn_amax_s        !: maximum ice concentration Southern hemisphere
127   CHARACTER(len=256), PUBLIC ::   cn_icerst_in     !: suffix of ice restart name (input)
128   CHARACTER(len=256), PUBLIC ::   cn_icerst_out    !: suffix of ice restart name (output)
129   CHARACTER(len=256), PUBLIC ::   cn_icerst_indir  !: ice restart input directory
130   CHARACTER(len=256), PUBLIC ::   cn_icerst_outdir !: ice restart output directory
[1465]131
[9019]132   !                                     !!** ice-itd namelist (namitd) **
133   REAL(wp), PUBLIC ::   rn_himin         !: minimum ice thickness
[7646]134   
[9019]135   !                                     !!** ice-dynamics namelist (namdyn) **
136   REAL(wp), PUBLIC ::   rn_ishlat        !: lateral boundary condition for sea-ice
[10413]137   LOGICAL , PUBLIC ::   ln_landfast_L16  !: landfast ice parameterizationfrom lemieux2016
138   LOGICAL , PUBLIC ::   ln_landfast_home !: landfast ice parameterizationfrom home made
139   REAL(wp), PUBLIC ::   rn_depfra        !:    fraction of ocean depth that ice must reach to initiate landfast ice
140   REAL(wp), PUBLIC ::   rn_icebfr        !:    maximum bottom stress per unit area of contact (lemieux2016) or per unit volume (home)
141   REAL(wp), PUBLIC ::   rn_lfrelax       !:    relaxation time scale (s-1) to reach static friction
142   REAL(wp), PUBLIC ::   rn_tensile       !:    isotropic tensile strength
[9019]143   !
[10413]144   !                                     !!** ice-ridging/rafting namelist (namdyn_rdgrft) **
145   REAL(wp), PUBLIC ::   rn_crhg          !: determines changes in ice strength (also used for landfast param)
146   !
147   !                                     !!** ice-rheology namelist (namdyn_rhg) **
[9019]148   LOGICAL , PUBLIC ::   ln_aEVP          !: using adaptive EVP (T or F)
[5123]149   REAL(wp), PUBLIC ::   rn_creepl        !: creep limit : has to be under 1.0e-9
150   REAL(wp), PUBLIC ::   rn_ecc           !: eccentricity of the elliptical yield curve
[7646]151   INTEGER , PUBLIC ::   nn_nevp          !: number of iterations for subcycling
[5123]152   REAL(wp), PUBLIC ::   rn_relast        !: ratio => telast/rdt_ice (1/3 or 1/9 depending on nb of subcycling nevp)
[9019]153   !
[10413]154   !                                     !!** ice-advection namelist (namdyn_adv) **
155   LOGICAL , PUBLIC ::   ln_adv_Pra       !: Prather        advection scheme
156   LOGICAL , PUBLIC ::   ln_adv_UMx       !: Ultimate-Macho advection scheme
157   !
[10535]158   !                                     !!** ice-surface boundary conditions namelist (namsbc) **
[9019]159                                          ! -- icethd_dh -- !
160   REAL(wp), PUBLIC ::   rn_blow_s        !: coef. for partitioning of snowfall between leads and sea ice
161                                          ! -- icethd -- !
162   REAL(wp), PUBLIC ::   rn_cio           !: drag coefficient for oceanic stress
163   INTEGER , PUBLIC ::   nn_flxdist       !: Redistribute heat flux over ice categories
164   !                                      !   =-1  Do nothing (needs N(cat) fluxes)
165   !                                      !   = 0  Average N(cat) fluxes then apply the average over the N(cat) ice
166   !                                      !   = 1  Average N(cat) fluxes then redistribute over the N(cat) ice using T-ice and albedo sensitivity
167   !                                      !   = 2  Redistribute a single flux over categories
[10534]168   LOGICAL , PUBLIC ::   ln_cndflx        !: use conduction flux as surface boundary condition (instead of qsr and qns)
169   LOGICAL , PUBLIC ::   ln_cndemulate    !: emulate conduction flux (if not provided)
170   !                                      ! Conduction flux as surface forcing or not
171   INTEGER, PUBLIC, PARAMETER ::   np_cnd_OFF = 0  !: no forcing from conduction flux (ice thermodynamics forced via qsr and qns)
172   INTEGER, PUBLIC, PARAMETER ::   np_cnd_ON  = 1  !: forcing from conduction flux (SM0L) (compute qcn and qsr_tr via sbcblk.F90 or sbccpl.F90)
173   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)
[12369]174   INTEGER , PUBLIC :: cat
[5123]175
[9019]176   !                                     !!** ice-vertical diffusion namelist (namthd_zdf) **
177   LOGICAL , PUBLIC ::   ln_cndi_U64      !: thermal conductivity: Untersteiner (1964)
178   LOGICAL , PUBLIC ::   ln_cndi_P07      !: thermal conductivity: Pringle et al (2007)
[7646]179   REAL(wp), PUBLIC ::   rn_kappa_i       !: coef. for the extinction of radiation Grenfell et al. (2006) [1/m]
[9019]180   REAL(wp), PUBLIC ::   rn_cnd_s         !: thermal conductivity of the snow [W/m/K]   
[7646]181
[9019]182   !                                     !!** ice-salinity namelist (namthd_sal) **
[7646]183   INTEGER , PUBLIC ::   nn_icesal        !: salinity configuration used in the model
184   !                                      ! 1 - constant salinity in both space and time
185   !                                      ! 2 - prognostic salinity (s(z,t))
186   !                                      ! 3 - salinity profile, constant in time
187   REAL(wp), PUBLIC ::   rn_icesal        !: bulk salinity (ppt) in case of constant salinity
188   REAL(wp), PUBLIC ::   rn_simax         !: maximum ice salinity [PSU]
189   REAL(wp), PUBLIC ::   rn_simin         !: minimum ice salinity [PSU]
[825]190
[9019]191   !                                     !!** ice-ponds namelist (namthd_pnd)
192   LOGICAL , PUBLIC ::   ln_pnd_H12       !: Melt ponds scheme from Holland et al 2012
193   LOGICAL , PUBLIC ::   ln_pnd_CST       !: Melt ponds scheme with constant fraction and depth
194   REAL(wp), PUBLIC ::   rn_apnd          !: prescribed pond fraction (0<rn_apnd<1)
195   REAL(wp), PUBLIC ::   rn_hpnd          !: prescribed pond depth    (0<rn_hpnd<1)
196   LOGICAL , PUBLIC ::   ln_pnd_alb       !: melt ponds affect albedo
[825]197
[9019]198   !                                     !!** ice-diagnostics namelist (namdia) **
199   LOGICAL , PUBLIC ::   ln_icediachk     !: flag for ice diag (T) or not (F)
200   LOGICAL , PUBLIC ::   ln_icediahsb     !: flag for ice diag (T) or not (F)
201   LOGICAL , PUBLIC ::   ln_icectl        !: flag for sea-ice points output (T) or not (F)
202   INTEGER , PUBLIC ::   iiceprt          !: debug i-point
203   INTEGER , PUBLIC ::   jiceprt          !: debug j-point
204
[7646]205   !                                     !!** some other parameters
[9019]206   INTEGER , PUBLIC ::   kt_ice           !: iteration number
[7646]207   REAL(wp), PUBLIC ::   rdt_ice          !: ice time step
208   REAL(wp), PUBLIC ::   r1_rdtice        !: = 1. / rdt_ice
[5123]209   REAL(wp), PUBLIC ::   r1_nlay_i        !: 1 / nlay_i
210   REAL(wp), PUBLIC ::   r1_nlay_s        !: 1 / nlay_s
[7646]211   REAL(wp), PUBLIC ::   rswitch          !: switch for the presence of ice (1) or not (0)
[9019]212   REAL(wp), PUBLIC ::   rdiag_v, rdiag_s, rdiag_t, rdiag_fv, rdiag_fs, rdiag_ft   !: conservation diagnostics
213   REAL(wp), PUBLIC, PARAMETER ::   epsi06 = 1.e-06_wp  !: small number
214   REAL(wp), PUBLIC, PARAMETER ::   epsi10 = 1.e-10_wp  !: small number
215   REAL(wp), PUBLIC, PARAMETER ::   epsi20 = 1.e-20_wp  !: small number
[4990]216
[10425]217   !                                     !!** some other parameters for advection using the ULTIMATE-MACHO scheme
218   LOGICAL, PUBLIC, DIMENSION(2) :: l_split_advumx = .FALSE.    ! force one iteration at the first time-step
[9019]219
[7646]220   !                                     !!** define arrays
[9019]221   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_oce,v_oce !: surface ocean velocity used in ice dynamics
222   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ht_i_new    !: ice collection thickness accreted in leads
[7646]223   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   strength    !: ice strength
[2715]224   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   stress1_i, stress2_i, stress12_i   !: 1st, 2nd & diagonal stress tensor element
[7646]225   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   delta_i     !: ice rheology elta factor (Flato & Hibler 95) [s-1]
[9604]226   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   divu_i      !: Divergence of the velocity field             [s-1]
227   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   shear_i     !: Shear of the velocity field                  [s-1]
[2715]228   !
229   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   t_bo        !: Sea-Ice bottom temperature [Kelvin]     
[4688]230   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qlead       !: heat balance of the lead (or of the open ocean)
[9913]231   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qsb_ice_bot !: net downward heat flux from the ice to the ocean
[4688]232   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   fhld        !: heat flux from the lead used for bottom melting
233
[10881]234   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw     !: mass flux from snow-ocean mass exchange             [kg.m-2.s-1]
235   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sni !: mass flux from snow ice growth component of wfx_snw [kg.m-2.s-1]
236   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sum !: mass flux from surface melt component of wfx_snw    [kg.m-2.s-1]
237   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_pnd     !: mass flux from melt pond-ocean mass exchange        [kg.m-2.s-1]
238   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_spr     !: mass flux from snow precipitation on ice            [kg.m-2.s-1]
239   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sub     !: mass flux from sublimation of snow/ice              [kg.m-2.s-1]
240   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_sub !: mass flux from snow sublimation                     [kg.m-2.s-1]
241   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_ice_sub !: mass flux from ice sublimation                      [kg.m-2.s-1]
[4688]242
[10881]243   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snw_dyn !: mass flux from dynamical component of wfx_snw       [kg.m-2.s-1]
[9019]244
[10881]245   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_ice     !: mass flux from ice-ocean mass exchange                   [kg.m-2.s-1]
246   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sni     !: mass flux from snow ice growth component of wfx_ice      [kg.m-2.s-1]
[12475]247   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_snp     !: mass flux from snow melting into melt ponds              [kg.m-2.s-1]
[10881]248   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_opw     !: mass flux from lateral ice growth component of wfx_ice   [kg.m-2.s-1]
249   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_bog     !: mass flux from bottom ice growth component of wfx_ice    [kg.m-2.s-1]
250   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_dyn     !: mass flux from dynamical ice growth component of wfx_ice [kg.m-2.s-1]
251   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_bom     !: mass flux from bottom melt component of wfx_ice          [kg.m-2.s-1]
252   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_sum     !: mass flux from surface melt component of wfx_ice         [kg.m-2.s-1]
253   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_lam     !: mass flux from lateral melt component of wfx_ice         [kg.m-2.s-1]
254   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_res     !: mass flux from residual component of wfx_ice             [kg.m-2.s-1]
255   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   wfx_err_sub !: mass flux error after sublimation                        [kg.m-2.s-1]
[4688]256
[9604]257   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   afx_tot     !: ice concentration tendency (total)        [s-1]
[5123]258
[10881]259   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]
260   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]
261   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]
262   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]
263   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]
264   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]
265   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]
266   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]
267   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]
268   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]
[12449]269   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sfx_pnd     !: salt flux due to melt ponds leaking into the ocean   [pss.kg.m-2.s-1 => g.m-2.s-1]
[825]270
[9604]271   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_bog     !: total heat flux causing bottom ice growth           [W.m-2]
272   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_bom     !: total heat flux causing bottom ice melt             [W.m-2]
273   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_sum     !: total heat flux causing surface ice melt            [W.m-2]
274   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_opw     !: total heat flux causing open water ice formation    [W.m-2]
275   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_dif     !: total heat flux causing Temp change in the ice      [W.m-2]
276   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_snw     !: heat flux for snow melt                             [W.m-2]
[6416]277   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err_dif !: heat flux remaining due to change in non-solar flux [W.m-2]
[10881]278   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_err_rem !: heat flux error after heat remapping => must be 0   [W.m-2]
279   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qt_atm_oi   !: heat flux at the interface atm-[oce+ice]            [W.m-2]
280   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   qt_oce_ai   !: heat flux at the interface oce-[atm+ice]            [W.m-2]
[6416]281   
[4688]282   ! heat flux associated with ice-atmosphere mass exchange
[9604]283   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_sub     !: heat flux for sublimation            [W.m-2]
[6416]284   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_spr     !: heat flux of the snow precipitation  [W.m-2]
[4688]285
286   ! heat flux associated with ice-ocean mass exchange
[9019]287   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_thd     !: ice-ocean heat flux from thermo processes (icethd_dh) [W.m-2]
288   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_dyn     !: ice-ocean heat flux from ridging                      [W.m-2]
[10881]289   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hfx_res     !: heat flux due to correction on ice thick. (residual)  [W.m-2]
[4688]290
[7646]291   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   rn_amax_2d     !: maximum ice concentration 2d array
[9910]292   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qtr_ice_bot    !: transmitted solar radiation under ice
[10534]293   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t1_ice         !: temperature of the first layer                (ln_cndflx=T) [K]
294   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   cnd_ice        !: effective conductivity at the top of ice/snow (ln_cndflx=T) [W.m-2.K-1]
[4688]295
[9019]296   !!----------------------------------------------------------------------
[834]297   !! * Ice global state variables
[9019]298   !!----------------------------------------------------------------------
[834]299   !! Variables defined for each ice category
[10881]300   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   h_i       !: Ice thickness                           (m)
[7646]301   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i       !: Ice fractional areas (concentration)
[12369]302   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_i_last_couple    !: Ice fractional area at last coupling time
[10881]303   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_i       !: Ice volume per unit area                (m)
304   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_s       !: Snow volume per unit area               (m)
305   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   h_s       !: Snow thickness                          (m)
306   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t_su      !: Sea-Ice Surface Temperature             (K)
307   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   s_i       !: Sea-Ice Bulk salinity                   (pss)
308   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   sv_i      !: Sea-Ice Bulk salinity * volume per area (pss.m)
309   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   o_i       !: Sea-Ice Age                             (s)
310   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   oa_i      !: Sea-Ice Age times ice area              (s)
[7646]311   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   bv_i      !: brine volume
[825]312
[2715]313   !! Variables summed over all categories, or associated to all the ice in a single grid cell
[10881]314   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   u_ice, v_ice !: components of the ice velocity                          (m/s)
315   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   vt_i , vt_s  !: ice and snow total volume per unit area                 (m)
[7646]316   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   at_i         !: ice total fractional area (ice concentration)
317   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ato_i        !: =1-at_i ; total open water fractional area
[10881]318   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   et_i , et_s  !: ice and snow total heat content                         (J/m2)
319   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tm_i         !: mean ice temperature over all categories                (K)
320   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tm_s         !: mean snw temperature over all categories                (K)
[7646]321   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bvm_i        !: brine volume averaged over all categories
[10881]322   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   sm_i         !: mean sea ice salinity averaged over all categories      (pss)
323   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tm_su        !: mean surface temperature over all categories            (K)
324   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hm_i         !: mean ice  thickness over all categories                 (m)
325   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   hm_s         !: mean snow thickness over all categories                 (m)
326   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   om_i         !: mean ice age over all categories                        (s)
327   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tau_icebfr   !: ice friction on ocean bottom (landfast param activated)
[825]328
[9019]329   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_s      !: Snow temperatures     [K]
330   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s      !: Snow enthalpy         [J/m2]
331   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   t_i      !: ice temperatures      [K]
332   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i      !: ice enthalpy          [J/m2]
[10881]333   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   sz_i     !: ice salinity          [PSS]
[825]334
[9019]335   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_ip       !: melt pond fraction per grid cell area
[10881]336   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   v_ip       !: melt pond volume per grid cell area      [m]
[9019]337   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   a_ip_frac  !: melt pond volume per ice area
[10881]338   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   h_ip       !: melt pond thickness                      [m]
[12379]339   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   lh_ip      !: melt pond lid thickness                  [m]
[825]340
[9019]341   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   at_ip      !: total melt pond fraction
[10881]342   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   vt_ip      !: total melt pond volume per unit area     [m]
[9019]343
344   !!----------------------------------------------------------------------
[834]345   !! * Old values of global variables
[9019]346   !!----------------------------------------------------------------------
[10415]347   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   v_s_b, v_i_b, h_s_b, h_i_b, h_ip_b    !: snow and ice volumes/thickness
348   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:)   ::   a_i_b, sv_i_b, oa_i_b                 !:
349   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_s_b                                 !: snow heat content
350   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:,:) ::   e_i_b                                 !: ice temperatures
351   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   u_ice_b, v_ice_b                      !: ice velocity
352   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)     ::   at_i_b                                !: ice concentration (total)
[5123]353           
[9019]354   !!----------------------------------------------------------------------
[834]355   !! * Ice thickness distribution variables
[9019]356   !!----------------------------------------------------------------------
357   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   hi_max         !: Boundary of ice thickness categories in thickness space
358   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   hi_mean        !: Mean ice thickness in catgories
[4147]359   !
[9019]360   !!----------------------------------------------------------------------
[834]361   !! * Ice diagnostics
[9019]362   !!----------------------------------------------------------------------
[5123]363   ! thd refers to changes induced by thermodynamics
364   ! trp   ''         ''     ''       advection (transport of ice)
[7646]365   !
[9019]366   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_vi   !: transport of ice volume
367   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_vs   !: transport of snw volume
[10881]368   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_ei   !: transport of ice enthalpy [W/m2]
369   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_es   !: transport of snw enthalpy [W/m2]
[9019]370   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_trp_sv   !: transport of salt content
[4688]371   !
[9019]372   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_heat     !: snw/ice heat content variation   [W/m2]
373   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_sice     !: ice salt content variation   []
374   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_vice     !: ice volume variation   [m/s]
375   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   diag_vsnw     !: snw volume variation   [m/s]
376
[4688]377   !
[2715]378   !!----------------------------------------------------------------------
[9019]379   !! * SIMIP extra diagnostics
380   !!----------------------------------------------------------------------
381   ! Extra sea ice diagnostics to address the data request
382   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   t_si          !: Temperature at Snow-ice interface (K)
383   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   tm_si         !: mean temperature at the snow-ice interface (K)
[9916]384   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qcn_ice_bot   !: Bottom  conduction flux (W/m2)
385   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   qcn_ice_top   !: Surface conduction flux (W/m2)
[9019]386
[12369]387   INTEGER,  PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:) ::   to_print_2d
[9019]388   !
389   !!----------------------------------------------------------------------
[9598]390   !! NEMO/ICE 4.0 , NEMO Consortium (2018)
[2715]391   !! $Id$
[10068]392   !! Software governed by the CeCILL license (see ./LICENSE)
[2715]393   !!----------------------------------------------------------------------
394CONTAINS
395
396   FUNCTION ice_alloc()
397      !!-----------------------------------------------------------------
[7813]398      !!               *** Routine ice_alloc ***
[2715]399      !!-----------------------------------------------------------------
400      INTEGER :: ice_alloc
401      !
[12369]402      INTEGER :: ierr(16), ii
[2715]403      !!-----------------------------------------------------------------
404      ierr(:) = 0
405
406      ii = 1
[9604]407      ALLOCATE( u_oce    (jpi,jpj) , v_oce    (jpi,jpj) , ht_i_new  (jpi,jpj) , strength(jpi,jpj) ,  &
408         &      stress1_i(jpi,jpj) , stress2_i(jpi,jpj) , stress12_i(jpi,jpj) ,                      &
409         &      delta_i  (jpi,jpj) , divu_i   (jpi,jpj) , shear_i   (jpi,jpj) , STAT=ierr(ii) )
[2715]410
411      ii = ii + 1
[9913]412      ALLOCATE( t_bo       (jpi,jpj) , wfx_snw_sni(jpi,jpj) ,                                                &
413         &      wfx_snw    (jpi,jpj) , wfx_snw_dyn(jpi,jpj) , wfx_snw_sum(jpi,jpj) , wfx_snw_sub(jpi,jpj) ,  &
414         &      wfx_ice    (jpi,jpj) , wfx_sub    (jpi,jpj) , wfx_ice_sub(jpi,jpj) , wfx_lam    (jpi,jpj) ,  &
415         &      wfx_pnd    (jpi,jpj) ,                                                                       &
416         &      wfx_bog    (jpi,jpj) , wfx_dyn   (jpi,jpj) , wfx_bom(jpi,jpj) , wfx_sum(jpi,jpj) ,           &
417         &      wfx_res    (jpi,jpj) , wfx_sni   (jpi,jpj) , wfx_opw(jpi,jpj) , wfx_spr(jpi,jpj) ,           &
[12475]418         &      afx_tot    (jpi,jpj) , rn_amax_2d(jpi,jpj) , wfx_snp(jpi,jpj) ,                              &
[9913]419         &      qsb_ice_bot(jpi,jpj) , qlead     (jpi,jpj) ,                                                 &
420         &      sfx_res    (jpi,jpj) , sfx_bri   (jpi,jpj) , sfx_dyn(jpi,jpj) , sfx_sub(jpi,jpj) , sfx_lam(jpi,jpj) ,  &
421         &      sfx_bog    (jpi,jpj) , sfx_bom   (jpi,jpj) , sfx_sum(jpi,jpj) , sfx_sni(jpi,jpj) , sfx_opw(jpi,jpj) ,  &
[12449]422         &      sfx_pnd    (jpi,jpj) ,                                                                 &
[9913]423         &      hfx_res    (jpi,jpj) , hfx_snw   (jpi,jpj) , hfx_sub(jpi,jpj) ,                        & 
424         &      qt_atm_oi  (jpi,jpj) , qt_oce_ai (jpi,jpj) , fhld   (jpi,jpj) ,                        &
425         &      hfx_sum    (jpi,jpj) , hfx_bom   (jpi,jpj) , hfx_bog(jpi,jpj) , hfx_dif(jpi,jpj) ,     &
426         &      hfx_opw    (jpi,jpj) , hfx_thd   (jpi,jpj) , hfx_dyn(jpi,jpj) , hfx_spr(jpi,jpj) ,     &
[9912]427         &      hfx_err_dif(jpi,jpj) , hfx_err_rem(jpi,jpj) , wfx_err_sub(jpi,jpj)             ,  STAT=ierr(ii) )
[2715]428
429      ! * Ice global state variables
430      ii = ii + 1
[9910]431      ALLOCATE( qtr_ice_bot(jpi,jpj,jpl) , cnd_ice(jpi,jpj,jpl) , t1_ice(jpi,jpj,jpl) ,  &
432         &      h_i        (jpi,jpj,jpl) , a_i    (jpi,jpj,jpl) , v_i   (jpi,jpj,jpl) ,  &
433         &      v_s        (jpi,jpj,jpl) , h_s    (jpi,jpj,jpl) , t_su  (jpi,jpj,jpl) ,  &
434         &      s_i        (jpi,jpj,jpl) , sv_i   (jpi,jpj,jpl) , o_i   (jpi,jpj,jpl) ,  &
435         &      oa_i       (jpi,jpj,jpl) , bv_i   (jpi,jpj,jpl) , STAT=ierr(ii) )
[9604]436
[2715]437      ii = ii + 1
[12369]438      ALLOCATE( a_i_last_couple(jpi,jpj,jpl) , STAT=ierr(ii) )
439
440      ii = ii + 1
[9604]441      ALLOCATE( u_ice(jpi,jpj) , v_ice(jpi,jpj) ,                                   &
442         &      vt_i (jpi,jpj) , vt_s (jpi,jpj) , at_i(jpi,jpj) , ato_i(jpi,jpj) ,  &
443         &      et_i (jpi,jpj) , et_s (jpi,jpj) , tm_i(jpi,jpj) , tm_s (jpi,jpj) ,  &
444         &      sm_i (jpi,jpj) , tm_su(jpi,jpj) , hm_i(jpi,jpj) , hm_s (jpi,jpj) ,  &
445         &      om_i (jpi,jpj) , bvm_i(jpi,jpj) , tau_icebfr(jpi,jpj)            , STAT=ierr(ii) )
446
[2715]447      ii = ii + 1
[5123]448      ALLOCATE( t_s(jpi,jpj,nlay_s,jpl) , e_s(jpi,jpj,nlay_s,jpl) , STAT=ierr(ii) )
[9604]449
[2715]450      ii = ii + 1
[9019]451      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]452
453      ii = ii + 1
[12379]454      ALLOCATE( a_ip(jpi,jpj,jpl) , v_ip(jpi,jpj,jpl) , a_ip_frac(jpi,jpj,jpl) , h_ip(jpi,jpj,jpl), lh_ip(jpi,jpj,jpl) , STAT = ierr(ii) )
[9604]455
[2715]456      ii = ii + 1
[9019]457      ALLOCATE( at_ip(jpi,jpj) , vt_ip(jpi,jpj) , STAT = ierr(ii) )
[2715]458
459      ! * Old values of global variables
460      ii = ii + 1
[10415]461      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), h_ip_b(jpi,jpj,jpl),  &
462         &      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) ,               &
[9604]463         &      oa_i_b(jpi,jpj,jpl)                                                   , STAT=ierr(ii) )
464
[7646]465      ii = ii + 1
466      ALLOCATE( u_ice_b(jpi,jpj) , v_ice_b(jpi,jpj) , at_i_b(jpi,jpj) , STAT=ierr(ii) )
[2715]467     
468      ! * Ice thickness distribution variables
469      ii = ii + 1
[4869]470      ALLOCATE( hi_max(0:jpl), hi_mean(jpl),  STAT=ierr(ii) )
[2715]471
472      ! * Ice diagnostics
473      ii = ii + 1
[7646]474      ALLOCATE( diag_trp_vi(jpi,jpj) , diag_trp_vs (jpi,jpj) , diag_trp_ei(jpi,jpj),   & 
[9019]475         &      diag_trp_es(jpi,jpj) , diag_trp_sv (jpi,jpj) , diag_heat  (jpi,jpj),   &
476         &      diag_sice  (jpi,jpj) , diag_vice   (jpi,jpj) , diag_vsnw  (jpi,jpj), STAT=ierr(ii) )
[2715]477
[9019]478      ! * SIMIP diagnostics
479      ii = ii + 1
[9916]480      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]481
[12369]482      ALLOCATE( to_print_2d(jpi,jpj), STAT = ierr(ii) )
483
[2715]484      ice_alloc = MAXVAL( ierr(:) )
[10425]485      IF( ice_alloc /= 0 )   CALL ctl_stop( 'STOP', 'ice_alloc: failed to allocate arrays.' )
[2715]486      !
487   END FUNCTION ice_alloc
488
[825]489#else
490   !!----------------------------------------------------------------------
[9570]491   !!   Default option         Empty module           NO SI3 sea-ice model
[825]492   !!----------------------------------------------------------------------
493#endif
494
495   !!======================================================================
496END MODULE ice
Note: See TracBrowser for help on using the repository browser.