cflp-2009.2.1: Constraint Functional-Logic Programming in HaskellSource codeContentsIndex
CFLP.Constraints.Boolean
Documentation
Boolean (Var, Yes, No, Not, :&&:, :||:)
yes :: Monad m => Nondet c m BooleanSource
no :: Monad m => Nondet c m BooleanSource
neg :: Monad m => Nondet c m Boolean -> Nondet c m BooleanSource
(.&&.) :: Monad m => Nondet c m Boolean -> Nondet c m Boolean -> Nondet c m BooleanSource
(.||.) :: Monad m => Nondet c m Boolean -> Nondet c m Boolean -> Nondet c m BooleanSource
class BooleanSolver c whereSource
Methods
lookupBoolean :: Int -> c -> Maybe BoolSource
assertBoolean :: MonadPlus m => c -> Boolean -> c -> m cSource
show/hide Instances
data SatCtx c Source
show/hide Instances
Transformer SatCtx
Solvable c => Solvable (SatCtx c)
BooleanSolver (SatCtx c)
data Sat s a Source
show/hide Instances
BooleanSolver c => StrategyT c Sat
Monad s => Monad (Sat s)
MonadPlus s => MonadPlus (Sat s)
Enumerable s => Enumerable (Sat s)
satSolving :: Monad s => s c -> Sat s (SatCtx c)Source
ifThen :: (CFLP s, BooleanSolver (Ctx s)) => Data s Boolean -> Data s a -> Context (Ctx s) -> Data s aSource
ifThenElse :: (CFLP s, BooleanSolver (Ctx s)) => Data s Boolean -> Data s a -> Data s a -> Context (Ctx s) -> Data s aSource
booleanToBool :: (CFLP s, BooleanSolver (Ctx s)) => Data s Boolean -> Context (Ctx s) -> Data s BoolSource
Produced by Haddock version 2.4.2