clingo-0.2.0.0: Haskell bindings to the Clingo ASP solver

Safe HaskellNone
LanguageHaskell2010

Clingo.AST

Synopsis

Documentation

parseProgram Source #

Arguments

:: Text

Program

-> Maybe (ClingoWarning -> Text -> IO ())

Logger Callback

-> Natural

Logger Call Limit

-> Clingo s [Statement (Symbol s) (Signature s)] 

Parse a logic program into a list of statements.

fromPureAST :: (Monad (m s), MonadSymbol m) => [Statement PureSymbol PureSignature] -> m s [Statement (Symbol s) (Signature s)] Source #

An AST can be constructed in a pure environment using PureSymbol and PureSignature and then registered with the solver when required. Creation calls for the same symbol in multiple places will be repeated, i.e. no symbol table is being created internally by this function!

data Sign Source #

Instances

Eq Sign Source # 

Methods

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

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

Ord Sign Source # 

Methods

compare :: Sign -> Sign -> Ordering #

(<) :: Sign -> Sign -> Bool #

(<=) :: Sign -> Sign -> Bool #

(>) :: Sign -> Sign -> Bool #

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

max :: Sign -> Sign -> Sign #

min :: Sign -> Sign -> Sign #

Show Sign Source # 

Methods

showsPrec :: Int -> Sign -> ShowS #

show :: Sign -> String #

showList :: [Sign] -> ShowS #

Pretty Sign Source # 

Methods

pretty :: Sign -> Doc #

prettyList :: [Sign] -> Doc #

data Symbol s Source #

Instances

Eq (Symbol s) Source # 

Methods

(==) :: Symbol s -> Symbol s -> Bool #

(/=) :: Symbol s -> Symbol s -> Bool #

Ord (Symbol s) Source # 

Methods

compare :: Symbol s -> Symbol s -> Ordering #

(<) :: Symbol s -> Symbol s -> Bool #

(<=) :: Symbol s -> Symbol s -> Bool #

(>) :: Symbol s -> Symbol s -> Bool #

(>=) :: Symbol s -> Symbol s -> Bool #

max :: Symbol s -> Symbol s -> Symbol s #

min :: Symbol s -> Symbol s -> Symbol s #

Generic (Symbol s) Source # 

Associated Types

type Rep (Symbol s) :: * -> * #

Methods

from :: Symbol s -> Rep (Symbol s) x #

to :: Rep (Symbol s) x -> Symbol s #

NFData (Symbol s) Source # 

Methods

rnf :: Symbol s -> () #

Hashable (Symbol s) Source # 

Methods

hashWithSalt :: Int -> Symbol s -> Int #

hash :: Symbol s -> Int #

type Rep (Symbol s) Source # 

data UnaryOperation a Source #

Instances

Functor UnaryOperation Source # 

Methods

fmap :: (a -> b) -> UnaryOperation a -> UnaryOperation b #

(<$) :: a -> UnaryOperation b -> UnaryOperation a #

Foldable UnaryOperation Source # 

Methods

fold :: Monoid m => UnaryOperation m -> m #

foldMap :: Monoid m => (a -> m) -> UnaryOperation a -> m #

foldr :: (a -> b -> b) -> b -> UnaryOperation a -> b #

foldr' :: (a -> b -> b) -> b -> UnaryOperation a -> b #

foldl :: (b -> a -> b) -> b -> UnaryOperation a -> b #

foldl' :: (b -> a -> b) -> b -> UnaryOperation a -> b #

foldr1 :: (a -> a -> a) -> UnaryOperation a -> a #

foldl1 :: (a -> a -> a) -> UnaryOperation a -> a #

toList :: UnaryOperation a -> [a] #

null :: UnaryOperation a -> Bool #

length :: UnaryOperation a -> Int #

elem :: Eq a => a -> UnaryOperation a -> Bool #

maximum :: Ord a => UnaryOperation a -> a #

minimum :: Ord a => UnaryOperation a -> a #

sum :: Num a => UnaryOperation a -> a #

product :: Num a => UnaryOperation a -> a #

Traversable UnaryOperation Source # 

Methods

traverse :: Applicative f => (a -> f b) -> UnaryOperation a -> f (UnaryOperation b) #

sequenceA :: Applicative f => UnaryOperation (f a) -> f (UnaryOperation a) #

mapM :: Monad m => (a -> m b) -> UnaryOperation a -> m (UnaryOperation b) #

sequence :: Monad m => UnaryOperation (m a) -> m (UnaryOperation a) #

Eq a => Eq (UnaryOperation a) Source # 
Ord a => Ord (UnaryOperation a) Source # 
Show a => Show (UnaryOperation a) Source # 
Pretty a => Pretty (UnaryOperation a) Source # 

data BinaryOperation a Source #

Constructors

BinaryOperation BinaryOperator (Term a) (Term a) 

Instances

Functor BinaryOperation Source # 

Methods

fmap :: (a -> b) -> BinaryOperation a -> BinaryOperation b #

(<$) :: a -> BinaryOperation b -> BinaryOperation a #

Foldable BinaryOperation Source # 

Methods

fold :: Monoid m => BinaryOperation m -> m #

foldMap :: Monoid m => (a -> m) -> BinaryOperation a -> m #

foldr :: (a -> b -> b) -> b -> BinaryOperation a -> b #

foldr' :: (a -> b -> b) -> b -> BinaryOperation a -> b #

foldl :: (b -> a -> b) -> b -> BinaryOperation a -> b #

foldl' :: (b -> a -> b) -> b -> BinaryOperation a -> b #

foldr1 :: (a -> a -> a) -> BinaryOperation a -> a #

foldl1 :: (a -> a -> a) -> BinaryOperation a -> a #

toList :: BinaryOperation a -> [a] #

null :: BinaryOperation a -> Bool #

length :: BinaryOperation a -> Int #

elem :: Eq a => a -> BinaryOperation a -> Bool #

maximum :: Ord a => BinaryOperation a -> a #

minimum :: Ord a => BinaryOperation a -> a #

sum :: Num a => BinaryOperation a -> a #

product :: Num a => BinaryOperation a -> a #

Traversable BinaryOperation Source # 

Methods

traverse :: Applicative f => (a -> f b) -> BinaryOperation a -> f (BinaryOperation b) #

sequenceA :: Applicative f => BinaryOperation (f a) -> f (BinaryOperation a) #

mapM :: Monad m => (a -> m b) -> BinaryOperation a -> m (BinaryOperation b) #

sequence :: Monad m => BinaryOperation (m a) -> m (BinaryOperation a) #

Eq a => Eq (BinaryOperation a) Source # 
Ord a => Ord (BinaryOperation a) Source # 
Show a => Show (BinaryOperation a) Source # 
Pretty a => Pretty (BinaryOperation a) Source # 

data Interval a Source #

Constructors

Interval (Term a) (Term a) 

Instances

Functor Interval Source # 

Methods

fmap :: (a -> b) -> Interval a -> Interval b #

(<$) :: a -> Interval b -> Interval a #

Foldable Interval Source # 

Methods

fold :: Monoid m => Interval m -> m #

foldMap :: Monoid m => (a -> m) -> Interval a -> m #

foldr :: (a -> b -> b) -> b -> Interval a -> b #

foldr' :: (a -> b -> b) -> b -> Interval a -> b #

foldl :: (b -> a -> b) -> b -> Interval a -> b #

foldl' :: (b -> a -> b) -> b -> Interval a -> b #

foldr1 :: (a -> a -> a) -> Interval a -> a #

foldl1 :: (a -> a -> a) -> Interval a -> a #

toList :: Interval a -> [a] #

null :: Interval a -> Bool #

length :: Interval a -> Int #

elem :: Eq a => a -> Interval a -> Bool #

maximum :: Ord a => Interval a -> a #

minimum :: Ord a => Interval a -> a #

sum :: Num a => Interval a -> a #

product :: Num a => Interval a -> a #

Traversable Interval Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Interval a -> f (Interval b) #

sequenceA :: Applicative f => Interval (f a) -> f (Interval a) #

mapM :: Monad m => (a -> m b) -> Interval a -> m (Interval b) #

sequence :: Monad m => Interval (m a) -> m (Interval a) #

Eq a => Eq (Interval a) Source # 

Methods

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

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

Ord a => Ord (Interval a) Source # 

Methods

compare :: Interval a -> Interval a -> Ordering #

(<) :: Interval a -> Interval a -> Bool #

(<=) :: Interval a -> Interval a -> Bool #

(>) :: Interval a -> Interval a -> Bool #

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

max :: Interval a -> Interval a -> Interval a #

min :: Interval a -> Interval a -> Interval a #

Show a => Show (Interval a) Source # 

Methods

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

show :: Interval a -> String #

showList :: [Interval a] -> ShowS #

Pretty a => Pretty (Interval a) Source # 

Methods

pretty :: Interval a -> Doc #

prettyList :: [Interval a] -> Doc #

data Function a Source #

Constructors

Function Text [Term a] 

Instances

Functor Function Source # 

Methods

fmap :: (a -> b) -> Function a -> Function b #

(<$) :: a -> Function b -> Function a #

Foldable Function Source # 

Methods

fold :: Monoid m => Function m -> m #

foldMap :: Monoid m => (a -> m) -> Function a -> m #

foldr :: (a -> b -> b) -> b -> Function a -> b #

foldr' :: (a -> b -> b) -> b -> Function a -> b #

foldl :: (b -> a -> b) -> b -> Function a -> b #

foldl' :: (b -> a -> b) -> b -> Function a -> b #

foldr1 :: (a -> a -> a) -> Function a -> a #

foldl1 :: (a -> a -> a) -> Function a -> a #

toList :: Function a -> [a] #

null :: Function a -> Bool #

length :: Function a -> Int #

elem :: Eq a => a -> Function a -> Bool #

maximum :: Ord a => Function a -> a #

minimum :: Ord a => Function a -> a #

sum :: Num a => Function a -> a #

product :: Num a => Function a -> a #

Traversable Function Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Function a -> f (Function b) #

sequenceA :: Applicative f => Function (f a) -> f (Function a) #

mapM :: Monad m => (a -> m b) -> Function a -> m (Function b) #

sequence :: Monad m => Function (m a) -> m (Function a) #

Eq a => Eq (Function a) Source # 

Methods

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

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

Ord a => Ord (Function a) Source # 

Methods

compare :: Function a -> Function a -> Ordering #

(<) :: Function a -> Function a -> Bool #

(<=) :: Function a -> Function a -> Bool #

(>) :: Function a -> Function a -> Bool #

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

max :: Function a -> Function a -> Function a #

min :: Function a -> Function a -> Function a #

Show a => Show (Function a) Source # 

Methods

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

show :: Function a -> String #

showList :: [Function a] -> ShowS #

Pretty a => Pretty (Function a) Source # 

Methods

pretty :: Function a -> Doc #

prettyList :: [Function a] -> Doc #

data Pool a Source #

Constructors

Pool [Term a] 

Instances

Functor Pool Source # 

Methods

fmap :: (a -> b) -> Pool a -> Pool b #

(<$) :: a -> Pool b -> Pool a #

Foldable Pool Source # 

Methods

fold :: Monoid m => Pool m -> m #

foldMap :: Monoid m => (a -> m) -> Pool a -> m #

foldr :: (a -> b -> b) -> b -> Pool a -> b #

foldr' :: (a -> b -> b) -> b -> Pool a -> b #

foldl :: (b -> a -> b) -> b -> Pool a -> b #

foldl' :: (b -> a -> b) -> b -> Pool a -> b #

foldr1 :: (a -> a -> a) -> Pool a -> a #

foldl1 :: (a -> a -> a) -> Pool a -> a #

toList :: Pool a -> [a] #

null :: Pool a -> Bool #

length :: Pool a -> Int #

elem :: Eq a => a -> Pool a -> Bool #

maximum :: Ord a => Pool a -> a #

minimum :: Ord a => Pool a -> a #

sum :: Num a => Pool a -> a #

product :: Num a => Pool a -> a #

Traversable Pool Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Pool a -> f (Pool b) #

sequenceA :: Applicative f => Pool (f a) -> f (Pool a) #

mapM :: Monad m => (a -> m b) -> Pool a -> m (Pool b) #

sequence :: Monad m => Pool (m a) -> m (Pool a) #

Eq a => Eq (Pool a) Source # 

Methods

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

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

Ord a => Ord (Pool a) Source # 

Methods

compare :: Pool a -> Pool a -> Ordering #

(<) :: Pool a -> Pool a -> Bool #

(<=) :: Pool a -> Pool a -> Bool #

(>) :: Pool a -> Pool a -> Bool #

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

max :: Pool a -> Pool a -> Pool a #

min :: Pool a -> Pool a -> Pool a #

Show a => Show (Pool a) Source # 

Methods

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

show :: Pool a -> String #

showList :: [Pool a] -> ShowS #

Pretty a => Pretty (Pool a) Source # 

Methods

pretty :: Pool a -> Doc #

prettyList :: [Pool a] -> Doc #

data Term a Source #

Instances

Functor Term Source # 

Methods

fmap :: (a -> b) -> Term a -> Term b #

(<$) :: a -> Term b -> Term a #

Foldable Term Source # 

Methods

fold :: Monoid m => Term m -> m #

foldMap :: Monoid m => (a -> m) -> Term a -> m #

foldr :: (a -> b -> b) -> b -> Term a -> b #

foldr' :: (a -> b -> b) -> b -> Term a -> b #

foldl :: (b -> a -> b) -> b -> Term a -> b #

foldl' :: (b -> a -> b) -> b -> Term a -> b #

foldr1 :: (a -> a -> a) -> Term a -> a #

foldl1 :: (a -> a -> a) -> Term a -> a #

toList :: Term a -> [a] #

null :: Term a -> Bool #

length :: Term a -> Int #

elem :: Eq a => a -> Term a -> Bool #

maximum :: Ord a => Term a -> a #

minimum :: Ord a => Term a -> a #

sum :: Num a => Term a -> a #

product :: Num a => Term a -> a #

Traversable Term Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Term a -> f (Term b) #

sequenceA :: Applicative f => Term (f a) -> f (Term a) #

mapM :: Monad m => (a -> m b) -> Term a -> m (Term b) #

sequence :: Monad m => Term (m a) -> m (Term a) #

Eq a => Eq (Term a) Source # 

Methods

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

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

Ord a => Ord (Term a) Source # 

Methods

compare :: Term a -> Term a -> Ordering #

(<) :: Term a -> Term a -> Bool #

(<=) :: Term a -> Term a -> Bool #

(>) :: Term a -> Term a -> Bool #

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

max :: Term a -> Term a -> Term a #

min :: Term a -> Term a -> Term a #

Show a => Show (Term a) Source # 

Methods

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

show :: Term a -> String #

showList :: [Term a] -> ShowS #

Pretty a => Pretty (Term a) Source # 

Methods

pretty :: Term a -> Doc #

prettyList :: [Term a] -> Doc #

data CspProductTerm a Source #

Constructors

CspProductTerm Location (Term a) (Maybe (Term a)) 

Instances

Functor CspProductTerm Source # 

Methods

fmap :: (a -> b) -> CspProductTerm a -> CspProductTerm b #

(<$) :: a -> CspProductTerm b -> CspProductTerm a #

Foldable CspProductTerm Source # 

Methods

fold :: Monoid m => CspProductTerm m -> m #

foldMap :: Monoid m => (a -> m) -> CspProductTerm a -> m #

foldr :: (a -> b -> b) -> b -> CspProductTerm a -> b #

foldr' :: (a -> b -> b) -> b -> CspProductTerm a -> b #

foldl :: (b -> a -> b) -> b -> CspProductTerm a -> b #

foldl' :: (b -> a -> b) -> b -> CspProductTerm a -> b #

foldr1 :: (a -> a -> a) -> CspProductTerm a -> a #

foldl1 :: (a -> a -> a) -> CspProductTerm a -> a #

toList :: CspProductTerm a -> [a] #

null :: CspProductTerm a -> Bool #

length :: CspProductTerm a -> Int #

elem :: Eq a => a -> CspProductTerm a -> Bool #

maximum :: Ord a => CspProductTerm a -> a #

minimum :: Ord a => CspProductTerm a -> a #

sum :: Num a => CspProductTerm a -> a #

product :: Num a => CspProductTerm a -> a #

Traversable CspProductTerm Source # 

Methods

traverse :: Applicative f => (a -> f b) -> CspProductTerm a -> f (CspProductTerm b) #

sequenceA :: Applicative f => CspProductTerm (f a) -> f (CspProductTerm a) #

mapM :: Monad m => (a -> m b) -> CspProductTerm a -> m (CspProductTerm b) #

sequence :: Monad m => CspProductTerm (m a) -> m (CspProductTerm a) #

Eq a => Eq (CspProductTerm a) Source # 
Ord a => Ord (CspProductTerm a) Source # 
Show a => Show (CspProductTerm a) Source # 

data CspSumTerm a Source #

Instances

Functor CspSumTerm Source # 

Methods

fmap :: (a -> b) -> CspSumTerm a -> CspSumTerm b #

(<$) :: a -> CspSumTerm b -> CspSumTerm a #

Foldable CspSumTerm Source # 

Methods

fold :: Monoid m => CspSumTerm m -> m #

foldMap :: Monoid m => (a -> m) -> CspSumTerm a -> m #

foldr :: (a -> b -> b) -> b -> CspSumTerm a -> b #

foldr' :: (a -> b -> b) -> b -> CspSumTerm a -> b #

foldl :: (b -> a -> b) -> b -> CspSumTerm a -> b #

foldl' :: (b -> a -> b) -> b -> CspSumTerm a -> b #

foldr1 :: (a -> a -> a) -> CspSumTerm a -> a #

foldl1 :: (a -> a -> a) -> CspSumTerm a -> a #

toList :: CspSumTerm a -> [a] #

null :: CspSumTerm a -> Bool #

length :: CspSumTerm a -> Int #

elem :: Eq a => a -> CspSumTerm a -> Bool #

maximum :: Ord a => CspSumTerm a -> a #

minimum :: Ord a => CspSumTerm a -> a #

sum :: Num a => CspSumTerm a -> a #

product :: Num a => CspSumTerm a -> a #

Traversable CspSumTerm Source # 

Methods

traverse :: Applicative f => (a -> f b) -> CspSumTerm a -> f (CspSumTerm b) #

sequenceA :: Applicative f => CspSumTerm (f a) -> f (CspSumTerm a) #

mapM :: Monad m => (a -> m b) -> CspSumTerm a -> m (CspSumTerm b) #

sequence :: Monad m => CspSumTerm (m a) -> m (CspSumTerm a) #

Eq a => Eq (CspSumTerm a) Source # 

Methods

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

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

Ord a => Ord (CspSumTerm a) Source # 
Show a => Show (CspSumTerm a) Source # 

data CspGuard a Source #

Instances

Functor CspGuard Source # 

Methods

fmap :: (a -> b) -> CspGuard a -> CspGuard b #

(<$) :: a -> CspGuard b -> CspGuard a #

Foldable CspGuard Source # 

Methods

fold :: Monoid m => CspGuard m -> m #

foldMap :: Monoid m => (a -> m) -> CspGuard a -> m #

foldr :: (a -> b -> b) -> b -> CspGuard a -> b #

foldr' :: (a -> b -> b) -> b -> CspGuard a -> b #

foldl :: (b -> a -> b) -> b -> CspGuard a -> b #

foldl' :: (b -> a -> b) -> b -> CspGuard a -> b #

foldr1 :: (a -> a -> a) -> CspGuard a -> a #

foldl1 :: (a -> a -> a) -> CspGuard a -> a #

toList :: CspGuard a -> [a] #

null :: CspGuard a -> Bool #

length :: CspGuard a -> Int #

elem :: Eq a => a -> CspGuard a -> Bool #

maximum :: Ord a => CspGuard a -> a #

minimum :: Ord a => CspGuard a -> a #

sum :: Num a => CspGuard a -> a #

product :: Num a => CspGuard a -> a #

Traversable CspGuard Source # 

Methods

traverse :: Applicative f => (a -> f b) -> CspGuard a -> f (CspGuard b) #

sequenceA :: Applicative f => CspGuard (f a) -> f (CspGuard a) #

mapM :: Monad m => (a -> m b) -> CspGuard a -> m (CspGuard b) #

sequence :: Monad m => CspGuard (m a) -> m (CspGuard a) #

Eq a => Eq (CspGuard a) Source # 

Methods

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

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

Ord a => Ord (CspGuard a) Source # 

Methods

compare :: CspGuard a -> CspGuard a -> Ordering #

(<) :: CspGuard a -> CspGuard a -> Bool #

(<=) :: CspGuard a -> CspGuard a -> Bool #

(>) :: CspGuard a -> CspGuard a -> Bool #

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

max :: CspGuard a -> CspGuard a -> CspGuard a #

min :: CspGuard a -> CspGuard a -> CspGuard a #

Show a => Show (CspGuard a) Source # 

Methods

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

show :: CspGuard a -> String #

showList :: [CspGuard a] -> ShowS #

data CspLiteral a Source #

Constructors

CspLiteral (CspSumTerm a) [CspGuard a] 

Instances

Functor CspLiteral Source # 

Methods

fmap :: (a -> b) -> CspLiteral a -> CspLiteral b #

(<$) :: a -> CspLiteral b -> CspLiteral a #

Foldable CspLiteral Source # 

Methods

fold :: Monoid m => CspLiteral m -> m #

foldMap :: Monoid m => (a -> m) -> CspLiteral a -> m #

foldr :: (a -> b -> b) -> b -> CspLiteral a -> b #

foldr' :: (a -> b -> b) -> b -> CspLiteral a -> b #

foldl :: (b -> a -> b) -> b -> CspLiteral a -> b #

foldl' :: (b -> a -> b) -> b -> CspLiteral a -> b #

foldr1 :: (a -> a -> a) -> CspLiteral a -> a #

foldl1 :: (a -> a -> a) -> CspLiteral a -> a #

toList :: CspLiteral a -> [a] #

null :: CspLiteral a -> Bool #

length :: CspLiteral a -> Int #

elem :: Eq a => a -> CspLiteral a -> Bool #

maximum :: Ord a => CspLiteral a -> a #

minimum :: Ord a => CspLiteral a -> a #

sum :: Num a => CspLiteral a -> a #

product :: Num a => CspLiteral a -> a #

Traversable CspLiteral Source # 

Methods

traverse :: Applicative f => (a -> f b) -> CspLiteral a -> f (CspLiteral b) #

sequenceA :: Applicative f => CspLiteral (f a) -> f (CspLiteral a) #

mapM :: Monad m => (a -> m b) -> CspLiteral a -> m (CspLiteral b) #

sequence :: Monad m => CspLiteral (m a) -> m (CspLiteral a) #

Eq a => Eq (CspLiteral a) Source # 

Methods

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

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

Ord a => Ord (CspLiteral a) Source # 
Show a => Show (CspLiteral a) Source # 

data Comparison a Source #

Constructors

Comparison ComparisonOperator (Term a) (Term a) 

Instances

Functor Comparison Source # 

Methods

fmap :: (a -> b) -> Comparison a -> Comparison b #

(<$) :: a -> Comparison b -> Comparison a #

Foldable Comparison Source # 

Methods

fold :: Monoid m => Comparison m -> m #

foldMap :: Monoid m => (a -> m) -> Comparison a -> m #

foldr :: (a -> b -> b) -> b -> Comparison a -> b #

foldr' :: (a -> b -> b) -> b -> Comparison a -> b #

foldl :: (b -> a -> b) -> b -> Comparison a -> b #

foldl' :: (b -> a -> b) -> b -> Comparison a -> b #

foldr1 :: (a -> a -> a) -> Comparison a -> a #

foldl1 :: (a -> a -> a) -> Comparison a -> a #

toList :: Comparison a -> [a] #

null :: Comparison a -> Bool #

length :: Comparison a -> Int #

elem :: Eq a => a -> Comparison a -> Bool #

maximum :: Ord a => Comparison a -> a #

minimum :: Ord a => Comparison a -> a #

sum :: Num a => Comparison a -> a #

product :: Num a => Comparison a -> a #

Traversable Comparison Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Comparison a -> f (Comparison b) #

sequenceA :: Applicative f => Comparison (f a) -> f (Comparison a) #

mapM :: Monad m => (a -> m b) -> Comparison a -> m (Comparison b) #

sequence :: Monad m => Comparison (m a) -> m (Comparison a) #

Eq a => Eq (Comparison a) Source # 

Methods

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

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

Ord a => Ord (Comparison a) Source # 
Show a => Show (Comparison a) Source # 
Pretty a => Pretty (Comparison a) Source # 

Methods

pretty :: Comparison a -> Doc #

prettyList :: [Comparison a] -> Doc #

data Literal a Source #

Instances

Functor Literal Source # 

Methods

fmap :: (a -> b) -> Literal a -> Literal b #

(<$) :: a -> Literal b -> Literal a #

Foldable Literal Source # 

Methods

fold :: Monoid m => Literal m -> m #

foldMap :: Monoid m => (a -> m) -> Literal a -> m #

foldr :: (a -> b -> b) -> b -> Literal a -> b #

foldr' :: (a -> b -> b) -> b -> Literal a -> b #

foldl :: (b -> a -> b) -> b -> Literal a -> b #

foldl' :: (b -> a -> b) -> b -> Literal a -> b #

foldr1 :: (a -> a -> a) -> Literal a -> a #

foldl1 :: (a -> a -> a) -> Literal a -> a #

toList :: Literal a -> [a] #

null :: Literal a -> Bool #

length :: Literal a -> Int #

elem :: Eq a => a -> Literal a -> Bool #

maximum :: Ord a => Literal a -> a #

minimum :: Ord a => Literal a -> a #

sum :: Num a => Literal a -> a #

product :: Num a => Literal a -> a #

Traversable Literal Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Literal a -> f (Literal b) #

sequenceA :: Applicative f => Literal (f a) -> f (Literal a) #

mapM :: Monad m => (a -> m b) -> Literal a -> m (Literal b) #

sequence :: Monad m => Literal (m a) -> m (Literal a) #

Eq a => Eq (Literal a) Source # 

Methods

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

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

Ord a => Ord (Literal a) Source # 

Methods

compare :: Literal a -> Literal a -> Ordering #

(<) :: Literal a -> Literal a -> Bool #

(<=) :: Literal a -> Literal a -> Bool #

(>) :: Literal a -> Literal a -> Bool #

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

max :: Literal a -> Literal a -> Literal a #

min :: Literal a -> Literal a -> Literal a #

Show a => Show (Literal a) Source # 

Methods

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

show :: Literal a -> String #

showList :: [Literal a] -> ShowS #

Pretty a => Pretty (Literal a) Source # 

Methods

pretty :: Literal a -> Doc #

prettyList :: [Literal a] -> Doc #

data AggregateGuard a Source #

Instances

Functor AggregateGuard Source # 

Methods

fmap :: (a -> b) -> AggregateGuard a -> AggregateGuard b #

(<$) :: a -> AggregateGuard b -> AggregateGuard a #

Foldable AggregateGuard Source # 

Methods

fold :: Monoid m => AggregateGuard m -> m #

foldMap :: Monoid m => (a -> m) -> AggregateGuard a -> m #

foldr :: (a -> b -> b) -> b -> AggregateGuard a -> b #

foldr' :: (a -> b -> b) -> b -> AggregateGuard a -> b #

foldl :: (b -> a -> b) -> b -> AggregateGuard a -> b #

foldl' :: (b -> a -> b) -> b -> AggregateGuard a -> b #

foldr1 :: (a -> a -> a) -> AggregateGuard a -> a #

foldl1 :: (a -> a -> a) -> AggregateGuard a -> a #

toList :: AggregateGuard a -> [a] #

null :: AggregateGuard a -> Bool #

length :: AggregateGuard a -> Int #

elem :: Eq a => a -> AggregateGuard a -> Bool #

maximum :: Ord a => AggregateGuard a -> a #

minimum :: Ord a => AggregateGuard a -> a #

sum :: Num a => AggregateGuard a -> a #

product :: Num a => AggregateGuard a -> a #

Traversable AggregateGuard Source # 

Methods

traverse :: Applicative f => (a -> f b) -> AggregateGuard a -> f (AggregateGuard b) #

sequenceA :: Applicative f => AggregateGuard (f a) -> f (AggregateGuard a) #

mapM :: Monad m => (a -> m b) -> AggregateGuard a -> m (AggregateGuard b) #

sequence :: Monad m => AggregateGuard (m a) -> m (AggregateGuard a) #

Eq a => Eq (AggregateGuard a) Source # 
Ord a => Ord (AggregateGuard a) Source # 
Show a => Show (AggregateGuard a) Source # 
Pretty a => Pretty (AggregateGuard a) Source #

Instance describing left-guards.

data ConditionalLiteral a Source #

Constructors

ConditionalLiteral (Literal a) [Literal a] 

Instances

Functor ConditionalLiteral Source # 
Foldable ConditionalLiteral Source # 

Methods

fold :: Monoid m => ConditionalLiteral m -> m #

foldMap :: Monoid m => (a -> m) -> ConditionalLiteral a -> m #

foldr :: (a -> b -> b) -> b -> ConditionalLiteral a -> b #

foldr' :: (a -> b -> b) -> b -> ConditionalLiteral a -> b #

foldl :: (b -> a -> b) -> b -> ConditionalLiteral a -> b #

foldl' :: (b -> a -> b) -> b -> ConditionalLiteral a -> b #

foldr1 :: (a -> a -> a) -> ConditionalLiteral a -> a #

foldl1 :: (a -> a -> a) -> ConditionalLiteral a -> a #

toList :: ConditionalLiteral a -> [a] #

null :: ConditionalLiteral a -> Bool #

length :: ConditionalLiteral a -> Int #

elem :: Eq a => a -> ConditionalLiteral a -> Bool #

maximum :: Ord a => ConditionalLiteral a -> a #

minimum :: Ord a => ConditionalLiteral a -> a #

sum :: Num a => ConditionalLiteral a -> a #

product :: Num a => ConditionalLiteral a -> a #

Traversable ConditionalLiteral Source # 
Eq a => Eq (ConditionalLiteral a) Source # 
Ord a => Ord (ConditionalLiteral a) Source # 
Show a => Show (ConditionalLiteral a) Source # 
Pretty a => Pretty (ConditionalLiteral a) Source # 

data Aggregate a Source #

Instances

Functor Aggregate Source # 

Methods

fmap :: (a -> b) -> Aggregate a -> Aggregate b #

(<$) :: a -> Aggregate b -> Aggregate a #

Foldable Aggregate Source # 

Methods

fold :: Monoid m => Aggregate m -> m #

foldMap :: Monoid m => (a -> m) -> Aggregate a -> m #

foldr :: (a -> b -> b) -> b -> Aggregate a -> b #

foldr' :: (a -> b -> b) -> b -> Aggregate a -> b #

foldl :: (b -> a -> b) -> b -> Aggregate a -> b #

foldl' :: (b -> a -> b) -> b -> Aggregate a -> b #

foldr1 :: (a -> a -> a) -> Aggregate a -> a #

foldl1 :: (a -> a -> a) -> Aggregate a -> a #

toList :: Aggregate a -> [a] #

null :: Aggregate a -> Bool #

length :: Aggregate a -> Int #

elem :: Eq a => a -> Aggregate a -> Bool #

maximum :: Ord a => Aggregate a -> a #

minimum :: Ord a => Aggregate a -> a #

sum :: Num a => Aggregate a -> a #

product :: Num a => Aggregate a -> a #

Traversable Aggregate Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Aggregate a -> f (Aggregate b) #

sequenceA :: Applicative f => Aggregate (f a) -> f (Aggregate a) #

mapM :: Monad m => (a -> m b) -> Aggregate a -> m (Aggregate b) #

sequence :: Monad m => Aggregate (m a) -> m (Aggregate a) #

Eq a => Eq (Aggregate a) Source # 

Methods

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

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

Ord a => Ord (Aggregate a) Source # 
Show a => Show (Aggregate a) Source # 
Pretty a => Pretty (Aggregate a) Source # 

Methods

pretty :: Aggregate a -> Doc #

prettyList :: [Aggregate a] -> Doc #

data BodyAggregateElement a Source #

Constructors

BodyAggregateElement [Term a] [Literal a] 

Instances

Functor BodyAggregateElement Source # 
Foldable BodyAggregateElement Source # 

Methods

fold :: Monoid m => BodyAggregateElement m -> m #

foldMap :: Monoid m => (a -> m) -> BodyAggregateElement a -> m #

foldr :: (a -> b -> b) -> b -> BodyAggregateElement a -> b #

foldr' :: (a -> b -> b) -> b -> BodyAggregateElement a -> b #

foldl :: (b -> a -> b) -> b -> BodyAggregateElement a -> b #

foldl' :: (b -> a -> b) -> b -> BodyAggregateElement a -> b #

foldr1 :: (a -> a -> a) -> BodyAggregateElement a -> a #

foldl1 :: (a -> a -> a) -> BodyAggregateElement a -> a #

toList :: BodyAggregateElement a -> [a] #

null :: BodyAggregateElement a -> Bool #

length :: BodyAggregateElement a -> Int #

elem :: Eq a => a -> BodyAggregateElement a -> Bool #

maximum :: Ord a => BodyAggregateElement a -> a #

minimum :: Ord a => BodyAggregateElement a -> a #

sum :: Num a => BodyAggregateElement a -> a #

product :: Num a => BodyAggregateElement a -> a #

Traversable BodyAggregateElement Source # 
Eq a => Eq (BodyAggregateElement a) Source # 
Ord a => Ord (BodyAggregateElement a) Source # 
Show a => Show (BodyAggregateElement a) Source # 
Pretty a => Pretty (BodyAggregateElement a) Source # 

data BodyAggregate a Source #

Instances

Functor BodyAggregate Source # 

Methods

fmap :: (a -> b) -> BodyAggregate a -> BodyAggregate b #

(<$) :: a -> BodyAggregate b -> BodyAggregate a #

Foldable BodyAggregate Source # 

Methods

fold :: Monoid m => BodyAggregate m -> m #

foldMap :: Monoid m => (a -> m) -> BodyAggregate a -> m #

foldr :: (a -> b -> b) -> b -> BodyAggregate a -> b #

foldr' :: (a -> b -> b) -> b -> BodyAggregate a -> b #

foldl :: (b -> a -> b) -> b -> BodyAggregate a -> b #

foldl' :: (b -> a -> b) -> b -> BodyAggregate a -> b #

foldr1 :: (a -> a -> a) -> BodyAggregate a -> a #

foldl1 :: (a -> a -> a) -> BodyAggregate a -> a #

toList :: BodyAggregate a -> [a] #

null :: BodyAggregate a -> Bool #

length :: BodyAggregate a -> Int #

elem :: Eq a => a -> BodyAggregate a -> Bool #

maximum :: Ord a => BodyAggregate a -> a #

minimum :: Ord a => BodyAggregate a -> a #

sum :: Num a => BodyAggregate a -> a #

product :: Num a => BodyAggregate a -> a #

Traversable BodyAggregate Source # 

Methods

traverse :: Applicative f => (a -> f b) -> BodyAggregate a -> f (BodyAggregate b) #

sequenceA :: Applicative f => BodyAggregate (f a) -> f (BodyAggregate a) #

mapM :: Monad m => (a -> m b) -> BodyAggregate a -> m (BodyAggregate b) #

sequence :: Monad m => BodyAggregate (m a) -> m (BodyAggregate a) #

Eq a => Eq (BodyAggregate a) Source # 
Ord a => Ord (BodyAggregate a) Source # 
Show a => Show (BodyAggregate a) Source # 
Pretty a => Pretty (BodyAggregate a) Source # 

data HeadAggregateElement a Source #

Instances

Functor HeadAggregateElement Source # 
Foldable HeadAggregateElement Source # 

Methods

fold :: Monoid m => HeadAggregateElement m -> m #

foldMap :: Monoid m => (a -> m) -> HeadAggregateElement a -> m #

foldr :: (a -> b -> b) -> b -> HeadAggregateElement a -> b #

foldr' :: (a -> b -> b) -> b -> HeadAggregateElement a -> b #

foldl :: (b -> a -> b) -> b -> HeadAggregateElement a -> b #

foldl' :: (b -> a -> b) -> b -> HeadAggregateElement a -> b #

foldr1 :: (a -> a -> a) -> HeadAggregateElement a -> a #

foldl1 :: (a -> a -> a) -> HeadAggregateElement a -> a #

toList :: HeadAggregateElement a -> [a] #

null :: HeadAggregateElement a -> Bool #

length :: HeadAggregateElement a -> Int #

elem :: Eq a => a -> HeadAggregateElement a -> Bool #

maximum :: Ord a => HeadAggregateElement a -> a #

minimum :: Ord a => HeadAggregateElement a -> a #

sum :: Num a => HeadAggregateElement a -> a #

product :: Num a => HeadAggregateElement a -> a #

Traversable HeadAggregateElement Source # 
Eq a => Eq (HeadAggregateElement a) Source # 
Ord a => Ord (HeadAggregateElement a) Source # 
Show a => Show (HeadAggregateElement a) Source # 
Pretty a => Pretty (HeadAggregateElement a) Source # 

data HeadAggregate a Source #

Instances

Functor HeadAggregate Source # 

Methods

fmap :: (a -> b) -> HeadAggregate a -> HeadAggregate b #

(<$) :: a -> HeadAggregate b -> HeadAggregate a #

Foldable HeadAggregate Source # 

Methods

fold :: Monoid m => HeadAggregate m -> m #

foldMap :: Monoid m => (a -> m) -> HeadAggregate a -> m #

foldr :: (a -> b -> b) -> b -> HeadAggregate a -> b #

foldr' :: (a -> b -> b) -> b -> HeadAggregate a -> b #

foldl :: (b -> a -> b) -> b -> HeadAggregate a -> b #

foldl' :: (b -> a -> b) -> b -> HeadAggregate a -> b #

foldr1 :: (a -> a -> a) -> HeadAggregate a -> a #

foldl1 :: (a -> a -> a) -> HeadAggregate a -> a #

toList :: HeadAggregate a -> [a] #

null :: HeadAggregate a -> Bool #

length :: HeadAggregate a -> Int #

elem :: Eq a => a -> HeadAggregate a -> Bool #

maximum :: Ord a => HeadAggregate a -> a #

minimum :: Ord a => HeadAggregate a -> a #

sum :: Num a => HeadAggregate a -> a #

product :: Num a => HeadAggregate a -> a #

Traversable HeadAggregate Source # 

Methods

traverse :: Applicative f => (a -> f b) -> HeadAggregate a -> f (HeadAggregate b) #

sequenceA :: Applicative f => HeadAggregate (f a) -> f (HeadAggregate a) #

mapM :: Monad m => (a -> m b) -> HeadAggregate a -> m (HeadAggregate b) #

sequence :: Monad m => HeadAggregate (m a) -> m (HeadAggregate a) #

Eq a => Eq (HeadAggregate a) Source # 
Ord a => Ord (HeadAggregate a) Source # 
Show a => Show (HeadAggregate a) Source # 
Pretty a => Pretty (HeadAggregate a) Source # 

data Disjunction a Source #

Instances

Functor Disjunction Source # 

Methods

fmap :: (a -> b) -> Disjunction a -> Disjunction b #

(<$) :: a -> Disjunction b -> Disjunction a #

Foldable Disjunction Source # 

Methods

fold :: Monoid m => Disjunction m -> m #

foldMap :: Monoid m => (a -> m) -> Disjunction a -> m #

foldr :: (a -> b -> b) -> b -> Disjunction a -> b #

foldr' :: (a -> b -> b) -> b -> Disjunction a -> b #

foldl :: (b -> a -> b) -> b -> Disjunction a -> b #

foldl' :: (b -> a -> b) -> b -> Disjunction a -> b #

foldr1 :: (a -> a -> a) -> Disjunction a -> a #

foldl1 :: (a -> a -> a) -> Disjunction a -> a #

toList :: Disjunction a -> [a] #

null :: Disjunction a -> Bool #

length :: Disjunction a -> Int #

elem :: Eq a => a -> Disjunction a -> Bool #

maximum :: Ord a => Disjunction a -> a #

minimum :: Ord a => Disjunction a -> a #

sum :: Num a => Disjunction a -> a #

product :: Num a => Disjunction a -> a #

Traversable Disjunction Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Disjunction a -> f (Disjunction b) #

sequenceA :: Applicative f => Disjunction (f a) -> f (Disjunction a) #

mapM :: Monad m => (a -> m b) -> Disjunction a -> m (Disjunction b) #

sequence :: Monad m => Disjunction (m a) -> m (Disjunction a) #

Eq a => Eq (Disjunction a) Source # 
Ord a => Ord (Disjunction a) Source # 
Show a => Show (Disjunction a) Source # 
Pretty a => Pretty (Disjunction a) Source # 

Methods

pretty :: Disjunction a -> Doc #

prettyList :: [Disjunction a] -> Doc #

data DisjointElement a Source #

Constructors

DisjointElement Location [Term a] (CspSumTerm a) [Literal a] 

Instances

Functor DisjointElement Source # 

Methods

fmap :: (a -> b) -> DisjointElement a -> DisjointElement b #

(<$) :: a -> DisjointElement b -> DisjointElement a #

Foldable DisjointElement Source # 

Methods

fold :: Monoid m => DisjointElement m -> m #

foldMap :: Monoid m => (a -> m) -> DisjointElement a -> m #

foldr :: (a -> b -> b) -> b -> DisjointElement a -> b #

foldr' :: (a -> b -> b) -> b -> DisjointElement a -> b #

foldl :: (b -> a -> b) -> b -> DisjointElement a -> b #

foldl' :: (b -> a -> b) -> b -> DisjointElement a -> b #

foldr1 :: (a -> a -> a) -> DisjointElement a -> a #

foldl1 :: (a -> a -> a) -> DisjointElement a -> a #

toList :: DisjointElement a -> [a] #

null :: DisjointElement a -> Bool #

length :: DisjointElement a -> Int #

elem :: Eq a => a -> DisjointElement a -> Bool #

maximum :: Ord a => DisjointElement a -> a #

minimum :: Ord a => DisjointElement a -> a #

sum :: Num a => DisjointElement a -> a #

product :: Num a => DisjointElement a -> a #

Traversable DisjointElement Source # 

Methods

traverse :: Applicative f => (a -> f b) -> DisjointElement a -> f (DisjointElement b) #

sequenceA :: Applicative f => DisjointElement (f a) -> f (DisjointElement a) #

mapM :: Monad m => (a -> m b) -> DisjointElement a -> m (DisjointElement b) #

sequence :: Monad m => DisjointElement (m a) -> m (DisjointElement a) #

Eq a => Eq (DisjointElement a) Source # 
Ord a => Ord (DisjointElement a) Source # 
Show a => Show (DisjointElement a) Source # 

data Disjoint a Source #

Constructors

Disjoint [DisjointElement a] 

Instances

Functor Disjoint Source # 

Methods

fmap :: (a -> b) -> Disjoint a -> Disjoint b #

(<$) :: a -> Disjoint b -> Disjoint a #

Foldable Disjoint Source # 

Methods

fold :: Monoid m => Disjoint m -> m #

foldMap :: Monoid m => (a -> m) -> Disjoint a -> m #

foldr :: (a -> b -> b) -> b -> Disjoint a -> b #

foldr' :: (a -> b -> b) -> b -> Disjoint a -> b #

foldl :: (b -> a -> b) -> b -> Disjoint a -> b #

foldl' :: (b -> a -> b) -> b -> Disjoint a -> b #

foldr1 :: (a -> a -> a) -> Disjoint a -> a #

foldl1 :: (a -> a -> a) -> Disjoint a -> a #

toList :: Disjoint a -> [a] #

null :: Disjoint a -> Bool #

length :: Disjoint a -> Int #

elem :: Eq a => a -> Disjoint a -> Bool #

maximum :: Ord a => Disjoint a -> a #

minimum :: Ord a => Disjoint a -> a #

sum :: Num a => Disjoint a -> a #

product :: Num a => Disjoint a -> a #

Traversable Disjoint Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Disjoint a -> f (Disjoint b) #

sequenceA :: Applicative f => Disjoint (f a) -> f (Disjoint a) #

mapM :: Monad m => (a -> m b) -> Disjoint a -> m (Disjoint b) #

sequence :: Monad m => Disjoint (m a) -> m (Disjoint a) #

Eq a => Eq (Disjoint a) Source # 

Methods

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

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

Ord a => Ord (Disjoint a) Source # 

Methods

compare :: Disjoint a -> Disjoint a -> Ordering #

(<) :: Disjoint a -> Disjoint a -> Bool #

(<=) :: Disjoint a -> Disjoint a -> Bool #

(>) :: Disjoint a -> Disjoint a -> Bool #

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

max :: Disjoint a -> Disjoint a -> Disjoint a #

min :: Disjoint a -> Disjoint a -> Disjoint a #

Show a => Show (Disjoint a) Source # 

Methods

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

show :: Disjoint a -> String #

showList :: [Disjoint a] -> ShowS #

data TheoryTermArray a Source #

Constructors

TheoryTermArray [TheoryTerm a] 

Instances

Functor TheoryTermArray Source # 

Methods

fmap :: (a -> b) -> TheoryTermArray a -> TheoryTermArray b #

(<$) :: a -> TheoryTermArray b -> TheoryTermArray a #

Foldable TheoryTermArray Source # 

Methods

fold :: Monoid m => TheoryTermArray m -> m #

foldMap :: Monoid m => (a -> m) -> TheoryTermArray a -> m #

foldr :: (a -> b -> b) -> b -> TheoryTermArray a -> b #

foldr' :: (a -> b -> b) -> b -> TheoryTermArray a -> b #

foldl :: (b -> a -> b) -> b -> TheoryTermArray a -> b #

foldl' :: (b -> a -> b) -> b -> TheoryTermArray a -> b #

foldr1 :: (a -> a -> a) -> TheoryTermArray a -> a #

foldl1 :: (a -> a -> a) -> TheoryTermArray a -> a #

toList :: TheoryTermArray a -> [a] #

null :: TheoryTermArray a -> Bool #

length :: TheoryTermArray a -> Int #

elem :: Eq a => a -> TheoryTermArray a -> Bool #

maximum :: Ord a => TheoryTermArray a -> a #

minimum :: Ord a => TheoryTermArray a -> a #

sum :: Num a => TheoryTermArray a -> a #

product :: Num a => TheoryTermArray a -> a #

Traversable TheoryTermArray Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TheoryTermArray a -> f (TheoryTermArray b) #

sequenceA :: Applicative f => TheoryTermArray (f a) -> f (TheoryTermArray a) #

mapM :: Monad m => (a -> m b) -> TheoryTermArray a -> m (TheoryTermArray b) #

sequence :: Monad m => TheoryTermArray (m a) -> m (TheoryTermArray a) #

Eq a => Eq (TheoryTermArray a) Source # 
Ord a => Ord (TheoryTermArray a) Source # 
Show a => Show (TheoryTermArray a) Source # 

data TheoryFunction a Source #

Constructors

TheoryFunction Text [TheoryTerm a] 

Instances

Functor TheoryFunction Source # 

Methods

fmap :: (a -> b) -> TheoryFunction a -> TheoryFunction b #

(<$) :: a -> TheoryFunction b -> TheoryFunction a #

Foldable TheoryFunction Source # 

Methods

fold :: Monoid m => TheoryFunction m -> m #

foldMap :: Monoid m => (a -> m) -> TheoryFunction a -> m #

foldr :: (a -> b -> b) -> b -> TheoryFunction a -> b #

foldr' :: (a -> b -> b) -> b -> TheoryFunction a -> b #

foldl :: (b -> a -> b) -> b -> TheoryFunction a -> b #

foldl' :: (b -> a -> b) -> b -> TheoryFunction a -> b #

foldr1 :: (a -> a -> a) -> TheoryFunction a -> a #

foldl1 :: (a -> a -> a) -> TheoryFunction a -> a #

toList :: TheoryFunction a -> [a] #

null :: TheoryFunction a -> Bool #

length :: TheoryFunction a -> Int #

elem :: Eq a => a -> TheoryFunction a -> Bool #

maximum :: Ord a => TheoryFunction a -> a #

minimum :: Ord a => TheoryFunction a -> a #

sum :: Num a => TheoryFunction a -> a #

product :: Num a => TheoryFunction a -> a #

Traversable TheoryFunction Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TheoryFunction a -> f (TheoryFunction b) #

sequenceA :: Applicative f => TheoryFunction (f a) -> f (TheoryFunction a) #

mapM :: Monad m => (a -> m b) -> TheoryFunction a -> m (TheoryFunction b) #

sequence :: Monad m => TheoryFunction (m a) -> m (TheoryFunction a) #

Eq a => Eq (TheoryFunction a) Source # 
Ord a => Ord (TheoryFunction a) Source # 
Show a => Show (TheoryFunction a) Source # 

data TheoryUnparsedTermElement a Source #

Instances

Functor TheoryUnparsedTermElement Source # 
Foldable TheoryUnparsedTermElement Source # 

Methods

fold :: Monoid m => TheoryUnparsedTermElement m -> m #

foldMap :: Monoid m => (a -> m) -> TheoryUnparsedTermElement a -> m #

foldr :: (a -> b -> b) -> b -> TheoryUnparsedTermElement a -> b #

foldr' :: (a -> b -> b) -> b -> TheoryUnparsedTermElement a -> b #

foldl :: (b -> a -> b) -> b -> TheoryUnparsedTermElement a -> b #

foldl' :: (b -> a -> b) -> b -> TheoryUnparsedTermElement a -> b #

foldr1 :: (a -> a -> a) -> TheoryUnparsedTermElement a -> a #

foldl1 :: (a -> a -> a) -> TheoryUnparsedTermElement a -> a #

toList :: TheoryUnparsedTermElement a -> [a] #

null :: TheoryUnparsedTermElement a -> Bool #

length :: TheoryUnparsedTermElement a -> Int #

elem :: Eq a => a -> TheoryUnparsedTermElement a -> Bool #

maximum :: Ord a => TheoryUnparsedTermElement a -> a #

minimum :: Ord a => TheoryUnparsedTermElement a -> a #

sum :: Num a => TheoryUnparsedTermElement a -> a #

product :: Num a => TheoryUnparsedTermElement a -> a #

Traversable TheoryUnparsedTermElement Source # 
Eq a => Eq (TheoryUnparsedTermElement a) Source # 
Ord a => Ord (TheoryUnparsedTermElement a) Source # 
Show a => Show (TheoryUnparsedTermElement a) Source # 

data TheoryUnparsedTerm a Source #

Instances

Functor TheoryUnparsedTerm Source # 
Foldable TheoryUnparsedTerm Source # 

Methods

fold :: Monoid m => TheoryUnparsedTerm m -> m #

foldMap :: Monoid m => (a -> m) -> TheoryUnparsedTerm a -> m #

foldr :: (a -> b -> b) -> b -> TheoryUnparsedTerm a -> b #

foldr' :: (a -> b -> b) -> b -> TheoryUnparsedTerm a -> b #

foldl :: (b -> a -> b) -> b -> TheoryUnparsedTerm a -> b #

foldl' :: (b -> a -> b) -> b -> TheoryUnparsedTerm a -> b #

foldr1 :: (a -> a -> a) -> TheoryUnparsedTerm a -> a #

foldl1 :: (a -> a -> a) -> TheoryUnparsedTerm a -> a #

toList :: TheoryUnparsedTerm a -> [a] #

null :: TheoryUnparsedTerm a -> Bool #

length :: TheoryUnparsedTerm a -> Int #

elem :: Eq a => a -> TheoryUnparsedTerm a -> Bool #

maximum :: Ord a => TheoryUnparsedTerm a -> a #

minimum :: Ord a => TheoryUnparsedTerm a -> a #

sum :: Num a => TheoryUnparsedTerm a -> a #

product :: Num a => TheoryUnparsedTerm a -> a #

Traversable TheoryUnparsedTerm Source # 
Eq a => Eq (TheoryUnparsedTerm a) Source # 
Ord a => Ord (TheoryUnparsedTerm a) Source # 
Show a => Show (TheoryUnparsedTerm a) Source # 

data TheoryTerm a Source #

Instances

Functor TheoryTerm Source # 

Methods

fmap :: (a -> b) -> TheoryTerm a -> TheoryTerm b #

(<$) :: a -> TheoryTerm b -> TheoryTerm a #

Foldable TheoryTerm Source # 

Methods

fold :: Monoid m => TheoryTerm m -> m #

foldMap :: Monoid m => (a -> m) -> TheoryTerm a -> m #

foldr :: (a -> b -> b) -> b -> TheoryTerm a -> b #

foldr' :: (a -> b -> b) -> b -> TheoryTerm a -> b #

foldl :: (b -> a -> b) -> b -> TheoryTerm a -> b #

foldl' :: (b -> a -> b) -> b -> TheoryTerm a -> b #

foldr1 :: (a -> a -> a) -> TheoryTerm a -> a #

foldl1 :: (a -> a -> a) -> TheoryTerm a -> a #

toList :: TheoryTerm a -> [a] #

null :: TheoryTerm a -> Bool #

length :: TheoryTerm a -> Int #

elem :: Eq a => a -> TheoryTerm a -> Bool #

maximum :: Ord a => TheoryTerm a -> a #

minimum :: Ord a => TheoryTerm a -> a #

sum :: Num a => TheoryTerm a -> a #

product :: Num a => TheoryTerm a -> a #

Traversable TheoryTerm Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TheoryTerm a -> f (TheoryTerm b) #

sequenceA :: Applicative f => TheoryTerm (f a) -> f (TheoryTerm a) #

mapM :: Monad m => (a -> m b) -> TheoryTerm a -> m (TheoryTerm b) #

sequence :: Monad m => TheoryTerm (m a) -> m (TheoryTerm a) #

Eq a => Eq (TheoryTerm a) Source # 

Methods

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

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

Ord a => Ord (TheoryTerm a) Source # 
Show a => Show (TheoryTerm a) Source # 

data TheoryAtomElement a Source #

Constructors

TheoryAtomElement [TheoryTerm a] [Literal a] 

Instances

Functor TheoryAtomElement Source # 
Foldable TheoryAtomElement Source # 

Methods

fold :: Monoid m => TheoryAtomElement m -> m #

foldMap :: Monoid m => (a -> m) -> TheoryAtomElement a -> m #

foldr :: (a -> b -> b) -> b -> TheoryAtomElement a -> b #

foldr' :: (a -> b -> b) -> b -> TheoryAtomElement a -> b #

foldl :: (b -> a -> b) -> b -> TheoryAtomElement a -> b #

foldl' :: (b -> a -> b) -> b -> TheoryAtomElement a -> b #

foldr1 :: (a -> a -> a) -> TheoryAtomElement a -> a #

foldl1 :: (a -> a -> a) -> TheoryAtomElement a -> a #

toList :: TheoryAtomElement a -> [a] #

null :: TheoryAtomElement a -> Bool #

length :: TheoryAtomElement a -> Int #

elem :: Eq a => a -> TheoryAtomElement a -> Bool #

maximum :: Ord a => TheoryAtomElement a -> a #

minimum :: Ord a => TheoryAtomElement a -> a #

sum :: Num a => TheoryAtomElement a -> a #

product :: Num a => TheoryAtomElement a -> a #

Traversable TheoryAtomElement Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TheoryAtomElement a -> f (TheoryAtomElement b) #

sequenceA :: Applicative f => TheoryAtomElement (f a) -> f (TheoryAtomElement a) #

mapM :: Monad m => (a -> m b) -> TheoryAtomElement a -> m (TheoryAtomElement b) #

sequence :: Monad m => TheoryAtomElement (m a) -> m (TheoryAtomElement a) #

Eq a => Eq (TheoryAtomElement a) Source # 
Ord a => Ord (TheoryAtomElement a) Source # 
Show a => Show (TheoryAtomElement a) Source # 

data TheoryGuard a Source #

Constructors

TheoryGuard Text (TheoryTerm a) 

Instances

Functor TheoryGuard Source # 

Methods

fmap :: (a -> b) -> TheoryGuard a -> TheoryGuard b #

(<$) :: a -> TheoryGuard b -> TheoryGuard a #

Foldable TheoryGuard Source # 

Methods

fold :: Monoid m => TheoryGuard m -> m #

foldMap :: Monoid m => (a -> m) -> TheoryGuard a -> m #

foldr :: (a -> b -> b) -> b -> TheoryGuard a -> b #

foldr' :: (a -> b -> b) -> b -> TheoryGuard a -> b #

foldl :: (b -> a -> b) -> b -> TheoryGuard a -> b #

foldl' :: (b -> a -> b) -> b -> TheoryGuard a -> b #

foldr1 :: (a -> a -> a) -> TheoryGuard a -> a #

foldl1 :: (a -> a -> a) -> TheoryGuard a -> a #

toList :: TheoryGuard a -> [a] #

null :: TheoryGuard a -> Bool #

length :: TheoryGuard a -> Int #

elem :: Eq a => a -> TheoryGuard a -> Bool #

maximum :: Ord a => TheoryGuard a -> a #

minimum :: Ord a => TheoryGuard a -> a #

sum :: Num a => TheoryGuard a -> a #

product :: Num a => TheoryGuard a -> a #

Traversable TheoryGuard Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TheoryGuard a -> f (TheoryGuard b) #

sequenceA :: Applicative f => TheoryGuard (f a) -> f (TheoryGuard a) #

mapM :: Monad m => (a -> m b) -> TheoryGuard a -> m (TheoryGuard b) #

sequence :: Monad m => TheoryGuard (m a) -> m (TheoryGuard a) #

Eq a => Eq (TheoryGuard a) Source # 
Ord a => Ord (TheoryGuard a) Source # 
Show a => Show (TheoryGuard a) Source # 

data TheoryAtom a Source #

Constructors

TheoryAtom (Term a) [TheoryAtomElement a] (TheoryGuard a) 

Instances

Functor TheoryAtom Source # 

Methods

fmap :: (a -> b) -> TheoryAtom a -> TheoryAtom b #

(<$) :: a -> TheoryAtom b -> TheoryAtom a #

Foldable TheoryAtom Source # 

Methods

fold :: Monoid m => TheoryAtom m -> m #

foldMap :: Monoid m => (a -> m) -> TheoryAtom a -> m #

foldr :: (a -> b -> b) -> b -> TheoryAtom a -> b #

foldr' :: (a -> b -> b) -> b -> TheoryAtom a -> b #

foldl :: (b -> a -> b) -> b -> TheoryAtom a -> b #

foldl' :: (b -> a -> b) -> b -> TheoryAtom a -> b #

foldr1 :: (a -> a -> a) -> TheoryAtom a -> a #

foldl1 :: (a -> a -> a) -> TheoryAtom a -> a #

toList :: TheoryAtom a -> [a] #

null :: TheoryAtom a -> Bool #

length :: TheoryAtom a -> Int #

elem :: Eq a => a -> TheoryAtom a -> Bool #

maximum :: Ord a => TheoryAtom a -> a #

minimum :: Ord a => TheoryAtom a -> a #

sum :: Num a => TheoryAtom a -> a #

product :: Num a => TheoryAtom a -> a #

Traversable TheoryAtom Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TheoryAtom a -> f (TheoryAtom b) #

sequenceA :: Applicative f => TheoryAtom (f a) -> f (TheoryAtom a) #

mapM :: Monad m => (a -> m b) -> TheoryAtom a -> m (TheoryAtom b) #

sequence :: Monad m => TheoryAtom (m a) -> m (TheoryAtom a) #

Eq a => Eq (TheoryAtom a) Source # 

Methods

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

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

Ord a => Ord (TheoryAtom a) Source # 
Show a => Show (TheoryAtom a) Source # 

data HeadLiteral a Source #

Instances

Functor HeadLiteral Source # 

Methods

fmap :: (a -> b) -> HeadLiteral a -> HeadLiteral b #

(<$) :: a -> HeadLiteral b -> HeadLiteral a #

Foldable HeadLiteral Source # 

Methods

fold :: Monoid m => HeadLiteral m -> m #

foldMap :: Monoid m => (a -> m) -> HeadLiteral a -> m #

foldr :: (a -> b -> b) -> b -> HeadLiteral a -> b #

foldr' :: (a -> b -> b) -> b -> HeadLiteral a -> b #

foldl :: (b -> a -> b) -> b -> HeadLiteral a -> b #

foldl' :: (b -> a -> b) -> b -> HeadLiteral a -> b #

foldr1 :: (a -> a -> a) -> HeadLiteral a -> a #

foldl1 :: (a -> a -> a) -> HeadLiteral a -> a #

toList :: HeadLiteral a -> [a] #

null :: HeadLiteral a -> Bool #

length :: HeadLiteral a -> Int #

elem :: Eq a => a -> HeadLiteral a -> Bool #

maximum :: Ord a => HeadLiteral a -> a #

minimum :: Ord a => HeadLiteral a -> a #

sum :: Num a => HeadLiteral a -> a #

product :: Num a => HeadLiteral a -> a #

Traversable HeadLiteral Source # 

Methods

traverse :: Applicative f => (a -> f b) -> HeadLiteral a -> f (HeadLiteral b) #

sequenceA :: Applicative f => HeadLiteral (f a) -> f (HeadLiteral a) #

mapM :: Monad m => (a -> m b) -> HeadLiteral a -> m (HeadLiteral b) #

sequence :: Monad m => HeadLiteral (m a) -> m (HeadLiteral a) #

Eq a => Eq (HeadLiteral a) Source # 
Ord a => Ord (HeadLiteral a) Source # 
Show a => Show (HeadLiteral a) Source # 
Pretty a => Pretty (HeadLiteral a) Source # 

Methods

pretty :: HeadLiteral a -> Doc #

prettyList :: [HeadLiteral a] -> Doc #

data BodyLiteral a Source #

Instances

Functor BodyLiteral Source # 

Methods

fmap :: (a -> b) -> BodyLiteral a -> BodyLiteral b #

(<$) :: a -> BodyLiteral b -> BodyLiteral a #

Foldable BodyLiteral Source # 

Methods

fold :: Monoid m => BodyLiteral m -> m #

foldMap :: Monoid m => (a -> m) -> BodyLiteral a -> m #

foldr :: (a -> b -> b) -> b -> BodyLiteral a -> b #

foldr' :: (a -> b -> b) -> b -> BodyLiteral a -> b #

foldl :: (b -> a -> b) -> b -> BodyLiteral a -> b #

foldl' :: (b -> a -> b) -> b -> BodyLiteral a -> b #

foldr1 :: (a -> a -> a) -> BodyLiteral a -> a #

foldl1 :: (a -> a -> a) -> BodyLiteral a -> a #

toList :: BodyLiteral a -> [a] #

null :: BodyLiteral a -> Bool #

length :: BodyLiteral a -> Int #

elem :: Eq a => a -> BodyLiteral a -> Bool #

maximum :: Ord a => BodyLiteral a -> a #

minimum :: Ord a => BodyLiteral a -> a #

sum :: Num a => BodyLiteral a -> a #

product :: Num a => BodyLiteral a -> a #

Traversable BodyLiteral Source # 

Methods

traverse :: Applicative f => (a -> f b) -> BodyLiteral a -> f (BodyLiteral b) #

sequenceA :: Applicative f => BodyLiteral (f a) -> f (BodyLiteral a) #

mapM :: Monad m => (a -> m b) -> BodyLiteral a -> m (BodyLiteral b) #

sequence :: Monad m => BodyLiteral (m a) -> m (BodyLiteral a) #

Eq a => Eq (BodyLiteral a) Source # 
Ord a => Ord (BodyLiteral a) Source # 
Show a => Show (BodyLiteral a) Source # 
Pretty a => Pretty (BodyLiteral a) Source # 

Methods

pretty :: BodyLiteral a -> Doc #

prettyList :: [BodyLiteral a] -> Doc #

data Rule a Source #

Constructors

Rule (HeadLiteral a) [BodyLiteral a] 

Instances

Functor Rule Source # 

Methods

fmap :: (a -> b) -> Rule a -> Rule b #

(<$) :: a -> Rule b -> Rule a #

Foldable Rule Source # 

Methods

fold :: Monoid m => Rule m -> m #

foldMap :: Monoid m => (a -> m) -> Rule a -> m #

foldr :: (a -> b -> b) -> b -> Rule a -> b #

foldr' :: (a -> b -> b) -> b -> Rule a -> b #

foldl :: (b -> a -> b) -> b -> Rule a -> b #

foldl' :: (b -> a -> b) -> b -> Rule a -> b #

foldr1 :: (a -> a -> a) -> Rule a -> a #

foldl1 :: (a -> a -> a) -> Rule a -> a #

toList :: Rule a -> [a] #

null :: Rule a -> Bool #

length :: Rule a -> Int #

elem :: Eq a => a -> Rule a -> Bool #

maximum :: Ord a => Rule a -> a #

minimum :: Ord a => Rule a -> a #

sum :: Num a => Rule a -> a #

product :: Num a => Rule a -> a #

Traversable Rule Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Rule a -> f (Rule b) #

sequenceA :: Applicative f => Rule (f a) -> f (Rule a) #

mapM :: Monad m => (a -> m b) -> Rule a -> m (Rule b) #

sequence :: Monad m => Rule (m a) -> m (Rule a) #

Eq a => Eq (Rule a) Source # 

Methods

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

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

Ord a => Ord (Rule a) Source # 

Methods

compare :: Rule a -> Rule a -> Ordering #

(<) :: Rule a -> Rule a -> Bool #

(<=) :: Rule a -> Rule a -> Bool #

(>) :: Rule a -> Rule a -> Bool #

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

max :: Rule a -> Rule a -> Rule a #

min :: Rule a -> Rule a -> Rule a #

Show a => Show (Rule a) Source # 

Methods

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

show :: Rule a -> String #

showList :: [Rule a] -> ShowS #

Pretty a => Pretty (Rule a) Source # 

Methods

pretty :: Rule a -> Doc #

prettyList :: [Rule a] -> Doc #

data Definition a Source #

Constructors

Definition Text (Term a) Bool 

Instances

Functor Definition Source # 

Methods

fmap :: (a -> b) -> Definition a -> Definition b #

(<$) :: a -> Definition b -> Definition a #

Foldable Definition Source # 

Methods

fold :: Monoid m => Definition m -> m #

foldMap :: Monoid m => (a -> m) -> Definition a -> m #

foldr :: (a -> b -> b) -> b -> Definition a -> b #

foldr' :: (a -> b -> b) -> b -> Definition a -> b #

foldl :: (b -> a -> b) -> b -> Definition a -> b #

foldl' :: (b -> a -> b) -> b -> Definition a -> b #

foldr1 :: (a -> a -> a) -> Definition a -> a #

foldl1 :: (a -> a -> a) -> Definition a -> a #

toList :: Definition a -> [a] #

null :: Definition a -> Bool #

length :: Definition a -> Int #

elem :: Eq a => a -> Definition a -> Bool #

maximum :: Ord a => Definition a -> a #

minimum :: Ord a => Definition a -> a #

sum :: Num a => Definition a -> a #

product :: Num a => Definition a -> a #

Traversable Definition Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Definition a -> f (Definition b) #

sequenceA :: Applicative f => Definition (f a) -> f (Definition a) #

mapM :: Monad m => (a -> m b) -> Definition a -> m (Definition b) #

sequence :: Monad m => Definition (m a) -> m (Definition a) #

Eq a => Eq (Definition a) Source # 

Methods

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

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

Ord a => Ord (Definition a) Source # 
Show a => Show (Definition a) Source # 

data ShowSignature b Source #

Constructors

ShowSignature b Bool 

Instances

Functor ShowSignature Source # 

Methods

fmap :: (a -> b) -> ShowSignature a -> ShowSignature b #

(<$) :: a -> ShowSignature b -> ShowSignature a #

Foldable ShowSignature Source # 

Methods

fold :: Monoid m => ShowSignature m -> m #

foldMap :: Monoid m => (a -> m) -> ShowSignature a -> m #

foldr :: (a -> b -> b) -> b -> ShowSignature a -> b #

foldr' :: (a -> b -> b) -> b -> ShowSignature a -> b #

foldl :: (b -> a -> b) -> b -> ShowSignature a -> b #

foldl' :: (b -> a -> b) -> b -> ShowSignature a -> b #

foldr1 :: (a -> a -> a) -> ShowSignature a -> a #

foldl1 :: (a -> a -> a) -> ShowSignature a -> a #

toList :: ShowSignature a -> [a] #

null :: ShowSignature a -> Bool #

length :: ShowSignature a -> Int #

elem :: Eq a => a -> ShowSignature a -> Bool #

maximum :: Ord a => ShowSignature a -> a #

minimum :: Ord a => ShowSignature a -> a #

sum :: Num a => ShowSignature a -> a #

product :: Num a => ShowSignature a -> a #

Traversable ShowSignature Source # 

Methods

traverse :: Applicative f => (a -> f b) -> ShowSignature a -> f (ShowSignature b) #

sequenceA :: Applicative f => ShowSignature (f a) -> f (ShowSignature a) #

mapM :: Monad m => (a -> m b) -> ShowSignature a -> m (ShowSignature b) #

sequence :: Monad m => ShowSignature (m a) -> m (ShowSignature a) #

Eq b => Eq (ShowSignature b) Source # 
Ord b => Ord (ShowSignature b) Source # 
Show b => Show (ShowSignature b) Source # 

data ShowTerm a Source #

Constructors

ShowTerm (Term a) [BodyLiteral a] Bool 

Instances

Functor ShowTerm Source # 

Methods

fmap :: (a -> b) -> ShowTerm a -> ShowTerm b #

(<$) :: a -> ShowTerm b -> ShowTerm a #

Foldable ShowTerm Source # 

Methods

fold :: Monoid m => ShowTerm m -> m #

foldMap :: Monoid m => (a -> m) -> ShowTerm a -> m #

foldr :: (a -> b -> b) -> b -> ShowTerm a -> b #

foldr' :: (a -> b -> b) -> b -> ShowTerm a -> b #

foldl :: (b -> a -> b) -> b -> ShowTerm a -> b #

foldl' :: (b -> a -> b) -> b -> ShowTerm a -> b #

foldr1 :: (a -> a -> a) -> ShowTerm a -> a #

foldl1 :: (a -> a -> a) -> ShowTerm a -> a #

toList :: ShowTerm a -> [a] #

null :: ShowTerm a -> Bool #

length :: ShowTerm a -> Int #

elem :: Eq a => a -> ShowTerm a -> Bool #

maximum :: Ord a => ShowTerm a -> a #

minimum :: Ord a => ShowTerm a -> a #

sum :: Num a => ShowTerm a -> a #

product :: Num a => ShowTerm a -> a #

Traversable ShowTerm Source # 

Methods

traverse :: Applicative f => (a -> f b) -> ShowTerm a -> f (ShowTerm b) #

sequenceA :: Applicative f => ShowTerm (f a) -> f (ShowTerm a) #

mapM :: Monad m => (a -> m b) -> ShowTerm a -> m (ShowTerm b) #

sequence :: Monad m => ShowTerm (m a) -> m (ShowTerm a) #

Eq a => Eq (ShowTerm a) Source # 

Methods

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

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

Ord a => Ord (ShowTerm a) Source # 

Methods

compare :: ShowTerm a -> ShowTerm a -> Ordering #

(<) :: ShowTerm a -> ShowTerm a -> Bool #

(<=) :: ShowTerm a -> ShowTerm a -> Bool #

(>) :: ShowTerm a -> ShowTerm a -> Bool #

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

max :: ShowTerm a -> ShowTerm a -> ShowTerm a #

min :: ShowTerm a -> ShowTerm a -> ShowTerm a #

Show a => Show (ShowTerm a) Source # 

Methods

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

show :: ShowTerm a -> String #

showList :: [ShowTerm a] -> ShowS #

data Minimize a Source #

Constructors

Minimize (Term a) (Term a) [Term a] [BodyLiteral a] 

Instances

Functor Minimize Source # 

Methods

fmap :: (a -> b) -> Minimize a -> Minimize b #

(<$) :: a -> Minimize b -> Minimize a #

Foldable Minimize Source # 

Methods

fold :: Monoid m => Minimize m -> m #

foldMap :: Monoid m => (a -> m) -> Minimize a -> m #

foldr :: (a -> b -> b) -> b -> Minimize a -> b #

foldr' :: (a -> b -> b) -> b -> Minimize a -> b #

foldl :: (b -> a -> b) -> b -> Minimize a -> b #

foldl' :: (b -> a -> b) -> b -> Minimize a -> b #

foldr1 :: (a -> a -> a) -> Minimize a -> a #

foldl1 :: (a -> a -> a) -> Minimize a -> a #

toList :: Minimize a -> [a] #

null :: Minimize a -> Bool #

length :: Minimize a -> Int #

elem :: Eq a => a -> Minimize a -> Bool #

maximum :: Ord a => Minimize a -> a #

minimum :: Ord a => Minimize a -> a #

sum :: Num a => Minimize a -> a #

product :: Num a => Minimize a -> a #

Traversable Minimize Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Minimize a -> f (Minimize b) #

sequenceA :: Applicative f => Minimize (f a) -> f (Minimize a) #

mapM :: Monad m => (a -> m b) -> Minimize a -> m (Minimize b) #

sequence :: Monad m => Minimize (m a) -> m (Minimize a) #

Eq a => Eq (Minimize a) Source # 

Methods

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

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

Ord a => Ord (Minimize a) Source # 

Methods

compare :: Minimize a -> Minimize a -> Ordering #

(<) :: Minimize a -> Minimize a -> Bool #

(<=) :: Minimize a -> Minimize a -> Bool #

(>) :: Minimize a -> Minimize a -> Bool #

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

max :: Minimize a -> Minimize a -> Minimize a #

min :: Minimize a -> Minimize a -> Minimize a #

Show a => Show (Minimize a) Source # 

Methods

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

show :: Minimize a -> String #

showList :: [Minimize a] -> ShowS #

data External a Source #

Constructors

External (Term a) [BodyLiteral a] 

Instances

Functor External Source # 

Methods

fmap :: (a -> b) -> External a -> External b #

(<$) :: a -> External b -> External a #

Foldable External Source # 

Methods

fold :: Monoid m => External m -> m #

foldMap :: Monoid m => (a -> m) -> External a -> m #

foldr :: (a -> b -> b) -> b -> External a -> b #

foldr' :: (a -> b -> b) -> b -> External a -> b #

foldl :: (b -> a -> b) -> b -> External a -> b #

foldl' :: (b -> a -> b) -> b -> External a -> b #

foldr1 :: (a -> a -> a) -> External a -> a #

foldl1 :: (a -> a -> a) -> External a -> a #

toList :: External a -> [a] #

null :: External a -> Bool #

length :: External a -> Int #

elem :: Eq a => a -> External a -> Bool #

maximum :: Ord a => External a -> a #

minimum :: Ord a => External a -> a #

sum :: Num a => External a -> a #

product :: Num a => External a -> a #

Traversable External Source # 

Methods

traverse :: Applicative f => (a -> f b) -> External a -> f (External b) #

sequenceA :: Applicative f => External (f a) -> f (External a) #

mapM :: Monad m => (a -> m b) -> External a -> m (External b) #

sequence :: Monad m => External (m a) -> m (External a) #

Eq a => Eq (External a) Source # 

Methods

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

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

Ord a => Ord (External a) Source # 

Methods

compare :: External a -> External a -> Ordering #

(<) :: External a -> External a -> Bool #

(<=) :: External a -> External a -> Bool #

(>) :: External a -> External a -> Bool #

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

max :: External a -> External a -> External a #

min :: External a -> External a -> External a #

Show a => Show (External a) Source # 

Methods

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

show :: External a -> String #

showList :: [External a] -> ShowS #

Pretty a => Pretty (External a) Source # 

Methods

pretty :: External a -> Doc #

prettyList :: [External a] -> Doc #

data Edge a Source #

Constructors

Edge (Term a) (Term a) [BodyLiteral a] 

Instances

Functor Edge Source # 

Methods

fmap :: (a -> b) -> Edge a -> Edge b #

(<$) :: a -> Edge b -> Edge a #

Foldable Edge Source # 

Methods

fold :: Monoid m => Edge m -> m #

foldMap :: Monoid m => (a -> m) -> Edge a -> m #

foldr :: (a -> b -> b) -> b -> Edge a -> b #

foldr' :: (a -> b -> b) -> b -> Edge a -> b #

foldl :: (b -> a -> b) -> b -> Edge a -> b #

foldl' :: (b -> a -> b) -> b -> Edge a -> b #

foldr1 :: (a -> a -> a) -> Edge a -> a #

foldl1 :: (a -> a -> a) -> Edge a -> a #

toList :: Edge a -> [a] #

null :: Edge a -> Bool #

length :: Edge a -> Int #

elem :: Eq a => a -> Edge a -> Bool #

maximum :: Ord a => Edge a -> a #

minimum :: Ord a => Edge a -> a #

sum :: Num a => Edge a -> a #

product :: Num a => Edge a -> a #

Traversable Edge Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Edge a -> f (Edge b) #

sequenceA :: Applicative f => Edge (f a) -> f (Edge a) #

mapM :: Monad m => (a -> m b) -> Edge a -> m (Edge b) #

sequence :: Monad m => Edge (m a) -> m (Edge a) #

Eq a => Eq (Edge a) Source # 

Methods

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

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

Ord a => Ord (Edge a) Source # 

Methods

compare :: Edge a -> Edge a -> Ordering #

(<) :: Edge a -> Edge a -> Bool #

(<=) :: Edge a -> Edge a -> Bool #

(>) :: Edge a -> Edge a -> Bool #

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

max :: Edge a -> Edge a -> Edge a #

min :: Edge a -> Edge a -> Edge a #

Show a => Show (Edge a) Source # 

Methods

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

show :: Edge a -> String #

showList :: [Edge a] -> ShowS #

data Heuristic a Source #

Constructors

Heuristic (Term a) [BodyLiteral a] (Term a) (Term a) (Term a) 

Instances

Functor Heuristic Source # 

Methods

fmap :: (a -> b) -> Heuristic a -> Heuristic b #

(<$) :: a -> Heuristic b -> Heuristic a #

Foldable Heuristic Source # 

Methods

fold :: Monoid m => Heuristic m -> m #

foldMap :: Monoid m => (a -> m) -> Heuristic a -> m #

foldr :: (a -> b -> b) -> b -> Heuristic a -> b #

foldr' :: (a -> b -> b) -> b -> Heuristic a -> b #

foldl :: (b -> a -> b) -> b -> Heuristic a -> b #

foldl' :: (b -> a -> b) -> b -> Heuristic a -> b #

foldr1 :: (a -> a -> a) -> Heuristic a -> a #

foldl1 :: (a -> a -> a) -> Heuristic a -> a #

toList :: Heuristic a -> [a] #

null :: Heuristic a -> Bool #

length :: Heuristic a -> Int #

elem :: Eq a => a -> Heuristic a -> Bool #

maximum :: Ord a => Heuristic a -> a #

minimum :: Ord a => Heuristic a -> a #

sum :: Num a => Heuristic a -> a #

product :: Num a => Heuristic a -> a #

Traversable Heuristic Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Heuristic a -> f (Heuristic b) #

sequenceA :: Applicative f => Heuristic (f a) -> f (Heuristic a) #

mapM :: Monad m => (a -> m b) -> Heuristic a -> m (Heuristic b) #

sequence :: Monad m => Heuristic (m a) -> m (Heuristic a) #

Eq a => Eq (Heuristic a) Source # 

Methods

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

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

Ord a => Ord (Heuristic a) Source # 
Show a => Show (Heuristic a) Source # 
Pretty a => Pretty (Heuristic a) Source # 

Methods

pretty :: Heuristic a -> Doc #

prettyList :: [Heuristic a] -> Doc #

data Project a Source #

Constructors

Project (Term a) [BodyLiteral a] 

Instances

Functor Project Source # 

Methods

fmap :: (a -> b) -> Project a -> Project b #

(<$) :: a -> Project b -> Project a #

Foldable Project Source # 

Methods

fold :: Monoid m => Project m -> m #

foldMap :: Monoid m => (a -> m) -> Project a -> m #

foldr :: (a -> b -> b) -> b -> Project a -> b #

foldr' :: (a -> b -> b) -> b -> Project a -> b #

foldl :: (b -> a -> b) -> b -> Project a -> b #

foldl' :: (b -> a -> b) -> b -> Project a -> b #

foldr1 :: (a -> a -> a) -> Project a -> a #

foldl1 :: (a -> a -> a) -> Project a -> a #

toList :: Project a -> [a] #

null :: Project a -> Bool #

length :: Project a -> Int #

elem :: Eq a => a -> Project a -> Bool #

maximum :: Ord a => Project a -> a #

minimum :: Ord a => Project a -> a #

sum :: Num a => Project a -> a #

product :: Num a => Project a -> a #

Traversable Project Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Project a -> f (Project b) #

sequenceA :: Applicative f => Project (f a) -> f (Project a) #

mapM :: Monad m => (a -> m b) -> Project a -> m (Project b) #

sequence :: Monad m => Project (m a) -> m (Project a) #

Eq a => Eq (Project a) Source # 

Methods

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

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

Ord a => Ord (Project a) Source # 

Methods

compare :: Project a -> Project a -> Ordering #

(<) :: Project a -> Project a -> Bool #

(<=) :: Project a -> Project a -> Bool #

(>) :: Project a -> Project a -> Bool #

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

max :: Project a -> Project a -> Project a #

min :: Project a -> Project a -> Project a #

Show a => Show (Project a) Source # 

Methods

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

show :: Project a -> String #

showList :: [Project a] -> ShowS #

data Statement a b Source #

Instances

Bifunctor Statement Source # 

Methods

bimap :: (a -> b) -> (c -> d) -> Statement a c -> Statement b d #

first :: (a -> b) -> Statement a c -> Statement b c #

second :: (b -> c) -> Statement a b -> Statement a c #

Bitraversable Statement Source # 

Methods

bitraverse :: Applicative f => (a -> f c) -> (b -> f d) -> Statement a b -> f (Statement c d) #

Bifoldable Statement Source # 

Methods

bifold :: Monoid m => Statement m m -> m #

bifoldMap :: Monoid m => (a -> m) -> (b -> m) -> Statement a b -> m #

bifoldr :: (a -> c -> c) -> (b -> c -> c) -> c -> Statement a b -> c #

bifoldl :: (c -> a -> c) -> (c -> b -> c) -> c -> Statement a b -> c #

Functor (Statement a) Source # 

Methods

fmap :: (a -> b) -> Statement a a -> Statement a b #

(<$) :: a -> Statement a b -> Statement a a #

Foldable (Statement a) Source # 

Methods

fold :: Monoid m => Statement a m -> m #

foldMap :: Monoid m => (a -> m) -> Statement a a -> m #

foldr :: (a -> b -> b) -> b -> Statement a a -> b #

foldr' :: (a -> b -> b) -> b -> Statement a a -> b #

foldl :: (b -> a -> b) -> b -> Statement a a -> b #

foldl' :: (b -> a -> b) -> b -> Statement a a -> b #

foldr1 :: (a -> a -> a) -> Statement a a -> a #

foldl1 :: (a -> a -> a) -> Statement a a -> a #

toList :: Statement a a -> [a] #

null :: Statement a a -> Bool #

length :: Statement a a -> Int #

elem :: Eq a => a -> Statement a a -> Bool #

maximum :: Ord a => Statement a a -> a #

minimum :: Ord a => Statement a a -> a #

sum :: Num a => Statement a a -> a #

product :: Num a => Statement a a -> a #

Traversable (Statement a) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Statement a a -> f (Statement a b) #

sequenceA :: Applicative f => Statement a (f a) -> f (Statement a a) #

mapM :: Monad m => (a -> m b) -> Statement a a -> m (Statement a b) #

sequence :: Monad m => Statement a (m a) -> m (Statement a a) #

(Eq b, Eq a) => Eq (Statement a b) Source # 

Methods

(==) :: Statement a b -> Statement a b -> Bool #

(/=) :: Statement a b -> Statement a b -> Bool #

(Ord b, Ord a) => Ord (Statement a b) Source # 

Methods

compare :: Statement a b -> Statement a b -> Ordering #

(<) :: Statement a b -> Statement a b -> Bool #

(<=) :: Statement a b -> Statement a b -> Bool #

(>) :: Statement a b -> Statement a b -> Bool #

(>=) :: Statement a b -> Statement a b -> Bool #

max :: Statement a b -> Statement a b -> Statement a b #

min :: Statement a b -> Statement a b -> Statement a b #

(Show b, Show a) => Show (Statement a b) Source # 

Methods

showsPrec :: Int -> Statement a b -> ShowS #

show :: Statement a b -> String #

showList :: [Statement a b] -> ShowS #

(Pretty a, Pretty b) => Pretty (Statement a b) Source # 

Methods

pretty :: Statement a b -> Doc #

prettyList :: [Statement a b] -> Doc #