decision-diagrams-0.1.0.0: Binary Decision Diagrams (BDD) and Zero-suppressed Binary Decision Diagrams (ZDD)
Copyright(c) Masahiro Sakai 2021
LicenseBSD-style
Maintainermasahiro.sakai@gmail.com
Stabilityunstable
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.DecisionDiagram.BDD

Description

Reduced Ordered Binary Decision Diagrams (ROBDD).

References:

Synopsis

The BDD type

data BDD a where Source #

Reduced ordered binary decision diagram representing boolean function

Bundled Patterns

pattern F :: BDD a 
pattern T :: BDD a 
pattern Branch :: Int -> BDD a -> BDD a -> BDD a

Smart constructor that takes the BDD reduction rules into account

Instances

Instances details
Eq (BDD a) Source # 
Instance details

Defined in Data.DecisionDiagram.BDD

Methods

(==) :: BDD a -> BDD a -> Bool #

(/=) :: BDD a -> BDD a -> Bool #

Read (BDD a) Source # 
Instance details

Defined in Data.DecisionDiagram.BDD

Show (BDD a) Source # 
Instance details

Defined in Data.DecisionDiagram.BDD

Methods

showsPrec :: Int -> BDD a -> ShowS #

show :: BDD a -> String #

showList :: [BDD a] -> ShowS #

Hashable (BDD a) Source # 
Instance details

Defined in Data.DecisionDiagram.BDD

Methods

hashWithSalt :: Int -> BDD a -> Int #

hash :: BDD a -> Int #

Item ordering

class ItemOrder a where Source #

Methods

compareItem :: proxy a -> Int -> Int -> Ordering Source #

Instances

Instances details
ItemOrder DescOrder Source # 
Instance details

Defined in Data.DecisionDiagram.BDD.Internal.ItemOrder

Methods

compareItem :: proxy DescOrder -> Int -> Int -> Ordering Source #

ItemOrder AscOrder Source # 
Instance details

Defined in Data.DecisionDiagram.BDD.Internal.ItemOrder

Methods

compareItem :: proxy AscOrder -> Int -> Int -> Ordering Source #

data AscOrder Source #

Instances

Instances details
ItemOrder AscOrder Source # 
Instance details

Defined in Data.DecisionDiagram.BDD.Internal.ItemOrder

Methods

compareItem :: proxy AscOrder -> Int -> Int -> Ordering Source #

data DescOrder Source #

Instances

Instances details
ItemOrder DescOrder Source # 
Instance details

Defined in Data.DecisionDiagram.BDD.Internal.ItemOrder

Methods

compareItem :: proxy DescOrder -> Int -> Int -> Ordering Source #

withDefaultOrder :: forall r. (forall a. ItemOrder a => Proxy a -> r) -> r Source #

Currently the default order is AscOrder

withAscOrder :: forall r. (Proxy AscOrder -> r) -> r Source #

withDescOrder :: forall r. (Proxy DescOrder -> r) -> r Source #

withCustomOrder :: forall r. (Int -> Int -> Ordering) -> (forall a. ItemOrder a => Proxy a -> r) -> r Source #

Boolean operations

true :: BDD a Source #

True

false :: BDD a Source #

False

var :: Int -> BDD a Source #

A variable \(x_i\)

notB :: BDD a -> BDD a Source #

Negation of a boolean function

(.&&.) :: forall a. ItemOrder a => BDD a -> BDD a -> BDD a infixr 3 Source #

Conjunction of two boolean function

(.||.) :: forall a. ItemOrder a => BDD a -> BDD a -> BDD a infixr 2 Source #

Disjunction of two boolean function

xor :: forall a. ItemOrder a => BDD a -> BDD a -> BDD a Source #

XOR

(.=>.) :: forall a. ItemOrder a => BDD a -> BDD a -> BDD a infixr 1 Source #

Implication

(.<=>.) :: forall a. ItemOrder a => BDD a -> BDD a -> BDD a infix 1 Source #

Equivalence

ite :: forall a. ItemOrder a => BDD a -> BDD a -> BDD a -> BDD a Source #

If-then-else

andB :: forall f a. (Foldable f, ItemOrder a) => f (BDD a) -> BDD a Source #

Conjunction of a list of BDDs.

orB :: forall f a. (Foldable f, ItemOrder a) => f (BDD a) -> BDD a Source #

Disjunction of a list of BDDs.

Quantification

forAll :: forall a. ItemOrder a => Int -> BDD a -> BDD a Source #

Universal quantification (∀)

exists :: forall a. ItemOrder a => Int -> BDD a -> BDD a Source #

Existential quantification (∃)

existsUnique :: forall a. ItemOrder a => Int -> BDD a -> BDD a Source #

Unique existential quantification (∃!)

forAllSet :: forall a. ItemOrder a => IntSet -> BDD a -> BDD a Source #

Universal quantification (∀) over a set of variables

existsSet :: forall a. ItemOrder a => IntSet -> BDD a -> BDD a Source #

Existential quantification (∃) over a set of variables

existsUniqueSet :: forall a. ItemOrder a => IntSet -> BDD a -> BDD a Source #

Unique existential quantification (∃!) over a set of variables

Query

support :: BDD a -> IntSet Source #

All the variables that this BDD depends on.

evaluate :: (Int -> Bool) -> BDD a -> Bool Source #

Evaluate a boolean function represented as BDD under the valuation given by (Int -> Bool), i.e. it lifts a valuation function from variables to BDDs.

Restriction / Cofactor

restrict :: forall a. ItemOrder a => Int -> Bool -> BDD a -> BDD a Source #

Compute \(F_x \) or \(F_{\neg x} \).

restrictSet :: forall a. ItemOrder a => IntMap Bool -> BDD a -> BDD a Source #

Compute \(F_{\{x_i = v_i\}_i} \).

restrictLaw :: forall a. ItemOrder a => BDD a -> BDD a -> BDD a Source #

Compute generalized cofactor of F with respect to C.

Note that C is the first argument.

Substition / Composition

subst :: forall a. ItemOrder a => Int -> BDD a -> BDD a -> BDD a Source #

subst x N M computes substitution \(M_{x = N}\).

This operation is also known as Composition.

substSet :: forall a. ItemOrder a => IntMap (BDD a) -> BDD a -> BDD a Source #

Simultaneous substitution

Fold

fold :: b -> b -> (Int -> b -> b -> b) -> BDD a -> b Source #

Fold over the graph structure of the BDD.

It takes values for substituting false (F) and true (T), and a function for substiting non-terminal node (Branch).

fold' :: b -> b -> (Int -> b -> b -> b) -> BDD a -> b Source #

Strict version of fold

Conversion from/to graphs

data Node Source #

Constructors

NodeF 
NodeT 
NodeBranch !Int Int Int 

Instances

Instances details
Eq Node Source # 
Instance details

Defined in Data.DecisionDiagram.BDD

Methods

(==) :: Node -> Node -> Bool #

(/=) :: Node -> Node -> Bool #

Read Node Source # 
Instance details

Defined in Data.DecisionDiagram.BDD

Show Node Source # 
Instance details

Defined in Data.DecisionDiagram.BDD

Methods

showsPrec :: Int -> Node -> ShowS #

show :: Node -> String #

showList :: [Node] -> ShowS #

toGraph :: BDD a -> (Graph, Int) Source #

Convert a BDD into a pointed graph

toGraph' :: Traversable t => t (BDD a) -> (Graph, t Int) Source #

Convert multiple BDDs into a graph

fromGraph :: (Graph, Int) -> BDD a Source #

Convert a pointed graph into a BDD

fromGraph' :: Graph -> IntMap (BDD a) Source #

Convert nodes of a graph into BDDs