rhine-0.8.0.1: Functional Reactive Programming with type-level clocks
Safe HaskellNone
LanguageHaskell2010

FRP.Rhine.ClSF.Except

Description

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

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 in
  • cl: The clock on which the signal function ticks
  • a: The input type
  • b: The output type
  • e: The type of exceptions that can be thrown

throwS :: Monad m => ClSF (ExceptT e m) cl 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.

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.

try :: Monad m => ClSF (ExceptT e m) cl a b -> ClSFExcept m cl a b e Source #

Enter the monad context in the exception for ClSFs in the ExceptT monad. The ClSF will be run until it encounters an exception.

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.

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

A variant of once without input.

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.

safe :: forall (m :: Type -> Type) a b e. Monad m => MSF m a b -> MSFExcept m a b e #

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

safely :: forall (m :: Type -> Type) a b. Monad m => MSFExcept m a b Void -> MSF m a b #

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

exceptS :: forall (m :: Type -> Type) e a b. (Functor m, Monad m) => MSF (ExceptT e m) a b -> MSF m a (Either e b) #

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.

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

currentInput :: forall (m :: Type -> Type) e b. Monad m => MSFExcept m e b e #

Immediately throw the current input as an exception.