{-# LANGUAGE DeriveFunctor #-} module Distribution.Client.Dependency.Modular.Package ( I(..) , Loc(..) , PackageId , PackageIdentifier(..) , PackageName(..) , PI(..) , PN , PP(..) , QPN , QPV , Q(..) , instI , makeIndependent , primaryPP , showI , showPI , showQPN , stripBase , unPN ) where import Data.List as L import Distribution.Package -- from Cabal import Distribution.Text -- from Cabal import Distribution.Client.Dependency.Modular.Version -- | A package name. type PN = PackageName -- | Unpacking a package name. unPN :: PN -> String unPN (PackageName pn) = pn -- | Package version. A package name plus a version number. type PV = PackageId -- | Qualified package version. type QPV = Q PV -- | Package id. Currently just a black-box string. type PId = UnitId -- | Location. Info about whether a package is installed or not, and where -- exactly it is located. For installed packages, uniquely identifies the -- package instance via its 'PId'. -- -- TODO: More information is needed about the repo. data Loc = Inst PId | InRepo deriving (Eq, Ord, Show) -- | Instance. A version number and a location. data I = I Ver Loc deriving (Eq, Ord, Show) -- | String representation of an instance. showI :: I -> String showI (I v InRepo) = showVer v showI (I v (Inst uid)) = showVer v ++ "/installed" ++ shortId uid where -- A hack to extract the beginning of the package ABI hash shortId (SimpleUnitId (ComponentId i)) = snip (splitAt 4) (++ "...") . snip ((\ (x, y) -> (reverse x, y)) . break (=='-') . reverse) ('-':) $ i snip p f xs = case p xs of (ys, zs) -> (if L.null zs then id else f) ys -- | Package instance. A package name and an instance. data PI qpn = PI qpn I deriving (Eq, Ord, Show, Functor) -- | String representation of a package instance. showPI :: PI QPN -> String showPI (PI qpn i) = showQPN qpn ++ "-" ++ showI i instI :: I -> Bool instI (I _ (Inst _)) = True instI _ = False -- | Package path. -- -- Stored in reverse order data PP = -- User-specified independent goal Independent Int PP -- Setup dependencies are always considered independent from their package | Setup PN PP -- Any dependency on base is considered independent (allows for base shims) | Base PN PP -- Unqualified | None deriving (Eq, Ord, Show) -- | Strip any 'Base' qualifiers from a PP -- -- (the Base qualifier does not get inherited) stripBase :: PP -> PP stripBase (Independent i pp) = Independent i (stripBase pp) stripBase (Setup pn pp) = Setup pn (stripBase pp) stripBase (Base _pn pp) = stripBase pp stripBase None = None -- | Is the package in the primary group of packages. In particular this -- does not include packages pulled in as setup deps. -- primaryPP :: PP -> Bool primaryPP (Independent _ pp) = primaryPP pp primaryPP (Setup _ _ ) = False primaryPP (Base _ pp) = primaryPP pp primaryPP None = True -- | String representation of a package path. -- -- NOTE: This always ends in a period showPP :: PP -> String showPP (Independent i pp) = show i ++ "." ++ showPP pp showPP (Setup pn pp) = display pn ++ "-setup" ++ "." ++ showPP pp showPP (Base pn pp) = display pn ++ "." ++ showPP pp showPP None = "" -- | A qualified entity. Pairs a package path with the entity. data Q a = Q PP a deriving (Eq, Ord, Show) -- | Standard string representation of a qualified entity. showQ :: (a -> String) -> (Q a -> String) showQ showa (Q None x) = showa x showQ showa (Q pp x) = showPP pp ++ showa x -- | Qualified package name. type QPN = Q PN -- | String representation of a qualified package path. showQPN :: QPN -> String showQPN = showQ display -- | Create artificial parents for each of the package names, making -- them all independent. makeIndependent :: [PN] -> [QPN] makeIndependent ps = [ Q pp pn | (pn, i) <- zip ps [0::Int ..] , let pp = Independent i None ]