Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides exception handling, and thus control flow, to synchronous signal functions.
The API presented here closely follows dunai's Except
,
and reexports everything needed from there.
Synopsis
- type BehaviorFExcept m time a b e = BehaviourFExcept m time a b e
- type BehaviourFExcept m time a b e = forall cl. time ~ Time cl => ClSFExcept m cl a b e
- type ClSFExcept m cl a b e = MSFExcept (ReaderT (TimeInfo cl) m) a b e
- throwS :: Monad m => ClSF (ExceptT e m) cl e a
- throw :: Monad m => e -> MSF (ExceptT e m) a b
- pass :: Monad m => MSF (ExceptT e m) a a
- throwOn :: Monad m => e -> ClSF (ExceptT e m) cl Bool ()
- throwOn' :: Monad m => ClSF (ExceptT e m) cl (Bool, e) ()
- throwOnCond :: Monad m => (a -> Bool) -> e -> ClSF (ExceptT e m) cl a a
- throwOnCondM :: Monad m => (a -> m Bool) -> e -> ClSF (ExceptT e m) cl a a
- throwMaybe :: Monad m => ClSF (ExceptT e m) cl (Maybe e) (Maybe a)
- runClSFExcept :: Monad m => ClSFExcept m cl a b e -> ClSF (ExceptT e m) cl a b
- try :: Monad m => ClSF (ExceptT e m) cl a b -> ClSFExcept m cl a b e
- once :: Monad m => (a -> m e) -> ClSFExcept m cl a b e
- once_ :: Monad m => m e -> ClSFExcept m cl a b e
- step :: Monad m => (a -> m (b, e)) -> ClSFExcept m cl a b e
- module Control.Monad.Trans.Except
- safe :: Monad m => MSF m a b -> MSFExcept m a b e
- safely :: Monad m => MSFExcept m a b Empty -> MSF m a b
- data Empty
- exceptS :: (Functor m, Monad m) => MSF (ExceptT e m) a b -> MSF m a (Either e b)
- runMSFExcept :: MSFExcept m a b e -> MSF (ExceptT e m) a b
- currentInput :: Monad m => MSFExcept m e b e
Documentation
type BehaviorFExcept m time a b e = BehaviourFExcept m time a b e Source #
Compatibility to U.S. american spelling.
type BehaviourFExcept m time a b e = forall cl. time ~ Time cl => ClSFExcept m cl a b e Source #
A clock polymorphic ClSFExcept
,
or equivalently an exception-throwing behaviour.
Any clock with time domain time
may occur.
type ClSFExcept m cl a b e = MSFExcept (ReaderT (TimeInfo cl) m) a b e Source #
A synchronous exception-throwing signal function.
It is based on a newtype
from Dunai, MSFExcept
,
to exhibit a monad interface in the exception type.
return
then corresponds to throwing an exception,
and `(>>=)` is exception handling.
(For more information, see the documentation of MSFExcept
.)
m
: The monad that the signal function may take side effects incl
: The clock on which the signal function ticksa
: The input typeb
: The output typee
: The type of exceptions that can be thrown
throwOn :: Monad m => e -> ClSF (ExceptT e m) cl Bool () Source #
Throw the given exception when the Bool
turns true.
throwOn' :: Monad m => ClSF (ExceptT e m) cl (Bool, e) () Source #
Variant of throwOn
, where the exception can vary every tick.
throwOnCond :: Monad m => (a -> Bool) -> e -> ClSF (ExceptT e m) cl a a Source #
Throw the exception e
whenever the function evaluates to True
.
throwOnCondM :: Monad m => (a -> m Bool) -> e -> ClSF (ExceptT e m) cl a a Source #
Variant of throwOnCond
for Kleisli arrows.
| Throws the exception when the input is True
.
throwMaybe :: Monad m => ClSF (ExceptT e m) cl (Maybe e) (Maybe a) Source #
When the input is Just e
, throw the exception e
.
runClSFExcept :: Monad m => ClSFExcept m cl a b e -> ClSF (ExceptT e m) cl a b Source #
Leave the monad context, to use the ClSFExcept
as an Arrow
.
once :: Monad m => (a -> m e) -> ClSFExcept m cl a b e Source #
Within the same tick, perform a monadic action, and immediately throw the value as an exception.
step :: Monad m => (a -> m (b, e)) -> ClSFExcept m cl a b e Source #
Advances a single tick with the given Kleisli arrow, and then throws an exception.
module Control.Monad.Trans.Except
runMSFExcept :: MSFExcept m a b e -> MSF (ExceptT e m) a b #
currentInput :: Monad m => MSFExcept m e b e #
Immediately throw the current input as an exception.