clingo-0.2.0.0: Haskell bindings to the Clingo ASP solver

Safe HaskellNone
LanguageHaskell2010

Clingo.Propagation

Contents

Description

High level API for writing propagators.

Synopsis

Documentation

data Propagation phase s a Source #

A concrete monad for propagators, which observes the invariants stipulated by clingo.

Instances

MonadSymbol (Propagation phase) Source # 
MonadReader (PropagateInit s) (Propagation Init s) Source # 
MonadReader (PropagateCtrl s) (Propagation Solving s) Source # 
Monad (Propagation phase s) Source # 

Methods

(>>=) :: Propagation phase s a -> (a -> Propagation phase s b) -> Propagation phase s b #

(>>) :: Propagation phase s a -> Propagation phase s b -> Propagation phase s b #

return :: a -> Propagation phase s a #

fail :: String -> Propagation phase s a #

Functor (Propagation phase s) Source # 

Methods

fmap :: (a -> b) -> Propagation phase s a -> Propagation phase s b #

(<$) :: a -> Propagation phase s b -> Propagation phase s a #

Applicative (Propagation phase s) Source # 

Methods

pure :: a -> Propagation phase s a #

(<*>) :: Propagation phase s (a -> b) -> Propagation phase s a -> Propagation phase s b #

(*>) :: Propagation phase s a -> Propagation phase s b -> Propagation phase s b #

(<*) :: Propagation phase s a -> Propagation phase s b -> Propagation phase s a #

MonadIO (Propagation phase s) Source # 

Methods

liftIO :: IO a -> Propagation phase s a #

MonadThrow (Propagation phase s) Source # 

Methods

throwM :: Exception e => e -> Propagation phase s a #

data PropagationPhase Source #

Propagators can be in one of two phases, initialization and solving.

Constructors

Init 
Solving 

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

A propagator is defined by four functions. The first is executed during the initialization phase. The remaining three are called during solving, depending on how the propagator is initialized.

Initialization: This function is called once before each solving step. It is used to map relevant program literals to solver literals, add watches for solver literals, and initialize the data structures used during propagation. This is the last point to access symbolic and theory atoms. Once the search has started, they are no longer accessible.

Propagation: Can be used to add conflicts in order to propagate solver literals.

Undo: Is called on backjumping and can be used to synchronize internal data structures of the propagator.

Check: Can be used to check whether an assignment is valid.

data Propagator s Source #

A propagator is defined by four functions. No function is mandatory.

emptyPropagator :: Propagator s Source #

The empty propagator for convenience.

addWatch :: CanAddWatch phase => Literal s -> Propagation phase s () Source #

Watches can be added in any phase of the propagation. The propagate and undo functions will only be called on changes to watched literals!

Initialization

countThreads :: Propagation Init s Integer Source #

Obtain the number of solver threads.

propSymbolicAtoms :: Propagation Init s (SymbolicAtoms s) Source #

Obtain a handle to the symbolic atoms, see Symbolic

propTheoryAtoms :: Propagation Init s (TheoryAtoms s) Source #

Obtain a handle to the theory atoms, see Theory

Actions During Solving

data Clause s Source #

Constructors

Clause [Literal s] ClauseType 

Instances

Show (Clause s) Source # 

Methods

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

show :: Clause s -> String #

showList :: [Clause s] -> ShowS #

addClause :: Clause s -> Propagation Solving s () Source #

Add a clause. This call might result in termination of the propagation function, when backjumping is necessary.

propagate :: Propagation Solving s () Source #

Propagate implied literals from added clauses. Might result in backjumping and hence termination of the propagation.

hasWatch :: Literal s -> Propagation Solving s Bool Source #

Check whether a Literal is watched.

removeWatch :: Literal s -> Propagation Solving s () Source #

Stop watching a literal.

getThreadId :: Propagation Solving s Integer Source #

Get the thread id of the calling solver thread.

newLiteral :: Propagation Solving s (Literal s) Source #

Introduce a new literal to the solver.

assignment :: Propagation Solving s (Assignment s) Source #

Obtain the current (partial) assignment.

Assignment

decisionLevel :: Assignment s -> Propagation Solving s Natural Source #

Get the current decision level.

hasConflict :: Assignment s -> Propagation Solving s Bool Source #

Determine whether assignment has a conflict.

hasLiteral :: Assignment s -> Literal s -> Propagation Solving s Bool Source #

Determine whether a literal is part of an assignment.

levelOf :: Assignment s -> Literal s -> Propagation Solving s Natural Source #

Find the decision level of a given literal in an assignment.

decision :: Assignment s -> Natural -> Propagation Solving s (Literal s) Source #

Determine the decision literal given a decision level.

isFixed :: Assignment s -> Literal s -> Propagation Solving s Bool Source #

Check if a literal has a fixed truth value.

truthValue :: Assignment s -> Literal s -> Propagation Solving s TruthValue Source #

Obtain the truth value of a literal

Truth Values