/[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.18 - (show annotations) (download)
Thu Dec 22 12:35:02 2011 UTC (12 years, 5 months ago) by mlosch
Branch: MAIN
Changes since 1.17: +32 -16 lines
the exf-flag EXF_LWDOWN_WITH_EMISSIVITY now gets rid off the
hard-wired emissivities of 0.97 associated with lwdownloc until we
agree on how to handle this bug properly, but I need a solution now.

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

  ViewVC Help
Powered by ViewVC 1.1.22