Line data Source code
1 : !=======================================================================
2 :
3 : ! Level-ice meltpond parameterization
4 : !
5 : ! This meltpond parameterization was developed for use with the delta-
6 : ! Eddington radiation scheme, and only affects the radiation budget in
7 : ! the model. That is, although the pond volume is tracked, that liquid
8 : ! water is not used elsewhere in the model for mass budgets or other
9 : ! physical processes.
10 : !
11 : ! authors Elizabeth Hunke (LANL)
12 : ! David Hebert (NRL Stennis)
13 : ! Olivier Lecomte (Univ. Louvain)
14 :
15 : module icepack_meltpond_lvl
16 :
17 : use icepack_kinds
18 : use icepack_parameters, only: c0, c1, c2, c10, p01, p5, puny
19 : use icepack_parameters, only: viscosity_dyn, rhoi, rhos, rhow, Timelt, Tffresh, Lfresh
20 : use icepack_parameters, only: gravit, depressT, rhofresh, kice
21 : use icepack_warnings, only: warnstr, icepack_warnings_add
22 : use icepack_warnings, only: icepack_warnings_setabort, icepack_warnings_aborted
23 :
24 : implicit none
25 :
26 : private
27 : public :: compute_ponds_lvl
28 :
29 : !=======================================================================
30 :
31 : contains
32 :
33 : !=======================================================================
34 :
35 3046488360 : subroutine compute_ponds_lvl(dt, nilyr, &
36 : ktherm, &
37 : hi_min, dpscale, &
38 0 : frzpnd, pndaspect, &
39 : rfrac, meltt, melts, &
40 : frain, Tair, fsurfn,&
41 : dhs, ffrac, &
42 : aicen, vicen, vsnon, &
43 3046488360 : qicen, sicen, &
44 : Tsfcn, alvl, &
45 : apnd, hpnd, ipnd)
46 :
47 : integer (kind=int_kind), intent(in) :: &
48 : nilyr, & ! number of ice layers
49 : ktherm ! type of thermodynamics (0 0-layer, 1 BL99, 2 mushy)
50 :
51 : real (kind=dbl_kind), intent(in) :: &
52 : dt, & ! time step (s)
53 : hi_min, & ! minimum ice thickness allowed for thermo (m)
54 : dpscale, & ! alter e-folding time scale for flushing
55 : pndaspect ! ratio of pond depth to pond fraction
56 :
57 : character (len=char_len), intent(in) :: &
58 : frzpnd ! pond refreezing parameterization
59 :
60 : real (kind=dbl_kind), &
61 : intent(in) :: &
62 : Tsfcn, & ! surface temperature (C)
63 : alvl, & ! fraction of level ice
64 : rfrac, & ! water fraction retained for melt ponds
65 : meltt, & ! top melt rate (m/s)
66 : melts, & ! snow melt rate (m/s)
67 : frain, & ! rainfall rate (kg/m2/s)
68 : Tair, & ! air temperature (K)
69 : fsurfn,& ! atm-ice surface heat flux (W/m2)
70 : aicen, & ! ice area fraction
71 : vicen, & ! ice volume (m)
72 : vsnon ! snow volume (m)
73 :
74 : real (kind=dbl_kind), &
75 : intent(inout) :: &
76 : apnd, hpnd, ipnd
77 :
78 : real (kind=dbl_kind), dimension (:), intent(in) :: &
79 : qicen, & ! ice layer enthalpy (J m-3)
80 : sicen ! salinity (ppt)
81 :
82 : real (kind=dbl_kind), &
83 : intent(in) :: &
84 : dhs ! depth difference for snow on sea ice and pond ice
85 :
86 : real (kind=dbl_kind), &
87 : intent(out) :: &
88 : ffrac ! fraction of fsurfn over pond used to melt ipond
89 :
90 : ! local temporary variables
91 :
92 : real (kind=dbl_kind) :: &
93 148911600 : volpn ! pond volume per unit area (m)
94 :
95 : real (kind=dbl_kind), dimension (nilyr) :: &
96 4386692760 : Tmlt ! melting temperature (C)
97 :
98 : real (kind=dbl_kind) :: &
99 148911600 : hi , & ! ice thickness (m)
100 148911600 : hs , & ! snow depth (m)
101 148911600 : dTs , & ! surface temperature diff for freeze-up (C)
102 148911600 : Tp , & ! pond freezing temperature (C)
103 148911600 : Ts , & ! surface air temperature (C)
104 148911600 : apondn , & ! local pond area
105 148911600 : hpondn , & ! local pond depth (m)
106 148911600 : dvn , & ! change in pond volume (m)
107 297823200 : hlid, alid , & ! refrozen lid thickness, area
108 148911600 : dhlid , & ! change in refrozen lid thickness
109 148911600 : bdt , & ! 2 kice dT dt / (rhoi Lfresh)
110 148911600 : alvl_tmp , & ! level ice fraction of ice area
111 446734800 : draft, deltah, pressure_head, perm, drain ! for permeability
112 :
113 : real (kind=dbl_kind), parameter :: &
114 : Td = c2 , & ! temperature difference for freeze-up (C)
115 : rexp = p01 ! pond contraction scaling
116 :
117 : character(len=*),parameter :: subname='(compute_ponds_lvl)'
118 :
119 : !-----------------------------------------------------------------
120 : ! Initialize
121 : !-----------------------------------------------------------------
122 :
123 3046488360 : volpn = hpnd * aicen * alvl * apnd
124 3046488360 : ffrac = c0
125 :
126 : !-----------------------------------------------------------------
127 : ! Identify grid cells where ponds can be
128 : !-----------------------------------------------------------------
129 :
130 3046488360 : if (aicen*alvl > puny**2) then
131 :
132 552384067 : hi = vicen/aicen
133 552384067 : hs = vsnon/aicen
134 552384067 : alvl_tmp = alvl
135 :
136 552384067 : if (hi < hi_min) then
137 :
138 : !--------------------------------------------------------------
139 : ! Remove ponds on thin ice
140 : !--------------------------------------------------------------
141 1526916 : apondn = c0
142 1526916 : hpondn = c0
143 1526916 : volpn = c0
144 1526916 : hlid = c0
145 :
146 : else
147 :
148 : !-----------------------------------------------------------
149 : ! initialize pond area as fraction of ice
150 : !-----------------------------------------------------------
151 550857151 : apondn = apnd*alvl_tmp
152 :
153 : !-----------------------------------------------------------
154 : ! update pond volume
155 : !-----------------------------------------------------------
156 : ! add melt water
157 : dvn = rfrac/rhofresh*(meltt*rhoi &
158 : + melts*rhos &
159 550857151 : + frain* dt)*aicen
160 :
161 : ! shrink pond volume under freezing conditions
162 550857151 : if (trim(frzpnd) == 'cesm') then
163 0 : Tp = Timelt - Td
164 0 : dTs = max(Tp - Tsfcn,c0)
165 0 : dvn = dvn - volpn * (c1 - exp(rexp*dTs/Tp))
166 :
167 : else
168 : ! trim(frzpnd) == 'hlid' Stefan approximation
169 : ! assumes pond is fresh (freezing temperature = 0 C)
170 : ! and ice grows from existing pond ice
171 550857151 : hlid = ipnd
172 550857151 : if (dvn == c0) then ! freeze pond
173 316560149 : Ts = Tair - Tffresh
174 316560149 : if (Ts < c0) then
175 : ! if (Ts < -c2) then ! as in meltpond_cesm
176 314711757 : bdt = -c2*Ts*kice*dt/(rhoi*Lfresh)
177 314711757 : dhlid = p5*sqrt(bdt) ! open water freezing
178 314711757 : if (hlid > dhlid) dhlid = p5*bdt/hlid ! existing ice
179 314711757 : dhlid = min(dhlid, hpnd*rhofresh/rhoi)
180 314711757 : hlid = hlid + dhlid
181 : else
182 1848392 : dhlid = c0 ! to account for surface inversions
183 : endif
184 : else ! convert refrozen pond ice back to water
185 234297002 : dhlid = max(fsurfn*dt / (rhoi*Lfresh), c0) ! > 0
186 234297002 : dhlid = -min(dhlid, hlid) ! < 0
187 234297002 : hlid = max(hlid + dhlid, c0)
188 234297002 : if (hs - dhs < puny) then ! pond ice is snow-free
189 44471036 : ffrac = c1 ! fraction of fsurfn over pond used to melt ipond
190 44471036 : if (fsurfn > puny) &
191 35916986 : ffrac = min(-dhlid*rhoi*Lfresh/(dt*fsurfn), c1)
192 : endif
193 : endif
194 550857151 : alid = apondn * aicen
195 550857151 : dvn = dvn - dhlid*alid*rhoi/rhofresh
196 : endif
197 :
198 550857151 : volpn = volpn + dvn
199 :
200 : !-----------------------------------------------------------
201 : ! update pond area and depth
202 : !-----------------------------------------------------------
203 550857151 : if (volpn <= c0) then
204 303389454 : volpn = c0
205 303389454 : apondn = c0
206 : endif
207 :
208 550857151 : if (apondn*aicen > puny) then ! existing ponds
209 : apondn = max(c0, min(alvl_tmp, &
210 187266404 : apondn + 0.5*dvn/(pndaspect*apondn*aicen)))
211 187266404 : hpondn = c0
212 187266404 : if (apondn > puny) &
213 182302542 : hpondn = volpn/(apondn*aicen)
214 :
215 363590747 : elseif (alvl_tmp*aicen > c10*puny) then ! new ponds
216 357309228 : apondn = min (sqrt(volpn/(pndaspect*aicen)), alvl_tmp)
217 357309228 : hpondn = pndaspect * apondn
218 :
219 : else ! melt water runs off deformed ice
220 6281519 : apondn = c0
221 6281519 : hpondn = c0
222 : endif
223 550857151 : apondn = max(apondn, c0)
224 :
225 : ! limit pond depth to maintain nonnegative freeboard
226 550857151 : hpondn = min(hpondn, ((rhow-rhoi)*hi - rhos*hs)/rhofresh)
227 :
228 : ! fraction of grid cell covered by ponds
229 550857151 : apondn = apondn * aicen
230 :
231 550857151 : volpn = hpondn*apondn
232 550857151 : if (volpn <= c0) then
233 311639075 : volpn = c0
234 311639075 : apondn = c0
235 311639075 : hpondn = c0
236 311639075 : hlid = c0
237 : endif
238 :
239 : !-----------------------------------------------------------
240 : ! drainage due to permeability (flushing)
241 : ! setting dpscale = 0 turns this off
242 : ! NOTE this uses the initial salinity and melting T profiles
243 : !-----------------------------------------------------------
244 :
245 550857151 : if (ktherm /= 2 .and. hpondn > c0 .and. dpscale > puny) then
246 14367306 : draft = (rhos*hs + rhoi*hi)/rhow + hpondn
247 14367306 : deltah = hpondn + hi - draft
248 14367306 : pressure_head = gravit * rhow * max(deltah, c0)
249 114938448 : Tmlt(:) = -sicen(:) * depressT
250 0 : call brine_permeability(nilyr, qicen, &
251 14367306 : sicen, Tmlt, perm)
252 14367306 : if (icepack_warnings_aborted(subname)) return
253 14367306 : drain = perm*pressure_head*dt / (viscosity_dyn*hi) * dpscale
254 14367306 : deltah = min(drain, hpondn)
255 14367306 : dvn = -deltah*apondn
256 14367306 : volpn = volpn + dvn
257 : apondn = max(c0, min(apondn &
258 14367306 : + 0.5*dvn/(pndaspect*apondn), alvl_tmp*aicen))
259 14367306 : hpondn = c0
260 14367306 : if (apondn > puny) hpondn = volpn/apondn
261 : endif
262 :
263 : endif
264 :
265 : !-----------------------------------------------------------
266 : ! Reload tracer array
267 : !-----------------------------------------------------------
268 :
269 552384067 : hpnd = hpondn
270 552384067 : apnd = apondn / (aicen*alvl_tmp)
271 552384067 : if (trim(frzpnd) == 'hlid') ipnd = hlid
272 :
273 : endif
274 :
275 : end subroutine compute_ponds_lvl
276 :
277 : !=======================================================================
278 :
279 : ! determine the liquid fraction of brine in the ice and the permeability
280 :
281 14367306 : subroutine brine_permeability(nilyr, qicen, salin, Tmlt, perm)
282 :
283 : use icepack_therm_shared, only: calculate_Tin_from_qin
284 :
285 : integer (kind=int_kind), intent(in) :: &
286 : nilyr ! number of ice layers
287 :
288 : real (kind=dbl_kind), dimension(:), intent(in) :: &
289 : qicen, & ! enthalpy for each ice layer (J m-3)
290 : salin, & ! salinity (ppt)
291 : Tmlt ! melting temperature (C)
292 :
293 : real (kind=dbl_kind), intent(out) :: &
294 : perm ! permeability (m^2)
295 :
296 : ! local variables
297 :
298 : real (kind=dbl_kind) :: &
299 121746 : Sbr ! brine salinity
300 :
301 : real (kind=dbl_kind), dimension(nilyr) :: &
302 29465088 : Tin, & ! ice temperature (C)
303 29586834 : phi ! liquid fraction
304 :
305 : integer (kind=int_kind) :: k
306 :
307 : character(len=*),parameter :: subname='(brine_permeability)'
308 :
309 : !-----------------------------------------------------------------
310 : ! Compute ice temperatures from enthalpies using quadratic formula
311 : !-----------------------------------------------------------------
312 :
313 114938448 : do k = 1,nilyr
314 114938448 : Tin(k) = calculate_Tin_from_qin(qicen(k),Tmlt(k))
315 : enddo
316 :
317 : !-----------------------------------------------------------------
318 : ! brine salinity and liquid fraction
319 : !-----------------------------------------------------------------
320 :
321 114938448 : do k = 1,nilyr
322 100571142 : Sbr = c1/(1.e-3_dbl_kind - depressT/Tin(k)) ! Notz thesis eq 3.6
323 100571142 : phi(k) = salin(k)/Sbr ! liquid fraction
324 114938448 : if (phi(k) < 0.05) phi(k) = c0 ! impermeable
325 : enddo
326 :
327 : !-----------------------------------------------------------------
328 : ! permeability
329 : !-----------------------------------------------------------------
330 :
331 129305754 : perm = 3.0e-8_dbl_kind * (minval(phi))**3
332 :
333 14367306 : end subroutine brine_permeability
334 :
335 : !=======================================================================
336 :
337 : end module icepack_meltpond_lvl
338 :
339 : !=======================================================================
|