simple-effects-0.7.0.2: 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 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 effectively 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

MonadEffect (Signal a b) IO => MonadEffectSignal a b IO Source # 

Methods

signal :: a -> IO b Source #

(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 b (MaybeT m) Source # 

Methods

signal :: a -> MaybeT m b Source #

(Monad m, Show e) => MonadEffectSignal e b (ExceptT SomeSignal m) Source # 

Methods

signal :: e -> ExceptT SomeSignal m b Source #

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

Methods

signal :: e -> ExceptT e m b 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.

handleException :: Monad m => (a -> m c) -> ExceptT a 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.

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

MonadTrans MaybeT 

Methods

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

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 #

RunnableTrans MaybeT Source # 

Associated Types

type TransformerState (MaybeT :: (* -> *) -> * -> *) (m :: * -> *) :: * Source #

type TransformerResult (MaybeT :: (* -> *) -> * -> *) (m :: * -> *) a :: * Source #

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

Methods

signal :: a -> MaybeT m b Source #

MonadSplit g m => MonadSplit g (MaybeT m) 

Methods

getSplit :: MaybeT m g #

MonadBase b m => MonadBase b (MaybeT m) 

Methods

liftBase :: b α -> MaybeT m α #

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 #

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 #

MonadState s m => MonadState s (MaybeT m) 

Methods

get :: MaybeT m s #

put :: s -> MaybeT m () #

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

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

Monad m => MonadPlus (MaybeT m) 

Methods

mzero :: MaybeT m a #

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

MonadIO m => MonadIO (MaybeT m) 

Methods

liftIO :: IO a -> MaybeT m a #

MonadRandom m => MonadRandom (MaybeT m) 

Methods

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

getRandom :: Random a => MaybeT m a #

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

getRandoms :: Random a => MaybeT m [a] #

MonadInterleave m => MonadInterleave (MaybeT m) 

Methods

interleave :: 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) #

(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] #

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 #

(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 #

type StT MaybeT a 
type StT MaybeT a = Maybe a
type TransformerState MaybeT m Source # 
type TransformerResult MaybeT m a Source # 
type PrimState (MaybeT m) 
type StM (MaybeT m) a 
type StM (MaybeT m) a = ComposeSt MaybeT m a

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

Discard all the Throws and MonadEffectSignal 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 and MonadEffectSignal constraints if they all throw Showable exceptions. The first thrown exception will be shown and returned as a Left result.

class Throws e m => Handles e m where Source #

A class of monads that throw and catch exceptions of type e. An overlappable instance is given so you just need to make sure your transformers have a RunnableTrans instance.

Minimal complete definition

handleRecursive

Methods

handleRecursive :: (e -> m a) -> m a -> m a Source #

Use this function to handle exceptions without discarding the Throws constraint. You'll want to use this if you're writing a recursive function. Using the regular handlers in that case will result with infinite types.

Since this function doesn't discard constraints, you still need to handle the whole thing.

Here's a slightly contrived example.

  data NotFound = NotFound
  data Tree a = Leaf a | Node (Tree a) (Tree a)
  data Step = GoLeft | GoRight
  findIndex :: (Handles NotFound m, Eq a) => a -> Tree a -> m [Step]
  findIndex x (Leaf a) | x == a    = return []
                       | otherwise = throwSignal NotFound
  findIndex x (Node l r) = ((GoLeft :) $ findIndex x l)
      & handleRecursive (NotFound -> (GoRight :) $ findIndex x r)

Note: When you finally handle the exception effect, the order in which you handle it and other effects determines whether handleRecursive rolls back other effects if an exception occured or it preserves all of them up to the point of the exception. Handling exceptions last and handling them first will produce the former and latter behaviour respectively.

Instances

(Monad m, Monad (t m), Handles e m, RunnableTrans t) => Handles e (t m) Source # 

Methods

handleRecursive :: (e -> t m a) -> t m a -> t m a Source #

Monad m => Handles e (ExceptT e m) Source # 

Methods

handleRecursive :: (e -> ExceptT e m a) -> ExceptT e m a -> ExceptT e m a Source #

handleToEitherRecursive :: Handles e m => m a -> m (Either e a) Source #

handleToEither that doesn't discard Throws constraints. See documentation for handleRecursive.