Skip to content

Commit

Permalink
Initialize input fields needed for unit-testing of dust emissions and…
Browse files Browse the repository at this point in the history
… get the unit tester to PASS!
  • Loading branch information
ekluzek committed May 18, 2024
1 parent 3254949 commit 5244813
Show file tree
Hide file tree
Showing 4 changed files with 235 additions and 15 deletions.
205 changes: 195 additions & 10 deletions src/biogeochem/test/DustEmis_test/test_DustEmis.pf
Original file line number Diff line number Diff line change
Expand Up @@ -5,15 +5,20 @@ module test_DustEmis
use funit
use unittestSubgridMod
use unittestSimpleSubgridSetupsMod, only : setup_single_veg_patch
use clm_varpar, only : nlevsoi, nlevgrnd, nlevsno, clm_varpar_init
use clm_varctl, only : soil_layerstruct_predefined, create_crop_landunit, use_crop, create_crop_landunit
use clm_varcon, only : clm_varcon_init, clm_varcon_clean
use SnowHydrologyMod, only : InitSnowLayers, SnowHydrologySetControlForTesting
use DUSTMod
use shr_kind_mod , only : r8 => shr_kind_r8
use unittestFilterBuilderMod, only : filter_from_range
use atm2lndType, only : atm2lnd_type
use atm2lndType, only : atm2lnd_type, atm2lnd_params_type
use SoilStateType, only : soilstate_type
use CanopyStateType, only : canopystate_type
use WaterStateBulkType, only : waterstatebulk_type
use WaterDiagnosticBulkType, only : waterdiagnosticbulk_type
use TemperatureType, only : temperature_type
use WaterType, only : water_type
use FrictionVelocityMod, only : frictionvel_type
use unittestWaterTypeFactory, only : unittest_water_type_factory_type

implicit none

Expand All @@ -25,42 +30,222 @@ module test_DustEmis
type(atm2lnd_type) :: atm2lnd_inst
type(soilstate_type) :: soilstate_inst
type(canopystate_type) :: canopystate_inst
type(WaterStateBulk_Type) :: waterstatebulk_inst
type(waterdiagnosticbulk_type) :: waterdiagnosticbulk_inst
type(temperature_type) :: temperature_inst
type(unittest_water_type_factory_type) :: water_factory
type(water_type) :: water_inst
type(frictionvel_type) :: frictionvel_inst
contains
procedure :: setUp
procedure :: tearDown
procedure :: setupEnvironment
procedure :: create_atm2lnd
procedure :: create_fv
end type TestDustEmis

contains

!-----------------------------------------------------------------------

subroutine setUp(this)
use ColumnType, only : col
class(TestDustEmis), intent(inout) :: this

character(len=5) :: NLFilename = 'none'
real(r8), allocatable :: snow_depth_col(:)
real(r8), allocatable :: urb_em(:)
integer :: begl, endl, begc, endc
integer :: c
type(atm2lnd_params_type) :: atm2lnd_params

soil_layerstruct_predefined = '20SL_8.5m'
create_crop_landunit = .true.
use_crop = .false.
call clm_varpar_init( actual_maxsoil_patches=17, surf_numpft=15, surf_numcft=2, actual_nlevurb=5 )
call clm_varcon_init( is_simple_buildtemp=.true.)
call this%water_factory%init()
call this%water_factory%setup_before_subgrid( &
my_nlevsoi = nlevsoi, &
nlevgrnd_additional = nlevgrnd - nlevsoi, &
my_nlevsno = 3)
call setup_single_veg_patch( pft_type=0 )
begl = bounds%begl
endl = bounds%endl
begc = bounds%begc
endc = bounds%endc
allocate( urb_em(begl:endl) )

call setup_single_veg_patch( pft_type=0 )
call this%dust_emis%Init( bounds, NLFilename )
call filter_from_range(start=bounds%begp, end=bounds%endp, numf=this%num_nolakep, filter=this%filter_nolakep)
call this%dust_emis%Init( bounds, NLFilename )
call filter_from_range(start=bounds%begp, end=bounds%endp, numf=this%num_nolakep, filter=this%filter_nolakep)
atm2lnd_params = atm2lnd_params_type( repartition_rain_snow = .false., &
glcmec_downscale_longwave = .false., &
lapse_rate = 0.01_r8 & ! arbitrary (this is unused for these tests)
)
allocate (snow_depth_col(begc:endc))
snow_depth_col(begc:endc) = 0.0_r8
call SnowHydrologySetControlForTesting()
call InitSnowLayers(bounds, snow_depth_col(bounds%begc:bounds%endc))
call this%water_factory%setup_after_subgrid(snl = 3)
call this%soilstate_inst%Init(bounds)
do c = begc, endc
this%soilstate_inst%watsat_col(c,:) = 0.05_r8 * (c - bounds%begc + 1)
end do
call this%setupEnvironment( )
call this%water_factory%create_water_type(this%water_inst, watsat_col=this%soilstate_inst%watsat_col)
call this%atm2lnd_inst%InitForTesting(bounds, atm2lnd_params)
call this%canopystate_inst%SetNMLForTesting()
call this%canopystate_inst%Init(bounds)
call this%frictionvel_inst%InitForTesting(bounds)
urb_em(begl:endl) = 0.99_r8
call this%temperature_inst%Init(bounds, &
em_roof_lun=urb_em(begl:endl), &
em_wall_lun=urb_em(begl:endl), &
em_improad_lun=urb_em(begl:endl), &
em_perroad_lun=urb_em(begl:endl), &
is_simple_buildtemp=.true., is_prog_buildtemp=.false.)
deallocate (snow_depth_col )
deallocate( urb_em )
end subroutine setUp

!-----------------------------------------------------------------------

subroutine tearDown(this)
class(TestDustEmis), intent(inout) :: this

call this%water_factory%teardown(this%water_inst)
call unittest_subgrid_teardown()
call this%atm2lnd_inst%Clean()
call clm_varcon_clean()
deallocate( this%filter_nolakep )
end subroutine tearDown

!-----------------------------------------------------------------------

subroutine setupEnvironment(this)
!
! !DESCRIPTION:
! Sets up the external environment used by Dust emissions - i.e., things accessed via
! 'use' statements.
!
! Assumes nlevgrnd and nlevsoi have been set, and that all necessary subgrid setup has
! been completed.
!
use ColumnType, only : col
use GridcellType, only : grc
class(TestDustEmis), intent(in) :: this
!
integer :: c,j
real(r8), parameter :: clay = 10.0_r8

!-----------------------------------------------------------------------
col%dz(:,1:nlevgrnd) = 1.0_r8
do j = 1, nlevgrnd
do c = bounds%begc, bounds%endc
col%z(c,j) = sum(col%dz(c,1:j-1)) + 0.5_r8*col%dz(c,j)
end do
end do

do c = bounds%begc, bounds%endc
! Setting nbedrock to nlevsoi means that none of the layers from 1:nlevsoi are
! considered bedrock
col%nbedrock(c) = nlevsoi

this%soilstate_inst%gwc_thr_col(c) = 0.17_r8 + 0.14_r8 * clay * 0.01_r8
this%soilstate_inst%mss_frc_cly_vld_col(c) = 0.17_r8
end do


! Use longitude along Greenich so don't have to calculate offsets for longitudes (that's calculated in clm_time_manager)
grc%londeg(:) = 0.0_r8

grc%area(:) = 10.0_r8

end subroutine setupEnvironment

!-----------------------------------------------------------------------

subroutine create_atm2lnd(this, forc_t, forc_pbot, forc_rho )
! Initializes some fields needed for dust emissions in this%atm2lnd_inst, and sets
! forcing fields based on inputs. Excluded inputs are given a default value
class(TestDustEmis), intent(inout) :: this
real(r8), intent(in), optional :: forc_t(:)
real(r8), intent(in), optional :: forc_pbot(:)
real(r8), intent(in), optional :: forc_rho(:)

real(r8), parameter :: forc_t_default = 301._r8
real(r8), parameter :: forc_pbot_default = 100000._r8
real(r8), parameter :: forc_rho_default = 1.1_r8
! ------------------------------------------------------------------------

if (present(forc_t)) then
this%atm2lnd_inst%forc_t_downscaled_col(bounds%begc:bounds%endc) = forc_t(:)
else
this%atm2lnd_inst%forc_t_downscaled_col(bounds%begc:bounds%endc) = forc_t_default
end if

if (present(forc_pbot)) then
this%atm2lnd_inst%forc_pbot_downscaled_col(bounds%begc:bounds%endc) = forc_pbot(:)
else
this%atm2lnd_inst%forc_pbot_downscaled_col(bounds%begc:bounds%endc) = forc_pbot_default
end if

if (present(forc_rho)) then
this%atm2lnd_inst%forc_rho_downscaled_col(bounds%begc:bounds%endc) = forc_rho(:)
else
this%atm2lnd_inst%forc_rho_downscaled_col(bounds%begc:bounds%endc) = forc_rho_default
end if

end subroutine create_atm2lnd

!-----------------------------------------------------------------------

subroutine create_fv(this, fv, u10, ram1)
! Initializes some fields needed for dust emissions in this%frictionvel_inst, and sets
! fields based on inputs. Excluded inputs are given a default value
class(TestDustEmis), intent(inout) :: this
real(r8), intent(in), optional :: fv(:)
real(r8), intent(in), optional :: u10(:)
real(r8), intent(in), optional :: ram1(:)

real(r8), parameter :: fv_default = 0.2_r8
real(r8), parameter :: u10_default = 4._r8
real(r8), parameter :: ram1_default = 200._r8
! ------------------------------------------------------------------------

if (present(fv)) then
this%frictionvel_inst%fv_patch(bounds%begp:bounds%endp) = fv(:)
else
this%frictionvel_inst%fv_patch(bounds%begp:bounds%endp) = fv_default
end if

if (present(u10)) then
this%frictionvel_inst%u10_patch(bounds%begp:bounds%endp) = u10(:)
else
this%frictionvel_inst%u10_patch(bounds%begp:bounds%endp) = u10_default
end if

if (present(ram1)) then
this%frictionvel_inst%ram1_patch(bounds%begp:bounds%endp) = ram1(:)
else
this%frictionvel_inst%ram1_patch(bounds%begp:bounds%endp) = ram1_default
end if

end subroutine create_fv

!-----------------------------------------------------------------------

@Test
subroutine check_dust_emis(this)
class(TestDustEmis), intent(inout) :: this

call this%create_atm2lnd()
call this%create_fv()
call DustEmission(bounds, this%num_nolakep, this%filter_nolakep, this%atm2lnd_inst, &
this%soilstate_inst, this%canopystate_inst, this%waterstatebulk_inst, &
this%waterdiagnosticbulk_inst, this%frictionvel_inst, this%dust_emis)
this%soilstate_inst, this%canopystate_inst, this%water_inst%waterstatebulk_inst, &
this%water_inst%waterdiagnosticbulk_inst, this%frictionvel_inst, this%dust_emis)
call DustDryDep(bounds, this%atm2lnd_inst, this%frictionvel_inst, this%dust_emis)

!-----------------------------------------------------------------------

end subroutine check_dust_emis

end module test_DustEmis
17 changes: 17 additions & 0 deletions src/biogeophys/CanopyStateType.F90
Original file line number Diff line number Diff line change
Expand Up @@ -72,6 +72,8 @@ module CanopyStateType
procedure, public :: UpdateAccVars
procedure, public :: Restart

procedure, public :: SetNMLForTesting ! Set namelist for unit-testing

end type CanopyState_type

character(len=*), parameter, private :: sourcefile = &
Expand Down Expand Up @@ -442,6 +444,21 @@ subroutine ReadNML( this, NLFilename )

end subroutine ReadNML

!-----------------------------------------------------------------------

subroutine SetNMLForTesting( this )
!
! Set canopy parameter namelist control settings for unit-testing
!
class(canopystate_type) :: this
! LOCAL VARIABLES:
!-----------------------------------------------------------------------


this%leaf_mr_vcm = 0.015_r8

end subroutine SetNMLForTesting

!-----------------------------------------------------------------------
subroutine UpdateAccVars (this, bounds)
!
Expand Down
18 changes: 18 additions & 0 deletions src/biogeophys/FrictionVelocityMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -89,6 +89,8 @@ module FrictionVelocityMod
procedure, public :: FrictionVelocity ! Calculate friction velocity
procedure, public :: MoninObukIni ! Initialization of the Monin-Obukhov length

procedure, public :: InitForTesting ! version of Init meant for unit testing

! Private procedures
procedure, private :: InitAllocate
procedure, private :: InitHistory
Expand Down Expand Up @@ -122,6 +124,22 @@ subroutine Init(this, bounds, NLFilename, params_ncid)

end subroutine Init

!------------------------------------------------------------------------
subroutine InitForTesting(this, bounds)
! Initialization for unit testing, hardcodes namelist and parameter file settings
class(frictionvel_type) :: this
type(bounds_type), intent(in) :: bounds

call this%InitAllocate(bounds)
call this%InitHistory(bounds)
call this%InitCold(bounds)
this%zetamaxstable = 0.5_r8
this%zsno = 0.00085_r8
this%zlnd = 0.000775_r8
this%zglc = 0.00230000005_r8

end subroutine InitForTesting

!------------------------------------------------------------------------
subroutine InitAllocate(this, bounds)
!
Expand Down
10 changes: 5 additions & 5 deletions src/main/clm_instMod.F90
Original file line number Diff line number Diff line change
Expand Up @@ -296,11 +296,11 @@ subroutine clm_instInit(bounds)
! Initialization of public data types

call temperature_inst%Init(bounds, &
urbanparams_inst%em_roof(begl:endl), &
urbanparams_inst%em_wall(begl:endl), &
urbanparams_inst%em_improad(begl:endl), &
urbanparams_inst%em_perroad(begl:endl), &
IsSimpleBuildTemp(), IsProgBuildTemp() )
em_roof_lun=urbanparams_inst%em_roof(begl:endl), &
em_wall_lun=urbanparams_inst%em_wall(begl:endl), &
em_improad_lun=urbanparams_inst%em_improad(begl:endl), &
em_perroad_lun=urbanparams_inst%em_perroad(begl:endl), &
is_simple_buildtemp=IsSimpleBuildTemp(), is_prog_buildtemp=IsProgBuildTemp() )

call active_layer_inst%Init(bounds)

Expand Down

0 comments on commit 5244813

Please sign in to comment.