Skip to content

Commit

Permalink
Solve for, build, and add to path build-tools dependencies.
Browse files Browse the repository at this point in the history
This fixes #220: new-build now builds, installs and adds executables to
PATH automatically if they show up in 'build-tools'.  However, there is
still more that could be done: the new behavior only applies to a
specific list of 'build-tools' (alex, happy, etc) which Cabal recognizes
out of the box.  The plan is to introduce a new 'tool-depends' field to
allow dependencies on other executables as well.

Signed-off-by: Edward Z. Yang <ezyang@cs.stanford.edu>
  • Loading branch information
ezyang committed Aug 21, 2016
1 parent f63273d commit c0a4860
Show file tree
Hide file tree
Showing 28 changed files with 436 additions and 141 deletions.
4 changes: 3 additions & 1 deletion Cabal/Distribution/Simple/Configure.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1393,7 +1393,9 @@ configureRequiredProgram :: Verbosity -> ProgramConfiguration -> Dependency
configureRequiredProgram verbosity conf
(Dependency (PackageName progName) verRange) =
case lookupKnownProgram progName conf of
Nothing -> die ("Unknown build tool " ++ progName)
Nothing ->
-- Try to configure it as a 'simpleProgram' automatically
configureProgram verbosity (simpleProgram progName) conf
Just prog
-- requireProgramVersion always requires the program have a version
-- but if the user says "build-depends: foo" ie no version constraint
Expand Down
3 changes: 2 additions & 1 deletion cabal-install/Distribution/Client/Dependency.hs
Original file line number Diff line number Diff line change
Expand Up @@ -768,7 +768,7 @@ showPackageProblem (InvalidDep dep pkgid) =
configuredPackageProblems :: Platform -> CompilerInfo
-> SolverPackage UnresolvedPkgLoc -> [PackageProblem]
configuredPackageProblems platform cinfo
(SolverPackage pkg specifiedFlags stanzas specifiedDeps') =
(SolverPackage pkg specifiedFlags stanzas specifiedDeps' _specifiedExeDeps') =
[ DuplicateFlag flag | ((flag,_):_) <- duplicates specifiedFlags ]
++ [ MissingFlag flag | OnlyInLeft flag <- mergedFlags ]
++ [ ExtraFlag flag | OnlyInRight flag <- mergedFlags ]
Expand All @@ -779,6 +779,7 @@ configuredPackageProblems platform cinfo
++ [ ExtraDep pkgid | OnlyInRight pkgid <- mergedDeps ]
++ [ InvalidDep dep pkgid | InBoth dep pkgid <- mergedDeps
, not (packageSatisfiesDependency pkgid dep) ]
-- TODO: sanity tests on executable deps
where
specifiedDeps :: ComponentDeps [PackageId]
specifiedDeps = fmap (map solverSrcId) specifiedDeps'
Expand Down
8 changes: 5 additions & 3 deletions cabal-install/Distribution/Client/InstallPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,7 @@ import Distribution.Client.SolverInstallPlan (SolverInstallPlan)
import qualified Distribution.Solver.Types.ComponentDeps as CD
import Distribution.Solver.Types.Settings
import Distribution.Solver.Types.SolverId
import Distribution.Solver.Types.InstSolverPackage

-- TODO: Need this when we compute final UnitIds
-- import qualified Distribution.Simple.Configure as Configure
Expand Down Expand Up @@ -415,8 +416,8 @@ configureInstallPlan :: SolverInstallPlan -> InstallPlan
configureInstallPlan solverPlan =
flip fromSolverInstallPlan solverPlan $ \mapDep planpkg ->
[case planpkg of
SolverInstallPlan.PreExisting pkg _ ->
PreExisting pkg
SolverInstallPlan.PreExisting pkg ->
PreExisting (instSolverPkgIPI pkg)

SolverInstallPlan.Configured pkg ->
Configured (configureSolverPackage mapDep pkg)
Expand All @@ -438,9 +439,10 @@ configureInstallPlan solverPlan =
confPkgFlags = solverPkgFlags spkg,
confPkgStanzas = solverPkgStanzas spkg,
confPkgDeps = deps
-- NB: no support for executable dependencies
}
where
deps = fmap (concatMap (map configuredId . mapDep)) (solverPkgDeps spkg)
deps = fmap (concatMap (map configuredId . mapDep)) (solverPkgLibDeps spkg)


-- ------------------------------------------------------------
Expand Down
101 changes: 83 additions & 18 deletions cabal-install/Distribution/Client/ProjectPlanning.hs
Original file line number Diff line number Diff line change
Expand Up @@ -79,6 +79,7 @@ import Distribution.Solver.Types.PkgConfigDb
import Distribution.Solver.Types.Settings
import Distribution.Solver.Types.SolverId
import Distribution.Solver.Types.SolverPackage
import Distribution.Solver.Types.InstSolverPackage
import Distribution.Solver.Types.SourcePackage

import Distribution.Package hiding
Expand Down Expand Up @@ -1040,8 +1041,8 @@ elaborateInstallPlan platform compiler compilerprogdb
elaboratedInstallPlan =
flip InstallPlan.fromSolverInstallPlan solverPlan $ \mapDep planpkg ->
case planpkg of
SolverInstallPlan.PreExisting pkg _ ->
[InstallPlan.PreExisting pkg]
SolverInstallPlan.PreExisting pkg ->
[InstallPlan.PreExisting (instSolverPkgIPI pkg)]

SolverInstallPlan.Configured pkg ->
-- SolverPackage
Expand Down Expand Up @@ -1073,7 +1074,7 @@ elaborateInstallPlan platform compiler compilerprogdb
:: (SolverId -> [ElaboratedPlanPackage])
-> SolverPackage UnresolvedPkgLoc
-> [ElaboratedConfiguredPackage]
elaborateSolverToComponents mapDep spkg@(SolverPackage _ _ _ deps0)
elaborateSolverToComponents mapDep spkg@(SolverPackage _ _ _ deps0 exe_deps0)
= snd (mapAccumL buildComponent (Map.empty, Map.empty) comps_graph)
where
elab0@ElaboratedConfiguredPackage{..} = elaborateSolverToCommon mapDep spkg
Expand Down Expand Up @@ -1121,19 +1122,28 @@ elaborateInstallPlan platform compiler compilerprogdb
compComponentName = Just cname
compSolverName = CD.componentNameToComponent cname
compLibDependencies =
concatMap (elaborateSolverId mapDep)
concatMap (elaborateLibSolverId mapDep)
(CD.select (== compSolverName) deps0) ++
internal_lib_deps
compExeDependencies =
(map confInstId $
concatMap (elaborateExeSolverId mapDep)
(CD.select (== compSolverName) exe_deps0)) ++
internal_exe_deps
compExeDependencyPaths =
concatMap (elaborateExePath mapDep)
(CD.select (== compSolverName) exe_deps0) ++
internal_exe_paths

bi = Cabal.componentBuildInfo comp
confid = ConfiguredId elabPkgSourceId cid

compSetupDependencies = concatMap (elaborateSolverId mapDep) (CD.setupDeps deps0)
compSetupDependencies = concatMap (elaborateLibSolverId mapDep) (CD.setupDeps deps0)
internal_lib_deps
= [ confid'
| Dependency pkgname _ <- PD.targetBuildDepends bi
, Just confid' <- [Map.lookup pkgname internal_map] ]
(compExeDependencies, compExeDependencyPaths)
(internal_exe_deps, internal_exe_paths)
= unzip $
[ (confInstId confid', path)
| Dependency (PackageName toolname) _ <- PD.buildTools bi
Expand Down Expand Up @@ -1190,22 +1200,56 @@ elaborateInstallPlan platform compiler compilerprogdb
(compilerId compiler)
cid

elaborateSolverId :: (SolverId -> [ElaboratedPlanPackage])
elaborateLibSolverId :: (SolverId -> [ElaboratedPlanPackage])
-> SolverId -> [ConfiguredId]
elaborateSolverId mapDep = map configuredId . filter is_lib . mapDep
elaborateLibSolverId mapDep = map configuredId . filter is_lib . mapDep
where is_lib (InstallPlan.PreExisting _) = True
is_lib (InstallPlan.Configured elab) =
case elabPkgOrComp elab of
ElabPackage _ -> True
ElabComponent comp -> compSolverName comp == CD.ComponentLib

elaborateExeSolverId :: (SolverId -> [ElaboratedPlanPackage])
-> SolverId -> [ConfiguredId]
elaborateExeSolverId mapDep = map configuredId . filter is_exe . mapDep
where is_exe (InstallPlan.PreExisting _) = False
is_exe (InstallPlan.Configured elab) =
case elabPkgOrComp elab of
ElabPackage _ -> True
ElabComponent comp ->
case compSolverName comp of
CD.ComponentExe _ -> True
_ -> False

elaborateExePath :: (SolverId -> [ElaboratedPlanPackage])
-> SolverId -> [FilePath]
elaborateExePath mapDep = concatMap get_exe_path . mapDep
where
-- Pre-existing executables are assumed to be in PATH
-- already. In fact, this should be impossible.
-- Modest duplication with 'inplace_bin_dir'
get_exe_path (InstallPlan.PreExisting _) = []
get_exe_path (InstallPlan.Configured elab) =
[if elabBuildStyle elab == BuildInplaceOnly
then distBuildDirectory
(elabDistDirParams elaboratedSharedConfig elab) </>
"build" </>
case elabPkgOrComp elab of
ElabPackage _ -> ""
ElabComponent comp ->
case fmap Cabal.componentNameString
(compComponentName comp) of
Just (Just n) -> n
_ -> ""
else InstallDirs.bindir (elabInstallDirs elab)]

elaborateSolverToPackage :: (SolverId -> [ElaboratedPlanPackage])
-> SolverPackage UnresolvedPkgLoc
-> ElaboratedConfiguredPackage
elaborateSolverToPackage
mapDep
pkg@(SolverPackage (SourcePackage pkgid _gdesc _srcloc _descOverride)
_flags _stanzas deps0) =
_flags _stanzas deps0 exe_deps0) =
-- Knot tying: the final elab includes the
-- pkgInstalledId, which is calculated by hashing many
-- of the other fields of the elaboratedPackage.
Expand All @@ -1219,7 +1263,7 @@ elaborateInstallPlan platform compiler compilerprogdb
elabPkgOrComp = ElabPackage $ ElaboratedPackage {..}
}

deps = fmap (concatMap (elaborateSolverId mapDep)) deps0
deps = fmap (concatMap (elaborateLibSolverId mapDep)) deps0

requires_reg = PD.hasPublicLib elabPkgDescription
pkgInstalledId
Expand All @@ -1238,6 +1282,8 @@ elaborateInstallPlan platform compiler compilerprogdb
++ " is missing a source hash: " ++ display pkgid

pkgLibDependencies = deps
pkgExeDependencies = fmap (concatMap (elaborateExeSolverId mapDep)) exe_deps0
pkgExeDependencyPaths = fmap (concatMap (elaborateExePath mapDep)) exe_deps0

-- Filled in later
pkgStanzasEnabled = Set.empty
Expand Down Expand Up @@ -1269,7 +1315,7 @@ elaborateInstallPlan platform compiler compilerprogdb
-> ElaboratedConfiguredPackage
elaborateSolverToCommon mapDep
pkg@(SolverPackage (SourcePackage pkgid gdesc srcloc descOverride)
flags stanzas deps0) =
flags stanzas deps0 _exe_deps0) =
elaboratedPackage
where
elaboratedPackage = ElaboratedConfiguredPackage {..}
Expand Down Expand Up @@ -1332,7 +1378,7 @@ elaborateInstallPlan platform compiler compilerprogdb

elabSetupScriptStyle = packageSetupScriptStyle elabPkgDescription
-- Computing the deps here is a little awful
deps = fmap (concatMap (elaborateSolverId mapDep)) deps0
deps = fmap (concatMap (elaborateLibSolverId mapDep)) deps0
elabSetupScriptCliVersion = packageSetupScriptSpecVersion
elabSetupScriptStyle elabPkgDescription deps
elabSetupPackageDBStack = buildAndRegisterDbs
Expand Down Expand Up @@ -1838,7 +1884,8 @@ pruneInstallPlanPass2 pkgs =
setStanzasDepsAndTargets elab =
elab {
elabBuildTargets = elabBuildTargets elab
++ targetsRequiredForRevDeps,
++ libTargetsRequiredForRevDeps
++ exeTargetsRequiredForRevDeps,
elabPkgOrComp =
case elabPkgOrComp elab of
ElabPackage pkg ->
Expand All @@ -1849,24 +1896,40 @@ pruneInstallPlanPass2 pkgs =
keepNeeded _ _ = True
in ElabPackage $ pkg {
pkgStanzasEnabled = stanzas,
pkgLibDependencies = CD.filterDeps keepNeeded (pkgLibDependencies pkg)
pkgLibDependencies = CD.filterDeps keepNeeded (pkgLibDependencies pkg),
pkgExeDependencies = CD.filterDeps keepNeeded (pkgExeDependencies pkg),
pkgExeDependencyPaths = CD.filterDeps keepNeeded (pkgExeDependencyPaths pkg)
}
r@(ElabComponent _) -> r
}
where
targetsRequiredForRevDeps =
libTargetsRequiredForRevDeps =
[ ComponentTarget Cabal.defaultLibName WholeComponent
| installedUnitId elab `Set.member` hasReverseLibDeps
]
exeTargetsRequiredForRevDeps =
-- TODO: allow requesting executable with different name
-- than package name
[ ComponentTarget (Cabal.CExeName (unPackageName (packageName (elabPkgSourceId elab))))
WholeComponent
| installedUnitId elab `Set.member` hasReverseExeDeps
]


availablePkgs :: Set UnitId
availablePkgs = Set.fromList (map installedUnitId pkgs)

hasReverseLibDeps :: Set UnitId
hasReverseLibDeps =
Set.fromList [ depid | pkg <- pkgs
, depid <- InstallPlan.depends pkg ]
Set.fromList [ SimpleUnitId (confInstId depid)
| InstallPlan.Configured pkg <- pkgs
, depid <- elabLibDependencies pkg ]

hasReverseExeDeps :: Set UnitId
hasReverseExeDeps =
Set.fromList [ SimpleUnitId depid
| InstallPlan.Configured pkg <- pkgs
, depid <- elabExeDependencies pkg ]

mapConfiguredPackage :: (srcpkg -> srcpkg')
-> InstallPlan.GenericPlanPackage ipkg srcpkg
Expand Down Expand Up @@ -2436,7 +2499,9 @@ packageHashInputs
ElabPackage (ElaboratedPackage{..}) ->
Set.fromList $
[ confInstId dep
| dep <- CD.select relevantDeps pkgLibDependencies ]
| dep <- CD.select relevantDeps pkgLibDependencies ] ++
[ confInstId dep
| dep <- CD.select relevantDeps pkgExeDependencies ]
ElabComponent comp ->
Set.fromList (map confInstId (compLibDependencies comp)
++ compExeDependencies comp),
Expand Down
23 changes: 20 additions & 3 deletions cabal-install/Distribution/Client/ProjectPlanning/Types.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,6 +16,7 @@ module Distribution.Client.ProjectPlanning.Types (
elabDistDirParams,
elabExeDependencyPaths,
elabLibDependencies,
elabExeDependencies,
elabSetupDependencies,

ElaboratedPackageOrComponent(..),
Expand Down Expand Up @@ -73,6 +74,7 @@ import Data.Set (Set)
import qualified Data.ByteString.Lazy as LBS
import Distribution.Compat.Binary
import GHC.Generics (Generic)
import qualified Data.Monoid as Mon



Expand Down Expand Up @@ -296,9 +298,15 @@ elabLibDependencies ElaboratedConfiguredPackage { elabPkgOrComp = ElabPackage pk
elabLibDependencies ElaboratedConfiguredPackage { elabPkgOrComp = ElabComponent comp }
= compLibDependencies comp

elabExeDependencies :: ElaboratedConfiguredPackage -> [ComponentId]
elabExeDependencies ElaboratedConfiguredPackage { elabPkgOrComp = ElabPackage pkg }
= map confInstId (CD.nonSetupDeps (pkgExeDependencies pkg))
elabExeDependencies ElaboratedConfiguredPackage { elabPkgOrComp = ElabComponent comp }
= compExeDependencies comp

elabExeDependencyPaths :: ElaboratedConfiguredPackage -> [FilePath]
elabExeDependencyPaths ElaboratedConfiguredPackage { elabPkgOrComp = ElabPackage _ }
= [] -- TODO: not implemented
elabExeDependencyPaths ElaboratedConfiguredPackage { elabPkgOrComp = ElabPackage pkg }
= CD.nonSetupDeps (pkgExeDependencyPaths pkg)
elabExeDependencyPaths ElaboratedConfiguredPackage { elabPkgOrComp = ElabComponent comp }
= compExeDependencyPaths comp

Expand Down Expand Up @@ -353,6 +361,14 @@ data ElaboratedPackage
--
pkgLibDependencies :: ComponentDeps [ConfiguredId],

-- | Dependencies on executable packages.
--
pkgExeDependencies :: ComponentDeps [ConfiguredId],

-- | Paths where executable dependencies live.
--
pkgExeDependencyPaths :: ComponentDeps [FilePath],

-- | Which optional stanzas (ie testsuites, benchmarks) will actually
-- be enabled during the package configure step.
pkgStanzasEnabled :: Set OptionalStanza
Expand All @@ -363,7 +379,8 @@ instance Binary ElaboratedPackage

pkgOrderDependencies :: ElaboratedPackage -> ComponentDeps [UnitId]
pkgOrderDependencies pkg =
fmap (map (SimpleUnitId . confInstId)) (pkgLibDependencies pkg)
fmap (map (SimpleUnitId . confInstId)) (pkgLibDependencies pkg) `Mon.mappend`
fmap (map (SimpleUnitId . confInstId)) (pkgExeDependencies pkg)

-- | This is used in the install plan to indicate how the package will be
-- built.
Expand Down
14 changes: 7 additions & 7 deletions cabal-install/Distribution/Client/SolverInstallPlan.hs
Original file line number Diff line number Diff line change
Expand Up @@ -125,7 +125,7 @@ showInstallPlan :: SolverInstallPlan -> String
showInstallPlan = showPlanIndex . planIndex

showPlanPackage :: SolverPlanPackage -> String
showPlanPackage (PreExisting ipkg _) = "PreExisting " ++ display (packageId ipkg)
showPlanPackage (PreExisting ipkg) = "PreExisting " ++ display (packageId ipkg)
++ " (" ++ display (installedUnitId ipkg)
++ ")"
showPlanPackage (Configured spkg) = "Configured " ++ display (packageId spkg)
Expand Down Expand Up @@ -207,7 +207,7 @@ showPlanProblem (PackageStateInvalid pkg pkg') =
++ " which is in the " ++ showPlanState pkg'
++ " state"
where
showPlanState (PreExisting _ _) = "pre-existing"
showPlanState (PreExisting _) = "pre-existing"
showPlanState (Configured _) = "configured"

-- | For an invalid plan, produce a detailed list of problems as human readable
Expand Down Expand Up @@ -279,7 +279,7 @@ nonSetupClosure index pkgids0 = closure Graph.empty pkgids0
Just _ -> closure completed pkgids
Nothing -> closure completed' pkgids'
where completed' = Graph.insert pkg completed
pkgids' = CD.nonSetupDeps (resolverPackageDeps pkg) ++ pkgids
pkgids' = CD.nonSetupDeps (resolverPackageLibDeps pkg) ++ pkgids

-- | Compute the root sets of a plan
--
Expand Down Expand Up @@ -310,7 +310,7 @@ libraryRoots index =
-- | The setup dependencies of each package in the plan
setupRoots :: SolverPlanIndex -> [[SolverId]]
setupRoots = filter (not . null)
. map (CD.setupDeps . resolverPackageDeps)
. map (CD.setupDeps . resolverPackageLibDeps)
. Graph.toList

-- | Given a package index where we assume we want to use all the packages
Expand Down Expand Up @@ -342,7 +342,7 @@ dependencyInconsistencies' index =
| -- For each package @pkg@
pkg <- Graph.toList index
-- Find out which @sid@ @pkg@ depends on
, sid <- CD.nonSetupDeps (resolverPackageDeps pkg)
, sid <- CD.nonSetupDeps (resolverPackageLibDeps pkg)
-- And look up those @sid@ (i.e., @sid@ is the ID of @dep@)
, Just dep <- [Graph.lookup sid index]
]
Expand All @@ -358,8 +358,8 @@ dependencyInconsistencies' index =
reallyIsInconsistent [p1, p2] =
let pid1 = nodeKey p1
pid2 = nodeKey p2
in pid1 `notElem` CD.nonSetupDeps (resolverPackageDeps p2)
&& pid2 `notElem` CD.nonSetupDeps (resolverPackageDeps p1)
in pid1 `notElem` CD.nonSetupDeps (resolverPackageLibDeps p2)
&& pid2 `notElem` CD.nonSetupDeps (resolverPackageLibDeps p1)
reallyIsInconsistent _ = True


Expand Down
Loading

0 comments on commit c0a4860

Please sign in to comment.