| Copyright | (c) Nicolas Pouillard 20082009 |
|---|---|
| License | BSD3 |
| Maintainer | Nicolas Pouillard <nicolas.pouillard@gmail.com> |
| Stability | provisional |
| Portability | |
| Safe Haskell | Safe-Inferred |
| Language | Haskell98 |
Data.BoolExpr
Description
Boolean expressions and various representations.
Synopsis
- class Boolean f where
- bAnd :: (Foldable t, Boolean f) => t (f b) -> f b
- bAll :: (Foldable t, Boolean f) => (a -> f b) -> t a -> f b
- bOr :: (Foldable t, Boolean f) => t (f b) -> f b
- bAny :: (Foldable t, Boolean f) => (a -> f b) -> t a -> f b
- data BoolExpr a
- reduceBoolExpr :: BoolExpr Bool -> Bool
- evalBoolExpr :: (a -> Bool) -> BoolExpr a -> Bool
- newtype Eval b a = Eval {
- runEval :: (a -> b) -> b
- runEvalId :: Eval a a -> a
- data Signed a
- negateSigned :: Signed a -> Signed a
- evalSigned :: (a -> Bool) -> Signed a -> Bool
- reduceSigned :: Signed Bool -> Bool
- constants :: BoolExpr a -> [Signed a]
- negateConstant :: Boolean f => Signed a -> f a
- newtype CNF a = CNF {}
- newtype Conj a = Conj {
- unConj :: [a]
- fromCNF :: Boolean f => CNF a -> f a
- boolTreeToCNF :: BoolExpr a -> CNF a
- reduceCNF :: CNF Bool -> Bool
- newtype Disj a = Disj {
- unDisj :: [a]
- newtype DNF a = DNF {}
- fromDNF :: Boolean f => DNF a -> f a
- boolTreeToDNF :: BoolExpr a -> DNF a
- reduceDNF :: DNF Bool -> Bool
- dualize :: Boolean f => BoolExpr a -> f a
- fromBoolExpr :: Boolean f => BoolExpr a -> f a
- pushNotInwards :: Boolean f => BoolExpr a -> f a
A boolean class
class Boolean f where Source #
A boolean type class.
Generic functions derived from Boolean
Boolean trees
Syntax of boolean expressions parameterized over a set of leaves, named constants.
Constructors
| BAnd (BoolExpr a) (BoolExpr a) | |
| BOr (BoolExpr a) (BoolExpr a) | |
| BNot (BoolExpr a) | |
| BTrue | |
| BFalse | |
| BConst (Signed a) |
Instances
| Foldable BoolExpr Source # | |
Defined in Data.BoolExpr Methods fold :: Monoid m => BoolExpr m -> m # foldMap :: Monoid m => (a -> m) -> BoolExpr a -> m # foldMap' :: Monoid m => (a -> m) -> BoolExpr a -> m # foldr :: (a -> b -> b) -> b -> BoolExpr a -> b # foldr' :: (a -> b -> b) -> b -> BoolExpr a -> b # foldl :: (b -> a -> b) -> b -> BoolExpr a -> b # foldl' :: (b -> a -> b) -> b -> BoolExpr a -> b # foldr1 :: (a -> a -> a) -> BoolExpr a -> a # foldl1 :: (a -> a -> a) -> BoolExpr a -> a # elem :: Eq a => a -> BoolExpr a -> Bool # maximum :: Ord a => BoolExpr a -> a # minimum :: Ord a => BoolExpr a -> a # | |
| Traversable BoolExpr Source # | |
| Functor BoolExpr Source # | |
| Boolean BoolExpr Source # | |
| Show a => Show (BoolExpr a) Source # | |
| Eq a => Eq (BoolExpr a) Source # | |
| Ord a => Ord (BoolExpr a) Source # | |
reduceBoolExpr :: BoolExpr Bool -> Bool Source #
Reduce a boolean tree annotated by booleans to a single boolean.
Boolean evaluation semantic
Instances
Signed constants
Signed values are either positive or negative.
Instances
| Foldable Signed Source # | |
Defined in Data.BoolExpr Methods fold :: Monoid m => Signed m -> m # foldMap :: Monoid m => (a -> m) -> Signed a -> m # foldMap' :: Monoid m => (a -> m) -> Signed a -> m # foldr :: (a -> b -> b) -> b -> Signed a -> b # foldr' :: (a -> b -> b) -> b -> Signed a -> b # foldl :: (b -> a -> b) -> b -> Signed a -> b # foldl' :: (b -> a -> b) -> b -> Signed a -> b # foldr1 :: (a -> a -> a) -> Signed a -> a # foldl1 :: (a -> a -> a) -> Signed a -> a # elem :: Eq a => a -> Signed a -> Bool # maximum :: Ord a => Signed a -> a # minimum :: Ord a => Signed a -> a # | |
| Traversable Signed Source # | |
| Applicative Signed Source # | |
| Functor Signed Source # | |
| Monad Signed Source # | |
| Read a => Read (Signed a) Source # | |
| Show a => Show (Signed a) Source # | |
| Eq a => Eq (Signed a) Source # | |
| Ord a => Ord (Signed a) Source # | |
Defined in Data.BoolExpr | |
negateSigned :: Signed a -> Signed a Source #
constants :: BoolExpr a -> [Signed a] Source #
Returns constants used in a given boolean tree, these constants are returned signed depending one how many negations stands over a given constant.
negateConstant :: Boolean f => Signed a -> f a Source #
Conjunctive Normal Form
boolTreeToCNF :: BoolExpr a -> CNF a Source #
Convert a boolean tree to a conjunctive normal form.
reduceCNF :: CNF Bool -> Bool Source #
Reduce a boolean expression in conjunctive normal form to a single boolean.
Disjunctive Normal Form
boolTreeToDNF :: BoolExpr a -> DNF a Source #
Convert a boolean tree to a disjunctive normal form.
reduceDNF :: DNF Bool -> Bool Source #
Reduce a boolean expression in disjunctive normal form to a single boolean.
Other transformations
fromBoolExpr :: Boolean f => BoolExpr a -> f a Source #
Turns a boolean tree into any boolean type.
pushNotInwards :: Boolean f => BoolExpr a -> f a Source #
Push the negations inwards as much as possible. The resulting boolean tree no longer use negations.