2 SUBROUTINE calvis_gsd(CZEN,VIS)
97 use vrbls3d, only: qqw, qqi, qqs, qqr, qqg, t, pmid, q, u, v, extcof55, aextc55
99 use ctlblk_mod
, only: jm, im, jsta_2l, jend_2u, lm, modelname, spval
103 integer :: j, i, k, ll
105 real :: tx, pol, esx, es, e
106 REAL vis(im,jsta_2l:jend_2u) ,rhb(im,jsta_2l:jend_2u,lm), czen(im,jsta_2l:jend_2u)
109 real celkel,tice,coeflc,coeflp,coeffc,coeffp,coeffg
110 real exponlc,exponlp,exponfc,exponfp,exponfg,const1
111 real rhoice,rhowat,qrain,qsnow,qgraupel,qclw,qclice,tv,rhoair, &
112 vovermd,conclc,conclp,concfc,concfp,concfg,betav
114 real coeffp_dry, coeffp_wet, shear_fac, temp_fac
115 real coef_snow, shear
117 real coefrh,qrh,visrh
118 real rhmax,shear5_cnt, shear8_cnt
119 real shear5_cnt_lowvis, shear8_cnt_lowvis
120 real shear4_cnt, shear4_cnt_lowvis
121 integer night_cnt, lowsun_cnt
123 real visrh10_cnt, vis1km_cnt, visrh_lower
126 real vis_min, visrh_min
127 real vis_night, zen_fac
149 shear4_cnt_lowvis = 0
150 shear5_cnt_lowvis = 0
151 shear8_cnt_lowvis = 0
209 if(t(i,j,lm)<spval .and. u(i,j,lm)<spval .and. v(i,j,lm)<spval &
210 .and. pmid(i,j,lm)<spval)
then
220 if(qqw(i,j,ll)<spval)qclw = max(qclw, qqw(i,j,ll) )
221 if(qqi(i,j,ll)<spval)qclice = max(qclice, qqi(i,j,ll) )
222 if(qqs(i,j,ll)<spval)qsnow = max(qsnow, qqs(i,j,ll) )
223 if(qqr(i,j,ll)<spval)qrain = max(qrain, qqr(i,j,ll) )
224 if(qqg(i,j,ll)<spval)qgraupel = max(qgraupel, qqg(i,j,ll) )
228 pol = 0.99999683 + tx*(-0.90826951e-02 + &
229 tx*(0.78736169e-04 + tx*(-0.61117958e-06 + &
230 tx*(0.43884187e-08 + tx*(-0.29883885e-10 + &
231 tx*(0.21874425e-12 + tx*(-0.17892321e-14 + &
232 tx*(0.11112018e-16 + tx*(-0.30994571e-19)))))))))
233 if(abs(pol) > 0.)
THEN
237 e = pmid(i,j,ll)/100.*q(i,j,ll)/(0.62197+q(i,j,ll)*0.37803)
238 rhb(i,j,ll) = 100.*amin1(1.,e/es)
244 rhmax = max(rhb(i,j,lm),rhb(i,j,lm-1))
245 qrh = max(0.0,min(0.8,(rhmax/100.-0.15)))
249 visrh = 90. * exp(-2.5*qrh)
257 shear = sqrt( (u(i,j,lm-3)-u(i,j,lm))**2 &
258 +(v(i,j,lm-3)-v(i,j,lm))**2 )
260 shear_fac = min(1.,max(0.,(shear-4.)/2.) )
261 if (visrh<10.) visrh = visrh + (10.-visrh)* &
264 if (shear>4.) shear4_cnt = shear4_cnt +1
265 if (shear>5.) shear5_cnt = shear5_cnt +1
266 if (shear>6.) shear8_cnt = shear8_cnt +1
268 if (shear>4..and.visrh<10) &
269 shear4_cnt_lowvis = shear4_cnt_lowvis +1
270 if (shear>5..and.visrh<10) &
271 shear5_cnt_lowvis = shear5_cnt_lowvis +1
272 if (shear>6..and.visrh<10) &
273 shear8_cnt_lowvis = shear8_cnt_lowvis +1
275 if (visrh<10.) visrh10_cnt = visrh10_cnt+1
276 if (czen(i,j)<0.) night_cnt = night_cnt + 1
277 if (czen(i,j)<0.1) lowsun_cnt = lowsun_cnt + 1
279 tv=t(i,j,lm)*(h1+d608*q(i,j,lm))
281 rhoair=pmid(i,j,lm)/(rd*tv)
283 vovermd=(1.+q(i,j,lm))/rhoair+(qclw+qrain)/rhowat+ &
285 (qgraupel+qclice+qsnow)/rhoice
286 conclc=qclw/vovermd*1000.
287 conclp=qrain/vovermd*1000.
288 concfc=qclice/vovermd*1000.
289 concfp=qsnow/vovermd*1000.
290 concfg=qgraupel/vovermd*1000.
292 temp_fac = min(1.,max((t(i,j,lm)-271.15),0.) )
294 coef_snow = coeffp_dry*(1.-temp_fac) &
295 + coeffp_wet* temp_fac
297 if (t(i,j,lm)< 270. .and. temp_fac==1.) &
298 write (6,*)
'Problem w/ temp_fac - calvis'
301 betav=coeffc*concfc**exponfc &
302 + coef_snow*concfp**exponfp &
303 + coeflc*conclc**exponlc + coeflp*conclp**exponlp &
304 + coeffg*concfg**exponfg +1.e-10
307 if(method == 2 .or. method == 3)
then
308 betav = betav + aextc55(i,j,lm)*1000.
311 if (i==290 .and. j==112)
then
312 write (6,*)
'BETAV, extcof55 =',betav,extcof55(i,j,lm)
316 vis(i,j)=min(90.,const1/(betav+extcof55(i,j,lm)))
318 if (vis(i,j)<vis_min) vis_min = vis(i,j)
319 if (visrh<visrh_min) visrh_min = visrh
321 if (visrh<vis(i,j)) visrh_lower = visrh_lower + 1
326 vis_night = 1.69 * ((vis(i,j)/1.609)**0.86) * 1.609
328 zen_fac = min(0.1,max(czen(i,j),0.))/ 0.1
329 if (i==290 .and. j==112)
then
330 write (6,*)
'zen_fac,vis_night, vis =',zen_fac,vis_night, vis(i,j)
333 vis(i,j) = zen_fac * vis(i,j) + (1.-zen_fac)*vis_night
335 if (i==290 .and. j==112)
then
336 write (6,*)
'visrh, vis =',visrh, vis(i,j)
339 if(method == 1 .or. method == 3)
then
340 vis(i,j) = min(vis(i,j),visrh)
343 if (vis(i,j)<1.) vis1km_cnt = vis1km_cnt + 1
344 if (vis(i,j)<3.) vis3km_cnt = vis3km_cnt + 1
345 if (vis(i,j)<5.) vis5km_cnt = vis5km_cnt + 1
347 vis(i,j) = vis(i,j) * 1000.