Added qualifier to 'PackageConstraint' data type.
[cabal.git] / cabal-install / Distribution / Solver / Types / PackagePath.hs
blobba098cc92eead74e3e9d8a78a4ed981e71648352
1 {-# LANGUAGE DeriveGeneric #-}
2 module Distribution.Solver.Types.PackagePath
3 ( PackagePath(..)
4 , Namespace(..)
5 , Qualifier(..)
6 , dispQualifier
7 , Qualified(..)
8 , unqualified
9 , QPN
10 , dispQPN
11 , showQPN
12 ) where
14 import Distribution.Package
15 import Distribution.Text
16 import qualified Text.PrettyPrint as Disp
17 import Distribution.Client.Compat.Prelude ((<<>>))
18 import GHC.Generics (Generic)
19 import Distribution.Compat.Binary (Binary)
21 -- | A package path consists of a namespace and a package path inside that
22 -- namespace.
23 data PackagePath = PackagePath Namespace Qualifier
24 deriving (Eq, Ord, Show, Generic)
26 instance Binary PackagePath
28 -- | Top-level namespace
30 -- Package choices in different namespaces are considered completely independent
31 -- by the solver.
32 data Namespace =
33 -- | The default namespace
34 DefaultNamespace
36 -- | Independent namespace
38 -- For now we just number these (rather than giving them more structure).
39 | Independent Int
40 deriving (Eq, Ord, Show, Generic)
42 instance Binary Namespace
44 -- | Pretty-prints a namespace. The result is either empty or
45 -- ends in a period, so it can be prepended onto a package name.
46 dispNamespace :: Namespace -> Disp.Doc
47 dispNamespace DefaultNamespace = Disp.empty
48 dispNamespace (Independent i) = Disp.int i <<>> Disp.text "."
50 -- | Qualifier of a package within a namespace (see 'PackagePath')
51 data Qualifier =
52 -- | Top-level dependency in this namespace
53 Unqualified
55 -- | Any dependency on base is considered independent
57 -- This makes it possible to have base shims.
58 | Base PackageName
60 -- | Setup dependency
62 -- By rights setup dependencies ought to be nestable; after all, the setup
63 -- dependencies of a package might themselves have setup dependencies, which
64 -- are independent from everything else. However, this very quickly leads to
65 -- infinite search trees in the solver. Therefore we limit ourselves to
66 -- a single qualifier (within a given namespace).
67 | Setup PackageName
69 -- | If we depend on an executable from a package (via
70 -- @build-tools@), we should solve for the dependencies of that
71 -- package separately (since we're not going to actually try to
72 -- link it.) We qualify for EACH package separately; e.g.,
73 -- @'Exe' pn1 pn2@ qualifies the @build-tools@ dependency on
74 -- @pn2@ from package @pn1@. (If we tracked only @pn1@, that
75 -- would require a consistent dependency resolution for all
76 -- of the depended upon executables from a package; if we
77 -- tracked only @pn2@, that would require us to pick only one
78 -- version of an executable over the entire install plan.)
79 | Exe PackageName PackageName
80 deriving (Eq, Ord, Show, Generic)
82 instance Binary Qualifier
84 -- | Pretty-prints a qualifier. The result is either empty or
85 -- ends in a period, so it can be prepended onto a package name.
87 -- NOTE: the base qualifier is for a dependency _on_ base; the qualifier is
88 -- there to make sure different dependencies on base are all independent.
89 -- So we want to print something like @"A.base"@, where the @"A."@ part
90 -- is the qualifier and @"base"@ is the actual dependency (which, for the
91 -- 'Base' qualifier, will always be @base@).
92 dispQualifier :: Qualifier -> Disp.Doc
93 dispQualifier Unqualified = Disp.empty
94 dispQualifier (Setup pn) = disp pn <<>> Disp.text ":setup."
95 dispQualifier (Exe pn pn2) = disp pn <<>> Disp.text ":" <<>>
96 disp pn2 <<>> Disp.text ":exe."
97 dispQualifier (Base pn) = disp pn <<>> Disp.text "."
99 -- | A qualified entity. Pairs a package path with the entity.
100 data Qualified a = Q PackagePath a
101 deriving (Eq, Ord, Show, Generic)
103 instance Binary a => Binary (Qualified a)
105 -- | Marks the entity as a top-level dependency in the default namespace.
106 unqualified :: a -> Qualified a
107 unqualified = Q (PackagePath DefaultNamespace Unqualified)
109 -- | Qualified package name.
110 type QPN = Qualified PackageName
112 -- | Pretty-prints a qualified package name.
113 dispQPN :: QPN -> Disp.Doc
114 dispQPN (Q (PackagePath ns qual) pn) =
115 dispNamespace ns <<>> dispQualifier qual <<>> disp pn
117 -- | String representation of a qualified package name.
118 showQPN :: QPN -> String
119 showQPN = Disp.renderStyle flatStyle . dispQPN