Skip to content

Commit eda3485

Browse files
committed
Clamp down on dependencies:
Previously: - "build-depends" entries on internal libraries with an explicit version range are an error. Now for all three of "build-tools", "tool-depends", and "build-inputs": - Explicit versions ranges on internal components that are satisfied by the current package cause a warning. - Explicit version ranges on internal components are are not satisfied by the current package are an error. And additionally for "tool-depends": - dependencies on a non-existent executable in the current package are an error.
1 parent 8d8bf92 commit eda3485

File tree

3 files changed

+140
-8
lines changed

3 files changed

+140
-8
lines changed

Cabal/Cabal.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -288,6 +288,7 @@ library
288288
Distribution.Simple.GHC.IPI642
289289
Distribution.Simple.GHC.IPIConvert
290290
Distribution.Simple.GHC.ImplInfo
291+
Distribution.FooBar
291292
Paths_Cabal
292293

293294
if flag(bundled-binary-generic)

Cabal/Distribution/FooBar.hs

Lines changed: 59 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,59 @@
1+
module Distribution.FooBar where
2+
3+
import Data.Maybe
4+
import qualified Data.Map as Map
5+
6+
import Distribution.Package
7+
import Distribution.PackageDescription
8+
import Distribution.Types.ExeDependency
9+
import Distribution.Types.LegacyExeDependency
10+
import Distribution.Types.UnqualComponentName
11+
12+
-- | Desugar a "build-tools" entry into proper a executable dependency if
13+
-- possible.
14+
--
15+
-- An entry can be so desguared in two cases:
16+
--
17+
-- 1. The name in build-tools matches a locally defined executable. The
18+
-- executable dependency produced is on that exe in the current package.
19+
--
20+
-- 2. The name in build-tools matches a hard-coded set of known tools. For now,
21+
-- the executable dependency produced is one an executable in a package of
22+
-- the same, but the hard-coding could just as well be per-key.
23+
--
24+
-- The first cases matches first.
25+
desugarBuildTool :: PackageDescription
26+
-> LegacyExeDependency
27+
-> Maybe ExeDependency
28+
desugarBuildTool pkg led =
29+
if foundLocal
30+
then Just $ ExeDependency (packageName pkg) toolName reqVer
31+
else Map.lookup name whiteMap
32+
where
33+
LegacyExeDependency name reqVer = led
34+
toolName = mkUnqualComponentName name
35+
foundLocal = toolName `elem` map exeName (executables pkg)
36+
whitelist = [ "hscolour", "haddock", "happy", "alex", "hsc2hs", "c2hs"
37+
, "cpphs", "greencard"]
38+
whiteMap = Map.fromList $ flip map whitelist $ \n ->
39+
(n, ExeDependency (mkPackageName n) (mkUnqualComponentName n) reqVer)
40+
41+
-- | Get everything from "tool-depends", along with entries from "build-tools"
42+
-- that we know how to desugar.
43+
--
44+
-- This should almost always be used instead of just accessing the
45+
-- `toolDepends` field directly.
46+
getAllToolDependencies :: PackageDescription
47+
-> BuildInfo
48+
-> [ExeDependency]
49+
getAllToolDependencies pkg bi =
50+
toolDepends bi ++ mapMaybe (desugarBuildTool pkg) (buildTools bi)
51+
52+
-- | Does the given executable dependency map to this current package?
53+
--
54+
-- This is a tiny function, but used in a number of places. Note that the
55+
-- version bounds and components of the package are unchecked. This is because
56+
-- we sanitize exe deps so that the matching name implies these other
57+
-- conditions.
58+
isInternal :: PackageDescription -> ExeDependency -> Bool
59+
isInternal pkg (ExeDependency n _ _) = n == packageName pkg

Cabal/Distribution/PackageDescription/Check.hs

Lines changed: 80 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -45,11 +45,13 @@ import Distribution.Simple.BuildPaths (autogenPathsModuleName)
4545
import Distribution.Simple.CCompiler
4646
import Distribution.Types.ComponentRequestedSpec
4747
import Distribution.Types.Dependency
48+
import Distribution.Types.ExeDependency
4849
import Distribution.Types.UnqualComponentName
4950
import Distribution.Simple.Utils hiding (findPackageDesc, notice)
5051
import Distribution.Version
5152
import Distribution.Package
5253
import Distribution.Text
54+
import Distribution.FooBar
5355
import Language.Haskell.Extension
5456

5557
import Control.Monad (mapM)
@@ -526,13 +528,42 @@ checkFields pkg =
526528
++ "for example 'tested-with: GHC==6.10.4, GHC==6.12.3' and not "
527529
++ "'tested-with: GHC==6.10.4 && ==6.12.3'."
528530

529-
, check (not (null buildDependsRangeOnInternalLibrary)) $
531+
, check (not (null depInternalLibraryWithExtraVersion)) $
530532
PackageBuildWarning $
531-
"The package has a version range for a dependency on an "
533+
"The package has an extraneous version range for a dependency on an "
532534
++ "internal library: "
533-
++ commaSep (map display buildDependsRangeOnInternalLibrary)
534-
++ ". This version range has no semantic meaning and can be "
535-
++ "removed."
535+
++ commaSep (map display depInternalLibraryWithExtraVersion)
536+
++ ". This version range includes the current package but isn't needed "
537+
++ "as the current package's library will always be used."
538+
539+
, check (not (null depInternalLibraryWithImpossibleVersion)) $
540+
PackageBuildImpossible $
541+
"The package has an impossible version range for a dependency on an "
542+
++ "internal library: "
543+
++ commaSep (map display depInternalLibraryWithImpossibleVersion)
544+
++ ". This version range does not include the current package, and must "
545+
++ "be removed as the current package's library will always be used."
546+
547+
, check (not (null depInternalExecutableWithExtraVersion)) $
548+
PackageBuildWarning $
549+
"The package has an extraneous version range for a dependency on an "
550+
++ "internal executable: "
551+
++ commaSep (map display depInternalExecutableWithExtraVersion)
552+
++ ". This version range includes the current package but isn't needed "
553+
++ "as the current package's executable will always be used."
554+
555+
, check (not (null depInternalExecutableWithImpossibleVersion)) $
556+
PackageBuildImpossible $
557+
"The package has an impossible version range for a dependency on an "
558+
++ "internal executable: "
559+
++ commaSep (map display depInternalExecutableWithImpossibleVersion)
560+
++ ". This version range does not include the current package, and must "
561+
++ "be removed as the current package's executable will always be used."
562+
563+
, check (not (null depMissingInternalExecutable)) $
564+
PackageBuildImpossible $
565+
"The package depends on a missing internal executable: "
566+
++ commaSep (map display depInternalExecutableWithImpossibleVersion)
536567
]
537568
where
538569
unknownCompilers = [ name | (OtherCompiler name, _) <- testedWith pkg ]
@@ -558,14 +589,55 @@ checkFields pkg =
558589
internalLibraries =
559590
map (maybe (packageName pkg) (unqualComponentNameToPackageName) . libName)
560591
(allLibraries pkg)
561-
buildDependsRangeOnInternalLibrary =
592+
593+
internalExecutables = map exeName $ executables pkg
594+
595+
internalLibDeps =
562596
[ dep
563597
| bi <- allBuildInfo pkg
564-
, dep@(Dependency name versionRange) <- targetBuildDepends bi
565-
, not (isAnyVersion versionRange)
598+
, dep@(Dependency name _) <- targetBuildDepends bi
566599
, name `elem` internalLibraries
567600
]
568601

602+
internalExeDeps =
603+
[ dep
604+
| bi <- allBuildInfo pkg
605+
, dep <- getAllToolDependencies pkg bi
606+
, isInternal pkg dep
607+
]
608+
609+
depInternalLibraryWithExtraVersion =
610+
[ dep
611+
| dep@(Dependency _ versionRange) <- internalLibDeps
612+
, not $ isAnyVersion versionRange
613+
, packageVersion pkg `withinRange` versionRange
614+
]
615+
616+
depInternalLibraryWithImpossibleVersion =
617+
[ dep
618+
| dep@(Dependency _ versionRange) <- internalLibDeps
619+
, not $ packageVersion pkg `withinRange` versionRange
620+
]
621+
622+
depInternalExecutableWithExtraVersion =
623+
[ dep
624+
| dep@(ExeDependency _ _ versionRange) <- internalExeDeps
625+
, not $ isAnyVersion versionRange
626+
, packageVersion pkg `withinRange` versionRange
627+
]
628+
629+
depInternalExecutableWithImpossibleVersion =
630+
[ dep
631+
| dep@(ExeDependency _ _ versionRange) <- internalExeDeps
632+
, not $ packageVersion pkg `withinRange` versionRange
633+
]
634+
635+
depMissingInternalExecutable =
636+
[ dep
637+
| dep@(ExeDependency _ eName _) <- internalExeDeps
638+
, not $ eName `elem` internalExecutables
639+
]
640+
569641

570642
checkLicense :: PackageDescription -> [PackageCheck]
571643
checkLicense pkg =

0 commit comments

Comments
 (0)