weighted-0.3.0.1: Writer monad which uses semiring constraint

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Weighted.Filter

Description

This module provides a weighted monad which filters out zero-weighted results from a computation at every opportunity.

Synopsis

Documentation

data FilterT s m a Source #

A weighted monad which discards results which are zero as it goes.

Instances

(DetectableZero s, Alternative m, MonadError e m) => MonadError e (FilterT s m) Source # 

Methods

throwError :: e -> FilterT s m a #

catchError :: FilterT s m a -> (e -> FilterT s m a) -> FilterT s m a #

(DetectableZero s, Alternative m, MonadReader r m) => MonadReader r (FilterT s m) Source # 

Methods

ask :: FilterT s m r #

local :: (r -> r) -> FilterT s m a -> FilterT s m a #

reader :: (r -> a) -> FilterT s m a #

(Alternative m, MonadState s m, DetectableZero w) => MonadState s (FilterT w m) Source # 

Methods

get :: FilterT w m s #

put :: s -> FilterT w m () #

state :: (s -> (a, s)) -> FilterT w m a #

(DetectableZero s, Alternative m, MonadWriter w m) => MonadWriter w (FilterT s m) Source # 

Methods

writer :: (a, w) -> FilterT s m a #

tell :: w -> FilterT s m () #

listen :: FilterT s m a -> FilterT s m (a, w) #

pass :: FilterT s m (a, w -> w) -> FilterT s m a #

(DetectableZero w, Monad m, Alternative m) => MonadWeighted w (FilterT w m) Source # 

Methods

weighted :: (a, w) -> FilterT w m a Source #

weight :: w -> FilterT w m () Source #

weigh :: FilterT w m a -> FilterT w m (a, w) Source #

scale :: FilterT w m (a, w -> w) -> FilterT w m a Source #

MonadTrans (FilterT s) Source # 

Methods

lift :: Monad m => m a -> FilterT s m a #

(Alternative m, Monad m, DetectableZero s) => Monad (FilterT s m) Source # 

Methods

(>>=) :: FilterT s m a -> (a -> FilterT s m b) -> FilterT s m b #

(>>) :: FilterT s m a -> FilterT s m b -> FilterT s m b #

return :: a -> FilterT s m a #

fail :: String -> FilterT s m a #

(Alternative m, DetectableZero s) => Functor (FilterT s m) Source # 

Methods

fmap :: (a -> b) -> FilterT s m a -> FilterT s m b #

(<$) :: a -> FilterT s m b -> FilterT s m a #

(DetectableZero s, Alternative m, MonadFix m) => MonadFix (FilterT s m) Source # 

Methods

mfix :: (a -> FilterT s m a) -> FilterT s m a #

(DetectableZero s, Alternative m, MonadFail m) => MonadFail (FilterT s m) Source # 

Methods

fail :: String -> FilterT s m a #

(Alternative m, Monad m, DetectableZero s) => Applicative (FilterT s m) Source # 

Methods

pure :: a -> FilterT s m a #

(<*>) :: FilterT s m (a -> b) -> FilterT s m a -> FilterT s m b #

(*>) :: FilterT s m a -> FilterT s m b -> FilterT s m b #

(<*) :: FilterT s m a -> FilterT s m b -> FilterT s m a #

(Foldable m, DetectableZero w, Alternative m, Monad m) => Foldable (FilterT w m) Source # 

Methods

fold :: Monoid m => FilterT w m m -> m #

foldMap :: Monoid m => (a -> m) -> FilterT w m a -> m #

foldr :: (a -> b -> b) -> b -> FilterT w m a -> b #

foldr' :: (a -> b -> b) -> b -> FilterT w m a -> b #

foldl :: (b -> a -> b) -> b -> FilterT w m a -> b #

foldl' :: (b -> a -> b) -> b -> FilterT w m a -> b #

foldr1 :: (a -> a -> a) -> FilterT w m a -> a #

foldl1 :: (a -> a -> a) -> FilterT w m a -> a #

toList :: FilterT w m a -> [a] #

null :: FilterT w m a -> Bool #

length :: FilterT w m a -> Int #

elem :: Eq a => a -> FilterT w m a -> Bool #

maximum :: Ord a => FilterT w m a -> a #

minimum :: Ord a => FilterT w m a -> a #

sum :: Num a => FilterT w m a -> a #

product :: Num a => FilterT w m a -> a #

(Traversable m, DetectableZero w, Alternative m, Monad m) => Traversable (FilterT w m) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> FilterT w m a -> f (FilterT w m b) #

sequenceA :: Applicative f => FilterT w m (f a) -> f (FilterT w m a) #

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

sequence :: Monad m => FilterT w m (m a) -> m (FilterT w m a) #

(Eq1 m, Eq w, DetectableZero w, Monad m, Alternative m) => Eq1 (FilterT w m) Source # 

Methods

liftEq :: (a -> b -> Bool) -> FilterT w m a -> FilterT w m b -> Bool #

(Ord1 m, Ord w, DetectableZero w, Monad m, Alternative m) => Ord1 (FilterT w m) Source # 

Methods

liftCompare :: (a -> b -> Ordering) -> FilterT w m a -> FilterT w m b -> Ordering #

(Read w, Read1 m, DetectableZero w, Alternative m, Monad m) => Read1 (FilterT w m) Source # 

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (FilterT w m a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [FilterT w m a] #

(Show w, Show1 m, DetectableZero w, Monad m, Alternative m) => Show1 (FilterT w m) Source # 

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> FilterT w m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [FilterT w m a] -> ShowS #

(DetectableZero s, Alternative m, MonadIO m) => MonadIO (FilterT s m) Source # 

Methods

liftIO :: IO a -> FilterT s m a #

(DetectableZero s, MonadPlus m) => Alternative (FilterT s m) Source # 

Methods

empty :: FilterT s m a #

(<|>) :: FilterT s m a -> FilterT s m a -> FilterT s m a #

some :: FilterT s m a -> FilterT s m [a] #

many :: FilterT s m a -> FilterT s m [a] #

(DetectableZero s, MonadPlus m) => MonadPlus (FilterT s m) Source # 

Methods

mzero :: FilterT s m a #

mplus :: FilterT s m a -> FilterT s m a -> FilterT s m a #

(DetectableZero s, Alternative m, MonadCont m) => MonadCont (FilterT s m) Source # 

Methods

callCC :: ((a -> FilterT s m b) -> FilterT s m a) -> FilterT s m a #

(Eq w, Eq1 m, Eq a, DetectableZero w, Monad m, Alternative m) => Eq (FilterT w m a) Source # 

Methods

(==) :: FilterT w m a -> FilterT w m a -> Bool #

(/=) :: FilterT w m a -> FilterT w m a -> Bool #

(Ord w, Ord1 m, Ord a, DetectableZero w, Monad m, Alternative m) => Ord (FilterT w m a) Source # 

Methods

compare :: FilterT w m a -> FilterT w m a -> Ordering #

(<) :: FilterT w m a -> FilterT w m a -> Bool #

(<=) :: FilterT w m a -> FilterT w m a -> Bool #

(>) :: FilterT w m a -> FilterT w m a -> Bool #

(>=) :: FilterT w m a -> FilterT w m a -> Bool #

max :: FilterT w m a -> FilterT w m a -> FilterT w m a #

min :: FilterT w m a -> FilterT w m a -> FilterT w m a #

(Read w, Read1 m, Read a, DetectableZero w, Alternative m, Monad m) => Read (FilterT w m a) Source # 

Methods

readsPrec :: Int -> ReadS (FilterT w m a) #

readList :: ReadS [FilterT w m a] #

readPrec :: ReadPrec (FilterT w m a) #

readListPrec :: ReadPrec [FilterT w m a] #

(Show w, Show1 m, Show a, DetectableZero w, Alternative m, Monad m) => Show (FilterT w m a) Source # 

Methods

showsPrec :: Int -> FilterT w m a -> ShowS #

show :: FilterT w m a -> String #

showList :: [FilterT w m a] -> ShowS #

pattern FilterT :: forall m s a. (Alternative m, DetectableZero s, Monad m) => m (a, s) -> FilterT s m a Source #

This pattern gives an interface to the FilterT monad which makes it look as if it were defined without the state monad.

runFilterT :: (DetectableZero s, Alternative m, Monad m) => FilterT s m a -> m (a, s) Source #

Run a filtered computation in the underlying monad.

evalFilterT :: (Monad m, Semiring s) => FilterT s m a -> m a Source #

Evaluate a filtered computation in the underlying monad and return its result.

execFilterT :: (Monad m, Semiring s) => FilterT s m a -> m s Source #

Evaluate a filtered computation in the underlying monad and collect its weight.