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

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

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


Revision 1.24 - (show annotations) (download)
Fri May 2 22:15:26 2014 UTC (10 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.23: +36 -9 lines
from Jeff Scott: add option (#define EXF_CALC_ATMRHO) to calculate local
  air density as function of air Temp, Humidity and atm pressure.

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_get_exf.F,v 1.23 2013/06/01 19:49:29 heimbach Exp $
2 C $Name: $
3
4 #include "THSICE_OPTIONS.h"
5 #ifdef ALLOW_EXF
6 #include "EXF_OPTIONS.h"
7 #endif
8
9 CBOP
10 C !ROUTINE: THSICE_GET_EXF
11 C !INTERFACE:
12 SUBROUTINE THSICE_GET_EXF(
13 I bi, bj, it2,
14 I iMin,iMax, jMin,jMax,
15 I icFlag, hSnow1, tsfCel,
16 O flxExcSw, dFlxdT, evapLoc, dEvdT,
17 I myTime, myIter, myThid )
18
19 C !DESCRIPTION: \bv
20 C *==========================================================*
21 C | S/R THSICE_GET_EXF
22 C *==========================================================*
23 C | Interface S/R : get Surface Fluxes from pkg EXF
24 C *==========================================================*
25 C \ev
26
27 C !USES:
28 IMPLICIT NONE
29
30 C == Global data ==
31 #include "SIZE.h"
32 #include "EEPARAMS.h"
33 #include "PARAMS.h"
34 #ifdef ALLOW_EXF
35 # include "EXF_CONSTANTS.h"
36 # include "EXF_PARAM.h"
37 # include "EXF_FIELDS.h"
38 #endif
39 #ifdef ALLOW_AUTODIFF_TAMC
40 # include "tamc.h"
41 # include "tamc_keys.h"
42 # include "THSICE_SIZE.h"
43 #endif
44
45 C !INPUT/OUTPUT PARAMETERS:
46 C === Routine arguments ===
47 C bi,bj :: tile indices
48 C it :: solv4temp iteration
49 C iMin,iMax :: computation domain: 1rst index range
50 C jMin,jMax :: computation domain: 2nd index range
51 C icFlag :: True= get fluxes at this location ; False= do nothing
52 C hSnow1 :: snow height [m]
53 C tsfCel :: surface (ice or snow) temperature (oC)
54 C flxExcSw :: net (downward) surface heat flux, except short-wave [W/m2]
55 C dFlxdT :: deriv of flx with respect to Tsf [W/m/K]
56 C evapLoc :: surface evaporation (>0 if evaporate) [kg/m2/s]
57 C dEvdT :: deriv of evap. with respect to Tsf [kg/m2/s/K]
58 C myTime :: current Time of simulation [s]
59 C myIter :: current Iteration number in simulation
60 C myThid :: my Thread Id number
61 INTEGER bi, bj
62 INTEGER it2
63 INTEGER iMin, iMax
64 INTEGER jMin, jMax
65 _RL icFlag (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
66 _RL hSnow1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
67 _RL tsfCel (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
68 _RL flxExcSw(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
69 _RL dFlxdT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
70 _RL evapLoc (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71 _RL dEvdT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72 _RL myTime
73 INTEGER myIter
74 INTEGER myThid
75 CEOP
76
77 #ifdef ALLOW_EXF
78 #ifdef ALLOW_ATM_TEMP
79 #ifdef ALLOW_DOWNWARD_RADIATION
80
81 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
82 C === Local variables ===
83 C hsLocal, hlLocal :: sensible & latent heat flux over sea-ice
84 C t0 :: virtual temperature (K)
85 C ssq :: saturation specific humidity (kg/kg)
86 C deltap :: potential temperature diff (K)
87 _RL hsLocal
88 _RL hlLocal
89 INTEGER iter
90 INTEGER i, j
91 _RL czol
92 _RL wsm ! limited wind speed [m/s] (> umin)
93 _RL t0 ! virtual temperature [K]
94 C copied from exf_bulkformulae:
95 C these need to be 2D-arrays for vectorizing code
96 C turbulent temperature scale [K]
97 _RL tstar (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
98 C turbulent humidity scale [kg/kg]
99 _RL qstar (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
100 C friction velocity [m/s]
101 _RL ustar (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
102 C neutral, zref (=10m) values of rd
103 _RL rdn (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
104 _RL rd (1-OLx:sNx+OLx,1-OLy:sNy+OLy) ! = sqrt(Cd) [-]
105 _RL rh (1-OLx:sNx+OLx,1-OLy:sNy+OLy) ! = Ch / sqrt(Cd) [-]
106 _RL re (1-OLx:sNx+OLx,1-OLy:sNy+OLy) ! = Ce / sqrt(Cd) [-]
107 C specific humidity difference [kg/kg]
108 _RL delq (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
109 _RL deltap(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
110 #ifdef EXF_CALC_ATMRHO
111 C local atmospheric density [kg/m^3]
112 _RL atmrho_loc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
113 #endif
114 C
115 _RL ssq (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
116 _RL ren, rhn ! neutral, zref (=10m) values of re, rh
117 _RL usn, usm ! neutral, zref (=10m) wind-speed (+limited)
118 _RL stable ! = 1 if stable ; = 0 if unstable
119 C stability parameter at zwd [-] (=z/Monin-Obuklov length)
120 _RL huol
121 _RL htol ! stability parameter at zth [-]
122 _RL hqol
123 _RL x ! stability function [-]
124 _RL xsq ! = x^2 [-]
125 _RL psimh ! momentum stability function
126 _RL psixh ! latent & sensib. stability function
127 _RL zwln ! = log(zwd/zref)
128 _RL ztln ! = log(zth/zref)
129 _RL tau ! surface stress coef = rhoA * Ws * sqrt(Cd)
130 _RL tmpbulk
131
132 C additional variables that are copied from bulkf_formula_lay:
133 C upward LW at surface (W m-2)
134 _RL flwup
135 C net (downward) LW at surface (W m-2)
136 _RL flwNet_dwn
137 C gradients of latent/sensible net upward heat flux
138 C w/ respect to temperature
139 _RL dflhdT
140 _RL dfshdT
141 _RL dflwupdT
142 C emissivities, called emittance in exf
143 _RL emiss
144 C Tsf :: surface temperature [K]
145 C Ts2 :: surface temperature square [K^2]
146 _RL Tsf
147 _RL Ts2
148 C latent heat of evaporation or sublimation [J/kg]
149 _RL lath
150 _RL qsat_fac
151 _RL qsat_exp
152 #ifdef ALLOW_DBUG_THSICE
153 LOGICAL dBugFlag
154 INTEGER stdUnit
155 #endif
156
157 C == external functions ==
158
159 c _RL exf_BulkqSat
160 c external exf_BulkqSat
161 c _RL exf_BulkCdn
162 c external exf_BulkCdn
163 c _RL exf_BulkRhn
164 c external exf_BulkRhn
165
166 C == end of interface ==
167
168 C- Define grid-point location where to print debugging values
169 #include "THSICE_DEBUG.h"
170
171 #ifdef ALLOW_DBUG_THSICE
172 dBugFlag = debugLevel.GE.debLevC
173 stdUnit = standardMessageUnit
174 #endif
175
176 C-- Set surface parameters :
177 zwln = LOG(hu/zref)
178 ztln = LOG(ht/zref)
179 czol = hu*karman*gravity_mks
180 ren = cDalton
181 C more abbreviations
182 lath = flamb+flami
183 qsat_fac = cvapor_fac_ice
184 qsat_exp = cvapor_exp_ice
185
186 C initialisation of local arrays
187 DO j = 1-OLy,sNy+OLy
188 DO i = 1-OLx,sNx+OLx
189 tstar(i,j) = 0. _d 0
190 qstar(i,j) = 0. _d 0
191 ustar(i,j) = 0. _d 0
192 rdn(i,j) = 0. _d 0
193 rd(i,j) = 0. _d 0
194 rh(i,j) = 0. _d 0
195 re(i,j) = 0. _d 0
196 delq(i,j) = 0. _d 0
197 deltap(i,j) = 0. _d 0
198 ssq(i,j) = 0. _d 0
199 ENDDO
200 ENDDO
201 C
202 DO j=jMin,jMax
203 DO i=iMin,iMax
204 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
205 #ifdef ALLOW_DBUG_THSICE
206 IF ( dBug(i,j,bi,bj) .AND. (icFlag(i,j).GT.0. _d 0) )
207 & WRITE(stdUnit,'(A,2I4,2I2,2F12.6)')
208 & 'ThSI_GET_EXF: i,j,atemp,lwd=',
209 & i,j,bi,bj, atemp(i,j,bi,bj),lwdown(i,j,bi,bj)
210 #endif
211
212 #ifdef ALLOW_AUTODIFF_TAMC
213 act1 = bi - myBxLo(myThid)
214 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
215 act2 = bj - myByLo(myThid)
216 max2 = myByHi(myThid) - myByLo(myThid) + 1
217 act3 = myThid - 1
218 max3 = nTx*nTy
219 act4 = ikey_dynamics - 1
220 ikey_1 = i
221 & + sNx*(j-1)
222 & + sNx*sNy*(it2-1)
223 & + sNx*sNy*MaxTsf*act1
224 & + sNx*sNy*MaxTsf*max1*act2
225 & + sNx*sNy*MaxTsf*max1*max2*act3
226 & + sNx*sNy*MaxTsf*max1*max2*max3*act4
227 #endif
228
229 C-- Use atmospheric state to compute surface fluxes.
230 IF ( (icFlag(i,j).GT.0. _d 0) .AND.
231 & (atemp(i,j,bi,bj).NE.0. _d 0) ) THEN
232 IF ( hSnow1(i,j).GT.3. _d -1 ) THEN
233 emiss = snow_emissivity
234 ELSE
235 emiss = ice_emissivity
236 ENDIF
237 C copy a few variables to names used in bulkf_formula_lay
238 Tsf = tsfCel(i,j)+cen2kel
239 Ts2 = Tsf*Tsf
240 C wind speed
241 #ifdef ALLOW_AUTODIFF_TAMC
242 CADJ STORE sh(i,j,bi,bj) = comlev1_thsice_3, key = ikey_1
243 #endif
244 wsm = sh(i,j,bi,bj)
245 C-- air - surface difference of temperature & humidity
246 c tmpbulk= exf_BulkqSat(Tsf)
247 c ssq(i,j) = saltsat*tmpbulk/atmrho
248 tmpbulk = qsat_fac*EXP(-qsat_exp/Tsf)
249 #ifdef EXF_CALC_ATMRHO
250 atmrho_loc(i,j) = apressure(i,j,bi,bj) /
251 & (287.04 _d 0*atemp(i,j,bi,bj)
252 & *(1. _d 0 + humid_fac*aqh(i,j,bi,bj)))
253 ssq(i,j) = tmpbulk/atmrho_loc(i,j)
254 #else
255 ssq(i,j) = tmpbulk/atmrho
256 #endif
257 deltap(i,j) = atemp(i,j,bi,bj) + gamma_blk*ht - Tsf
258 delq(i,j) = aqh(i,j,bi,bj) - ssq(i,j)
259 C Do the part of the output variables that do not depend
260 C on the ice here to save a few re-computations
261 C This is not yet dEvdT, but just a cheap way to save a 2D-field
262 C for ssq and recomputing Ts2 lateron
263 dEvdT(i,j) = ssq(i,j)*qsat_exp/Ts2
264 flwup = emiss*stefanBoltzmann*Ts2*Ts2
265 dflwupdT = emiss*stefanBoltzmann*Ts2*Tsf * 4. _d 0
266 c flwNet_dwn = lwdown(i,j,bi,bj) - flwup
267 C- assume long-wave albedo = 1 - emissivity :
268 flwNet_dwn = emiss*lwdown(i,j,bi,bj) - flwup
269 C-- This is not yet the total derivative with respect to surface temperature
270 dFlxdT(i,j) = -dflwupdT
271 C-- This is not yet the Net downward radiation excluding shortwave
272 flxExcSw(i,j) = flwNet_dwn
273 ENDIF
274 ENDDO
275 ENDDO
276
277 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
278
279 IF ( useStabilityFct_overIce ) THEN
280 DO j=jMin,jMax
281 DO i=iMin,iMax
282 #ifdef ALLOW_AUTODIFF_TAMC
283 act1 = bi - myBxLo(myThid)
284 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
285 act2 = bj - myByLo(myThid)
286 max2 = myByHi(myThid) - myByLo(myThid) + 1
287 act3 = myThid - 1
288 max3 = nTx*nTy
289 act4 = ikey_dynamics - 1
290 ikey_1 = i
291 & + sNx*(j-1)
292 & + sNx*sNy*(it2-1)
293 & + sNx*sNy*MaxTsf*act1
294 & + sNx*sNy*MaxTsf*max1*act2
295 & + sNx*sNy*MaxTsf*max1*max2*act3
296 & + sNx*sNy*MaxTsf*max1*max2*max3*act4
297 C--
298 CADJ STORE sh(i,j,bi,bj) = comlev1_thsice_3, key = ikey_1
299 #endif
300 IF ( (icFlag(i,j).GT.0. _d 0) .AND.
301 & (atemp(i,j,bi,bj).NE.0. _d 0) ) THEN
302 C-- Compute the turbulent surface fluxes (function of stability).
303
304 C Initial guess: z/l=0.0; hu=ht=hq=z
305 C Iterations: converge on z/l and hence the fluxes.
306
307 t0 = atemp(i,j,bi,bj)*
308 & (exf_one + humid_fac*aqh(i,j,bi,bj))
309 stable = exf_half + SIGN(exf_half, deltap(i,j))
310 c tmpbulk = exf_BulkCdn(sh(i,j,bi,bj))
311 wsm = sh(i,j,bi,bj)
312 tmpbulk = cdrag_1/wsm + cdrag_2 + cdrag_3*wsm
313 IF (tmpbulk.NE.0.) THEN
314 rdn(i,j) = SQRT(tmpbulk)
315 ELSE
316 rdn(i,j) = 0. _d 0
317 ENDIF
318 C-- initial guess for exchange other coefficients:
319 c rhn = exf_BulkRhn(stable)
320 rhn = (exf_one-stable)*cstanton_1 + stable*cstanton_2
321 C-- calculate turbulent scales
322 ustar(i,j) = rdn(i,j)*wsm
323 tstar(i,j) = rhn*deltap(i,j)
324 qstar(i,j) = ren*delq(i,j)
325 ENDIF
326 ENDDO
327 ENDDO
328
329 C start iteration
330 DO iter = 1,niter_bulk
331 DO j=jMin,jMax
332 DO i=iMin,iMax
333 IF ( (icFlag(i,j).GT.0. _d 0) .AND.
334 & (atemp(i,j,bi,bj).NE.0. _d 0) ) THEN
335
336 #ifdef ALLOW_AUTODIFF_TAMC
337 ikey_2 = iter
338 & + niter_bulk*(i-1)
339 & + niter_bulk*sNx*(j-1)
340 & + niter_bulk*sNx*sNy*(it2-1)
341 & + niter_bulk*sNx*sNy*MaxTsf*act1
342 & + niter_bulk*sNx*sNy*MaxTsf*max1*act2
343 & + niter_bulk*sNx*sNy*MaxTsf*max1*max2*act3
344 & + niter_bulk*sNx*sNy*MaxTsf*max1*max2*max3*act4
345 CADJ STORE rdn(i,j) = comlev1_thsice_5, key = ikey_2
346 CADJ STORE ustar(i,j) = comlev1_thsice_5, key = ikey_2
347 CADJ STORE qstar(i,j) = comlev1_thsice_5, key = ikey_2
348 CADJ STORE tstar(i,j) = comlev1_thsice_5, key = ikey_2
349 CADJ STORE sh(i,j,bi,bj) = comlev1_thsice_5, key = ikey_2
350 #endif
351
352 t0 = atemp(i,j,bi,bj)*
353 & (exf_one + humid_fac*aqh(i,j,bi,bj))
354 huol = (tstar(i,j)/t0 +
355 & qstar(i,j)/(exf_one/humid_fac+aqh(i,j,bi,bj))
356 & )*czol/(ustar(i,j)*ustar(i,j))
357 #ifdef ALLOW_BULK_LARGEYEAGER04
358 C- Large&Yeager_2004 code:
359 huol = MIN( MAX(-10. _d 0,huol), 10. _d 0 )
360 #else
361 C- Large&Pond_1981 code (zolmin default = -100):
362 huol = MAX(huol,zolmin)
363 #endif /* ALLOW_BULK_LARGEYEAGER04 */
364 htol = huol*ht/hu
365 hqol = huol*hq/hu
366 stable = exf_half + SIGN(exf_half, huol)
367
368 C Evaluate all stability functions assuming hq = ht.
369 #ifdef ALLOW_BULK_LARGEYEAGER04
370 C- Large&Yeager_2004 code:
371 xsq = SQRT( ABS(exf_one - huol*16. _d 0) )
372 #else
373 C- Large&Pond_1981 code:
374 xsq = MAX(SQRT(ABS(exf_one - huol*16. _d 0)),exf_one)
375 #endif /* ALLOW_BULK_LARGEYEAGER04 */
376 x = SQRT(xsq)
377 psimh = -psim_fac*huol*stable
378 & + (exf_one-stable)
379 & *( LOG( (exf_one + exf_two*x + xsq)
380 & *(exf_one+xsq)*0.125 _d 0 )
381 & -exf_two*ATAN(x) + exf_half*pi )
382 #ifdef ALLOW_BULK_LARGEYEAGER04
383 C- Large&Yeager_2004 code:
384 xsq = SQRT( ABS(exf_one - htol*16. _d 0) )
385 #else
386 C- Large&Pond_1981 code:
387 xsq = MAX(SQRT(ABS(exf_one - htol*16. _d 0)),exf_one)
388 #endif /* ALLOW_BULK_LARGEYEAGER04 */
389 psixh = -psim_fac*htol*stable
390 & + (exf_one-stable)
391 & *exf_two*LOG( exf_half*(exf_one+xsq) )
392
393 C Shift wind speed using old coefficient
394 #ifdef ALLOW_BULK_LARGEYEAGER04
395 C-- Large&Yeager04:
396 usn = wspeed(i,j,bi,bj)
397 & /( exf_one + rdn(i,j)*(zwln-psimh)/karman )
398 #else
399 C-- Large&Pond1981:
400 usn = sh(i,j,bi,bj)/(exf_one - rdn(i,j)/karman*psimh)
401 #endif /* ALLOW_BULK_LARGEYEAGER04 */
402 usm = MAX(usn, umin)
403
404 C- Update the 10m, neutral stability transfer coefficients
405 c tmpbulk= exf_BulkCdn(usm)
406 tmpbulk= cdrag_1/usm + cdrag_2 + cdrag_3*usm
407 rdn(i,j) = SQRT(tmpbulk)
408 c rhn = exf_BulkRhn(stable)
409 rhn = (exf_one-stable)*cstanton_1 + stable*cstanton_2
410
411 C Shift all coefficients to the measurement height and stability.
412 #ifdef ALLOW_BULK_LARGEYEAGER04
413 rd(i,j)= rdn(i,j)/( exf_one + rdn(i,j)*(zwln-psimh)/karman )
414 #else
415 rd(i,j)= rdn(i,j)/( exf_one - rdn(i,j)/karman*psimh )
416 #endif /* ALLOW_BULK_LARGEYEAGER04 */
417 rh(i,j)= rhn/( exf_one + rhn*(ztln-psixh)/karman )
418 re(i,j)= ren/( exf_one + ren*(ztln-psixh)/karman )
419
420 C Update ustar, tstar, qstar using updated, shifted coefficients.
421 ustar(i,j) = rd(i,j)*sh(i,j,bi,bj)
422 qstar(i,j) = re(i,j)*delq(i,j)
423 tstar(i,j) = rh(i,j)*deltap(i,j)
424 ENDIF
425 C end i/j-loops
426 ENDDO
427 ENDDO
428 C end iteration loop
429 ENDDO
430 DO j=jMin,jMax
431 DO i=iMin,iMax
432 IF ( (icFlag(i,j).GT.0. _d 0) .AND.
433 & (atemp(i,j,bi,bj).NE.0. _d 0) ) THEN
434 #ifdef EXF_CALC_ATMRHO
435 tau = atmrho_loc(i,j)*rd(i,j)*wspeed(i,j,bi,bj)
436 #else
437 tau = atmrho*rd(i,j)*wspeed(i,j,bi,bj)
438 #endif
439 evapLoc(i,j) = -tau*qstar(i,j)
440 hlLocal = -lath*evapLoc(i,j)
441 hsLocal = atmcp*tau*tstar(i,j)
442 c ustress = tau*rd(i,j)*UwindSpeed
443 c vstress = tau*rd(i,j)*VwindSpeed
444
445 C--- surf.Temp derivative of turbulent Fluxes
446 C complete computation of dEvdT
447 dEvdT(i,j) = (tau*re(i,j))*dEvdT(i,j)
448 dflhdT = -lath*dEvdT(i,j)
449 dfshdT = -atmcp*tau*rh(i,j)
450 C-- Update total derivative with respect to surface temperature
451 dFlxdT(i,j) = dFlxdT(i,j) + dfshdT + dflhdT
452 C-- Update net downward radiation excluding shortwave
453 flxExcSw(i,j) = flxExcSw(i,j) + hsLocal + hlLocal
454
455 ENDIF
456 ENDDO
457 ENDDO
458 ELSE
459 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
460 C-- Compute the turbulent surface fluxes using fixed transfert Coeffs
461 C with no stability dependence ( useStabilityFct_overIce = false )
462 DO j=jMin,jMax
463 DO i=iMin,iMax
464 IF ( (icFlag(i,j).GT.0. _d 0) .AND.
465 & (atemp(i,j,bi,bj).NE.0. _d 0) ) THEN
466 wsm = sh(i,j,bi,bj)
467 #ifdef EXF_CALC_ATMRHO
468 tau = atmrho_loc(i,j)*exf_iceCe*wsm
469 #else
470 tau = atmrho*exf_iceCe*wsm
471 #endif
472 evapLoc(i,j) = -tau*delq(i,j)
473 hlLocal = -lath*evapLoc(i,j)
474 #ifdef EXF_CALC_ATMRHO
475 hsLocal = atmcp*atmrho_loc(i,j)
476 & *exf_iceCh*wsm*deltap(i,j)
477 #else
478 hsLocal = atmcp*atmrho*exf_iceCh*wsm*deltap(i,j)
479 #endif
480 #ifdef ALLOW_DBUG_THSICE
481 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,'(A,4F12.6)')
482 & 'ThSI_GET_EXF: wsm,hl,hs,Lw=',
483 & wsm,hlLocal,hsLocal,flxExcSw(i,j)
484 #endif
485 C--- surf.Temp derivative of turbulent Fluxes
486 C complete computation of dEvdT
487 dEvdT(i,j) = tau*dEvdT(i,j)
488 dflhdT = -lath*dEvdT(i,j)
489 #ifdef EXF_CALC_ATMRHO
490 dfshdT = -atmcp*atmrho_loc(i,j)*exf_iceCh*wsm
491 #else
492 dfshdT = -atmcp*atmrho*exf_iceCh*wsm
493 #endif
494 C-- Update total derivative with respect to surface temperature
495 dFlxdT(i,j) = dFlxdT(i,j) + dfshdT + dflhdT
496 C-- Update net downward radiation excluding shortwave
497 flxExcSw(i,j) = flxExcSw(i,j) + hsLocal + hlLocal
498 #ifdef ALLOW_DBUG_THSICE
499 IF ( dBug(i,j,bi,bj) ) WRITE(stdUnit,'(A,4F12.6)')
500 & 'ThSI_GET_EXF: flx,dFlxdT,evap,dEvdT',
501 & flxExcSw(i,j), dFlxdT(i,j), evapLoc(i,j),dEvdT(i,j)
502 #endif
503 ENDIF
504 ENDDO
505 ENDDO
506 C endif useStabilityFct_overIce
507 ENDIF
508 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
509 DO j=jMin,jMax
510 DO i=iMin,iMax
511 IF ( (icFlag(i,j).GT.0. _d 0) .AND.
512 & (atemp(i,j,bi,bj).LE.0. _d 0) ) THEN
513 C-- in case atemp is zero:
514 flxExcSw(i,j) = 0. _d 0
515 dFlxdT (i,j) = 0. _d 0
516 evapLoc (i,j) = 0. _d 0
517 dEvdT (i,j) = 0. _d 0
518 ENDIF
519 ENDDO
520 ENDDO
521
522 #else /* ALLOW_DOWNWARD_RADIATION */
523 STOP 'ABNORMAL END: S/R THSICE_GET_EXF: DOWNWARD_RADIATION undef'
524 #endif /* ALLOW_DOWNWARD_RADIATION */
525 #else /* ALLOW_ATM_TEMP */
526 STOP 'ABNORMAL END: S/R THSICE_GET_EXF: ATM_TEMP undef'
527 #endif /* ALLOW_ATM_TEMP */
528 #ifdef EXF_READ_EVAP
529 STOP 'ABNORMAL END: S/R THSICE_GET_EXF: EXF_READ_EVAP defined'
530 #endif /* EXF_READ_EVAP */
531 #endif /* ALLOW_EXF */
532
533 RETURN
534 END

  ViewVC Help
Powered by ViewVC 1.1.22