clingo-0.2.0.0: Haskell bindings to the Clingo ASP solver

Safe HaskellNone
LanguageHaskell2010

Clingo.Internal.Types

Synopsis

Documentation

newtype IOSym s a Source #

A monad that serves as witness that data registered with a running solver still exists and can be used.

Constructors

IOSym 

Fields

Instances

MonadSymbol IOSym Source # 
MonadModel IOSym Source # 
MonadSolve IOSym Source # 
Monad (IOSym s) Source # 

Methods

(>>=) :: IOSym s a -> (a -> IOSym s b) -> IOSym s b #

(>>) :: IOSym s a -> IOSym s b -> IOSym s b #

return :: a -> IOSym s a #

fail :: String -> IOSym s a #

Functor (IOSym s) Source # 

Methods

fmap :: (a -> b) -> IOSym s a -> IOSym s b #

(<$) :: a -> IOSym s b -> IOSym s a #

MonadFix (IOSym s) Source # 

Methods

mfix :: (a -> IOSym s a) -> IOSym s a #

Applicative (IOSym s) Source # 

Methods

pure :: a -> IOSym s a #

(<*>) :: IOSym s (a -> b) -> IOSym s a -> IOSym s b #

(*>) :: IOSym s a -> IOSym s b -> IOSym s b #

(<*) :: IOSym s a -> IOSym s b -> IOSym s a #

MonadIO (IOSym s) Source # 

Methods

liftIO :: IO a -> IOSym s a #

Alternative (IOSym s) Source # 

Methods

empty :: IOSym s a #

(<|>) :: IOSym s a -> IOSym s a -> IOSym s a #

some :: IOSym s a -> IOSym s [a] #

many :: IOSym s a -> IOSym s [a] #

MonadPlus (IOSym s) Source # 

Methods

mzero :: IOSym s a #

mplus :: IOSym s a -> IOSym s a -> IOSym s a #

MonadThrow (IOSym s) Source # 

Methods

throwM :: Exception e => e -> IOSym s a #

MonadCatch (IOSym s) Source # 

Methods

catch :: Exception e => IOSym s a -> (e -> IOSym s a) -> IOSym s a #

MonadMask (IOSym s) Source # 

Methods

mask :: ((forall a. IOSym s a -> IOSym s a) -> IOSym s b) -> IOSym s b #

uninterruptibleMask :: ((forall a. IOSym s a -> IOSym s a) -> IOSym s b) -> IOSym s b #

newtype Clingo s a Source #

The Clingo monad provides a base monad for computations utilizing the clingo answer set solver. It uses an additional type parameter to ensure that values that are managed by the solver can not leave scope.

Constructors

Clingo 

Fields

Instances

MonadSymbol Clingo Source # 
MonadModel Clingo Source # 
MonadSolve Clingo Source # 
Monad (Clingo s) Source # 

Methods

(>>=) :: Clingo s a -> (a -> Clingo s b) -> Clingo s b #

(>>) :: Clingo s a -> Clingo s b -> Clingo s b #

return :: a -> Clingo s a #

fail :: String -> Clingo s a #

Functor (Clingo s) Source # 

Methods

fmap :: (a -> b) -> Clingo s a -> Clingo s b #

(<$) :: a -> Clingo s b -> Clingo s a #

MonadFix (Clingo s) Source # 

Methods

mfix :: (a -> Clingo s a) -> Clingo s a #

Applicative (Clingo s) Source # 

Methods

pure :: a -> Clingo s a #

(<*>) :: Clingo s (a -> b) -> Clingo s a -> Clingo s b #

(*>) :: Clingo s a -> Clingo s b -> Clingo s b #

(<*) :: Clingo s a -> Clingo s b -> Clingo s a #

MonadIO (Clingo s) Source # 

Methods

liftIO :: IO a -> Clingo s a #

Alternative (Clingo s) Source # 

Methods

empty :: Clingo s a #

(<|>) :: Clingo s a -> Clingo s a -> Clingo s a #

some :: Clingo s a -> Clingo s [a] #

many :: Clingo s a -> Clingo s [a] #

MonadPlus (Clingo s) Source # 

Methods

mzero :: Clingo s a #

mplus :: Clingo s a -> Clingo s a -> Clingo s a #

MonadThrow (Clingo s) Source # 

Methods

throwM :: Exception e => e -> Clingo s a #

MonadCatch (Clingo s) Source # 

Methods

catch :: Exception e => Clingo s a -> (e -> Clingo s a) -> Clingo s a #

MonadMask (Clingo s) Source # 

Methods

mask :: ((forall a. Clingo s a -> Clingo s a) -> Clingo s b) -> Clingo s b #

uninterruptibleMask :: ((forall a. Clingo s a -> Clingo s a) -> Clingo s b) -> Clingo s b #

runClingo :: Control -> Clingo s a -> IO a Source #

Run a clingo computation from an explicit handle. The handle must be cleaned up manually afterwards, or on failure!

askC :: Clingo s Control Source #

Get the control handle from the Clingo monad. Arbitrarily unsafe things can be done with this!

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 SymbolicLiteral s Source #

Constructors

SLPositive (Symbol s) 
SLNegative (Symbol s) 

Instances

Eq (SymbolicLiteral s) Source # 
Ord (SymbolicLiteral s) Source # 
Generic (SymbolicLiteral s) Source # 

Associated Types

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

Hashable (SymbolicLiteral s) Source # 
Signed (SymbolicLiteral s) Source # 
type Rep (SymbolicLiteral s) Source # 
type Rep (SymbolicLiteral s) = D1 (MetaData "SymbolicLiteral" "Clingo.Internal.Types" "clingo-0.2.0.0-DzJnCg9nABaE1yAGw8EIsO" False) ((:+:) (C1 (MetaCons "SLPositive" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Symbol s)))) (C1 (MetaCons "SLNegative" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Symbol s)))))

newtype Literal s Source #

Constructors

Literal 

Fields

Instances

Eq (Literal s) Source # 

Methods

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

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

Ord (Literal s) Source # 

Methods

compare :: Literal s -> Literal s -> Ordering #

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

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

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

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

max :: Literal s -> Literal s -> Literal s #

min :: Literal s -> Literal s -> Literal s #

Show (Literal s) Source # 

Methods

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

show :: Literal s -> String #

showList :: [Literal s] -> ShowS #

Generic (Literal s) Source # 

Associated Types

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

Methods

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

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

NFData (Literal s) Source # 

Methods

rnf :: Literal s -> () #

Hashable (Literal s) Source # 

Methods

hashWithSalt :: Int -> Literal s -> Int #

hash :: Literal s -> Int #

Signed (Literal s) Source # 
type Rep (Literal s) Source # 
type Rep (Literal s) = D1 (MetaData "Literal" "Clingo.Internal.Types" "clingo-0.2.0.0-DzJnCg9nABaE1yAGw8EIsO" True) (C1 (MetaCons "Literal" PrefixI True) (S1 (MetaSel (Just Symbol "rawLiteral") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal)))

data WeightedLiteral s Source #

Constructors

WeightedLiteral (Literal s) Integer 

Instances

Eq (WeightedLiteral s) Source # 
Ord (WeightedLiteral s) Source # 
Show (WeightedLiteral s) Source # 
Generic (WeightedLiteral s) Source # 

Associated Types

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

NFData (WeightedLiteral s) Source # 

Methods

rnf :: WeightedLiteral s -> () #

Hashable (WeightedLiteral s) Source # 
type Rep (WeightedLiteral s) Source # 
type Rep (WeightedLiteral s) = D1 (MetaData "WeightedLiteral" "Clingo.Internal.Types" "clingo-0.2.0.0-DzJnCg9nABaE1yAGw8EIsO" False) (C1 (MetaCons "WeightedLiteral" PrefixI False) ((:*:) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Literal s))) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Integer))))

data ExternalType Source #

Instances

Enum ExternalType Source # 
Eq ExternalType Source # 
Ord ExternalType Source # 
Read ExternalType Source # 
Show ExternalType Source # 
Generic ExternalType Source # 

Associated Types

type Rep ExternalType :: * -> * #

Hashable ExternalType Source # 
type Rep ExternalType Source # 
type Rep ExternalType = D1 (MetaData "ExternalType" "Clingo.Internal.Types" "clingo-0.2.0.0-DzJnCg9nABaE1yAGw8EIsO" False) ((:+:) ((:+:) (C1 (MetaCons "ExtFree" PrefixI False) U1) (C1 (MetaCons "ExtTrue" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ExtFalse" PrefixI False) U1) (C1 (MetaCons "ExtRelease" PrefixI False) U1)))

data HeuristicType Source #

Instances

Enum HeuristicType Source # 
Eq HeuristicType Source # 
Ord HeuristicType Source # 
Read HeuristicType Source # 
Show HeuristicType Source # 
Generic HeuristicType Source # 

Associated Types

type Rep HeuristicType :: * -> * #

Hashable HeuristicType Source # 
type Rep HeuristicType Source # 
type Rep HeuristicType = D1 (MetaData "HeuristicType" "Clingo.Internal.Types" "clingo-0.2.0.0-DzJnCg9nABaE1yAGw8EIsO" False) ((:+:) ((:+:) (C1 (MetaCons "HeuristicLevel" PrefixI False) U1) ((:+:) (C1 (MetaCons "HeuristicSign" PrefixI False) U1) (C1 (MetaCons "HeuristicFactor" PrefixI False) U1))) ((:+:) (C1 (MetaCons "HeuristicInit" PrefixI False) U1) ((:+:) (C1 (MetaCons "HeuristicTrue" PrefixI False) U1) (C1 (MetaCons "HeuristicFalse" PrefixI False) U1))))

newtype AspifLiteral s Source #

Constructors

AspifLiteral 

Instances

Eq (AspifLiteral s) Source # 
Ord (AspifLiteral s) Source # 
Show (AspifLiteral s) Source # 
Generic (AspifLiteral s) Source # 

Associated Types

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

Methods

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

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

NFData (AspifLiteral s) Source # 

Methods

rnf :: AspifLiteral s -> () #

Hashable (AspifLiteral s) Source # 
Signed (AspifLiteral s) Source # 
type Rep (AspifLiteral s) Source # 
type Rep (AspifLiteral s) = D1 (MetaData "AspifLiteral" "Clingo.Internal.Types" "clingo-0.2.0.0-DzJnCg9nABaE1yAGw8EIsO" True) (C1 (MetaCons "AspifLiteral" PrefixI True) (S1 (MetaSel (Just Symbol "rawAspifLiteral") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Literal)))

newtype Atom s Source #

Constructors

Atom 

Fields

Instances

Eq (Atom s) Source # 

Methods

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

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

Ord (Atom s) Source # 

Methods

compare :: Atom s -> Atom s -> Ordering #

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

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

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

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

max :: Atom s -> Atom s -> Atom s #

min :: Atom s -> Atom s -> Atom s #

Show (Atom s) Source # 

Methods

showsPrec :: Int -> Atom s -> ShowS #

show :: Atom s -> String #

showList :: [Atom s] -> ShowS #

Generic (Atom s) Source # 

Associated Types

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

Methods

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

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

NFData (Atom s) Source # 

Methods

rnf :: Atom s -> () #

Hashable (Atom s) Source # 

Methods

hashWithSalt :: Int -> Atom s -> Int #

hash :: Atom s -> Int #

type Rep (Atom s) Source # 
type Rep (Atom s) = D1 (MetaData "Atom" "Clingo.Internal.Types" "clingo-0.2.0.0-DzJnCg9nABaE1yAGw8EIsO" True) (C1 (MetaCons "Atom" PrefixI True) (S1 (MetaSel (Just Symbol "rawAtom") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Atom)))

newtype Model s Source #

Constructors

Model Model 

newtype Solver s Source #

Constructors

Solver SolveHandle 

wrapCBLogger :: MonadIO m => (ClingoWarning -> Text -> IO ()) -> m (FunPtr (Logger ())) Source #

newtype Statistics s Source #

Constructors

Statistics Statistics 

newtype Backend s Source #

Constructors

Backend Backend 

newtype TheoryAtoms s Source #

Constructors

TheoryAtoms TheoryAtoms 

class AMVTree t where Source #

Minimal complete definition

atArray, atMap, value

Methods

atArray :: Int -> t v -> Maybe (t v) Source #

atMap :: Text -> t v -> Maybe (t v) Source #

value :: t v -> Maybe v Source #