| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Cudd.Imperative
Description
An ST Monad based interface to the CUDD BDD library
This is a straightforward wrapper around the C library. See http://vlsi.colorado.edu/~fabio/CUDD/ for documentation.
Exampe usage:
import Control.Monad.ST
import Cudd.Imperative
main = do
res <- stToIO $ withManagerDefaults $ \manager -> do
v1 <- ithVar manager 0
v2 <- ithVar manager 1
conj <- bAnd manager v1 v2
implies <- lEq manager conj v1
deref manager conj
return implies
print resDocumentation
Constructors
| DDManager | |
Fields | |
cuddInitDefaults :: ST s (DDManager s u) Source
withManager :: Int -> Int -> Int -> Int -> Int -> (forall u. DDManager s u -> ST s a) -> ST s a Source
withManagerDefaults :: (forall u. DDManager s u -> ST s a) -> ST s a Source
withManagerIO :: MonadIO m => Int -> Int -> Int -> Int -> Int -> (forall u. DDManager RealWorld u -> m a) -> m a Source
withManagerIODefaults :: MonadIO m => (forall u. DDManager RealWorld u -> m a) -> m a Source
shuffleHeap :: DDManager s u -> [Int] -> ST s () Source
swapVariables :: DDManager s u -> [DDNode s u] -> [DDNode s u] -> DDNode s u -> ST s (DDNode s u) Source
xorExistAbstract :: DDManager s u -> DDNode s u -> DDNode s u -> DDNode s u -> ST s (DDNode s u) Source
debugCheck :: DDManager s u -> ST s Int Source
checkZeroRef :: DDManager s u -> ST s Int Source
readNodeCount :: DDManager s u -> ST s Integer Source
readPeakNodeCount :: DDManager s u -> ST s Integer Source
readMaxCache :: DDManager s u -> ST s Int Source
readMaxCacheHard :: DDManager s u -> ST s Int Source
setMaxCacheHard :: DDManager s u -> Int -> ST s () Source
readCacheSlots :: DDManager s u -> ST s Int Source
readCacheUsedSlots :: DDManager s u -> ST s Int Source
printMinterm :: DDManager s u -> DDNode s u -> ST s () Source
isGenEmpty :: DDGen s u t -> ST s Bool Source
firstPrime :: DDManager s u -> DDNode s u -> DDNode s u -> ST s (Maybe ([SatBit], DDGen s u Prime)) Source
module Cudd.Common