/[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.2 - (show annotations) (download)
Tue Jun 6 18:52:13 2006 UTC (18 years ago) by mlosch
Branch: MAIN
Changes since 1.1: +2 -2 lines
 fix an indexing bug

1 C $Header: /u/gcmpack/MITgcm/pkg/thsice/thsice_get_exf.F,v 1.1 2006/05/30 22:49:00 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, Tsf,
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
37 C !INPUT/OUTPUT PARAMETERS:
38 C === Routine arguments ===
39 C iceornot :: 0=open water, 1=ice cover
40 C Tsf :: surface (ice or snow) temperature (oC)
41 C flxExceptSw :: net (downward) surface heat flux, except short-wave [W/m2]
42 C df0dT :: deriv of flx with respect to Tsf [W/m/K]
43 C evapLoc :: surface evaporation (>0 if evaporate) [kg/m2/s]
44 C dEvdT :: deriv of evap. with respect to Tsf [kg/m2/s/K]
45 C i,j, bi,bj :: current grid point indices
46 C myThid :: Thread no. that called this routine.
47 INTEGER i,j, bi,bj
48 INTEGER myThid
49 INTEGER iceornot
50 _RL Tsf
51 _RL flxExceptSw
52 _RL df0dT
53 _RL evapLoc
54 _RL dEvdT
55 CEOP
56
57 #ifdef ALLOW_THSICE
58 #ifdef ALLOW_EXF
59
60 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
61 C === Local variables ===
62
63 _RL aln
64
65 #ifdef ALLOW_ATM_TEMP
66 integer iter
67 _RL delq
68 _RL deltap
69 _RL hqol
70 _RL htol
71 _RL huol
72 _RL psimh
73 _RL psixh
74 _RL qstar
75 _RL rd
76 _RL re
77 _RL rdn
78 _RL rh
79 _RL ssttmp
80 _RL ssq
81 _RL stable
82 _RL tstar
83 _RL t0
84 _RL ustar
85 _RL uzn
86 _RL shn
87 _RL xsq
88 _RL x
89 _RL tau
90 #ifdef ALLOW_AUTODIFF_TAMC
91 integer ikey_1
92 integer ikey_2
93 #endif
94 #endif /* ALLOW_ATM_TEMP */
95
96 _RL tmpbulk
97
98 C additional variables that are copied from bulkf_formula_lay:
99 C upward LW at surface (W m-2)
100 _RL flwup
101 C net (downward) LW at surface (W m-2)
102 _RL flwNet_dwn
103 C gradients of latent/sensible net upward heat flux
104 C w/ respect to temperature
105 _RL dflhdT, dfshdT, dflwupdT
106 C emissivities, called emittance in exf
107 _RL emiss
108 C abbreviation
109 _RL Ts2
110 C latent heat, of evaporation at 0degC, ice melt [J/kg]
111 _RL lath, Lvap, Lfresh
112 C above and below freezing saturated specific humidity
113 _RL qs2w, qs2i
114
115 c == external functions ==
116
117 integer ilnblnk
118 external ilnblnk
119
120 _RL exf_BulkqSat
121 external exf_BulkqSat
122 _RL exf_BulkCdn
123 external exf_BulkCdn
124 _RL exf_BulkRhn
125 external exf_BulkRhn
126
127 c == end of interface ==
128
129 C copy a few variables to names used in bulkf_formula_lay
130 qs2w = cvapor_exp
131 qs2i = cvapor_exp_ice
132 Lvap = flamb
133 Lfresh = flami
134 Ts2 = (Tsf+cen2kel)*(Tsf+cen2kel)
135
136 C This is more or less a copy from exf_bulkformulae (loops kernel)
137
138 cph This statement cannot be a PARAMETER statement in the header,
139 cph but must come here; it is not fortran77 standard
140 aln = log(ht/zref)
141
142 c-- Use atmospheric state to compute surface fluxes.
143
144 CMLc Loop over tiles.
145 CML#ifdef ALLOW_AUTODIFF_TAMC
146 CMLC-- HPF directive to help TAMC
147 CMLCHPF$ INDEPENDENT
148 CML#endif
149 CML do bj = mybylo(mythid),mybyhi(mythid)
150 CML#ifdef ALLOW_AUTODIFF_TAMC
151 CMLC-- HPF directive to help TAMC
152 CMLCHPF$ INDEPENDENT
153 CML#endif
154 CML do bi = mybxlo(mythid),mybxhi(mythid)
155 CML k = 1
156 CML do j = 1,sny
157 CML do i = 1,snx
158
159 #ifdef ALLOW_AUTODIFF_TAMC
160 act1 = bi - myBxLo(myThid)
161 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
162 act2 = bj - myByLo(myThid)
163 max2 = myByHi(myThid) - myByLo(myThid) + 1
164 act3 = myThid - 1
165 max3 = nTx*nTy
166 act4 = ikey_dynamics - 1
167
168 ikey_1 = i
169 & + sNx*(j-1)
170 & + sNx*sNy*act1
171 & + sNx*sNy*max1*act2
172 & + sNx*sNy*max1*max2*act3
173 & + sNx*sNy*max1*max2*max3*act4
174 #endif
175
176 c-- Compute the turbulent surface fluxes.
177
178 #ifdef ALLOW_ATM_TEMP
179
180 c Initial guess: z/l=0.0; hu=ht=hq=z
181 c Iterations: converge on z/l and hence the fluxes.
182 c t0 : virtual temperature (K)
183 c ssq : sea surface humidity (kg/kg)
184 c deltap : potential temperature diff (K)
185
186 if ( atemp(i,j,bi,bj) .ne. 0. _d 0 ) then
187 t0 = atemp(i,j,bi,bj)*
188 & (exf_one + humid_fac*aqh(i,j,bi,bj))
189 CML ssttmp = theta(i,j,k,bi,bj)
190 ssttmp = Tsf
191 tmpbulk= exf_BulkqSat(ssttmp + cen2kel)
192 ssq = saltsat*tmpbulk/atmrho
193 deltap = atemp(i,j,bi,bj) + gamma_blk*ht -
194 & ssttmp - cen2kel
195 delq = aqh(i,j,bi,bj) - ssq
196 stable = exf_half + sign(exf_half, deltap)
197 #ifdef ALLOW_AUTODIFF_TAMC
198 CADJ STORE sh(i,j,bi,bj) = comlev1_exf_1, key = ikey_1
199 #endif
200 tmpbulk= exf_BulkCdn(sh(i,j,bi,bj))
201 rdn = sqrt(tmpbulk)
202 ustar = rdn*sh(i,j,bi,bj)
203 tmpbulk= exf_BulkRhn(stable)
204 tstar = tmpbulk*deltap
205 qstar = cdalton*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 CADJ STORE us(i,j,bi,bj) = comlev1_exf_2, key = ikey_2
224 #endif
225
226 huol = czol*(tstar/t0 +
227 & qstar/(exf_one/humid_fac+aqh(i,j,bi,bj)))/
228 & ustar**2
229 huol = max(huol,zolmin)
230 stable = exf_half + sign(exf_half, huol)
231 htol = huol*ht/hu
232 hqol = huol*hq/hu
233
234 c Evaluate all stability functions assuming hq = ht.
235 xsq = max(sqrt(abs(exf_one - 16.*huol)),exf_one)
236 x = sqrt(xsq)
237 psimh = -psim_fac*huol*stable +
238 & (exf_one - stable)*
239 & (log((exf_one + x*(exf_two + x))*
240 & (exf_one + xsq)/8.) - exf_two*atan(x) +
241 & pi*exf_half)
242 xsq = max(sqrt(abs(exf_one - 16.*htol)),exf_one)
243 psixh = -psim_fac*htol*stable + (exf_one - stable)*
244 & exf_two*log((exf_one + xsq)/exf_two)
245
246 c Shift wind speed using old coefficient
247 ccc rd = rdn/(exf_one + rdn/karman*
248 ccc & (log(hu/zref) - psimh) )
249 rd = rdn/(exf_one - rdn/karman*psimh )
250 shn = sh(i,j,bi,bj)*rd/rdn
251 uzn = max(shn, umin)
252
253 c Update the transfer coefficients at 10 meters
254 c and neutral stability.
255
256 tmpbulk= exf_BulkCdn(uzn)
257 rdn = sqrt(tmpbulk)
258
259 c Shift all coefficients to the measurement height
260 c and stability.
261 c rd = rdn/(exf_one + rdn/karman*(log(hu/zref) - psimh))
262 rd = rdn/(exf_one - rdn/karman*psimh)
263 tmpbulk= exf_BulkRhn(stable)
264 rh = tmpbulk/( exf_one +
265 & tmpbulk/karman*(aln - psixh) )
266 re = cdalton/( exf_one +
267 & cdalton/karman*(aln - psixh) )
268
269 c Update ustar, tstar, qstar using updated, shifted
270 c coefficients.
271 ustar = rd*sh(i,j,bi,bj)
272 qstar = re*delq
273 tstar = rh*deltap
274 tau = atmrho*ustar**2
275 tau = tau*us(i,j,bi,bj)/sh(i,j,bi,bj)
276
277 enddo
278
279 #ifdef ALLOW_AUTODIFF_TAMC
280 CADJ STORE ustar = comlev1_exf_1, key = ikey_1
281 CADJ STORE qstar = comlev1_exf_1, key = ikey_1
282 CADJ STORE tstar = comlev1_exf_1, key = ikey_1
283 CADJ STORE tau = comlev1_exf_1, key = ikey_1
284 CADJ STORE cw(i,j,bi,bj) = comlev1_exf_1, key = ikey_1
285 CADJ STORE sw(i,j,bi,bj) = comlev1_exf_1, key = ikey_1
286 #endif
287
288 hs(i,j,bi,bj) = atmcp*tau*tstar/ustar
289 hl(i,j,bi,bj) = flamb*tau*qstar/ustar
290 #ifndef EXF_READ_EVAP
291 cdm evap(i,j,bi,bj) = tau*qstar/ustar
292 cdm !!! need to change sign and to convert from kg/m^2/s to m/s !!!
293 evap(i,j,bi,bj) = -recip_rhonil*tau*qstar/ustar
294 #endif
295
296 C From here one this is pretty much a copy of parts of
297 C bulkf_formula_lay and thsice_get_bulkf to compute the required outputs
298
299 C--- surf.Temp derivative of turbulent Fluxes
300 C--- Compute turbulent surface fluxes
301 C--- Pot. Temp and saturated specific humidity
302 IF ( iceornot.EQ.0 ) THEN
303 lath = Lvap
304 dEvdT = qs2w
305 ELSE
306 lath = Lvap+Lfresh
307 dEvdT = qs2i
308 ENDIF
309 dEvdT = tau*re*ssq*dEvdT/Ts2
310 dflhdT = -lath*dEvdT
311 dfshdT = -atmcp*tau*rh
312
313 C--- Upward long wave radiation
314 IF ( iceornot.EQ.0 ) THEN
315 emiss = ocean_emissivity
316 ELSEIF (iceornot.EQ.2) THEN
317 emiss = snow_emissivity
318 ELSE
319 emiss = ice_emissivity
320 ENDIF
321 flwup = emiss*stefanBoltzmann*Ts2*Ts2
322 dflwupdT = emiss*stefanBoltzmann*Ts2*(Tsf+cen2kel) * 4. _d 0
323
324 C-- Total derivative with respect to surface temperature
325 df0dT = -dflwupdT+dfshdT+dflhdT
326
327 flwNet_dwn = lwdown(i,j,bi,bj) - flwup
328 flxExceptSw = flwNet_dwn + hs(i,j,bi,bj) + hl(i,j,bi,bj)
329 C
330 evapLoc = evap(i,j,bi,bj)*rhoNil
331 C This is where the copies from bulkf_formula_lay and thsice_get_bulkf
332 C end
333
334 CML ustress(i,j,bi,bj) = tau*cw(i,j,bi,bj)
335 CML vstress(i,j,bi,bj) = tau*sw(i,j,bi,bj)
336 CML else
337 CML ustress(i,j,bi,bj) = 0. _d 0
338 CML vstress(i,j,bi,bj) = 0. _d 0
339 CML hflux (i,j,bi,bj) = 0. _d 0
340 CML hs(i,j,bi,bj) = 0. _d 0
341 CML hl(i,j,bi,bj) = 0. _d 0
342
343 endif
344
345 #else /* ifndef ALLOW_ATM_TEMP */
346 CML#ifdef ALLOW_ATM_WIND
347 CML tmpbulk= exf_BulkCdn(sh(i,j,bi,bj))
348 CML ustress(i,j,bi,bj) = atmrho*tmpbulk*us(i,j,bi,bj)*
349 CML & uwind(i,j,bi,bj)
350 CML vstress(i,j,bi,bj) = atmrho*tmpbulk*us(i,j,bi,bj)*
351 CML & vwind(i,j,bi,bj)
352 CML#endif
353 #endif /* ifndef ALLOW_ATM_TEMP */
354 CML enddo
355 CML enddo
356 CML enddo
357 CML enddo
358
359 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
360
361 #endif /* ALLOW_EXF */
362 #endif /* ALLOW_THSICE */
363
364 RETURN
365 END

  ViewVC Help
Powered by ViewVC 1.1.22