module Distribution.Types.CondTree (
CondTree(..),
CondBranch(..),
condIfThen,
condIfThenElse,
mapCondTree,
mapTreeConstrs,
mapTreeConds,
mapTreeData,
traverseCondTreeV,
traverseCondBranchV,
extractCondition,
simplifyCondTree,
ignoreConditions,
) where
import Prelude ()
import Distribution.Compat.Prelude
import Distribution.Types.Condition
data CondTree v c a = CondNode
{ condTreeData :: a
, condTreeConstraints :: c
, condTreeComponents :: [CondBranch v c a]
}
deriving (Show, Eq, Typeable, Data, Generic, Functor, Foldable, Traversable)
instance (Binary v, Binary c, Binary a) => Binary (CondTree v c a)
instance (NFData v, NFData c, NFData a) => NFData (CondTree v c a) where rnf = genericRnf
data CondBranch v c a = CondBranch
{ condBranchCondition :: Condition v
, condBranchIfTrue :: CondTree v c a
, condBranchIfFalse :: Maybe (CondTree v c a)
}
deriving (Show, Eq, Typeable, Data, Generic, Functor, Traversable)
instance Foldable (CondBranch v c) where
foldMap f (CondBranch _ c Nothing) = foldMap f c
foldMap f (CondBranch _ c (Just a)) = foldMap f c `mappend` foldMap f a
instance (Binary v, Binary c, Binary a) => Binary (CondBranch v c a)
instance (NFData v, NFData c, NFData a) => NFData (CondBranch v c a) where rnf = genericRnf
condIfThen :: Condition v -> CondTree v c a -> CondBranch v c a
condIfThen c t = CondBranch c t Nothing
condIfThenElse :: Condition v -> CondTree v c a -> CondTree v c a -> CondBranch v c a
condIfThenElse c t e = CondBranch c t (Just e)
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 (CondBranch cnd t me)
= CondBranch (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
traverseCondTreeV :: Applicative f => (v -> f w) -> CondTree v c a -> f (CondTree w c a)
traverseCondTreeV f (CondNode a c ifs) =
CondNode a c <$> traverse (traverseCondBranchV f) ifs
traverseCondBranchV :: Applicative f => (v -> f w) -> CondBranch v c a -> f (CondBranch w c a)
traverseCondBranchV f (CondBranch cnd t me) = CondBranch
<$> traverse f cnd
<*> traverseCondTreeV f t
<*> traverse (traverseCondTreeV f) me
extractCondition :: Eq v => (a -> Bool) -> CondTree v c a -> Condition v
extractCondition p = go
where
go (CondNode x _ cs) | not (p x) = Lit False
| otherwise = goList cs
goList [] = Lit True
goList (CondBranch c t e : cs) =
let
ct = go t
ce = maybe (Lit True) go e
in
((c `cAnd` ct) `cOr` (CNot c `cAnd` ce)) `cAnd` goList cs
simplifyCondTree :: (Monoid a, Monoid d) =>
(v -> Either v Bool)
-> CondTree v d a
-> (d, a)
simplifyCondTree env (CondNode a d ifs) =
mconcat $ (d, a) : mapMaybe simplifyIf ifs
where
simplifyIf (CondBranch cnd t me) =
case simplifyCondition cnd env of
(Lit True, _) -> Just $ simplifyCondTree env t
(Lit False, _) -> fmap (simplifyCondTree env) me
_ -> Nothing
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 (CondBranch _ t me) = ignoreConditions t
: maybeToList (fmap ignoreConditions me)