Cabal-1.2.1: A framework for packaging Haskell softwareContentsIndex
Distribution.Configuration
Portabilityportable
Stabilityalpha
MaintainerIsaac Jones <ijones@syntaxpolice.org>
Description
Configurations
Synopsis
data Flag = MkFlag {
flagName :: String
flagDescription :: String
flagDefault :: Bool
}
data ConfVar
= OS String
| Arch String
| Flag ConfFlag
| Impl String VersionRange
data Condition c
= Var c
| Lit Bool
| CNot (Condition c)
| COr (Condition c) (Condition c)
| CAnd (Condition c) (Condition c)
parseCondition :: ReadP r (Condition ConfVar)
simplifyCondition :: Condition c -> (c -> Either d Bool) -> (Condition d, [d])
data CondTree v c a = CondNode {
condTreeData :: a
condTreeConstraints :: c
condTreeComponents :: [(Condition v, CondTree v c a, Maybe (CondTree v c a))]
}
ppCondTree :: Show v => CondTree v c a -> (c -> Doc) -> Doc
mapTreeData :: (a -> b) -> CondTree v c a -> CondTree v c b
resolveWithFlags :: Monoid a => [(String, [Bool])] -> String -> String -> (String, Version) -> [CondTree ConfVar [d] a] -> ([d] -> DepTestRslt [d]) -> Either [d] ([a], [d], [(String, Bool)])
ignoreConditions :: (Monoid a, Monoid c) => CondTree v c a -> (a, c)
data DepTestRslt d
= DepOk
| MissingDeps d
Documentation
data Flag
A flag can represent a feature to be included, or a way of linking a target against its dependencies, or in fact whatever you can think of.
Constructors
MkFlag
flagName :: String
flagDescription :: String
flagDefault :: Bool
show/hide Instances
data ConfVar
A ConfVar represents the variable type used.
Constructors
OS String
Arch String
Flag ConfFlag
Impl String VersionRange
show/hide Instances
data Condition c
A boolean expression parameterized over the variable type used.
Constructors
Var c
Lit Bool
CNot (Condition c)
COr (Condition c) (Condition c)
CAnd (Condition c) (Condition c)
show/hide Instances
parseCondition :: ReadP r (Condition ConfVar)
Parse a configuration condition from a string.
simplifyCondition
:: Condition c
-> (c -> Either d Bool)(partial) variable assignment
-> (Condition d, [d])
Simplify the condition and return its free variables.
data CondTree v c a
Constructors
CondNode
condTreeData :: a
condTreeConstraints :: c
condTreeComponents :: [(Condition v, CondTree v c a, Maybe (CondTree v c a))]
show/hide Instances
(Show v, Show c) => Show (CondTree v c a)
ppCondTree :: Show v => CondTree v c a -> (c -> Doc) -> Doc
mapTreeData :: (a -> b) -> CondTree v c a -> CondTree v c b
resolveWithFlags
:: Monoid a
=> [(String, [Bool])]Domain for each flag name, will be tested in order.
-> StringOS name, as returned by System.Info.os
-> Stringarch name, as returned by System.Info.arch
-> (String, Version)Compiler name + version
-> [CondTree ConfVar [d] a]
-> ([d] -> DepTestRslt [d])Dependency test function.
-> Either [d] ([a], [d], [(String, Bool)])

Try to find a flag assignment that satisfies the constaints of all trees.

Returns either the missing dependencies, or a tuple containing the resulting data, the associated dependencies, and the chosen flag assignments.

In case of failure, the _smallest_ number of of missing dependencies is returned. [XXX: Could also be specified with a function argument.]

XXX: The current algorithm is rather naive. A better approach would be to:

  • Rule out possible paths, by taking a look at the associated dependencies.
  • Infer the required values for the conditions of these paths, and calculate the required domains for the variables used in these conditions. Then picking a flag assignment would be linear (I guess).

This would require some sort of SAT solving, though, thus it's not implemented unless we really need it.

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.
data DepTestRslt d
Result of dependency test. Isomorphic to Maybe d but renamed for clarity.
Constructors
DepOk
MissingDeps d
show/hide Instances
Produced by Haddock version 0.8