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

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

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


Revision 1.4 - (hide annotations) (download)
Fri Dec 17 03:44:52 2004 UTC (19 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint57o_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint57i_post, checkpoint57y_post, checkpoint57e_post, checkpoint57g_pre, checkpoint57y_pre, checkpoint57f_pre, checkpoint57v_post, checkpoint57r_post, checkpoint58, eckpoint57e_pre, checkpoint57h_done, checkpoint57x_post, checkpoint57n_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint57f_post, checkpoint57q_post, checkpoint57z_post, checkpoint57c_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post
Changes since 1.3: +2 -1 lines
include header file EEPARAMS.h

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

  ViewVC Help
Powered by ViewVC 1.1.22