Skip to content

Commit

Permalink
Bug fix for blowing snow effect on visibility (NOAA-EMC#915)
Browse files Browse the repository at this point in the history
* Correcting bug in CALVIS_GSD.f

* Introducing roughness length impact on BLSN (no BLSN effect at z0>0.7).

* Removing some gridpoint print statements for testing.

* Checking change to compile_upp.sh

* Reverting change.
  • Loading branch information
EricJames-NOAA committed Apr 12, 2024
1 parent fd93933 commit 8bc3fc9
Showing 1 changed file with 7 additions and 4 deletions.
11 changes: 7 additions & 4 deletions sorc/ncep_post.fd/CALVIS_GSD.f
Original file line number Diff line number Diff line change
Expand Up @@ -94,11 +94,13 @@ SUBROUTINE CALVIS_GSD(CZEN,VIS)
! 2023-11 Tim Corrie, Eric James - addition of attenuation for blowing snow
! 2024-03 Eric James - removal of extcof55 factor in visibility
! calculation (extcof55 is all zeroes)
! 2024-04 Eric James - correcting bug in BLSN effect (missing factor of
! ustar_t) and removing BLSN effect for z0>0.7 (forests)
!
!------------------------------------------------------------------
!
use vrbls2d, only: sno, si, ustar
use vrbls2d, only: sno, si, ustar, z0
use vrbls3d, only: qqw, qqi, qqs, qqr, qqg, t, pmid, q, u, v, aextc55
use params_mod, only: h1, d608, rd, g
use ctlblk_mod, only: jm, im, jsta_2l, jend_2u, lm, modelname, spval, method_blsn,&
Expand Down Expand Up @@ -321,14 +323,14 @@ SUBROUTINE CALVIS_GSD(CZEN,VIS)
! print *, i,j


if (si(i,j)<spval .and. si(i,j) .ge. 1.0) then
if (si(i,j)<spval .and. si(i,j) .ge. 1.0 .and. ustar(i,j) > ustar_t .and. z0(i,j) .le. 0.7) then
z_r = 1.6*(ustar(i,j)**2./(2.*g))
Q_s = max((0.68/ustar(i,j))*(RHOAIR/g)*(ustar(i,j)**2.-ustar_t**2.),0.0)
Q_s = max((0.68/ustar(i,j))*(RHOAIR/g)*ustar_t*(ustar(i,j)**2.-ustar_t**2.),0.0)
C_r = (Q_s/u_p)*(lamda*g/ustar(i,j)**2.)*exp(-lamda*z_r*g/ustar(i,j)**2.)
c_z = max(C_r * exp(-1.55*((0.05628*ustar(i,j))**-0.544 - z**-0.544)),1e-15)
c_alpha = alpha/(alpha+2) !simplified version of (6) in Letcher et al (2021)
rho_sno = sno(i,j)/(si(i,j)/1.0e3)
rho_sno = rho_sno*2. + 10.*max(0.,rho_sno-0.15)
rho_sno = rho_sno*2. + 10.*max(0.,rho_sno-150.0)
vis_blsn = (5.217*rho_sno*r_bar**1.011)/(1.82*c_z*c_alpha)
BETABLSN = 3.912/(vis_blsn/1000.0)
! print to ensure quality
Expand All @@ -342,6 +344,7 @@ SUBROUTINE CALVIS_GSD(CZEN,VIS)
!print *, "rho_sno", rho_sno
!print *, "vis_blsn", vis_blsn
!print *, "BETABLSN", BETABLSN
!print *, "ustar", ustar(i,j)
else
BETABLSN = 0
!print *, "BETABLSN", BETABLSN
Expand Down

0 comments on commit 8bc3fc9

Please sign in to comment.