Skip to content

Commit

Permalink
Option for rain-to-snow to immediately run off in some regions
Browse files Browse the repository at this point in the history
Up until now: When repartition_rain_snow is .true. (which is the default
for CLM5), rain that falls when the near-surface temperature is cold is
converted to snow. This repartitioning was put in place for two
reasons: (1) Downscaling to elevation classes: changing the balance
between rain and snow for different elevation classes; (2) Correcting
problems in CAM. However, members of the Land Ice Working Group would
like to change this behavior so that, when CAM produces cold-temperature
rain, this rain immediately runs off rather than being converted to
snow. The purpose of this is to reduce the too-high SMB over portions of
Greenland in CESM2 coupled runs (which results in part from CAM's
generation of liquid precipitation despite very cold temperatures).

This new behavior is implemented in a glacier region-specific manner,
based on a new namelist flag, glacier_region_rain_to_snow_behavior. It
is not at all ideal to make this aspect of the physics differ by region,
but this has been requested by members of the Land Ice Working Group in
order to address biases over Greenland while having minimal impact on
the climate (so that the climate can stay very similar to that of the
official CMIP6 runs). Note that, unlike other glacier region-specific
behaviors, this one applies to all landunits, not just glaciers. This
also seems a bit non-ideal, but we want the physics to be the same for
all landunit types in a given region, and we also want this behavior to
apply to vegetated columns because they are used for glacial
inception (and we want this alternate behavior to apply to glacial
inception, too, in order to decrease some instances of inception).

The justification for this new physics is: In the case of (1) above: If
CAM is generating rain at a given elevation / temperature, that doesn't
necessarily imply that an equal water equivalent of snow would be
generated at a higher elevation / lower temperature: indeed, in reality,
there might not be any precipitation falling at that higher elevation /
lower temperature. In the case of (2) above: There seem to be problems
with CAM's microphysics that cause it to produce too much rain when
temperatures are very cold; it seems (at least to some people) equally
justifiable to throw this cold rain away (by sending it to the ocean as
runoff) as it is to convert this cold rain to snow.

Note: I don't think any changes are needed in
BalanceCheck (unfortunately), since BalanceCheck currently uses the
post-downscaling precipitation fluxes, and the pre-lnd2atm runoff
fluxes (i.e., the new runoff flux isn't included in the terms in
BalanceCheck, and it doesn't need to be because BalanceCheck uses the
post-downscaling precipitation fluxes). (See also
#201 (comment) .)
  • Loading branch information
billsacks committed Dec 5, 2018
1 parent f32045c commit 71b3a0a
Show file tree
Hide file tree
Showing 11 changed files with 335 additions and 51 deletions.
1 change: 1 addition & 0 deletions bld/CLMBuildNamelist.pm
Original file line number Diff line number Diff line change
Expand Up @@ -2039,6 +2039,7 @@ sub setup_logic_glacier {
add_default($opts, $nl_flags->{'inputdata_rootdir'}, $definition, $defaults, $nl, 'glacier_region_behavior');
add_default($opts, $nl_flags->{'inputdata_rootdir'}, $definition, $defaults, $nl, 'glacier_region_melt_behavior');
add_default($opts, $nl_flags->{'inputdata_rootdir'}, $definition, $defaults, $nl, 'glacier_region_ice_runoff_behavior');
add_default($opts, $nl_flags->{'inputdata_rootdir'}, $definition, $defaults, $nl, 'glacier_region_rain_to_snow_behavior');
}
}

Expand Down
2 changes: 2 additions & 0 deletions bld/namelist_files/namelist_defaults_clm4_5.xml
Original file line number Diff line number Diff line change
Expand Up @@ -336,6 +336,8 @@ attributes from the config_cache.xml file (with keys converted to upper-case).
Antarctica: remains_ice -->
<glacier_region_ice_runoff_behavior>'melted','melted','remains_ice','remains_ice'</glacier_region_ice_runoff_behavior>

<glacier_region_rain_to_snow_behavior>'converted_to_snow','converted_to_snow','converted_to_snow','converted_to_snow'</glacier_region_rain_to_snow_behavior>

<!-- This parameter is tied (in a scientific sense) to h2osno_max: For large
values of h2osno_max, glc_snow_persistence_max_days should be 0; for small
values of h2osno_max, glc_snow_persistence_max_days should be non-zero. For
Expand Down
17 changes: 17 additions & 0 deletions bld/namelist_files/namelist_definition_clm4_5.xml
Original file line number Diff line number Diff line change
Expand Up @@ -507,6 +507,23 @@ Allowed values are:
Only applies when melt_non_icesheet_ice_runoff is .true.
</entry>

<entry id="glacier_region_rain_to_snow_behavior" type="char*32(10)" category="clm_physics"
group="clm_glacier_behavior"
valid_values="converted_to_snow,runs_off" >
When rain-snow repartitioning / downscaling results in rain being converted to
snow, the behavior of the resulting additional snow.
First item corresponds to GLACIER_REGION with ID 0 in the surface dataset,
second to GLACIER_REGION with ID 1, etc.
Allowed values are:
'converted_to_snow': rain is converted to snow, with a corresponding sensible
heat flux correction
'runs_off': rather than being converted to snow, the excess rain runs off
immediately
IMPORTANT NOTE: Unlike other glacier_region*behavior namelist options, this
option applies to all landunit types in the given regions.
Only applies when repartition_rain_snow is .true.
</entry>

<entry id="glc_snow_persistence_max_days" type="integer" category="clm_physics"
group="clm_inparm" valid_values="" >
Number of days before one considers the perennially snow-covered point 'land ice'
Expand Down
8 changes: 8 additions & 0 deletions src/biogeophys/WaterfluxType.F90
Original file line number Diff line number Diff line change
Expand Up @@ -87,6 +87,7 @@ module WaterfluxType
real(r8), pointer :: qflx_snomelt_lyr_col (:,:) ! col snow melt in each layer (mm H2O /s)
real(r8), pointer :: qflx_snow_drain_col (:) ! col drainage from snow pack
real(r8), pointer :: qflx_qrgwl_col (:) ! col qflx_surf at glaciers, wetlands, lakes
real(r8), pointer :: qflx_runoff_rain_to_snow_conversion_col(:) ! col runoff flux from rain-to-snow conversion, when this conversion leads to immediate runoff rather than snow (mm H2O /s)
real(r8), pointer :: qflx_runoff_col (:) ! col total runoff (qflx_drain+qflx_surf+qflx_qrgwl) (mm H2O /s)
real(r8), pointer :: qflx_runoff_r_col (:) ! col Rural total runoff (qflx_drain+qflx_surf+qflx_qrgwl) (mm H2O /s)
real(r8), pointer :: qflx_runoff_u_col (:) ! col urban total runoff (qflx_drain+qflx_surf) (mm H2O /s)
Expand Down Expand Up @@ -226,6 +227,7 @@ subroutine InitAllocate(this, bounds)
allocate(this%qflx_snofrz_col (begc:endc)) ; this%qflx_snofrz_col (:) = nan
allocate(this%qflx_snofrz_lyr_col (begc:endc,-nlevsno+1:0)) ; this%qflx_snofrz_lyr_col (:,:) = nan
allocate(this%qflx_qrgwl_col (begc:endc)) ; this%qflx_qrgwl_col (:) = nan
allocate(this%qflx_runoff_rain_to_snow_conversion_col(begc:endc)); this%qflx_runoff_rain_to_snow_conversion_col(:) = nan
allocate(this%qflx_drain_perched_col (begc:endc)) ; this%qflx_drain_perched_col (:) = nan
allocate(this%qflx_deficit_col (begc:endc)) ; this%qflx_deficit_col (:) = nan
allocate(this%qflx_floodc_col (begc:endc)) ; this%qflx_floodc_col (:) = nan
Expand Down Expand Up @@ -299,6 +301,12 @@ subroutine InitHistory(this, bounds)
long_name='surface runoff at glaciers (liquid only), wetlands, lakes; also includes melted ice runoff from QSNWCPICE', &
ptr_col=this%qflx_qrgwl_col, c2l_scale_type='urbanf')

this%qflx_runoff_rain_to_snow_conversion_col(begc:endc) = spval
call hist_addfld1d (fname='QRUNOFF_RAIN_TO_SNOW_CONVERSION', units='mm/s', &
avgflag='A', &
long_name='liquid runoff from rain-to-snow conversion when this conversion leads to immediate runoff', &
ptr_col=this%qflx_runoff_rain_to_snow_conversion_col, c2l_scale_type='urbanf')

this%qflx_drain_col(begc:endc) = spval
call hist_addfld1d (fname='QDRAI', units='mm/s', &
avgflag='A', long_name='sub-surface drainage', &
Expand Down
47 changes: 39 additions & 8 deletions src/main/atm2lndMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -22,6 +22,7 @@ module atm2lndMod
use LandunitType , only : lun
use ColumnType , only : col
use landunit_varcon, only : istice_mec
use glcBehaviorMod , only : glc_behavior_type
!
! !PUBLIC TYPES:
implicit none
Expand Down Expand Up @@ -51,7 +52,8 @@ module atm2lndMod

!-----------------------------------------------------------------------
subroutine downscale_forcings(bounds, &
topo_inst, atm2lnd_inst, eflx_sh_precip_conversion)
topo_inst, glc_behavior, atm2lnd_inst, &
eflx_sh_precip_conversion, qflx_runoff_rain_to_snow_conversion)
!
! !DESCRIPTION:
! Downscale atmospheric forcing fields from gridcell to column.
Expand All @@ -76,8 +78,10 @@ subroutine downscale_forcings(bounds, &
! !ARGUMENTS:
type(bounds_type) , intent(in) :: bounds
class(topo_type) , intent(in) :: topo_inst
type(glc_behavior_type), intent(in) :: glc_behavior
type(atm2lnd_type) , intent(inout) :: atm2lnd_inst
real(r8) , intent(out) :: eflx_sh_precip_conversion(bounds%begc:) ! sensible heat flux from precipitation conversion (W/m**2) [+ to atm]
real(r8) , intent(inout) :: qflx_runoff_rain_to_snow_conversion(bounds%begc:) ! runoff flux from rain-to-snow conversion, when this conversion leads to immediate runoff rather than snow (mm H2O /s)
!
! !LOCAL VARIABLES:
integer :: g, l, c, fc ! indices
Expand All @@ -96,6 +100,7 @@ subroutine downscale_forcings(bounds, &
!-----------------------------------------------------------------------

SHR_ASSERT_ALL((ubound(eflx_sh_precip_conversion) == (/bounds%endc/)), errMsg(sourcefile, __LINE__))
SHR_ASSERT_ALL((ubound(qflx_runoff_rain_to_snow_conversion) == [bounds%endc]), errMsg(sourcefile, __LINE__))

associate(&
! Parameters:
Expand Down Expand Up @@ -207,8 +212,9 @@ subroutine downscale_forcings(bounds, &

end do

call partition_precip(bounds, atm2lnd_inst, &
eflx_sh_precip_conversion(bounds%begc:bounds%endc))
call partition_precip(bounds, glc_behavior, atm2lnd_inst, &
eflx_sh_precip_conversion(bounds%begc:bounds%endc), &
qflx_runoff_rain_to_snow_conversion(bounds%begc:bounds%endc))

call downscale_longwave(bounds, downscale_filter_c, topo_inst, atm2lnd_inst)

Expand Down Expand Up @@ -245,7 +251,8 @@ pure function rhos(qbot, pbot, tbot)
end function rhos

!-----------------------------------------------------------------------
subroutine partition_precip(bounds, atm2lnd_inst, eflx_sh_precip_conversion)
subroutine partition_precip(bounds, glc_behavior, atm2lnd_inst, &
eflx_sh_precip_conversion, qflx_runoff_rain_to_snow_conversion)
!
! !DESCRIPTION:
! Partition precipitation into rain/snow based on temperature.
Expand All @@ -254,9 +261,11 @@ subroutine partition_precip(bounds, atm2lnd_inst, eflx_sh_precip_conversion)
! all points - not just those within the downscale filter.
!
! !ARGUMENTS:
type(bounds_type) , intent(in) :: bounds
type(bounds_type) , intent(in) :: bounds
type(glc_behavior_type), intent(in) :: glc_behavior
type(atm2lnd_type) , intent(inout) :: atm2lnd_inst
real(r8), intent(inout) :: eflx_sh_precip_conversion(bounds%begc:) ! sensible heat flux from precipitation conversion (W/m**2) [+ to atm]
real(r8) , intent(inout) :: qflx_runoff_rain_to_snow_conversion(bounds%begc:) ! runoff flux from rain-to-snow conversion, when this conversion leads to immediate runoff rather than snow (mm H2O /s)
!
! !LOCAL VARIABLES:
integer :: c,l,g ! indices
Expand All @@ -269,6 +278,7 @@ subroutine partition_precip(bounds, atm2lnd_inst, eflx_sh_precip_conversion)
!-----------------------------------------------------------------------

SHR_ASSERT_ALL((ubound(eflx_sh_precip_conversion) == (/bounds%endc/)), errMsg(sourcefile, __LINE__))
SHR_ASSERT_ALL((ubound(qflx_runoff_rain_to_snow_conversion) == [bounds%endc]), errMsg(sourcefile, __LINE__))

associate(&
! Gridcell-level non-downscaled fields:
Expand All @@ -288,6 +298,7 @@ subroutine partition_precip(bounds, atm2lnd_inst, eflx_sh_precip_conversion)
forc_rain_c(c) = forc_rain_g(g)
forc_snow_c(c) = forc_snow_g(g)
eflx_sh_precip_conversion(c) = 0._r8
qflx_runoff_rain_to_snow_conversion(c) = 0._r8
end if
end do

Expand All @@ -296,6 +307,7 @@ subroutine partition_precip(bounds, atm2lnd_inst, eflx_sh_precip_conversion)
do c = bounds%begc, bounds%endc
if (col%active(c)) then
l = col%landunit(c)
g = col%gridcell(c)
rain_old = forc_rain_c(c)
snow_old = forc_snow_c(c)
if (lun%itype(l) == istice_mec) then
Expand All @@ -311,11 +323,21 @@ subroutine partition_precip(bounds, atm2lnd_inst, eflx_sh_precip_conversion)
frac_rain_slope = frac_rain_slope, &
rain = forc_rain_c(c), &
snow = forc_snow_c(c))
if (glc_behavior%rain_to_snow_runs_off_grc(g)) then
! Note that, despite being a flag in glc_behavior, this actually applies
! to all landunits
if (forc_snow_c(c) > snow_old) then
! Instead of converting rain to snow, make it run off immediately
qflx_runoff_rain_to_snow_conversion(c) = forc_snow_c(c) - snow_old
forc_snow_c(c) = snow_old
end if
end if
call sens_heat_from_precip_conversion(&
rain_old = rain_old, &
snow_old = snow_old, &
rain_new = forc_rain_c(c), &
snow_new = forc_snow_c(c), &
rain_to_snow_runoff = qflx_runoff_rain_to_snow_conversion(c), &
sens_heat_flux = eflx_sh_precip_conversion(c))
end if
end do
Expand Down Expand Up @@ -361,7 +383,7 @@ end subroutine repartition_rain_snow_one_col

!-----------------------------------------------------------------------
subroutine sens_heat_from_precip_conversion(rain_old, snow_old, rain_new, snow_new, &
sens_heat_flux)
rain_to_snow_runoff, sens_heat_flux)
!
! !DESCRIPTION:
! Given old and new rain and snow amounts, compute the sensible heat flux needed to
Expand All @@ -374,6 +396,7 @@ subroutine sens_heat_from_precip_conversion(rain_old, snow_old, rain_new, snow_n
real(r8), intent(in) :: snow_old ! [(mm water equivalent)/s]
real(r8), intent(in) :: rain_new ! [mm/s]
real(r8), intent(in) :: snow_new ! [(mm water equivalent)/s]
real(r8), intent(in) :: rain_to_snow_runoff ! rain that, rather than being converted to snow, instead immediately runs off [mm/s]
real(r8), intent(out) :: sens_heat_flux ! [W/m^2]
!
! !LOCAL VARIABLES:
Expand All @@ -388,10 +411,18 @@ subroutine sens_heat_from_precip_conversion(rain_old, snow_old, rain_new, snow_n
!-----------------------------------------------------------------------

total_old = rain_old + snow_old
total_new = rain_new + snow_new
total_new = rain_new + snow_new + rain_to_snow_runoff
SHR_ASSERT(abs(total_new - total_old) <= (tol * total_old), subname//' ERROR: mismatch between old and new totals')

! rain to snow releases energy, so results in a positive heat flux to atm
! Rain to snow releases energy, so results in a positive heat flux to atm.
!
! While perhaps not immediately obvious, we can calculate the energy flux entirely
! based on the change in snow. This is because there are three possible conversions:
! (1) snow to rain, (2) rain to snow, and (3) rain to runoff. (1) and (2) have a
! change in rain that is exactly opposite the change in snow (so the difference in
! snow is all we need to know); (3) doesn't result in any change in snow and also
! doesn't result in any necessary heat flux, so just considering the change in snow
! is again correct.
rain_to_snow = snow_new - snow_old
sens_heat_flux = rain_to_snow * mm_to_m * denh2o * hfus

Expand Down
7 changes: 5 additions & 2 deletions src/main/clm_driver.F90
Original file line number Diff line number Diff line change
Expand Up @@ -410,8 +410,11 @@ subroutine clm_drv(doalb, nextsw_cday, declinp1, declin, rstwr, nlend, rdate, ro
atm_topo = atm2lnd_inst%forc_topo_grc(bounds_clump%begg:bounds_clump%endg))

call downscale_forcings(bounds_clump, &
topo_inst, atm2lnd_inst, &
eflx_sh_precip_conversion = energyflux_inst%eflx_sh_precip_conversion_col(bounds_clump%begc:bounds_clump%endc))
topo_inst, glc_behavior, atm2lnd_inst, &
eflx_sh_precip_conversion = &
energyflux_inst%eflx_sh_precip_conversion_col(bounds_clump%begc:bounds_clump%endc), &
qflx_runoff_rain_to_snow_conversion = &
waterflux_inst%qflx_runoff_rain_to_snow_conversion_col(bounds_clump%begc:bounds_clump%endc))

! Update filters that depend on variables set in clm_drv_init

Expand Down
Loading

0 comments on commit 71b3a0a

Please sign in to comment.