/[MITgcm]/MITgcm/pkg/exf/exf_bulk_largeyeager04.F
ViewVC logotype

Contents of /MITgcm/pkg/exf/exf_bulk_largeyeager04.F

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


Revision 1.11 - (show annotations) (download)
Fri May 21 10:13:57 2010 UTC (13 years, 11 months ago) by mlosch
Branch: MAIN
CVS Tags: HEAD
Changes since 1.10: +1 -1 lines
FILE REMOVED
merge exf_bulkformulae and exf_bulk_largeyeager04:
end of Step2: remove exf_bulk_largeyeager04.F

1 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_bulk_largeyeager04.F,v 1.10 2010/05/21 09:58:21 mlosch Exp $
2 C $Name: $
3
4 #include "EXF_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: EXF_BULK_LARGEYEAGER04
8 C !INTERFACE:
9 SUBROUTINE EXF_BULK_LARGEYEAGER04( myTime, myIter, myThid )
10
11 C !DESCRIPTION: \bv
12 C *==========================================================*
13 C | SUBROUTINE EXF_BULK_LARGEYEAGER04
14 C | o Calculate bulk formula fluxes over open ocean or seaice
15 C | Large and Yeager, 2004, NCAR/TN-460+STR.
16 C *==========================================================*
17 C \ev
18 C
19 C === Turbulent Fluxes :
20 C * use the approach "B": shift coeff to height & stability of the
21 C atmosphere state (instead of "C": shift temp & humid to the height
22 C of wind, then shift the coeff to this height & stability of the atmos).
23 C * similar to EXF (except over sea-ice) ; default parameter values
24 C taken from Large & Yeager.
25 C * assume that Qair & Tair inputs are from the same height (zq=zt)
26 C * formulae in short:
27 C wind stress = (ust,vst) = rhoA * Cd * Ws * (del.u,del.v)
28 C Sensib Heat flux = fsha = rhoA * Ch * Ws * del.T * CpAir
29 C Latent Heat flux = flha = rhoA * Ce * Ws * del.Q * Lvap
30 C = -Evap * Lvap
31 C with Ws = wind speed = sqrt(del.u^2 +del.v^2) ;
32 C del.T = Tair - Tsurf ; del.Q = Qair - Qsurf ;
33 C Cd,Ch,Ce = drag coefficient, Stanton number and Dalton number
34 C respectively [no-units], function of height & stability
35
36 C !USES:
37 IMPLICIT NONE
38 C === Global variables ===
39 #include "EEPARAMS.h"
40 #include "SIZE.h"
41 #include "PARAMS.h"
42 #include "DYNVARS.h"
43 #include "GRID.h"
44
45 #include "EXF_PARAM.h"
46 #include "EXF_FIELDS.h"
47 #include "EXF_CONSTANTS.h"
48
49 #ifdef ALLOW_AUTODIFF_TAMC
50 #include "tamc.h"
51 #endif
52
53 C !INPUT/OUTPUT PARAMETERS:
54 C input:
55 C myTime :: Current time in simulation
56 C myIter :: Current iteration number in simulation
57 C myThid :: My Thread Id number
58 _RL myTime
59 INTEGER myIter
60 INTEGER myThid
61 C output:
62 CEOP
63
64 #ifdef ALLOW_BULK_LARGEYEAGER04
65
66 C == external Functions
67
68 C == Local variables ==
69 C i,j :: grid point indices
70 C bi,bj :: tile indices
71 C ssq :: saturation specific humidity [kg/kg] in eq. with Sea-Surface water
72 INTEGER i,j,bi,bj
73
74 _RL czol
75 _RL Tsf ! surface temperature [K]
76 _RL wsm ! limited wind speed [m/s] (> umin)
77 _RL t0 ! virtual temperature [K]
78 C these need to be 2D-arrays for vectorizing code
79 _RL tstar (1:sNx,1:sNy) ! turbulent temperature scale [K]
80 _RL qstar (1:sNx,1:sNy) ! turbulent humidity scale [kg/kg]
81 _RL ustar (1:sNx,1:sNy) ! friction velocity [m/s]
82 _RL tau (1:sNx,1:sNy) ! surface stress coef = rhoA * Ws * sqrt(Cd)
83 _RL rdn (1:sNx,1:sNy) ! neutral, zref (=10m) values of rd
84 _RL rd (1:sNx,1:sNy) ! = sqrt(Cd) [-]
85 _RL delq (1:sNx,1:sNy) ! specific humidity difference [kg/kg]
86 _RL deltap(1:sNx,1:sNy)
87 C
88 _RL dzTmp
89 _RL SSTtmp
90 _RL ssq
91 _RL re ! = Ce / sqrt(Cd) [-]
92 _RL rh ! = Ch / sqrt(Cd) [-]
93 _RL ren, rhn ! neutral, zref (=10m) values of re, rh
94 _RL usn, usm
95 _RL stable ! = 1 if stable ; = 0 if unstable
96 _RL huol ! stability parameter at zwd [-] (=z/Monin-Obuklov length)
97 _RL htol ! stability parameter at zth [-]
98 _RL hqol
99 _RL x ! stability function [-]
100 _RL xsq ! = x^2 [-]
101 _RL psimh ! momentum stability function
102 _RL psixh ! latent & sensib. stability function
103 _RL zwln ! = log(zwd/zref)
104 _RL ztln ! = log(zth/zref)
105 _RL windStress ! surface wind-stress (@ grid cell center)
106 _RL tmpbulk
107 INTEGER iter
108 C solve4Stress :: if F, by-pass momentum turb. flux (wind-stress) calculation
109 LOGICAL solve4Stress
110 #ifdef ALLOW_ATM_WIND
111 PARAMETER ( solve4Stress = .TRUE. )
112 #endif
113
114 #ifdef ALLOW_AUTODIFF_TAMC
115 integer ikey_1
116 integer ikey_2
117 #endif
118
119 #ifndef ALLOW_ATM_WIND
120 solve4Stress = wspeedfile .NE. ' '
121 #endif
122
123 C-- Set surface parameters :
124 zwln = LOG(hu/zref)
125 ztln = LOG(ht/zref)
126 czol = hu*karman*gravity_mks
127
128 c Loop over tiles.
129 #ifdef ALLOW_AUTODIFF_TAMC
130 C-- HPF directive to help TAMC
131 CHPF$ INDEPENDENT
132 #endif
133 DO bj = myByLo(myThid),myByHi(myThid)
134 #ifdef ALLOW_AUTODIFF_TAMC
135 C-- HPF directive to help TAMC
136 CHPF$ INDEPENDENT
137 #endif
138 DO bi = myBxLo(myThid),myBxHi(myThid)
139 DO j = 1,sNy
140 DO i = 1,sNx
141
142 #ifdef ALLOW_AUTODIFF_TAMC
143 act1 = bi - myBxLo(myThid)
144 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
145 act2 = bj - myByLo(myThid)
146 max2 = myByHi(myThid) - myByLo(myThid) + 1
147 act3 = myThid - 1
148 max3 = nTx*nTy
149 act4 = ikey_dynamics - 1
150
151 ikey_1 = i
152 & + sNx*(j-1)
153 & + sNx*sNy*act1
154 & + sNx*sNy*max1*act2
155 & + sNx*sNy*max1*max2*act3
156 & + sNx*sNy*max1*max2*max3*act4
157 #endif
158
159 #ifdef ALLOW_ATM_TEMP
160
161 #ifdef ALLOW_AUTODIFF_TAMC
162 deltap(i,j) = 0. _d 0
163 delq(i,j) = 0. _d 0
164 #endif
165 C--- Compute turbulent surface fluxes
166 C- Pot. Temp and saturated specific humidity
167 IF ( atemp(i,j,bi,bj) .NE. 0. _d 0 ) THEN
168 C- Surface Temp.
169 Tsf = theta(i,j,1,bi,bj) + cen2kel
170 IF ( sstExtrapol.GT.0. _d 0 ) THEN
171 SSTtmp = sstExtrapol
172 & *( theta(i,j,1,bi,bj)-theta(i,j,2,bi,bj) )
173 & * maskC(i,j,2,bi,bj)
174 Tsf = Tsf + MAX( SSTtmp, 0. _d 0 )
175 ENDIF
176 c
177 tmpbulk = cvapor_fac*exp(-cvapor_exp/Tsf)
178 ssq = saltsat*tmpbulk/atmrho
179 deltap(i,j) = atemp(i,j,bi,bj) + gamma_blk*ht - Tsf
180 delq(i,j) = aqh(i,j,bi,bj) - ssq
181 C-- no negative evaporation over ocean:
182 IF ( noNegativeEvap ) delq(i,j) = MIN( 0. _d 0, delq(i,j) )
183
184 C-- initial guess for exchange coefficients:
185 C take U_N = del.U ; stability from del.Theta ;
186 stable = exf_half + SIGN(exf_half, deltap(i,j))
187
188 #ifndef ALLOW_ATM_WIND
189 IF ( solve4Stress ) THEN
190 #endif
191 #ifdef ALLOW_AUTODIFF_TAMC
192 CADJ STORE sh(i,j,bi,bj) = comlev1_exf_1, key = ikey_1
193 #endif /* ALLOW_AUTODIFF_TAMC */
194 C-- Wind speed
195 wsm = sh(i,j,bi,bj)
196 tmpbulk = exf_scal_BulkCdn *
197 & ( cdrag_1/wsm + cdrag_2 + cdrag_3*wsm )
198 rdn(i,j) = SQRT(tmpbulk)
199 ustar(i,j) = rdn(i,j)*wsm
200 #ifndef ALLOW_ATM_WIND
201 ELSE
202 windStress = wStress(i,j,bi,bj)
203 ustar(i,j) = sqrt(windStress/atmrho)
204 c tau(i,j) = windStress/ustar(i,j)
205 tau(i,j) = sqrt(windStress*atmrho)
206 ENDIF
207 #endif /* ALLOW_ATM_WIND */
208
209 C-- initial guess for exchange other coefficients:
210 rhn = (exf_one-stable)*cstanton_1 + stable*cstanton_2
211 ren = cDalton
212 C-- calculate turbulent scales
213 tstar(i,j)=rhn*deltap(i,j)
214 qstar(i,j)=ren*delq(i,j)
215
216 ELSE
217 C atemp(i,j,bi,bj) .EQ. 0.
218 tstar (i,j) = 0. _d 0
219 qstar (i,j) = 0. _d 0
220 ustar (i,j) = 0. _d 0
221 tau (i,j) = 0. _d 0
222 rdn (i,j) = 0. _d 0
223 ENDIF
224 ENDDO
225 ENDDO
226 DO iter=1,niter_bulk
227 DO j = 1,sNy
228 DO i = 1,sNx
229 IF ( atemp(i,j,bi,bj) .NE. 0. _d 0 ) THEN
230 C--- iterate with psi-functions to find transfer coefficients
231
232 #ifdef ALLOW_AUTODIFF_TAMC
233 ikey_2 = i
234 & + sNx*(j-1)
235 & + sNx*sNy*(iter-1)
236 & + sNx*sNy*niter_bulk*act1
237 & + sNx*sNy*niter_bulk*max1*act2
238 & + sNx*sNy*niter_bulk*max1*max2*act3
239 & + sNx*sNy*niter_bulk*max1*max2*max3*act4
240 CADJ STORE rdn(i,j) = comlev1_exf_2, key = ikey_2
241 CADJ STORE ustar(i,j) = comlev1_exf_2, key = ikey_2
242 CADJ STORE qstar(i,j) = comlev1_exf_2, key = ikey_2
243 CADJ STORE tstar(i,j) = comlev1_exf_2, key = ikey_2
244 CADJ STORE sh(i,j,bi,bj) = comlev1_exf_2, key = ikey_2
245 CADJ STORE wspeed(i,j,bi,bj) = comlev1_exf_2, key = ikey_2
246 #endif
247
248 t0 = atemp(i,j,bi,bj)*
249 & (exf_one + humid_fac*aqh(i,j,bi,bj))
250 huol = ( tstar(i,j)/t0 +
251 & qstar(i,j)/(exf_one/humid_fac+aqh(i,j,bi,bj))
252 & )*czol/(ustar(i,j)*ustar(i,j))
253 cph The following is different in Large&Pond1981 code:
254 cph huol = max(huol,zolmin) with zolmin = -100
255 tmpbulk = MIN(abs(huol),10. _d 0)
256 huol = SIGN(tmpbulk , huol)
257 htol = huol*ht/hu
258 hqol = huol*hq/hu
259 stable = exf_half + sign(exf_half, huol)
260
261 c Evaluate all stability functions assuming hq = ht.
262 #ifndef ALLOW_ATM_WIND
263 IF ( solve4Stress ) THEN
264 #endif
265 cph The following is different in Large&Pond1981 code:
266 cph xsq = max(sqrt(abs(exf_one - 16.*huol)),exf_one)
267 xsq = SQRT( ABS(exf_one - huol*16. _d 0) )
268 x = SQRT(xsq)
269 psimh = -psim_fac*huol*stable
270 & +(exf_one-stable)*
271 & ( LOG( (exf_one + exf_two*x + xsq)*
272 & (exf_one+xsq)*.125 _d 0 )
273 & -exf_two*ATAN(x) + exf_half*pi )
274 #ifndef ALLOW_ATM_WIND
275 ENDIF
276 #endif
277 cph The following is different in Large&Pond1981 code:
278 cph xsq = max(sqrt(abs(exf_one - 16.*htol)),exf_one)
279 xsq = SQRT( ABS(exf_one - htol*16. _d 0) )
280 psixh = -psim_fac*htol*stable + (exf_one-stable)*
281 & ( exf_two*LOG(exf_half*(exf_one+xsq)) )
282
283 #ifndef ALLOW_ATM_WIND
284 IF ( solve4Stress ) THEN
285 #endif
286 C- Shift wind speed using old coefficient
287 dzTmp = (zwln-psimh)/karman
288 usn = wspeed(i,j,bi,bj)
289 & /(exf_one + rdn(i,j)*dzTmp )
290 usm = MAX(usn, umin)
291
292 C- Update the 10m, neutral stability transfer coefficients (momentum)
293 tmpbulk = exf_scal_BulkCdn *
294 & ( cdrag_1/usm + cdrag_2 + cdrag_3*usm )
295 rdn(i,j) = SQRT(tmpbulk)
296 rd(i,j) = rdn(i,j)/(exf_one + rdn(i,j)*dzTmp)
297 ustar(i,j) = rd(i,j)*sh(i,j,bi,bj)
298 C- Coeff:
299 tau(i,j) = atmrho*rd(i,j)*wspeed(i,j,bi,bj)
300 #ifndef ALLOW_ATM_WIND
301 ENDIF
302 #endif
303
304 C- Update the 10m, neutral stability transfer coefficients (sens&evap)
305 rhn = (exf_one-stable)*cstanton_1 + stable*cstanton_2
306 ren = cDalton
307
308 C- Shift all coefficients to the measurement height and stability.
309 rh = rhn/(exf_one + rhn*(ztln-psixh)/karman)
310 re = ren/(exf_one + ren*(ztln-psixh)/karman)
311
312 C-- Update ustar, tstar, qstar using updated, shifted coefficients.
313 qstar(i,j) = re*delq(i,j)
314 tstar(i,j) = rh*deltap(i,j)
315
316 ENDIF
317 ENDDO
318 ENDDO
319 c end of iteration loop
320 ENDDO
321 DO j = 1,sNy
322 DO i = 1,sNx
323 IF ( atemp(i,j,bi,bj) .NE. 0. _d 0 ) THEN
324
325 #ifdef ALLOW_AUTODIFF_TAMC
326 ikey_1 = i
327 & + sNx*(j-1)
328 & + sNx*sNy*act1
329 & + sNx*sNy*max1*act2
330 & + sNx*sNy*max1*max2*act3
331 & + sNx*sNy*max1*max2*max3*act4
332 CADJ STORE qstar(i,j) = comlev1_exf_1, key = ikey_1
333 CADJ STORE tstar(i,j) = comlev1_exf_1, key = ikey_1
334 CADJ STORE tau(i,j) = comlev1_exf_1, key = ikey_1
335 CADJ STORE rd(i,j) = comlev1_exf_1, key = ikey_1
336 #endif
337
338 C- Turbulent Fluxes
339 hs(i,j,bi,bj) = atmcp*tau(i,j)*tstar(i,j)
340 hl(i,j,bi,bj) = flamb*tau(i,j)*qstar(i,j)
341 #ifndef EXF_READ_EVAP
342 C change sign and convert from kg/m^2/s to m/s via rhoConstFresh
343 C but older version was using rhonil instead:
344 c evap(i,j,bi,bj) = -recip_rhonil*tau(i,j)*qstar(i,j)
345 evap(i,j,bi,bj) = -tau(i,j)*qstar(i,j)/rhoConstFresh
346 #endif
347 #ifdef ALLOW_ATM_WIND
348 c ustress(i,j,bi,bj) = tau(i,j)*rd(i,j)*ws*cw(i,j,bi,bj)
349 c vstress(i,j,bi,bj) = tau(i,j)*rd(i,j)*ws*sw(i,j,bi,bj)
350 C- jmc: below is how it should be written ; different from above when
351 C both wind-speed & 2 compon. of the wind are specified, and in
352 C- this case, formula below is better.
353 ustress(i,j,bi,bj) = tau(i,j)*rd(i,j)*uwind(i,j,bi,bj)
354 vstress(i,j,bi,bj) = tau(i,j)*rd(i,j)*vwind(i,j,bi,bj)
355 #endif
356
357 c IF ( ATEMP(i,j,bi,bj) .NE. 0. )
358 else
359 #ifdef ALLOW_ATM_WIND
360 ustress(i,j,bi,bj) = 0. _d 0
361 vstress(i,j,bi,bj) = 0. _d 0
362 #endif /* ALLOW_ATM_WIND */
363 hflux (i,j,bi,bj) = 0. _d 0
364 evap (i,j,bi,bj) = 0. _d 0
365 hs (i,j,bi,bj) = 0. _d 0
366 hl (i,j,bi,bj) = 0. _d 0
367
368 c IF ( ATEMP(i,j,bi,bj) .NE. 0. )
369 endif
370
371 #else /* ifndef ALLOW_ATM_TEMP */
372 #ifdef ALLOW_ATM_WIND
373 wsm = sh(i,j,bi,bj)
374 tmpbulk = exf_scal_BulkCdn *
375 & ( cdrag_1/wsm + cdrag_2 + cdrag_3*wsm )
376 ustress(i,j,bi,bj) = atmrho*tmpbulk*wspeed(i,j,bi,bj)*
377 & uwind(i,j,bi,bj)
378 vstress(i,j,bi,bj) = atmrho*tmpbulk*wspeed(i,j,bi,bj)*
379 & vwind(i,j,bi,bj)
380 #endif
381 #endif /* ifndef ALLOW_ATM_TEMP */
382 ENDDO
383 ENDDO
384 ENDDO
385 ENDDO
386
387 #endif /* ALLOW_BULK_LARGEYEAGER04 */
388
389 RETURN
390 END

  ViewVC Help
Powered by ViewVC 1.1.22