Skip to content

Commit

Permalink
Set --enable-tests and --enable-benchmarks optimistically #805
Browse files Browse the repository at this point in the history
  • Loading branch information
snoyberg committed Aug 18, 2015
1 parent 4159ec0 commit 00c8778
Show file tree
Hide file tree
Showing 7 changed files with 82 additions and 18 deletions.
1 change: 1 addition & 0 deletions ChangeLog.md
Original file line number Diff line number Diff line change
Expand Up @@ -12,6 +12,7 @@ Other enhancements:
* Code page changes on Windows only apply to the build command (and its synonyms), and can be controlled via a command line flag (still defaults to on) [#757](https://github.com/commercialhaskell/stack/issues/757)
* Implicitly add packages to extra-deps when a flag for them is set [#807](https://github.com/commercialhaskell/stack/issues/807)
* Use a precompiled Setup.hs for simple build types [#801](https://github.com/commercialhaskell/stack/issues/801)
* Set --enable-tests and --enable-benchmarks optimistically [#805](https://github.com/commercialhaskell/stack/issues/805)

Bug fixes:

Expand Down
2 changes: 1 addition & 1 deletion src/Stack/Build.hs
Original file line number Diff line number Diff line change
Expand Up @@ -98,7 +98,7 @@ build setLocalFiles mbuildLk bopts = do

if boptsDryrun bopts
then printPlan plan
else executePlan menv bopts baseConfigOpts locals sourceMap plan
else executePlan menv bopts baseConfigOpts locals sourceMap installedMap plan
where
profiling = boptsLibProfile bopts || boptsExeProfile bopts

Expand Down
8 changes: 7 additions & 1 deletion src/Stack/Build/ConstructPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -445,14 +445,20 @@ checkDirtiness ps installed package present wanted = do
case moldOpts of
Nothing -> Just "old configure information not found"
Just oldOpts
| oldOpts /= wantConfigCache -> Just $ describeConfigDiff oldOpts wantConfigCache
| stripIgnoredOpts oldOpts /= stripIgnoredOpts wantConfigCache -> Just $ describeConfigDiff oldOpts wantConfigCache
| psDirty ps -> Just "local file changes"
| otherwise -> Nothing
case mreason of
Nothing -> return False
Just reason -> do
tell mempty { wDirty = Map.singleton (packageName package) reason }
return True
where
stripIgnoredOpts cc = cc
{ configCacheOpts = filter
(`Set.notMember` Set.fromList ["--enable-tests", "--enable-benchmarks"])
(configCacheOpts cc)
}

describeConfigDiff :: ConfigCache -> ConfigCache -> Text
describeConfigDiff old new
Expand Down
70 changes: 54 additions & 16 deletions src/Stack/Build/Execute.hs
Original file line number Diff line number Diff line change
Expand Up @@ -317,10 +317,11 @@ executePlan :: M env m
-> BaseConfigOpts
-> [LocalPackage]
-> SourceMap
-> InstalledMap
-> Plan
-> m ()
executePlan menv bopts baseConfigOpts locals sourceMap plan = do
withExecuteEnv menv bopts baseConfigOpts locals sourceMap (executePlan' plan)
executePlan menv bopts baseConfigOpts locals sourceMap installedMap plan = do
withExecuteEnv menv bopts baseConfigOpts locals sourceMap (executePlan' installedMap plan)

unless (Map.null $ planInstallExes plan) $ do
snapBin <- (</> bindirSuffix) `liftM` installationRootDeps
Expand Down Expand Up @@ -400,10 +401,11 @@ windowsRenameCopy src dest = do

-- | Perform the actual plan (internal)
executePlan' :: M env m
=> Plan
=> InstalledMap
-> Plan
-> ExecuteEnv
-> m ()
executePlan' plan ee@ExecuteEnv {..} = do
executePlan' installedMap plan ee@ExecuteEnv {..} = do
wc <- getWhichCompiler
case Map.toList $ planUnregisterLocal plan of
[] -> return ()
Expand All @@ -424,7 +426,7 @@ executePlan' plan ee@ExecuteEnv {..} = do
-- stack always using transformer stacks that are safe for this use case.
runInBase <- liftBaseWith $ \run -> return (void . run)

let actions = concatMap (toActions runInBase ee) $ Map.elems $ Map.mergeWithKey
let actions = concatMap (toActions installedMap runInBase ee) $ Map.elems $ Map.mergeWithKey
(\_ b f -> Just (Just b, Just f))
(fmap (\b -> (Just b, Nothing)))
(fmap (\f -> (Nothing, Just f)))
Expand Down Expand Up @@ -468,11 +470,12 @@ executePlan' plan ee@ExecuteEnv {..} = do
when (toCoverage $ boptsTestOpts eeBuildOpts) generateHpcMarkupIndex

toActions :: M env m
=> (m () -> IO ())
=> InstalledMap
-> (m () -> IO ())
-> ExecuteEnv
-> (Maybe Task, Maybe (Task, LocalPackageTB)) -- build and final
-> [Action]
toActions runInBase ee (mbuild, mfinal) =
toActions installedMap runInBase ee (mbuild, mfinal) =
abuild ++ afinal
where
abuild =
Expand All @@ -483,7 +486,7 @@ toActions runInBase ee (mbuild, mfinal) =
{ actionId = ActionId taskProvides ATBuild
, actionDeps =
(Set.map (\ident -> ActionId ident ATBuild) (tcoMissing taskConfigOpts))
, actionDo = \ac -> runInBase $ singleBuild ac ee task
, actionDo = \ac -> runInBase $ singleBuild ac ee task installedMap
}
]
afinal =
Expand All @@ -496,9 +499,9 @@ toActions runInBase ee (mbuild, mfinal) =
(Set.map (\ident -> ActionId ident ATBuild) (tcoMissing taskConfigOpts))
, actionDo = \ac -> runInBase $ do
unless (Set.null $ lptbTests lptb) $ do
singleTest topts lptb ac ee task
singleTest topts lptb ac ee task installedMap
unless (Set.null $ lptbBenches lptb) $ do
singleBench beopts lptb ac ee task
singleBench beopts lptb ac ee task installedMap
}
]
where
Expand Down Expand Up @@ -752,10 +755,22 @@ singleBuild :: M env m
=> ActionContext
-> ExecuteEnv
-> Task
-> InstalledMap
-> m ()
singleBuild ac@ActionContext {..} ee@ExecuteEnv {..} task@Task {..} =
singleBuild ac@ActionContext {..} ee@ExecuteEnv {..} task@Task {..} installedMap =
withSingleContext ac ee task Nothing $ \package cabalfp pkgDir cabal announce console _mlogFile -> do
(cache, _neededConfig) <- ensureConfig pkgDir ee task (announce "configure") cabal cabalfp []
(cache, _neededConfig) <- ensureConfig pkgDir ee task (announce "configure") cabal cabalfp $
-- We enable tests if the test suite dependencies are already
-- installed, so that we avoid unnecessary recompilation based on
-- cabal_macros.h changes when switching between 'stack build' and
-- 'stack test'. See:
-- https://github.com/commercialhaskell/stack/issues/805
case taskType of
TTLocal lp -> concat
[ ["--enable-tests" | depsPresent installedMap $ lpTestDeps lp]
, ["--enable-benchmarks" | depsPresent installedMap $ lpBenchDeps lp]
]
_ -> []
wc <- getWhichCompiler

markExeNotInstalled (taskLocation task) taskProvides
Expand Down Expand Up @@ -821,16 +836,32 @@ singleBuild ac@ActionContext {..} ee@ExecuteEnv {..} task@Task {..} =
(PackageIdentifier (packageName package) (packageVersion package))
Set.empty

-- | Determine if all of the dependencies given are installed
depsPresent :: InstalledMap -> Map PackageName VersionRange -> Bool
depsPresent installedMap deps = all
(\(name, range) ->
case Map.lookup name installedMap of
Just (version, _, _) -> version `withinRange` range
Nothing -> False)
(Map.toList deps)

singleTest :: M env m
=> TestOpts
-> LocalPackageTB
-> ActionContext
-> ExecuteEnv
-> Task
-> InstalledMap
-> m ()
singleTest topts lptb ac ee task =
singleTest topts lptb ac ee task installedMap =
withSingleContext ac ee task (Just "test") $ \package cabalfp pkgDir cabal announce console mlogFile -> do
(_cache, neededConfig) <- ensureConfig pkgDir ee task (announce "configure (test)") cabal cabalfp ["--enable-tests"]
(_cache, neededConfig) <- ensureConfig pkgDir ee task (announce "configure (test)") cabal cabalfp $
case taskType task of
TTLocal lp -> concat
[ ["--enable-tests"]
, ["--enable-benchmarks" | depsPresent installedMap $ lpBenchDeps lp]
]
_ -> []
config <- asks getConfig

testBuilt <- checkTestBuilt pkgDir
Expand Down Expand Up @@ -968,10 +999,17 @@ singleBench :: M env m
-> ActionContext
-> ExecuteEnv
-> Task
-> InstalledMap
-> m ()
singleBench beopts _lptb ac ee task =
singleBench beopts _lptb ac ee task installedMap =
withSingleContext ac ee task (Just "bench") $ \_package cabalfp pkgDir cabal announce console _mlogFile -> do
(_cache, neededConfig) <- ensureConfig pkgDir ee task (announce "configure (benchmarks)") cabal cabalfp ["--enable-benchmarks"]
(_cache, neededConfig) <- ensureConfig pkgDir ee task (announce "configure (benchmarks)") cabal cabalfp $
case taskType task of
TTLocal lp -> concat
[ ["--enable-tests" | depsPresent installedMap $ lpTestDeps lp]
, ["--enable-benchmarks"]
]
_ -> []

benchBuilt <- checkBenchBuilt pkgDir

Expand Down
13 changes: 13 additions & 0 deletions src/Stack/Build/Source.hs
Original file line number Diff line number Diff line change
Expand Up @@ -287,13 +287,24 @@ loadLocalPackage bopts targets (name, (lpv, gpkg)) = do
{ packageConfigEnableTests = not $ Set.null tests
, packageConfigEnableBenchmarks = not $ Set.null benches
}
testconfig = config
{ packageConfigEnableTests = True
, packageConfigEnableBenchmarks = False
}
benchconfig = config
{ packageConfigEnableTests = False
, packageConfigEnableBenchmarks = True
}

btpkg
| Set.null tests && Set.null benches = Nothing
| otherwise = Just $ LocalPackageTB
{ lptbPackage = resolvePackage btconfig gpkg
, lptbTests = tests
, lptbBenches = benches
}
testpkg = resolvePackage testconfig gpkg
benchpkg = resolvePackage benchconfig gpkg
mbuildCache <- tryGetBuildCache $ lpvRoot lpv
(_,modFiles,otherFiles,mainFiles,extraFiles) <- getPackageFiles (packageFiles pkg) (lpvCabalFP lpv)
let files =
Expand All @@ -307,6 +318,8 @@ loadLocalPackage bopts targets (name, (lpv, gpkg)) = do

return LocalPackage
{ lpPackage = pkg
, lpTestDeps = packageDeps $ testpkg
, lpBenchDeps = packageDeps $ benchpkg
, lpExeComponents =
case mtarget of
Nothing -> Nothing
Expand Down
2 changes: 2 additions & 0 deletions src/Stack/SDist.hs
Original file line number Diff line number Diff line change
Expand Up @@ -95,6 +95,8 @@ readLocalPackage pkgDir = do
, lpCabalFile = cabalfp
-- NOTE: these aren't the 'correct values, but aren't used in
-- the usage of this function in this module.
, lpTestDeps = Map.empty
, lpBenchDeps = Map.empty
, lpTestBench = Nothing
, lpDirtyFiles = True
, lpNewBuildCache = Map.empty
Expand Down
4 changes: 4 additions & 0 deletions src/Stack/Types/Package.hs
Original file line number Diff line number Diff line change
Expand Up @@ -182,6 +182,10 @@ data LocalPackageTB = LocalPackageTB
-- | Information on a locally available package of source code
data LocalPackage = LocalPackage
{ lpPackage :: !Package -- ^ The @Package@ info itself, after resolution with package flags, not including any tests or benchmarks
, lpTestDeps :: !(Map PackageName VersionRange)
-- ^ Used for determining if we can use --enable-tests in a normal build
, lpBenchDeps :: !(Map PackageName VersionRange)
-- ^ Used for determining if we can use --enable-benchmarks in a normal build
, lpExeComponents :: !(Maybe (Set Text)) -- ^ Executable components to build, Nothing if not a target

, lpTestBench :: !(Maybe LocalPackageTB)
Expand Down

0 comments on commit 00c8778

Please sign in to comment.