clingo-0.2.0.0: Haskell bindings to the Clingo ASP solver

Safe HaskellNone
LanguageHaskell2010

Clingo.Model

Synopsis

Documentation

data Model s Source #

data SymbolicLiteral s Source #

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)))))

class MonadSymbol m => MonadModel m where Source #

Methods

modelType :: Model s -> m s ModelType Source #

Get the type of a Model.

modelNumber :: Model s -> m s Natural Source #

Get the number of a Model.

modelSymbols :: Model s -> SymbolSelection -> m s [Symbol s] Source #

Get the selected symbols from a Model.

contains :: Model s -> Symbol s -> m s Bool Source #

Constant time lookup to test whether an atom is in a model.

costVector :: Model s -> m s [Integer] Source #

Get the cost vector of a Model

optimalityProven :: Model s -> m s Bool Source #

Check whether optimality of a model has been proven.

context :: Model s -> m s (SolveControl s) Source #

Get the associated SolveControl of a Model.

modelAddClause :: Foldable t => SolveControl s -> t (SymbolicLiteral s) -> m s () Source #

Add a clause from the model callback.