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

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

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


Revision 1.29 - (show annotations) (download)
Fri Dec 17 04:00:14 2010 UTC (13 years, 4 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.28: +15 -15 lines
rename iicekey as ticekey to avoid conflict with pkg/seaice

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_solve4temp.F,v 1.28 2010/10/26 22:26:59 heimbach Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: THSICE_SOLVE4TEMP
8 C !INTERFACE:
9 SUBROUTINE THSICE_SOLVE4TEMP(
10 I bi, bj,
11 I iMin,iMax, jMin,jMax, dBugFlag,
12 I useBulkForce, useEXF,
13 I iceMask, hIce, hSnow, tFrz, flxExSW,
14 U flxSW, tSrf, qIc1, qIc2,
15 O tIc1, tIc2, dTsrf,
16 O sHeat, flxCnB, flxAtm, evpAtm,
17 I myTime, myIter, myThid )
18 C !DESCRIPTION: \bv
19 C *==========================================================*
20 C | S/R THSICE_SOLVE4TEMP
21 C *==========================================================*
22 C | Solve (implicitly) for sea-ice and surface temperature
23 C *==========================================================*
24 C \ev
25
26 C ADAPTED FROM:
27 C LANL CICE.v2.0.2
28 C-----------------------------------------------------------------------
29 C.. thermodynamics (vertical physics) based on M. Winton 3-layer model
30 C.. See Bitz, C. M. and W. H. Lipscomb, 1999: An energy-conserving
31 C.. thermodynamic sea ice model for climate study.
32 C.. J. Geophys. Res., 104, 15669 - 15677.
33 C.. Winton, M., 1999: "A reformulated three-layer sea ice model."
34 C.. Submitted to J. Atmos. Ocean. Technol.
35 C.. authors Elizabeth C. Hunke and William Lipscomb
36 C.. Fluid Dynamics Group, Los Alamos National Laboratory
37 C-----------------------------------------------------------------------
38 Cc****subroutine thermo_winton(n,fice,fsnow,dqice,dTsfc)
39 C.. Compute temperature change using Winton model with 2 ice layers, of
40 C.. which only the top layer has a variable heat capacity.
41
42 C !USES:
43 IMPLICIT NONE
44
45 C == Global variables ===
46 #include "EEPARAMS.h"
47 #include "SIZE.h"
48 #include "THSICE_SIZE.h"
49 #include "THSICE_PARAMS.h"
50 #ifdef ALLOW_AUTODIFF_TAMC
51 # include "tamc.h"
52 # include "tamc_keys.h"
53 #endif
54
55 C !INPUT/OUTPUT PARAMETERS:
56 C == Routine Arguments ==
57 C bi,bj :: tile indices
58 C iMin,iMax :: computation domain: 1rst index range
59 C jMin,jMax :: computation domain: 2nd index range
60 C dBugFlag :: allow to print debugging stuff (e.g. on 1 grid point).
61 C useBulkForce:: use surf. fluxes from bulk-forcing external S/R
62 C useEXF :: use surf. fluxes from exf external S/R
63 C--- Input:
64 C iceMask :: sea-ice fractional mask [0-1]
65 C hIce :: ice height [m]
66 C hSnow :: snow height [m]
67 C tFrz :: sea-water freezing temperature [oC] (function of S)
68 C flxExSW :: surf. heat flux (+=down) except SW, function of surf. temp Ts:
69 C 0: Flx(Ts=0) ; 1: Flx(Ts=Ts^n) ; 2: d.Flx/dTs(Ts=Ts^n)
70 C--- Modified (input&output):
71 C flxSW :: net Short-Wave flux (+=down) [W/m2]: input= at surface
72 C :: output= below sea-ice, into the ocean
73 C tSrf :: surface (ice or snow) temperature
74 C qIc1 :: ice enthalpy (J/kg), 1rst level
75 C qIc2 :: ice enthalpy (J/kg), 2nd level
76 C--- Output
77 C tIc1 :: temperature of ice layer 1 [oC]
78 C tIc2 :: temperature of ice layer 2 [oC]
79 C dTsrf :: surf. temp adjusment: Ts^n+1 - Ts^n
80 C sHeat :: surf heating flux left to melt snow or ice (= Atmos-conduction)
81 C flxCnB :: heat flux conducted through the ice to bottom surface
82 C flxAtm :: net flux of energy from the atmosphere [W/m2] (+=down)
83 C without snow precip. (energy=0 for liquid water at 0.oC)
84 C evpAtm :: evaporation to the atmosphere [kg/m2/s] (>0 if evaporate)
85 C--- Input:
86 C myTime :: current Time of simulation [s]
87 C myIter :: current Iteration number in simulation
88 C myThid :: my Thread Id number
89 INTEGER bi,bj
90 INTEGER iMin, iMax
91 INTEGER jMin, jMax
92 LOGICAL dBugFlag
93 LOGICAL useBulkForce
94 LOGICAL useEXF
95 _RL iceMask(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
96 _RL hIce (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
97 _RL hSnow (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98 _RL tFrz (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
99 _RL flxExSW(iMin:iMax,jMin:jMax,0:2)
100 _RL flxSW (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
101 _RL tSrf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
102 _RL qIc1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
103 _RL qIc2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
104 _RL tIc1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
105 _RL tIc2 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
106 _RL dTsrf (iMin:iMax,jMin:jMax)
107 _RL sHeat (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
108 _RL flxCnB (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
109 _RL flxAtm (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
110 _RL evpAtm (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
111 _RL myTime
112 INTEGER myIter
113 INTEGER myThid
114 CEOP
115
116 #ifdef ALLOW_THSICE
117 C !LOCAL VARIABLES:
118 C == Local Variables ==
119 C useBlkFlx :: use some bulk-formulae to compute fluxes over sea-ice
120 C :: (otherwise, fluxes are passed as argument from AIM)
121 C iterate4Tsf :: to stop to iterate when all icy grid pts Tsf did converged
122 C iceFlag :: True= do iterate for Surf.Temp ; False= do nothing
123 C frsnow :: fractional snow cover
124 C fswpen :: SW penetrating beneath surface (W m-2)
125 C fswdn :: SW absorbed at surface (W m-2)
126 C fswint :: SW absorbed in ice (W m-2)
127 C fswocn :: SW passed through ice to ocean (W m-2)
128 C Tsf :: surface (ice or snow) temperature (local copy of tSrf)
129 C flx0exSW :: net surface heat flux over melting snow/ice, except short-wave.
130 C flxTexSW :: net surface heat flux, except short-wave (W/m2)
131 C dFlxdT :: deriv of flxNet wrt Tsf (W m-2 deg-1)
132 C evap0 :: evaporation over melting snow/ice [kg/m2/s] (>0 if evaporate)
133 C evapT :: evaporation over snow/ice [kg/m2/s] (>0 if evaporate)
134 C dEvdT :: derivative of evap. with respect to Tsf [kg/m2/s/K]
135 C flxNet :: net surf heat flux (+=down), from Atmos. to sea-ice (W m-2)
136 C netSW :: net Short-Wave flux at surface (+=down) [W/m2]
137 C fct :: heat conducted to top surface
138 C k12, k32 :: thermal conductivity terms
139 C a10,b10,c10 :: coefficients in quadratic eqn for T1
140 C a1, b1, c1 :: coefficients in quadratic eqn for T1
141 C dt :: timestep
142 LOGICAL useBlkFlx
143 LOGICAL iterate4Tsf
144 LOGICAL iceFlag(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
145 INTEGER i, j, k, iterMax
146 INTEGER ii, jj, icount, stdUnit
147 CHARACTER*(MAX_LEN_MBUF) msgBuf
148 _RL frsnow
149 _RL fswpen
150 _RL fswdn
151 _RL fswint
152 _RL fswocn
153 _RL Tsf (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
154 _RL flx0exSW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
155 _RL flxTexSW(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
156 _RL dFlxdT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
157 _RL evap0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
158 _RL evapT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
159 _RL dEvdT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
160 _RL flxNet
161 _RL fct
162 _RL k12 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
163 _RL k32
164 _RL a10 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
165 _RL b10 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
166 _RL c10 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
167 _RL a1, b1, c1
168 _RL dt
169 _RL recip_dhSnowLin
170 #ifdef ALLOW_DBUG_THSICE
171 _RL netSW
172 #endif
173
174 C- Define grid-point location where to print debugging values
175 #include "THSICE_DEBUG.h"
176
177 1010 FORMAT(A,I3,3F11.6)
178 1020 FORMAT(A,1P4E14.6)
179
180 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|
181
182 #ifdef ALLOW_AUTODIFF_TAMC
183 act1 = bi - myBxLo(myThid)
184 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
185 act2 = bj - myByLo(myThid)
186 max2 = myByHi(myThid) - myByLo(myThid) + 1
187 act3 = myThid - 1
188 max3 = nTx*nTy
189 act4 = ikey_dynamics - 1
190 ticekey = (act1 + 1) + act2*max1
191 & + act3*max1*max2
192 & + act4*max1*max2*max3
193 #endif /* ALLOW_AUTODIFF_TAMC */
194
195 #ifdef ALLOW_AUTODIFF_TAMC
196 CADJ STORE flxsw(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
197 DO j = 1-OLy, sNy+OLy
198 DO i = 1-OLx, sNx+OLx
199 tIc1(i,j) = 0. _d 0
200 tIc2(i,j) = 0. _d 0
201 ENDDO
202 ENDDO
203 #endif
204
205 stdUnit = standardMessageUnit
206 useBlkFlx = useEXF .OR. useBulkForce
207 dt = thSIce_dtTemp
208 IF ( dhSnowLin.GT.0. _d 0 ) THEN
209 recip_dhSnowLin = 1. _d 0 / dhSnowLin
210 ELSE
211 recip_dhSnowLin = 0. _d 0
212 ENDIF
213
214 iterate4Tsf = .FALSE.
215 icount = 0
216
217 DO j = jMin, jMax
218 DO i = iMin, iMax
219 #ifdef ALLOW_AUTODIFF_TAMC
220 c ikey_1 = i
221 c & + sNx*(j-1)
222 c & + sNx*sNy*act1
223 c & + sNx*sNy*max1*act2
224 c & + sNx*sNy*max1*max2*act3
225 c & + sNx*sNy*max1*max2*max3*act4
226 #endif /* ALLOW_AUTODIFF_TAMC */
227 #ifdef ALLOW_AUTODIFF_TAMC
228 cCADJ STORE devdt(i,j) = comlev1_thsice_1, key=ikey_1
229 cCADJ STORE dFlxdT(i,j) = comlev1_thsice_1, key=ikey_1
230 cCADJ STORE flxsw(i,j) = comlev1_thsice_1, key=ikey_1
231 cCADJ STORE qic1(i,j) = comlev1_thsice_1, key=ikey_1
232 cCADJ STORE qic2(i,j) = comlev1_thsice_1, key=ikey_1
233 cCADJ STORE tsrf(i,j) = comlev1_thsice_1, key=ikey_1
234 #endif
235 IF ( iceMask(i,j).GT.0. _d 0) THEN
236 iterate4Tsf = .TRUE.
237 iceFlag(i,j) = .TRUE.
238 #ifdef ALLOW_DBUG_THSICE
239 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,'(A,2I4,2I2)')
240 & 'ThSI_SOLVE4T: i,j=',i,j,bi,bj
241 #endif
242 IF ( hIce(i,j).LT.hIceMin ) THEN
243 C if hi < hIceMin, melt the ice.
244 C keep the position of this problem but do the stop later
245 ii = i
246 jj = j
247 icount = icount + 1
248 ENDIF
249
250 C-- Fractional snow cover:
251 C assume a linear distribution of snow thickness, with dhSnowLin slope,
252 C from hs-dhSnowLin to hs+dhSnowLin if full ice & snow cover.
253 C frsnow = fraction of snow over the ice-covered part of the grid cell
254 IF ( hSnow(i,j) .GT. iceMask(i,j)*dhSnowLin ) THEN
255 frsnow = 1. _d 0
256 ELSE
257 frsnow = hSnow(i,j)*recip_dhSnowLin/iceMask(i,j)
258 IF ( frsnow.GT.0. _d 0 ) frsnow = SQRT(frsnow)
259 ENDIF
260
261 C-- Compute SW flux absorbed at surface and penetrating to layer 1.
262 fswpen = flxSW(i,j) * (1. _d 0 - frsnow) * i0swFrac
263 fswocn = fswpen * exp(-ksolar*hIce(i,j))
264 fswint = fswpen - fswocn
265 fswdn = flxSW(i,j) - fswpen
266
267 C Initialise Atmospheric surf. heat flux with net SW flux at the surface
268 flxAtm(i,j) = flxSW(i,j)
269 C SW flux at sea-ice base left to the ocean
270 flxSW(i,j) = fswocn
271 C Initialise surface Heating with SW contribution
272 sHeat(i,j) = fswdn
273
274 C-- Compute conductivity terms at layer interfaces.
275 k12(i,j) = 4. _d 0*kIce*kSnow
276 & / (kSnow*hIce(i,j) + 4. _d 0*kIce*hSnow(i,j))
277 k32 = 2. _d 0*kIce / hIce(i,j)
278
279 C-- Compute ice temperatures
280 a1 = cpIce
281 b1 = qIc1(i,j) + (cpWater-cpIce )*Tmlt1 - Lfresh
282 c1 = Lfresh * Tmlt1
283 tIc1(i,j) = 0.5 _d 0 *(-b1 - SQRT(b1*b1-4. _d 0*a1*c1))/a1
284 tIc2(i,j) = (Lfresh-qIc2(i,j)) / cpIce
285
286 #ifdef ALLOW_DBUG_THSICE
287 IF (tIc1(i,j).GT.0. _d 0 ) THEN
288 WRITE(stdUnit,'(A,I12,1PE14.6)')
289 & ' BBerr: Tice(1) > 0 ; it=', myIter, qIc1(i,j)
290 WRITE(stdUnit,'(A,4I5,2F11.4)')
291 & ' BBerr: i,j,bi,bj,Tice = ',i,j,bi,bj,tIc1(i,j),tIc2(i,j)
292 ENDIF
293 IF ( tIc2(i,j).GT.0. _d 0) THEN
294 WRITE(stdUnit,'(A,I12,1PE14.6)')
295 & ' BBerr: Tice(2) > 0 ; it=', myIter, qIc2(i,j)
296 WRITE(stdUnit,'(A,4I5,2F11.4)')
297 & ' BBerr: i,j,bi,bj,Tice = ',i,j,bi,bj,tIc1(i,j),tIc2(i,j)
298 ENDIF
299 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,1010)
300 & 'ThSI_SOLVE4T: k, Ts, Tice=',0,tSrf(i,j),tIc1(i,j),tIc2(i,j)
301 #endif
302
303 C-- Compute coefficients used in quadratic formula.
304
305 a10(i,j) = rhoi*cpIce *hIce(i,j)/(2. _d 0*dt) +
306 & k32*( 4. _d 0*dt*k32 + rhoi*cpIce *hIce(i,j) )
307 & / ( 6. _d 0*dt*k32 + rhoi*cpIce *hIce(i,j) )
308 b10(i,j) = -hIce(i,j)*
309 & ( rhoi*cpIce*tIc1(i,j) + rhoi*Lfresh*Tmlt1/tIc1(i,j) )
310 & /(2. _d 0*dt)
311 & - k32*( 4. _d 0*dt*k32*tFrz(i,j)
312 & +rhoi*cpIce*hIce(i,j)*tIc2(i,j) )
313 & / ( 6. _d 0*dt*k32 + rhoi*cpIce *hIce(i,j) )
314 & - fswint
315 c10(i,j) = rhoi*Lfresh*hIce(i,j)*Tmlt1 / (2. _d 0*dt)
316
317 ELSE
318 iceFlag(i,j) = .FALSE.
319 ENDIF
320 ENDDO
321 ENDDO
322 IF ( icount .gt. 0 ) THEN
323 WRITE(stdUnit,'(A,I5,A)')
324 & 'THSICE_SOLVE4TEMP: there are ',icount,
325 & ' case(s) where hIce<hIceMin;'
326 WRITE(stdUnit,'(A,I3,A1,I3,A)')
327 & 'THSICE_SOLVE4TEMP: the last one was at (',ii,',',jj,
328 & ') with hIce = ', hIce(ii,jj)
329 WRITE( msgBuf, '(A)')
330 & 'THSICE_SOLVE4TEMP: should not enter if hIce<hIceMin'
331 CALL PRINT_ERROR( msgBuf , myThid )
332 STOP 'ABNORMAL END: S/R THSICE_SOLVE4TEMP'
333 ENDIF
334
335 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|
336
337 #ifdef ALLOW_AUTODIFF_TAMC
338 CADJ STORE devdt(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
339 CADJ STORE tsf(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
340 #endif
341
342 C-- Get surface fluxes over melting surface
343 #ifdef ALLOW_AUTODIFF_TAMC
344 IF ( useBlkFlx ) THEN
345 CADJ STORE tsf(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
346 #else
347 IF ( useBlkFlx .AND. iterate4Tsf ) THEN
348 #endif
349 DO j = jMin, jMax
350 DO i = iMin, iMax
351 Tsf(i,j) = 0.
352 ENDDO
353 ENDDO
354 IF ( useEXF ) THEN
355 CALL THSICE_GET_EXF( bi, bj,
356 I iMin, iMax, jMin, jMax,
357 I iceFlag, hSnow, Tsf,
358 O flx0exSW, dFlxdT, evap0, dEvdT,
359 I myTime, myIter, myThid )
360 C- could add this "ifdef" to hide THSICE_GET_BULKF from TAF
361 #ifdef ALLOW_BULK_FORCE
362 ELSEIF ( useBulkForce ) THEN
363 CALL THSICE_GET_BULKF( bi, bj,
364 I iMin, iMax, jMin, jMax,
365 I iceFlag, hSnow, Tsf,
366 O flx0exSW, dFlxdT, evap0, dEvdT,
367 I myTime, myIter, myThid )
368 #endif /* ALLOW_BULK_FORCE */
369 ENDIF
370 ENDIF
371
372 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|
373 C--- Compute new surface and internal temperatures; iterate until
374 C Tsfc converges.
375 DO j = jMin, jMax
376 DO i = iMin, iMax
377 Tsf(i,j) = tSrf(i,j)
378 dTsrf(i,j) = Terrmax
379 ENDDO
380 ENDDO
381 IF ( useBlkFlx ) THEN
382 iterMax = nitMaxTsf
383 ELSE
384 iterMax = 1
385 ENDIF
386
387 #ifdef ALLOW_AUTODIFF_TAMC
388 CADJ STORE devdt(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
389 CADJ STORE dflxdt(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
390 CADJ STORE flx0exsw(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
391 CADJ STORE flxtexsw(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
392 #endif
393
394 C ----- begin iteration -----
395 DO k = 1,iterMax
396 #ifndef ALLOW_AUTODIFF_TAMC
397 IF ( iterate4Tsf ) THEN
398 iterate4Tsf = .FALSE.
399 #endif
400
401 IF ( useBlkFlx ) THEN
402 C-- Compute top surface flux.
403 IF ( useEXF ) THEN
404 CALL THSICE_GET_EXF( bi, bj,
405 I iMin, iMax, jMin, jMax,
406 I iceFlag, hSnow, Tsf,
407 O flxTexSW, dFlxdT, evapT, dEvdT,
408 I myTime, myIter, myThid )
409 C- could add this "ifdef" to hide THSICE_GET_BULKF from TAF
410 #ifdef ALLOW_BULK_FORCE
411 ELSEIF ( useBulkForce ) THEN
412 CALL THSICE_GET_BULKF( bi, bj,
413 I iMin, iMax, jMin, jMax,
414 I iceFlag, hSnow, Tsf,
415 O flxTexSW, dFlxdT, evapT, dEvdT,
416 I myTime, myIter, myThid )
417 #endif /* ALLOW_BULK_FORCE */
418 ENDIF
419 ELSE
420 DO j = jMin, jMax
421 DO i = iMin, iMax
422 IF ( iceFlag(i,j) ) THEN
423 flxTexSW(i,j) = flxExSW(i,j,1)
424 dFlxdT(i,j) = flxExSW(i,j,2)
425 ENDIF
426 ENDDO
427 ENDDO
428 ENDIF
429
430 #ifdef ALLOW_AUTODIFF_TAMC
431 CADJ STORE devdt(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
432 CADJ STORE dflxdt(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
433 CADJ STORE flxtexsw(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
434 CADJ STORE iceflag(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
435 CADJ STORE tsf(:,:) = comlev1_bibj,key=ticekey,byte=isbyte
436 #endif
437
438 C-- Compute new top layer and surface temperatures.
439 C If Tsfc is computed to be > 0 C, fix Tsfc = 0 and recompute T1
440 C with different coefficients.
441 DO j = jMin, jMax
442 DO i = iMin, iMax
443 IF ( iceFlag(i,j) ) THEN
444 flxNet = sHeat(i,j) + flxTexSW(i,j)
445 #ifdef ALLOW_DBUG_THSICE
446 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,1020)
447 & 'ThSI_SOLVE4T: flxNet,dFlxdT,k12,D=',
448 & flxNet, dFlxdT(i,j), k12(i,j), k12(i,j)-dFlxdT(i,j)
449 #endif
450
451 a1 = a10(i,j) - k12(i,j)*dFlxdT(i,j) / (k12(i,j)-dFlxdT(i,j))
452 b1 = b10(i,j) - k12(i,j)*(flxNet-dFlxdT(i,j)*Tsf(i,j))
453 & /(k12(i,j)-dFlxdT(i,j))
454 c1 = c10(i,j)
455 tIc1(i,j) = -(b1 + SQRT(b1*b1-4. _d 0*a1*c1))/(2. _d 0*a1)
456 dTsrf(i,j) = (flxNet + k12(i,j)*(tIc1(i,j)-Tsf(i,j)))
457 & /(k12(i,j)-dFlxdT(i,j))
458 Tsf(i,j) = Tsf(i,j) + dTsrf(i,j)
459 IF ( Tsf(i,j) .GT. 0. _d 0 ) THEN
460 #ifdef ALLOW_DBUG_THSICE
461 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,1010)
462 & 'ThSI_SOLVE4T: k,ts,t1,dTs=',k,Tsf(i,j),tIc1(i,j),dTsrf(i,j)
463 #endif
464 a1 = a10(i,j) + k12(i,j)
465 C note: b1 = b10 - k12*Tf0
466 b1 = b10(i,j)
467 tIc1(i,j) = (-b1 - SQRT(b1*b1-4. _d 0*a1*c1))/(2. _d 0*a1)
468 Tsf(i,j) = 0. _d 0
469 IF ( useBlkFlx ) THEN
470 flxTexSW(i,j) = flx0exSW(i,j)
471 evapT(i,j) = evap0(i,j)
472 dTsrf(i,j) = 0. _d 0
473 ELSE
474 flxTexSW(i,j) = flxExSW(i,j,0)
475 dTsrf(i,j) = 1000.
476 dFlxdT(i,j) = 0.
477 ENDIF
478 ENDIF
479
480 C-- Check for convergence. If no convergence, then repeat.
481 iceFlag(i,j) = ABS(dTsrf(i,j)).GE.Terrmax
482 iterate4Tsf = iterate4Tsf .OR. iceFlag(i,j)
483
484 C Convergence test: Make sure Tsfc has converged, within prescribed error.
485 C (Energy conservation is guaranteed within machine roundoff, even
486 C if Tsfc has not converged.)
487 C If no convergence, then repeat.
488
489 #ifdef ALLOW_DBUG_THSICE
490 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,1010)
491 & 'ThSI_SOLVE4T: k,ts,t1,dTs=', k,Tsf(i,j),tIc1(i,j),dTsrf(i,j)
492 IF ( useBlkFlx .AND. k.EQ.nitMaxTsf .AND. iceFlag(i,j) ) THEN
493 WRITE(stdUnit,'(A,4I4,I12,F15.9)')
494 & ' BB: not converge: i,j,it,hi=',i,j,bi,bj,myIter,hIce(i,j)
495 WRITE(stdUnit,*)
496 & 'BB: not converge: Tsf, dTsf=', Tsf(i,j), dTsrf(i,j)
497 WRITE(stdUnit,*)
498 & 'BB: not converge: flxNet,dFlxT=', flxNet, dFlxdT(i,j)
499 IF ( Tsf(i,j).LT.-70. _d 0 ) THEN
500 WRITE( msgBuf, '(A,2I4,2I3,I10,F12.3)')
501 & 'THSICE_SOLVE4TEMP: Too low Tsf in', i, j, bi, bj,
502 & myIter, Tsf(i,j)
503 CALL PRINT_ERROR( msgBuf , myThid )
504 STOP 'ABNORMAL END: S/R THSICE_SOLVE4TEMP'
505 ENDIF
506 ENDIF
507 #endif
508
509 ENDIF
510 ENDDO
511 ENDDO
512 #ifndef ALLOW_AUTODIFF_TAMC
513 ENDIF
514 #endif
515 ENDDO
516 C ------ end iteration ------------
517
518 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|
519
520 DO j = jMin, jMax
521 DO i = iMin, iMax
522 IF ( iceMask(i,j).GT.0. _d 0 ) THEN
523
524 C-- Compute new bottom layer temperature.
525 k32 = 2. _d 0*kIce / hIce(i,j)
526 tIc2(i,j) = ( 2. _d 0*dt*k32*(tIc1(i,j)+2. _d 0*tFrz(i,j))
527 & + rhoi*cpIce*hIce(i,j)*tIc2(i,j))
528 & /(6. _d 0*dt*k32 + rhoi*cpIce*hIce(i,j))
529 #ifdef ALLOW_DBUG_THSICE
530 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,1010)
531 & 'ThSI_SOLVE4T: k, Ts, Tice=',k,Tsf(i,j),tIc1(i,j),tIc2(i,j)
532 netSW = flxAtm(i,j)
533 #endif
534
535 C-- Compute final flux values at surfaces.
536 tSrf(i,j) = Tsf(i,j)
537 fct = k12(i,j)*(Tsf(i,j)-tIc1(i,j))
538 flxCnB(i,j) = 4. _d 0*kIce *(tIc2(i,j)-tFrz(i,j))/hIce(i,j)
539 flxNet = sHeat(i,j) + flxTexSW(i,j)
540 flxNet = flxNet + dFlxdT(i,j)*dTsrf(i,j)
541 IF ( useBlkFlx ) THEN
542 C- needs to update also Evap (Tsf changes) since Latent heat has been updated
543 evpAtm(i,j) = evapT(i,j) + dEvdT(i,j)*dTsrf(i,j)
544 ELSE
545 C- WARNING: Evap & +Evap*Lfresh are missing ! (but only affects Diagnostics)
546 evpAtm(i,j) = 0.
547 ENDIF
548 C- Update energy flux to Atmos with other than SW contributions;
549 C use latent heat = Lvap (energy=0 for liq. water at 0.oC)
550 flxAtm(i,j) = flxAtm(i,j) + flxTexSW(i,j)
551 & + dFlxdT(i,j)*dTsrf(i,j) + evpAtm(i,j)*Lfresh
552 C- excess of energy @ surface (used for surface melting):
553 sHeat(i,j) = flxNet - fct
554
555 #ifdef ALLOW_DBUG_THSICE
556 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,1020)
557 & 'ThSI_SOLVE4T: flxNet,fct,Dif,flxCnB=',
558 & flxNet,fct,flxNet-fct,flxCnB(i,j)
559 #endif
560
561 C-- Compute new enthalpy for each layer.
562 qIc1(i,j) = -cpWater*Tmlt1 + cpIce *(Tmlt1-tIc1(i,j))
563 & + Lfresh*(1. _d 0-Tmlt1/tIc1(i,j))
564 qIc2(i,j) = -cpIce *tIc2(i,j) + Lfresh
565
566 #ifdef ALLOW_DBUG_THSICE
567 C-- Make sure internal ice temperatures do not exceed Tmlt.
568 C (This should not happen for reasonable values of i0swFrac)
569 IF (tIc1(i,j) .GE. Tmlt1) THEN
570 WRITE(stdUnit,'(A,2I4,2I3,1P2E14.6)')
571 & ' BBerr - Bug: IceT(1) > Tmlt',i,j,bi,bj,tIc1(i,j),Tmlt1
572 ENDIF
573 IF (tIc2(i,j) .GE. 0. _d 0) THEN
574 WRITE(stdUnit,'(A,2I4,2I3,1P2E14.6)')
575 & ' BBerr - Bug: IceT(2) > 0',i,j,bi,bj,tIc2(i,j)
576 ENDIF
577
578 IF ( dBug(i,j,bi,bj) ) THEN
579 WRITE(stdUnit,1020) 'ThSI_SOLV_4T: Tsf, Tice(1,2), dTsurf=',
580 & Tsf(i,j), tIc1(i,j), tIc2(i,j), dTsrf(i,j)
581 WRITE(stdUnit,1020) 'ThSI_SOLV_4T: sHeat, flxCndBt, Qice =',
582 & sHeat(i,j), flxCnB(i,j), qIc1(i,j), qIc2(i,j)
583 WRITE(stdUnit,1020) 'ThSI_SOLV_4T: flxA, evpA, fxSW_bf,af=',
584 & flxAtm(i,j), evpAtm(i,j), netSW, flxSW(i,j)
585 ENDIF
586 #endif
587
588 ELSE
589 C-- ice-free grid point:
590 c tIc1 (i,j) = 0. _d 0
591 c tIc2 (i,j) = 0. _d 0
592 dTsrf (i,j) = 0. _d 0
593 c sHeat (i,j) = 0. _d 0
594 c flxCnB(i,j) = 0. _d 0
595 c flxAtm(i,j) = 0. _d 0
596 c evpAtm(i,j) = 0. _d 0
597
598 ENDIF
599 ENDDO
600 ENDDO
601 #endif /* ALLOW_THSICE */
602
603 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|
604
605 RETURN
606 END

  ViewVC Help
Powered by ViewVC 1.1.22