Cabal-2.0.0.2: A framework for packaging Haskell software

Safe HaskellNone
LanguageHaskell2010

Distribution.Types.CondTree

Synopsis

Documentation

data CondTree v c a #

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 Monoids.

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.)

Constructors

CondNode 

Instances

Functor (CondTree v c) # 

Methods

fmap :: (a -> b) -> CondTree v c a -> CondTree v c b #

(<$) :: a -> CondTree v c b -> CondTree v c a #

Foldable (CondTree v c) # 

Methods

fold :: Monoid m => CondTree v c m -> m #

foldMap :: Monoid m => (a -> m) -> CondTree v c a -> m #

foldr :: (a -> b -> b) -> b -> CondTree v c a -> b #

foldr' :: (a -> b -> b) -> b -> CondTree v c a -> b #

foldl :: (b -> a -> b) -> b -> CondTree v c a -> b #

foldl' :: (b -> a -> b) -> b -> CondTree v c a -> b #

foldr1 :: (a -> a -> a) -> CondTree v c a -> a #

foldl1 :: (a -> a -> a) -> CondTree v c a -> a #

toList :: CondTree v c a -> [a] #

null :: CondTree v c a -> Bool #

length :: CondTree v c a -> Int #

elem :: Eq a => a -> CondTree v c a -> Bool #

maximum :: Ord a => CondTree v c a -> a #

minimum :: Ord a => CondTree v c a -> a #

sum :: Num a => CondTree v c a -> a #

product :: Num a => CondTree v c a -> a #

Traversable (CondTree v c) # 

Methods

traverse :: Applicative f => (a -> f b) -> CondTree v c a -> f (CondTree v c b) #

sequenceA :: Applicative f => CondTree v c (f a) -> f (CondTree v c a) #

mapM :: Monad m => (a -> m b) -> CondTree v c a -> m (CondTree v c b) #

sequence :: Monad m => CondTree v c (m a) -> m (CondTree v c a) #

(Eq v, Eq c, Eq a) => Eq (CondTree v c a) # 

Methods

(==) :: CondTree v c a -> CondTree v c a -> Bool #

(/=) :: CondTree v c a -> CondTree v c a -> Bool #

(Data a, Data c, Data v) => Data (CondTree v c a) # 

Methods

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CondTree v c a) #

toConstr :: CondTree v c a -> Constr #

dataTypeOf :: CondTree v c a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CondTree v c a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CondTree v c a)) #

gmapT :: (forall b. Data b => b -> b) -> CondTree v c a -> CondTree v c a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CondTree v c a -> r #

gmapQ :: (forall d. Data d => d -> u) -> CondTree v c a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CondTree v c a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CondTree v c a -> m (CondTree v c a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CondTree v c a -> m (CondTree v c a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CondTree v c a -> m (CondTree v c a) #

(Show v, Show c, Show a) => Show (CondTree v c a) # 

Methods

showsPrec :: Int -> CondTree v c a -> ShowS #

show :: CondTree v c a -> String #

showList :: [CondTree v c a] -> ShowS #

Generic (CondTree v c a) # 

Associated Types

type Rep (CondTree v c a) :: * -> * #

Methods

from :: CondTree v c a -> Rep (CondTree v c a) x #

to :: Rep (CondTree v c a) x -> CondTree v c a #

(Binary v, Binary c, Binary a) => Binary (CondTree v c a) # 

Methods

put :: CondTree v c a -> Put #

get :: Get (CondTree v c a) #

putList :: [CondTree v c a] -> Put #

type Rep (CondTree v c a) # 
type Rep (CondTree v c a) = D1 * (MetaData "CondTree" "Distribution.Types.CondTree" "Cabal-2.0.0.2-48TVI32Hgv71FS4sRlskN" False) (C1 * (MetaCons "CondNode" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "condTreeData") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a)) ((:*:) * (S1 * (MetaSel (Just Symbol "condTreeConstraints") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * c)) (S1 * (MetaSel (Just Symbol "condTreeComponents") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * [CondBranch v c a])))))

data CondBranch v c a #

A CondBranch represents a conditional branch, e.g., if flag(foo) on some syntax a. It also has an optional false branch.

Instances

Functor (CondBranch v c) # 

Methods

fmap :: (a -> b) -> CondBranch v c a -> CondBranch v c b #

(<$) :: a -> CondBranch v c b -> CondBranch v c a #

Foldable (CondBranch v c) # 

Methods

fold :: Monoid m => CondBranch v c m -> m #

foldMap :: Monoid m => (a -> m) -> CondBranch v c a -> m #

foldr :: (a -> b -> b) -> b -> CondBranch v c a -> b #

foldr' :: (a -> b -> b) -> b -> CondBranch v c a -> b #

foldl :: (b -> a -> b) -> b -> CondBranch v c a -> b #

foldl' :: (b -> a -> b) -> b -> CondBranch v c a -> b #

foldr1 :: (a -> a -> a) -> CondBranch v c a -> a #

foldl1 :: (a -> a -> a) -> CondBranch v c a -> a #

toList :: CondBranch v c a -> [a] #

null :: CondBranch v c a -> Bool #

length :: CondBranch v c a -> Int #

elem :: Eq a => a -> CondBranch v c a -> Bool #

maximum :: Ord a => CondBranch v c a -> a #

minimum :: Ord a => CondBranch v c a -> a #

sum :: Num a => CondBranch v c a -> a #

product :: Num a => CondBranch v c a -> a #

Traversable (CondBranch v c) # 

Methods

traverse :: Applicative f => (a -> f b) -> CondBranch v c a -> f (CondBranch v c b) #

sequenceA :: Applicative f => CondBranch v c (f a) -> f (CondBranch v c a) #

mapM :: Monad m => (a -> m b) -> CondBranch v c a -> m (CondBranch v c b) #

sequence :: Monad m => CondBranch v c (m a) -> m (CondBranch v c a) #

(Eq a, Eq c, Eq v) => Eq (CondBranch v c a) # 

Methods

(==) :: CondBranch v c a -> CondBranch v c a -> Bool #

(/=) :: CondBranch v c a -> CondBranch v c a -> Bool #

(Data a, Data c, Data v) => Data (CondBranch v c a) # 

Methods

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) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (CondBranch v c a) #

toConstr :: CondBranch v c a -> Constr #

dataTypeOf :: CondBranch v c a -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (CondBranch v c a)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (CondBranch v c a)) #

gmapT :: (forall b. Data b => b -> b) -> CondBranch v c a -> CondBranch v c a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CondBranch v c a -> r #

gmapQ :: (forall d. Data d => d -> u) -> CondBranch v c a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CondBranch v c a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CondBranch v c a -> m (CondBranch v c a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CondBranch v c a -> m (CondBranch v c a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CondBranch v c a -> m (CondBranch v c a) #

(Show a, Show c, Show v) => Show (CondBranch v c a) # 

Methods

showsPrec :: Int -> CondBranch v c a -> ShowS #

show :: CondBranch v c a -> String #

showList :: [CondBranch v c a] -> ShowS #

Generic (CondBranch v c a) # 

Associated Types

type Rep (CondBranch v c a) :: * -> * #

Methods

from :: CondBranch v c a -> Rep (CondBranch v c a) x #

to :: Rep (CondBranch v c a) x -> CondBranch v c a #

(Binary v, Binary c, Binary a) => Binary (CondBranch v c a) # 

Methods

put :: CondBranch v c a -> Put #

get :: Get (CondBranch v c a) #

putList :: [CondBranch v c a] -> Put #

type Rep (CondBranch v c a) # 
type Rep (CondBranch v c a) = D1 * (MetaData "CondBranch" "Distribution.Types.CondTree" "Cabal-2.0.0.2-48TVI32Hgv71FS4sRlskN" False) (C1 * (MetaCons "CondBranch" PrefixI True) ((:*:) * (S1 * (MetaSel (Just Symbol "condBranchCondition") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Condition v))) ((:*:) * (S1 * (MetaSel (Just Symbol "condBranchIfTrue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (CondTree v c a))) (S1 * (MetaSel (Just Symbol "condBranchIfFalse") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * (Maybe (CondTree v c a)))))))

condIfThen :: Condition v -> CondTree v c a -> CondBranch v c a #

condIfThenElse :: Condition v -> CondTree v c a -> CondTree v c a -> CondBranch v c a #

mapCondTree :: (a -> b) -> (c -> d) -> (Condition v -> Condition w) -> CondTree v c a -> CondTree w d b #

mapTreeConstrs :: (c -> d) -> CondTree v c a -> CondTree v d a #

mapTreeConds :: (Condition v -> Condition w) -> CondTree v c a -> CondTree w c a #

mapTreeData :: (a -> b) -> CondTree v c a -> CondTree v c b #

extractCondition :: Eq v => (a -> Bool) -> CondTree v c a -> Condition v #

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.

simplifyCondTree :: (Monoid a, Monoid d) => (v -> Either v Bool) -> CondTree v d a -> (d, a) #

Flattens a CondTree using a partial flag assignment. When a condition cannot be evaluated, both branches are ignored.

ignoreConditions :: (Monoid a, Monoid c) => CondTree v c a -> (a, c) #

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.