clingo-0.2.0.0: Haskell bindings to the Clingo ASP solver

Safe HaskellNone
LanguageHaskell2010

Clingo.Statistics

Synopsis

Documentation

data StatsTree v Source #

The polymorphic statistics tree.

Constructors

SValue v 
SMap [(Text, StatsTree v)] 
SArray [(Int, StatsTree v)] 

Instances

Functor StatsTree Source # 

Methods

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

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

Foldable StatsTree Source # 

Methods

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

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

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

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

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

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

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

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

toList :: StatsTree a -> [a] #

null :: StatsTree a -> Bool #

length :: StatsTree a -> Int #

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

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

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

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

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

Traversable StatsTree Source # 

Methods

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

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

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

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

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

Methods

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

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

Ord v => Ord (StatsTree v) Source # 
Show v => Show (StatsTree v) Source # 
Generic (StatsTree v) Source # 

Associated Types

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

Methods

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

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

NFData v => NFData (StatsTree v) Source # 

Methods

rnf :: StatsTree v -> () #

type Rep (StatsTree 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.

fromStats :: NFData w => Statistics s -> (StatsTree Double -> Maybe w) -> Clingo s (Maybe w) Source #

Get a statistics value 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!

fromStatsMany :: NFData w => Statistics s -> [StatsTree Double -> Maybe w] -> Clingo s [Maybe w] Source #

Like fromTree but supporting multiple paths.

subStats :: NFData w => Statistics s -> (StatsTree Double -> Maybe (StatsTree w)) -> Clingo s (Maybe (StatsTree w)) Source #

Get an entire subtree from the statistics. The entire subtree will be evaluated before returning!