clingo-0.2.0.0: Haskell bindings to the Clingo ASP solver

Safe HaskellNone
LanguageHaskell2010

Clingo.Symbol

Contents

Description

Functions for handling symbols and signatures with clingo.

Synopsis

Documentation

data 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.

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 #

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 # 

Symbol types

symbolType :: Symbol s -> SymbolType Source #

Get the type of a symbol

Function symbols

Signature parsing/inspection

parseTerm Source #

Arguments

:: Text

Term as Text

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

Logger callback

-> Natural

Callback limit

-> Clingo s (Symbol s) 

Parse a term in string form. This does not return an AST Term!

signatureArity :: Signature s -> Natural Source #

Get the arity of a signature.

signatureHash :: Signature s -> Integer Source #

Hash a signature.

signatureName :: Signature s -> Text Source #

Get the name of a signature.

Symbol and signature creation

class MonadSymbol m where Source #

Methods

createSignature :: Text -> Natural -> Bool -> m s (Signature s) Source #

Create a new signature with the solver, taking a name, an arity and a bool determining the sign.

createNumber :: Integral a => a -> m s (Symbol s) Source #

Create a number symbol.

createSupremum :: m s (Symbol s) Source #

Create a supremum symbol, #sup.

createInfimum :: m s (Symbol s) Source #

Create a infimum symbol, #inf.

createString :: Text -> m s (Symbol s) Source #

Construct a symbol representing a string.

createFunction :: Text -> [Symbol s] -> Bool -> m s (Symbol s) Source #

Construct a symbol representing a function or tuple from a name, arguments, and whether the sign is positive.

createId :: MonadSymbol m => Text -> Bool -> m s (Symbol s) Source #

Construct a symbol representing an id.

Symbol inspection

symbolArguments :: Symbol s -> [Symbol s] Source #

Obtain the arguments of a symbol. May be empty.

symbolGetArg :: Symbol s -> Int -> Maybe (Symbol s) Source #

Obtain the n-th argument of a symbol.

symbolHash :: Symbol s -> Integer Source #

Hash a symbol

symbolName :: Symbol s -> Maybe Text Source #

Obtain the name of a symbol when possible.

symbolNumber :: Symbol s -> Maybe Integer Source #

Obtain number from symbol. Will fail for invalid symbol types.

symbolString :: Symbol s -> Maybe Text Source #

Obtain the string from a suitable symbol.

prettySymbol :: Symbol s -> Text Source #

Pretty print a symbol into a Text.

Pure types

data PureSymbol Source #

PureSymbol represents a completely pure Haskell alternative to the handled Symbol type of the clingo library.

Instances

Eq PureSymbol Source # 
Ord PureSymbol Source # 
Show PureSymbol Source # 
Generic PureSymbol Source # 

Associated Types

type Rep PureSymbol :: * -> * #

Pretty PureSymbol Source # 
type Rep PureSymbol Source # 

unpureSymbol :: (Monad (m s), MonadSymbol m) => PureSymbol -> m s (Symbol s) Source #

Create a Symbol in the solver from a PureSymbol

data PureSignature Source #

PureSignature represents a completely pure Haskell alternative to the handled Signature type of the clingo library.

unpureSignature :: MonadSymbol m => PureSignature -> m s (Signature s) Source #

Create a Signature in the solver from a PureSignature