-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Monadic effect framework -- -- Please see the README on GitHub at -- https://github.com/nbloomf/trans-fx#readme @package trans-fx-core @version 0.0.1 module Control.FX -- | Class representing monads from which we can extract a pure value. -- Instances should satisfy the following laws: -- --
--   (1) unwrap . return === id
--   
--   (2) return . unwrap === id
--   
--   (3) x >>= f === f (unwrap x)
--   
class (Monad m, forall x. (Eq x) => Eq (m x), forall x. (Semigroup x) => Semigroup (m x), forall x. (Monoid x) => Monoid (m x)) => MonadIdentity m -- | Extract a pure value unwrap :: MonadIdentity m => m a -> a -- | Class representing monads which can fail catastrophically, returning -- nothing. Instances should satisfy the following laws: -- --
--   (1) halt a >> x === halt a
--   
class (Monad m, MonadIdentity mark) => MonadHalt mark m -- | Fail catastrophically, returning nothing. halt :: MonadHalt mark m => mark () -> m a -- | Fail catastrophically, returning nothing. halt :: (MonadHalt mark m, Monad m1, MonadTrans t1, m ~ t1 m1, MonadHalt mark m1) => mark () -> m a -- | Class representing monads which can raise and handle marked exceptions -- of type mark e. Instances should satisfy the following laws: -- --
--   (1) catch (return a) h === return a
--   
--   (2) catch (throw e) h === h e
--   
--   (3) throw e >>= f === throw e
--   
class (Monad m, MonadIdentity mark) => MonadExcept mark e m -- | Raise an exception throw :: MonadExcept mark e m => mark e -> m a -- | Raise an exception throw :: (MonadExcept mark e m, Monad m1, MonadTrans t1, m ~ t1 m1, MonadExcept mark e m1) => mark e -> m a -- | Run a computation, applying a handler to any raised exceptions catch :: MonadExcept mark e m => m a -> (mark e -> m a) -> m a -- | Run a computation, applying a handler to any raised exceptions catch :: (MonadExcept mark e m, Monad m1, MonadTrans t1, m ~ t1 m1, LiftCatch t1, MonadExcept mark e m1) => m a -> (mark e -> m a) -> m a -- | Class representing monads with access to a marked mutable state -- mark s. Instances should satisfy the following laws: -- --
--   (1) put s1 >> put s2 === put s2
--   
--   (2) put s >> get === put s >> return s
--   
--   (3) get >>= put === return ()
--   
--   (4) get >>= \\s -> get >>= k s === get >>= \\s -> k s s
--   
class (Monad m, MonadIdentity mark) => MonadState mark s m -- | Retrieve the current state get :: MonadState mark s m => m (mark s) -- | Retrieve the current state get :: (MonadState mark s m, Monad m1, MonadTrans t1, m ~ t1 m1, MonadState mark s m1) => m (mark s) -- | Replace the current state put :: MonadState mark s m => mark s -> m () -- | Replace the current state put :: (MonadState mark s m, Monad m1, MonadTrans t1, m ~ t1 m1, MonadState mark s m1) => mark s -> m () -- | Class representing monads with access to a marked write-only state -- mark w. Note that w must be an instance of -- Monoid. Instances should satisfy the following laws: -- --
--   (1) draft (tell w) === return ((),w)
--   
--   (2) tell mempty === return ()
--   
--   (3) tell w1 >> tell w2 === tell (mappend w1 w2)
--   
--   (4) draft (return a) === return (a, mempty)
--   
--   (5) draft (x >>= f) === draft x >>= (draft' f)
--         where draft' f (a,w) = mapsnd (mappend w) <$> draft (f a)
--   
class (Monad m, Monoid w, MonadIdentity mark) => MonadWriteOnly mark w m -- | Combine a value with the current write-only state tell :: MonadWriteOnly mark w m => mark w -> m () -- | Combine a value with the current write-only state tell :: (MonadWriteOnly mark w m, Monad m1, MonadTrans t1, m ~ t1 m1, MonadWriteOnly mark w m1) => mark w -> m () -- | Run a computation, returning the write-only state with the result -- rather than writing it draft :: MonadWriteOnly mark w m => m a -> m (Pair (mark w) a) -- | Run a computation, returning the write-only state with the result -- rather than writing it draft :: (MonadWriteOnly mark w m, Monad m1, MonadTrans t1, m ~ t1 m1, LiftDraft t1, MonadWriteOnly mark w m1) => m a -> m (Pair (mark w) a) -- | Class representing monads with access to a marked read-only state -- mark r. Instances should satisfy the following laws: -- --
--   (1) local u ask === fmap u ask
--   
--   (2) local u (local v x) === local (v . u) x
--   
--   (3) local u x >> ask === ask >>= \r -> local u x >> return r
--   
--   (4) local u (return a) === return a
--   
--   (5) local u (x >>= f) === local u x >>= (local u . f)
--   
class (Monad m, MonadIdentity mark) => MonadReadOnly mark r m -- | Retrieve the read-only state ask :: MonadReadOnly mark r m => m (mark r) -- | Retrieve the read-only state ask :: (MonadReadOnly mark r m, Monad m1, MonadTrans t1, m ~ t1 m1, MonadReadOnly mark r m1) => m (mark r) -- | Run a computation with a locally modified read-only state local :: MonadReadOnly mark r m => (mark r -> mark r) -> m a -> m a -- | Run a computation with a locally modified read-only state local :: (MonadReadOnly mark r m, Monad m1, MonadTrans t1, m ~ t1 m1, LiftLocal t1, MonadReadOnly mark r m1) => (mark r -> mark r) -> m a -> m a -- | Class representing monads with access to a marked append-only state -- mark w. Instances should satisfy the following laws: -- --
--   (1) jot mempty  ===  return ()
--   
--   (2) jot (a <> b)  ===  jot a >> jot b
--   
--   (3) look  ===  return mempty
--   
--   (4) x >> look >> y  ===  x >> y
--   
--   (5) jot w >> look  ===  jot w >> return w
--   
class (Monad m, MonadIdentity mark) => MonadAppendOnly mark w m -- | Retrieve the append-only state look :: MonadAppendOnly mark w m => m (mark w) -- | Retrieve the append-only state look :: (MonadAppendOnly mark w m, Monad m1, MonadTrans t1, m ~ t1 m1, MonadAppendOnly mark w m1) => m (mark w) -- | Append a value to the state jot :: MonadAppendOnly mark w m => mark w -> m () -- | Append a value to the state jot :: (MonadAppendOnly mark w m, Monad m1, MonadTrans t1, m ~ t1 m1, MonadAppendOnly mark w m1) => mark w -> m () -- | Class representing monads with access to a write-once, read-many state -- mark w. Instances should satisfy the following laws. -- --
--   (1) etch a >> etch b  ===  etch a >> return False
--   
--   (2) etch a >> press  ===  return (Just $ pure a)
--   
class (Monad m, MonadIdentity mark) => MonadWriteOnce mark w m -- | Attempt to record the write-once state, returning True if and -- only if the write succeeds. etch :: MonadWriteOnce mark w m => mark w -> m Bool -- | Attempt to record the write-once state, returning True if and -- only if the write succeeds. etch :: (MonadWriteOnce mark w m, Monad m1, MonadTrans t1, m ~ t1 m1, MonadWriteOnce mark w m1) => mark w -> m Bool -- | Attempt to read a copy of the write-once state. press :: MonadWriteOnce mark w m => m (Maybe (mark w)) -- | Attempt to read a copy of the write-once state. press :: (MonadWriteOnce mark w m, Monad m1, MonadTrans t1, m ~ t1 m1, MonadWriteOnce mark w m1) => m (Maybe (mark w)) -- | Class representing monads which can prompt an oracle for a monadic -- result. class (Monad m, MonadIdentity mark) => MonadPrompt mark (p :: * -> *) m -- | Prompt an oracle of type mark (p a), receiving a monadic -- result prompt :: MonadPrompt mark p m => mark (p a) -> m (mark a) -- | Prompt an oracle of type mark (p a), receiving a monadic -- result prompt :: (MonadPrompt mark p m, Monad m1, MonadTrans t1, m ~ t1 m1, MonadPrompt mark p m1) => mark (p a) -> m (mark a) -- | Concrete identity monad data Identity (a :: *) Identity :: a -> Identity -- | Extract a pure value [unIdentity] :: Identity -> a -- | Concrete composite monad newtype Compose (m1 :: * -> *) (m2 :: * -> *) (a :: *) Compose :: m1 (m2 a) -> Compose [unCompose] :: Compose -> m1 (m2 a) -- | Concrete read-only state monad with state type r newtype ReadOnly (mark :: * -> *) (r :: *) (a :: *) ReadOnly :: (r -> a) -> ReadOnly [unReadOnly] :: ReadOnly -> r -> a -- | Concrete state monad newtype State (mark :: * -> *) (s :: *) (a :: *) State :: (s -> Pair s a) -> State [unState] :: State -> s -> Pair s a -- | Concrete exception monad, throwing marked exceptions of type mark -- e and producing values of type a data Except (mark :: * -> *) (e :: *) (a :: *) -- | Exceptional result Except :: e -> Except -- | Normal result Accept :: a -> Except -- | Concrete write-only state monad with state type w newtype WriteOnly (mark :: * -> *) (w :: *) (a :: *) WriteOnly :: Pair w a -> WriteOnly [unWriteOnly] :: WriteOnly -> Pair w a -- | Concrete monad representing catastrophic failure mark e and -- producing values of type a data Halt (mark :: * -> *) (a :: *) -- | Proceed Step :: a -> Halt -- | Bail out Halt :: Halt -- | Concrete append-only state monad with state type w newtype AppendOnly (mark :: * -> *) (w :: *) (a :: *) AppendOnly :: (w -> Pair w a) -> AppendOnly -- | f = unAppendOnly x must have the property that if f w1 = -- Pair w2 a, then there exists w such that w2 == w1 -- <> w. This cannot be enforced by the type, but the class -- instance methods for AppendOnly all preserve it. [unAppendOnly] :: AppendOnly -> w -> Pair w a -- | Concrete write-once state monad newtype WriteOnce (mark :: * -> *) (w :: *) (a :: *) WriteOnce :: (LeftZero w -> Pair (LeftZero w) a) -> WriteOnce [unWriteOnce] :: WriteOnce -> LeftZero w -> Pair (LeftZero w) a -- | Concrete identity monad transformer newtype IdentityT (m :: * -> *) (a :: *) IdentityT :: m a -> IdentityT [unIdentityT] :: IdentityT -> m a runIdentityT :: Monad m => IdentityT m a -> m (Identity a) -- | Class representing monad transformers which can be composed on top of -- an arbitrary monad transformer. class (MonadTrans t1) => ComposableT t1 where { -- | Concrete composite monad transformer data family ComposeT (t1 :: (* -> *) -> * -> *) (t2 :: (* -> *) -> * -> *) (m :: * -> *) (a :: *); } toComposeT :: ComposableT t1 => t1 (t2 m) a -> ComposeT t1 t2 m a unComposeT :: ComposableT t1 => ComposeT t1 t2 m a -> t1 (t2 m) a -- | Concrete ReadOnly monad transformer newtype ReadOnlyT (mark :: * -> *) (r :: *) (m :: * -> *) (a :: *) ReadOnlyT :: ReadOnly mark r (m a) -> ReadOnlyT [unReadOnlyT] :: ReadOnlyT -> ReadOnly mark r (m a) runReadOnlyT :: (Monad m, MonadIdentity mark, Commutant mark) => mark r -> ReadOnlyT mark r m a -> m (mark a) -- | Concrete State monad transformer newtype StateT (mark :: * -> *) (s :: *) (m :: * -> *) (a :: *) StateT :: (s -> m (Pair s a)) -> StateT [unStateT] :: StateT -> s -> m (Pair s a) runStateT :: (Monad m, MonadIdentity mark) => mark s -> StateT mark s m a -> m (Pair (mark s) a) -- | Concrete Maybe monad transformer newtype HaltT (mark :: * -> *) (m :: * -> *) (a :: *) HaltT :: m (Halt mark a) -> HaltT [unHaltT] :: HaltT -> m (Halt mark a) runHaltT :: (Monad m, MonadIdentity mark) => HaltT mark m a -> m (Halt mark a) -- | Concrete exception monad transformer newtype ExceptT (mark :: * -> *) (e :: *) (m :: * -> *) (a :: *) ExceptT :: m (Except mark e a) -> ExceptT [unExceptT] :: ExceptT -> m (Except mark e a) runExceptT :: (Monad m, MonadIdentity mark) => ExceptT mark e m a -> m (Except mark e a) -- | Concrete write-only state monad transformer newtype WriteOnlyT (mark :: * -> *) (w :: *) (m :: * -> *) (a :: *) WriteOnlyT :: m (WriteOnly mark w a) -> WriteOnlyT [unWriteOnlyT] :: WriteOnlyT -> m (WriteOnly mark w a) runWriteOnlyT :: (Monad m, MonadIdentity mark, Monoid w) => WriteOnlyT mark w m a -> m (Pair (mark w) a) -- | Concrete State monad transformer newtype WriteOnceT (mark :: * -> *) (w :: *) (m :: * -> *) (a :: *) WriteOnceT :: (LeftZero w -> m (Pair (LeftZero w) a)) -> WriteOnceT [unWriteOnceT] :: WriteOnceT -> LeftZero w -> m (Pair (LeftZero w) a) runWriteOnceT :: (Monad m, MonadIdentity mark) => WriteOnceT mark w m a -> m (Pair (mark (Maybe w)) a) -- | Concrete State monad transformer newtype AppendOnlyT (mark :: * -> *) (w :: *) (m :: * -> *) (a :: *) AppendOnlyT :: (w -> m (Pair w a)) -> AppendOnlyT [unAppendOnlyT] :: AppendOnlyT -> w -> m (Pair w a) runAppendOnlyT :: (Monad m, MonadIdentity mark, Monoid w) => AppendOnlyT mark w m a -> m (Pair (mark w) a) -- | Concrete identity monad transformer transformer data IdentityTT (t :: (* -> *) -> * -> *) (m :: * -> *) (a :: *) IdentityTT :: t m a -> IdentityTT [unIdentityTT] :: IdentityTT -> t m a runIdentityTT :: (Monad m, MonadTrans t) => IdentityTT t m a -> t m (Identity a) -- | Concrete prompt monad transformer transformer data PromptTT (mark :: * -> *) (p :: * -> *) (t :: (* -> *) -> * -> *) (m :: * -> *) (a :: *) PromptTT :: (forall v. (a -> t m v) -> (forall u. p u -> (u -> t m v) -> t m v) -> t m v) -> PromptTT [unPromptTT] :: PromptTT -> forall v. (a -> t m v) -> (forall u. p u -> (u -> t m v) -> t m v) -> t m v runPromptTT :: (Monad m, MonadTrans t, MonadIdentity mark, Commutant mark) => Eval p m -> PromptTT mark p t m a -> t m (mark a) -- | Helper type for running prompt computations data Eval (p :: * -> *) (m :: * -> *) Eval :: (forall u. p u -> m u) -> Eval [unEval] :: Eval -> forall u. p u -> m u runOverTT :: (RunMonadTransTrans u, RunMonadTrans v, OverableT v, Monad m, MonadTrans t, MonadTrans v) => InputTT u m -> InputT v -> OverTT v u t m a -> t m (OutputTT u (OutputT v a)) class (MonadTrans v) => OverableT v where { -- | Concrete monad transformer transformer which applies a monad functor data family OverTT (v :: (* -> *) -> * -> *) (u :: ((* -> *) -> * -> *) -> (* -> *) -> * -> *) (t :: (* -> *) -> * -> *) (m :: * -> *) (a :: *); } toOverTT :: OverableT v => v (u t m) a -> OverTT v u t m a unOverTT :: OverableT v => OverTT v u t m a -> v (u t m) a newtype StateTT (mark :: * -> *) (s :: *) (t :: (* -> *) -> * -> *) (m :: * -> *) (a :: *) StateTT :: StateT mark s (t m) a -> StateTT [unStateTT] :: StateTT -> StateT mark s (t m) a runStateTT :: (MonadIdentity mark, Monad m, MonadTrans t) => mark s -> StateTT mark s t m a -> t m (Pair (mark s) a) newtype ReadOnlyTT (mark :: * -> *) (r :: *) (t :: (* -> *) -> * -> *) (m :: * -> *) (a :: *) ReadOnlyTT :: ReadOnlyT mark r (t m) a -> ReadOnlyTT [unReadOnlyTT] :: ReadOnlyTT -> ReadOnlyT mark r (t m) a runReadOnlyTT :: (MonadIdentity mark, Commutant mark, Monad m, MonadTrans t) => mark r -> ReadOnlyTT mark r t m a -> t m (mark a) newtype WriteOnlyTT (mark :: * -> *) (w :: *) (t :: (* -> *) -> * -> *) (m :: * -> *) (a :: *) WriteOnlyTT :: WriteOnlyT mark w (t m) a -> WriteOnlyTT [unWriteOnlyTT] :: WriteOnlyTT -> WriteOnlyT mark w (t m) a runWriteOnlyTT :: (MonadIdentity mark, Monad m, MonadTrans t, Monoid w) => mark () -> WriteOnlyTT mark w t m a -> t m (Pair (mark w) a) newtype ExceptTT (mark :: * -> *) (e :: *) (t :: (* -> *) -> * -> *) (m :: * -> *) (a :: *) ExceptTT :: ExceptT mark e (t m) a -> ExceptTT [unExceptTT] :: ExceptTT -> ExceptT mark e (t m) a runExceptTT :: (MonadIdentity mark, Monad m, MonadTrans t) => mark () -> ExceptTT mark e t m a -> t m (Except mark e a) newtype HaltTT (mark :: * -> *) (t :: (* -> *) -> * -> *) (m :: * -> *) (a :: *) HaltTT :: HaltT mark (t m) a -> HaltTT [unHaltTT] :: HaltTT -> HaltT mark (t m) a runHaltTT :: (Monad m, MonadTrans t, MonadIdentity mark) => HaltTT mark t m a -> t m (Halt mark a) newtype AppendOnlyTT (mark :: * -> *) (w :: *) (t :: (* -> *) -> * -> *) (m :: * -> *) (a :: *) AppendOnlyTT :: AppendOnlyT mark w (t m) a -> AppendOnlyTT [unAppendOnlyTT] :: AppendOnlyTT -> AppendOnlyT mark w (t m) a runAppendOnlyTT :: (MonadIdentity mark, Monad m, MonadTrans t, Monoid w) => mark () -> AppendOnlyTT mark w t m a -> t m (Pair (mark w) a) newtype WriteOnceTT (mark :: * -> *) (w :: *) (t :: (* -> *) -> * -> *) (m :: * -> *) (a :: *) WriteOnceTT :: WriteOnceT mark w (t m) a -> WriteOnceTT [unWriteOnceTT] :: WriteOnceTT -> WriteOnceT mark w (t m) a runWriteOnceTT :: (MonadIdentity mark, Monad m, MonadTrans t) => mark () -> WriteOnceTT mark w t m a -> t m (Pair (mark (Maybe w)) a) -- | Class representing monads that can be "run" inside some context -- z, producing a value in some result context f. class (Monad m) => RunMonad m where { data family Input m :: *; data family Output m :: * -> *; } -- | Run a monadic computation in context run :: RunMonad m => Input m -> m a -> Output m a -- | Class representing monad transformers which can be run in an input -- context, producting a monadic value in an output context. class (MonadTrans t) => RunMonadTrans t where { data family InputT t :: *; data family OutputT t :: * -> *; } runT :: (RunMonadTrans t, Monad m) => InputT t -> t m a -> m (OutputT t a) -- | Class representing monad transformer transformers which can be "run" -- in a context z m, producing a value in context t m (f -- a). class (MonadTransTrans u) => RunMonadTransTrans u where { data family InputTT u (m :: * -> *) :: *; data family OutputTT u :: * -> *; } runTT :: (RunMonadTransTrans u, Monad m, MonadTrans t) => InputTT u m -> u t m a -> t m (OutputTT u a) -- | Class representing types which can be compared for equality within an -- environment. Instances should satisfy the following laws: -- --
--   (1) eqIn env x x  ===  True
--   
--   (2) eqIn env x y  ===  eqIn env y x
--   
--   (3) if (eqIn env x y) && (eqIn env y z) then eqIn env x z else True
--   
class EqIn (t :: * -> *) where { data family Context t; } eqIn :: (EqIn t, Eq a) => Context t -> t a -> t a -> Bool -- | The signature of catch from MonadExcept type Catch e m a = m a -> (e -> m a) -> m a -- | Class representing monad transformers through which catch -- from MonadExcept can be lifted. Instances should satisfy the -- following law: -- --
--   (1) lift (catch x h) === liftCatch catch (lift x) (lift . h)
--   
class (MonadTrans t, RunMonadTrans t) => LiftCatch t liftCatch :: (LiftCatch t, Monad m) => Catch e m (OutputT t a) -> Catch e (t m) a -- | Class representing monad transformer transformers through which -- catch from MonadExcept can be lifted. class (MonadTransTrans u, RunMonadTransTrans u) => LiftCatchT u liftCatchT :: (LiftCatchT u, Monad m, MonadTrans t) => (forall x. Catch e (t m) (OutputTT u x)) -> forall x. Catch e (u t m) x -- | The signature of draft from MonadWriteOnly type Draft w m a = m a -> m (Pair w a) -- | Class representing monad transformers through which draft -- from MonadWriteOnly can be lifted. Instances should satisfy -- the following law: -- --
--   (1) liftDraft draft (lift x) === lift (draft x)
--   
class (MonadTrans t, RunMonadTrans t) => LiftDraft t liftDraft :: (LiftDraft t, Monad m, Monoid w) => Draft w m (OutputT t a) -> Draft w (t m) a -- | Class representing monad transformer transformers through which -- draft from MonadWriteOnly can be lifted. class (MonadTransTrans u, RunMonadTransTrans u) => LiftDraftT u liftDraftT :: (LiftDraftT u, Monad m, MonadTrans t, Monoid w) => (forall x. Draft w (t m) (OutputTT u x)) -> forall x. Draft w (u t m) x -- | The signature of local from MonadReadOnly type Local r m a = (r -> r) -> m a -> m a -- | Class representing monad transformers through which local -- from MonadReadOnly can be lifted class (MonadTrans t, RunMonadTrans t) => LiftLocal t liftLocal :: (LiftLocal t, Monad m) => Local r m (OutputT t a) -> Local r (t m) a -- | Class representing monad transformer transformers through which -- local from MonadReadOnly can be lifted. class (MonadTransTrans u, RunMonadTransTrans u) => LiftLocalT u liftLocalT :: (LiftLocalT u, Monad m, MonadTrans t) => (forall x. Local r (t m) (OutputTT u x)) -> forall x. Local r (u t m) x -- | Class representing Functors which "commute" with every -- Applicative in a precise sense. Instances should satisfy the -- following law: -- --
--   (1) commute . fmap pure  ===  pure
--   
-- -- This looks a lot like the sequenceA function from -- Traversable, but that class entails a bunch of extra -- technology that we don't really need. -- -- The motivation for Commutant comes from the observation that -- most useful monads can be run to produce a "value", though in -- general that value will depend on some other context. In every case -- I've tried so far that context is a Commutant functor, which -- is enough to make a generic RunMonad instance for -- Compose. class (Functor d) => Commutant d commute :: (Commutant d, Applicative f) => d (f a) -> f (d a) -- | Class representing monads that commute with every other monad. -- Instances should satisfy the following laws: -- --
--   (1) commute . return === fmap return
--   
--   (2) commute . join === fmap join . commute . fmap commute
--   
--   (3) commute . fmap join === join . fmap commute . commute
--   
class (Commutant c, Monad c) => Central c -- | Class representing bifunctors on the category of types. Instances -- should satisfy the following laws: -- --
--   (1) bimap1 id  ===  id
--   
--   (2) bimap1 (f . g)  ===  bimap1 f . bimap1 g
--   
--   (3) bimap2 id  ===  id
--   
--   (4) bimap2 (f . g)  ===  bimap2 f . bimap2 g
--   
--   (5) bimap1 f . bimap2 g  ===  bimap2 g . bimap1 f
--   
class Bifunctor (f :: * -> * -> *) -- | fmap in the "first" component bimap1 :: Bifunctor f => (a -> c) -> f a b -> f c b -- | fmap in the "second" component bimap2 :: Bifunctor f => (b -> c) -> f a b -> f a c newtype Wrap f a Wrap :: f a -> Wrap f a [unWrap] :: Wrap f a -> f a class Renaming f namingMap :: Renaming f => a -> f a namingInv :: Renaming f => f a -> a -- | Tuple type, isomorphic to (a,b). This is here so we can have -- a partially applied tuple type Pair a without syntax hacks. data Pair (a :: *) (b :: *) Pair :: a -> b -> Pair [slot1] :: Pair -> a [slot2] :: Pair -> b -- | Type representing the left zero semigroup on a with an -- identity attached. As a functor LeftZero is isomorphic to -- Maybe. data LeftZero (a :: *) LeftZero :: a -> LeftZero LeftUnit :: LeftZero -- | Type representing the right zero semigroup on a with an -- identity attached. As a functor RightZero is isomorphic to -- Maybe. data RightZero (a :: *) RightZero :: a -> RightZero RightUnit :: RightZero -- | Class representing type constructors which are isomorphic to -- Maybe. Instances should satisfy the following laws: -- --
--   (1) toMaybe . fromMaybe  ==  id
--   
--   (2) fromMaybe . toMaybe  ==  id
--   
class IsMaybe (f :: * -> *) -- | Convert from Maybe a fromMaybe :: IsMaybe f => Maybe a -> f a -- | Convert to Maybe a toMaybe :: IsMaybe f => f a -> Maybe a -- | Class representing monad transformers class (forall m. (Monad m) => Monad (t m)) => MonadTrans (t :: (* -> *) -> * -> *) -- | Lift a computation from the inner monad to the transformed monad lift :: (MonadTrans t, Monad m) => m a -> t m a -- | Class representing monad functors class (MonadTrans t) => MonadFunctor t hoist :: (MonadFunctor t, Monad m, Monad n) => (forall u. m u -> n u) -> t m a -> t n a -- | Class representing monad transformer transformers class (forall t. (MonadTrans t) => MonadTrans (u t), forall t m. (Monad m, MonadTrans t) => Monad (u t m)) => MonadTransTrans (u :: ((* -> *) -> (* -> *)) -> (* -> *) -> * -> *) liftT :: (MonadTransTrans u, Monad m, MonadTrans t) => t m a -> u t m a