/[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.3 - (show annotations) (download)
Mon May 14 14:03:50 2007 UTC (17 years, 1 month ago) by jmc
Branch: MAIN
Changes since 1.2: +10 -9 lines
-fix typo (so that it compiles)
-fix #undef ALLOW_ATM_WIND case

1 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_bulk_largeyeager04.F,v 1.2 2007/05/07 19:35:20 jmc 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 == Local variables ==
67 C i,j :: grid point indices
68 C bi,bj :: tile indices
69 C ssq :: saturation specific humidity [kg/kg] in eq. with Sea-Surface water
70 INTEGER i,j,bi,bj
71
72 _RL czol
73 _RL Tsf ! surface temperature [K]
74 _RL Ts2 ! surface temperature square [K^2]
75 _RL ws
76 _RL wsm ! limited wind speed [m/s] (> umin)
77 _RL t0 ! virtual temperature [K]
78 _RL delq ! specific humidity difference [kg/kg]
79 _RL deltap
80 _RL ustar ! friction velocity [m/s]
81 _RL tstar ! turbulent temperature scale [K]
82 _RL qstar ! turbulent humidity scale [kg/kg]
83 _RL ssttmp
84 _RL ssq
85 _RL rd ! = sqrt(Cd) [-]
86 _RL re ! = Ce / sqrt(Cd) [-]
87 _RL rh ! = Ch / sqrt(Cd) [-]
88 _RL rdn, ren, rhn ! neutral, zref (=10m) values of rd, re, rh
89 _RL usn, usm
90 _RL stable ! = 1 if stable ; = 0 if unstable
91 _RL huol ! stability parameter at zwd [-] (=z/Monin-Obuklov length)
92 _RL htol ! stability parameter at zth [-]
93 _RL hqol
94 _RL x ! stability function [-]
95 _RL xsq ! = x^2 [-]
96 _RL psimh ! momentum stability function
97 _RL psixh ! latent & sensib. stability function
98 _RL zwln ! = log(zwd/zref)
99 _RL ztln ! = log(zth/zref)
100 _RL tau ! surface stress coef = rhoA * Ws * sqrt(Cd)
101 _RL windStress ! surface wind-stress (@ grid cell center)
102 _RL tmpbulk
103 INTEGER iter
104
105 #ifdef ALLOW_AUTODIFF_TAMC
106 integer ikey_1
107 integer ikey_2
108 #endif
109
110 C == external Functions
111
112 C-- Set surface parameters :
113 zwln = LOG(hu/zref)
114 ztln = LOG(ht/zref)
115 czol = hu*karman*gravity_mks
116
117 c Loop over tiles.
118 #ifdef ALLOW_AUTODIFF_TAMC
119 C-- HPF directive to help TAMC
120 CHPF$ INDEPENDENT
121 #endif
122 DO bj = myByLo(myThid),myByHi(myThid)
123 #ifdef ALLOW_AUTODIFF_TAMC
124 C-- HPF directive to help TAMC
125 CHPF$ INDEPENDENT
126 #endif
127 DO bi = myBxLo(myThid),myBxHi(myThid)
128 DO j = 1,sNy
129 DO i = 1,sNx
130
131 #ifdef ALLOW_AUTODIFF_TAMC
132 act1 = bi - myBxLo(myThid)
133 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
134 act2 = bj - myByLo(myThid)
135 max2 = myByHi(myThid) - myByLo(myThid) + 1
136 act3 = myThid - 1
137 max3 = nTx*nTy
138 act4 = ikey_dynamics - 1
139
140 ikey_1 = i
141 & + sNx*(j-1)
142 & + sNx*sNy*act1
143 & + sNx*sNy*max1*act2
144 & + sNx*sNy*max1*max2*act3
145 & + sNx*sNy*max1*max2*max3*act4
146 #endif
147
148 #ifdef ALLOW_ATM_TEMP
149
150 C- Surface Temp.
151 ssttmp = theta(i,j,1,bi,bj)
152 Tsf = ssttmp + cen2kel
153 Ts2 = Tsf*Tsf
154 C- Wind speed
155 ws = us(i,j,bi,bj)
156 wsm = sh(i,j,bi,bj)
157
158 C--- Compute turbulent surface fluxes
159 C- Pot. Temp and saturated specific humidity
160 if ( atemp(i,j,bi,bj) .NE. 0. _d 0 ) then
161 c
162 t0 = atemp(i,j,bi,bj)*
163 & (exf_one + humid_fac*aqh(i,j,bi,bj))
164 tmpbulk = cvapor_fac*exp(-cvapor_exp/Tsf)
165 ssq = saltsat*tmpbulk/atmrho
166 deltap = atemp(i,j,bi,bj) + gamma_blk*ht - Tsf
167 delq = aqh(i,j,bi,bj) - ssq
168
169 C-- initial guess for exchange coefficients:
170 C take U_N = del.U ; stability from del.Theta ;
171 stable = exf_half + SIGN(exf_half, deltap)
172
173 #ifdef ALLOW_ATM_WIND
174 tmpbulk = cdrag_1/wsm + cdrag_2 + cdrag_3*wsm
175 rdn = SQRT(tmpbulk)
176 ustar=rdn*wsm
177 #else /* ifndef ALLOW_ATM_WIND */
178 C in this case ustress and vstress are defined a u and v points
179 C respectively, and we need to average to mass points to avoid
180 C windStress = 0 near coasts or other boundaries
181 windStress = sqrt( 0.5 _d 0*
182 & (ustress(i, j,bi,bj)*ustress(i ,j,bi,bj)
183 & +ustress(i+1,j,bi,bj)*ustress(i+1,j,bi,bj)
184 & +vstress(i,j, bi,bj)*vstress(i,j ,bi,bj)
185 & +vstress(i,j+1,bi,bj)*vstress(i,j+1,bi,bj)
186 & ) )
187 ustar = sqrt(windStress/atmrho)
188 c tau = windStress/ustar
189 tau = sqrt(windStress*atmrho)
190 #endif /* ALLOW_ATM_WIND */
191
192 C-- initial guess for exchange other coefficients:
193 rhn = (exf_one-stable)*cstanton_1 + stable*cstanton_2
194 ren = cDalton
195 C-- calculate turbulent scales
196 tstar=rhn*deltap
197 qstar=ren*delq
198
199 C--- iterate with psi-functions to find transfer coefficients
200 DO iter=1,niter_bulk
201
202 #ifdef ALLOW_AUTODIFF_TAMC
203 ikey_2 = iter
204 & + niter_bulk*(i-1)
205 & + niter_bulk*sNx*(j-1)
206 & + niter_bulk*sNx*sNy*act1
207 & + niter_bulk*sNx*sNy*max1*act2
208 & + niter_bulk*sNx*sNy*max1*max2*act3
209 & + niter_bulk*sNx*sNy*max1*max2*max3*act4
210 CADJ STORE rdn = comlev1_exf_2, key = ikey_2
211 CADJ STORE ustar = comlev1_exf_2, key = ikey_2
212 CADJ STORE qstar = comlev1_exf_2, key = ikey_2
213 CADJ STORE tstar = comlev1_exf_2, key = ikey_2
214 CADJ STORE sh(i,j,bi,bj) = comlev1_exf_2, key = ikey_2
215 CADJ STORE us(i,j,bi,bj) = comlev1_exf_2, key = ikey_2
216 #endif
217
218 huol = ( tstar/t0 +
219 & qstar/(exf_one/humid_fac+aqh(i,j,bi,bj))
220 & )*czol/(ustar*ustar)
221 cph The following is different in Large&Pond1981 code:
222 cph huol = max(huol,zolmin) with zolmin = -100
223 tmpbulk = MIN(abs(huol),10. _d 0)
224 huol = SIGN(tmpbulk , huol)
225 htol = huol*ht/hu
226 hqol = huol*hq/hu
227 stable = exf_half + sign(exf_half, huol)
228
229 c Evaluate all stability functions assuming hq = ht.
230 #ifdef ALLOW_ATM_WIND
231 cph The following is different in Large&Pond1981 code:
232 cph xsq = max(sqrt(abs(exf_one - 16.*huol)),exf_one)
233 xsq = SQRT( ABS(exf_one - huol*16. _d 0) )
234 x = SQRT(xsq)
235 psimh = -psim_fac*huol*stable
236 & +(exf_one-stable)*
237 & ( LOG( (exf_one + exf_two*x + xsq)*
238 & (exf_one+xsq)*.125 _d 0 )
239 & -exf_two*ATAN(x) + exf_half*pi )
240 #endif /* ALLOW_ATM_WIND */
241 cph The following is different in Large&Pond1981 code:
242 cph xsq = max(sqrt(abs(exf_one - 16.*htol)),exf_one)
243 xsq = SQRT( ABS(exf_one - htol*16. _d 0) )
244 psixh = -psim_fac*htol*stable + (exf_one-stable)*
245 & ( exf_two*LOG(exf_half*(exf_one+xsq)) )
246
247 #ifdef ALLOW_ATM_WIND
248 C- Shift wind speed using old coefficient
249 usn = ws/(exf_one + rdn/karman*(zwln-psimh) )
250 usm = MAX(usn, umin)
251
252 C- Update the 10m, neutral stability transfer coefficients (momentum)
253 tmpbulk = cdrag_1/usm + cdrag_2 + cdrag_3*usm
254 rdn = SQRT(tmpbulk)
255 rd = rdn/(exf_one + rdn*(zwln-psimh)/karman)
256 ustar = rd*wsm
257 C- Coeff:
258 tau = atmrho*rd*ws
259 #endif
260
261 C- Update the 10m, neutral stability transfer coefficients (sens&evap)
262 rhn = (exf_one-stable)*cstanton_1 + stable*cstanton_2
263 ren = cDalton
264
265 C- Shift all coefficients to the measurement height and stability.
266 rh = rhn/(exf_one + rhn*(ztln-psixh)/karman)
267 re = ren/(exf_one + ren*(ztln-psixh)/karman)
268
269 C-- Update ustar, tstar, qstar using updated, shifted coefficients.
270 qstar = re*delq
271 tstar = rh*deltap
272
273 c end of iteration loop
274 ENDDO
275
276 #ifdef ALLOW_AUTODIFF_TAMC
277 CADJ STORE ustar = comlev1_exf_1, key = ikey_1
278 CADJ STORE qstar = comlev1_exf_1, key = ikey_1
279 CADJ STORE tstar = comlev1_exf_1, key = ikey_1
280 CADJ STORE tau = comlev1_exf_1, key = ikey_1
281 CADJ STORE cw(i,j,bi ,bj) = comlev1_exf_1, key = ikey_1
282 CADJ STORE sw(i,j,bi,bj) = comlev1_exf_1, key = ikey_1
283 #endif
284
285 C- Turbulent Fluxes
286 hs(i,j,bi,bj) = atmcp*tau*tstar
287 hl(i,j,bi,bj) = flamb*tau*qstar
288 #ifndef EXF_READ_EVAP
289 cdm !!! need to change sign and to convert from kg/m^2/s to m/s via recip_rhonil !!!
290 cph rhonil should be replaced by rhoFresh
291 evap(i,j,bi,bj) = -recip_rhonil*tau*qstar
292 #endif
293 #ifdef ALLOW_ATM_WIND
294 ustress(i,j,bi,bj) = tau*rd*ws*cw(i,j,bi,bj)
295 vstress(i,j,bi,bj) = tau*rd*ws*sw(i,j,bi,bj)
296 #endif
297
298 c IF ( ATEMP(i,j,bi,bj) .NE. 0. )
299 else
300 #ifdef ALLOW_ATM_WIND
301 ustress(i,j,bi,bj) = 0. _d 0
302 vstress(i,j,bi,bj) = 0. _d 0
303 #endif
304 hflux (i,j,bi,bj) = 0. _d 0
305 evap (i,j,bi,bj) = 0. _d 0
306 hs(i,j,bi,bj) = 0. _d 0
307 hl(i,j,bi,bj) = 0. _d 0
308
309 c IF ( ATEMP(i,j,bi,bj) .NE. 0. )
310 endif
311
312 #else /* ifndef ALLOW_ATM_TEMP */
313 #ifdef ALLOW_ATM_WIND
314 wsm = sh(i,j,bi,bj)
315 tmpbulk = cdrag_1/wsm + cdrag_2 + cdrag_3*wsm
316 ustress(i,j,bi,bj) = atmrho*tmpbulk*us(i,j,bi,bj)*
317 & uwind(i,j,bi,bj)
318 vstress(i,j,bi,bj) = atmrho*tmpbulk*us(i,j,bi,bj)*
319 & vwind(i,j,bi,bj)
320 #endif
321 #endif /* ifndef ALLOW_ATM_TEMP */
322 ENDDO
323 ENDDO
324 ENDDO
325 ENDDO
326
327 #endif /* ALLOW_BULK_LARGEYEAGER04 */
328
329 RETURN
330 END

  ViewVC Help
Powered by ViewVC 1.1.22