make LTS branch pre-releases
[cabal.git] / cabal-install-solver / src / Distribution / Solver / Modular / Package.hs
blobccd0e4d4a70ffc146d9692a4fd78126ef98434db
1 {-# LANGUAGE DeriveFunctor #-}
2 module Distribution.Solver.Modular.Package
3 ( I(..)
4 , Loc(..)
5 , PackageId
6 , PackageIdentifier(..)
7 , PackageName, mkPackageName, unPackageName
8 , PkgconfigName, mkPkgconfigName, unPkgconfigName
9 , PI(..)
10 , PN
11 , QPV
12 , instI
13 , makeIndependent
14 , primaryPP
15 , setupPP
16 , showI
17 , showPI
18 , unPN
19 ) where
21 import Prelude ()
22 import Distribution.Solver.Compat.Prelude
24 import Distribution.Package -- from Cabal
25 import Distribution.Pretty (prettyShow)
27 import Distribution.Solver.Modular.Version
28 import Distribution.Solver.Types.PackagePath
30 -- | A package name.
31 type PN = PackageName
33 -- | Unpacking a package name.
34 unPN :: PN -> String
35 unPN = unPackageName
37 -- | Package version. A package name plus a version number.
38 type PV = PackageId
40 -- | Qualified package version.
41 type QPV = Qualified PV
43 -- | Package id. Currently just a black-box string.
44 type PId = UnitId
46 -- | Location. Info about whether a package is installed or not, and where
47 -- exactly it is located. For installed packages, uniquely identifies the
48 -- package instance via its 'PId'.
50 -- TODO: More information is needed about the repo.
51 data Loc = Inst PId | InRepo
52 deriving (Eq, Ord, Show)
54 -- | Instance. A version number and a location.
55 data I = I Ver Loc
56 deriving (Eq, Ord, Show)
58 -- | String representation of an instance.
59 showI :: I -> String
60 showI (I v InRepo) = showVer v
61 showI (I v (Inst uid)) = showVer v ++ "/installed" ++ extractPackageAbiHash uid
62 where
63 extractPackageAbiHash xs =
64 case first reverse $ break (=='-') $ reverse (prettyShow xs) of
65 (ys, []) -> ys
66 (ys, _) -> '-' : ys
68 -- | Package instance. A package name and an instance.
69 data PI qpn = PI qpn I
70 deriving (Eq, Ord, Show, Functor)
72 -- | String representation of a package instance.
73 showPI :: PI QPN -> String
74 showPI (PI qpn i) = showQPN qpn ++ "-" ++ showI i
76 instI :: I -> Bool
77 instI (I _ (Inst _)) = True
78 instI _ = False
80 -- | Is the package in the primary group of packages. This is used to
81 -- determine (1) if we should try to establish stanza preferences
82 -- for this goal, and (2) whether or not a user specified @--constraint@
83 -- should apply to this dependency (grep 'primaryPP' to see the
84 -- use sites). In particular this does not include packages pulled in
85 -- as setup deps.
87 primaryPP :: PackagePath -> Bool
88 primaryPP (PackagePath _ns q) = go q
89 where
90 go QualToplevel = True
91 go (QualBase _) = True
92 go (QualSetup _) = False
93 go (QualExe _ _) = False
95 -- | Is the package a dependency of a setup script. This is used to
96 -- establish whether or not certain constraints should apply to this
97 -- dependency (grep 'setupPP' to see the use sites).
99 setupPP :: PackagePath -> Bool
100 setupPP (PackagePath _ns (QualSetup _)) = True
101 setupPP (PackagePath _ns _) = False
103 -- | Qualify a target package with its own name so that its dependencies are not
104 -- required to be consistent with other targets.
105 makeIndependent :: PN -> QPN
106 makeIndependent pn = Q (PackagePath (Independent pn) QualToplevel) pn