dunai-0.4.0.0: Generalised reactive framework supporting classic, arrowized and monadic FRP.

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Trans.MSF.Except

Contents

Description

MSFs in the ExceptT monad are monadic stream functions that can throw exceptions, i.e. return an exception value instead of a continuation. This module gives ways to throw exceptions in various ways, and to handle them through a monadic interface.

Synopsis

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.)

throwS :: Monad m => MSF (ExceptT e m) e a Source #

Immediately throw the incoming exception.

throw :: Monad m => e -> MSF (ExceptT e m) a b Source #

Immediately throw the given exception.

pass :: Monad m => MSF (ExceptT e m) a a Source #

Do not throw an exception.

maybeToExceptS :: (Functor m, Monad m) => MSF (MaybeT m) a b -> MSF (ExceptT () m) a b Source #

Whenever Nothing is thrown, throw '()' instead.

Catching exceptions

catchS :: Monad m => MSF (ExceptT e m) a b -> (e -> MSF m a b) -> MSF m a b Source #

Catch an exception in an MSF. As soon as an exception occurs, the current continuation is replaced by a new MSF, the exception handler, based on the exception value. For exception catching where the handler can throw further exceptions, see MSFExcept further below.

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.

exceptS :: Monad m => MSF (ExceptT e m) a b -> MSF m a (Either e b) Source #

Escape an ExceptT layer by outputting the exception whenever it occurs. If an exception occurs, the current MSF continuation is tested again on the next input.

inExceptT :: Monad m => MSF (ExceptT e m) (ExceptT e m a) a Source #

Embed an ExceptT value inside the MSF. Whenever the input value is an ordinary value, it is passed on. If it is an exception, it is raised.

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 #

MSFs 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.

Constructors

MSFExcept 

Fields

Instances

Monad m => Monad (MSFExcept m a b) Source #

Monad instance for MSFExcept. Bind uses the exception as the "return" value in the monad.

Methods

(>>=) :: MSFExcept m a b a -> (a -> MSFExcept m a b b) -> MSFExcept m a b b #

(>>) :: MSFExcept m a b a -> MSFExcept m a b b -> MSFExcept m a b b #

return :: a -> MSFExcept m a b a #

fail :: String -> MSFExcept m a b a #

Monad m => Functor (MSFExcept m a b) Source #

Functor instance for MSFs on the Either monad. Fmapping is the same as applying a transformation to the Left values.

Methods

fmap :: (a -> b) -> MSFExcept m a b a -> MSFExcept m a b b #

(<$) :: a -> MSFExcept m a b b -> MSFExcept m a b a #

Monad m => Applicative (MSFExcept m a b) Source #

Applicative instance for MSFs on the Either monad. The function pure throws an exception.

Methods

pure :: a -> MSFExcept m a b a #

(<*>) :: MSFExcept m a b (a -> b) -> MSFExcept m a b a -> MSFExcept m a b b #

(*>) :: MSFExcept m a b a -> MSFExcept m a b b -> MSFExcept m a b b #

(<*) :: MSFExcept m a b a -> MSFExcept m a b b -> MSFExcept m a b a #

try :: MSF (ExceptT e m) a b -> MSFExcept m a b e Source #

An alias for the |MSFExcept| constructor, used to enter the |MSFExcept| monad context. Execute an MSF in ExceptT until it raises an exception.

currentInput :: Monad m => MSFExcept m e b e Source #

Immediately throw the current input as an exception.

data Empty Source #

The empty type. As an exception type, it encodes "no exception possible".

safely :: Monad m => MSFExcept m a b Empty -> MSF m a b Source #

If no exception can occur, the MSF can be executed without the ExceptT layer.

safe :: Monad m => MSF m a b -> MSFExcept m a b e Source #

An MSF without an ExceptT layer never throws an exception, and can thus have an arbitrary exception type.

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.

once_ :: Monad m => m e -> MSFExcept m a b e Source #

Variant of once without input.

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.

reactimateB :: Monad m => MSF m () Bool -> m () Source #

Reactimates an MSF until it returns True.