UPP  001
All Data Structures Files Functions Pages
CALVIS_GSD.f
1 !**********************************************************************c
2  SUBROUTINE calvis_gsd(CZEN,VIS)
3 
4 ! SUBPROGRAM: CALVIS CALCULATE HORIZONTAL VISIBILITY
5 !
6 ! PRGMMR: BENJAMIN, STAN ORG: NOAA/FSL DATE: 99-09-07
7 !
8 ! ABSTRACT:
9 !
10 ! Started with Stoelinga-Warner algorithm for hydrometeors only.
11 ! Added coefficients for graupel.
12 ! Added algorithm for clear-air RH-based visibility.
13 !
14 ! This routine computes horizontal visibility (in km) at the
15 ! surface or lowest model layer, from qc, qr, qi, qs, and qg.
16 ! qv--water vapor mixing ratio (kg/kg)
17 ! qc--cloud water mixing ratio (kg/kg)
18 ! qr--rain water mixing ratio (kg/kg)
19 ! qi--cloud ice mixing ratio (kg/kg)
20 ! qs--snow mixing ratio (kg/kg)
21 ! qg--graupel mixing ratio (kg/kg)
22 ! u/v - u/v wind components (m/s)
23 ! tb -- temperature (k)
24 ! pp--pressure (Pa)
25 ! rhb-- relative humidity (0-100%)
26 ! aextc55--aerosol extinction coefficient (m**-1)
27 !
28 !
29 ! Independent of the above definitions, the scheme can use different
30 ! assumptions of the state of hydrometeors:
31 ! meth='r': Uses the four mixing ratios qrain, qsnow, qclw,
32 ! and qclice
33 !
34 ! The routine uses the following
35 ! expressions for extinction coefficient, beta (in km**-1),
36 ! with C being the mass concentration (in g/m**3):
37 !
38 ! cloud water: beta = 144.7 * C ** (0.8800)
39 ! rain water: beta = 2.24 * C ** (0.7500)
40 ! cloud ice: beta = 327.8 * C ** (1.0000)
41 ! snow: beta = 10.36 * C ** (0.7776)
42 ! graupel: beta = 8.0 * C ** (0.7500)
43 !
44 ! These expressions were obtained from the following sources:
45 !
46 ! for cloud water: from Kunkel (1984)
47 ! for rainwater: from M-P dist'n, with No=8e6 m**-4 and
48 ! rho_w=1000 kg/m**3
49 ! for cloud ice: assume randomly oriented plates which follow
50 ! mass-diameter relationship from Rutledge and Hobbs (1983)
51 ! for snow: from Stallabrass (1985), assuming beta = -ln(.02)/vis
52 ! for graupel: guestimate by John Brown and Stan Benjamin,
53 ! similar to snow, but a smaller extinction coef seemed
54 ! reasonable. 27 Aug 99
55 !
56 ! The extinction coefficient for each water species present is
57 ! calculated, and then all applicable betas are summed to yield
58 ! a single beta. Then the following relationship is used to
59 ! determine visibility (in km), where epsilon is the threshhold
60 ! of contrast, usually taken to be .02:
61 !
62 ! vis = -ln(epsilon)/beta [found in Kunkel (1984)]
63 !
64 ! The 'aextc55' field is 3-D and is derived from the 'aod_3d' field
65 ! by dividing by dz, the vertical thickness of that model level in 'm'.
66 ! This can be handled as a 2-D field if needed to save resources.
67 !
68 ! HISTORY
69 ! PROGRAM HISTORY LOG:
70 ! 99-05- Version from Eta model and from
71 ! Mark Stoelinga and Tom Warner
72 ! 99-09-07 S. Benjamin Modified for MM5 microphysics variables
73 ! include graupel mixing ratio
74 ! 99-09 S. Benjamin Added algorithm for RH-based clear-air
75 ! visibility
76 ! 00-08 S. Benjamin Added mods for base of 60km instead of 90km,
77 ! max RH from lowest 2 levels instead of
78 ! lev 2 only, max hydrometeor mix ratio
79 ! from lowest 5 levs instead of lev 1 only
80 ! Based on Schwartz stats and Smirnova et al
81 ! paper, and on METAR verif started this week
82 ! Dec 03 S. Benjamin - updates
83 ! - day/night distinction for vis constants
84 ! from Roy Rasmussen
85 ! - low-level wind shear term
86 ! - recommended by Evan Kuchera
87 ! 2015-17 S. Benjamin, T. Smirnova - modifications for RH-based clear-air vis
88 ! 2017-12 R. Ahmadov, Steve Albers - addition for attenuation from aerosols
89 ! (not related to water vapor or RH at this point)
90 ! 2021-05 Wen Meng Unify CONST1 and VISRH.
91 ! 2021-05 Wen Meng - Add checking for undefined points invloved in computation
92 ! 2021-08 Wen Meng - Restrict divided by 0.
93 !
94 !------------------------------------------------------------------
95 !
96 
97  use vrbls3d, only: qqw, qqi, qqs, qqr, qqg, t, pmid, q, u, v, extcof55, aextc55
98  use params_mod, only: h1, d608, rd
99  use ctlblk_mod, only: jm, im, jsta_2l, jend_2u, lm, modelname, spval
100 
101  implicit none
102 
103  integer :: j, i, k, ll
104  integer :: method
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)
107 
108 
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
113 
114  real coeffp_dry, coeffp_wet, shear_fac, temp_fac
115  real coef_snow, shear
116 
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
122 
123  real visrh10_cnt, vis1km_cnt, visrh_lower
124  real vis3km_cnt
125  real vis5km_cnt
126  real vis_min, visrh_min
127  real vis_night, zen_fac
128 !------------------------------------------------------------------
129 
130 ! Method used for clear-air visibility with extension for aerosols
131  method = 3
132 ! RH-only method (1),
133 ! Aerosol method (2),
134 ! Smoke added to RH method for clear air (3)
135 ! 3 - option to add reducted visibility from smoke-based aerosols.
136 
137  celkel = 273.15
138  tice = celkel-10.
139  coeflc = 144.7
140  coeflp = 2.24
141  coeffc = 327.8
142  coeffp = 10.36
143 
144 ! - Initialize counters
145 
146  shear4_cnt = 0
147  shear5_cnt = 0
148  shear8_cnt = 0
149  shear4_cnt_lowvis = 0
150  shear5_cnt_lowvis = 0
151  shear8_cnt_lowvis = 0
152  night_cnt = 0
153  lowsun_cnt = 0
154  visrh10_cnt = 0
155  visrh_lower = 0
156  vis1km_cnt = 0
157  vis3km_cnt = 0
158  vis5km_cnt = 0
159 
160 ! - snow-based vis attenuation - coefficient values from Roy Rasmussen - Dec 2003
161 ! COEFFP_dry = 17.7
162 ! COEFFP_wet = 4.18
163 ! - modified number - Stan B. - Dec 2007
164 ! after quick talks with John Brown and Ismail Gultepe
165  coeffp_dry = 10.0
166  coeffp_wet = 6.0
167 
168 ! COEFFg = 8.0
169 ! - values from Roy Rasmussen - Dec 2003
170 ! Rasmussen et al. 2003, J. App. Meteor.
171 ! Snow Nowcasting Using a Real-Time Correlation of Radar Reflectivity with Snow Gauge Accumulation
172  coeffg = 4.0
173 
174  exponlc = 0.8800
175  exponlp = 0.7500
176  exponfc = 1.0000
177 ! EXPONFP = 0.7776
178 ! - new value from Roy Rasmussen - Dec 2003
179  exponfp = 1.0
180 
181  exponfg = 0.75
182 ! CONST1=-LOG(.02)
183 ! CONST1=3.912
184  const1= 3.000
185 
186 ! visibility with respect to RH is
187 ! calculated from optical depth linearly
188 ! related to RH as follows:
189 
190 ! vis = 60 exp (-2.5 * (RH-15)/80)
191 ! changed on 3/14/01
192 
193 ! coefficient of 3 gives visibility of 5 km
194 ! at 95% RH
195 
196 ! Total visibility is minimum of vis-rh (developed by Benjamin, Brown, Smirnova)
197 ! and vis-hydrometeors from Stoelinga/Warner
198 
199  rhoice=917.
200  rhowat=1000.
201 
202  vis_min = 1.e6
203  visrh_min = 1.e6
204 
205  DO j=jsta_2l,jend_2u
206  DO i=1,im
207  vis(i,j)=spval
208 ! -checking undedined points
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
211 ! - take max hydrometeor mixing ratios in lowest 3 levels (lowest 13 hPa, 100m with RAP/HRRR
212  qrain = 0.
213  qsnow = 0.
214  qgraupel = 0.
215  qclw = 0.
216  qclice = 0.
217 
218  do k = 1,3
219  ll=lm-k+1
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) )
225 ! - compute relative humidity
226  tx=t(i,j,ll)-273.15
227  rhb(i,j,ll)=0.
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
234  esx = 6.1078/pol**8
235 
236  es = esx
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)
239  ENDIF
240 
241  enddo
242 
243 ! - take max RH of levels 1 and 2 near the sfc
244  rhmax = max(rhb(i,j,lm),rhb(i,j,lm-1))
245  qrh = max(0.0,min(0.8,(rhmax/100.-0.15)))
246 
247 !tgs 23 feb 2017 - increase of base value to 90 km to reduce attenuation
248 ! from RH for clear-air visibility. (i.e., increase clear-air vis overall)
249  visrh = 90. * exp(-2.5*qrh)
250 
251 ! -- add term to increase RH vis term for
252 ! low-level wind shear increasing from 4 to 6 ms-1
253 ! (using Evan Kuchera's paper as a guideline)
254 
255 ! -- calculate term for shear between levels 1 and 4
256 ! (about 25 hPa for HRRR/RAP)
257  shear = sqrt( (u(i,j,lm-3)-u(i,j,lm))**2 &
258  +(v(i,j,lm-3)-v(i,j,lm))**2 )
259 
260  shear_fac = min(1.,max(0.,(shear-4.)/2.) )
261  if (visrh<10.) visrh = visrh + (10.-visrh)* &
262  shear_fac
263 
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
267 
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
274 
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
278 
279  tv=t(i,j,lm)*(h1+d608*q(i,j,lm))
280 
281  rhoair=pmid(i,j,lm)/(rd*tv)
282 
283  vovermd=(1.+q(i,j,lm))/rhoair+(qclw+qrain)/rhowat+ &
284 ! VOVERMD=(1.+Q(I,J,1))/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.
291 
292  temp_fac = min(1.,max((t(i,j,lm)-271.15),0.) )
293 
294  coef_snow = coeffp_dry*(1.-temp_fac) &
295  + coeffp_wet* temp_fac
296 
297  if (t(i,j,lm)< 270. .and. temp_fac==1.) &
298  write (6,*) 'Problem w/ temp_fac - calvis'
299 
300 ! Key calculation of attenuation from each hydrometeor type (cloud, snow, graupel, rain, ice)
301  betav=coeffc*concfc**exponfc &
302  + coef_snow*concfp**exponfp &
303  + coeflc*conclc**exponlc + coeflp*conclp**exponlp &
304  + coeffg*concfg**exponfg +1.e-10
305 
306 ! Addition of attenuation from aerosols if option selected
307  if(method == 2 .or. method == 3)then ! aerosol method
308  betav = betav + aextc55(i,j,lm)*1000.
309  endif
310 
311  if (i==290 .and. j==112) then
312  write (6,*) 'BETAV, extcof55 =',betav,extcof55(i,j,lm)
313  end if
314 
315 ! Calculation of visibility based on hydrometeor and aerosols. (RH effect not yet included.)
316  vis(i,j)=min(90.,const1/(betav+extcof55(i,j,lm))) ! max of 90km
317 
318  if (vis(i,j)<vis_min) vis_min = vis(i,j)
319  if (visrh<visrh_min) visrh_min = visrh
320 
321  if (visrh<vis(i,j)) visrh_lower = visrh_lower + 1
322 
323 
324 ! -- Dec 2003 - Roy Rasmussen (NCAR) expression for night vs. day vis
325 ! 1.609 factor is number of km in mile.
326  vis_night = 1.69 * ((vis(i,j)/1.609)**0.86) * 1.609
327 
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)
331  end if
332 
333  vis(i,j) = zen_fac * vis(i,j) + (1.-zen_fac)*vis_night
334 
335  if (i==290 .and. j==112) then
336  write (6,*) 'visrh, vis =',visrh, vis(i,j)
337  end if
338 
339  if(method == 1 .or. method == 3)then ! RH method (if lower vis)
340  vis(i,j) = min(vis(i,j),visrh)
341  endif
342 
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
346 ! convert vis from km to [m]
347  vis(i,j) = vis(i,j) * 1000.
348 
349  endif !end checking undefined points
350  ENDDO
351  ENDDO
352 
353 ! write (6,*)
354 ! write (6,*) ' Visibility diagnostics follow: ------------'
355 ! write (6,*) ' -------------------------------------------'
356 ! write (6,*) &
357 ! ' any vis / vis < 10 km '
358 ! write (6,*)'No. of grid pts with shear (lev4-1) > 4m/s', &
359 ! shear4_cnt, shear4_cnt_lowvis
360 ! write (6,*)'No. of grid pts with shear (lev4-1) > 5m/s', &
361 ! shear5_cnt, shear5_cnt_lowvis
362 ! write (6,*)'No. of grid pts with shear (lev4-1) > 6m/s', &
363 ! shear8_cnt, shear8_cnt_lowvis
364 ! write (6,*)
365 ! write (6,*)'No. of grid pts with vis-RH < 10 km', &
366 ! visrh10_cnt
367 ! write (6,*)'No. of grid pts with vis < 1 km', &
368 ! vis1km_cnt
369 ! write (6,*)'No. of grid pts with vis < 3 km', &
370 ! vis3km_cnt
371 ! write (6,*)'No. of grid pts with vis < 5 km', &
372 ! vis5km_cnt
373 ! write (6,*)
374 ! write (6,*)'Min vis-hydrometeor, vis-RH', vis_min, visrh_min
375 !
376 ! write (6,*)'No. of grid pts with visRH < vis(hydrometeor)', &
377 ! visrh_lower
378 ! write (6,*)'% grid pts with night/cos(zen) < 0.1', &
379 ! float(night_cnt)/float(IM*JM),float(lowsun_cnt)/ &
380 ! float(IM*JM)
381 ! write (6,*)
382 !
383  RETURN
384  END