/[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.11 - (show annotations) (download)
Mon May 14 20:48:26 2007 UTC (17 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.10: +2 -2 lines
remove us (use wspeed instead);

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_get_exf.F,v 1.10 2007/05/09 12:46:10 jmc 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 iceornot, tsfCel,
14 O flxExceptSw, df0dT, evapLoc, dEvdT,
15 I i,j,bi,bj,myThid )
16 C !DESCRIPTION: \bv
17 C *==========================================================*
18 C | S/R THSICE_GET_EXF
19 C *==========================================================*
20 C | Interface S/R : get Surface Fluxes from pkg EXF
21 C *==========================================================*
22 C \ev
23
24 C !USES:
25 IMPLICIT NONE
26
27 C == Global data ==
28 #include "SIZE.h"
29 #include "EEPARAMS.h"
30 #include "PARAMS.h"
31 #ifdef ALLOW_EXF
32 # include "EXF_CONSTANTS.h"
33 # include "EXF_PARAM.h"
34 # include "EXF_FIELDS.h"
35 #endif
36 #ifdef ALLOW_AUTODIFF_TAMC
37 # include "tamc.h"
38 # include "tamc_keys.h"
39 #endif
40
41 C !INPUT/OUTPUT PARAMETERS:
42 C === Routine arguments ===
43 C iceornot :: 0=open water, 1=ice cover
44 C tsfCel :: surface (ice or snow) temperature (oC)
45 C flxExceptSw :: net (downward) surface heat flux, except short-wave [W/m2]
46 C df0dT :: deriv of flx with respect to Tsf [W/m/K]
47 C evapLoc :: surface evaporation (>0 if evaporate) [kg/m2/s]
48 C dEvdT :: deriv of evap. with respect to Tsf [kg/m2/s/K]
49 C i,j, bi,bj :: current grid point indices
50 C myThid :: My Thread Id number
51 INTEGER i,j, bi,bj
52 INTEGER myThid
53 INTEGER iceornot
54 _RL tsfCel
55 _RL flxExceptSw
56 _RL df0dT
57 _RL evapLoc
58 _RL dEvdT
59 CEOP
60
61 #ifdef ALLOW_EXF
62 #ifdef ALLOW_ATM_TEMP
63
64 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
65 C === Local variables ===
66 C hsLocal, hlLocal :: sensible & latent heat flux over sea-ice
67 C t0 :: virtual temperature (K)
68 C ssq :: saturation specific humidity (kg/kg)
69 C deltap :: potential temperature diff (K)
70
71 _RL hsLocal, hlLocal
72 INTEGER iter
73 _RL delq
74 _RL deltap
75 _RL czol
76 _RL ws ! wind speed [m/s] (unlimited)
77 _RL wsm ! limited wind speed [m/s] (> umin)
78 _RL t0 ! virtual temperature [K]
79 _RL ustar ! friction velocity [m/s]
80 _RL tstar ! turbulent temperature scale [K]
81 _RL qstar ! turbulent humidity scale [kg/kg]
82 _RL ssq
83 _RL rd ! = sqrt(Cd) [-]
84 _RL re ! = Ce / sqrt(Cd) [-]
85 _RL rh ! = Ch / sqrt(Cd) [-]
86 _RL rdn, ren, rhn ! neutral, zref (=10m) values of rd, re, rh
87 _RL usn, usm ! neutral, zref (=10m) wind-speed (+limited)
88 _RL stable ! = 1 if stable ; = 0 if unstable
89 _RL huol ! stability parameter at zwd [-] (=z/Monin-Obuklov length)
90 _RL htol ! stability parameter at zth [-]
91 _RL hqol
92 _RL x ! stability function [-]
93 _RL xsq ! = x^2 [-]
94 _RL psimh ! momentum stability function
95 _RL psixh ! latent & sensib. stability function
96 _RL zwln ! = log(zwd/zref)
97 _RL ztln ! = log(zth/zref)
98 _RL tau ! surface stress coef = rhoA * Ws * sqrt(Cd)
99 _RL tmpbulk
100
101 C additional variables that are copied from bulkf_formula_lay:
102 C upward LW at surface (W m-2)
103 _RL flwup
104 C net (downward) LW at surface (W m-2)
105 _RL flwNet_dwn
106 C gradients of latent/sensible net upward heat flux
107 C w/ respect to temperature
108 _RL dflhdT, dfshdT, dflwupdT
109 C emissivities, called emittance in exf
110 _RL emiss
111 C Tsf :: surface temperature [K]
112 C Ts2 :: surface temperature square [K^2]
113 _RL Tsf
114 _RL Ts2
115 C latent heat of evaporation or sublimation [J/kg]
116 _RL lath
117 _RL qsat_fac, qsat_exp
118 #ifdef ALLOW_AUTODIFF_TAMC
119 INTEGER ikey_1
120 INTEGER ikey_2
121 #endif
122
123 C == external functions ==
124
125 c _RL exf_BulkqSat
126 c external exf_BulkqSat
127 c _RL exf_BulkCdn
128 c external exf_BulkCdn
129 c _RL exf_BulkRhn
130 c external exf_BulkRhn
131
132 C == end of interface ==
133
134 #ifdef ALLOW_AUTODIFF_TAMC
135 act1 = bi - myBxLo(myThid)
136 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
137 act2 = bj - myByLo(myThid)
138 max2 = myByHi(myThid) - myByLo(myThid) + 1
139 act3 = myThid - 1
140 max3 = nTx*nTy
141 act4 = ikey_dynamics - 1
142
143 ikey_1 = i
144 & + sNx*(j-1)
145 & + sNx*sNy*act1
146 & + sNx*sNy*max1*act2
147 & + sNx*sNy*max1*max2*act3
148 & + sNx*sNy*max1*max2*max3*act4
149 #endif
150
151 C copy a few variables to names used in bulkf_formula_lay
152 Tsf = tsfCel+cen2kel
153 Ts2 = Tsf*Tsf
154 C wind speed
155 ws = wspeed(i,j,bi,bj)
156 #ifdef ALLOW_AUTODIFF_TAMC
157 CADJ STORE sh(i,j,bi,bj) = comlev1_exf_1, key = ikey_1
158 #endif
159 wsm = sh(i,j,bi,bj)
160 IF ( iceornot.EQ.0 ) THEN
161 lath = flamb
162 qsat_fac = cvapor_fac
163 qsat_exp = cvapor_exp
164 ELSE
165 lath = flamb+flami
166 qsat_fac = cvapor_fac_ice
167 qsat_exp = cvapor_exp_ice
168 ENDIF
169
170 C-- Use atmospheric state to compute surface fluxes.
171 IF ( atemp(i,j,bi,bj) .NE. 0. _d 0 ) THEN
172
173 C-- air - surface difference of temperature & humidity
174 c tmpbulk= exf_BulkqSat(Tsf)
175 c ssq = saltsat*tmpbulk/atmrho
176 tmpbulk= qsat_fac*EXP(-qsat_exp/Tsf)
177 ssq = tmpbulk/atmrho
178 deltap = atemp(i,j,bi,bj) + gamma_blk*ht - Tsf
179 delq = aqh(i,j,bi,bj) - ssq
180
181 IF ( useStabilityFct_overIce ) THEN
182 C-- Compute the turbulent surface fluxes (function of stability).
183
184 C-- Set surface parameters :
185 zwln = LOG(hu/zref)
186 ztln = LOG(ht/zref)
187 czol = hu*karman*gravity_mks
188
189 C Initial guess: z/l=0.0; hu=ht=hq=z
190 C Iterations: converge on z/l and hence the fluxes.
191
192 t0 = atemp(i,j,bi,bj)*
193 & (exf_one + humid_fac*aqh(i,j,bi,bj))
194 stable = exf_half + SIGN(exf_half, deltap)
195 c tmpbulk= exf_BulkCdn(sh(i,j,bi,bj))
196 tmpbulk= cdrag_1/wsm + cdrag_2 + cdrag_3*wsm
197 rdn = SQRT(tmpbulk)
198 C-- initial guess for exchange other coefficients:
199 c rhn = exf_BulkRhn(stable)
200 rhn = (exf_one-stable)*cstanton_1 + stable*cstanton_2
201 ren = cDalton
202 C-- calculate turbulent scales
203 ustar = rdn*wsm
204 tstar = rhn*deltap
205 qstar = ren*delq
206
207 DO iter = 1,niter_bulk
208
209 #ifdef ALLOW_AUTODIFF_TAMC
210 ikey_2 = iter
211 & + niter_bulk*(i-1)
212 & + niter_bulk*sNx*(j-1)
213 & + niter_bulk*sNx*sNy*act1
214 & + niter_bulk*sNx*sNy*max1*act2
215 & + niter_bulk*sNx*sNy*max1*max2*act3
216 & + niter_bulk*sNx*sNy*max1*max2*max3*act4
217
218 CADJ STORE rdn = comlev1_exf_2, key = ikey_2
219 CADJ STORE ustar = comlev1_exf_2, key = ikey_2
220 CADJ STORE qstar = comlev1_exf_2, key = ikey_2
221 CADJ STORE tstar = comlev1_exf_2, key = ikey_2
222 CADJ STORE sh(i,j,bi,bj) = comlev1_exf_2, key = ikey_2
223 #endif
224
225 huol = (tstar/t0 +
226 & qstar/(exf_one/humid_fac+aqh(i,j,bi,bj))
227 & )*czol/(ustar*ustar)
228 C- Large&Pond_1981 code (zolmin default = -100):
229 c huol = MAX(huol,zolmin)
230 C- Large&Yeager_2004 code:
231 huol = MIN( MAX(-10. _d 0,huol), 10. _d 0 )
232 htol = huol*ht/hu
233 hqol = huol*hq/hu
234 stable = exf_half + SIGN(exf_half, huol)
235
236 C Evaluate all stability functions assuming hq = ht.
237 C- Large&Pond_1981 code:
238 c xsq = MAX(SQRT(ABS(exf_one - huol*16. _d 0)),exf_one)
239 C- Large&Yeager_2004 code:
240 xsq = SQRT( ABS(exf_one - huol*16. _d 0) )
241 x = SQRT(xsq)
242 psimh = -psim_fac*huol*stable
243 & + (exf_one-stable)
244 & *( LOG( (exf_one + exf_two*x + xsq)
245 & *(exf_one+xsq)*0.125 _d 0 )
246 & -exf_two*ATAN(x) + exf_half*pi )
247 C- Large&Pond_1981 code:
248 c xsq = MAX(SQRT(ABS(exf_one - htol*16. _d 0)),exf_one)
249 C- Large&Yeager_2004 code:
250 xsq = SQRT( ABS(exf_one - htol*16. _d 0) )
251 psixh = -psim_fac*htol*stable
252 & + (exf_one-stable)
253 & *exf_two*LOG( exf_half*(exf_one+xsq) )
254
255 C Shift wind speed using old coefficient
256 usn = ws/( exf_one + rdn*(zwln-psimh)/karman )
257 usm = MAX(usn, umin)
258
259 C- Update the 10m, neutral stability transfer coefficients
260 c tmpbulk= exf_BulkCdn(usm)
261 tmpbulk= cdrag_1/usm + cdrag_2 + cdrag_3*usm
262 rdn = SQRT(tmpbulk)
263 c rhn = exf_BulkRhn(stable)
264 rhn = (exf_one-stable)*cstanton_1 + stable*cstanton_2
265
266 C Shift all coefficients to the measurement height and stability.
267 rd = rdn/( exf_one + rdn*(zwln-psimh)/karman )
268 rh = rhn/( exf_one + rhn*(ztln-psixh)/karman )
269 re = ren/( exf_one + ren*(ztln-psixh)/karman )
270
271 C Update ustar, tstar, qstar using updated, shifted coefficients.
272 ustar = rd*wsm
273 qstar = re*delq
274 tstar = rh*deltap
275 ENDDO
276
277 tau = atmrho*rd*ws
278
279 evapLoc = -tau*qstar
280 hlLocal = -lath*evapLoc
281 hsLocal = atmcp*tau*tstar
282 c ustress = tau*rd*UwindSpeed
283 c vstress = tau*rd*VwindSpeed
284
285 C--- surf.Temp derivative of turbulent Fluxes
286 dEvdT = (tau*re)*ssq*qsat_exp/Ts2
287 dflhdT = -lath*dEvdT
288 dfshdT = -atmcp*tau*rh
289
290 ELSE
291 C-- Compute the turbulent surface fluxes using fixed transfert Coeffs
292 C with no stability dependence ( useStabilityFct_overIce = false )
293
294 evapLoc = -atmrho*exf_iceCe*wsm*delq
295 hlLocal = -lath*evapLoc
296 hsLocal = atmcp*atmrho*exf_iceCh*wsm*deltap
297 C--- surf.Temp derivative of turbulent Fluxes
298 dEvdT = (atmrho*exf_iceCe*wsm)*(ssq*qsat_exp/Ts2)
299 dflhdT = -lath*dEvdT
300 dfshdT = -atmcp*atmrho*exf_iceCh*wsm
301
302 ENDIF
303 C--- Upward long wave radiation
304 IF ( iceornot.EQ.0 ) THEN
305 emiss = ocean_emissivity
306 ELSEIF (iceornot.EQ.2) THEN
307 emiss = snow_emissivity
308 ELSE
309 emiss = ice_emissivity
310 ENDIF
311 flwup = emiss*stefanBoltzmann*Ts2*Ts2
312 dflwupdT = emiss*stefanBoltzmann*Ts2*Tsf * 4. _d 0
313
314 C-- Total derivative with respect to surface temperature
315 df0dT = -dflwupdT+dfshdT+dflhdT
316
317 #ifdef ALLOW_DOWNWARD_RADIATION
318 c flwNet_dwn = lwdown(i,j,bi,bj) - flwup
319 C- assume long-wave albedo = 1 - emissivity :
320 flwNet_dwn = emiss*lwdown(i,j,bi,bj) - flwup
321 #else
322 STOP 'ABNORMAL END: S/R THSICE_GET_EXF: DOWNWARD_RADIATION undef'
323 #endif
324 flxExceptSw = flwNet_dwn + hsLocal + hlLocal
325
326 ELSE
327 flxExceptSw = 0. _d 0
328 df0dT = 0. _d 0
329 evapLoc = 0. _d 0
330 dEvdT = 0. _d 0
331 ENDIF
332
333 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
334
335 #else /* ALLOW_ATM_TEMP */
336 STOP 'ABNORMAL END: S/R THSICE_GET_EXF: ATM_TEMP undef'
337 #endif /* ALLOW_ATM_TEMP */
338 #ifdef EXF_READ_EVAP
339 STOP 'ABNORMAL END: S/R THSICE_GET_EXF: EXF_READ_EVAP defined'
340 #endif /* EXF_READ_EVAP */
341 #endif /* ALLOW_EXF */
342
343 RETURN
344 END

  ViewVC Help
Powered by ViewVC 1.1.22