Skip to content
Snippets Groups Projects
Commit 40d1b4f1 authored by Duncan Coutts's avatar Duncan Coutts
Browse files

Fix implementation of addBuildableCondition

The addBuildableCondition function was added to solve the problem with
"buildable: False". The problem was that we would solve or check
dependencies on the basis of the component in question being needed, and
then at the end discover that the component is actually not buildable at
all, and if we'd known that up front we would not have solved for the
component's dependencies.

The trick that addBuildableCondition does is a syntactic transformation,
from components like:

executable blah
  buildable: False
  build-depends: foo >= 1, bar < 2
  something-else: whatever

to:

executable blah
  -- empty!

Or at least, that's the intention. In the above situation the
implementation of addBuildableCondition returns an empty CondNode:

CondNode mempty mempty []

The type at which mempty is used is important here. This transformation
is used in two places: one in the solver and the other in finalizePD.
In the solver the mempty is used at types from the PackageDescription:
Library, Executable, TestSuite etc. So in this case the transformation
works fine we end up with empty executables, test suites etc.

In finalizePD however the mempty gets used at type PDTagged (which is
sort of a union of Library, Executable etc plus none/null) and the
mempty for PDTagged is PDNull which means it does not even specify
which component we're referring to. So effectively that means instead of
ending up with an empty executable in the above example, we end up
deleting the executable entirely!

This was a change in behaviour. Prior to adding addBuildableCondition
the result of finalizePD would include non-buildable components and the
rest of the build system infrastructure was set up to skip over them
when building. The change was not noticed precisely because the rest of
the system was already set up to ignore non-buildable components.

This is not however a benign change in behaviour. In particular in
cabal-install in the install plan we end up completley forgetting about
all the non-buildable components. This means we cannot even report that
components are non-buildable when users ask to build them, because we've
completely forgotten that they exist.

So this patch keeps the original addBuildableCondition for use by the
solver since the solver uses it at sensible monoid types. The patch adds
a special version for the PDTagged type which changes the transformation
so that in the above example we end up with:

executable blah
  buildable: False
  something-else: whatever

So we've stripped out all the build-depends but we keep everything else,
including of course the "buildable: False".
parent 2502ea1b
No related branches found
No related tags found
No related merge requests found
......@@ -228,7 +228,7 @@ resolveWithFlags dom enabled os arch impl constrs trees checkDeps =
-- dependencies to dependency maps.
simplifiedTrees :: [CondTree FlagName DependencyMap PDTagged]
simplifiedTrees = map ( mapTreeConstrs toDepMap -- convert to maps
. addBuildableCondition pdTaggedBuildInfo
. addBuildableConditionPDTagged
. mapTreeConds (fst . simplifyWithSysParams os arch impl))
trees
......@@ -277,11 +277,6 @@ resolveWithFlags dom enabled os arch impl constrs trees checkDeps =
env :: FlagAssignment -> FlagName -> Either FlagName Bool
env flags flag = (maybe (Left flag) Right . lookup flag) flags
pdTaggedBuildInfo :: PDTagged -> BuildInfo
pdTaggedBuildInfo (Lib l) = libBuildInfo l
pdTaggedBuildInfo (SubComp _ c) = componentBuildInfo c
pdTaggedBuildInfo PDNull = mempty
-- | Transforms a 'CondTree' by putting the input under the "then" branch of a
-- conditional that is True when Buildable is True. If 'addBuildableCondition'
-- can determine that Buildable is always True, it returns the input unchanged.
......@@ -295,6 +290,33 @@ addBuildableCondition getInfo t =
Lit False -> CondNode mempty mempty []
c -> CondNode mempty mempty [(c, t, Nothing)]
-- | This is a special version of 'addBuildableCondition' for the 'PDTagged'
-- type.
--
-- It is not simply a specialisation. It is more complicated than it
-- ought to be because of the way the 'PDTagged' monoid instance works. The
-- @mempty = 'PDNull'@ forgets the component type, which has the effect of
-- completely deleting components that are not buildable.
--
-- See <https://github.com/haskell/cabal/pull/4094> for more details.
--
addBuildableConditionPDTagged :: (Eq v, Monoid c) =>
CondTree v c PDTagged
-> CondTree v c PDTagged
addBuildableConditionPDTagged t =
case extractCondition (buildable . getInfo) t of
Lit True -> t
Lit False -> deleteConstraints t
c -> CondNode mempty mempty [(c, t, Just (deleteConstraints t))]
where
deleteConstraints = mapTreeConstrs (const mempty)
getInfo :: PDTagged -> BuildInfo
getInfo (Lib l) = libBuildInfo l
getInfo (SubComp _ c) = componentBuildInfo c
getInfo PDNull = mempty
-- Note: extracting buildable conditions.
-- --------------------------------------
--
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment