/[MITgcm]/MITgcm/pkg/seaice/seaice_solve4temp.F
ViewVC logotype

Contents of /MITgcm/pkg/seaice/seaice_solve4temp.F

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


Revision 1.16 - (show annotations) (download)
Wed Jun 29 21:39:06 2011 UTC (12 years, 11 months ago) by ifenty
Branch: MAIN
CVS Tags: checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63
Changes since 1.15: +58 -17 lines
seaice package/sublimation treatment:  added a cap on the latent heat flux over sea ice
such that the amount of sublimation over one time step cannot exceed the amount of
mass in the sea ice and snow.  Works for the non-legacy version of seaice_solve4temp.

Added diagnostics SImaxLHF, SIactLHF (max and actual latent heat flux) and
SIrsSubl (residual freshwater flux following removal of ice and snow)


 ----------------------------------------------------------------------
 Modified Files:
 	seaice_diagnostics_init.F seaice_growth.F seaice_solve4temp.F
 ----------------------------------------------------------------------

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_solve4temp.F,v 1.15 2011/06/19 23:01:54 ifenty Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: SEAICE_SOLVE4TEMP
8 C !INTERFACE:
9 SUBROUTINE SEAICE_SOLVE4TEMP(
10 I UG, HICE_ACTUAL, HSNOW_ACTUAL,
11 #ifdef SEAICE_ADD_SUBLIMATION_TO_FWBUDGET
12 I F_lh_max,
13 #endif
14 U TSURF,
15 O F_ia, IcePenetSWFlux,
16 O FWsublim,
17 I bi, bj, myTime, myIter, myThid )
18
19 C !DESCRIPTION: \bv
20 C *==========================================================*
21 C | SUBROUTINE SOLVE4TEMP
22 C | o Calculate ice growth rate, surface fluxes and
23 C | temperature of ice surface.
24 C | see Hibler, MWR, 108, 1943-1973, 1980
25 C *==========================================================*
26 C \ev
27
28 C !USES:
29 IMPLICIT NONE
30 C === Global variables ===
31 #include "SIZE.h"
32 #include "GRID.h"
33 #include "EEPARAMS.h"
34 #include "PARAMS.h"
35 #include "FFIELDS.h"
36 #include "SEAICE_SIZE.h"
37 #include "SEAICE_PARAMS.h"
38 #include "SEAICE.h"
39 #ifdef SEAICE_VARIABLE_FREEZING_POINT
40 #include "DYNVARS.h"
41 #endif /* SEAICE_VARIABLE_FREEZING_POINT */
42 #ifdef ALLOW_EXF
43 # include "EXF_OPTIONS.h"
44 # include "EXF_FIELDS.h"
45 #endif
46 #ifdef ALLOW_AUTODIFF_TAMC
47 # include "tamc.h"
48 #endif
49
50 C !INPUT/OUTPUT PARAMETERS
51 C === Routine arguments ===
52 C INPUT:
53 C UG :: thermal wind of atmosphere
54 C HICE_ACTUAL :: actual ice thickness
55 C HSNOW_ACTUAL :: actual snow thickness
56 C TSURF :: surface temperature of ice in Kelvin, updated
57 C bi,bj :: loop indices
58 C OUTPUT:
59 C F_io_net :: net upward conductive heat flux through ice at the base
60 C of the ice
61 C F_ia_net :: net heat flux divergence at the sea ice/snow surface:
62 C includes ice conductive fluxes and atmospheric fluxes (W/m^2)
63 C F_ia :: upward sea ice/snow surface heat flux to atmosphere (W/m^2)
64 C IcePenetSWFlux :: short wave heat flux under ice
65 C FWsublim :: fresh water (mass) flux implied by latent heat of
66 C sublimation (kg/m^2/s)
67 _RL UG (1:sNx,1:sNy)
68 _RL HICE_ACTUAL (1:sNx,1:sNy)
69 _RL HSNOW_ACTUAL (1:sNx,1:sNy)
70 #ifdef SEAICE_ADD_SUBLIMATION_TO_FWBUDGET
71 _RL F_lh_max (1:sNx,1:sNy)
72 #endif
73 _RL TSURF (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
74 c _RL F_io_net (1:sNx,1:sNy)
75 c _RL F_ia_net (1:sNx,1:sNy)
76 _RL F_ia (1:sNx,1:sNy)
77 _RL IcePenetSWFlux (1:sNx,1:sNy)
78 _RL FWsublim (1:sNx,1:sNy)
79 INTEGER bi, bj
80 _RL myTime
81 INTEGER myIter, myThid
82
83 C !LOCAL VARIABLES:
84 C === Local variables ===
85 _RL F_io_net (1:sNx,1:sNy)
86 _RL F_ia_net (1:sNx,1:sNy)
87 #ifndef SEAICE_SOLVE4TEMP_LEGACY
88 _RL F_swi (1:sNx,1:sNy)
89 _RL F_lwd (1:sNx,1:sNy)
90 _RL F_lwu (1:sNx,1:sNy)
91 _RL F_sens (1:sNx,1:sNy)
92 _RL hice_tmp
93 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
94 _RL F_lh (1:sNx,1:sNy)
95 _RL F_c (1:sNx,1:sNy)
96 _RL qhice (1:sNx,1:sNy)
97
98 _RL AbsorbedSWFlux (1:sNx,1:sNy)
99 _RL IcePenetSWFluxFrac (1:sNx,1:sNy)
100
101 C local copies of global variables
102 _RL tsurfLoc (1:sNx,1:sNy)
103 _RL atempLoc (1:sNx,1:sNy)
104 _RL lwdownLoc (1:sNx,1:sNy)
105 _RL ALB (1:sNx,1:sNy)
106 _RL ALB_ICE (1:sNx,1:sNy)
107 _RL ALB_SNOW (1:sNx,1:sNy)
108
109 C i, j :: Loop counters
110 C kSrf :: vertical index of surface layer
111 INTEGER i, j
112 #ifdef SEAICE_VARIABLE_FREEZING_POINT
113 INTEGER kSrf
114 #endif /* SEAICE_VARIABLE_FREEZING_POINT */
115 INTEGER ITER
116
117 C This is HICE_ACTUAL.GT.0.
118 LOGICAL iceOrNot(1:sNx,1:sNy)
119
120 C TB :: temperature in boundary layer (=freezing point temperature) (K)
121 _RL TB (1:sNx,1:sNy)
122 C
123 _RL D1, D1I, D3
124 _RL TMELT, XKI, XKS, HCUT, XIO
125 _RL SurfMeltTemp
126 C effective conductivity of combined ice and snow
127 _RL effConduct(1:sNx,1:sNy)
128
129 C Constants to calculate Saturation Vapor Pressure
130 #ifdef SEAICE_SOLVE4TEMP_LEGACY
131 _RL TMELTP, C1, C2, C3, C4, C5, QS1
132 _RL A2 (1:sNx,1:sNy)
133 _RL A3 (1:sNx,1:sNy)
134 c _RL B (1:sNx,1:sNy)
135 _RL A1 (1:sNx,1:sNy)
136 #else /* SEAICE_SOLVE4TEMP_LEGACY */
137 _RL dFiDTs1
138 _RL aa1,aa2,bb1,bb2,Ppascals,cc0,cc1,cc2,cc3t
139 C specific humidity at ice surface variables
140 _RL mm_pi,mm_log10pi,dqhice_dTice
141 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
142
143 C latent heat of sublimation for ice (SEAICE_lhEvap +
144 C SEAICE_lhFusion)
145 _RL lhSublim
146
147 C powers of temperature
148 _RL t1, t2, t3, t4
149 _RL lnTEN
150 CEOP
151
152 #ifdef ALLOW_AUTODIFF_TAMC
153 CADJ INIT comlev1_solve4temp = COMMON, sNx*sNy*NMAX_TICE
154 #endif /* ALLOW_AUTODIFF_TAMC */
155
156 lnTEN = log(10.0 _d 0)
157 #ifdef SEAICE_SOLVE4TEMP_LEGACY
158 C MAYKUTS CONSTANTS FOR SAT. VAP. PRESSURE TEMP. POLYNOMIAL
159 C1= 2.7798202 _d -06
160 C2= -2.6913393 _d -03
161 C3= 0.97920849 _d +00
162 C4= -158.63779 _d +00
163 C5= 9653.1925 _d +00
164
165 QS1=0.622 _d +00/1013.0 _d +00
166
167 #else /* SEAICE_SOLVE4TEMP_LEGACY */
168 aa1 = 2663.5 _d 0
169 aa2 = 12.537 _d 0
170 bb1 = 0.622 _d 0
171 bb2 = 1.0 _d 0 - bb1
172 Ppascals = 100000. _d 0
173 C cc0 = TEN ** aa2
174 cc0 = exp(aa2*lnTEN)
175 cc1 = cc0*aa1*bb1*Ppascals*lnTEN
176 cc2 = cc0*bb2
177 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
178
179 #ifdef SEAICE_VARIABLE_FREEZING_POINT
180 kSrf = 1
181 #endif /* SEAICE_VARIABLE_FREEZING_POINT */
182
183 C SENSIBLE HEAT CONSTANT
184 D1=SEAICE_dalton*SEAICE_cpAir*SEAICE_rhoAir
185
186 C ICE LATENT HEAT CONSTANT
187 lhSublim = SEAICE_lhEvap + SEAICE_lhFusion
188 D1I=SEAICE_dalton*lhSublim*SEAICE_rhoAir
189
190 C STEFAN BOLTZMAN CONSTANT TIMES 0.97 EMISSIVITY
191 D3=SEAICE_emissivity
192
193 C MELTING TEMPERATURE OF ICE
194 #ifdef SEAICE_SOLVE4TEMP_LEGACY
195 TMELT = 273.16 _d +00
196 TMELTP = 273.159 _d +00
197 SurfMeltTemp = TMELTP
198 #else /* SEAICE_SOLVE4TEMP_LEGACY */
199 TMELT = celsius2K
200 SurfMeltTemp = TMELT
201 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
202
203 C ICE CONDUCTIVITY
204 XKI=SEAICE_iceConduct
205
206 C SNOW CONDUCTIVITY
207 XKS=SEAICE_snowConduct
208
209 C CUTOFF SNOW THICKNESS
210 HCUT=SEAICE_snowThick
211
212 C PENETRATION SHORTWAVE RADIATION FACTOR
213 XIO=SEAICE_shortwave
214
215 C Initialize variables
216 DO J=1,sNy
217 DO I=1,sNx
218 C HICE_ACTUAL is modified in this routine, but at the same time
219 C used to decided where there is ice, therefore we save this information
220 C here in a separate array
221 iceOrNot (I,J) = HICE_ACTUAL(I,J) .GT. 0. _d 0
222 C
223 IcePenetSWFlux (I,J) = 0. _d 0
224 IcePenetSWFluxFrac (I,J) = 0. _d 0
225 AbsorbedSWFlux (I,J) = 0. _d 0
226
227 qhice (I,J) = 0. _d 0
228 F_ia (I,J) = 0. _d 0
229
230 F_io_net (I,J) = 0. _d 0
231 F_ia_net (I,J) = 0. _d 0
232
233 F_lh (I,J) = 0. _d 0
234
235 C Reset the snow/ice surface to TMELT and bound the atmospheric temperature
236 #ifdef SEAICE_SOLVE4TEMP_LEGACY
237 tsurfLoc (I,J) = MIN(273.16 _d 0 + MAX_TICE,TSURF(I,J,bi,bj))
238 atempLoc (I,J) = MAX(273.16 _d 0 + MIN_ATEMP,ATEMP(I,J,bi,bj))
239 A1(I,J) = 0.0 _d 0
240 A2(I,J) = 0.0 _d 0
241 A3(I,J) = 0.0 _d 0
242 c B(I,J) = 0.0 _d 0
243 lwdownLoc(I,J) = MAX(MIN_LWDOWN,LWDOWN(I,J,bi,bj))
244 #else /* SEAICE_SOLVE4TEMP_LEGACY */
245 F_swi (I,J) = 0. _d 0
246 F_lwd (I,J) = 0. _d 0
247 F_lwu (I,J) = 0. _d 0
248 F_sens (I,J) = 0. _d 0
249
250 tsurfLoc (I,J) = TSURF(I,J,bi,bj)
251 atempLoc (I,J) = MAX(TMELT + MIN_ATEMP,ATEMP(I,J,bi,bj))
252 lwdownLoc(I,J) = LWDOWN(I,J,bi,bj)
253 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
254
255 C FREEZING TEMPERATURE OF SEAWATER
256 #ifdef SEAICE_VARIABLE_FREEZING_POINT
257 C Use a variable seawater freezing point
258 TB(I,J) = -0.0575 _d 0*salt(I,J,kSrf,bi,bj) + 0.0901 _d 0
259 & + celsius2K
260 #else
261 C Use a constant freezing temperature (SEAICE_VARIABLE_FREEZING_POINT undef)
262 #ifdef SEAICE_SOLVE4TEMP_LEGACY
263 TB(I,J) = 271.2 _d 0
264 #else /* SEAICE_SOLVE4TEMP_LEGACY */
265 TB(I,J) = celsius2K + SEAICE_freeze
266 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
267 #endif /* SEAICE_VARIABLE_FREEZING_POINT */
268 ENDDO
269 ENDDO
270
271 DO J=1,sNy
272 DO I=1,sNx
273
274 C DECIDE ON ALBEDO
275 IF ( iceOrNot(I,J) ) THEN
276
277 IF ( YC(I,J,bi,bj) .LT. 0.0 _d 0 ) THEN
278 IF (tsurfLoc(I,J) .GE. SurfMeltTemp) THEN
279 ALB_ICE (I,J) = SEAICE_wetIceAlb_south
280 ALB_SNOW(I,J) = SEAICE_wetSnowAlb_south
281 ELSE ! no surface melting
282 ALB_ICE (I,J) = SEAICE_dryIceAlb_south
283 ALB_SNOW(I,J) = SEAICE_drySnowAlb_south
284 ENDIF
285 ELSE !/ Northern Hemisphere
286 IF (tsurfLoc(I,J) .GE. SurfMeltTemp) THEN
287 ALB_ICE (I,J) = SEAICE_wetIceAlb
288 ALB_SNOW(I,J) = SEAICE_wetSnowAlb
289 ELSE ! no surface melting
290 ALB_ICE (I,J) = SEAICE_dryIceAlb
291 ALB_SNOW(I,J) = SEAICE_drySnowAlb
292 ENDIF
293 ENDIF !/ Albedo for snow and ice
294
295 #ifdef SEAICE_SOLVE4TEMP_LEGACY
296 C If actual snow thickness exceeds the cutoff thickness, use the
297 C snow albedo
298 IF (HSNOW_ACTUAL(I,J) .GT. HCUT) THEN
299 ALB(I,J) = ALB_SNOW(I,J)
300
301 C otherwise, use some combination of ice and snow albedo
302 C (What is the source of this formulation ?)
303 ELSE
304 ALB(I,J) = MIN(ALB_ICE(I,J) + HSNOW_ACTUAL(I,J)/HCUT*
305 & (ALB_SNOW(I,J) -ALB_ICE(I,J)),
306 & ALB_SNOW(I,J))
307 ENDIF
308
309 #else /* SEAICE_SOLVE4TEMP_LEGACY */
310 IF (HSNOW_ACTUAL(I,J) .GT. 0.0 _d 0) THEN
311 ALB(I,J) = ALB_SNOW(I,J)
312 ELSE
313 ALB(I,J) = ALB_ICE(I,J)
314 ENDIF
315 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
316
317 #ifdef SEAICE_SOLVE4TEMP_LEGACY
318 C NOW DETERMINE FIXED FORCING TERM IN HEAT BUDGET
319
320 #ifdef ALLOW_DOWNWARD_RADIATION
321 IF(HSNOW_ACTUAL(I,J).GT.0.0) THEN
322 C NO SW PENETRATION WITH SNOW
323 A1(I,J)=(1.0 _d 0 - ALB(I,J))*SWDOWN(I,J,bi,bj)
324 & +lwdownLoc(I,J)*0.97 _d 0
325 & +D1*UG(I,J)*atempLoc(I,J)+D1I*UG(I,J)*AQH(I,J,bi,bj)
326 ELSE
327 C SW PENETRATION UNDER ICE
328 A1(I,J)=(1.0 _d 0 - ALB(I,J))*SWDOWN(I,J,bi,bj)
329 & *(1.0 _d 0 - XIO*EXP(-1.5 _d 0*HICE_ACTUAL(I,J)))
330 & +lwdownLoc(I,J)*0.97 _d 0
331 & +D1*UG(I,J)*atempLoc(I,J)+D1I*UG(I,J)*AQH(I,J,bi,bj)
332 ENDIF
333 #endif /* ALLOW_DOWNWARD_RADIATION */
334
335 #else /* SEAICE_SOLVE4TEMP_LEGACY */
336
337 C The longwave radiative flux convergence
338 F_lwd(I,J) = - 0.97 _d 0 * lwdownLoc(I,J)
339
340 C Determine the fraction of shortwave radiative flux
341 C remaining after scattering through the snow and ice at
342 C the ocean interface. If snow is present, no radiation
343 C penetrates to the ocean.
344 IF (HSNOW_ACTUAL(I,J) .GT. 0.0 _d 0) THEN
345 IcePenetSWFluxFrac(I,J) = 0.0 _d 0
346 ELSE
347 IcePenetSWFluxFrac(I,J) =
348 & XIO*EXP(-1.5 _d 0 * HICE_ACTUAL(I,J))
349 ENDIF
350
351 C The shortwave radiative flux convergence in the
352 C seaice.
353 AbsorbedSWFlux(I,J) = -(1.0 _d 0 - ALB(I,J))*
354 & (1.0 _d 0 - IcePenetSWFluxFrac(I,J))
355 & *SWDOWN(I,J,bi,bj)
356
357 C The shortwave radiative flux convergence in the
358 C ocean beneath ice.
359 IcePenetSWFlux(I,J) = -(1.0 _d 0 - ALB(I,J))*
360 & IcePenetSWFluxFrac(I,J)
361 & *SWDOWN(I,J,bi,bj)
362
363 F_swi(I,J) = AbsorbedSWFlux(I,J)
364
365 C Set a mininum sea ice thickness of 5 cm to bound
366 C the magnitude of conductive heat fluxes.
367 cif * now taken care of by SEAICE_hice_reg in seaice_growth
368 C hice_tmp = max(HICE_ACTUAL(I,J),5. _d -2)
369
370 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
371
372 C The effective conductivity of the two-layer
373 C snow/ice system.
374 #ifdef SEAICE_SOLVE4TEMP_LEGACY
375 effConduct(I,J)=
376 & XKS/(HSNOW_ACTUAL(I,J)/HICE_ACTUAL(I,J) +
377 & XKS/XKI)/HICE_ACTUAL(I,J)
378 #else /* SEAICE_SOLVE4TEMP_LEGACY */
379 effConduct(I,J) = XKI * XKS /
380 & (XKS * HICE_ACTUAL(I,j) + XKI * HSNOW_ACTUAL(I,J))
381 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
382
383 #ifdef SEAICE_DEBUG
384 IF ( (I .EQ. SEAICE_debugPointI) .and.
385 & (J .EQ. SEAICE_debugPointJ) ) THEN
386
387 print '(A,i6)','-----------------------------------'
388 print '(A,i6)','ibi merged initialization ', myIter
389
390 print '(A,i6,4(1x,D24.15))',
391 & 'ibi iter, TSL, TS ',myIter,
392 & tsurfLoc(I,J), TSURF(I,J,bi,bj)
393
394 print '(A,i6,4(1x,D24.15))',
395 & 'ibi iter, TMELT ',myIter,TMELT
396
397 print '(A,i6,4(1x,D24.15))',
398 & 'ibi iter, HIA, EFKCON ',myIter,
399 & HICE_ACTUAL(I,J), effConduct(I,J)
400
401 print '(A,i6,4(1x,D24.15))',
402 & 'ibi iter, HSNOW ',myIter,
403 & HSNOW_ACTUAL(I,J), ALB(I,J)
404
405 print '(A,i6)','-----------------------------------'
406 print '(A,i6)','ibi energy balance iterat ', myIter
407
408 ENDIF
409 #endif /* SEAICE_DEBUG */
410
411 ENDIF !/* iceOrNot */
412 ENDDO !/* i */
413 ENDDO !/* j */
414 Ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
415 DO ITER=1,IMAX_TICE
416 DO J=1,sNy
417 DO I=1,sNx
418 #ifdef ALLOW_AUTODIFF_TAMC
419 iicekey = I + sNx*(J-1) + (ITER-1)*sNx*sNy
420 CADJ STORE tsurfloc(i,j) = comlev1_solve4temp,
421 CADJ & key = iicekey, byte = isbyte
422 #endif /* ALLOW_AUTODIFF_TAMC */
423
424 IF ( iceOrNot(I,J) ) THEN
425
426 t1 = tsurfLoc(I,J)
427 t2 = t1*t1
428 t3 = t2*t1
429 t4 = t2*t2
430
431 C Calculate the specific humidity in the BL above the snow/ice
432 #ifdef SEAICE_SOLVE4TEMP_LEGACY
433 C Use the Maykut polynomial
434 qhice(I,J)=QS1*(C1*t4+C2*t3 +C3*t2+C4*t1+C5)
435
436 #else /* SEAICE_SOLVE4TEMP_LEGACY */
437 C Use an approximation which is more accurate at low temperatures
438
439 C log 10 of the sat vap pressure
440 mm_log10pi = -aa1 / t1 + aa2
441
442 C The saturation vapor pressure (SVP) in the surface
443 C boundary layer (BL) above the snow/ice.
444 C mm_pi = TEN **(mm_log10pi)
445 C The following form does the same, but is faster
446 mm_pi = exp(mm_log10pi*lnTEN)
447
448 qhice(I,J) = bb1*mm_pi / (Ppascals - (1.0 _d 0 - bb1) *
449 & mm_pi)
450 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
451
452 C Calculate the flux terms based on the updated tsurfLoc
453 F_c(I,J) = -effConduct(I,J)*(TB(I,J)-tsurfLoc(I,J))
454 F_lh(I,J) = D1I*UG(I,J)*(qhice(I,J)-AQH(I,J,bi,bj))
455 #ifdef SEAICE_SOLVE4TEMP_LEGACY
456 A2(I,J)=-D1*UG(I,J)*t1-D1I*UG(I,J)*qhice(I,J)-D3*t4
457 A3(I,J) = 4.0 _d 0 * D3 * t3 + effConduct(I,J) + D1*UG(I,J)
458 #else /* SEAICE_SOLVE4TEMP_LEGACY */
459 C A constant for SVP derivative w.r.t TICE
460 C cc3t = TEN **(aa1 / t1)
461 C The following form does the same, but is faster
462 cc3t = exp(aa1 / t1 * lnTEN)
463
464 c d(qh)/d(TICE)
465 dqhice_dTice = cc1*cc3t/((cc2-cc3t*Ppascals)**2 *t2)
466
467 #ifdef SEAICE_ADD_SUBLIMATION_TO_FWBUDGET
468 c if the latent heat flux implied by tsurfLoc exceeds
469 c F_lh_max, cap F_lh and decouple the flux magnitude from TICE
470 if (F_lh(I,J) .GT. F_lh_max(I,J)) THEN
471 F_lh(I,J) = F_lh_max(I,J)
472 dqhice_dTice = ZERO
473 endif
474 #endif
475
476
477 c d(F_ia)/d(TICE)
478 dFiDTs1 = 4.0 _d 0 * D3*t3 + effConduct(I,J) + D1*UG(I,J)
479 & + D1I*UG(I,J)*dqhice_dTice
480
481 F_lwu(I,J)= t4 * D3
482
483 F_sens(I,J)= D1 * UG(I,J) * (t1 - atempLoc(I,J))
484
485 F_ia(I,J) = F_lwd(I,J) + F_swi(I,J) + F_lwu(I,J) +
486 & F_c(I,J) + F_sens(I,J) + F_lh(I,J)
487
488 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
489
490 #ifdef SEAICE_DEBUG
491 IF ( (I .EQ. SEAICE_debugPointI) .and.
492 & (J .EQ. SEAICE_debugPointJ) ) THEN
493 print '(A,i6,4(1x,D24.15))',
494 & 'ice-iter qhICE, ', ITER,qhIce(I,J)
495
496 #ifdef SEAICE_SOLVE4TEMP_LEGACY
497 print '(A,i6,4(1x,D24.15))',
498 & 'ice-iter A1 A2 B ', ITER,A1(I,J), A2(I,J),
499 & -F_c(I,J)
500
501 print '(A,i6,4(1x,D24.15))',
502 & 'ice-iter A3 (-A1+A2) ', ITER, A3(I,J),
503 & -(A1(I,J) + A2(I,J))
504 #else /* SEAICE_SOLVE4TEMP_LEGACY */
505
506 print '(A,i6,4(1x,D24.15))',
507 & 'ice-iter dFiDTs1 F_ia ', ITER, dFiDTs1,
508 & F_ia(I,J)
509 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
510
511 ENDIF
512 #endif /* SEAICE_DEBUG */
513
514 C Update tsurfLoc
515 #ifdef SEAICE_SOLVE4TEMP_LEGACY
516 tsurfLoc(I,J)=tsurfLoc(I,J)
517 & +(A1(I,J)+A2(I,J)-F_c(I,J))/A3(I,J)
518
519 tsurfLoc(I,J) =MAX(273.16 _d 0+MIN_TICE,tsurfLoc(I,J))
520 tsurfLoc(I,J) =MIN(tsurfLoc(I,J),TMELT)
521
522 #else /* SEAICE_SOLVE4TEMP_LEGACY */
523 tsurfLoc(I,J) = tsurfLoc(I,J) - F_ia(I,J) / dFiDTs1
524
525 C If the search leads to tsurfLoc < 50 Kelvin,
526 C restart the search at tsurfLoc = TMELT. Note that one
527 C solution to the energy balance problem is an
528 C extremely low temperature - a temperature far below
529 C realistic values.
530
531 IF (tsurfLoc(I,J) .LT. 50.0 _d 0 ) THEN
532 tsurfLoc(I,J) = TMELT
533 ENDIF
534 tsurfLoc(I,J) =MIN(tsurfLoc(I,J),TMELT)
535 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
536
537 #ifdef SEAICE_DEBUG
538 IF ( (I .EQ. SEAICE_debugPointI) .and.
539 & (J .EQ. SEAICE_debugPointJ) ) THEN
540
541 print '(A,i6,4(1x,D24.15))',
542 & 'ice-iter tsurfLc,|dif|', ITER,
543 & tsurfLoc(I,J),
544 & log10(abs(tsurfLoc(I,J) - t1))
545 ENDIF
546 #endif /* SEAICE_DEBUG */
547
548 ENDIF !/* iceOrNot */
549 ENDDO !/* i */
550 ENDDO !/* j */
551 ENDDO !/* Iterations */
552 Ccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
553 DO J=1,sNy
554 DO I=1,sNx
555 IF ( iceOrNot(I,J) ) THEN
556
557 C Finalize the flux terms
558 #ifdef SEAICE_SOLVE4TEMP_LEGACY
559 F_ia(I,J)=-A1(I,J)-A2(I,J)
560 TSURF(I,J,bi,bj)=MIN(tsurfLoc(I,J),TMELT)
561
562 IF (HSNOW_ACTUAL(I,J) .GT. 0.0 _d 0 ) THEN
563 C NO SW PENETRATION WITH SNOW
564 IcePenetSWFlux(I,J)=0.0 _d 0
565 ELSE
566 C SW PENETRATION UNDER ICE
567
568 #ifdef ALLOW_DOWNWARD_RADIATION
569 IcePenetSWFlux(I,J)=-(1.0 _d 0 -ALB(I,J))*SWDOWN(I,J,bi,bj)
570 & *XIO*EXP(-1.5 _d 0*HICE_ACTUAL(I,J))
571 #endif /* ALLOW_DOWNWARD_RADIATION */
572 ENDIF
573
574 #else /* SEAICE_SOLVE4TEMP_LEGACY */
575 TSURF(I,J,bi,bj) = tsurfLoc(I,J)
576
577 C Recalculate the fluxes based on the (possibly) adjusted TSURF
578 t1 = tsurfLoc(I,J)
579 t2 = t1*t1
580 t3 = t2*t1
581 t4 = t2*t2
582
583 C log 10 of the sat vap pressure
584 mm_log10pi = -aa1 / t1 + aa2
585
586 C saturation vapor pressure
587 C mm_pi = TEN **(mm_log10pi)
588 C The following form does the same, but is faster
589 mm_pi = exp(mm_log10pi*lnTEN)
590
591 C over ice specific humidity
592 qhice(I,J) = bb1*mm_pi/(Ppascals- (1.0 _d 0 - bb1) * mm_pi)
593
594 F_lh(I,J) = D1I * UG(I,J)*(qhice(I,J)-AQH(I,J,bi,bj))
595
596 #ifdef SEAICE_ADD_SUBLIMATION_TO_FWBUDGET
597 if (F_lh(I,J) .GT. F_lh_max(I,J)) THEN
598 F_lh(I,J) = F_lh_max(I,J)
599 endif
600 #endif
601
602 F_c(I,J) = -effConduct(I,J) * (TB(I,J) - t1)
603 F_lwu(I,J) = t4 * D3
604 F_sens(I,J) = D1 * UG(I,J) * (t1 - atempLoc(I,J))
605
606 C The flux between the ice/snow surface and the atmosphere.
607 C (excludes upward conductive fluxes)
608 F_ia(I,J) = F_lwd(I,J) + F_swi(I,J) + F_lwu(I,J) +
609 & F_sens(I,J) + F_lh(I,J)
610 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
611
612 #ifdef SEAICE_MODIFY_GROWTH_ADJ
613 Cgf no additional dependency through solver, snow, etc.
614 if ( SEAICEadjMODE.GE.2 ) then
615 CALL ZERO_ADJ_1D( 1, TSURF(I,J,bi,bj), myThid)
616 t1 = TSURF(I,J,bi,bj)
617 t2 = t1*t1
618 t3 = t2*t1
619 t4 = t2*t2
620 qhice(I,J)=QS1*(C1*t4+C2*t3 +C3*t2+C4*t1+C5)
621
622 A1(I,J)=0.3 _d 0 *SWDOWN(I,J,bi,bj)+lwdownLoc(I,J)*0.97 _d 0
623 & +D1*UG(I,J)*atempLoc(I,J)+D1I*UG(I,J)*AQH(I,J,bi,bj)
624 A2(I,J)=-D1*UG(I,J)*t1-D1I*UG(I,J)*qhice(I,J)-D3*t4
625
626 F_ia(I,J)=-A1(I,J)-A2(I,J)
627 IcePenetSWFlux(I,J)= 0. _d 0
628 endif
629 #endif
630
631 C Caclulate the net ice-ocean and ice-atmosphere fluxes
632 IF (F_c(I,J) .LT. 0.0 _d 0) THEN
633 F_io_net(I,J) = -F_c(I,J)
634 F_ia_net(I,J) = 0.0 _d 0
635 ELSE
636 F_io_net(I,J) = 0.0 _d 0
637 F_ia_net(I,J) = F_ia(I,J)
638 ENDIF !/* conductive fluxes up or down */
639 C Fresh water flux (kg/m^2/s) from latent heat of sublimation.
640 C F_lh is positive upward (sea ice looses heat) and FWsublim
641 C is also positive upward (atmosphere gains freshwater)
642 FWsublim(I,J) = F_lh(I,J)/lhSublim
643
644 #ifdef SEAICE_DEBUG
645 IF ( (I .EQ. SEAICE_debugPointI) .and.
646 & (J .EQ. SEAICE_debugPointJ) ) THEN
647
648 print '(A)','----------------------------------------'
649 print '(A,i6)','ibi complete ', myIter
650
651 print '(A,4(1x,D24.15))',
652 & 'ibi T(SURF, surfLoc,atmos) ',
653 & TSURF(I,J,bi,bj), tsurfLoc(I,J),atempLoc(I,J)
654
655 print '(A,4(1x,D24.15))',
656 & 'ibi LWL ', lwdownLoc(I,J)
657
658 print '(A,4(1x,D24.15))',
659 & 'ibi QSW(Total, Penetrating)',
660 & SWDOWN(I,J,bi,bj), IcePenetSWFlux(I,J)
661
662 print '(A,4(1x,D24.15))',
663 & 'ibi qh(ATM ICE) ',
664 & AQH(I,J,bi,bj),qhice(I,J)
665
666 #ifndef SEAICE_SOLVE4TEMP_LEGACY
667 print '(A,4(1x,D24.15))',
668 & 'ibi F(lwd,swi,lwu) ',
669 & F_lwd(I,J), F_swi(I,J), F_lwu(I,J)
670
671 print '(A,4(1x,D24.15))',
672 & 'ibi F(c,lh,sens) ',
673 & F_c(I,J), F_lh(I,J), F_sens(I,J)
674
675 #ifdef SEAICE_ADD_SUBLIMATION_TO_FWBUDGET
676 IF (F_lh_max(I,J) .GT. ZERO) THEN
677 print '(A,4(1x,D24.15))',
678 & 'ibi F_lh_max, F_lh/lhmax) ',
679 & F_lh_max(I,J), F_lh(I,J)/ F_lh_max(I,J)
680 ELSE
681 print '(A,4(1x,D24.15))',
682 & 'ibi F_lh_max = ZERO! '
683 ENDIF
684
685 print '(A,4(1x,D24.15))',
686 & 'ibi FWsub, FWsubm*dT/rhoI ',
687 & FWsublim(I,J),
688 & FWsublim(I,J)*SEAICE_deltaTtherm/SEAICE_rhoICE
689 #endif
690 #endif
691
692 print '(A,4(1x,D24.15))',
693 & 'ibi F_ia, F_ia_net, F_c ',
694 #ifdef SEAICE_SOLVE4TEMP_LEGACY
695 & -(A1(I,J)+A2(I,J)),
696 & -(A1(I,J)+A2(I,J)-F_c(I,J)),
697 & F_c(I,J)
698 #else /* SEAICE_SOLVE4TEMP_LEGACY */
699 & F_ia(I,J),
700 & F_ia_net(I,J),
701 & F_c(I,J)
702 #endif /* SEAICE_SOLVE4TEMP_LEGACY */
703
704 print '(A)','----------------------------------------'
705
706 ENDIF
707 #endif /* SEAICE_DEBUG */
708
709 ENDIF !/* iceOrNot */
710 ENDDO !/* i */
711 ENDDO !/* j */
712
713 RETURN
714 END

  ViewVC Help
Powered by ViewVC 1.1.22