simple-effects-0.5.0.3: A simple effect system that integrates with MTL

Safe HaskellNone
LanguageHaskell2010

Control.Effects.Signal

Synopsis

Documentation

class MonadEffect (Signal a b) m => MonadEffectSignal a b m | m a -> b where Source #

This class allows you to "throw" a signal. For the most part signals are the same as checked exceptions. The difference here is that the handler has the option to provide the value that will be the result _of calling the signal function_. This effectibvely allows you to have recoverable exceptions at the call site, instead of just at the handling site.

This class can be considered an alias for MonadEffect (Signal a b) so your code isn't required to provide any instances.

Methods

signal :: a -> m b Source #

There are no restrictions on the type of values that can be thrown or returned.

Instances

(MonadEffectSignal a b m, MonadTrans t, Monad (t m)) => MonadEffectSignal a b (t m) Source # 

Methods

signal :: a -> t m b Source #

Monad m => MonadEffectSignal a Void (MaybeT m) Source # 

Methods

signal :: a -> MaybeT m Void Source #

Monad m => MonadEffectSignal e Void (ExceptT e m) Source # 

Methods

signal :: e -> ExceptT e m Void Source #

data ResumeOrBreak b c Source #

The handle function will return a value of this type.

Constructors

Resume b

Give a value to the caller of signal and keep going.

Break c

Continue the execution after the handler. The handler will return this value

throwSignal :: Throws a m => a -> m b Source #

Throw a signal with no possible recovery. The handler is forced to only return the Break constructor because it cannot construct a Void value.

If this function is used along with handleAsException, this module behaves like regular checked exceptions.

handleSignal :: Monad m => (a -> m (ResumeOrBreak b c)) -> EffectHandler (Signal a b) (ExceptT c m) c -> m c Source #

Handle signals of a computation. The handler function has the option to provide a value to the caller of signal and continue execution there, or do what regular exception handlers do and continue execution after the handler.

handleAsException :: Monad m => (a -> m c) -> EffectHandler (Signal a b) (ExceptT c m) c -> m c Source #

This handler can only behave like a regular exception handler. If used along with throwSignal this module behaves like regular checked exceptions.

handleException :: Monad m => (a -> m c) -> ExceptT a m c -> m c Source #

In case only throwSignal is used then the function signatures will have a Throws a m constraint or, equivalently, a MonadEffectSignal a Void m constraint. In those cases you can use this function to handle their exceptions. This function will not work for handing other signals because ExceptT doesn't satisfy other constraints.

The advantage of using this handler is that your inferred transformer stack will have one less layer which can potentially lead to slight performance increases.

handleToEither :: ExceptT e m a -> m (Either e a) Source #

See documentation for handleException. This handler gives you an Either.

newtype MaybeT m a :: (* -> *) -> * -> * #

The parameterizable maybe monad, obtained by composing an arbitrary monad with the Maybe monad.

Computations are actions that may produce a value or exit.

The return function yields a computation that produces that value, while >>= sequences two subcomputations, exiting if either computation does.

Constructors

MaybeT 

Fields

Instances

MonadTransControl MaybeT 

Associated Types

type StT (MaybeT :: (* -> *) -> * -> *) a :: * #

Methods

liftWith :: Monad m => (Run MaybeT -> m a) -> MaybeT m a #

restoreT :: Monad m => m (StT MaybeT a) -> MaybeT m a #

MonadTrans MaybeT 

Methods

lift :: Monad m => m a -> MaybeT m a #

Monad m => MonadEffectSignal a Void (MaybeT m) Source # 

Methods

signal :: a -> MaybeT m Void Source #

MonadState s m => MonadState s (MaybeT m) 

Methods

get :: MaybeT m s #

put :: s -> MaybeT m () #

state :: (s -> (a, s)) -> MaybeT m a #

MonadReader r m => MonadReader r (MaybeT m) 

Methods

ask :: MaybeT m r #

local :: (r -> r) -> MaybeT m a -> MaybeT m a #

reader :: (r -> a) -> MaybeT m a #

MonadBaseControl b m => MonadBaseControl b (MaybeT m) 

Associated Types

type StM (MaybeT m :: * -> *) a :: * #

Methods

liftBaseWith :: (RunInBase (MaybeT m) b -> b a) -> MaybeT m a #

restoreM :: StM (MaybeT m) a -> MaybeT m a #

MonadBase b m => MonadBase b (MaybeT m) 

Methods

liftBase :: b α -> MaybeT m α #

Monad m => Monad (MaybeT m) 

Methods

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

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

return :: a -> MaybeT m a #

fail :: String -> MaybeT m a #

Functor m => Functor (MaybeT m) 

Methods

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

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

MonadFix m => MonadFix (MaybeT m) 

Methods

mfix :: (a -> MaybeT m a) -> MaybeT m a #

Monad m => MonadFail (MaybeT m) 

Methods

fail :: String -> MaybeT m a #

(Functor m, Monad m) => Applicative (MaybeT m) 

Methods

pure :: a -> MaybeT m a #

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

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

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

Foldable f => Foldable (MaybeT f) 

Methods

fold :: Monoid m => MaybeT f m -> m #

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

foldr :: (a -> b -> b) -> b -> MaybeT f a -> b #

foldr' :: (a -> b -> b) -> b -> MaybeT f a -> b #

foldl :: (b -> a -> b) -> b -> MaybeT f a -> b #

foldl' :: (b -> a -> b) -> b -> MaybeT f a -> b #

foldr1 :: (a -> a -> a) -> MaybeT f a -> a #

foldl1 :: (a -> a -> a) -> MaybeT f a -> a #

toList :: MaybeT f a -> [a] #

null :: MaybeT f a -> Bool #

length :: MaybeT f a -> Int #

elem :: Eq a => a -> MaybeT f a -> Bool #

maximum :: Ord a => MaybeT f a -> a #

minimum :: Ord a => MaybeT f a -> a #

sum :: Num a => MaybeT f a -> a #

product :: Num a => MaybeT f a -> a #

Traversable f => Traversable (MaybeT f) 

Methods

traverse :: Applicative f => (a -> f b) -> MaybeT f a -> f (MaybeT f b) #

sequenceA :: Applicative f => MaybeT f (f a) -> f (MaybeT f a) #

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

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

Contravariant m => Contravariant (MaybeT m) 

Methods

contramap :: (a -> b) -> MaybeT m b -> MaybeT m a #

(>$) :: b -> MaybeT m b -> MaybeT m a #

(Functor m, Monad m) => Alternative (MaybeT m) 

Methods

empty :: MaybeT m a #

(<|>) :: MaybeT m a -> MaybeT m a -> MaybeT m a #

some :: MaybeT m a -> MaybeT m [a] #

many :: MaybeT m a -> MaybeT m [a] #

Monad m => MonadPlus (MaybeT m) 

Methods

mzero :: MaybeT m a #

mplus :: MaybeT m a -> MaybeT m a -> MaybeT m a #

Eq1 m => Eq1 (MaybeT m) 

Methods

liftEq :: (a -> b -> Bool) -> MaybeT m a -> MaybeT m b -> Bool #

Ord1 m => Ord1 (MaybeT m) 

Methods

liftCompare :: (a -> b -> Ordering) -> MaybeT m a -> MaybeT m b -> Ordering #

Read1 m => Read1 (MaybeT m) 

Methods

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

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

Show1 m => Show1 (MaybeT m) 

Methods

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

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

MonadZip m => MonadZip (MaybeT m) 

Methods

mzip :: MaybeT m a -> MaybeT m b -> MaybeT m (a, b) #

mzipWith :: (a -> b -> c) -> MaybeT m a -> MaybeT m b -> MaybeT m c #

munzip :: MaybeT m (a, b) -> (MaybeT m a, MaybeT m b) #

MonadIO m => MonadIO (MaybeT m) 

Methods

liftIO :: IO a -> MaybeT m a #

MonadThrow m => MonadThrow (MaybeT m)

Throws exceptions into the base monad.

Methods

throwM :: Exception e => e -> MaybeT m a #

MonadCatch m => MonadCatch (MaybeT m)

Catches exceptions from the base monad.

Methods

catch :: Exception e => MaybeT m a -> (e -> MaybeT m a) -> MaybeT m a #

PrimMonad m => PrimMonad (MaybeT m) 

Associated Types

type PrimState (MaybeT m :: * -> *) :: * #

Methods

primitive :: (State# (PrimState (MaybeT m)) -> (#VoidRep, PtrRepLifted, State# (PrimState (MaybeT m)), a#)) -> MaybeT m a #

Zoom m n s t => Zoom (MaybeT m) (MaybeT n) s t 

Methods

zoom :: LensLike' (Zoomed (MaybeT m) c) t s -> MaybeT m c -> MaybeT n c #

(Eq1 m, Eq a) => Eq (MaybeT m a) 

Methods

(==) :: MaybeT m a -> MaybeT m a -> Bool #

(/=) :: MaybeT m a -> MaybeT m a -> Bool #

(Ord1 m, Ord a) => Ord (MaybeT m a) 

Methods

compare :: MaybeT m a -> MaybeT m a -> Ordering #

(<) :: MaybeT m a -> MaybeT m a -> Bool #

(<=) :: MaybeT m a -> MaybeT m a -> Bool #

(>) :: MaybeT m a -> MaybeT m a -> Bool #

(>=) :: MaybeT m a -> MaybeT m a -> Bool #

max :: MaybeT m a -> MaybeT m a -> MaybeT m a #

min :: MaybeT m a -> MaybeT m a -> MaybeT m a #

(Read1 m, Read a) => Read (MaybeT m a) 
(Show1 m, Show a) => Show (MaybeT m a) 

Methods

showsPrec :: Int -> MaybeT m a -> ShowS #

show :: MaybeT m a -> String #

showList :: [MaybeT m a] -> ShowS #

Wrapped (MaybeT m a) 

Associated Types

type Unwrapped (MaybeT m a) :: * #

Methods

_Wrapped' :: Iso' (MaybeT m a) (Unwrapped (MaybeT m a)) #

(~) * t (MaybeT n b) => Rewrapped (MaybeT m a) t 
type StT MaybeT a 
type StT MaybeT a = Maybe a
type Zoomed (MaybeT m) 
type PrimState (MaybeT m) 
type StM (MaybeT m) a 
type StM (MaybeT m) a = ComposeSt MaybeT m a
type Unwrapped (MaybeT m a) 
type Unwrapped (MaybeT m a) = m (Maybe a)

discardAllExceptions :: MaybeT m a -> m (Maybe a) Source #

Discard all the Throws constraints. If any exception was thrown the result will be Nothing.

showAllExceptions :: Functor m => ExceptT SomeSignal m a -> m (Either Text a) Source #

Satisfies all the Throws constraints _if_ they all throw Showable exceptions. The first thrown exception will be shown and returned as a Left result.