Skip to content

Commit ba507b1

Browse files
authored
Merge pull request haskell#10273 from 9999years/missing-or-private-details
Show why configuring dependencies failed
2 parents db5628c + ec60185 commit ba507b1

File tree

29 files changed

+328
-93
lines changed

29 files changed

+328
-93
lines changed

Cabal-syntax/Cabal-syntax.cabal

+3
Original file line numberDiff line numberDiff line change
@@ -135,6 +135,7 @@ library
135135
Distribution.Types.ConfVar
136136
Distribution.Types.Dependency
137137
Distribution.Types.DependencyMap
138+
Distribution.Types.DependencySatisfaction
138139
Distribution.Types.ExeDependency
139140
Distribution.Types.Executable
140141
Distribution.Types.Executable.Lens
@@ -158,6 +159,8 @@ library
158159
Distribution.Types.Library.Lens
159160
Distribution.Types.LibraryName
160161
Distribution.Types.LibraryVisibility
162+
Distribution.Types.MissingDependency
163+
Distribution.Types.MissingDependencyReason
161164
Distribution.Types.Mixin
162165
Distribution.Types.Module
163166
Distribution.Types.ModuleReexport

Cabal-syntax/src/Distribution/Compat/NonEmptySet.hs

+4
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ module Distribution.Compat.NonEmptySet
1212

1313
-- * Deletion
1414
, delete
15+
, filter
1516

1617
-- * Conversions
1718
, toNonEmpty
@@ -116,6 +117,9 @@ delete x (NES xs)
116117
where
117118
res = Set.delete x xs
118119

120+
filter :: (a -> Bool) -> NonEmptySet a -> Set.Set a
121+
filter predicate (NES set) = Set.filter predicate set
122+
119123
-------------------------------------------------------------------------------
120124
-- Conversions
121125
-------------------------------------------------------------------------------

Cabal-syntax/src/Distribution/PackageDescription/Configuration.hs

+24-38
Original file line numberDiff line numberDiff line change
@@ -56,12 +56,13 @@ import Distribution.System
5656
import Distribution.Types.Component
5757
import Distribution.Types.ComponentRequestedSpec
5858
import Distribution.Types.DependencyMap
59+
import Distribution.Types.DependencySatisfaction (DependencySatisfaction (..))
60+
import Distribution.Types.MissingDependency (MissingDependency (..))
5961
import Distribution.Types.PackageVersionConstraint
6062
import Distribution.Utils.Generic
6163
import Distribution.Utils.Path (sameDirectory)
6264
import Distribution.Version
6365

64-
import qualified Data.Map.Lazy as Map
6566
import Data.Tree (Tree (Node))
6667

6768
------------------------------------------------------------------------------
@@ -144,15 +145,17 @@ parseCondition = condOr
144145

145146
------------------------------------------------------------------------------
146147

147-
-- | Result of dependency test. Isomorphic to @Maybe d@ but renamed for
148+
-- | Result of dependency test. Isomorphic to @Maybe@ but renamed for
148149
-- clarity.
149-
data DepTestRslt d = DepOk | MissingDeps d
150+
data DepTestRslt
151+
= DepOk
152+
| MissingDeps [MissingDependency]
150153

151-
instance Semigroup d => Monoid (DepTestRslt d) where
154+
instance Monoid DepTestRslt where
152155
mempty = DepOk
153156
mappend = (<>)
154157

155-
instance Semigroup d => Semigroup (DepTestRslt d) where
158+
instance Semigroup DepTestRslt where
156159
DepOk <> x = x
157160
x <> DepOk = x
158161
(MissingDeps d) <> (MissingDeps d') = MissingDeps (d <> d')
@@ -190,13 +193,13 @@ resolveWithFlags
190193
-> [PackageVersionConstraint]
191194
-- ^ Additional constraints
192195
-> [CondTree ConfVar [Dependency] PDTagged]
193-
-> ([Dependency] -> DepTestRslt [Dependency])
196+
-> ([Dependency] -> DepTestRslt)
194197
-- ^ Dependency test function.
195-
-> Either [Dependency] (TargetSet PDTagged, FlagAssignment)
198+
-> Either [MissingDependency] (TargetSet PDTagged, FlagAssignment)
196199
-- ^ Either the missing dependencies (error case), or a pair of
197200
-- (set of build targets with dependencies, chosen flag assignments)
198201
resolveWithFlags dom enabled os arch impl constrs trees checkDeps =
199-
either (Left . fromDepMapUnion) Right $ explore (build mempty dom)
202+
explore (build mempty dom)
200203
where
201204
-- simplify trees by (partially) evaluating all conditions and converting
202205
-- dependencies to dependency maps.
@@ -216,7 +219,7 @@ resolveWithFlags dom enabled os arch impl constrs trees checkDeps =
216219
-- computation overhead in the successful case.
217220
explore
218221
:: Tree FlagAssignment
219-
-> Either DepMapUnion (TargetSet PDTagged, FlagAssignment)
222+
-> Either [MissingDependency] (TargetSet PDTagged, FlagAssignment)
220223
explore (Node flags ts) =
221224
let targetSet =
222225
TargetSet $
@@ -229,7 +232,7 @@ resolveWithFlags dom enabled os arch impl constrs trees checkDeps =
229232
DepOk
230233
| null ts -> Right (targetSet, flags)
231234
| otherwise -> tryAll $ map explore ts
232-
MissingDeps mds -> Left (toDepMapUnion mds)
235+
MissingDeps mds -> Left mds
233236

234237
-- Builds a tree of all possible flag assignments. Internal nodes
235238
-- have only partial assignments.
@@ -238,18 +241,18 @@ resolveWithFlags dom enabled os arch impl constrs trees checkDeps =
238241
build assigned ((fn, vals) : unassigned) =
239242
Node assigned $ map (\v -> build (insertFlagAssignment fn v assigned) unassigned) vals
240243

241-
tryAll :: [Either DepMapUnion a] -> Either DepMapUnion a
244+
tryAll :: Monoid a => [Either a b] -> Either a b
242245
tryAll = foldr mp mz
243246

244247
-- special version of `mplus' for our local purposes
245-
mp :: Either DepMapUnion a -> Either DepMapUnion a -> Either DepMapUnion a
248+
mp :: Monoid a => Either a b -> Either a b -> Either a b
246249
mp m@(Right _) _ = m
247250
mp _ m@(Right _) = m
248251
mp (Left xs) (Left ys) = Left (xs <> ys)
249252

250253
-- `mzero'
251-
mz :: Either DepMapUnion a
252-
mz = Left (DepMapUnion Map.empty)
254+
mz :: Monoid a => Either a b
255+
mz = Left mempty
253256

254257
env :: FlagAssignment -> FlagName -> Either FlagName Bool
255258
env flags flag = (maybe (Left flag) Right . lookupFlagAssignment flag) flags
@@ -323,27 +326,6 @@ extractConditions f gpkg =
323326
, extractCondition (f . benchmarkBuildInfo) . snd <$> condBenchmarks gpkg
324327
]
325328

326-
-- | A map of package constraints that combines version ranges using 'unionVersionRanges'.
327-
newtype DepMapUnion = DepMapUnion {unDepMapUnion :: Map PackageName (VersionRange, NonEmptySet LibraryName)}
328-
329-
instance Semigroup DepMapUnion where
330-
DepMapUnion x <> DepMapUnion y =
331-
DepMapUnion $
332-
Map.unionWith unionVersionRanges' x y
333-
334-
unionVersionRanges'
335-
:: (VersionRange, NonEmptySet LibraryName)
336-
-> (VersionRange, NonEmptySet LibraryName)
337-
-> (VersionRange, NonEmptySet LibraryName)
338-
unionVersionRanges' (vr, cs) (vr', cs') = (unionVersionRanges vr vr', cs <> cs')
339-
340-
toDepMapUnion :: [Dependency] -> DepMapUnion
341-
toDepMapUnion ds =
342-
DepMapUnion $ Map.fromListWith unionVersionRanges' [(p, (vr, cs)) | Dependency p vr cs <- ds]
343-
344-
fromDepMapUnion :: DepMapUnion -> [Dependency]
345-
fromDepMapUnion m = [Dependency p vr cs | (p, (vr, cs)) <- Map.toList (unDepMapUnion m)]
346-
347329
freeVars :: CondTree ConfVar c a -> [FlagName]
348330
freeVars t = [f | PackageFlag f <- freeVars' t]
349331
where
@@ -453,7 +435,7 @@ finalizePD
453435
:: FlagAssignment
454436
-- ^ Explicitly specified flag assignments
455437
-> ComponentRequestedSpec
456-
-> (Dependency -> Bool)
438+
-> (Dependency -> DependencySatisfaction)
457439
-- ^ Is a given dependency satisfiable from the set of
458440
-- available packages? If this is unknown then use
459441
-- True.
@@ -465,7 +447,7 @@ finalizePD
465447
-- ^ Additional constraints
466448
-> GenericPackageDescription
467449
-> Either
468-
[Dependency]
450+
[MissingDependency]
469451
(PackageDescription, FlagAssignment)
470452
-- ^ Either missing dependencies or the resolved package
471453
-- description along with the flag assignments chosen.
@@ -526,7 +508,11 @@ finalizePD
526508
| otherwise -> [b, not b]
527509
-- flagDefaults = map (\(n,x:_) -> (n,x)) flagChoices
528510
check ds =
529-
let missingDeps = filter (not . satisfyDep) ds
511+
let missingDeps =
512+
[ MissingDependency dependency reason
513+
| (dependency, Unsatisfied reason) <-
514+
map (\dependency -> (dependency, satisfyDep dependency)) ds
515+
]
530516
in if null missingDeps
531517
then DepOk
532518
else MissingDeps missingDeps

Cabal-syntax/src/Distribution/Pretty.hs

+10
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,8 @@ module Distribution.Pretty
1010
, showTokenStr
1111
, showFreeText
1212
, showFreeTextV3
13+
, commaSpaceSep
14+
, commaSep
1315

1416
-- * Deprecated
1517
, Separator
@@ -118,3 +120,11 @@ lines_ s =
118120
in l : case s' of
119121
[] -> []
120122
(_ : s'') -> lines_ s''
123+
124+
-- | Separate a list of documents by commas and spaces.
125+
commaSpaceSep :: Pretty a => [a] -> PP.Doc
126+
commaSpaceSep = PP.hsep . PP.punctuate PP.comma . map pretty
127+
128+
-- | Separate a list of documents by commas.
129+
commaSep :: Pretty a => [a] -> PP.Doc
130+
commaSep = PP.hcat . PP.punctuate PP.comma . map pretty

Cabal-syntax/src/Distribution/Types/Dependency.hs

+3-13
Original file line numberDiff line numberDiff line change
@@ -78,31 +78,21 @@ instance NFData Dependency where rnf = genericRnf
7878
-- "pkg"
7979
--
8080
-- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.insert (LSubLibName $ mkUnqualComponentName "sublib") mainLibSet
81-
-- "pkg:{pkg, sublib}"
81+
-- "pkg:{pkg,sublib}"
8282
--
8383
-- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.singleton (LSubLibName $ mkUnqualComponentName "sublib")
8484
-- "pkg:sublib"
8585
--
8686
-- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.insert (LSubLibName $ mkUnqualComponentName "sublib-b") $ NES.singleton (LSubLibName $ mkUnqualComponentName "sublib-a")
87-
-- "pkg:{sublib-a, sublib-b}"
87+
-- "pkg:{sublib-a,sublib-b}"
8888
instance Pretty Dependency where
89-
pretty (Dependency name ver sublibs) = withSubLibs (pretty name) <+> pver
89+
pretty (Dependency name ver sublibs) = prettyLibraryNames name (NES.toNonEmpty sublibs) <+> pver
9090
where
9191
-- TODO: change to isAnyVersion after #6736
9292
pver
9393
| isAnyVersionLight ver = PP.empty
9494
| otherwise = pretty ver
9595

96-
withSubLibs doc = case NES.toList sublibs of
97-
[LMainLibName] -> doc
98-
[LSubLibName uq] -> doc <<>> PP.colon <<>> pretty uq
99-
_ -> doc <<>> PP.colon <<>> PP.braces prettySublibs
100-
101-
prettySublibs = PP.hsep $ PP.punctuate PP.comma $ prettySublib <$> NES.toList sublibs
102-
103-
prettySublib LMainLibName = PP.text $ unPackageName name
104-
prettySublib (LSubLibName un) = PP.text $ unUnqualComponentName un
105-
10696
-- |
10797
--
10898
-- >>> simpleParsec "mylib:sub" :: Maybe Dependency
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,14 @@
1+
module Distribution.Types.DependencySatisfaction
2+
( DependencySatisfaction (..)
3+
) where
4+
5+
import Distribution.Types.MissingDependencyReason (MissingDependencyReason)
6+
7+
-- | Whether or not a dependency constraint is satisfied.
8+
data DependencySatisfaction
9+
= -- | The dependency constraint is satisfied.
10+
Satisfied
11+
| -- | The dependency constraint is not satisfied.
12+
--
13+
-- Includes a reason for explanation.
14+
Unsatisfied MissingDependencyReason

Cabal-syntax/src/Distribution/Types/LibraryName.hs

+18
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,7 @@ module Distribution.Types.LibraryName
1010
, libraryNameString
1111

1212
-- * Pretty & Parse
13+
, prettyLibraryNames
1314
, prettyLibraryNameComponent
1415
, parsecLibraryNameComponent
1516
) where
@@ -21,6 +22,7 @@ import Distribution.Parsec
2122
import Distribution.Pretty
2223
import Distribution.Types.UnqualComponentName
2324

25+
import qualified Data.List.NonEmpty as NEL
2426
import qualified Distribution.Compat.CharParsing as P
2527
import qualified Text.PrettyPrint as Disp
2628

@@ -42,6 +44,22 @@ prettyLibraryNameComponent :: LibraryName -> Disp.Doc
4244
prettyLibraryNameComponent LMainLibName = Disp.text "lib"
4345
prettyLibraryNameComponent (LSubLibName str) = Disp.text "lib:" <<>> pretty str
4446

47+
-- | Pretty print a 'LibraryName' after a package name.
48+
--
49+
-- Produces output like @foo@, @foo:bar@, or @foo:{bar,baz}@
50+
prettyLibraryNames :: Pretty a => a -> NonEmpty LibraryName -> Disp.Doc
51+
prettyLibraryNames package libraries =
52+
let doc = pretty package
53+
54+
prettyComponent LMainLibName = pretty package
55+
prettyComponent (LSubLibName component) = Disp.text $ unUnqualComponentName component
56+
57+
prettyComponents = commaSep $ prettyComponent <$> NEL.toList libraries
58+
in case libraries of
59+
LMainLibName :| [] -> doc
60+
LSubLibName component :| [] -> doc <<>> Disp.colon <<>> pretty component
61+
_ -> doc <<>> Disp.colon <<>> Disp.braces prettyComponents
62+
4563
parsecLibraryNameComponent :: CabalParsing m => m LibraryName
4664
parsecLibraryNameComponent = do
4765
_ <- P.string "lib"
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,34 @@
1+
module Distribution.Types.MissingDependency
2+
( MissingDependency (..)
3+
) where
4+
5+
import Distribution.Compat.Prelude
6+
import Distribution.Pretty
7+
import Distribution.Types.Dependency
8+
( Dependency
9+
, simplifyDependency
10+
)
11+
import Distribution.Types.LibraryName
12+
( prettyLibraryNames
13+
)
14+
import Distribution.Types.MissingDependencyReason
15+
( MissingDependencyReason (..)
16+
)
17+
18+
import qualified Text.PrettyPrint as PP
19+
20+
-- | A missing dependency and information on why it's missing.
21+
data MissingDependency = MissingDependency Dependency MissingDependencyReason
22+
deriving (Show)
23+
24+
instance Pretty MissingDependency where
25+
pretty (MissingDependency dependency reason) =
26+
let prettyReason =
27+
case reason of
28+
MissingLibrary libraries ->
29+
PP.text "missing" <+> prettyLibraryNames PP.empty libraries
30+
MissingPackage -> PP.text "missing"
31+
MissingComponent name -> PP.text "missing component" <+> pretty name
32+
WrongVersion versions ->
33+
PP.text "installed:" <+> commaSpaceSep versions
34+
in pretty (simplifyDependency dependency) <+> PP.parens prettyReason
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,25 @@
1+
module Distribution.Types.MissingDependencyReason
2+
( MissingDependencyReason (..)
3+
) where
4+
5+
import Data.List.NonEmpty (NonEmpty)
6+
import Distribution.Types.LibraryName (LibraryName)
7+
import Distribution.Types.PackageName (PackageName)
8+
import Distribution.Types.Version (Version)
9+
10+
-- | A reason for a depency failing to solve.
11+
--
12+
-- This helps pinpoint dependencies that are installed with an incorrect
13+
-- version vs. dependencies that are not installed at all.
14+
data MissingDependencyReason
15+
= -- | One or more libraries is missing.
16+
MissingLibrary (NonEmpty LibraryName)
17+
| -- | A package is not installed.
18+
MissingPackage
19+
| -- | A package is installed, but the versions don't match.
20+
--
21+
-- Contains the available versions.
22+
WrongVersion [Version]
23+
| -- | A component is not installed.
24+
MissingComponent PackageName
25+
deriving (Show)

Cabal-tests/tests/ParserTests/regressions/issue-5846.format

+2-2
Original file line numberDiff line numberDiff line change
@@ -5,7 +5,7 @@ version: 5846
55
library
66
default-language: Haskell2010
77
build-depends:
8-
lib1:{a, b},
8+
lib1:{a,b},
99
lib2:c,
1010
lib3:d >=1,
11-
lib4:{a, b} >=1
11+
lib4:{a,b} >=1

Cabal/Cabal.cabal

+3
Original file line numberDiff line numberDiff line change
@@ -248,6 +248,7 @@ library
248248
Distribution.Types.ConfVar,
249249
Distribution.Types.Dependency,
250250
Distribution.Types.DependencyMap,
251+
Distribution.Types.DependencySatisfaction,
251252
Distribution.Types.ExeDependency,
252253
Distribution.Types.Executable,
253254
Distribution.Types.Executable.Lens,
@@ -271,6 +272,8 @@ library
271272
Distribution.Types.Library.Lens,
272273
Distribution.Types.LibraryName,
273274
Distribution.Types.LibraryVisibility,
275+
Distribution.Types.MissingDependency,
276+
Distribution.Types.MissingDependencyReason,
274277
Distribution.Types.Mixin,
275278
Distribution.Types.Module,
276279
Distribution.Types.ModuleReexport,

0 commit comments

Comments
 (0)