clingo-0.2.0.0: Haskell bindings to the Clingo ASP solver

Safe HaskellNone
LanguageHaskell2010

Clingo.ProgramBuilding

Contents

Description

A module providing program building capabilities for both ground and non-ground programs.

Synopsis

Documentation

newtype Node Source #

Constructors

Node 

Fields

data Literal s Source #

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

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

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

assume :: Foldable t => t (AspifLiteral s) -> GroundStatement s Source #

Add an assumption directive.

Ground Programs

data GroundStatement s Source #

A GroundStatement is a statement built from ground atoms. Because the atoms are only valid within the context of clingo, they may not leave this context. They can be added to the current program using the addGroundStatements function.

addGroundStatements :: Foldable t => Backend s -> t (GroundStatement s) -> Clingo s () Source #

Add a collection of GroundStatement to the program via a Backend handle.

acycEdge :: Foldable t => Node -> Node -> t (Literal s) -> GroundStatement s Source #

Build an edge directive.

atom :: (MonadIO m, MonadThrow m) => Backend s -> m (Atom s) Source #

Obtain a fresh atom to be used in aspif directives.

atomAspifLiteral :: Atom s -> AspifLiteral s Source #

Use an Atom as a positive AspifLiteral

external :: Atom s -> ExternalType -> GroundStatement s Source #

Build an external statement.

heuristic Source #

Arguments

:: Foldable t 
=> Atom s 
-> HeuristicType 
-> Int

Bias

-> Natural

Priority

-> t (AspifLiteral s)

Condition

-> GroundStatement s 

Build a heuristic directive.

minimize Source #

Arguments

:: Foldable t 
=> Integer

Priority

-> t (WeightedLiteral s)

Literals to minimize

-> GroundStatement s 

Build a minimize constraint (or weak constraint).

rule Source #

Arguments

:: Foldable t 
=> Bool

Is a choice rule?

-> t (Atom s)

Head

-> t (AspifLiteral s)

Body

-> GroundStatement s 

Build a rule.

weightedRule Source #

Arguments

:: Foldable t 
=> Bool

Is a choice rule?

-> t (Atom s)

Head

-> Natural

Lower Bound

-> t (WeightedLiteral s)

Body

-> GroundStatement s 

Build a weighted rule.

project :: Foldable t => t (Atom s) -> GroundStatement s Source #

Build a projection directive

Non-Ground Programs

See AST for the abstract syntax tree to build Statements.

addStatements :: Traversable t => ProgramBuilder s -> t (Statement (Symbol s) (Signature s)) -> Clingo s () Source #

Add a collection of non-ground statements to the solver.