diff --git a/bld/CLMBuildNamelist.pm b/bld/CLMBuildNamelist.pm
index 9562cca9bd..c88af453b5 100755
--- a/bld/CLMBuildNamelist.pm
+++ b/bld/CLMBuildNamelist.pm
@@ -5315,6 +5315,7 @@ sub write_output_files {
push @groups, "clm_canopy_inparm";
push @groups, "prigentroughness";
push @groups, "zendersoilerod";
+ push @groups, "for_testing_options";
if (remove_leading_and_trailing_quotes($nl->get_value('snow_cover_fraction_method')) eq 'SwensonLawrence2012') {
push @groups, "scf_swenson_lawrence_2012_inparm";
}
diff --git a/bld/namelist_files/namelist_definition_ctsm.xml b/bld/namelist_files/namelist_definition_ctsm.xml
index 69a243bd27..2b5b4f2e99 100644
--- a/bld/namelist_files/namelist_definition_ctsm.xml
+++ b/bld/namelist_files/namelist_definition_ctsm.xml
@@ -1259,12 +1259,38 @@ Whether to use subgrid fluxes for snow
Whether snow on the vegetation canopy affects the radiation/albedo calculations
+
+
+
+
+
+
+For testing whether to bypass the rest of the initialization after the self test driver is run
+
+
+
+For testing whether to bypass most of the run phase other than the clock advance
+
+
+
+Whether to exit early after the initialization self tests are run. This is typically only used in automated tests.
+
+
+ group="for_testing_options" >
Whether to run some tests of ncdio_pio as part of the model run. This is
typically only used in automated tests.
+
+Whether to run some tests of decompInit (to get the gridcell to MPI task decomposition) as part of the model run. This is
+typically only used in automated tests.
+
+
If true, allocate memory for and use a second crop grain pool. This is
diff --git a/cime_config/buildlib b/cime_config/buildlib
index a4b853924e..3ce5080dc4 100755
--- a/cime_config/buildlib
+++ b/cime_config/buildlib
@@ -135,6 +135,7 @@ def _main_func():
os.path.join(lnd_root, "src", "dyn_subgrid"),
os.path.join(lnd_root, "src", "init_interp"),
os.path.join(lnd_root, "src", "self_tests"),
+ os.path.join(lnd_root, "src", "unit_test_shr"),
os.path.join(lnd_root, "src", "fates"),
os.path.join(lnd_root, "src", "fates", "main"),
os.path.join(lnd_root, "src", "fates", "biogeophys"),
diff --git a/cime_config/testdefs/ExpectedTestFails.xml b/cime_config/testdefs/ExpectedTestFails.xml
index f8f05bf5f1..34c3729b18 100644
--- a/cime_config/testdefs/ExpectedTestFails.xml
+++ b/cime_config/testdefs/ExpectedTestFails.xml
@@ -381,13 +381,6 @@
-
-
- FAIL
- #3316
-
-
-
diff --git a/cime_config/testdefs/testmods_dirs/clm/for_testing_fastsetup_bypassrun/user_nl_clm b/cime_config/testdefs/testmods_dirs/clm/for_testing_fastsetup_bypassrun/user_nl_clm
index c2a2d14793..573df5c02e 100644
--- a/cime_config/testdefs/testmods_dirs/clm/for_testing_fastsetup_bypassrun/user_nl_clm
+++ b/cime_config/testdefs/testmods_dirs/clm/for_testing_fastsetup_bypassrun/user_nl_clm
@@ -1,3 +1,6 @@
+! Exit early and bypass the run phase
+for_testing_exit_after_self_tests = .true.
+
! Turn off history, restarts, and output
hist_empty_htapes = .true.
use_noio = .true.
diff --git a/cime_config/testdefs/testmods_dirs/clm/run_self_tests/shell_commands b/cime_config/testdefs/testmods_dirs/clm/run_self_tests/shell_commands
new file mode 100755
index 0000000000..9383f70de0
--- /dev/null
+++ b/cime_config/testdefs/testmods_dirs/clm/run_self_tests/shell_commands
@@ -0,0 +1,9 @@
+#!/bin/bash
+./xmlchange CLM_FORCE_COLDSTART="on"
+
+# We use this testmod in a _Ln1 test; this requires forcing the ROF coupling frequency to every time step
+./xmlchange ROF_NCPL=48
+
+# Restarts aren't allowed for these tests, and turn off CPL history
+./xmlchange REST_OPTION="never"
+./xmlchange HIST_OPTION="never"
diff --git a/cime_config/testdefs/testmods_dirs/clm/run_self_tests/user_nl_clm b/cime_config/testdefs/testmods_dirs/clm/run_self_tests/user_nl_clm
index 9e8e0fcd04..3a71b46936 100644
--- a/cime_config/testdefs/testmods_dirs/clm/run_self_tests/user_nl_clm
+++ b/cime_config/testdefs/testmods_dirs/clm/run_self_tests/user_nl_clm
@@ -1,5 +1,14 @@
+! Bypass as much of the init phase as can be done
+! Bypassing the run phase already was inherited from the for_testing_fastsetup_bypassrun testmod
+for_testing_bypass_init = .true.
+
+! Turn on some of the self tests
for_testing_run_ncdiopio_tests = .true.
! Turn off history, restarts, and output
hist_empty_htapes = .true.
use_noio = .true.
+for_testing_run_decomp_init_tests = .true.
+
+! Exit initialization phase after the self tests
+for_testing_bypass_init = .true.
diff --git a/src/cpl/nuopc/lnd_comp_nuopc.F90 b/src/cpl/nuopc/lnd_comp_nuopc.F90
index 3db987f2fa..3e0fc3c2f7 100644
--- a/src/cpl/nuopc/lnd_comp_nuopc.F90
+++ b/src/cpl/nuopc/lnd_comp_nuopc.F90
@@ -49,6 +49,7 @@ module lnd_comp_nuopc
use lnd_import_export , only : advertise_fields, realize_fields, import_fields, export_fields
use lnd_comp_shr , only : mesh, model_meshfile, model_clock
use perf_mod , only : t_startf, t_stopf, t_barrierf
+ use SelfTestDriver , only : for_testing_exit_after_self_tests
implicit none
private ! except
@@ -351,6 +352,8 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
use lnd_set_decomp_and_domain , only : lnd_set_decomp_and_domain_from_readmesh
use lnd_set_decomp_and_domain , only : lnd_set_mesh_for_single_column
use lnd_set_decomp_and_domain , only : lnd_set_decomp_and_domain_for_single_column
+ use SelfTestDriver , only : for_testing_bypass_init_after_self_tests, &
+ for_testing_exit_after_self_tests
! input/output variables
type(ESMF_GridComp) :: gcomp
@@ -500,6 +503,12 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
else
single_column = .false.
end if
+ !if ( for_testing_exit_after_self_tests) then
+ ! *******************
+ ! *** RETURN HERE ***
+ ! *******************
+ !RETURN
+ !end if
!----------------------------------------------------------------------------
! Reset shr logging to my log file
@@ -676,14 +685,19 @@ subroutine InitializeRealize(gcomp, importState, exportState, clock, rc)
call t_startf('clm_init2')
call initialize2(ni, nj, currtime)
call t_stopf('clm_init2')
+ if (for_testing_exit_after_self_tests) then
+ RETURN
+ end if
!--------------------------------
! Create land export state
!--------------------------------
+ if ( .not. for_testing_bypass_init_after_self_tests() ) then
call get_proc_bounds(bounds)
call export_fields(gcomp, bounds, glc_present, rof_prognostic, &
water_inst%waterlnd2atmbulk_inst, lnd2atm_inst, lnd2glc_inst, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
+ end if
! Set scalars in export state
call State_SetScalar(dble(ldomain%ni), flds_scalar_index_nx, exportState, &
@@ -731,6 +745,7 @@ subroutine ModelAdvance(gcomp, rc)
use clm_instMod , only : water_inst, atm2lnd_inst, glc2lnd_inst, lnd2atm_inst, lnd2glc_inst
use decompMod , only : bounds_type, get_proc_bounds
use clm_driver , only : clm_drv
+ use SelfTestDriver, only : for_testing_bypass_init_after_self_tests
! input/output variables
type(ESMF_GridComp) :: gcomp
@@ -786,6 +801,9 @@ subroutine ModelAdvance(gcomp, rc)
if (single_column .and. .not. scol_valid) then
RETURN
end if
+ !if (for_testing_exit_after_self_tests) then
+ ! RETURN
+ !end if
!$ call omp_set_num_threads(nthrds)
@@ -818,16 +836,20 @@ subroutine ModelAdvance(gcomp, rc)
flds_scalar_index_nextsw_cday, nextsw_cday, &
flds_scalar_name, flds_scalar_num, rc)
- ! Get proc bounds
- call get_proc_bounds(bounds)
-
!--------------------------------
! Unpack import state
!--------------------------------
+ if ( .not. for_testing_bypass_init_after_self_tests() ) then
+ ! Get proc bounds for both import and export
+ call get_proc_bounds(bounds)
+
+ call t_startf ('lc_lnd_import')
call import_fields( gcomp, bounds, glc_present, rof_prognostic, &
atm2lnd_inst, glc2lnd_inst, water_inst%wateratm2lndbulk_inst, rc )
if (ChkErr(rc,__LINE__,u_FILE_u)) return
+ call t_stopf ('lc_lnd_import')
+ end if
!--------------------------------
! Run model
@@ -917,9 +939,13 @@ subroutine ModelAdvance(gcomp, rc)
! Pack export state
!--------------------------------
+ if ( .not. for_testing_bypass_init_after_self_tests() ) then
+ call t_startf ('lc_lnd_export')
call export_fields(gcomp, bounds, glc_present, rof_prognostic, &
water_inst%waterlnd2atmbulk_inst, lnd2atm_inst, lnd2glc_inst, rc)
if (ChkErr(rc,__LINE__,u_FILE_u)) return
+ call t_stopf ('lc_lnd_export')
+ end if
!--------------------------------
! Advance ctsm time step
@@ -1009,6 +1035,7 @@ subroutine ModelSetRunClock(gcomp, rc)
rc = ESMF_SUCCESS
call ESMF_LogWrite(subname//' called', ESMF_LOGMSG_INFO)
if (.not. scol_valid) return
+ !if (for_testing_exit_after_self_tests) return
! query the Component for its clocks
call NUOPC_ModelGet(gcomp, driverClock=dclock, modelClock=mclock, rc=rc)
@@ -1320,6 +1347,9 @@ subroutine CheckImport(gcomp, rc)
if (single_column .and. .not. scol_valid) then
RETURN
end if
+ !if (for_testing_exit_after_self_tests) then
+ !RETURN
+ !end if
! The remander of this should be equivalent to the NUOPC internal routine
! from NUOPC_ModeBase.F90
diff --git a/src/main/clm_driver.F90 b/src/main/clm_driver.F90
index 3a47a7eed3..279154f52c 100644
--- a/src/main/clm_driver.F90
+++ b/src/main/clm_driver.F90
@@ -85,6 +85,7 @@ module clm_driver
use clm_instMod
use SoilMoistureStreamMod , only : PrescribedSoilMoistureInterp, PrescribedSoilMoistureAdvance
use SoilBiogeochemDecompCascadeConType , only : no_soil_decomp, decomp_method
+ use SelfTestDriver , only : for_testing_bypass_run_except_clock_advance
!
! !PUBLIC TYPES:
implicit none
@@ -165,6 +166,7 @@ subroutine clm_drv(doalb, nextsw_cday, declinp1, declin, rstwr, nlend, rdate, ro
! CalcIrrigationNeeded. Simply declaring this variable makes the ICE go away.
real(r8), allocatable :: dummy1_to_make_pgi_happy(:)
!-----------------------------------------------------------------------
+ if ( for_testing_bypass_run_except_clock_advance() ) return
! Determine processor bounds and clumps for this processor
@@ -1576,6 +1578,8 @@ subroutine clm_drv_init(bounds, &
integer :: fp, fc ! filter indices
!-----------------------------------------------------------------------
+ if ( for_testing_bypass_run_except_clock_advance() ) return
+
associate( &
snl => col%snl , & ! Input: [integer (:) ] number of snow layers
@@ -1657,6 +1661,7 @@ subroutine clm_drv_patch2col (bounds, &
! !LOCAL VARIABLES:
integer :: c,fc ! indices
! -----------------------------------------------------------------
+ if ( for_testing_bypass_run_except_clock_advance() ) return
! Note: lake points are excluded from many of the following
! averages. For some fields, this is because the field doesn't
@@ -1752,6 +1757,8 @@ subroutine write_diagnostic (bounds, nstep, lnd2atm_inst)
integer :: status(MPI_STATUS_SIZE) ! mpi status
!------------------------------------------------------------------------
+ if ( for_testing_bypass_run_except_clock_advance() ) return
+
call get_proc_global(ng=numg)
if (masterproc) then
diff --git a/src/main/clm_initializeMod.F90 b/src/main/clm_initializeMod.F90
index 1c26b55cfd..0ffa7737a8 100644
--- a/src/main/clm_initializeMod.F90
+++ b/src/main/clm_initializeMod.F90
@@ -30,7 +30,7 @@ module clm_initializeMod
use CLMFatesInterfaceMod , only : CLMFatesGlobals1,CLMFatesGlobals2
use CLMFatesInterfaceMod , only : CLMFatesTimesteps
use dynSubgridControlMod , only : dynSubgridControl_init, get_reset_dynbal_baselines
- use SelfTestDriver , only : self_test_driver
+ use SelfTestDriver , only : self_test_driver, for_testing_bypass_init_after_self_tests
use SoilMoistureStreamMod , only : PrescribedSoilMoistureInit
use clm_instMod
!
@@ -67,6 +67,7 @@ subroutine initialize1(dtime)
use SoilBiogeochemDecompCascadeConType , only : decomp_cascade_par_init
use CropReprPoolsMod , only: crop_repr_pools_init
use HillslopeHydrologyMod, only: hillslope_properties_init
+ use SelfTestDriver , only: self_test_readnml
!
! !ARGUMENTS
integer, intent(in) :: dtime ! model time step (seconds)
@@ -102,6 +103,8 @@ subroutine initialize1(dtime)
call surfrd_get_num_patches(fsurdat, actual_maxsoil_patches, actual_numpft, actual_numcft)
call surfrd_get_nlevurb(fsurdat, actual_nlevurb)
+ call self_test_readnml( NLFilename )
+
! If fates is on, we override actual_maxsoil_patches. FATES dictates the
! number of patches per column. We still use numcft from the surface
! file though...
@@ -182,6 +185,7 @@ subroutine initialize2(ni,nj, currtime)
use FATESFireFactoryMod , only : scalar_lightning
use dynFATESLandUseChangeMod , only : dynFatesLandUseInit
use HillslopeHydrologyMod , only : InitHillslope
+ use SelfTestDriver , only : for_testing_bypass_init_after_self_tests
!
! !ARGUMENTS
integer, intent(in) :: ni, nj ! global grid sizes
@@ -333,6 +337,7 @@ subroutine initialize2(ni,nj, currtime)
! Run any requested self-tests
call self_test_driver(bounds_proc)
+ if ( .not. for_testing_bypass_init_after_self_tests() )then
! Deallocate surface grid dynamic memory for variables that aren't needed elsewhere.
! Some things are kept until the end of initialize2; urban_valid is kept through the
! end of the run for error checking, pct_urban_max is kept through the end of the run
@@ -349,8 +354,9 @@ subroutine initialize2(ni,nj, currtime)
allocate(nutrient_competition_method, &
source=create_nutrient_competition_method(bounds_proc))
call readParameters(photosyns_inst)
-
+ end if ! End of bypass
+ ! Self test skipping should still do the time manager initialization
! Initialize time manager
if (nsrest == nsrStartup) then
call timemgr_init()
@@ -376,6 +382,7 @@ subroutine initialize2(ni,nj, currtime)
call t_stopf('clm_init2_part2')
call t_startf('clm_init2_part3')
+ if ( .not. for_testing_bypass_init_after_self_tests() )then
! Initialize Balance checking (after time-manager)
call BalanceCheckInit()
@@ -423,7 +430,9 @@ subroutine initialize2(ni,nj, currtime)
call SnowAge_init( ) ! SNICAR aging parameters:
! Print history field info to standard out
- call hist_printflds()
+ if ( .not. use_noio )then
+ call hist_printflds()
+ end if
! Initializate dynamic subgrid weights (for prescribed transient Patches, CNDV
! and/or dynamic landunits); note that these will be overwritten in a restart run
@@ -508,6 +517,7 @@ subroutine initialize2(ni,nj, currtime)
if (nsrest == nsrContinue ) then
call htapes_fieldlist()
end if
+ end if ! End of bypass
! Read restart/initial info
is_cold_start = .false.
@@ -601,6 +611,8 @@ subroutine initialize2(ni,nj, currtime)
call t_stopf('clm_init2_init_interp')
end if
+ if ( .not. for_testing_bypass_init_after_self_tests() )then
+
! If requested, reset dynbal baselines
! This needs to happen after reading the restart file (including after reading the
! interpolated restart file, if applicable).
@@ -759,6 +771,7 @@ subroutine initialize2(ni,nj, currtime)
water_inst%waterdiagnosticbulk_inst, canopystate_inst, &
soilstate_inst, soilbiogeochem_carbonflux_inst)
end if
+ end if ! end of bypass
! topo_glc_mec was allocated in initialize1, but needed to be kept around through
! initialize2 because it is used to initialize other variables; now it can be deallocated
diff --git a/src/main/controlMod.F90 b/src/main/controlMod.F90
index 089503dc8b..4a956e33b2 100644
--- a/src/main/controlMod.F90
+++ b/src/main/controlMod.F90
@@ -210,7 +210,7 @@ subroutine control_init(dtime)
snow_thermal_cond_method, snow_thermal_cond_glc_method, &
snow_thermal_cond_lake_method, snow_cover_fraction_method, &
irrigate, run_zero_weight_urban, all_active, &
- crop_fsat_equals_zero, for_testing_run_ncdiopio_tests, &
+ crop_fsat_equals_zero, &
for_testing_use_second_grain_pool, for_testing_use_repr_structure_pool, &
for_testing_no_crop_seed_replenishment, &
z0param_method, use_z0m_snowmelt
@@ -766,9 +766,6 @@ subroutine control_spmd()
! Crop saturated excess runoff
call mpi_bcast(crop_fsat_equals_zero, 1, MPI_LOGICAL, 0, mpicom, ier)
- ! Whether to run tests of ncdio_pio
- call mpi_bcast(for_testing_run_ncdiopio_tests, 1, MPI_LOGICAL, 0, mpicom, ier)
-
! Various flags used for testing infrastructure for having multiple crop reproductive pools
call mpi_bcast(for_testing_use_second_grain_pool, 1, MPI_LOGICAL, 0, mpicom, ier)
call mpi_bcast(for_testing_use_repr_structure_pool, 1, MPI_LOGICAL, 0, mpicom, ier)
diff --git a/src/self_tests/SelfTestDriver.F90 b/src/self_tests/SelfTestDriver.F90
index d109a27827..208c60c1db 100644
--- a/src/self_tests/SelfTestDriver.F90
+++ b/src/self_tests/SelfTestDriver.F90
@@ -6,9 +6,10 @@ module SelfTestDriver
!
! See the README file in this directory for a high-level overview of these self-tests.
- use clm_varctl, only : for_testing_run_ncdiopio_tests
use decompMod, only : bounds_type
use TestNcdioPio, only : test_ncdio_pio
+ use abortutils, only : endrun
+ use clm_varctl, only : iulog
implicit none
private
@@ -16,7 +17,17 @@ module SelfTestDriver
! Public routines
- public :: self_test_driver
+ public :: self_test_driver ! Run the self-tests asked for
+ public :: self_test_readnml ! Read in the general self testing options for overall code flow
+ public :: for_testing_bypass_init_after_self_tests ! For testing bypass the rest of the initialization after the self test driver was run
+ public :: for_testing_bypass_run_except_clock_advance ! For testing bypass most of the run phase other than the clock advance
+
+ ! Private module data
+ logical :: for_testing_bypass_init ! For testing bypass the initialization phase after the self-test driver
+ logical :: for_testing_bypass_run ! For testing bypass most of the run phase except the time advance
+ logical :: for_testing_run_ncdiopio_tests ! true => run tests of ncdio_pio
+ logical :: for_testing_run_decomp_init_tests ! true => run tests of decompInit
+ logical, public :: for_testing_exit_after_self_tests ! true => exit after running self tests
character(len=*), parameter, private :: sourcefile = &
__FILE__
@@ -32,6 +43,12 @@ subroutine self_test_driver(bounds)
! This subroutine should be called all the time, but each set of self tests is only
! run if the appropriate flag is set.
!
+ ! !USES:
+ use decompMod, only : bounds_type
+ use TestNcdioPio, only : test_ncdio_pio
+ use ESMF, only : ESMF_LogWrite, ESMF_LOGMSG_INFO, ESMF_Finalize
+ use shr_sys_mod, only : shr_sys_flush
+ use spmdMod, only : masterproc
! !ARGUMENTS:
type(bounds_type), intent(in) :: bounds
!
@@ -46,4 +63,90 @@ subroutine self_test_driver(bounds)
end subroutine self_test_driver
+ !-----------------------------------------------------------------------
+ subroutine self_test_readnml(NLFileName)
+ !
+ ! !DESCRIPTION:
+ ! Namelist read for the self-test driver. This includes bypass options
+ ! that will be used in other parts of the code to bypass bits of the code
+ ! for testing purposes.
+ !
+ ! !USES:
+ use shr_nl_mod , only : shr_nl_find_group_name
+ use spmdMod, only : masterproc, mpicom
+ use shr_mpi_mod, only : shr_mpi_bcast
+ use clm_varctl, only : iulog
+ !
+ ! !ARGUMENTS:
+ character(len=*), intent(in) :: NLFilename ! Namelist filename
+ !
+ ! !LOCAL VARIABLES:
+ integer :: ierr ! error code
+ integer :: unitn ! unit for namelist file
+
+ ! Namelist name: this has to be matched with the name in the read stqatement
+ character(len=*), parameter :: nmlname = 'for_testing_options'
+ !-----------------------------------------------------------------------
+
+ namelist /for_testing_options/ for_testing_bypass_init, for_testing_bypass_run, &
+ for_testing_run_ncdiopio_tests, for_testing_run_decomp_init_tests, &
+ for_testing_exit_after_self_tests
+
+ ! Initialize options to default values, in case they are not specified in
+ ! the namelist
+
+ if (masterproc) then
+ write(iulog,*) 'Read in '//nmlname//' namelist'
+ open(newunit=unitn, status='old', file=NLFilename)
+ call shr_nl_find_group_name(unitn, nmlname, status=ierr)
+ if (ierr == 0) then
+ read(unit=unitn, nml=for_testing_options, iostat=ierr)
+ if (ierr /= 0) then
+ call endrun(msg="ERROR reading "//nmlname//"namelist", file=sourcefile, line=__LINE__)
+ end if
+ else
+ call endrun(msg="ERROR finding "//nmlname//"namelist", file=sourcefile, line=__LINE__)
+ end if
+ close(unitn)
+ end if
+
+ call shr_mpi_bcast (for_testing_bypass_init, mpicom)
+ call shr_mpi_bcast (for_testing_bypass_run, mpicom)
+ call shr_mpi_bcast(for_testing_run_ncdiopio_tests, mpicom)
+ call shr_mpi_bcast(for_testing_run_decomp_init_tests, mpicom)
+ call shr_mpi_bcast(for_testing_exit_after_self_tests, mpicom)
+
+ if (masterproc) then
+ write(iulog,*) ' '
+ write(iulog,*) nmlname//' settings:'
+ write(iulog,nml=for_testing_options)
+ write(iulog,*) ' '
+ end if
+
+ end subroutine self_test_readnml
+
+ !-----------------------------------------------------------------------
+
+ logical function for_testing_bypass_init_after_self_tests()
+ ! Determine if should exit initialization early after having run the self tests
+ if ( for_testing_bypass_init ) then
+ for_testing_bypass_init_after_self_tests = .true.
+ else
+ for_testing_bypass_init_after_self_tests = .false.
+ end if
+ end function for_testing_bypass_init_after_self_tests
+
+ !-----------------------------------------------------------------------
+
+ logical function for_testing_bypass_run_except_clock_advance()
+ ! Determine if should skip most of the run phase other than the clock advance
+ if ( for_testing_bypass_init ) then
+ for_testing_bypass_run_except_clock_advance = .true.
+ else
+ for_testing_bypass_run_except_clock_advance = .false.
+ end if
+ end function for_testing_bypass_run_except_clock_advance
+
+ !-----------------------------------------------------------------------
+
end module SelfTestDriver