clingo-0.2.0.0: Haskell bindings to the Clingo ASP solver

Safe HaskellNone
LanguageHaskell2010

Clingo.Configuration

Contents

Synopsis

Tree interface

data ConfTree v Source #

The configuration tree type, polymorphic over the leaf values.

Constructors

CValue v 
CMap (Maybe v) [(Text, ConfTree v)] 
CArray (Maybe v) [(Int, ConfTree v)] 
CBoth (Maybe v) [((Text, Int), ConfTree v)] 

Instances

Functor ConfTree Source # 

Methods

fmap :: (a -> b) -> ConfTree a -> ConfTree b #

(<$) :: a -> ConfTree b -> ConfTree a #

Foldable ConfTree Source # 

Methods

fold :: Monoid m => ConfTree m -> m #

foldMap :: Monoid m => (a -> m) -> ConfTree a -> m #

foldr :: (a -> b -> b) -> b -> ConfTree a -> b #

foldr' :: (a -> b -> b) -> b -> ConfTree a -> b #

foldl :: (b -> a -> b) -> b -> ConfTree a -> b #

foldl' :: (b -> a -> b) -> b -> ConfTree a -> b #

foldr1 :: (a -> a -> a) -> ConfTree a -> a #

foldl1 :: (a -> a -> a) -> ConfTree a -> a #

toList :: ConfTree a -> [a] #

null :: ConfTree a -> Bool #

length :: ConfTree a -> Int #

elem :: Eq a => a -> ConfTree a -> Bool #

maximum :: Ord a => ConfTree a -> a #

minimum :: Ord a => ConfTree a -> a #

sum :: Num a => ConfTree a -> a #

product :: Num a => ConfTree a -> a #

Traversable ConfTree Source # 

Methods

traverse :: Applicative f => (a -> f b) -> ConfTree a -> f (ConfTree b) #

sequenceA :: Applicative f => ConfTree (f a) -> f (ConfTree a) #

mapM :: Monad m => (a -> m b) -> ConfTree a -> m (ConfTree b) #

sequence :: Monad m => ConfTree (m a) -> m (ConfTree a) #

AMVTree ConfTree Source # 
Eq v => Eq (ConfTree v) Source # 

Methods

(==) :: ConfTree v -> ConfTree v -> Bool #

(/=) :: ConfTree v -> ConfTree v -> Bool #

Ord v => Ord (ConfTree v) Source # 

Methods

compare :: ConfTree v -> ConfTree v -> Ordering #

(<) :: ConfTree v -> ConfTree v -> Bool #

(<=) :: ConfTree v -> ConfTree v -> Bool #

(>) :: ConfTree v -> ConfTree v -> Bool #

(>=) :: ConfTree v -> ConfTree v -> Bool #

max :: ConfTree v -> ConfTree v -> ConfTree v #

min :: ConfTree v -> ConfTree v -> ConfTree v #

Show v => Show (ConfTree v) Source # 

Methods

showsPrec :: Int -> ConfTree v -> ShowS #

show :: ConfTree v -> String #

showList :: [ConfTree v] -> ShowS #

Generic (ConfTree v) Source # 

Associated Types

type Rep (ConfTree v) :: * -> * #

Methods

from :: ConfTree v -> Rep (ConfTree v) x #

to :: Rep (ConfTree v) x -> ConfTree v #

NFData v => NFData (ConfTree v) Source # 

Methods

rnf :: ConfTree v -> () #

type Rep (ConfTree v) Source # 

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 #

(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> a -> m c infixr 1 #

Left-to-right Kleisli composition of monads.

fromConfig :: Configuration s -> (ConfTree (StateVar Text) -> Maybe w) -> Clingo s (Maybe w) Source #

Get a configuration option from the tree. If any lookup fails, the result will be Nothing. The tree will be traversed lazily, but the result is evaluated before returning!

fromConfigMany :: Configuration s -> [ConfTree (StateVar Text) -> Maybe w] -> Clingo s [Maybe w] Source #

Like fromConfig but supporting multiple paths.

Re-exported from StateVar

data StateVar a :: * -> * #

A concrete implementation of a readable and writable state variable, carrying one IO action to read the value and another IO action to write the new value. This data type represents a piece of mutable, imperative state with possible side-effects. These tend to encapsulate all sorts tricky behavior in external libraries, and may well throw exceptions. Inhabitants should satsify the following properties:

  • In the absence of concurrent mutation from other threads or a thrown exception:
do x <- get v; v $= y; v $= x

should restore the previous state.

  • Ideally, in the absence of thrown exceptions:
v $= a >> get v

should return a, regardless of a. In practice some StateVars only permit a very limited range of value assignments, and do not report failure.

Instances

HasSetter (StateVar a) a 

Methods

($=) :: MonadIO m => StateVar a -> a -> m () #

HasGetter (StateVar a) a 

Methods

get :: MonadIO m => StateVar a -> m a #

HasUpdate (StateVar a) a a 

Methods

($~) :: MonadIO m => StateVar a -> (a -> a) -> m () #

($~!) :: MonadIO m => StateVar a -> (a -> a) -> m () #

($=) :: HasSetter t a => forall m. MonadIO m => t -> a -> m () #

Write a new value into a state variable.

get :: HasGetter t a => forall m. MonadIO m => t -> m a #