Safe Haskell | Safe-Inferred |
---|
Defines a writer monad for computations that can be interrupted by a timeout. Written partial results are combined using their monoid operation and if a timeout occurs, the result is returned.
Several utility monoids that force their values to weak head normal form or to normal form are provided.
- class (Monoid w, Monad m) => MonadWriter w m | m -> w where
- class Monad m => MonadTimeout w m | m -> w where
- partialResult :: w -> m ()
- yield :: m ()
- class (Monoid w, MonadTimeout w m, MonadWriter w m) => MonadTimeoutWriter w m | m -> w where
- contained :: m r -> m (r, w)
- data TimeoutWriter w a
- runTimeout :: Monoid w => Int -> TimeoutWriter w r -> IO (Maybe r, w)
- withTimeoutWriter :: (w' -> w) -> TimeoutWriter w' a -> TimeoutWriter w a
- newtype Last' a = Last' {}
- newtype SeqMax a b = SeqMax (Maybe (a, b))
- newtype NFMonoid a = NFMonoid {
- getNFMonoid :: a
- defaultListen :: MonadTimeoutWriter w m => m a -> m (a, w)
- defaultPass :: MonadTimeoutWriter w m => m (a, w -> w) -> m a
Documentation
class (Monoid w, Monad m) => MonadWriter w m | m -> w where
writer :: (a, w) -> m a
embeds a simple writer action.
writer
(a,w)
tell :: w -> m ()
is an action that produces the output tell
ww
.
listen :: m a -> m (a, w)
is an action that executes the action listen
mm
and adds
its output to the value of the computation.
pass :: m (a, w -> w) -> m a
is an action that executes the action pass
mm
, which
returns a value and a function, and returns the value, applying
the function to the output.
(Monad (TimeoutWriter w), Monoid w) => MonadWriter w (TimeoutWriter w) | |
(Monoid w, Monad (MaybeT m), MonadWriter w m) => MonadWriter w (MaybeT m) | |
(Monoid w, Monad (IdentityT m), MonadWriter w m) => MonadWriter w (IdentityT m) | |
(Monad (WriterT w m), Monoid w, Monad m) => MonadWriter w (WriterT w m) | |
(Monad (WriterT w m), Monoid w, Monad m) => MonadWriter w (WriterT w m) | |
(Monoid w, Monad (StateT s m), MonadWriter w m) => MonadWriter w (StateT s m) | |
(Monoid w, Monad (StateT s m), MonadWriter w m) => MonadWriter w (StateT s m) | |
(Monoid w, Monad (ReaderT r m), MonadWriter w m) => MonadWriter w (ReaderT r m) | |
(Monoid w, Monad (ErrorT e m), Error e, MonadWriter w m) => MonadWriter w (ErrorT e m) | |
(Monad (RWST r w s m), Monoid w, Monad m) => MonadWriter w (RWST r w s m) | |
(Monad (RWST r w s m), Monoid w, Monad m) => MonadWriter w (RWST r w s m) |
class Monad m => MonadTimeout w m | m -> w whereSource
Monad for computations that can save partial results
of type w
during their evaluation.
partialResult :: w -> m ()Source
Store a new partial result. The precise semantics of what happens with the written value is by intent unspecified and left to be decided by implementations.
Explicitly allow interrupting the computation at this point. Experimental.
(Monad (TimeoutWriter w), Monoid w) => MonadTimeout w (TimeoutWriter w) | |
Monad (Timeout w) => MonadTimeout w (Timeout w) |
class (Monoid w, MonadTimeout w m, MonadWriter w m) => MonadTimeoutWriter w m | m -> w whereSource
Extends MonadTimeout
to MonadWriter
. Written values are combined
together using w
's monoid. In addition, allows to run a sub-computation
in a contained environment, without affecting the current partial result.
contained :: m r -> m (r, w)Source
Runs the given computation separately and return its result. Does not modify the current result!
(MonadTimeout w (TimeoutWriter w), MonadWriter w (TimeoutWriter w), Monoid w) => MonadTimeoutWriter w (TimeoutWriter w) |
data TimeoutWriter w a Source
An IO
-based implementation of MonadTimeoutWriter
. Calling
partialResult
(or equivalently tell
) combines the value with any
previously written values using w
's monoidal operation.
(Monad (TimeoutWriter w), Monoid w) => MonadWriter w (TimeoutWriter w) | |
(MonadTimeout w (TimeoutWriter w), MonadWriter w (TimeoutWriter w), Monoid w) => MonadTimeoutWriter w (TimeoutWriter w) | |
(Monad (TimeoutWriter w), Monoid w) => MonadTimeout w (TimeoutWriter w) | |
Monad (TimeoutWriter w) | |
Functor (TimeoutWriter w) | |
Functor (TimeoutWriter w) => Applicative (TimeoutWriter w) | |
Monad (TimeoutWriter w) => MonadIO (TimeoutWriter w) |
:: Monoid w | |
=> Int | TimeoutWriter in microseconds. |
-> TimeoutWriter w r | The computation. |
-> IO (Maybe r, w) | The final result (if available) and the saved partial result. |
Execute the given computation with a timeout limit. Each time a value
is written, the result of mappend
with the previous one is evaluated to
weak head normal form.
withTimeoutWriter :: (w' -> w) -> TimeoutWriter w' a -> TimeoutWriter w aSource
Modify written values using the given function.
A monoid equivalent to Last
. In addition, it forces evaluation of
values inside Maybe
using rseq
. This means that when it is used in
runTimeout
, the computations will be forced in the producing thread,
not in the consuming one. If you want to force evaluation to NF, wrap
it inside NFMonoid
.
A wrapper monoid that forces each result of mappend
to normal form'
NFMonoid | |
|
defaultListen :: MonadTimeoutWriter w m => m a -> m (a, w)Source
A default implementation of listen
using contained
.
Useful only for authors of implementations of MonadTimeout
.
defaultPass :: MonadTimeoutWriter w m => m (a, w -> w) -> m aSource
A default implementation of pass
using contained
.
Useful only for authors of implementations of MonadTimeout
.