1 {-# LANGUAGE DeriveDataTypeable #-}
2 {-# LANGUAGE DeriveGeneric #-}
4 module Distribution
.Types
.Dependency
14 import Distribution
.Compat
.Prelude
17 import Distribution
.Types
.VersionRange
(isAnyVersionLight
)
18 import Distribution
.Version
(VersionRange
, anyVersion
, simplifyVersionRange
)
20 import Distribution
.CabalSpecVersion
21 import Distribution
.Compat
.CharParsing
(char
, spaces
)
22 import Distribution
.Compat
.Parsing
(between
, option
)
23 import Distribution
.Parsec
24 import Distribution
.Pretty
25 import Distribution
.Types
.LibraryName
26 import Distribution
.Types
.PackageName
27 import Distribution
.Types
.UnqualComponentName
29 import qualified Distribution
.Compat
.NonEmptySet
as NES
30 import qualified Text
.PrettyPrint
as PP
32 -- | Describes a dependency on a source package (API)
34 -- /Invariant:/ package name does not appear as 'LSubLibName' in
35 -- set of library names.
37 = -- | The set of libraries required from the package.
38 -- Only the selected libraries will be built.
39 -- It does not affect the cabal-install solver yet.
43 (NonEmptySet LibraryName
)
44 deriving (Generic
, Read, Show, Eq
, Ord
, Typeable
, Data
)
46 depPkgName
:: Dependency
-> PackageName
47 depPkgName
(Dependency pn _ _
) = pn
49 depVerRange
:: Dependency
-> VersionRange
50 depVerRange
(Dependency _ vr _
) = vr
52 depLibraries
:: Dependency
-> NonEmptySet LibraryName
53 depLibraries
(Dependency _ _ cs
) = cs
55 -- | Smart constructor of 'Dependency'.
57 -- If 'PackageName' is appears as 'LSubLibName' in a set of sublibraries,
58 -- it is automatically converted to 'LMainLibName'.
61 mkDependency
:: PackageName
-> VersionRange
-> NonEmptySet LibraryName
-> Dependency
62 mkDependency pn vr lb
= Dependency pn vr
(NES
.map conv lb
)
64 pn
' = packageNameToUnqualComponentName pn
66 conv l
@LMainLibName
= l
67 conv l
@(LSubLibName ln
)
68 | ln
== pn
' = LMainLibName
71 instance Binary Dependency
72 instance Structured Dependency
73 instance NFData Dependency
where rnf
= genericRnf
77 -- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion mainLibSet
80 -- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.insert (LSubLibName $ mkUnqualComponentName "sublib") mainLibSet
81 -- "pkg:{pkg, sublib}"
83 -- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.singleton (LSubLibName $ mkUnqualComponentName "sublib")
86 -- >>> prettyShow $ Dependency (mkPackageName "pkg") anyVersion $ NES.insert (LSubLibName $ mkUnqualComponentName "sublib-b") $ NES.singleton (LSubLibName $ mkUnqualComponentName "sublib-a")
87 -- "pkg:{sublib-a, sublib-b}"
88 instance Pretty Dependency
where
89 pretty
(Dependency name ver sublibs
) = withSubLibs
(pretty name
) <+> pver
91 -- TODO: change to isAnyVersion after #6736
93 | isAnyVersionLight ver
= PP
.empty
94 |
otherwise = pretty ver
96 withSubLibs doc
= case NES
.toList sublibs
of
98 [LSubLibName uq
] -> doc
<<>> PP
.colon
<<>> pretty uq
99 _
-> doc
<<>> PP
.colon
<<>> PP
.braces prettySublibs
101 prettySublibs
= PP
.hsep
$ PP
.punctuate PP
.comma
$ prettySublib
<$> NES
.toList sublibs
103 prettySublib LMainLibName
= PP
.text
$ unPackageName name
104 prettySublib
(LSubLibName un
) = PP
.text
$ unUnqualComponentName un
108 -- >>> simpleParsec "mylib:sub" :: Maybe Dependency
109 -- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub") :| [])))
111 -- >>> simpleParsec "mylib:{sub1,sub2}" :: Maybe Dependency
112 -- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub1") :| [LSubLibName (UnqualComponentName "sub2")])))
114 -- >>> simpleParsec "mylib:{ sub1 , sub2 }" :: Maybe Dependency
115 -- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub1") :| [LSubLibName (UnqualComponentName "sub2")])))
117 -- >>> simpleParsec "mylib:{ sub1 , sub2 } ^>= 42" :: Maybe Dependency
118 -- Just (Dependency (PackageName "mylib") (MajorBoundVersion (mkVersion [42])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub1") :| [LSubLibName (UnqualComponentName "sub2")])))
120 -- >>> simpleParsec "mylib:{ } ^>= 42" :: Maybe Dependency
123 -- >>> traverse_ print (map simpleParsec ["mylib:mylib", "mylib:{mylib}", "mylib:{mylib,sublib}" ] :: [Maybe Dependency])
124 -- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LMainLibName :| [])))
125 -- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LMainLibName :| [])))
126 -- Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LMainLibName :| [LSubLibName (UnqualComponentName "sublib")])))
128 -- Spaces around colon are not allowed:
130 -- >>> map simpleParsec ["mylib: sub", "mylib :sub", "mylib: {sub1,sub2}", "mylib :{sub1,sub2}"] :: [Maybe Dependency]
131 -- [Nothing,Nothing,Nothing,Nothing]
133 -- Sublibrary syntax is accepted since @cabal-version: 3.0@
135 -- >>> map (`simpleParsec'` "mylib:sub") [CabalSpecV2_4, CabalSpecV3_0] :: [Maybe Dependency]
136 -- [Nothing,Just (Dependency (PackageName "mylib") (OrLaterVersion (mkVersion [0])) (fromNonEmpty (LSubLibName (UnqualComponentName "sub") :| [])))]
137 instance Parsec Dependency
where
141 libs
<- option mainLibSet
$ do
143 versionGuardMultilibs
144 NES
.singleton
<$> parseLib
<|
> parseMultipleLibs
146 spaces
-- https://github.com/haskell/cabal/issues/5846
147 ver
<- parsec
<|
> pure anyVersion
148 return $ mkDependency name ver libs
150 parseLib
= LSubLibName
<$> parsec
155 (NES
.fromNonEmpty
<$> parsecCommaNonEmpty parseLib
)
157 versionGuardMultilibs
:: CabalParsing m
=> m
()
158 versionGuardMultilibs
= do
159 csv
<- askCabalSpecVersion
160 when (csv
< CabalSpecV3_0
) $
163 [ "Sublibrary dependency syntax used."
164 , "To use this syntax the package needs to specify at least 'cabal-version: 3.0'."
165 , "Alternatively, if you are depending on an internal library, you can write"
166 , "directly the library name as it were a package."
169 -- | Library set with main library.
172 mainLibSet
:: NonEmptySet LibraryName
173 mainLibSet
= NES
.singleton LMainLibName
175 -- | Simplify the 'VersionRange' expression in a 'Dependency'.
176 -- See 'simplifyVersionRange'.
177 simplifyDependency
:: Dependency
-> Dependency
178 simplifyDependency
(Dependency name
range comps
) =
179 Dependency name
(simplifyVersionRange
range) comps