/[MITgcm]/MITgcm/pkg/thsice/thsice_calc_thickn.F
ViewVC logotype

Contents of /MITgcm/pkg/thsice/thsice_calc_thickn.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.3 - (show annotations) (download)
Fri May 7 21:33:34 2004 UTC (20 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint53d_post, checkpoint54a_pre, checkpoint55c_post, checkpoint54e_post, checkpoint54a_post, checkpoint53c_post, checkpoint55d_pre, checkpoint55j_post, checkpoint56b_post, checkpoint55h_post, checkpoint53b_post, checkpoint54b_post, checkpoint53b_pre, checkpoint55b_post, checkpoint54d_post, checkpoint56c_post, checkpoint55, checkpoint53a_post, checkpoint57a_post, checkpoint54, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, checkpoint53g_post, checkpoint55e_post, checkpoint53f_post, checkpoint55a_post, checkpoint53d_pre, checkpoint54c_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.2: +12 -14 lines
improve "debug" writing.

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_calc_thickn.F,v 1.2 2004/04/18 22:19:37 jmc Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: THSICE_CALC_THICKN
8 C !INTERFACE:
9 SUBROUTINE THSICE_CALC_THICKN(
10 I frzmlt, Tf, oceTs, oceV2s, snowPr,
11 I sHeating, flxCnB, evpAtm,
12 U compact, hi, hs, Tsf, qicen, qleft,
13 O fresh, fsalt, Fbot,
14 I dBugFlag, myThid )
15 C !DESCRIPTION: \bv
16 C *==========================================================*
17 C | S/R THSICE_CALC_THICKN
18 C | o Calculate ice & snow thickness changes
19 C *==========================================================*
20 C \ev
21
22 C !USES:
23 IMPLICIT NONE
24
25 C == Global variables ===
26 #include "THSICE_SIZE.h"
27 #include "THSICE_PARAMS.h"
28
29 C !INPUT/OUTPUT PARAMETERS:
30 C == Routine Arguments ==
31 C frzmlt :: ocean mixed-layer freezing/melting potential [W/m2]
32 C Tf :: sea-water freezing temperature [oC] (function of S)
33 C oceTs :: surface level oceanic temperature [oC]
34 C oceV2s :: square of ocean surface-level velocity [m2/s2]
35 C snowPr :: snow precipitation [kg/m2/s]
36 C sHeating :: surf heating flux left to melt snow or ice (= Atmos-conduction)
37 C flxCnB :: heat flux conducted through the ice to bottom surface
38 C evpAtm :: evaporation to the atmosphere [kg/m2/s] (>0 if evaporate)
39 C compact :: fraction of grid area covered in ice
40 C hi :: ice height
41 C hs :: snow height
42 C Tsf :: surface (ice or snow) temperature
43 C qicen :: ice enthalpy (J m-3)
44 C qleft :: net heat flux to ocean [W/m2] (> 0 downward)
45 C fresh :: Total fresh water flux to ocean [kg/m2/s] (> 0 downward)
46 C fsalt :: salt flux to ocean [g/m2/s] (> 0 downward)
47 C Fbot :: oceanic heat flux used to melt/form ice [W/m2]
48 C dBugFlag :: allow to print debugging stuff (e.g. on 1 grid point).
49 C myThid :: Thread no. that called this routine.
50 _RL frzmlt
51 _RL Tf
52 _RL oceTs, oceV2s, snowPr
53 _RL sHeating
54 _RL flxCnB
55 _RL evpAtm
56 _RL compact
57 _RL hi
58 _RL hs
59 _RL Tsf
60 _RL qicen(nlyr)
61
62 _RL qleft
63 _RL fresh
64 _RL fsalt
65 _RL Fbot
66 LOGICAL dBugFlag
67 INTEGER myThid
68 CEOP
69
70 #ifdef ALLOW_THSICE
71
72 C ADAPTED FROM:
73 C LANL CICE.v2.0.2
74 C-----------------------------------------------------------------------
75 C.. thermodynamics (vertical physics) based on M. Winton 3-layer model
76 C.. See Bitz, C. M. and W. H. Lipscomb, 1999: "An energy-conserving
77 C.. thermodynamic sea ice model for climate study." J. Geophys.
78 C.. Res., 104, 15669 - 15677.
79 C.. Winton, M., 1999: "A reformulated three-layer sea ice model."
80 C.. Submitted to J. Atmos. Ocean. Technol.
81 C.. authors Elizabeth C. Hunke and William Lipscomb
82 C.. Fluid Dynamics Group, Los Alamos National Laboratory
83 C-----------------------------------------------------------------------
84 Cc****subroutine thermo_winton(n,fice,fsnow,dqice,dTsfc)
85 C.. Compute temperature change using Winton model with 2 ice layers, of
86 C.. which only the top layer has a variable heat capacity.
87
88 C == Local Variables ==
89 INTEGER k
90
91 _RL rnlyr ! maximum number of ice layers (real value)
92 C evap :: evaporation over snow/ice [kg/m2/s] (>0 if evaporate)
93 _RL evap
94 _RL etop ! energy for top melting (J m-2)
95 _RL ebot ! energy for bottom melting (J m-2)
96 _RL etope ! energy (from top) for lateral melting (J m-2)
97 _RL ebote ! energy (from bottom) for lateral melting (J m-2)
98 _RL extend ! total energy for lateral melting (J m-2)
99 _RL hnew(nlyr) ! new ice layer thickness (m)
100 _RL hlyr ! individual ice layer thickness (m)
101 _RL dhi ! change in ice thickness
102 _RL dhs ! change in snow thickness
103 _RL rq ! rho * q for a layer
104 _RL rqh ! rho * q * h for a layer
105 _RL qbot ! q for new ice at bottom surf (J m-3)
106 _RL dt ! timestep
107 _RL esurp ! surplus energy from melting (J m-2)
108 _RL mwater0 ! fresh water mass gained/lost (kg/m^2)
109 _RL msalt0 ! salt gained/lost (kg/m^2)
110 _RL freshe ! fresh water gain from extension melting
111 _RL salte ! salt gained from extension melting
112
113 _RL ustar, cpchr
114
115 _RL chi, chs
116 _RL frace, rs, hq
117 LOGICAL dBug
118
119 1010 FORMAT(A,I3,3F8.3)
120 1020 FORMAT(A,1P4E11.3)
121
122 rnlyr = nlyr
123 dt = thSIce_deltaT
124 dBug = .FALSE.
125 c dBug = dBugFlag
126
127 C initialize energies
128 esurp = 0. _d 0
129
130 evap = evpAtm
131
132 C......................................................................
133 C.. Compute growth and/or melting at the top and bottom surfaces.......
134 C......................................................................
135
136 if (frzmlt.ge. 0. _d 0) then
137 C !-----------------------------------------------------------------
138 C ! freezing conditions
139 C !-----------------------------------------------------------------
140 C if higher than hihig, use all frzmlt energy to grow extra ice
141 if (hi.gt.hihig.and. compact.le.iceMaskmax) then
142 Fbot=0. _d 0
143 else
144 Fbot=frzmlt
145 endif
146 else
147 C !-----------------------------------------------------------------
148 C ! melting conditions
149 C !-----------------------------------------------------------------
150 ustar = 5. _d -2 !for no currents
151 C frictional velocity between ice and water
152 ustar = sqrt(0.00536 _d 0*oceV2s)
153 ustar=max(5. _d -3,ustar)
154 cpchr =cpwater*rhosw*transcoef
155 Fbot = cpchr*(Tf-oceTs)*ustar ! < 0
156 Fbot = max(Fbot,frzmlt) ! frzmlt < Fbot < 0
157 Fbot = min(Fbot,0. _d 0)
158 endif
159
160 C mass of fresh water and salt initially present in ice
161 mwater0 = rhos*hs + rhoi*hi
162 msalt0 = rhoi*hi*saltice
163
164 IF (dBug) WRITE(6,1020) 'ThSI_CALC_TH: evpAtm, frzmlt, Fbot =',
165 & evpAtm, frzmlt, Fbot
166
167 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
168
169 C Compute energy available for melting/growth.
170
171 if (hi.lt.himin0) then
172 C below a certain height, all energy goes to changing ice extent
173 frace=1. _d 0
174 else
175 frace=frac_energy
176 endif
177 if (hi.gt.hihig) then
178 C above certain height only melt from top
179 frace=0. _d 0
180 else
181 frace=frac_energy
182 endif
183 C force this when no ice fractionation
184 if (frac_energy.eq.0. _d 0) frace=0. _d 0
185
186 c if (Tsf .eq. 0. _d 0 .and. sHeating.gt.0. _d 0) then
187 if ( sHeating.gt.0. _d 0 ) then
188 etop = (1. _d 0-frace)*sHeating * dt
189 etope = frace*sHeating * dt
190 else
191 etop = 0. _d 0
192 etope = 0. _d 0
193 C jmc: found few cases where Tsf=0 & sHeating < 0 : add this line to conserv energy:
194 esurp = sHeating * dt
195 endif
196 C-- flux at the base of sea-ice:
197 C conduction H.flx= flxCnB (+ =down); oceanic turbulent H.flx= Fbot (+ =down).
198 C- ==> energy available(+ => melt)= (flxCnB-Fbot)*dt
199 c if (frzmlt.lt.0. _d 0) then
200 c ebot = (1. _d 0-frace)*(flxCnB-Fbot) * dt
201 c ebote = frace*(flxCnB-Fbot) * dt
202 c else
203 c ebot = (flxCnB-Fbot) * dt
204 c ebote = 0. _d 0
205 c endif
206 C- original formulation(above): Loose energy when flxCnB < Fbot < 0
207 ebot = (flxCnB-Fbot) * dt
208 if (ebot.gt.0. _d 0) then
209 ebote = frace*ebot
210 ebot = ebot-ebote
211 else
212 ebote = 0. _d 0
213 endif
214 IF (dBug) WRITE(6,1020) 'ThSI_CALC_TH: etop,etope,ebot,ebote=',
215 & etop,etope,ebot,ebote
216
217 C Initialize layer thicknesses.
218 C Make sure internal ice temperatures do not exceed Tmlt.
219 C If they do, then eliminate the layer. (Dont think this will happen
220 C for reasonable values of i0.)
221
222 hlyr = hi / rnlyr
223 do k = 1, nlyr
224 hnew(k) = hlyr
225 enddo
226
227 C Top melt: snow, then ice.
228
229 if (etop .gt. 0. _d 0) then
230 if (hs. gt. 0. _d 0) then
231 rq = rhos * qsnow
232 rqh = rq * hs
233 if (etop .lt. rqh) then
234 hs = hs - etop/rq
235 etop = 0. _d 0
236 else
237 etop = etop - rqh
238 hs = 0. _d 0
239 endif
240 endif
241
242 do k = 1, nlyr
243 if (etop .gt. 0. _d 0) then
244 rq = rhoi * qicen(k)
245 rqh = rq * hnew(k)
246 if (etop .lt. rqh) then
247 hnew(k) = hnew(k) - etop / rq
248 etop = 0. _d 0
249 else
250 etop = etop - rqh
251 hnew(k) = 0. _d 0
252 endif
253 endif
254 enddo
255 else
256 etop=0. _d 0
257 endif
258 C If ice is gone and melting energy remains
259 c if (etop .gt. 0. _d 0) then
260 c write (6,*) 'QQ All ice melts from top ', i,j
261 c hi=0. _d 0
262 c go to 200
263 c endif
264
265
266 C Bottom melt/growth.
267
268 if (ebot .lt. 0. _d 0) then
269 C Compute enthalpy of new ice growing at bottom surface.
270 qbot = -cpice *Tf + Lfresh
271 dhi = -ebot / (qbot * rhoi)
272 ebot = 0. _d 0
273 k = nlyr
274 qicen(k) = (hnew(k)*qicen(k)+dhi*qbot) / (hnew(k)+dhi)
275 hnew(k) = hnew(k) + dhi
276 else
277 do k = nlyr, 1, -1
278 if (ebot.gt.0. _d 0 .and. hnew(k).gt.0. _d 0) then
279 rq = rhoi * qicen(k)
280 rqh = rq * hnew(k)
281 if (ebot .lt. rqh) then
282 hnew(k) = hnew(k) - ebot / rq
283 ebot = 0. _d 0
284 else
285 ebot = ebot - rqh
286 hnew(k) = 0. _d 0
287 endif
288 endif
289 enddo
290
291 C If ice melts completely and snow is left, remove the snow with
292 C energy from the mixed layer
293
294 if (ebot.gt.0. _d 0 .and. hs.gt.0. _d 0) then
295 rq = rhos * qsnow
296 rqh = rq * hs
297 if (ebot .lt. rqh) then
298 hs = hs - ebot / rq
299 ebot = 0. _d 0
300 else
301 ebot = ebot - rqh
302 hs = 0. _d 0
303 endif
304 endif
305 c if (ebot .gt. 0. _d 0) then
306 c IF (dBug) WRITE(6,*) 'All ice (& snow) melts from bottom'
307 c hi=0. _d 0
308 c go to 200
309 c endif
310 endif
311
312 C Compute new total ice thickness.
313 hi = 0. _d 0
314 do k = 1, nlyr
315 hi = hi + hnew(k)
316 enddo
317 IF (dBug) WRITE(6,1020) 'ThSI_CALC_TH: etop, ebot, hi, hs =',
318 & etop, ebot, hi, hs
319
320 C If hi < himin, melt the ice.
321 if ( hi.lt.himin .AND. (hi+hs).gt.0. _d 0 ) then
322 esurp = esurp - rhos*qsnow*hs
323 do k = 1, nlyr
324 esurp = esurp - rhoi*qicen(k)*hnew(k)
325 enddo
326 hi = 0. _d 0
327 hs = 0. _d 0
328 Tsf=0. _d 0
329 compact = 0. _d 0
330 do k = 1, nlyr
331 qicen(k) = 0. _d 0
332 enddo
333 IF (dBug) WRITE(6,1020) 'ThSI_CALC_TH: -1 : esurp=',esurp
334 endif
335
336 C-- do a mass-budget of sea-ice to compute "fresh" = the fresh-water flux
337 C that is returned to the ocean ; needs to be done before snow/evap
338 fresh = (mwater0 - (rhos*hs + rhoi*hi))/dt
339
340 C- note : was not supposed to modify snowPr in THSICE_CALC_TH ;
341 C but to reproduce old results, reset to zero if Tsf >= 0
342 c IF ( Tsf.ge.0. _d 0 ) snowPr = 0.
343
344 IF ( hi .LE. 0. _d 0 ) THEN
345 C- return snow to the ocean (account for Latent heat of freezing)
346 fresh = fresh + snowPr
347 qleft = qleft - snowPr*Lfresh
348 GOTO 200
349 ENDIF
350
351 C Let it snow
352
353 hs = hs + dt*snowPr/rhos
354
355 C If ice evap is used to sublimate surface snow/ice or
356 C if no ice pass on to ocean
357 if (hs.gt.0. _d 0) then
358 if (evap/rhos *dt.gt.hs) then
359 evap=evap-hs*rhos/dt
360 hs=0. _d 0
361 else
362 hs = hs - evap/rhos *dt
363 evap=0. _d 0
364 endif
365 endif
366 if (hi.gt.0. _d 0.and.evap.gt.0. _d 0) then
367 do k = 1, nlyr
368 if (evap .gt. 0. _d 0) then
369 C-- original scheme, does not care about ice temp.
370 C- this can produce small error (< 1.W/m2) in the Energy budget
371 c if (evap/rhoi *dt.gt.hnew(k)) then
372 c evap=evap-hnew(k)*rhoi/dt
373 c hnew(k)=0. _d 0
374 c else
375 c hnew(k) = hnew(k) - evap/rhoi *dt
376 c evap=0. _d 0
377 c endif
378 C-- modified scheme. taking into account Ice enthalpy
379 dhi = evap/rhoi*dt
380 if (dhi.ge.hnew(k)) then
381 evap=evap-hnew(k)*rhoi/dt
382 esurp = esurp - hnew(k)*rhoi*(qicen(k)-Lfresh)
383 hnew(k)=0. _d 0
384 else
385 hq = hnew(k)*qicen(k)-dhi*Lfresh
386 hnew(k) = hnew(k) - dhi
387 qicen(k)=hq/hnew(k)
388 evap=0. _d 0
389 endif
390 C-------
391 endif
392 enddo
393 endif
394 c if (evap .gt. 0. _d 0) then
395 c write (6,*) 'BB All ice sublimates', i,j
396 c hi=0. _d 0
397 c go to 200
398 c endif
399
400 C Compute new total ice thickness.
401
402 hi = 0. _d 0
403 do k = 1, nlyr
404 hi = hi + hnew(k)
405 enddo
406
407 C If hi < himin, melt the ice.
408 if ( hi.gt.0. _d 0 .AND. hi.lt.himin ) then
409 fresh = fresh + (rhos*hs + rhoi*hi)/dt
410 esurp = esurp - rhos*qsnow*hs
411 do k = 1, nlyr
412 esurp = esurp - rhoi*qicen(k)*hnew(k)
413 enddo
414 hi = 0. _d 0
415 hs = 0. _d 0
416 Tsf=0. _d 0
417 compact = 0. _d 0
418 do k = 1, nlyr
419 qicen(k) = 0. _d 0
420 enddo
421 IF (dBug) WRITE(6,1020) 'ThSI_CALC_TH: -2 : esurp,fresh=',
422 & esurp, fresh
423 endif
424 IF ( hi .le. 0. _d 0 ) GOTO 200
425
426 C If there is enough snow to lower the ice/snow interface below
427 C freeboard, convert enough snow to ice to bring the interface back
428 C to sea-level. Adjust enthalpy of top ice layer accordingly.
429
430 if ( hs .gt. hi*rhoiw/rhos ) then
431 cBB write (6,*) 'Freeboard adjusts'
432 dhi = (hs * rhos - hi * rhoiw) / rhosw
433 dhs = dhi * rhoi / rhos
434 rqh = rhoi*qicen(1)*hnew(1) + rhos*qsnow*dhs
435 hnew(1) = hnew(1) + dhi
436 qicen(1) = rqh / (rhoi*hnew(1))
437 hi = hi + dhi
438 hs = hs - dhs
439 end if
440
441
442 C limit ice height
443 C- NOTE: this part does not conserve Energy ;
444 C but surplus of fresh water and salt are taken into account.
445 if (hi.gt.hiMax) then
446 cBB print*,'BBerr, hi>hiMax',i,j,hi
447 chi=hi-hiMax
448 do k=1,nlyr
449 hnew(k)=hnew(k)-chi/2. _d 0
450 enddo
451 fresh = fresh + chi*rhoi/dt
452 endif
453 if (hs.gt.hsMax) then
454 c print*,'BBerr, hs>hsMax',i,j,hs
455 chs=hs-hsMax
456 hs=hsMax
457 fresh = fresh + chs*rhos/dt
458 endif
459
460 C Compute new total ice thickness.
461
462 hi = 0. _d 0
463 do k = 1, nlyr
464 hi = hi + hnew(k)
465 enddo
466
467 IF (dBug) WRITE(6,1020) 'ThSI_CALC_TH: b-Winton: hnew, qice =',
468 & hnew, qicen
469
470 hlyr = hi/rnlyr
471 CALL THSICE_RESHAPE_LAYERS(
472 U qicen,
473 I hlyr, hnew, myThid )
474
475 IF (dBug) WRITE(6,1020) 'ThSI_CALC_TH: compact,hi, qtot, hs =',
476 & compact,hi,(qicen(1)+qicen(2))*0.5, hs
477
478 200 continue
479
480 C- Compute surplus energy left over from melting.
481
482 if (hi.le.0. _d 0) compact=0. _d 0
483
484 C.. heat fluxes left over for ocean
485 qleft = qleft + (Fbot+(esurp+etop+ebot)/dt)
486 IF(dBug) WRITE(6,1020)'ThSI_CALC_TH: [esurp,etop+ebot]/dt ='
487 & ,esurp/dt,etop/dt,ebot/dt
488
489 C-- Evaporation left to the ocean :
490 fresh = fresh - evap
491 C- Correct Atmos. fluxes for this different latent heat:
492 C evap was computed over freezing surf.(Tsf<0), latent heat = Lvap+Lfresh
493 C but should be Lvap only for the fraction "evap" that is left to the ocean.
494 qleft = qleft + evap*Lfresh
495
496 C fresh and salt fluxes
497 c fresh = (mwater0 - (rhos*(hs) + rhoi*(hi)))/dt-evap
498 c fsalt = (msalt0 - rhoi*hi*saltice)/35. _d 0/dt ! for same units as fresh
499 C note (jmc): fresh is computed from a sea-ice mass budget that already
500 C contains, at this point, snow & evaporation (of snow & ice)
501 C but are not meant to be part of ice/ocean fresh-water flux.
502 C fix: a) like below or b) by making the budget before snow/evap is added
503 c fresh = (mwater0 - (rhos*(hs) + rhoi*(hi)))/dt
504 c & + snow(i,j,bi,bj)*rhos - evpAtm
505 fsalt = (msalt0 - rhoi*hi*saltice)/dt
506
507 IF (dBug) WRITE(6,1020)'ThSI_CALC_TH:dH2O,Ev[kg],fresh,fsalt',
508 & (mwater0-(rhos*hs+rhoi*hi))/dt,evap,fresh,fsalt
509 IF (dBug) WRITE(6,1020)'ThSI_CALC_TH: Qleft,Fbot,extend/dt =',
510 & Qleft,Fbot,(etope+ebote)/dt
511
512 C-- note: at this point, compact has not been changed (unless reset to zero)
513 C and it can only be reduced by lateral melting in the following part:
514
515 C calculate extent changes
516 extend=etope+ebote
517 if (compact.gt.0. _d 0.and.extend.gt.0. _d 0) then
518 rq = rhoi * 0.5 _d 0*(qicen(1)+qicen(2))
519 rs = rhos * qsnow
520 rqh = rq * hi + rs * hs
521 freshe=(rhos*hs+rhoi*hi)/dt
522 salte=(rhoi*hi*saltice)/dt
523 if (extend .lt. rqh) then
524 compact=(1. _d 0-extend/rqh)*compact
525 fresh=fresh+extend/rqh*freshe
526 fsalt=fsalt+extend/rqh*salte
527 else
528 compact=0. _d 0
529 hi=0. _d 0
530 hs=0. _d 0
531 qleft=qleft+(extend-rqh)/dt
532 fresh=fresh+freshe
533 fsalt=fsalt+salte
534 endif
535 elseif (extend.gt.0. _d 0) then
536 qleft=qleft+extend/dt
537 endif
538
539 #endif /* ALLOW_THSICE */
540
541 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
542
543 RETURN
544 END

  ViewVC Help
Powered by ViewVC 1.1.22