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