Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
- throwOnCond :: Monad m => (a -> Bool) -> e -> MSF (ExceptT e m) a a
- throwOnCondM :: Monad m => (a -> m Bool) -> e -> MSF (ExceptT e m) a a
- throwOn :: Monad m => e -> MSF (ExceptT e m) Bool ()
- throwOn' :: Monad m => MSF (ExceptT e m) (Bool, e) ()
- throwMaybe :: Monad m => MSF (ExceptT e m) (Maybe e) (Maybe a)
- throwS :: Monad m => MSF (ExceptT e m) e a
- throw :: Monad m => e -> MSF (ExceptT e m) a b
- pass :: Monad m => MSF (ExceptT e m) a a
- maybeToExceptS :: (Functor m, Monad m) => MSF (MaybeT m) a b -> MSF (ExceptT () m) a b
- catchS :: Monad m => MSF (ExceptT e m) a b -> (e -> MSF m a b) -> MSF m a b
- untilE :: Monad m => MSF m a b -> MSF m b (Maybe e) -> MSF (ExceptT e m) a b
- exceptS :: Monad m => MSF (ExceptT e m) a b -> MSF m a (Either e b)
- inExceptT :: Monad m => MSF (ExceptT e m) (ExceptT e m a) a
- tagged :: Monad m => MSF (ExceptT e1 m) a b -> MSF (ExceptT e2 m) (a, e2) b
- newtype MSFExcept m a b e = MSFExcept {
- runMSFExcept :: MSF (ExceptT e m) a b
- try :: MSF (ExceptT e m) a b -> MSFExcept m a b e
- currentInput :: Monad m => MSFExcept m e b e
- data Empty
- safely :: Monad m => MSFExcept m a b Empty -> MSF m a b
- safe :: Monad m => MSF m a b -> MSFExcept m a b e
- once :: Monad m => (a -> m e) -> MSFExcept m a b e
- once_ :: Monad m => m e -> MSFExcept m a b e
- step :: Monad m => (a -> m (b, e)) -> MSFExcept m a b e
- performOnFirstSample :: Monad m => m (MSF m a b) -> MSF m a b
- reactimateExcept :: Monad m => MSFExcept m () () e -> m e
- reactimateB :: Monad m => MSF m () Bool -> m ()
- module Control.Monad.Trans.Except
Throwing exceptions
throwOnCond :: Monad m => (a -> Bool) -> e -> MSF (ExceptT e m) a a Source #
Throw the exception e
whenever the function evaluates to True
.
throwOnCondM :: Monad m => (a -> m Bool) -> e -> MSF (ExceptT e m) a a Source #
Variant of throwOnCond
for Kleisli arrows.
| Throws the exception when the input is True
.
throwOn :: Monad m => e -> MSF (ExceptT e m) Bool () Source #
Throw the exception when the input is True
.
throwOn' :: Monad m => MSF (ExceptT e m) (Bool, e) () Source #
Variant of throwOn
, where the exception may change every tick.
throwMaybe :: Monad m => MSF (ExceptT e m) (Maybe e) (Maybe a) Source #
When the input is 'Just e', throw the exception e
.
(Does not output any actual data.)
maybeToExceptS :: (Functor m, Monad m) => MSF (MaybeT m) a b -> MSF (ExceptT () m) a b Source #
Whenever Nothing
is thrown, throw '()' instead.
Catching exceptions
untilE :: Monad m => MSF m a b -> MSF m b (Maybe e) -> MSF (ExceptT e m) a b Source #
Similar to Yampa's delayed switching. Looses a b
in case of an exception.
tagged :: Monad m => MSF (ExceptT e1 m) a b -> MSF (ExceptT e2 m) (a, e2) b Source #
In case an exception occurs in the first argument, replace the exception by the second component of the tuple.
Monad interface for Exception MSFs
newtype MSFExcept m a b e Source #
MSF
s with an ExceptT
transformer layer
are in fact monads in the exception type.
return
corresponds to throwing an exception immediately.- '(>>=)' is exception handling: The first value throws an exception, while the Kleisli arrow handles the exception and produces a new signal function, which can throw exceptions in a different type.
MSFExcept | |
|
Monad m => Monad (MSFExcept m a b) Source # | Monad instance for |
Monad m => Functor (MSFExcept m a b) Source # | Functor instance for MSFs on the |
Monad m => Applicative (MSFExcept m a b) Source # | Applicative instance for MSFs on the |
currentInput :: Monad m => MSFExcept m e b e Source #
Immediately throw the current input as an exception.
once :: Monad m => (a -> m e) -> MSFExcept m a b e Source #
Inside the MSFExcept
monad, execute an action of the wrapped monad.
This passes the last input value to the action,
but doesn't advance a tick.
step :: Monad m => (a -> m (b, e)) -> MSFExcept m a b e Source #
Advances a single tick with the given Kleisli arrow, and then throws an exception.
Utilities definable in terms of MSFExcept
performOnFirstSample :: Monad m => m (MSF m a b) -> MSF m a b Source #
Extract MSF from a monadic action.
Runs a monadic action that produces an MSF on the first iteration/step, and uses that MSF as the main signal function for all inputs (including the first one).
reactimateExcept :: Monad m => MSFExcept m () () e -> m e Source #
Reactimates an MSFExcept
until it throws an exception.
module Control.Monad.Trans.Except