{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Distribution.Types.CondTree (
    CondTree(..),
    CondBranch(..),
    condIfThen,
    condIfThenElse,
    mapCondTree,
    mapTreeConstrs,
    mapTreeConds,
    mapTreeData,
    traverseCondTreeV,
    traverseCondBranchV,
    traverseCondTreeC,
    traverseCondBranchC,
    extractCondition,
    simplifyCondTree,
    ignoreConditions,
) where

import Prelude ()
import Distribution.Compat.Prelude

import Distribution.Types.Condition

import qualified Distribution.Compat.Lens as L


-- | A 'CondTree' is used to represent the conditional structure of
-- a Cabal file, reflecting a syntax element subject to constraints,
-- and then any number of sub-elements which may be enabled subject
-- to some condition.  Both @a@ and @c@ are usually 'Monoid's.
--
-- To be more concrete, consider the following fragment of a @Cabal@
-- file:
--
-- @
-- build-depends: base >= 4.0
-- if flag(extra)
--     build-depends: base >= 4.2
-- @
--
-- One way to represent this is to have @'CondTree' 'ConfVar'
-- ['Dependency'] 'BuildInfo'@.  Here, 'condTreeData' represents
-- the actual fields which are not behind any conditional, while
-- 'condTreeComponents' recursively records any further fields
-- which are behind a conditional.  'condTreeConstraints' records
-- the constraints (in this case, @base >= 4.0@) which would
-- be applied if you use this syntax; in general, this is
-- derived off of 'targetBuildInfo' (perhaps a good refactoring
-- would be to convert this into an opaque type, with a smart
-- constructor that pre-computes the dependencies.)
--
data CondTree v c a = CondNode
    { CondTree v c a -> a
condTreeData        :: a
    , CondTree v c a -> c
condTreeConstraints :: c
    , CondTree v c a -> [CondBranch v c a]
condTreeComponents  :: [CondBranch v c a]
    }
    deriving (Int -> CondTree v c a -> ShowS
[CondTree v c a] -> ShowS
CondTree v c a -> String
(Int -> CondTree v c a -> ShowS)
-> (CondTree v c a -> String)
-> ([CondTree v c a] -> ShowS)
-> Show (CondTree v c a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall v c a.
(Show a, Show c, Show v) =>
Int -> CondTree v c a -> ShowS
forall v c a. (Show a, Show c, Show v) => [CondTree v c a] -> ShowS
forall v c a. (Show a, Show c, Show v) => CondTree v c a -> String
showList :: [CondTree v c a] -> ShowS
$cshowList :: forall v c a. (Show a, Show c, Show v) => [CondTree v c a] -> ShowS
show :: CondTree v c a -> String
$cshow :: forall v c a. (Show a, Show c, Show v) => CondTree v c a -> String
showsPrec :: Int -> CondTree v c a -> ShowS
$cshowsPrec :: forall v c a.
(Show a, Show c, Show v) =>
Int -> CondTree v c a -> ShowS
Show, CondTree v c a -> CondTree v c a -> Bool
(CondTree v c a -> CondTree v c a -> Bool)
-> (CondTree v c a -> CondTree v c a -> Bool)
-> Eq (CondTree v c a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall v c a.
(Eq a, Eq c, Eq v) =>
CondTree v c a -> CondTree v c a -> Bool
/= :: CondTree v c a -> CondTree v c a -> Bool
$c/= :: forall v c a.
(Eq a, Eq c, Eq v) =>
CondTree v c a -> CondTree v c a -> Bool
== :: CondTree v c a -> CondTree v c a -> Bool
$c== :: forall v c a.
(Eq a, Eq c, Eq v) =>
CondTree v c a -> CondTree v c a -> Bool
Eq, Typeable, Typeable (CondTree v c a)
DataType
Constr
Typeable (CondTree v c a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> CondTree v c a -> c (CondTree v c a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (CondTree v c a))
-> (CondTree v c a -> Constr)
-> (CondTree v c a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (CondTree v c a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (CondTree v c a)))
-> ((forall b. Data b => b -> b)
    -> CondTree v c a -> CondTree v c a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> CondTree v c a -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> CondTree v c a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> CondTree v c a -> m (CondTree v c a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> CondTree v c a -> m (CondTree v c a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> CondTree v c a -> m (CondTree v c a))
-> Data (CondTree v c a)
CondTree v c a -> DataType
CondTree v c a -> Constr
(forall b. Data b => b -> b) -> CondTree v c a -> CondTree v c a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CondTree v c a -> c (CondTree v c a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CondTree v c a)
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CondTree v c a -> u
forall u. (forall d. Data d => d -> u) -> CondTree v c a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r
forall v c a. (Data v, Data c, Data a) => Typeable (CondTree v c a)
forall v c a.
(Data v, Data c, Data a) =>
CondTree v c a -> DataType
forall v c a. (Data v, Data c, Data a) => CondTree v c a -> Constr
forall v c a.
(Data v, Data c, Data a) =>
(forall b. Data b => b -> b) -> CondTree v c a -> CondTree v c a
forall v c a u.
(Data v, Data c, Data a) =>
Int -> (forall d. Data d => d -> u) -> CondTree v c a -> u
forall v c a u.
(Data v, Data c, Data a) =>
(forall d. Data d => d -> u) -> CondTree v c a -> [u]
forall v c a r r'.
(Data v, Data c, Data a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r
forall v c a r r'.
(Data v, Data c, Data a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r
forall v c a (m :: * -> *).
(Data v, Data c, Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CondTree v c a -> m (CondTree v c a)
forall v c a (m :: * -> *).
(Data v, Data c, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CondTree v c a -> m (CondTree v c a)
forall v c a (c :: * -> *).
(Data v, Data c, Data a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CondTree v c a)
forall v c a (c :: * -> *).
(Data v, Data c, Data a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CondTree v c a -> c (CondTree v c a)
forall v c a (t :: * -> *) (c :: * -> *).
(Data v, Data c, Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CondTree v c a))
forall v c a (t :: * -> * -> *) (c :: * -> *).
(Data v, Data c, Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CondTree v c a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CondTree v c a -> m (CondTree v c a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CondTree v c a -> m (CondTree v c a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CondTree v c a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CondTree v c a -> c (CondTree v c a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CondTree v c a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CondTree v c a))
$cCondNode :: Constr
$tCondTree :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> CondTree v c a -> m (CondTree v c a)
$cgmapMo :: forall v c a (m :: * -> *).
(Data v, Data c, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CondTree v c a -> m (CondTree v c a)
gmapMp :: (forall d. Data d => d -> m d)
-> CondTree v c a -> m (CondTree v c a)
$cgmapMp :: forall v c a (m :: * -> *).
(Data v, Data c, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CondTree v c a -> m (CondTree v c a)
gmapM :: (forall d. Data d => d -> m d)
-> CondTree v c a -> m (CondTree v c a)
$cgmapM :: forall v c a (m :: * -> *).
(Data v, Data c, Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CondTree v c a -> m (CondTree v c a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> CondTree v c a -> u
$cgmapQi :: forall v c a u.
(Data v, Data c, Data a) =>
Int -> (forall d. Data d => d -> u) -> CondTree v c a -> u
gmapQ :: (forall d. Data d => d -> u) -> CondTree v c a -> [u]
$cgmapQ :: forall v c a u.
(Data v, Data c, Data a) =>
(forall d. Data d => d -> u) -> CondTree v c a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r
$cgmapQr :: forall v c a r r'.
(Data v, Data c, Data a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r
$cgmapQl :: forall v c a r r'.
(Data v, Data c, Data a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r
gmapT :: (forall b. Data b => b -> b) -> CondTree v c a -> CondTree v c a
$cgmapT :: forall v c a.
(Data v, Data c, Data a) =>
(forall b. Data b => b -> b) -> CondTree v c a -> CondTree v c a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CondTree v c a))
$cdataCast2 :: forall v c a (t :: * -> * -> *) (c :: * -> *).
(Data v, Data c, Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CondTree v c a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CondTree v c a))
$cdataCast1 :: forall v c a (t :: * -> *) (c :: * -> *).
(Data v, Data c, Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CondTree v c a))
dataTypeOf :: CondTree v c a -> DataType
$cdataTypeOf :: forall v c a.
(Data v, Data c, Data a) =>
CondTree v c a -> DataType
toConstr :: CondTree v c a -> Constr
$ctoConstr :: forall v c a. (Data v, Data c, Data a) => CondTree v c a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CondTree v c a)
$cgunfold :: forall v c a (c :: * -> *).
(Data v, Data c, Data a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CondTree v c a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CondTree v c a -> c (CondTree v c a)
$cgfoldl :: forall v c a (c :: * -> *).
(Data v, Data c, Data a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CondTree v c a -> c (CondTree v c a)
$cp1Data :: forall v c a. (Data v, Data c, Data a) => Typeable (CondTree v c a)
Data, (forall x. CondTree v c a -> Rep (CondTree v c a) x)
-> (forall x. Rep (CondTree v c a) x -> CondTree v c a)
-> Generic (CondTree v c a)
forall x. Rep (CondTree v c a) x -> CondTree v c a
forall x. CondTree v c a -> Rep (CondTree v c a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall v c a x. Rep (CondTree v c a) x -> CondTree v c a
forall v c a x. CondTree v c a -> Rep (CondTree v c a) x
$cto :: forall v c a x. Rep (CondTree v c a) x -> CondTree v c a
$cfrom :: forall v c a x. CondTree v c a -> Rep (CondTree v c a) x
Generic, a -> CondTree v c b -> CondTree v c a
(a -> b) -> CondTree v c a -> CondTree v c b
(forall a b. (a -> b) -> CondTree v c a -> CondTree v c b)
-> (forall a b. a -> CondTree v c b -> CondTree v c a)
-> Functor (CondTree v c)
forall a b. a -> CondTree v c b -> CondTree v c a
forall a b. (a -> b) -> CondTree v c a -> CondTree v c b
forall v c a b. a -> CondTree v c b -> CondTree v c a
forall v c a b. (a -> b) -> CondTree v c a -> CondTree v c b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> CondTree v c b -> CondTree v c a
$c<$ :: forall v c a b. a -> CondTree v c b -> CondTree v c a
fmap :: (a -> b) -> CondTree v c a -> CondTree v c b
$cfmap :: forall v c a b. (a -> b) -> CondTree v c a -> CondTree v c b
Functor, CondTree v c a -> Bool
(a -> m) -> CondTree v c a -> m
(a -> b -> b) -> b -> CondTree v c a -> b
(forall m. Monoid m => CondTree v c m -> m)
-> (forall m a. Monoid m => (a -> m) -> CondTree v c a -> m)
-> (forall m a. Monoid m => (a -> m) -> CondTree v c a -> m)
-> (forall a b. (a -> b -> b) -> b -> CondTree v c a -> b)
-> (forall a b. (a -> b -> b) -> b -> CondTree v c a -> b)
-> (forall b a. (b -> a -> b) -> b -> CondTree v c a -> b)
-> (forall b a. (b -> a -> b) -> b -> CondTree v c a -> b)
-> (forall a. (a -> a -> a) -> CondTree v c a -> a)
-> (forall a. (a -> a -> a) -> CondTree v c a -> a)
-> (forall a. CondTree v c a -> [a])
-> (forall a. CondTree v c a -> Bool)
-> (forall a. CondTree v c a -> Int)
-> (forall a. Eq a => a -> CondTree v c a -> Bool)
-> (forall a. Ord a => CondTree v c a -> a)
-> (forall a. Ord a => CondTree v c a -> a)
-> (forall a. Num a => CondTree v c a -> a)
-> (forall a. Num a => CondTree v c a -> a)
-> Foldable (CondTree v c)
forall a. Eq a => a -> CondTree v c a -> Bool
forall a. Num a => CondTree v c a -> a
forall a. Ord a => CondTree v c a -> a
forall m. Monoid m => CondTree v c m -> m
forall a. CondTree v c a -> Bool
forall a. CondTree v c a -> Int
forall a. CondTree v c a -> [a]
forall a. (a -> a -> a) -> CondTree v c a -> a
forall m a. Monoid m => (a -> m) -> CondTree v c a -> m
forall b a. (b -> a -> b) -> b -> CondTree v c a -> b
forall a b. (a -> b -> b) -> b -> CondTree v c a -> b
forall v c a. Eq a => a -> CondTree v c a -> Bool
forall v c a. Num a => CondTree v c a -> a
forall v c a. Ord a => CondTree v c a -> a
forall v c m. Monoid m => CondTree v c m -> m
forall v c a. CondTree v c a -> Bool
forall v c a. CondTree v c a -> Int
forall v c a. CondTree v c a -> [a]
forall v c a. (a -> a -> a) -> CondTree v c a -> a
forall v c m a. Monoid m => (a -> m) -> CondTree v c a -> m
forall v c b a. (b -> a -> b) -> b -> CondTree v c a -> b
forall v c a b. (a -> b -> b) -> b -> CondTree v c a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: CondTree v c a -> a
$cproduct :: forall v c a. Num a => CondTree v c a -> a
sum :: CondTree v c a -> a
$csum :: forall v c a. Num a => CondTree v c a -> a
minimum :: CondTree v c a -> a
$cminimum :: forall v c a. Ord a => CondTree v c a -> a
maximum :: CondTree v c a -> a
$cmaximum :: forall v c a. Ord a => CondTree v c a -> a
elem :: a -> CondTree v c a -> Bool
$celem :: forall v c a. Eq a => a -> CondTree v c a -> Bool
length :: CondTree v c a -> Int
$clength :: forall v c a. CondTree v c a -> Int
null :: CondTree v c a -> Bool
$cnull :: forall v c a. CondTree v c a -> Bool
toList :: CondTree v c a -> [a]
$ctoList :: forall v c a. CondTree v c a -> [a]
foldl1 :: (a -> a -> a) -> CondTree v c a -> a
$cfoldl1 :: forall v c a. (a -> a -> a) -> CondTree v c a -> a
foldr1 :: (a -> a -> a) -> CondTree v c a -> a
$cfoldr1 :: forall v c a. (a -> a -> a) -> CondTree v c a -> a
foldl' :: (b -> a -> b) -> b -> CondTree v c a -> b
$cfoldl' :: forall v c b a. (b -> a -> b) -> b -> CondTree v c a -> b
foldl :: (b -> a -> b) -> b -> CondTree v c a -> b
$cfoldl :: forall v c b a. (b -> a -> b) -> b -> CondTree v c a -> b
foldr' :: (a -> b -> b) -> b -> CondTree v c a -> b
$cfoldr' :: forall v c a b. (a -> b -> b) -> b -> CondTree v c a -> b
foldr :: (a -> b -> b) -> b -> CondTree v c a -> b
$cfoldr :: forall v c a b. (a -> b -> b) -> b -> CondTree v c a -> b
foldMap' :: (a -> m) -> CondTree v c a -> m
$cfoldMap' :: forall v c m a. Monoid m => (a -> m) -> CondTree v c a -> m
foldMap :: (a -> m) -> CondTree v c a -> m
$cfoldMap :: forall v c m a. Monoid m => (a -> m) -> CondTree v c a -> m
fold :: CondTree v c m -> m
$cfold :: forall v c m. Monoid m => CondTree v c m -> m
Foldable, Functor (CondTree v c)
Foldable (CondTree v c)
Functor (CondTree v c)
-> Foldable (CondTree v c)
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> CondTree v c a -> f (CondTree v c b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    CondTree v c (f a) -> f (CondTree v c a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> CondTree v c a -> m (CondTree v c b))
-> (forall (m :: * -> *) a.
    Monad m =>
    CondTree v c (m a) -> m (CondTree v c a))
-> Traversable (CondTree v c)
(a -> f b) -> CondTree v c a -> f (CondTree v c b)
forall v c. Functor (CondTree v c)
forall v c. Foldable (CondTree v c)
forall v c (m :: * -> *) a.
Monad m =>
CondTree v c (m a) -> m (CondTree v c a)
forall v c (f :: * -> *) a.
Applicative f =>
CondTree v c (f a) -> f (CondTree v c a)
forall v c (m :: * -> *) a b.
Monad m =>
(a -> m b) -> CondTree v c a -> m (CondTree v c b)
forall v c (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> CondTree v c a -> f (CondTree v c b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
CondTree v c (m a) -> m (CondTree v c a)
forall (f :: * -> *) a.
Applicative f =>
CondTree v c (f a) -> f (CondTree v c a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> CondTree v c a -> m (CondTree v c b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> CondTree v c a -> f (CondTree v c b)
sequence :: CondTree v c (m a) -> m (CondTree v c a)
$csequence :: forall v c (m :: * -> *) a.
Monad m =>
CondTree v c (m a) -> m (CondTree v c a)
mapM :: (a -> m b) -> CondTree v c a -> m (CondTree v c b)
$cmapM :: forall v c (m :: * -> *) a b.
Monad m =>
(a -> m b) -> CondTree v c a -> m (CondTree v c b)
sequenceA :: CondTree v c (f a) -> f (CondTree v c a)
$csequenceA :: forall v c (f :: * -> *) a.
Applicative f =>
CondTree v c (f a) -> f (CondTree v c a)
traverse :: (a -> f b) -> CondTree v c a -> f (CondTree v c b)
$ctraverse :: forall v c (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> CondTree v c a -> f (CondTree v c b)
$cp2Traversable :: forall v c. Foldable (CondTree v c)
$cp1Traversable :: forall v c. Functor (CondTree v c)
Traversable)

instance (Binary v, Binary c, Binary a) => Binary (CondTree v c a)
instance (Structured v, Structured c, Structured a) => Structured (CondTree v c a)
instance (NFData v, NFData c, NFData a) => NFData (CondTree v c a) where rnf :: CondTree v c a -> ()
rnf = CondTree v c a -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf

-- | A 'CondBranch' represents a conditional branch, e.g., @if
-- flag(foo)@ on some syntax @a@.  It also has an optional false
-- branch.
--
data CondBranch v c a = CondBranch
    { CondBranch v c a -> Condition v
condBranchCondition :: Condition v
    , CondBranch v c a -> CondTree v c a
condBranchIfTrue    :: CondTree v c a
    , CondBranch v c a -> Maybe (CondTree v c a)
condBranchIfFalse   :: Maybe (CondTree v c a)
    }
    deriving (Int -> CondBranch v c a -> ShowS
[CondBranch v c a] -> ShowS
CondBranch v c a -> String
(Int -> CondBranch v c a -> ShowS)
-> (CondBranch v c a -> String)
-> ([CondBranch v c a] -> ShowS)
-> Show (CondBranch v c a)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall v c a.
(Show v, Show a, Show c) =>
Int -> CondBranch v c a -> ShowS
forall v c a.
(Show v, Show a, Show c) =>
[CondBranch v c a] -> ShowS
forall v c a.
(Show v, Show a, Show c) =>
CondBranch v c a -> String
showList :: [CondBranch v c a] -> ShowS
$cshowList :: forall v c a.
(Show v, Show a, Show c) =>
[CondBranch v c a] -> ShowS
show :: CondBranch v c a -> String
$cshow :: forall v c a.
(Show v, Show a, Show c) =>
CondBranch v c a -> String
showsPrec :: Int -> CondBranch v c a -> ShowS
$cshowsPrec :: forall v c a.
(Show v, Show a, Show c) =>
Int -> CondBranch v c a -> ShowS
Show, CondBranch v c a -> CondBranch v c a -> Bool
(CondBranch v c a -> CondBranch v c a -> Bool)
-> (CondBranch v c a -> CondBranch v c a -> Bool)
-> Eq (CondBranch v c a)
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall v c a.
(Eq v, Eq a, Eq c) =>
CondBranch v c a -> CondBranch v c a -> Bool
/= :: CondBranch v c a -> CondBranch v c a -> Bool
$c/= :: forall v c a.
(Eq v, Eq a, Eq c) =>
CondBranch v c a -> CondBranch v c a -> Bool
== :: CondBranch v c a -> CondBranch v c a -> Bool
$c== :: forall v c a.
(Eq v, Eq a, Eq c) =>
CondBranch v c a -> CondBranch v c a -> Bool
Eq, Typeable, Typeable (CondBranch v c a)
DataType
Constr
Typeable (CondBranch v c a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g)
    -> CondBranch v c a
    -> c (CondBranch v c a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (CondBranch v c a))
-> (CondBranch v c a -> Constr)
-> (CondBranch v c a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (CondBranch v c a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (CondBranch v c a)))
-> ((forall b. Data b => b -> b)
    -> CondBranch v c a -> CondBranch v c a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r)
-> (forall u.
    (forall d. Data d => d -> u) -> CondBranch v c a -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> CondBranch v c a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d)
    -> CondBranch v c a -> m (CondBranch v c a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> CondBranch v c a -> m (CondBranch v c a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d)
    -> CondBranch v c a -> m (CondBranch v c a))
-> Data (CondBranch v c a)
CondBranch v c a -> DataType
CondBranch v c a -> Constr
(forall b. Data b => b -> b)
-> CondBranch v c a -> CondBranch v c a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CondBranch v c a -> c (CondBranch v c a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CondBranch v c a)
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> CondBranch v c a -> u
forall u. (forall d. Data d => d -> u) -> CondBranch v c a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r
forall v c a.
(Data v, Data c, Data a) =>
Typeable (CondBranch v c a)
forall v c a.
(Data v, Data c, Data a) =>
CondBranch v c a -> DataType
forall v c a.
(Data v, Data c, Data a) =>
CondBranch v c a -> Constr
forall v c a.
(Data v, Data c, Data a) =>
(forall b. Data b => b -> b)
-> CondBranch v c a -> CondBranch v c a
forall v c a u.
(Data v, Data c, Data a) =>
Int -> (forall d. Data d => d -> u) -> CondBranch v c a -> u
forall v c a u.
(Data v, Data c, Data a) =>
(forall d. Data d => d -> u) -> CondBranch v c a -> [u]
forall v c a r r'.
(Data v, Data c, Data a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r
forall v c a r r'.
(Data v, Data c, Data a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r
forall v c a (m :: * -> *).
(Data v, Data c, Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CondBranch v c a -> m (CondBranch v c a)
forall v c a (m :: * -> *).
(Data v, Data c, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CondBranch v c a -> m (CondBranch v c a)
forall v c a (c :: * -> *).
(Data v, Data c, Data a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CondBranch v c a)
forall v c a (c :: * -> *).
(Data v, Data c, Data a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CondBranch v c a -> c (CondBranch v c a)
forall v c a (t :: * -> *) (c :: * -> *).
(Data v, Data c, Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CondBranch v c a))
forall v c a (t :: * -> * -> *) (c :: * -> *).
(Data v, Data c, Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CondBranch v c a))
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> CondBranch v c a -> m (CondBranch v c a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> CondBranch v c a -> m (CondBranch v c a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CondBranch v c a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CondBranch v c a -> c (CondBranch v c a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (CondBranch v c a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CondBranch v c a))
$cCondBranch :: Constr
$tCondBranch :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> CondBranch v c a -> m (CondBranch v c a)
$cgmapMo :: forall v c a (m :: * -> *).
(Data v, Data c, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CondBranch v c a -> m (CondBranch v c a)
gmapMp :: (forall d. Data d => d -> m d)
-> CondBranch v c a -> m (CondBranch v c a)
$cgmapMp :: forall v c a (m :: * -> *).
(Data v, Data c, Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> CondBranch v c a -> m (CondBranch v c a)
gmapM :: (forall d. Data d => d -> m d)
-> CondBranch v c a -> m (CondBranch v c a)
$cgmapM :: forall v c a (m :: * -> *).
(Data v, Data c, Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> CondBranch v c a -> m (CondBranch v c a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> CondBranch v c a -> u
$cgmapQi :: forall v c a u.
(Data v, Data c, Data a) =>
Int -> (forall d. Data d => d -> u) -> CondBranch v c a -> u
gmapQ :: (forall d. Data d => d -> u) -> CondBranch v c a -> [u]
$cgmapQ :: forall v c a u.
(Data v, Data c, Data a) =>
(forall d. Data d => d -> u) -> CondBranch v c a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r
$cgmapQr :: forall v c a r r'.
(Data v, Data c, Data a) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r
$cgmapQl :: forall v c a r r'.
(Data v, Data c, Data a) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r
gmapT :: (forall b. Data b => b -> b)
-> CondBranch v c a -> CondBranch v c a
$cgmapT :: forall v c a.
(Data v, Data c, Data a) =>
(forall b. Data b => b -> b)
-> CondBranch v c a -> CondBranch v c a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CondBranch v c a))
$cdataCast2 :: forall v c a (t :: * -> * -> *) (c :: * -> *).
(Data v, Data c, Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (CondBranch v c a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (CondBranch v c a))
$cdataCast1 :: forall v c a (t :: * -> *) (c :: * -> *).
(Data v, Data c, Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (CondBranch v c a))
dataTypeOf :: CondBranch v c a -> DataType
$cdataTypeOf :: forall v c a.
(Data v, Data c, Data a) =>
CondBranch v c a -> DataType
toConstr :: CondBranch v c a -> Constr
$ctoConstr :: forall v c a.
(Data v, Data c, Data a) =>
CondBranch v c a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CondBranch v c a)
$cgunfold :: forall v c a (c :: * -> *).
(Data v, Data c, Data a) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (CondBranch v c a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CondBranch v c a -> c (CondBranch v c a)
$cgfoldl :: forall v c a (c :: * -> *).
(Data v, Data c, Data a) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> CondBranch v c a -> c (CondBranch v c a)
$cp1Data :: forall v c a.
(Data v, Data c, Data a) =>
Typeable (CondBranch v c a)
Data, (forall x. CondBranch v c a -> Rep (CondBranch v c a) x)
-> (forall x. Rep (CondBranch v c a) x -> CondBranch v c a)
-> Generic (CondBranch v c a)
forall x. Rep (CondBranch v c a) x -> CondBranch v c a
forall x. CondBranch v c a -> Rep (CondBranch v c a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall v c a x. Rep (CondBranch v c a) x -> CondBranch v c a
forall v c a x. CondBranch v c a -> Rep (CondBranch v c a) x
$cto :: forall v c a x. Rep (CondBranch v c a) x -> CondBranch v c a
$cfrom :: forall v c a x. CondBranch v c a -> Rep (CondBranch v c a) x
Generic, a -> CondBranch v c b -> CondBranch v c a
(a -> b) -> CondBranch v c a -> CondBranch v c b
(forall a b. (a -> b) -> CondBranch v c a -> CondBranch v c b)
-> (forall a b. a -> CondBranch v c b -> CondBranch v c a)
-> Functor (CondBranch v c)
forall a b. a -> CondBranch v c b -> CondBranch v c a
forall a b. (a -> b) -> CondBranch v c a -> CondBranch v c b
forall v c a b. a -> CondBranch v c b -> CondBranch v c a
forall v c a b. (a -> b) -> CondBranch v c a -> CondBranch v c b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> CondBranch v c b -> CondBranch v c a
$c<$ :: forall v c a b. a -> CondBranch v c b -> CondBranch v c a
fmap :: (a -> b) -> CondBranch v c a -> CondBranch v c b
$cfmap :: forall v c a b. (a -> b) -> CondBranch v c a -> CondBranch v c b
Functor, Functor (CondBranch v c)
Foldable (CondBranch v c)
Functor (CondBranch v c)
-> Foldable (CondBranch v c)
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> CondBranch v c a -> f (CondBranch v c b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    CondBranch v c (f a) -> f (CondBranch v c a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> CondBranch v c a -> m (CondBranch v c b))
-> (forall (m :: * -> *) a.
    Monad m =>
    CondBranch v c (m a) -> m (CondBranch v c a))
-> Traversable (CondBranch v c)
(a -> f b) -> CondBranch v c a -> f (CondBranch v c b)
forall v c. Functor (CondBranch v c)
forall v c. Foldable (CondBranch v c)
forall v c (m :: * -> *) a.
Monad m =>
CondBranch v c (m a) -> m (CondBranch v c a)
forall v c (f :: * -> *) a.
Applicative f =>
CondBranch v c (f a) -> f (CondBranch v c a)
forall v c (m :: * -> *) a b.
Monad m =>
(a -> m b) -> CondBranch v c a -> m (CondBranch v c b)
forall v c (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> CondBranch v c a -> f (CondBranch v c b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
CondBranch v c (m a) -> m (CondBranch v c a)
forall (f :: * -> *) a.
Applicative f =>
CondBranch v c (f a) -> f (CondBranch v c a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> CondBranch v c a -> m (CondBranch v c b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> CondBranch v c a -> f (CondBranch v c b)
sequence :: CondBranch v c (m a) -> m (CondBranch v c a)
$csequence :: forall v c (m :: * -> *) a.
Monad m =>
CondBranch v c (m a) -> m (CondBranch v c a)
mapM :: (a -> m b) -> CondBranch v c a -> m (CondBranch v c b)
$cmapM :: forall v c (m :: * -> *) a b.
Monad m =>
(a -> m b) -> CondBranch v c a -> m (CondBranch v c b)
sequenceA :: CondBranch v c (f a) -> f (CondBranch v c a)
$csequenceA :: forall v c (f :: * -> *) a.
Applicative f =>
CondBranch v c (f a) -> f (CondBranch v c a)
traverse :: (a -> f b) -> CondBranch v c a -> f (CondBranch v c b)
$ctraverse :: forall v c (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> CondBranch v c a -> f (CondBranch v c b)
$cp2Traversable :: forall v c. Foldable (CondBranch v c)
$cp1Traversable :: forall v c. Functor (CondBranch v c)
Traversable)

-- This instance is written by hand because GHC 8.0.1/8.0.2 infinite
-- loops when trying to derive it with optimizations.  See
-- https://ghc.haskell.org/trac/ghc/ticket/13056
instance Foldable (CondBranch v c) where
    foldMap :: (a -> m) -> CondBranch v c a -> m
foldMap a -> m
f (CondBranch Condition v
_ CondTree v c a
c Maybe (CondTree v c a)
Nothing) = (a -> m) -> CondTree v c a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f CondTree v c a
c
    foldMap a -> m
f (CondBranch Condition v
_ CondTree v c a
c (Just CondTree v c a
a)) = (a -> m) -> CondTree v c a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f CondTree v c a
c m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` (a -> m) -> CondTree v c a -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f CondTree v c a
a

instance (Binary v, Binary c, Binary a) => Binary (CondBranch v c a)
instance (Structured v, Structured c, Structured a) => Structured (CondBranch v c a)
instance (NFData v, NFData c, NFData a) => NFData (CondBranch v c a) where rnf :: CondBranch v c a -> ()
rnf = CondBranch v c a -> ()
forall a. (Generic a, GNFData (Rep a)) => a -> ()
genericRnf

condIfThen :: Condition v -> CondTree v c a -> CondBranch v c a
condIfThen :: Condition v -> CondTree v c a -> CondBranch v c a
condIfThen Condition v
c CondTree v c a
t = Condition v
-> CondTree v c a -> Maybe (CondTree v c a) -> CondBranch v c a
forall v c a.
Condition v
-> CondTree v c a -> Maybe (CondTree v c a) -> CondBranch v c a
CondBranch Condition v
c CondTree v c a
t Maybe (CondTree v c a)
forall a. Maybe a
Nothing

condIfThenElse :: Condition v -> CondTree v c a -> CondTree v c a -> CondBranch v c a
condIfThenElse :: Condition v -> CondTree v c a -> CondTree v c a -> CondBranch v c a
condIfThenElse Condition v
c CondTree v c a
t CondTree v c a
e = Condition v
-> CondTree v c a -> Maybe (CondTree v c a) -> CondBranch v c a
forall v c a.
Condition v
-> CondTree v c a -> Maybe (CondTree v c a) -> CondBranch v c a
CondBranch Condition v
c CondTree v c a
t (CondTree v c a -> Maybe (CondTree v c a)
forall a. a -> Maybe a
Just CondTree v c a
e)

mapCondTree :: (a -> b) -> (c -> d) -> (Condition v -> Condition w)
            -> CondTree v c a -> CondTree w d b
mapCondTree :: (a -> b)
-> (c -> d)
-> (Condition v -> Condition w)
-> CondTree v c a
-> CondTree w d b
mapCondTree a -> b
fa c -> d
fc Condition v -> Condition w
fcnd (CondNode a
a c
c [CondBranch v c a]
ifs) =
    b -> d -> [CondBranch w d b] -> CondTree w d b
forall v c a. a -> c -> [CondBranch v c a] -> CondTree v c a
CondNode (a -> b
fa a
a) (c -> d
fc c
c) ((CondBranch v c a -> CondBranch w d b)
-> [CondBranch v c a] -> [CondBranch w d b]
forall a b. (a -> b) -> [a] -> [b]
map CondBranch v c a -> CondBranch w d b
g [CondBranch v c a]
ifs)
  where
    g :: CondBranch v c a -> CondBranch w d b
g (CondBranch Condition v
cnd CondTree v c a
t Maybe (CondTree v c a)
me)
        = Condition w
-> CondTree w d b -> Maybe (CondTree w d b) -> CondBranch w d b
forall v c a.
Condition v
-> CondTree v c a -> Maybe (CondTree v c a) -> CondBranch v c a
CondBranch (Condition v -> Condition w
fcnd Condition v
cnd)
                     ((a -> b)
-> (c -> d)
-> (Condition v -> Condition w)
-> CondTree v c a
-> CondTree w d b
forall a b c d v w.
(a -> b)
-> (c -> d)
-> (Condition v -> Condition w)
-> CondTree v c a
-> CondTree w d b
mapCondTree a -> b
fa c -> d
fc Condition v -> Condition w
fcnd CondTree v c a
t)
                     ((CondTree v c a -> CondTree w d b)
-> Maybe (CondTree v c a) -> Maybe (CondTree w d b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b)
-> (c -> d)
-> (Condition v -> Condition w)
-> CondTree v c a
-> CondTree w d b
forall a b c d v w.
(a -> b)
-> (c -> d)
-> (Condition v -> Condition w)
-> CondTree v c a
-> CondTree w d b
mapCondTree a -> b
fa c -> d
fc Condition v -> Condition w
fcnd) Maybe (CondTree v c a)
me)

mapTreeConstrs :: (c -> d) -> CondTree v c a -> CondTree v d a
mapTreeConstrs :: (c -> d) -> CondTree v c a -> CondTree v d a
mapTreeConstrs c -> d
f = (a -> a)
-> (c -> d)
-> (Condition v -> Condition v)
-> CondTree v c a
-> CondTree v d a
forall a b c d v w.
(a -> b)
-> (c -> d)
-> (Condition v -> Condition w)
-> CondTree v c a
-> CondTree w d b
mapCondTree a -> a
forall a. a -> a
id c -> d
f Condition v -> Condition v
forall a. a -> a
id

mapTreeConds :: (Condition v -> Condition w) -> CondTree v c a -> CondTree w c a
mapTreeConds :: (Condition v -> Condition w) -> CondTree v c a -> CondTree w c a
mapTreeConds Condition v -> Condition w
f = (a -> a)
-> (c -> c)
-> (Condition v -> Condition w)
-> CondTree v c a
-> CondTree w c a
forall a b c d v w.
(a -> b)
-> (c -> d)
-> (Condition v -> Condition w)
-> CondTree v c a
-> CondTree w d b
mapCondTree a -> a
forall a. a -> a
id c -> c
forall a. a -> a
id Condition v -> Condition w
f

mapTreeData :: (a -> b) -> CondTree v c a -> CondTree v c b
mapTreeData :: (a -> b) -> CondTree v c a -> CondTree v c b
mapTreeData a -> b
f = (a -> b)
-> (c -> c)
-> (Condition v -> Condition v)
-> CondTree v c a
-> CondTree v c b
forall a b c d v w.
(a -> b)
-> (c -> d)
-> (Condition v -> Condition w)
-> CondTree v c a
-> CondTree w d b
mapCondTree a -> b
f c -> c
forall a. a -> a
id Condition v -> Condition v
forall a. a -> a
id

-- | @@Traversal@@ for the variables
traverseCondTreeV :: L.Traversal (CondTree v c a) (CondTree w c a) v w
traverseCondTreeV :: LensLike f (CondTree v c a) (CondTree w c a) v w
traverseCondTreeV v -> f w
f (CondNode a
a c
c [CondBranch v c a]
ifs) =
    a -> c -> [CondBranch w c a] -> CondTree w c a
forall v c a. a -> c -> [CondBranch v c a] -> CondTree v c a
CondNode a
a c
c ([CondBranch w c a] -> CondTree w c a)
-> f [CondBranch w c a] -> f (CondTree w c a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (CondBranch v c a -> f (CondBranch w c a))
-> [CondBranch v c a] -> f [CondBranch w c a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (LensLike f (CondBranch v c a) (CondBranch w c a) v w
forall v c a w. Traversal (CondBranch v c a) (CondBranch w c a) v w
traverseCondBranchV v -> f w
f) [CondBranch v c a]
ifs

-- | @@Traversal@@ for the variables
traverseCondBranchV :: L.Traversal (CondBranch v c a) (CondBranch w c a) v w
traverseCondBranchV :: LensLike f (CondBranch v c a) (CondBranch w c a) v w
traverseCondBranchV v -> f w
f (CondBranch Condition v
cnd CondTree v c a
t Maybe (CondTree v c a)
me) = Condition w
-> CondTree w c a -> Maybe (CondTree w c a) -> CondBranch w c a
forall v c a.
Condition v
-> CondTree v c a -> Maybe (CondTree v c a) -> CondBranch v c a
CondBranch
    (Condition w
 -> CondTree w c a -> Maybe (CondTree w c a) -> CondBranch w c a)
-> f (Condition w)
-> f (CondTree w c a -> Maybe (CondTree w c a) -> CondBranch w c a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (v -> f w) -> Condition v -> f (Condition w)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse v -> f w
f Condition v
cnd
    f (CondTree w c a -> Maybe (CondTree w c a) -> CondBranch w c a)
-> f (CondTree w c a)
-> f (Maybe (CondTree w c a) -> CondBranch w c a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> LensLike f (CondTree v c a) (CondTree w c a) v w
forall v c a w. Traversal (CondTree v c a) (CondTree w c a) v w
traverseCondTreeV v -> f w
f CondTree v c a
t
    f (Maybe (CondTree w c a) -> CondBranch w c a)
-> f (Maybe (CondTree w c a)) -> f (CondBranch w c a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CondTree v c a -> f (CondTree w c a))
-> Maybe (CondTree v c a) -> f (Maybe (CondTree w c a))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (LensLike f (CondTree v c a) (CondTree w c a) v w
forall v c a w. Traversal (CondTree v c a) (CondTree w c a) v w
traverseCondTreeV v -> f w
f) Maybe (CondTree v c a)
me

-- | @@Traversal@@ for the aggregated constraints
traverseCondTreeC :: L.Traversal (CondTree v c a) (CondTree v d a) c d
traverseCondTreeC :: LensLike f (CondTree v c a) (CondTree v d a) c d
traverseCondTreeC c -> f d
f (CondNode a
a c
c [CondBranch v c a]
ifs) =
    a -> d -> [CondBranch v d a] -> CondTree v d a
forall v c a. a -> c -> [CondBranch v c a] -> CondTree v c a
CondNode a
a (d -> [CondBranch v d a] -> CondTree v d a)
-> f d -> f ([CondBranch v d a] -> CondTree v d a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> c -> f d
f c
c f ([CondBranch v d a] -> CondTree v d a)
-> f [CondBranch v d a] -> f (CondTree v d a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CondBranch v c a -> f (CondBranch v d a))
-> [CondBranch v c a] -> f [CondBranch v d a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (LensLike f (CondBranch v c a) (CondBranch v d a) c d
forall v c a d. Traversal (CondBranch v c a) (CondBranch v d a) c d
traverseCondBranchC c -> f d
f) [CondBranch v c a]
ifs

-- | @@Traversal@@ for the aggregated constraints
traverseCondBranchC :: L.Traversal (CondBranch v c a) (CondBranch v d a) c d
traverseCondBranchC :: LensLike f (CondBranch v c a) (CondBranch v d a) c d
traverseCondBranchC c -> f d
f (CondBranch Condition v
cnd CondTree v c a
t Maybe (CondTree v c a)
me) = Condition v
-> CondTree v d a -> Maybe (CondTree v d a) -> CondBranch v d a
forall v c a.
Condition v
-> CondTree v c a -> Maybe (CondTree v c a) -> CondBranch v c a
CondBranch Condition v
cnd
    (CondTree v d a -> Maybe (CondTree v d a) -> CondBranch v d a)
-> f (CondTree v d a)
-> f (Maybe (CondTree v d a) -> CondBranch v d a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> LensLike f (CondTree v c a) (CondTree v d a) c d
forall v c a d. Traversal (CondTree v c a) (CondTree v d a) c d
traverseCondTreeC c -> f d
f CondTree v c a
t
    f (Maybe (CondTree v d a) -> CondBranch v d a)
-> f (Maybe (CondTree v d a)) -> f (CondBranch v d a)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (CondTree v c a -> f (CondTree v d a))
-> Maybe (CondTree v c a) -> f (Maybe (CondTree v d a))
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (LensLike f (CondTree v c a) (CondTree v d a) c d
forall v c a d. Traversal (CondTree v c a) (CondTree v d a) c d
traverseCondTreeC c -> f d
f) Maybe (CondTree v c a)
me


-- | Extract the condition matched by the given predicate from a cond tree.
--
-- We use this mainly for extracting buildable conditions (see the Note above),
-- but the function is in fact more general.
extractCondition :: Eq v => (a -> Bool) -> CondTree v c a -> Condition v
extractCondition :: (a -> Bool) -> CondTree v c a -> Condition v
extractCondition a -> Bool
p = CondTree v c a -> Condition v
forall a c. Eq a => CondTree a c a -> Condition a
go
  where
    go :: CondTree a c a -> Condition a
go (CondNode a
x c
_ [CondBranch a c a]
cs) | Bool -> Bool
not (a -> Bool
p a
x) = Bool -> Condition a
forall c. Bool -> Condition c
Lit Bool
False
                         | Bool
otherwise = [CondBranch a c a] -> Condition a
goList [CondBranch a c a]
cs

    goList :: [CondBranch a c a] -> Condition a
goList []               = Bool -> Condition a
forall c. Bool -> Condition c
Lit Bool
True
    goList (CondBranch Condition a
c CondTree a c a
t Maybe (CondTree a c a)
e : [CondBranch a c a]
cs) =
      let
        ct :: Condition a
ct = CondTree a c a -> Condition a
go CondTree a c a
t
        ce :: Condition a
ce = Condition a
-> (CondTree a c a -> Condition a)
-> Maybe (CondTree a c a)
-> Condition a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (Bool -> Condition a
forall c. Bool -> Condition c
Lit Bool
True) CondTree a c a -> Condition a
go Maybe (CondTree a c a)
e
      in
        ((Condition a
c Condition a -> Condition a -> Condition a
forall a. Condition a -> Condition a -> Condition a
`cAnd` Condition a
ct) Condition a -> Condition a -> Condition a
forall v. Eq v => Condition v -> Condition v -> Condition v
`cOr` (Condition a -> Condition a
forall c. Condition c -> Condition c
CNot Condition a
c Condition a -> Condition a -> Condition a
forall a. Condition a -> Condition a -> Condition a
`cAnd` Condition a
ce)) Condition a -> Condition a -> Condition a
forall a. Condition a -> Condition a -> Condition a
`cAnd` [CondBranch a c a] -> Condition a
goList [CondBranch a c a]
cs

-- | Flattens a CondTree using a partial flag assignment.  When a condition
-- cannot be evaluated, both branches are ignored.
simplifyCondTree :: (Semigroup a, Semigroup d) =>
                    (v -> Either v Bool)
                 -> CondTree v d a
                 -> (d, a)
simplifyCondTree :: (v -> Either v Bool) -> CondTree v d a -> (d, a)
simplifyCondTree v -> Either v Bool
env (CondNode a
a d
d [CondBranch v d a]
ifs) =
    ((d, a) -> (d, a) -> (d, a)) -> (d, a) -> [(d, a)] -> (d, a)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (d, a) -> (d, a) -> (d, a)
forall a. Semigroup a => a -> a -> a
(<>) (d
d, a
a) ([(d, a)] -> (d, a)) -> [(d, a)] -> (d, a)
forall a b. (a -> b) -> a -> b
$ (CondBranch v d a -> Maybe (d, a))
-> [CondBranch v d a] -> [(d, a)]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe CondBranch v d a -> Maybe (d, a)
forall a d.
(Semigroup a, Semigroup d) =>
CondBranch v d a -> Maybe (d, a)
simplifyIf [CondBranch v d a]
ifs
  where
    simplifyIf :: CondBranch v d a -> Maybe (d, a)
simplifyIf (CondBranch Condition v
cnd CondTree v d a
t Maybe (CondTree v d a)
me) =
        case Condition v -> (v -> Either v Bool) -> (Condition v, [v])
forall c d.
Condition c -> (c -> Either d Bool) -> (Condition d, [d])
simplifyCondition Condition v
cnd v -> Either v Bool
env of
          (Lit Bool
True, [v]
_) -> (d, a) -> Maybe (d, a)
forall a. a -> Maybe a
Just ((d, a) -> Maybe (d, a)) -> (d, a) -> Maybe (d, a)
forall a b. (a -> b) -> a -> b
$ (v -> Either v Bool) -> CondTree v d a -> (d, a)
forall a d v.
(Semigroup a, Semigroup d) =>
(v -> Either v Bool) -> CondTree v d a -> (d, a)
simplifyCondTree v -> Either v Bool
env CondTree v d a
t
          (Lit Bool
False, [v]
_) -> (CondTree v d a -> (d, a))
-> Maybe (CondTree v d a) -> Maybe (d, a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((v -> Either v Bool) -> CondTree v d a -> (d, a)
forall a d v.
(Semigroup a, Semigroup d) =>
(v -> Either v Bool) -> CondTree v d a -> (d, a)
simplifyCondTree v -> Either v Bool
env) Maybe (CondTree v d a)
me
          (Condition v, [v])
_ -> Maybe (d, a)
forall a. Maybe a
Nothing

-- | Flatten a CondTree.  This will resolve the CondTree by taking all
--  possible paths into account.  Note that since branches represent exclusive
--  choices this may not result in a \"sane\" result.
ignoreConditions :: (Semigroup a, Semigroup c) => CondTree v c a -> (a, c)
ignoreConditions :: CondTree v c a -> (a, c)
ignoreConditions (CondNode a
a c
c [CondBranch v c a]
ifs) = ((a, c) -> (a, c) -> (a, c)) -> (a, c) -> [(a, c)] -> (a, c)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl (a, c) -> (a, c) -> (a, c)
forall a. Semigroup a => a -> a -> a
(<>) (a
a, c
c) ([(a, c)] -> (a, c)) -> [(a, c)] -> (a, c)
forall a b. (a -> b) -> a -> b
$ (CondBranch v c a -> [(a, c)]) -> [CondBranch v c a] -> [(a, c)]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap CondBranch v c a -> [(a, c)]
forall a c v.
(Semigroup a, Semigroup c) =>
CondBranch v c a -> [(a, c)]
f [CondBranch v c a]
ifs
  where f :: CondBranch v c a -> [(a, c)]
f (CondBranch Condition v
_ CondTree v c a
t Maybe (CondTree v c a)
me) = CondTree v c a -> (a, c)
forall a c v.
(Semigroup a, Semigroup c) =>
CondTree v c a -> (a, c)
ignoreConditions CondTree v c a
t
                       (a, c) -> [(a, c)] -> [(a, c)]
forall a. a -> [a] -> [a]
: Maybe (a, c) -> [(a, c)]
forall a. Maybe a -> [a]
maybeToList ((CondTree v c a -> (a, c))
-> Maybe (CondTree v c a) -> Maybe (a, c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CondTree v c a -> (a, c)
forall a c v.
(Semigroup a, Semigroup c) =>
CondTree v c a -> (a, c)
ignoreConditions Maybe (CondTree v c a)
me)