module Distribution.PackageDescription.Configuration (
finalizePackageDescription,
flattenPackageDescription,
parseCondition,
freeVars,
) where
import Distribution.Package
( PackageName, Package, Dependency(..) )
import Distribution.PackageDescription
( GenericPackageDescription(..), PackageDescription(..)
, Library(..), Executable(..), BuildInfo(..)
, Flag(..), FlagName(..), FlagAssignment
, CondTree(..), ConfVar(..), Condition(..) )
import Distribution.Simple.PackageIndex (PackageIndex)
import qualified Distribution.Simple.PackageIndex as PackageIndex
import Distribution.Version
( VersionRange(..), withinRange )
import Distribution.Compiler
( CompilerId(CompilerId) )
import Distribution.System
( OS, Arch )
import Distribution.Simple.Utils (currentDir, lowercase)
import Distribution.Text
( Text(parse) )
import Distribution.Compat.ReadP as ReadP hiding ( char )
import qualified Distribution.Compat.ReadP as ReadP ( char )
import Data.Char ( isAlphaNum )
import Data.Maybe ( catMaybes, maybeToList )
import Data.List ( nub )
import Data.Map ( Map, fromListWith, toList )
import qualified Data.Map as M
import Data.Monoid
#if defined(__GLASGOW_HASKELL__) && (__GLASGOW_HASKELL__ < 606)
import qualified Text.Read as R
import qualified Text.Read.Lex as L
#endif
simplifyCondition :: Condition c
-> (c -> Either d Bool)
-> (Condition d, [d])
simplifyCondition cond i = fv . walk $ cond
where
walk cnd = case cnd of
Var v -> either Var Lit (i v)
Lit b -> Lit b
CNot c -> case walk c of
Lit True -> Lit False
Lit False -> Lit True
c' -> CNot c'
COr c d -> case (walk c, walk d) of
(Lit False, d') -> d'
(Lit True, _) -> Lit True
(c', Lit False) -> c'
(_, Lit True) -> Lit True
(c',d') -> COr c' d'
CAnd c d -> case (walk c, walk d) of
(Lit False, _) -> Lit False
(Lit True, d') -> d'
(_, Lit False) -> Lit False
(c', Lit True) -> c'
(c',d') -> CAnd c' d'
fv c = (c, fv' c)
fv' c = case c of
Var v -> [v]
Lit _ -> []
CNot c' -> fv' c'
COr c1 c2 -> fv' c1 ++ fv' c2
CAnd c1 c2 -> fv' c1 ++ fv' c2
simplifyWithSysParams :: OS -> Arch -> CompilerId -> Condition ConfVar
-> (Condition FlagName, [FlagName])
simplifyWithSysParams os arch (CompilerId comp compVer) cond = (cond', flags)
where
(cond', flags) = simplifyCondition cond interp
interp (OS os') = Right $ os' == os
interp (Arch arch') = Right $ arch' == arch
interp (Impl comp' vr) = Right $ comp' == comp
&& compVer `withinRange` vr
interp (Flag f) = Left f
parseCondition :: ReadP r (Condition ConfVar)
parseCondition = condOr
where
condOr = sepBy1 condAnd (oper "||") >>= return . foldl1 COr
condAnd = sepBy1 cond (oper "&&")>>= return . foldl1 CAnd
cond = sp >> (boolLiteral +++ inparens condOr +++ notCond +++ osCond
+++ archCond +++ flagCond +++ implCond )
inparens = between (ReadP.char '(' >> sp) (sp >> ReadP.char ')' >> sp)
notCond = ReadP.char '!' >> sp >> cond >>= return . CNot
osCond = string "os" >> sp >> inparens osIdent >>= return . Var
archCond = string "arch" >> sp >> inparens archIdent >>= return . Var
flagCond = string "flag" >> sp >> inparens flagIdent >>= return . Var
implCond = string "impl" >> sp >> inparens implIdent >>= return . Var
boolLiteral = fmap Lit parse
archIdent = fmap Arch parse
osIdent = fmap OS parse
flagIdent = fmap (Flag . FlagName . lowercase) (munch1 isIdentChar)
isIdentChar c = isAlphaNum c || c == '_' || c == '-'
oper s = sp >> string s >> sp
sp = skipSpaces
implIdent = do i <- parse
vr <- sp >> option AnyVersion parse
return $ Impl i vr
mapCondTree :: (a -> b) -> (c -> d) -> (Condition v -> Condition w)
-> CondTree v c a -> CondTree w d b
mapCondTree fa fc fcnd (CondNode a c ifs) =
CondNode (fa a) (fc c) (map g ifs)
where
g (cnd, t, me) = (fcnd cnd, mapCondTree fa fc fcnd t,
fmap (mapCondTree fa fc fcnd) me)
mapTreeConstrs :: (c -> d) -> CondTree v c a -> CondTree v d a
mapTreeConstrs f = mapCondTree id f id
mapTreeConds :: (Condition v -> Condition w) -> CondTree v c a -> CondTree w c a
mapTreeConds f = mapCondTree id id f
mapTreeData :: (a -> b) -> CondTree v c a -> CondTree v c b
mapTreeData f = mapCondTree f id id
data DepTestRslt d = DepOk | MissingDeps d
instance Monoid d => Monoid (DepTestRslt d) where
mempty = DepOk
mappend DepOk x = x
mappend x DepOk = x
mappend (MissingDeps d) (MissingDeps d') = MissingDeps (d `mappend` d')
data BT a = BTN a | BTB (BT a) (BT a)
resolveWithFlags :: Monoid a =>
[(FlagName,[Bool])]
-> OS
-> Arch
-> CompilerId
-> [Dependency]
-> [CondTree ConfVar [Dependency] a]
-> ([Dependency] -> DepTestRslt [Dependency])
-> Either [Dependency]
([a], [Dependency], FlagAssignment)
resolveWithFlags dom os arch impl constrs trees checkDeps =
case try dom [] of
Right r -> Right r
Left dbt -> Left $ findShortest dbt
where
extraConstrs = toDepMap constrs
simplifiedTrees = map ( mapTreeConstrs toDepMap
. mapTreeConds (fst . simplifyWithSysParams os arch impl))
trees
leftJoin :: DependencyMap -> DependencyMap -> DependencyMap
leftJoin left extra =
DependencyMap $
M.foldWithKey tightenConstraint (unDependencyMap left)
(unDependencyMap extra)
where tightenConstraint n c l =
case M.lookup n l of
Nothing -> l
Just vr -> M.insert n (IntersectVersionRanges vr c) l
try [] flags =
let (depss, as) = unzip
. map (simplifyCondTree (env flags))
$ simplifiedTrees
deps = fromDepMap $ leftJoin (mconcat depss)
extraConstrs
in case (checkDeps deps, deps) of
(DepOk, ds) -> Right (as, ds, flags)
(MissingDeps mds, _) -> Left (BTN mds)
try ((n, vals):rest) flags =
tryAll $ map (\v -> try rest ((n, v):flags)) vals
tryAll = foldr mp mz
mp (Left xs) (Left ys) = (Left (BTB xs ys))
mp (Left _) m@(Right _) = m
mp m@(Right _) _ = m
mz = Left (BTN [])
env flags flag = (maybe (Left flag) Right . lookup flag) flags
findShortest (BTN x) = x
findShortest (BTB lt rt) =
let l = findShortest lt
r = findShortest rt
in case (l,r) of
([], xs) -> xs
(xs, []) -> xs
([x], _) -> [x]
(_, [x]) -> [x]
(xs, ys) -> if lazyLengthCmp xs ys
then xs else ys
lazyLengthCmp [] _ = True
lazyLengthCmp _ [] = False
lazyLengthCmp (_:xs) (_:ys) = lazyLengthCmp xs ys
newtype DependencyMap = DependencyMap { unDependencyMap :: Map PackageName VersionRange }
#if !defined(__GLASGOW_HASKELL__) || (__GLASGOW_HASKELL__ >= 606)
deriving (Show, Read)
#else
instance Show DependencyMap where
showsPrec d (DependencyMap m) =
showParen (d > 10) (showString "DependencyMap" . shows (M.toList m))
instance Read DependencyMap where
readPrec = parens $ R.prec 10 $ do
R.Ident "DependencyMap" <- R.lexP
xs <- R.readPrec
return (DependencyMap (M.fromList xs))
where parens :: R.ReadPrec a -> R.ReadPrec a
parens p = optional
where
optional = p R.+++ mandatory
mandatory = paren optional
paren :: R.ReadPrec a -> R.ReadPrec a
paren p = do L.Punc "(" <- R.lexP
x <- R.reset p
L.Punc ")" <- R.lexP
return x
readListPrec = R.readListPrecDefault
#endif
instance Monoid DependencyMap where
mempty = DependencyMap M.empty
(DependencyMap a) `mappend` (DependencyMap b) =
DependencyMap (M.unionWith IntersectVersionRanges a b)
toDepMap :: [Dependency] -> DependencyMap
toDepMap ds =
DependencyMap $ fromListWith IntersectVersionRanges [ (p,vr) | Dependency p vr <- ds ]
fromDepMap :: DependencyMap -> [Dependency]
fromDepMap m = [ Dependency p vr | (p,vr) <- toList (unDependencyMap m) ]
simplifyCondTree :: (Monoid a, Monoid d) =>
(v -> Either v Bool)
-> CondTree v d a
-> (d, a)
simplifyCondTree env (CondNode a d ifs) =
foldr mappend (d, a) $ catMaybes $ map simplifyIf ifs
where
simplifyIf (cnd, t, me) =
case simplifyCondition cnd env of
(Lit True, _) -> Just $ simplifyCondTree env t
(Lit False, _) -> fmap (simplifyCondTree env) me
_ -> error $ "Environment not defined for all free vars"
ignoreConditions :: (Monoid a, Monoid c) => CondTree v c a -> (a, c)
ignoreConditions (CondNode a c ifs) = (a, c) `mappend` mconcat (concatMap f ifs)
where f (_, t, me) = ignoreConditions t
: maybeToList (fmap ignoreConditions me)
freeVars :: CondTree ConfVar c a -> [FlagName]
freeVars t = [ f | Flag f <- freeVars' t ]
where
freeVars' (CondNode _ _ ifs) = concatMap compfv ifs
compfv (c, ct, mct) = condfv c ++ freeVars' ct ++ maybe [] freeVars' mct
condfv c = case c of
Var v -> [v]
Lit _ -> []
CNot c' -> condfv c'
COr c1 c2 -> condfv c1 ++ condfv c2
CAnd c1 c2 -> condfv c1 ++ condfv c2
data PDTagged = Lib Library | Exe String Executable | PDNull deriving Show
instance Monoid PDTagged where
mempty = PDNull
PDNull `mappend` x = x
x `mappend` PDNull = x
Lib l `mappend` Lib l' = Lib (l `mappend` l')
Exe n e `mappend` Exe n' e' | n == n' = Exe n (e `mappend` e')
_ `mappend` _ = bug "Cannot combine incompatible tags"
finalizePackageDescription ::
Package pkg
=> FlagAssignment
-> Maybe (PackageIndex pkg)
-> OS
-> Arch
-> CompilerId
-> [Dependency]
-> GenericPackageDescription
-> Either [Dependency]
(PackageDescription, FlagAssignment)
finalizePackageDescription userflags mpkgs os arch impl constraints
(GenericPackageDescription pkg flags mlib0 exes0) =
case resolveFlags of
Right ((mlib, exes'), deps, flagVals) ->
Right ( pkg { library = mlib
, executables = exes'
, buildDepends = nub deps
}
, flagVals )
Left missing -> Left $ nub missing
where
condTrees = maybeToList (fmap (mapTreeData Lib) mlib0 )
++ map (\(name,tree) -> mapTreeData (Exe name) tree) exes0
untagRslts = foldr untag (Nothing, [])
where
untag (Lib _) (Just _, _) = bug "Only one library expected"
untag (Lib l) (Nothing, exes) = (Just l, exes)
untag (Exe n e) (mlib, exes)
| any ((== n) . fst) exes = bug "Exe with same name found"
| otherwise = (mlib, exes ++ [(n, e)])
untag PDNull x = x
resolveFlags =
case resolveWithFlags flagChoices os arch impl constraints condTrees check of
Right (as, ds, fs) ->
let (mlib, exes) = untagRslts as in
Right ( (fmap libFillInDefaults mlib,
map (\(n,e) -> (exeFillInDefaults e) { exeName = n }) exes),
ds, fs)
Left missing -> Left missing
flagChoices = map (\(MkFlag n _ d manual) -> (n, d2c manual n d)) flags
d2c manual n b = case lookup n userflags of
Just val -> [val]
Nothing
| manual -> [b]
| otherwise -> [b, not b]
check ds = if all satisfyDep ds
then DepOk
else MissingDeps $ filter (not . satisfyDep) ds
satisfyDep = maybe (const True)
(\pkgs -> not . null . PackageIndex.lookupDependency pkgs)
mpkgs
flattenPackageDescription :: GenericPackageDescription -> PackageDescription
flattenPackageDescription (GenericPackageDescription pkg _ mlib0 exes0) =
pkg { library = mlib
, executables = reverse exes
, buildDepends = nub $ ldeps ++ reverse edeps
}
where
(mlib, ldeps) = case mlib0 of
Just lib -> let (l,ds) = ignoreConditions lib in
(Just (libFillInDefaults l), ds)
Nothing -> (Nothing, [])
(exes, edeps) = foldr flattenExe ([],[]) exes0
flattenExe (n, t) (es, ds) =
let (e, ds') = ignoreConditions t in
( (exeFillInDefaults $ e { exeName = n }) : es, ds' ++ ds )
libFillInDefaults :: Library -> Library
libFillInDefaults lib@(Library { libBuildInfo = bi }) =
lib { libBuildInfo = biFillInDefaults bi }
exeFillInDefaults :: Executable -> Executable
exeFillInDefaults exe@(Executable { buildInfo = bi }) =
exe { buildInfo = biFillInDefaults bi }
biFillInDefaults :: BuildInfo -> BuildInfo
biFillInDefaults bi =
if null (hsSourceDirs bi)
then bi { hsSourceDirs = [currentDir] }
else bi
bug :: String -> a
bug msg = error $ msg ++ ". Consider this a bug."