Safe Haskell | None |
---|---|
Language | Haskell2010 |
- data CondTree v c a = CondNode {
- condTreeData :: a
- condTreeConstraints :: c
- condTreeComponents :: [CondBranch v c a]
- data CondBranch v c a = CondBranch {
- condBranchCondition :: Condition v
- condBranchIfTrue :: CondTree v c a
- condBranchIfFalse :: 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
- traverseCondTreeV :: Applicative f => (v -> f w) -> CondTree v c a -> f (CondTree w c a)
- traverseCondBranchV :: Applicative f => (v -> f w) -> CondBranch v c a -> f (CondBranch w c a)
- extractCondition :: Eq v => (a -> Bool) -> CondTree v c a -> Condition v
- simplifyCondTree :: (Monoid a, Monoid d) => (v -> Either v Bool) -> CondTree v d a -> (d, a)
- ignoreConditions :: (Monoid a, Monoid c) => CondTree v c a -> (a, c)
Documentation
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
. Here, CondTree
ConfVar
[Dependency
] BuildInfo
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.)
CondNode | |
|
Functor (CondTree v c) # | |
Foldable (CondTree v c) # | |
Traversable (CondTree v c) # | |
(Eq v, Eq c, Eq a) => Eq (CondTree v c a) # | |
(Data a, Data c, Data v) => Data (CondTree v c a) # | |
(Show v, Show c, Show a) => Show (CondTree v c a) # | |
Generic (CondTree v c a) # | |
(Binary v, Binary c, Binary a) => Binary (CondTree v c a) # | |
type Rep (CondTree v c a) # | |
data CondBranch v c a Source #
A CondBranch
represents a conditional branch, e.g., if
flag(foo)
on some syntax a
. It also has an optional false
branch.
CondBranch | |
|
Functor (CondBranch v c) # | |
Foldable (CondBranch v c) # | |
Traversable (CondBranch v c) # | |
(Eq a, Eq c, Eq v) => Eq (CondBranch v c a) # | |
(Data a, Data c, Data v) => Data (CondBranch v c a) # | |
(Show a, Show c, Show v) => Show (CondBranch v c a) # | |
Generic (CondBranch v c a) # | |
(Binary v, Binary c, Binary a) => Binary (CondBranch v c a) # | |
type Rep (CondBranch v c a) # | |
condIfThen :: Condition v -> CondTree v c a -> CondBranch v c a Source #
condIfThenElse :: Condition v -> CondTree v c a -> CondTree v c a -> CondBranch v c a Source #
mapCondTree :: (a -> b) -> (c -> d) -> (Condition v -> Condition w) -> CondTree v c a -> CondTree w d b Source #
mapTreeConstrs :: (c -> d) -> CondTree v c a -> CondTree v d a Source #
mapTreeData :: (a -> b) -> CondTree v c a -> CondTree v c b Source #
traverseCondTreeV :: Applicative f => (v -> f w) -> CondTree v c a -> f (CondTree w c a) Source #
Traversal (CondTree v c a) (CondTree w c a) v w
traverseCondBranchV :: Applicative f => (v -> f w) -> CondBranch v c a -> f (CondBranch w c a) Source #
Traversal (CondBranch v c a) (CondBranch w c a) v w
extractCondition :: Eq v => (a -> Bool) -> CondTree v c a -> Condition v Source #
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.