Skip to content

Commit

Permalink
Relabel ice sizes
Browse files Browse the repository at this point in the history
Ice sizes are diameters, not radii
  • Loading branch information
RobertPincus authored Jan 14, 2025
2 parents fbf5f5e + 1194b96 commit 1e85cf9
Show file tree
Hide file tree
Showing 3 changed files with 25 additions and 25 deletions.
2 changes: 1 addition & 1 deletion CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -90,7 +90,7 @@ exit(tuple(map(int, xarray.__version__.split('.'))) < (0, 12, 2))"
ExternalProject_Add(
rrtmgp-data
GIT_REPOSITORY https://github.com/earth-system-radiation/rrtmgp-data.git
GIT_TAG "v1.8.2"
GIT_TAG "develop"
GIT_SHALLOW True
EXCLUDE_FROM_ALL True
PREFIX rrtmgp-data-cmake
Expand Down
12 changes: 6 additions & 6 deletions examples/all-sky/mo_load_cloud_coefficients.F90
Original file line number Diff line number Diff line change
Expand Up @@ -33,9 +33,9 @@ subroutine load_cld_lutcoeff(cloud_spec, cld_coeff_file)
real(wp) :: radliq_lwr ! liquid particle size lower bound for interpolation
real(wp) :: radliq_upr ! liquid particle size upper bound for interpolation
real(wp) :: radliq_fac ! constant for calculating interpolation indices for liquid
real(wp) :: radice_lwr ! ice particle size lower bound for interpolation
real(wp) :: radice_upr ! ice particle size upper bound for interpolation
real(wp) :: radice_fac ! constant for calculating interpolation indices for ice
real(wp) :: diamice_lwr ! ice particle size lower bound for interpolation
real(wp) :: diamice_upr ! ice particle size upper bound for interpolation
real(wp) :: diam_icefac ! constant for calculating interpolation indices for ice
! LUT coefficients
real(wp), dimension(:,:), allocatable :: lut_extliq ! extinction: liquid
real(wp), dimension(:,:), allocatable :: lut_ssaliq ! single scattering albedo: liquid
Expand All @@ -60,8 +60,8 @@ subroutine load_cld_lutcoeff(cloud_spec, cld_coeff_file)
! Read LUT constants
radliq_lwr = read_field(ncid, 'radliq_lwr')
radliq_upr = read_field(ncid, 'radliq_upr')
radice_lwr = read_field(ncid, 'radice_lwr')
radice_upr = read_field(ncid, 'radice_upr')
diamice_lwr = read_field(ncid, 'diamice_lwr')
diamice_upr = read_field(ncid, 'diamice_upr')

! Allocate cloud property lookup table input arrays
allocate(lut_extliq(nsize_liq, nband), &
Expand All @@ -82,7 +82,7 @@ subroutine load_cld_lutcoeff(cloud_spec, cld_coeff_file)
ncid = nf90_close(ncid)
call stop_on_err(cloud_spec%load(band_lims_wvn, &
radliq_lwr, radliq_upr, &
radice_lwr, radice_upr, &
diamice_lwr, diamice_upr, &
lut_extliq, lut_ssaliq, lut_asyliq, &
lut_extice, lut_ssaice, lut_asyice))
end subroutine load_cld_lutcoeff
Expand Down
36 changes: 18 additions & 18 deletions rrtmgp-frontend/mo_cloud_optics_rrtmgp.F90
Original file line number Diff line number Diff line change
Expand Up @@ -44,7 +44,7 @@ module mo_cloud_optics_rrtmgp
!
! Upper and lower limits of the tables
real(wp) :: radliq_lwr = 0._wp, radliq_upr = 0._wp
real(wp) :: radice_lwr = 0._wp, radice_upr = 0._wp
real(wp) :: diamice_lwr = 0._wp, diamice_upr = 0._wp
! How many steps in the table? (for convenience)
integer :: liq_nsteps = 0, ice_nsteps = 0
! How big is each step in the table?
Expand Down Expand Up @@ -90,15 +90,15 @@ module mo_cloud_optics_rrtmgp
! ------------------------------------------------------------------------------
function load_lut(this, band_lims_wvn, &
radliq_lwr, radliq_upr, &
radice_lwr, radice_upr, &
diamice_lwr, diamice_upr, &
lut_extliq, lut_ssaliq, lut_asyliq, &
lut_extice, lut_ssaice, lut_asyice) result(error_msg)
class(ty_cloud_optics_rrtmgp), intent(inout) :: this
real(wp), dimension(:,:), intent(in ) :: band_lims_wvn ! Spectral discretization
! Lookup table interpolation constants
! Lower and upper bounds of the tables; also the constant for calculating interpolation indices for liquid
real(wp), intent(in ) :: radliq_lwr, radliq_upr
real(wp), intent(in ) :: radice_lwr, radice_upr
real(wp), intent(in ) :: diamice_lwr, diamice_upr
! LUT coefficients
! Extinction, single-scattering albedo, and asymmetry parameter for liquid and ice respectively
real(wp), dimension(:,:), intent(in) :: lut_extliq, lut_ssaliq, lut_asyliq
Expand Down Expand Up @@ -139,7 +139,7 @@ function load_lut(this, band_lims_wvn, &
this%liq_nsteps = nsize_liq
this%ice_nsteps = nsize_ice
this%liq_step_size = (radliq_upr - radliq_lwr)/real(nsize_liq-1,wp)
this%ice_step_size = (radice_upr - radice_lwr)/real(nsize_ice-1,wp)
this%ice_step_size = (diamice_upr - diamice_lwr)/real(nsize_ice-1,wp)
! Allocate LUT coefficients
allocate(this%lut_extliq(nsize_liq, nbnd), &
this%lut_ssaliq(nsize_liq, nbnd), &
Expand All @@ -157,8 +157,8 @@ function load_lut(this, band_lims_wvn, &
! Load LUT constants
this%radliq_lwr = radliq_lwr
this%radliq_upr = radliq_upr
this%radice_lwr = radice_lwr
this%radice_upr = radice_upr
this%diamice_lwr = diamice_lwr
this%diamice_upr = diamice_upr

! Load LUT coefficients
!$acc kernels
Expand Down Expand Up @@ -245,19 +245,19 @@ function load_pade(this, band_lims_wvn, &
!
this%radliq_lwr = pade_sizreg_extliq(1)
this%radliq_upr = pade_sizreg_extliq(nbound)
this%radice_lwr = pade_sizreg_extice(1)
this%radice_upr = pade_sizreg_extice(nbound)
this%diamice_lwr = pade_sizreg_extice(1)
this%diamice_upr = pade_sizreg_extice(nbound)
if(error_msg /= "") return

if(any([pade_sizreg_ssaliq(1), pade_sizreg_asyliq(1)] < this%radliq_lwr)) &
error_msg = "cloud_optics%init(): one or more Pade size regimes have inconsistent lowest values"
if(any([pade_sizreg_ssaice(1), pade_sizreg_asyice(1)] < this%radice_lwr)) &
if(any([pade_sizreg_ssaice(1), pade_sizreg_asyice(1)] < this%diamice_lwr)) &
error_msg = "cloud_optics%init(): one or more Pade size regimes have inconsistent lower values"

if(any([pade_sizreg_ssaliq(nbound), pade_sizreg_asyliq(nbound)] > this%radliq_upr)) &
error_msg = "cloud_optics%init(): one or more Pade size regimes have lowest value less than radliq_upr"
if(any([pade_sizreg_ssaice(nbound), pade_sizreg_asyice(nbound)] > this%radice_upr)) &
error_msg = "cloud_optics%init(): one or more Pade size regimes have lowest value less than radice_upr"
if(any([pade_sizreg_ssaice(nbound), pade_sizreg_asyice(nbound)] > this%diamice_upr)) &
error_msg = "cloud_optics%init(): one or more Pade size regimes have lowest value less than diamice_upr"
if(error_msg /= "") return
!
! Allocate Pade coefficients
Expand Down Expand Up @@ -321,8 +321,8 @@ subroutine finalize(this)

this%radliq_lwr = 0._wp
this%radliq_upr = 0._wp
this%radice_lwr = 0._wp
this%radice_upr = 0._wp
this%diamice_lwr = 0._wp
this%diamice_upr = 0._wp

! Lookup table cloud optics coefficients
if(allocated(this%lut_extliq)) then
Expand Down Expand Up @@ -463,8 +463,8 @@ function cloud_optics(this, &
if(check_values) then
if(any_vals_outside(reliq, liqmsk, this%radliq_lwr, this%radliq_upr)) &
error_msg = 'cloud optics: liquid effective radius is out of bounds'
if(any_vals_outside(reice, icemsk, this%radice_lwr, this%radice_upr)) &
error_msg = 'cloud optics: ice effective radius is out of bounds'
if(any_vals_outside(reice, icemsk, this%diamice_lwr, this%diamice_upr)) &
error_msg = 'cloud optics: ice effective diameter is out of bounds'
if(any_vals_less_than(clwp, liqmsk, 0._wp) .or. any_vals_less_than(ciwp, icemsk, 0._wp)) &
error_msg = 'cloud optics: negative clwp or ciwp where clouds are supposed to be'
end if
Expand Down Expand Up @@ -493,7 +493,7 @@ function cloud_optics(this, &
! Ice
!
call compute_cld_from_table(ncol, nlay, nbnd, icemsk, ciwp, reice, &
this%ice_nsteps,this%ice_step_size,this%radice_lwr, &
this%ice_nsteps,this%ice_step_size,this%diamice_lwr, &
this%lut_extice(:,:,this%icergh), &
this%lut_ssaice(:,:,this%icergh), &
this%lut_asyice(:,:,this%icergh), &
Expand Down Expand Up @@ -609,13 +609,13 @@ function get_min_radius_ice(this) result(r)
class(ty_cloud_optics_rrtmgp), intent(in ) :: this
real(wp) :: r

r = this%radice_lwr
r = this%diamice_lwr
end function get_min_radius_ice
!-----------------------------------------------
function get_max_radius_ice(this) result(r)
class(ty_cloud_optics_rrtmgp), intent(in ) :: this
real(wp) :: r

r = this%radice_upr
r = this%diamice_upr
end function get_max_radius_ice
end module mo_cloud_optics_rrtmgp

0 comments on commit 1e85cf9

Please sign in to comment.