/[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.9 - (show annotations) (download)
Mon May 7 19:26:57 2007 UTC (17 years ago) by jmc
Branch: MAIN
Changes since 1.8: +129 -111 lines
- little rewriting to get closer to exf_bulk_largeyeager04.F
- use ice/snow emissivity for downward longwave (as well as
  upward lw). This results in significant changes in the output.

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

  ViewVC Help
Powered by ViewVC 1.1.22