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

Safe HaskellSafe
LanguageHaskell2010

Control.Monad.Trans.MSF.Except

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

Documentation

data Empty Source #

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

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.
  • m: The monad that the MSF may take side effects in.
  • a: The input type
  • b: The output type
  • e: The type of exceptions that can be thrown

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.

Instance details

Defined in Control.Monad.Trans.MSF.Except

Methods

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

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

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

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

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.

Instance details

Defined in Control.Monad.Trans.MSF.Except

Methods

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

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

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

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

Instance details

Defined in Control.Monad.Trans.MSF.Except

Methods

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

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

liftA2 :: (a0 -> b0 -> c) -> MSFExcept m a b a0 -> MSFExcept m a b b0 -> MSFExcept m a b c #

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

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

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 #

Converts an MSF in MaybeT to an MSF in ExceptT. Whenever Nothing is thrown, throw () instead.

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. Loses a b in case of an exception.

exceptS :: (Functor m, 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.

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.

handleExceptT :: Monad m => MSF (ExceptT e1 m) a b -> (e1 -> MSF (ExceptT e2 m) a b) -> MSF (ExceptT e2 m) a b Source #

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.

performOnFirstSample :: Monad m => m (MSF m a b) -> MSF m a b Source #

Extract an 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.

switch :: Monad m => MSF m a (b, Maybe c) -> (c -> MSF m a b) -> MSF m a b Source #

transG :: (Monad m1, Monad m2) => (a2 -> m1 a1) -> (forall c. a2 -> m1 (b1, c) -> m2 (b2, Maybe c)) -> MSF m1 a1 b1 -> MSF m2 a2 b2 Source #

More general lifting combinator that enables recovery. Note that, unlike a polymorphic lifting function forall a . m a -> m1 a, this auxiliary function needs to be a bit more structured, and produces a Maybe value. The previous MSF is used if a new one is not produced.

handleGen :: (a -> m1 (b1, MSF m1 a b1) -> m2 (b2, MSF m2 a b2)) -> MSF m1 a b1 -> MSF m2 a b2 Source #

newtype ExceptT e (m :: Type -> Type) a #

A monad transformer that adds exceptions to other monads.

ExceptT constructs a monad parameterized over two things:

  • e - The exception type.
  • m - The inner monad.

The return function yields a computation that produces the given value, while >>= sequences two subcomputations, exiting on the first exception.

Constructors

ExceptT (m (Either e a)) 
Instances
MonadSplit g m => MonadSplit g (ExceptT e m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getSplit :: ExceptT e m g #

MonadBase b m => MonadBase b (ExceptT e m) 
Instance details

Defined in Control.Monad.Base

Methods

liftBase :: b α -> ExceptT e m α #

MonadTrans (ExceptT e) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

lift :: Monad m => m a -> ExceptT e m a #

Monad m => Monad (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

(>>=) :: ExceptT e m a -> (a -> ExceptT e m b) -> ExceptT e m b #

(>>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b #

return :: a -> ExceptT e m a #

fail :: String -> ExceptT e m a #

Functor m => Functor (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

fmap :: (a -> b) -> ExceptT e m a -> ExceptT e m b #

(<$) :: a -> ExceptT e m b -> ExceptT e m a #

MonadFix m => MonadFix (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

mfix :: (a -> ExceptT e m a) -> ExceptT e m a #

MonadFail m => MonadFail (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

fail :: String -> ExceptT e m a #

(Functor m, Monad m) => Applicative (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

pure :: a -> ExceptT e m a #

(<*>) :: ExceptT e m (a -> b) -> ExceptT e m a -> ExceptT e m b #

liftA2 :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c #

(*>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b #

(<*) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m a #

Foldable f => Foldable (ExceptT e f) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

fold :: Monoid m => ExceptT e f m -> m #

foldMap :: Monoid m => (a -> m) -> ExceptT e f a -> m #

foldr :: (a -> b -> b) -> b -> ExceptT e f a -> b #

foldr' :: (a -> b -> b) -> b -> ExceptT e f a -> b #

foldl :: (b -> a -> b) -> b -> ExceptT e f a -> b #

foldl' :: (b -> a -> b) -> b -> ExceptT e f a -> b #

foldr1 :: (a -> a -> a) -> ExceptT e f a -> a #

foldl1 :: (a -> a -> a) -> ExceptT e f a -> a #

toList :: ExceptT e f a -> [a] #

null :: ExceptT e f a -> Bool #

length :: ExceptT e f a -> Int #

elem :: Eq a => a -> ExceptT e f a -> Bool #

maximum :: Ord a => ExceptT e f a -> a #

minimum :: Ord a => ExceptT e f a -> a #

sum :: Num a => ExceptT e f a -> a #

product :: Num a => ExceptT e f a -> a #

Traversable f => Traversable (ExceptT e f) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

traverse :: Applicative f0 => (a -> f0 b) -> ExceptT e f a -> f0 (ExceptT e f b) #

sequenceA :: Applicative f0 => ExceptT e f (f0 a) -> f0 (ExceptT e f a) #

mapM :: Monad m => (a -> m b) -> ExceptT e f a -> m (ExceptT e f b) #

sequence :: Monad m => ExceptT e f (m a) -> m (ExceptT e f a) #

(Monad m, Monoid e) => MonadPlus (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

mzero :: ExceptT e m a #

mplus :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

MonadIO m => MonadIO (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftIO :: IO a -> ExceptT e m a #

MonadRandom m => MonadRandom (ExceptT e m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

getRandomR :: Random a => (a, a) -> ExceptT e m a #

getRandom :: Random a => ExceptT e m a #

getRandomRs :: Random a => (a, a) -> ExceptT e m [a] #

getRandoms :: Random a => ExceptT e m [a] #

MonadInterleave m => MonadInterleave (ExceptT e m) 
Instance details

Defined in Control.Monad.Random.Class

Methods

interleave :: ExceptT e m a -> ExceptT e m a #

Contravariant m => Contravariant (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

contramap :: (a -> b) -> ExceptT e m b -> ExceptT e m a #

(>$) :: b -> ExceptT e m b -> ExceptT e m a #

(Eq e, Eq1 m) => Eq1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftEq :: (a -> b -> Bool) -> ExceptT e m a -> ExceptT e m b -> Bool #

(Ord e, Ord1 m) => Ord1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftCompare :: (a -> b -> Ordering) -> ExceptT e m a -> ExceptT e m b -> Ordering #

(Read e, Read1 m) => Read1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (ExceptT e m a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [ExceptT e m a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (ExceptT e m a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [ExceptT e m a] #

(Show e, Show1 m) => Show1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ExceptT e m a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ExceptT e m a] -> ShowS #

MonadZip m => MonadZip (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

mzip :: ExceptT e m a -> ExceptT e m b -> ExceptT e m (a, b) #

mzipWith :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c #

munzip :: ExceptT e m (a, b) -> (ExceptT e m a, ExceptT e m b) #

(Functor m, Monad m, Monoid e) => Alternative (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

empty :: ExceptT e m a #

(<|>) :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

some :: ExceptT e m a -> ExceptT e m [a] #

many :: ExceptT e m a -> ExceptT e m [a] #

(Eq e, Eq1 m, Eq a) => Eq (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

(==) :: ExceptT e m a -> ExceptT e m a -> Bool #

(/=) :: ExceptT e m a -> ExceptT e m a -> Bool #

(Ord e, Ord1 m, Ord a) => Ord (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

compare :: ExceptT e m a -> ExceptT e m a -> Ordering #

(<) :: ExceptT e m a -> ExceptT e m a -> Bool #

(<=) :: ExceptT e m a -> ExceptT e m a -> Bool #

(>) :: ExceptT e m a -> ExceptT e m a -> Bool #

(>=) :: ExceptT e m a -> ExceptT e m a -> Bool #

max :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

min :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a #

(Read e, Read1 m, Read a) => Read (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

readsPrec :: Int -> ReadS (ExceptT e m a) #

readList :: ReadS [ExceptT e m a] #

readPrec :: ReadPrec (ExceptT e m a) #

readListPrec :: ReadPrec [ExceptT e m a] #

(Show e, Show1 m, Show a) => Show (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

showsPrec :: Int -> ExceptT e m a -> ShowS #

show :: ExceptT e m a -> String #

showList :: [ExceptT e m a] -> ShowS #

type Except e = ExceptT e Identity #

The parameterizable exception monad.

Computations are either exceptions or normal values.

The return function returns a normal value, while >>= exits on the first exception. For a variant that continues after an error and collects all the errors, see Errors.

runExcept :: Except e a -> Either e a #

Extractor for computations in the exception monad. (The inverse of except).

mapExcept :: (Either e a -> Either e' b) -> Except e a -> Except e' b #

Map the unwrapped computation using the given function.

withExcept :: (e -> e') -> Except e a -> Except e' a #

Transform any exceptions thrown by the computation using the given function (a specialization of withExceptT).

runExceptT :: ExceptT e m a -> m (Either e a) #

The inverse of ExceptT.

mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b #

Map the unwrapped computation using the given function.

withExceptT :: Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a #

Transform any exceptions thrown by the computation using the given function.

catchE #

Arguments

:: Monad m 
=> ExceptT e m a

the inner computation

-> (e -> ExceptT e' m a)

a handler for exceptions in the inner computation

-> ExceptT e' m a 

Handle an exception.

throwE :: Monad m => e -> ExceptT e m a #

Signal an exception value e.

except :: Either e a -> Except e a #

Constructor for computations in the exception monad. (The inverse of runExcept).