Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module provides a set of indexed type classes (IxFunctor, IxApplicative, IxMonad, etc..) that correspond to existing type classes (Functor, Applicative, Monad, etc..)
The intent of this module is to replace the use of non-indexed type classes with indexed type class.
For that reason the indexed type classes expose functions that are named the same as the functions exposed by a corresponding non-indexed type class.
There are two ways to use this module:
import SessionTypes import qualified SessionTypes.Indexed as I prog = send 5 I.>> eps0
{-# LANGUAGE RebindableSyntax #-} import SessionTypes import SessionTypes.Indexed prog = do send 5 eps0
With RebindableSyntax
we construct a custom do notation by rebinding (>>=) with (>>=) of IxMonad
.
Rebinding is not limited to only (>>=), but also all other functions in Prelude.
We do not want to force importing Prelude if you use RebindableSyntax
.
Therefore this module also exports Prelude that hides functions already defined by
the indexed type classes.
- class IxFunctor f where
- class IxFunctor f => IxApplicative f where
- class IxApplicative m => IxMonad m where
- class IxMonad (t m) => IxMonadT t m where
- class IxMonad (t m) => IxMonadIxT t m where
- class IxMonad m => IxMonadReader r m | m -> r where
- class IxMonad m => IxMonadThrow m s where
- class IxMonadThrow m s => IxMonadCatch m s where
- class IxMonadCatch m s => IxMonadMask m s where
- class IxMonadIO m where
- ap :: IxMonad m => m s r (a -> b) -> m r k a -> m s k b
- ifThenElse :: Bool -> t -> t -> t
Classes
class IxFunctor f => IxApplicative f where Source #
class IxApplicative m => IxMonad m where Source #
Transformers
class IxMonad (t m) => IxMonadIxT t m where Source #
Type class for lifting indexed monadic computations
Mtl
class IxMonad m => IxMonadReader r m | m -> r where Source #
Type class representing the indexed monad reader
Exception
class IxMonad m => IxMonadThrow m s where Source #
Type class for indexed monads in which exceptions may be thrown.
class IxMonadThrow m s => IxMonadCatch m s where Source #
Type class for indexed monads to allow catching of exceptions.
class IxMonadCatch m s => IxMonadMask m s where Source #
Type class for indexed monads that may mask asynchronous exceptions.
mask :: ((m s s b -> m s s b) -> m s s b) -> m s s b Source #
run an action that disables asynchronous exceptions. The provided function can be used to restore the occurrence of asynchronous exceptions.
uninterruptibleMask :: ((m s s b -> m s s b) -> m s s b) -> m s s b Source #
Ensures that even interruptible functions may not raise asynchronous exceptions.
MonadIO
Combinators
Rebind
ifThenElse :: Bool -> t -> t -> t Source #