supermonad-0.1: Plugin and base library to support supermonads in Haskell

Safe HaskellNone
LanguageHaskell2010

Control.Supermonad

Contents

Description

Representation of supermonads in Haskell.

Synopsis

Supermonads

class (Functor m, Functor n, Functor p) => Bind m n p where Source #

Representation of bind operations for supermonads. A proper supermonad consists of an instance for Bind, Return and optionally Fail.

The instances are required to follow a certain scheme. If the type constructor of your supermonad is M there may only be exactly one Bind and one Return instance that look as follows:

instance Bind (M ...) (M ...) (M ...) where
  ...
instance Return (M ...) where
  ...

This is enforced by the plugin. A compilation error will result from either instance missing or multiple instances for M.

For supermonads we expect the usual monad laws to hold:

Minimal complete definition

(>>=)

Associated Types

type BindCts m n p :: Constraint Source #

Methods

(>>=) :: BindCts m n p => m a -> (a -> n b) -> p b Source #

(>>) :: BindCts m n p => m a -> n b -> p b Source #

Instances

Bind [] [] [] Source # 

Associated Types

type BindCts ([] :: * -> *) ([] :: * -> *) ([] :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts [] [] [] => [a] -> (a -> [b]) -> [b] Source #

(>>) :: BindCts [] [] [] => [a] -> [b] -> [b] Source #

Bind Maybe Maybe Maybe Source # 

Associated Types

type BindCts (Maybe :: * -> *) (Maybe :: * -> *) (Maybe :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts Maybe Maybe Maybe => Maybe a -> (a -> Maybe b) -> Maybe b Source #

(>>) :: BindCts Maybe Maybe Maybe => Maybe a -> Maybe b -> Maybe b Source #

Bind IO IO IO Source # 

Associated Types

type BindCts (IO :: * -> *) (IO :: * -> *) (IO :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts IO IO IO => IO a -> (a -> IO b) -> IO b Source #

(>>) :: BindCts IO IO IO => IO a -> IO b -> IO b Source #

Bind Identity Identity Identity Source # 

Associated Types

type BindCts (Identity :: * -> *) (Identity :: * -> *) (Identity :: * -> *) :: Constraint Source #

Bind Min Min Min Source # 

Associated Types

type BindCts (Min :: * -> *) (Min :: * -> *) (Min :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts Min Min Min => Min a -> (a -> Min b) -> Min b Source #

(>>) :: BindCts Min Min Min => Min a -> Min b -> Min b Source #

Bind Max Max Max Source # 

Associated Types

type BindCts (Max :: * -> *) (Max :: * -> *) (Max :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts Max Max Max => Max a -> (a -> Max b) -> Max b Source #

(>>) :: BindCts Max Max Max => Max a -> Max b -> Max b Source #

Bind First First First Source # 

Associated Types

type BindCts (First :: * -> *) (First :: * -> *) (First :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts First First First => First a -> (a -> First b) -> First b Source #

(>>) :: BindCts First First First => First a -> First b -> First b Source #

Bind Last Last Last Source # 

Associated Types

type BindCts (Last :: * -> *) (Last :: * -> *) (Last :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts Last Last Last => Last a -> (a -> Last b) -> Last b Source #

(>>) :: BindCts Last Last Last => Last a -> Last b -> Last b Source #

Bind Option Option Option Source # 

Associated Types

type BindCts (Option :: * -> *) (Option :: * -> *) (Option :: * -> *) :: Constraint Source #

Bind NonEmpty NonEmpty NonEmpty Source # 

Associated Types

type BindCts (NonEmpty :: * -> *) (NonEmpty :: * -> *) (NonEmpty :: * -> *) :: Constraint Source #

Bind Complex Complex Complex Source # 

Associated Types

type BindCts (Complex :: * -> *) (Complex :: * -> *) (Complex :: * -> *) :: Constraint Source #

Bind STM STM STM Source # 

Associated Types

type BindCts (STM :: * -> *) (STM :: * -> *) (STM :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts STM STM STM => STM a -> (a -> STM b) -> STM b Source #

(>>) :: BindCts STM STM STM => STM a -> STM b -> STM b Source #

Bind Dual Dual Dual Source # 

Associated Types

type BindCts (Dual :: * -> *) (Dual :: * -> *) (Dual :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts Dual Dual Dual => Dual a -> (a -> Dual b) -> Dual b Source #

(>>) :: BindCts Dual Dual Dual => Dual a -> Dual b -> Dual b Source #

Bind Sum Sum Sum Source # 

Associated Types

type BindCts (Sum :: * -> *) (Sum :: * -> *) (Sum :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts Sum Sum Sum => Sum a -> (a -> Sum b) -> Sum b Source #

(>>) :: BindCts Sum Sum Sum => Sum a -> Sum b -> Sum b Source #

Bind Product Product Product Source # 

Associated Types

type BindCts (Product :: * -> *) (Product :: * -> *) (Product :: * -> *) :: Constraint Source #

Bind First First First Source # 

Associated Types

type BindCts (First :: * -> *) (First :: * -> *) (First :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts First First First => First a -> (a -> First b) -> First b Source #

(>>) :: BindCts First First First => First a -> First b -> First b Source #

Bind Last Last Last Source # 

Associated Types

type BindCts (Last :: * -> *) (Last :: * -> *) (Last :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts Last Last Last => Last a -> (a -> Last b) -> Last b Source #

(>>) :: BindCts Last Last Last => Last a -> Last b -> Last b Source #

Bind ReadPrec ReadPrec ReadPrec Source # 

Associated Types

type BindCts (ReadPrec :: * -> *) (ReadPrec :: * -> *) (ReadPrec :: * -> *) :: Constraint Source #

Bind ReadP ReadP ReadP Source # 

Associated Types

type BindCts (ReadP :: * -> *) (ReadP :: * -> *) (ReadP :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts ReadP ReadP ReadP => ReadP a -> (a -> ReadP b) -> ReadP b Source #

(>>) :: BindCts ReadP ReadP ReadP => ReadP a -> ReadP b -> ReadP b Source #

Bind ((->) r) ((->) r) ((->) r) Source # 

Associated Types

type BindCts ((->) r :: * -> *) ((->) r :: * -> *) ((->) r :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts ((->) r) ((->) r) ((->) r) => (r -> a) -> (a -> r -> b) -> r -> b Source #

(>>) :: BindCts ((->) r) ((->) r) ((->) r) => (r -> a) -> (r -> b) -> r -> b Source #

Bind (Either e) (Either e) (Either e) Source # 

Associated Types

type BindCts (Either e :: * -> *) (Either e :: * -> *) (Either e :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (Either e) (Either e) (Either e) => Either e a -> (a -> Either e b) -> Either e b Source #

(>>) :: BindCts (Either e) (Either e) (Either e) => Either e a -> Either e b -> Either e b Source #

Bind (ST s) (ST s) (ST s) Source # 

Associated Types

type BindCts (ST s :: * -> *) (ST s :: * -> *) (ST s :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (ST s) (ST s) (ST s) => ST s a -> (a -> ST s b) -> ST s b Source #

(>>) :: BindCts (ST s) (ST s) (ST s) => ST s a -> ST s b -> ST s b Source #

Bind (ST s) (ST s) (ST s) Source # 

Associated Types

type BindCts (ST s :: * -> *) (ST s :: * -> *) (ST s :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (ST s) (ST s) (ST s) => ST s a -> (a -> ST s b) -> ST s b Source #

(>>) :: BindCts (ST s) (ST s) (ST s) => ST s a -> ST s b -> ST s b Source #

(Bind m m m, Monad m) => Bind (WrappedMonad m) (WrappedMonad m) (WrappedMonad m) Source #

TODO / FIXME: The wrapped monad instances for Functor and Monad are both based on m being a monad, although the functor instance should only be dependend on m being a functor (as can be seen below). This can only be fixed by either giving a custom version of WrappedMonad here or by fixing the version of WrappedMonad in base. Once this issue is fixed we can replace the Monad constraint with a Functor constraint.

instance (Functor m) => Functor (App.WrappedMonad m) where
  fmap f m = App.WrapMonad $ fmap (App.unwrapMonad m) f

Associated Types

type BindCts (WrappedMonad m :: * -> *) (WrappedMonad m :: * -> *) (WrappedMonad m :: * -> *) :: Constraint Source #

ArrowApply a => Bind (ArrowMonad a) (ArrowMonad a) (ArrowMonad a) Source # 

Associated Types

type BindCts (ArrowMonad a :: * -> *) (ArrowMonad a :: * -> *) (ArrowMonad a :: * -> *) :: Constraint Source #

Bind (Proxy *) (Proxy *) (Proxy *) Source # 

Associated Types

type BindCts (Proxy * :: * -> *) (Proxy * :: * -> *) (Proxy * :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (Proxy *) (Proxy *) (Proxy *) => Proxy * a -> (a -> Proxy * b) -> Proxy * b Source #

(>>) :: BindCts (Proxy *) (Proxy *) (Proxy *) => Proxy * a -> Proxy * b -> Proxy * b Source #

(Return n, Bind m n p) => Bind (MaybeT m) (MaybeT n) (MaybeT p) Source # 

Associated Types

type BindCts (MaybeT m :: * -> *) (MaybeT n :: * -> *) (MaybeT p :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (MaybeT m) (MaybeT n) (MaybeT p) => MaybeT m a -> (a -> MaybeT n b) -> MaybeT p b Source #

(>>) :: BindCts (MaybeT m) (MaybeT n) (MaybeT p) => MaybeT m a -> MaybeT n b -> MaybeT p b Source #

(Bind m n p, Bind n n n, Return n) => Bind (ListT m) (ListT n) (ListT p) Source # 

Associated Types

type BindCts (ListT m :: * -> *) (ListT n :: * -> *) (ListT p :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (ListT m) (ListT n) (ListT p) => ListT m a -> (a -> ListT n b) -> ListT p b Source #

(>>) :: BindCts (ListT m) (ListT n) (ListT p) => ListT m a -> ListT n b -> ListT p b Source #

Bind m n p => Bind (Alt * m) (Alt * n) (Alt * p) Source # 

Associated Types

type BindCts (Alt * m :: * -> *) (Alt * n :: * -> *) (Alt * p :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (Alt * m) (Alt * n) (Alt * p) => Alt * m a -> (a -> Alt * n b) -> Alt * p b Source #

(>>) :: BindCts (Alt * m) (Alt * n) (Alt * p) => Alt * m a -> Alt * n b -> Alt * p b Source #

(Bind m n p, Return n) => Bind (ExceptT e m) (ExceptT e n) (ExceptT e p) Source # 

Associated Types

type BindCts (ExceptT e m :: * -> *) (ExceptT e n :: * -> *) (ExceptT e p :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (ExceptT e m) (ExceptT e n) (ExceptT e p) => ExceptT e m a -> (a -> ExceptT e n b) -> ExceptT e p b Source #

(>>) :: BindCts (ExceptT e m) (ExceptT e n) (ExceptT e p) => ExceptT e m a -> ExceptT e n b -> ExceptT e p b Source #

Bind m n p => Bind (StateT s m) (StateT s n) (StateT s p) Source # 

Associated Types

type BindCts (StateT s m :: * -> *) (StateT s n :: * -> *) (StateT s p :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (StateT s m) (StateT s n) (StateT s p) => StateT s m a -> (a -> StateT s n b) -> StateT s p b Source #

(>>) :: BindCts (StateT s m) (StateT s n) (StateT s p) => StateT s m a -> StateT s n b -> StateT s p b Source #

Bind m n p => Bind (StateT s m) (StateT s n) (StateT s p) Source # 

Associated Types

type BindCts (StateT s m :: * -> *) (StateT s n :: * -> *) (StateT s p :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (StateT s m) (StateT s n) (StateT s p) => StateT s m a -> (a -> StateT s n b) -> StateT s p b Source #

(>>) :: BindCts (StateT s m) (StateT s n) (StateT s p) => StateT s m a -> StateT s n b -> StateT s p b Source #

(Monoid w, Bind m n p) => Bind (WriterT w m) (WriterT w n) (WriterT w p) Source # 

Associated Types

type BindCts (WriterT w m :: * -> *) (WriterT w n :: * -> *) (WriterT w p :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (WriterT w m) (WriterT w n) (WriterT w p) => WriterT w m a -> (a -> WriterT w n b) -> WriterT w p b Source #

(>>) :: BindCts (WriterT w m) (WriterT w n) (WriterT w p) => WriterT w m a -> WriterT w n b -> WriterT w p b Source #

(Monoid w, Bind m n p) => Bind (WriterT w m) (WriterT w n) (WriterT w p) Source # 

Associated Types

type BindCts (WriterT w m :: * -> *) (WriterT w n :: * -> *) (WriterT w p :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (WriterT w m) (WriterT w n) (WriterT w p) => WriterT w m a -> (a -> WriterT w n b) -> WriterT w p b Source #

(>>) :: BindCts (WriterT w m) (WriterT w n) (WriterT w p) => WriterT w m a -> WriterT w n b -> WriterT w p b Source #

Bind m n p => Bind (IdentityT * m) (IdentityT * n) (IdentityT * p) Source # 

Associated Types

type BindCts (IdentityT * m :: * -> *) (IdentityT * n :: * -> *) (IdentityT * p :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (IdentityT * m) (IdentityT * n) (IdentityT * p) => IdentityT * m a -> (a -> IdentityT * n b) -> IdentityT * p b Source #

(>>) :: BindCts (IdentityT * m) (IdentityT * n) (IdentityT * p) => IdentityT * m a -> IdentityT * n b -> IdentityT * p b Source #

(Bind m1 n1 p1, Bind m2 n2 p2) => Bind (Product * m1 m2) (Product * n1 n2) (Product * p1 p2) Source # 

Associated Types

type BindCts (Product * m1 m2 :: * -> *) (Product * n1 n2 :: * -> *) (Product * p1 p2 :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (Product * m1 m2) (Product * n1 n2) (Product * p1 p2) => Product * m1 m2 a -> (a -> Product * n1 n2 b) -> Product * p1 p2 b Source #

(>>) :: BindCts (Product * m1 m2) (Product * n1 n2) (Product * p1 p2) => Product * m1 m2 a -> Product * n1 n2 b -> Product * p1 p2 b Source #

Bind (ContT * r m) (ContT * r m) (ContT * r m) Source #

TODO / FIXME: Still need to figure out how and if we can generalize the continuation implementation.

Associated Types

type BindCts (ContT * r m :: * -> *) (ContT * r m :: * -> *) (ContT * r m :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (ContT * r m) (ContT * r m) (ContT * r m) => ContT * r m a -> (a -> ContT * r m b) -> ContT * r m b Source #

(>>) :: BindCts (ContT * r m) (ContT * r m) (ContT * r m) => ContT * r m a -> ContT * r m b -> ContT * r m b Source #

Bind m n p => Bind (ReaderT * r m) (ReaderT * r n) (ReaderT * r p) Source # 

Associated Types

type BindCts (ReaderT * r m :: * -> *) (ReaderT * r n :: * -> *) (ReaderT * r p :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (ReaderT * r m) (ReaderT * r n) (ReaderT * r p) => ReaderT * r m a -> (a -> ReaderT * r n b) -> ReaderT * r p b Source #

(>>) :: BindCts (ReaderT * r m) (ReaderT * r n) (ReaderT * r p) => ReaderT * r m a -> ReaderT * r n b -> ReaderT * r p b Source #

(Monoid w, Bind m n p) => Bind (RWST r w s m) (RWST r w s n) (RWST r w s p) Source # 

Associated Types

type BindCts (RWST r w s m :: * -> *) (RWST r w s n :: * -> *) (RWST r w s p :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (RWST r w s m) (RWST r w s n) (RWST r w s p) => RWST r w s m a -> (a -> RWST r w s n b) -> RWST r w s p b Source #

(>>) :: BindCts (RWST r w s m) (RWST r w s n) (RWST r w s p) => RWST r w s m a -> RWST r w s n b -> RWST r w s p b Source #

(Monoid w, Bind m n p) => Bind (RWST r w s m) (RWST r w s n) (RWST r w s p) Source # 

Associated Types

type BindCts (RWST r w s m :: * -> *) (RWST r w s n :: * -> *) (RWST r w s p :: * -> *) :: Constraint Source #

Methods

(>>=) :: BindCts (RWST r w s m) (RWST r w s n) (RWST r w s p) => RWST r w s m a -> (a -> RWST r w s n b) -> RWST r w s p b Source #

(>>) :: BindCts (RWST r w s m) (RWST r w s n) (RWST r w s p) => RWST r w s m a -> RWST r w s n b -> RWST r w s p b Source #

class Functor m => Return m where Source #

See Bind for details on laws and requirements.

Minimal complete definition

return

Associated Types

type ReturnCts m :: Constraint Source #

Methods

return :: ReturnCts m => a -> m a Source #

Instances

Return [] Source # 

Associated Types

type ReturnCts ([] :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts [] => a -> [a] Source #

Return Maybe Source # 

Associated Types

type ReturnCts (Maybe :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts Maybe => a -> Maybe a Source #

Return IO Source # 

Associated Types

type ReturnCts (IO :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts IO => a -> IO a Source #

Return Identity Source # 

Associated Types

type ReturnCts (Identity :: * -> *) :: Constraint Source #

Return Min Source # 

Associated Types

type ReturnCts (Min :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts Min => a -> Min a Source #

Return Max Source # 

Associated Types

type ReturnCts (Max :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts Max => a -> Max a Source #

Return First Source # 

Associated Types

type ReturnCts (First :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts First => a -> First a Source #

Return Last Source # 

Associated Types

type ReturnCts (Last :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts Last => a -> Last a Source #

Return Option Source # 

Associated Types

type ReturnCts (Option :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts Option => a -> Option a Source #

Return NonEmpty Source # 

Associated Types

type ReturnCts (NonEmpty :: * -> *) :: Constraint Source #

Return Complex Source # 

Associated Types

type ReturnCts (Complex :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts Complex => a -> Complex a Source #

Return STM Source # 

Associated Types

type ReturnCts (STM :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts STM => a -> STM a Source #

Return Dual Source # 

Associated Types

type ReturnCts (Dual :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts Dual => a -> Dual a Source #

Return Sum Source # 

Associated Types

type ReturnCts (Sum :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts Sum => a -> Sum a Source #

Return Product Source # 

Associated Types

type ReturnCts (Product :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts Product => a -> Product a Source #

Return First Source # 

Associated Types

type ReturnCts (First :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts First => a -> First a Source #

Return Last Source # 

Associated Types

type ReturnCts (Last :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts Last => a -> Last a Source #

Return ReadPrec Source # 

Associated Types

type ReturnCts (ReadPrec :: * -> *) :: Constraint Source #

Return ReadP Source # 

Associated Types

type ReturnCts (ReadP :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts ReadP => a -> ReadP a Source #

Return ((->) r) Source # 

Associated Types

type ReturnCts ((->) r :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts ((->) r) => a -> r -> a Source #

Return (Either e) Source # 

Associated Types

type ReturnCts (Either e :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (Either e) => a -> Either e a Source #

Return (ST s) Source # 

Associated Types

type ReturnCts (ST s :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (ST s) => a -> ST s a Source #

Return (ST s) Source # 

Associated Types

type ReturnCts (ST s :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (ST s) => a -> ST s a Source #

(Return m, Monad m) => Return (WrappedMonad m) Source #

TODO / FIXME: This has the same issue as the Bind instance for WrappedMonad.

Associated Types

type ReturnCts (WrappedMonad m :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (WrappedMonad m) => a -> WrappedMonad m a Source #

ArrowApply a => Return (ArrowMonad a) Source # 

Associated Types

type ReturnCts (ArrowMonad a :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (ArrowMonad a) => a -> ArrowMonad a a Source #

Return (Proxy *) Source # 

Associated Types

type ReturnCts (Proxy * :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (Proxy *) => a -> Proxy * a Source #

Return m => Return (MaybeT m) Source # 

Associated Types

type ReturnCts (MaybeT m :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (MaybeT m) => a -> MaybeT m a Source #

Return m => Return (ListT m) Source # 

Associated Types

type ReturnCts (ListT m :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (ListT m) => a -> ListT m a Source #

Return a => Return (Alt * a) Source # 

Associated Types

type ReturnCts (Alt * a :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (Alt * a) => a -> Alt * a a Source #

Return m => Return (ExceptT e m) Source # 

Associated Types

type ReturnCts (ExceptT e m :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (ExceptT e m) => a -> ExceptT e m a Source #

Return m => Return (StateT s m) Source # 

Associated Types

type ReturnCts (StateT s m :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (StateT s m) => a -> StateT s m a Source #

Return m => Return (StateT s m) Source # 

Associated Types

type ReturnCts (StateT s m :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (StateT s m) => a -> StateT s m a Source #

(Monoid w, Return m) => Return (WriterT w m) Source # 

Associated Types

type ReturnCts (WriterT w m :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (WriterT w m) => a -> WriterT w m a Source #

(Monoid w, Return m) => Return (WriterT w m) Source # 

Associated Types

type ReturnCts (WriterT w m :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (WriterT w m) => a -> WriterT w m a Source #

Return m => Return (IdentityT * m) Source # 

Associated Types

type ReturnCts (IdentityT * m :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (IdentityT * m) => a -> IdentityT * m a Source #

(Return m1, Return m2) => Return (Product * m1 m2) Source # 

Associated Types

type ReturnCts (Product * m1 m2 :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (Product * m1 m2) => a -> Product * m1 m2 a Source #

Return (ContT * r m) Source # 

Associated Types

type ReturnCts (ContT * r m :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (ContT * r m) => a -> ContT * r m a Source #

Return m => Return (ReaderT * r m) Source # 

Associated Types

type ReturnCts (ReaderT * r m :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (ReaderT * r m) => a -> ReaderT * r m a Source #

(Monoid w, Return m) => Return (RWST r w s m) Source # 

Associated Types

type ReturnCts (RWST r w s m :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (RWST r w s m) => a -> RWST r w s m a Source #

(Monoid w, Return m) => Return (RWST r w s m) Source # 

Associated Types

type ReturnCts (RWST r w s m :: * -> *) :: Constraint Source #

Methods

return :: ReturnCts (RWST r w s m) => a -> RWST r w s m a Source #

class Fail m where Source #

See Bind for details on laws and requirements.

Minimal complete definition

fail

Associated Types

type FailCts m :: Constraint Source #

Methods

fail :: FailCts m => String -> m a Source #

Instances

Fail [] Source # 

Associated Types

type FailCts ([] :: * -> *) :: Constraint Source #

Methods

fail :: FailCts [] => String -> [a] Source #

Fail Maybe Source # 

Associated Types

type FailCts (Maybe :: * -> *) :: Constraint Source #

Methods

fail :: FailCts Maybe => String -> Maybe a Source #

Fail IO Source # 

Associated Types

type FailCts (IO :: * -> *) :: Constraint Source #

Methods

fail :: FailCts IO => String -> IO a Source #

Fail Identity Source # 

Associated Types

type FailCts (Identity :: * -> *) :: Constraint Source #

Fail Min Source # 

Associated Types

type FailCts (Min :: * -> *) :: Constraint Source #

Methods

fail :: FailCts Min => String -> Min a Source #

Fail Max Source # 

Associated Types

type FailCts (Max :: * -> *) :: Constraint Source #

Methods

fail :: FailCts Max => String -> Max a Source #

Fail First Source # 

Associated Types

type FailCts (First :: * -> *) :: Constraint Source #

Methods

fail :: FailCts First => String -> First a Source #

Fail Last Source # 

Associated Types

type FailCts (Last :: * -> *) :: Constraint Source #

Methods

fail :: FailCts Last => String -> Last a Source #

Fail Option Source # 

Associated Types

type FailCts (Option :: * -> *) :: Constraint Source #

Methods

fail :: FailCts Option => String -> Option a Source #

Fail NonEmpty Source # 

Associated Types

type FailCts (NonEmpty :: * -> *) :: Constraint Source #

Fail Complex Source # 

Associated Types

type FailCts (Complex :: * -> *) :: Constraint Source #

Fail STM Source # 

Associated Types

type FailCts (STM :: * -> *) :: Constraint Source #

Methods

fail :: FailCts STM => String -> STM a Source #

Fail Dual Source # 

Associated Types

type FailCts (Dual :: * -> *) :: Constraint Source #

Methods

fail :: FailCts Dual => String -> Dual a Source #

Fail Sum Source # 

Associated Types

type FailCts (Sum :: * -> *) :: Constraint Source #

Methods

fail :: FailCts Sum => String -> Sum a Source #

Fail Product Source # 

Associated Types

type FailCts (Product :: * -> *) :: Constraint Source #

Fail First Source # 

Associated Types

type FailCts (First :: * -> *) :: Constraint Source #

Methods

fail :: FailCts First => String -> First a Source #

Fail Last Source # 

Associated Types

type FailCts (Last :: * -> *) :: Constraint Source #

Methods

fail :: FailCts Last => String -> Last a Source #

Fail ReadPrec Source # 

Associated Types

type FailCts (ReadPrec :: * -> *) :: Constraint Source #

Fail ReadP Source # 

Associated Types

type FailCts (ReadP :: * -> *) :: Constraint Source #

Methods

fail :: FailCts ReadP => String -> ReadP a Source #

Fail ((->) r) Source # 

Associated Types

type FailCts ((->) r :: * -> *) :: Constraint Source #

Methods

fail :: FailCts ((->) r) => String -> r -> a Source #

Fail (Either e) Source # 

Associated Types

type FailCts (Either e :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (Either e) => String -> Either e a Source #

Fail (ST s) Source # 

Associated Types

type FailCts (ST s :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (ST s) => String -> ST s a Source #

Fail (ST s) Source # 

Associated Types

type FailCts (ST s :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (ST s) => String -> ST s a Source #

(Fail m, Monad m) => Fail (WrappedMonad m) Source #

TODO / FIXME: This has the same issue as the Bind instance for WrappedMonad.

Associated Types

type FailCts (WrappedMonad m :: * -> *) :: Constraint Source #

ArrowApply a => Fail (ArrowMonad a) Source # 

Associated Types

type FailCts (ArrowMonad a :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (ArrowMonad a) => String -> ArrowMonad a a Source #

Fail (Proxy *) Source # 

Associated Types

type FailCts (Proxy * :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (Proxy *) => String -> Proxy * a Source #

Return m => Fail (MaybeT m) Source # 

Associated Types

type FailCts (MaybeT m :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (MaybeT m) => String -> MaybeT m a Source #

Return m => Fail (ListT m) Source # 

Associated Types

type FailCts (ListT m :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (ListT m) => String -> ListT m a Source #

Fail a => Fail (Alt * a) Source # 

Associated Types

type FailCts (Alt * a :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (Alt * a) => String -> Alt * a a Source #

Fail m => Fail (ExceptT e m) Source # 

Associated Types

type FailCts (ExceptT e m :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (ExceptT e m) => String -> ExceptT e m a Source #

Fail m => Fail (StateT s m) Source # 

Associated Types

type FailCts (StateT s m :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (StateT s m) => String -> StateT s m a Source #

Fail m => Fail (StateT s m) Source # 

Associated Types

type FailCts (StateT s m :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (StateT s m) => String -> StateT s m a Source #

(Monoid w, Fail m) => Fail (WriterT w m) Source # 

Associated Types

type FailCts (WriterT w m :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (WriterT w m) => String -> WriterT w m a Source #

(Monoid w, Fail m) => Fail (WriterT w m) Source # 

Associated Types

type FailCts (WriterT w m :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (WriterT w m) => String -> WriterT w m a Source #

Fail m => Fail (IdentityT * m) Source # 

Associated Types

type FailCts (IdentityT * m :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (IdentityT * m) => String -> IdentityT * m a Source #

(Fail m1, Fail m2) => Fail (Product * m1 m2) Source # 

Associated Types

type FailCts (Product * m1 m2 :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (Product * m1 m2) => String -> Product * m1 m2 a Source #

Fail m => Fail (ContT * r m) Source # 

Associated Types

type FailCts (ContT * r m :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (ContT * r m) => String -> ContT * r m a Source #

Fail m => Fail (ReaderT * r m) Source # 

Associated Types

type FailCts (ReaderT * r m :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (ReaderT * r m) => String -> ReaderT * r m a Source #

(Monoid w, Fail m) => Fail (RWST r w s m) Source # 

Associated Types

type FailCts (RWST r w s m :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (RWST r w s m) => String -> RWST r w s m a Source #

(Monoid w, Fail m) => Fail (RWST r w s m) Source # 

Associated Types

type FailCts (RWST r w s m :: * -> *) :: Constraint Source #

Methods

fail :: FailCts (RWST r w s m) => String -> RWST r w s m a Source #

Conveniences

type family Monad m :: Constraint where ... Source #

A short-hand for writing polymorphic standard monad functions.

Equations

Monad m = (Bind m m m, Return m, Fail m)