weighted-0.3.0.1: Writer monad which uses semiring constraint

Safe HaskellNone
LanguageHaskell2010

Control.Monad.Weighted

Contents

Description

This module provides monad transformer similar to WriterT, implemented using StateT, making it tail recursive. (The traditional writer always leaks space: see here for more information).

Pattern Synonyms are used to provide the same interface as WriterT. Unfortunately, current GHC warns whenever these patterns are used that there are unmatched patterns: the COMPLETE pragma should solve this problem in future version of GHC.

A pattern synonym is also provided for a non-transformer version of writer. Again, this is just StateT underneath, but its interface looks as if it was defined like so:

newtype Writer w a = Writer { runWriter :: (a, w) }

The other difference between this monad and WriterT is that it relies on <.> from Semiring, rather than mappend from Monoid.

Synopsis

Transformer

data WeightedT s m a Source #

A monad transformer similar to WriterT, except that it does not leak space. It is implemented using a state monad, so that mappend is tail recursive. See this email to the Haskell libraries committee for more information.

It also uses <.> from Semiring, rather than mappend from Monoid when combining computations.

Wherever possible, coercions are used to eliminate any overhead from the newtype wrapper.

Instances

MonadError e m => MonadError e (WeightedT s m) Source # 

Methods

throwError :: e -> WeightedT s m a #

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

MonadReader r m => MonadReader r (WeightedT s m) Source # 

Methods

ask :: WeightedT s m r #

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

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

MonadState s m => MonadState s (WeightedT w m) Source # 

Methods

get :: WeightedT w m s #

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

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

MonadWriter w m => MonadWriter w (WeightedT s m) Source # 

Methods

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

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

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

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

(Semiring w, Monad m) => MonadWeighted w (WeightedT w m) Source # 

Methods

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

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

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

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

MonadTrans (WeightedT s) Source # 

Methods

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

Monad m => Monad (WeightedT s m) Source # 

Methods

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

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

return :: a -> WeightedT s m a #

fail :: String -> WeightedT s m a #

Functor m => Functor (WeightedT s m) Source # 

Methods

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

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

MonadFix m => MonadFix (WeightedT s m) Source # 

Methods

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

MonadFail m => MonadFail (WeightedT s m) Source # 

Methods

fail :: String -> WeightedT s m a #

Monad m => Applicative (WeightedT s m) Source # 

Methods

pure :: a -> WeightedT s m a #

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

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

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

(Foldable m, Semiring w) => Foldable (WeightedT w m) Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: WeightedT w m a -> Bool #

length :: WeightedT w m a -> Int #

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

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

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

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

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

(Traversable m, Semiring w) => Traversable (WeightedT w m) Source # 

Methods

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

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

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

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

(Eq1 m, Eq w, Semiring w) => Eq1 (WeightedT w m) Source # 

Methods

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

(Ord1 m, Ord w, Semiring w) => Ord1 (WeightedT w m) Source # 

Methods

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

(Read w, Read1 m, Semiring w, Functor m) => Read1 (WeightedT w m) Source # 

Methods

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

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

(Show w, Show1 m, Semiring w) => Show1 (WeightedT w m) Source # 

Methods

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

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

MonadIO m => MonadIO (WeightedT s m) Source # 

Methods

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

MonadPlus m => Alternative (WeightedT s m) Source # 

Methods

empty :: WeightedT s m a #

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

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

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

MonadPlus m => MonadPlus (WeightedT s m) Source # 

Methods

mzero :: WeightedT s m a #

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

MonadCont m => MonadCont (WeightedT s m) Source # 

Methods

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

(Eq w, Eq1 m, Eq a, Semiring w) => Eq (WeightedT w m a) Source # 

Methods

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

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

(Ord w, Ord1 m, Ord a, Semiring w) => Ord (WeightedT w m a) Source # 

Methods

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

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

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

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

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

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

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

(Read w, Read1 m, Read a, Semiring w, Functor m) => Read (WeightedT w m a) Source # 
(Show w, Show1 m, Show a, Semiring w) => Show (WeightedT w m a) Source # 

Methods

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

show :: WeightedT w m a -> String #

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

runWeightedT :: Semiring s => WeightedT s m a -> m (a, s) Source #

Run a weighted computation in the underlying monad.

pattern WeightedT :: forall m s a. (Functor m, Semiring s) => m (a, s) -> WeightedT s m a Source #

This pattern gives the newtype wrapper around StateT the same interface as WriterT. Unfortunately, GHC currently warns that a function is incomplete wherever this pattern is used. This issue should be solved in a future version of GHC, when the COMPLETE pragma is implemented.

execWeightedT :: (Monad m, Semiring s) => WeightedT s m a -> m s Source #

Run a weighted computation in the underlying monad, and collect its weight.

evalWeightedT :: (Monad m, Semiring s) => WeightedT s m a -> m a Source #

Run a weighted computation in the underlying monad, and return its result.

Plain

type Weighted s = WeightedT s Identity Source #

A type synonym for the plain (non-transformer) version of Weighted. This can be used as if it were defined as:

newtype Weighted w a = Weighted { runWeighted :: (a, w) }

runWeighted :: Semiring s => Weighted s a -> (a, s) Source #

Run a weighted computation.

>>> runWeighted $ traverse (\x -> Weighted (show x, x)) [1..5]
(["1","2","3","4","5"],120)

pattern Weighted :: forall s a. Semiring s => (a, s) -> Weighted s a Source #

This pattern gives the newtype wrapper around StateT the same interface as as if it was defined like so:

newtype Weighted w a = Weighted { runWeighted :: (a, w) }

Unfortunately GHC warns that a function is incomplete wherever this pattern is used. This issue should be solved in a future version of GHC, when the COMPLETE pragma is implemented.

>>> execWeighted $ traverse (\x -> Weighted ((), x)) [1..5]
120

execWeighted :: Semiring s => Weighted s a -> s Source #

Run a weighted computation, and collect its weight.

evalWeighted :: Semiring s => Weighted s a -> a Source #

Run a weighted computation, and return its result.