module Distribution.Configuration (
Flag(..),
ConfVar(..),
Condition(..), parseCondition, simplifyCondition,
CondTree(..), ppCondTree, mapTreeData,
resolveWithFlags, ignoreConditions,
DepTestRslt(..)
) where
import Distribution.Compat.ReadP as ReadP hiding ( char )
import qualified Distribution.Compat.ReadP as ReadP ( char )
import Distribution.Version
( Version(..), VersionRange(..), withinRange
, showVersionRange, parseVersionRange )
import Text.PrettyPrint.HughesPJ
import Data.Char ( isAlphaNum, toLower )
import Data.Maybe ( catMaybes, maybeToList )
import Data.Monoid
#ifdef DEBUG
import Data.List ( (\\) )
import Distribution.ParseUtils
#endif
data Flag = MkFlag
{ flagName :: String
, flagDescription :: String
, flagDefault :: Bool
}
instance Show Flag where show (MkFlag n _ _) = n
data ConfFlag = ConfFlag String
deriving Eq
data ConfVar = OS String
| Arch String
| Flag ConfFlag
| Impl String VersionRange
deriving Eq
instance Show ConfVar where
show (OS n) = "os(" ++ n ++ ")"
show (Arch n) = "arch(" ++ n ++ ")"
show (Flag (ConfFlag f)) = "flag(" ++ f ++ ")"
show (Impl c v) = "impl(" ++ c ++ " " ++ showVersionRange v ++ ")"
data Condition c = Var c
| Lit Bool
| CNot (Condition c)
| COr (Condition c) (Condition c)
| CAnd (Condition c) (Condition c)
instance Show c => Show (Condition c) where
show c = render $ ppCond c
ppCond :: Show c => Condition c -> Doc
ppCond (Var x) = text (show x)
ppCond (Lit b) = text (show b)
ppCond (CNot c) = char '!' <> parens (ppCond c)
ppCond (COr c1 c2) = parens $ sep [ppCond c1, text "||" <+> ppCond c2]
ppCond (CAnd c1 c2) = parens $ sep [ppCond c1, text "&&" <+> ppCond c2]
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 :: String -> String -> (String, Version) -> Condition ConfVar ->
(Condition ConfFlag, [String])
simplifyWithSysParams os arch (impl, implVer) cond = (cond', flags)
where
(cond', fvs) = simplifyCondition cond interp
interp (OS name) = Right $ lcase name == lcase os
|| lcase name `elem` osAliases (lcase os)
interp (Arch name) = Right $ lcase name == lcase arch
interp (Impl i vr) = Right $ lcase impl == lcase i
&& implVer `withinRange` vr
interp (Flag f) = Left f
flags = [ fname | ConfFlag fname <- fvs ]
osAliases "mingw32" = ["windows"]
osAliases "solaris2" = ["solaris"]
osAliases _ = []
lcase = map toLower
parseCondition :: ReadP r (Condition ConfVar)
parseCondition = condOr
where
condOr = sepBy1 condAnd (oper "||") >>= return . foldl1 COr
condAnd = sepBy1 cond (oper "&&")>>= return . foldl1 CAnd
cond = sp >> (lit +++ 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. OS
archCond = string "arch" >> sp >> inparens archIdent >>= return . Var . Arch
flagCond = string "flag" >> sp >> inparens flagIdent >>= return . Var . Flag . ConfFlag
implCond = string "impl" >> sp >> inparens implIdent >>= return . Var
ident = munch1 isIdentChar >>= return . map toLower
lit = ((string "true" <++ string "True") >> return (Lit True)) <++
((string "false" <++ string "False") >> return (Lit False))
archIdent = ident >>= return
osIdent = ident >>= return
flagIdent = ident
isIdentChar c = isAlphaNum c || (c `elem` "_-")
oper s = sp >> string s >> sp
sp = skipSpaces
implIdent = do i <- ident
vr <- sp >> option AnyVersion parseVersionRange
return $ Impl i vr
data CondTree v c a = CondNode
{ condTreeData :: a
, condTreeConstraints :: c
, condTreeComponents :: [( Condition v
, CondTree v c a
, Maybe (CondTree v c a))]
}
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
instance (Show v, Show c) => Show (CondTree v c a) where
show t = render $ ppCondTree t (text . show)
ppCondTree :: Show v => CondTree v c a -> (c -> Doc) -> Doc
ppCondTree (CondNode _dat cs ifs) ppD =
(text "build-depends: " <+>
ppD cs)
$+$
(vcat $ map ppIf ifs)
where
ppIf (c,thenTree,mElseTree) =
((text "if" <+> ppCond c <> colon) $$
nest 2 (ppCondTree thenTree ppD))
$+$ (maybe empty (\t -> text "else: " $$ nest 2 (ppCondTree t ppD))
mElseTree)
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 =>
[(String,[Bool])]
-> String
-> String
-> (String, Version)
-> [CondTree ConfVar [d] a]
-> ([d] -> DepTestRslt [d])
-> (Either [d]
([a], [d], [(String, Bool)]))
resolveWithFlags dom os arch impl trees checkDeps =
case try dom [] of
Right r -> Right r
Left dbt -> Left $ findShortest dbt
where
preCheckedTrees = map ( mapTreeConstrs (\d -> (checkDeps d,d))
. mapTreeConds (fst . simplifyWithSysParams os arch impl) )
trees
try [] flags =
let (depss, as) = unzip
. map (simplifyCondTree (env flags))
$ preCheckedTrees
in case mconcat depss 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@(ConfFlag n) = maybe (Left flag) Right . lookup n $ 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
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)
#if (__GLASGOW_HASKELL__ && __GLASGOW_HASKELL__ <= 602)
instance (Monoid a, Monoid b) => Monoid (a,b) where
mempty = (mempty, mempty)
(a1,b1) `mappend` (a2,b2) =
(a1 `mappend` a2, b1 `mappend` b2)
#endif
#ifdef DEBUG
tstTree :: CondTree ConfVar [Int] String
tstTree = CondNode "A" [0]
[ (CNot (Var (Flag (ConfFlag "a"))),
CondNode "B" [1] [],
Nothing)
, (CAnd (Var (Flag (ConfFlag "b"))) (Var (Flag (ConfFlag "c"))),
CondNode "C" [2] [],
Just $ CondNode "D" [3]
[ (Lit True,
CondNode "E" [4] [],
Just $ CondNode "F" [5] []) ])
]
test_simplify = simplifyWithSysParams i386 darwin ("ghc",Version [6,6] []) tstCond
where
tstCond = COr (CAnd (Var (Arch ppc)) (Var (OS darwin)))
(CAnd (Var (Flag (ConfFlag "debug"))) (Var (OS darwin)))
[ppc,i386] = ["ppc","i386"]
[darwin,windows] = ["darwin","windows"]
test_parseCondition = map (runP 1 "test" parseCondition) testConditions
where
testConditions = [ "os(darwin)"
, "arch(i386)"
, "!os(linux)"
, "! arch(ppc)"
, "os(windows) && arch(i386)"
, "os(windows) && arch(i386) && flag(debug)"
, "true && false || false && true"
, "(true && false) || (false && true)"
, "(os(darwin))"
, " ( os ( darwin ) ) "
, "true && !(false || os(plan9))"
, "flag( foo_bar )"
, "flag( foo_O_-_O_bar )"
, "impl ( ghc )"
, "impl( ghc >= 6.6.1 )"
]
test_ppCondTree = render $ ppCondTree tstTree (text . show)
test_simpCondTree = simplifyCondTree env tstTree
where
env x = maybe (Left x) Right (lookup x flags)
flags = [(mkFlag "a",False), (mkFlag "b",False), (mkFlag "c", True)]
mkFlag = Flag . ConfFlag
test_resolveWithFlags = resolveWithFlags dom "os" "arch" ("ghc",Version [6,6] []) [tstTree] check
where
dom = [("a", [False,True]), ("b", [True,False]), ("c", [True,False])]
check ds = let missing = ds \\ avail in
case missing of
[] -> DepOk
_ -> MissingDeps missing
avail = [0,1,3,4]
test_ignoreConditions = ignoreConditions tstTree
#endif