hBDD-0.0.2: An abstraction layer for BDD libraries

Safe HaskellSafe-Infered

Data.Boolean

Contents

Description

An interface to libraries supporting efficient manipulation of Boolean functions, such as BDDs. It is an evolution of Logical Abstractions in Haskell by Nancy A. Day, John Launchbury and Jeff Lewis, Haskell Workshop, Paris, October 1999.

The purity of this interface may make it difficult to predict when BDDs actually get constructed.

Note the use of neg rather than not to avoid a clash with Prelude.not.

Synopsis

Abstract interface.

class BooleanVariable b whereSource

Boolean variables.

Methods

bvar :: String -> bSource

A single variable.

bvars :: [String] -> [b]Source

A set of variables, notionally 'adjacent'. What this means is implementation-defined, but the intention is to support (current, next)-state variable pairing.

unbvar :: b -> StringSource

Reverse mapping.

Instances

class Boolean b whereSource

The operators have similar fixities and associativies to the standard boolean operators, but at higher precedence (they bind more strongly).

The overloaded Boolean operations proper. Provides defaults for operations with obvious expansions, such as nand. A minimal instance should define '(/)' and neg.

Methods

false :: bSource

true :: bSource

(/\) :: b -> b -> bSource

neg :: b -> bSource

nand :: b -> b -> bSource

(\/) :: b -> b -> bSource

nor :: b -> b -> bSource

xor :: b -> b -> bSource

(-->) :: b -> b -> bSource

Implication

(<->) :: b -> b -> bSource

If-and-only-if is exclusive nor.

Instances

class (Boolean b, BooleanVariable b) => QBF b whereSource

Quantified Boolean Formulae (QBF) operations.

Associated Types

data Group b :: *Source

The type of aggregations of BooleanVariables.

Some BDD packages have efficient (reusable) variable aggregation structures.

Methods

mkGroup :: [b] -> Group bSource

Construct aggregations.

exists :: Group b -> b -> bSource

Existentially quantify out a given set of variables.

forall :: Group b -> b -> bSource

Universally quantify out a given set of variables.

rel_product :: Group b -> b -> b -> bSource

Computes the relational product of two Boolean formulas:

rel_product qvars f g = exists qvars (f /\ g)

Instances

class (Boolean b, BooleanVariable b) => Substitution b whereSource

Substitutions.

Associated Types

data Subst b :: *Source

Methods

mkSubst :: [(b, b)] -> Subst bSource

Builds a new substitution. The arguments are (Variable, Formula) pairs.

rename :: Subst b -> b -> bSource

Substitutes variables for variables in a Boolean formula. Note that it is the user's responsibility to ensure the Formulas in the substitution are in fact BDD variables, and that the domain and range do not overlap.

substitute :: Subst b -> b -> bSource

Substitutes formulas for variables in a Boolean formula.

Instances

Derived boolean operations.

(<--) :: Boolean b => b -> b -> bSource

Reverse implication

conjoin :: Boolean b => [b] -> bSource

Forms the Big Conjunction of a list of Boolean formulas.

disjoin :: Boolean b => [b] -> bSource

Forms the Big Disjunction of a list of Boolean formulas.

fix :: Eq b => b -> (b -> b) -> bSource

Compute the fixpoint of a Boolean function.

fix2 :: Eq b => a -> b -> (a -> b -> (a, b)) -> (a, b)Source

fix with state.

BDD-specific operations.

class (Eq b, QBF b, Substitution b) => BDDOps b whereSource

Operations provided by BDD representations.

Note that the Eq instance is expected to provide semantic equality on boolean functions, as is typical of BDD packages.

Methods

get_bdd_ptr :: b -> IntPtrSource

Return a pointer to the underlying representation.

bifSource

Arguments

:: b

f

-> b 

Extracts the variable labelling the topmost node in f.

belseSource

Arguments

:: b

f

-> b 

Extracts the this-node-false-branch of a f.

bthenSource

Arguments

:: b

f

-> b 

Extracts the this-node-true-branch of a f.

reduceSource

Arguments

:: b

f

-> b

g (a care set)

-> b 

Returns a BDD which agrees with f for all valuations for which g is true, and which is hopefully smaller than f.

satisfySource

Arguments

:: b

f

-> b 

Finds a satisfying variable assignment for f.

supportSource

Arguments

:: b

f

-> [b] 

Finds the set of variables that f depends on.

data ReorderingMethod Source

BDD libraries tend to include some kind of variable reordering heuristics. These are some common ones.

Constructors

ReorderNone

Switch off variable reordering.

ReorderSift

Sifting

ReorderSiftSym

Sifting with identification of symmetric variables

ReorderStableWindow3

Window permutation.

class RenderBool a whereSource

A class for the text constants and operators used by sop.

Instances

sop :: (BDDOps b, RenderBool a) => b -> aSource

Render a Boolean type as a sum-of-products. This was stolen lock-stock from David Long's calculator example.

countPaths :: BDDOps b => b -> IntegerSource

Count the number of paths in a BDD leading to true.