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

Safe HaskellNone
LanguageHaskell2010

Control.Supermonad.Constrained

Contents

Description

Definition of supermonads that support constrained monads.

Synopsis

Supermonads

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

See Control.Supermonad.Bind for details on laws and requirements.

Minimal complete definition

(>>=)

Associated Types

type BindCts m n p (a :: *) (b :: *) :: Constraint Source #

Methods

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

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

Instances

Bind [] [] [] Source # 

Associated Types

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

Methods

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

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

Bind Maybe Maybe Maybe Source # 

Associated Types

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

Methods

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

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

Bind IO IO IO Source # 

Associated Types

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

Methods

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

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

Bind Identity Identity Identity Source # 

Associated Types

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

Bind Min Min Min Source # 

Associated Types

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

Methods

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

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

Bind Max Max Max Source # 

Associated Types

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

Methods

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

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

Bind First First First Source # 

Associated Types

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

Methods

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

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

Bind Last Last Last Source # 

Associated Types

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

Methods

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

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

Bind Option Option Option Source # 

Associated Types

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

Methods

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

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

Bind NonEmpty NonEmpty NonEmpty Source # 

Associated Types

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

Bind Complex Complex Complex Source # 

Associated Types

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

Bind STM STM STM Source # 

Associated Types

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

Methods

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

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

Bind Dual Dual Dual Source # 

Associated Types

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

Methods

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

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

Bind Sum Sum Sum Source # 

Associated Types

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

Methods

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

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

Bind Product Product Product Source # 

Associated Types

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

Bind First First First Source # 

Associated Types

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

Methods

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

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

Bind Last Last Last Source # 

Associated Types

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

Methods

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

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

Bind ReadPrec ReadPrec ReadPrec Source # 

Associated Types

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

Bind ReadP ReadP ReadP Source # 

Associated Types

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

Methods

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

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

Bind Set Set Set Source # 

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

(>>) :: BindCts ((->) r) ((->) r) ((->) r) a b => (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 :: * -> *) a b :: Constraint Source #

Methods

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

(>>) :: BindCts (Either e) (Either e) (Either e) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

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

(>>) :: BindCts (ST s) (ST s) (ST s) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

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

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

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

Associated Types

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

(>>) :: BindCts (Proxy *) (Proxy *) (Proxy *) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

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

(>>) :: BindCts (MaybeT m) (MaybeT n) (MaybeT p) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

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

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

Bind f f f => Bind (Alt * f) (Alt * f) (Alt * f) Source # 

Associated Types

type BindCts (Alt * f :: * -> *) (Alt * f :: * -> *) (Alt * f :: * -> *) a b :: Constraint Source #

Methods

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

(>>) :: BindCts (Alt * f) (Alt * f) (Alt * f) a b => Alt * f a -> Alt * f b -> Alt * f 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 :: * -> *) a b :: Constraint Source #

Methods

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

(>>) :: BindCts (ExceptT e m) (ExceptT e n) (ExceptT e p) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

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

(>>) :: BindCts (StateT s m) (StateT s n) (StateT s p) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

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

(>>) :: BindCts (StateT s m) (StateT s n) (StateT s p) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

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

(>>) :: BindCts (WriterT w m) (WriterT w n) (WriterT w p) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

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

(>>) :: BindCts (WriterT w m) (WriterT w n) (WriterT w p) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

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

(>>) :: BindCts (IdentityT * m) (IdentityT * n) (IdentityT * p) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

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

(>>) :: BindCts (Product * m1 m2) (Product * n1 n2) (Product * p1 p2) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

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

(>>) :: BindCts (ContT * r m) (ContT * r m) (ContT * r m) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

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

(>>) :: BindCts (ReaderT * r m) (ReaderT * r n) (ReaderT * r p) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

(>>=) :: BindCts (RWST r w s m) (RWST r w s n) (RWST r w s p) a b => 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) a b => 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 :: * -> *) a b :: Constraint Source #

Methods

(>>=) :: BindCts (RWST r w s m) (RWST r w s n) (RWST r w s p) a b => 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) a b => RWST r w s m a -> RWST r w s n b -> RWST r w s p b Source #

class CFunctor m => Return m where Source #

See Bind for details on laws and requirements.

Minimal complete definition

return

Associated Types

type ReturnCts m (a :: *) :: Constraint Source #

Methods

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

Instances

Return [] Source # 

Associated Types

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

Methods

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

Return Maybe Source # 

Associated Types

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

Methods

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

Return IO Source # 

Associated Types

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

Methods

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

Return Identity Source # 

Associated Types

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

Methods

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

Return Min Source # 

Associated Types

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

Methods

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

Return Max Source # 

Associated Types

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

Methods

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

Return First Source # 

Associated Types

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

Methods

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

Return Last Source # 

Associated Types

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

Methods

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

Return Option Source # 

Associated Types

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

Methods

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

Return NonEmpty Source # 

Associated Types

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

Methods

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

Return Complex Source # 

Associated Types

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

Methods

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

Return STM Source # 

Associated Types

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

Methods

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

Return Dual Source # 

Associated Types

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

Methods

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

Return Sum Source # 

Associated Types

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

Methods

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

Return Product Source # 

Associated Types

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

Methods

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

Return First Source # 

Associated Types

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

Methods

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

Return Last Source # 

Associated Types

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

Methods

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

Return ReadPrec Source # 

Associated Types

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

Methods

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

Return ReadP Source # 

Associated Types

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

Methods

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

Return Set Source # 

Associated Types

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

Methods

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

Return ((->) r) Source # 

Associated Types

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

Methods

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

Return (Either e) Source # 

Associated Types

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

Methods

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

Return (ST s) Source # 

Associated Types

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

Methods

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

Return (ST s) Source # 

Associated Types

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

Methods

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

Return m => Return (WrappedMonad m) Source # 

Associated Types

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

Methods

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

ArrowApply a => Return (ArrowMonad a) Source # 

Associated Types

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

Methods

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

Return (Proxy *) Source # 

Associated Types

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

Methods

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

Return m => Return (MaybeT m) Source # 

Associated Types

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

Methods

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

Return m => Return (ListT m) Source # 

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

Return (ContT * r m) Source # 

Associated Types

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

Methods

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

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

Associated Types

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

Methods

return :: ReturnCts (ReaderT * r m) a => 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 :: * -> *) a :: Constraint Source #

Methods

return :: ReturnCts (RWST r w s m) a => 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 :: * -> *) a :: Constraint Source #

Methods

return :: ReturnCts (RWST r w s m) a => 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 (a :: *) :: Constraint Source #

Methods

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

Instances

Fail [] Source # 

Associated Types

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

Methods

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

Fail Maybe Source # 

Associated Types

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

Methods

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

Fail IO Source # 

Associated Types

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

Methods

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

Fail Identity Source # 

Associated Types

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

Fail Min Source # 

Associated Types

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

Methods

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

Fail Max Source # 

Associated Types

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

Methods

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

Fail First Source # 

Associated Types

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

Methods

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

Fail Last Source # 

Associated Types

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

Methods

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

Fail Option Source # 

Associated Types

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

Methods

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

Fail NonEmpty Source # 

Associated Types

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

Fail Complex Source # 

Associated Types

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

Methods

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

Fail STM Source # 

Associated Types

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

Methods

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

Fail Dual Source # 

Associated Types

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

Methods

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

Fail Sum Source # 

Associated Types

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

Methods

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

Fail Product Source # 

Associated Types

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

Methods

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

Fail First Source # 

Associated Types

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

Methods

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

Fail Last Source # 

Associated Types

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

Methods

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

Fail ReadPrec Source # 

Associated Types

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

Fail ReadP Source # 

Associated Types

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

Methods

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

Fail Set Source # 

Associated Types

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

Methods

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

Fail ((->) r) Source # 

Associated Types

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

Methods

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

Fail (Either e) Source # 

Associated Types

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

Methods

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

Fail (ST s) Source # 

Associated Types

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

Methods

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

Fail (ST s) Source # 

Associated Types

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

Methods

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

Fail m => Fail (WrappedMonad m) Source # 

Associated Types

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

Methods

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

ArrowApply a => Fail (ArrowMonad a) Source # 

Associated Types

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

Methods

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

Fail (Proxy *) Source # 

Associated Types

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

Methods

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

Return m => Fail (MaybeT m) Source # 

Associated Types

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

Methods

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

Return m => Fail (ListT m) Source # 

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

fail :: FailCts (ReaderT * r m) a => 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 :: * -> *) a :: Constraint Source #

Methods

fail :: FailCts (RWST r w s m) a => 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 :: * -> *) a :: Constraint Source #

Methods

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

class CFunctor f where Source #

Class for constrained functors. Obeys all of the same laws as the standard Functor class, but allows to constrain the functors result type.

Minimal complete definition

fmap

Associated Types

type CFunctorCts f (a :: *) (b :: *) :: Constraint Source #

Methods

fmap :: CFunctorCts f a b => (a -> b) -> f a -> f b Source #

(<$) :: CFunctorCts f b a => a -> f b -> f a Source #

Instances

CFunctor [] Source # 

Associated Types

type CFunctorCts ([] :: * -> *) a b :: Constraint Source #

Methods

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

(<$) :: CFunctorCts [] b a => a -> [b] -> [a] Source #

CFunctor Maybe Source # 

Associated Types

type CFunctorCts (Maybe :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts Maybe a b => (a -> b) -> Maybe a -> Maybe b Source #

(<$) :: CFunctorCts Maybe b a => a -> Maybe b -> Maybe a Source #

CFunctor IO Source # 

Associated Types

type CFunctorCts (IO :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts IO a b => (a -> b) -> IO a -> IO b Source #

(<$) :: CFunctorCts IO b a => a -> IO b -> IO a Source #

CFunctor Identity Source # 

Associated Types

type CFunctorCts (Identity :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts Identity a b => (a -> b) -> Identity a -> Identity b Source #

(<$) :: CFunctorCts Identity b a => a -> Identity b -> Identity a Source #

CFunctor Min Source # 

Associated Types

type CFunctorCts (Min :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts Min a b => (a -> b) -> Min a -> Min b Source #

(<$) :: CFunctorCts Min b a => a -> Min b -> Min a Source #

CFunctor Max Source # 

Associated Types

type CFunctorCts (Max :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts Max a b => (a -> b) -> Max a -> Max b Source #

(<$) :: CFunctorCts Max b a => a -> Max b -> Max a Source #

CFunctor First Source # 

Associated Types

type CFunctorCts (First :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts First a b => (a -> b) -> First a -> First b Source #

(<$) :: CFunctorCts First b a => a -> First b -> First a Source #

CFunctor Last Source # 

Associated Types

type CFunctorCts (Last :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts Last a b => (a -> b) -> Last a -> Last b Source #

(<$) :: CFunctorCts Last b a => a -> Last b -> Last a Source #

CFunctor Option Source # 

Associated Types

type CFunctorCts (Option :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts Option a b => (a -> b) -> Option a -> Option b Source #

(<$) :: CFunctorCts Option b a => a -> Option b -> Option a Source #

CFunctor NonEmpty Source # 

Associated Types

type CFunctorCts (NonEmpty :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts NonEmpty a b => (a -> b) -> NonEmpty a -> NonEmpty b Source #

(<$) :: CFunctorCts NonEmpty b a => a -> NonEmpty b -> NonEmpty a Source #

CFunctor Complex Source # 

Associated Types

type CFunctorCts (Complex :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts Complex a b => (a -> b) -> Complex a -> Complex b Source #

(<$) :: CFunctorCts Complex b a => a -> Complex b -> Complex a Source #

CFunctor STM Source # 

Associated Types

type CFunctorCts (STM :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts STM a b => (a -> b) -> STM a -> STM b Source #

(<$) :: CFunctorCts STM b a => a -> STM b -> STM a Source #

CFunctor Dual Source # 

Associated Types

type CFunctorCts (Dual :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts Dual a b => (a -> b) -> Dual a -> Dual b Source #

(<$) :: CFunctorCts Dual b a => a -> Dual b -> Dual a Source #

CFunctor Sum Source # 

Associated Types

type CFunctorCts (Sum :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts Sum a b => (a -> b) -> Sum a -> Sum b Source #

(<$) :: CFunctorCts Sum b a => a -> Sum b -> Sum a Source #

CFunctor Product Source # 

Associated Types

type CFunctorCts (Product :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts Product a b => (a -> b) -> Product a -> Product b Source #

(<$) :: CFunctorCts Product b a => a -> Product b -> Product a Source #

CFunctor First Source # 

Associated Types

type CFunctorCts (First :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts First a b => (a -> b) -> First a -> First b Source #

(<$) :: CFunctorCts First b a => a -> First b -> First a Source #

CFunctor Last Source # 

Associated Types

type CFunctorCts (Last :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts Last a b => (a -> b) -> Last a -> Last b Source #

(<$) :: CFunctorCts Last b a => a -> Last b -> Last a Source #

CFunctor ReadPrec Source # 

Associated Types

type CFunctorCts (ReadPrec :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts ReadPrec a b => (a -> b) -> ReadPrec a -> ReadPrec b Source #

(<$) :: CFunctorCts ReadPrec b a => a -> ReadPrec b -> ReadPrec a Source #

CFunctor ReadP Source # 

Associated Types

type CFunctorCts (ReadP :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts ReadP a b => (a -> b) -> ReadP a -> ReadP b Source #

(<$) :: CFunctorCts ReadP b a => a -> ReadP b -> ReadP a Source #

CFunctor Set Source # 

Associated Types

type CFunctorCts (Set :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts Set a b => (a -> b) -> Set a -> Set b Source #

(<$) :: CFunctorCts Set b a => a -> Set b -> Set a Source #

CFunctor ((->) r) Source # 

Associated Types

type CFunctorCts ((->) r :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts ((->) r) a b => (a -> b) -> (r -> a) -> r -> b Source #

(<$) :: CFunctorCts ((->) r) b a => a -> (r -> b) -> r -> a Source #

CFunctor (Either e) Source # 

Associated Types

type CFunctorCts (Either e :: * -> *) a b :: Constraint Source #

Methods

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

(<$) :: CFunctorCts (Either e) b a => a -> Either e b -> Either e a Source #

CFunctor (ST s) Source # 

Associated Types

type CFunctorCts (ST s :: * -> *) a b :: Constraint Source #

Methods

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

(<$) :: CFunctorCts (ST s) b a => a -> ST s b -> ST s a Source #

CFunctor (ST s) Source # 

Associated Types

type CFunctorCts (ST s :: * -> *) a b :: Constraint Source #

Methods

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

(<$) :: CFunctorCts (ST s) b a => a -> ST s b -> ST s a Source #

CFunctor m => CFunctor (WrappedMonad m) Source # 

Associated Types

type CFunctorCts (WrappedMonad m :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (WrappedMonad m) a b => (a -> b) -> WrappedMonad m a -> WrappedMonad m b Source #

(<$) :: CFunctorCts (WrappedMonad m) b a => a -> WrappedMonad m b -> WrappedMonad m a Source #

ArrowApply a => CFunctor (ArrowMonad a) Source # 

Associated Types

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

Methods

fmap :: CFunctorCts (ArrowMonad a) a b => (a -> b) -> ArrowMonad a a -> ArrowMonad a b Source #

(<$) :: CFunctorCts (ArrowMonad a) b a => a -> ArrowMonad a b -> ArrowMonad a a Source #

CFunctor (Proxy *) Source # 

Associated Types

type CFunctorCts (Proxy * :: * -> *) a b :: Constraint Source #

Methods

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

(<$) :: CFunctorCts (Proxy *) b a => a -> Proxy * b -> Proxy * a Source #

CFunctor m => CFunctor (MaybeT m) Source # 

Associated Types

type CFunctorCts (MaybeT m :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (MaybeT m) a b => (a -> b) -> MaybeT m a -> MaybeT m b Source #

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

CFunctor m => CFunctor (ListT m) Source # 

Associated Types

type CFunctorCts (ListT m :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (ListT m) a b => (a -> b) -> ListT m a -> ListT m b Source #

(<$) :: CFunctorCts (ListT m) b a => a -> ListT m b -> ListT m a Source #

CFunctor f => CFunctor (Alt * f) Source # 

Associated Types

type CFunctorCts (Alt * f :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (Alt * f) a b => (a -> b) -> Alt * f a -> Alt * f b Source #

(<$) :: CFunctorCts (Alt * f) b a => a -> Alt * f b -> Alt * f a Source #

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

Associated Types

type CFunctorCts (ExceptT e m :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (ExceptT e m) a b => (a -> b) -> ExceptT e m a -> ExceptT e m b Source #

(<$) :: CFunctorCts (ExceptT e m) b a => a -> ExceptT e m b -> ExceptT e m a Source #

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

Associated Types

type CFunctorCts (StateT s m :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (StateT s m) a b => (a -> b) -> StateT s m a -> StateT s m b Source #

(<$) :: CFunctorCts (StateT s m) b a => a -> StateT s m b -> StateT s m a Source #

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

Associated Types

type CFunctorCts (StateT s m :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (StateT s m) a b => (a -> b) -> StateT s m a -> StateT s m b Source #

(<$) :: CFunctorCts (StateT s m) b a => a -> StateT s m b -> StateT s m a Source #

CFunctor m => CFunctor (WriterT w m) Source # 

Associated Types

type CFunctorCts (WriterT w m :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (WriterT w m) a b => (a -> b) -> WriterT w m a -> WriterT w m b Source #

(<$) :: CFunctorCts (WriterT w m) b a => a -> WriterT w m b -> WriterT w m a Source #

CFunctor m => CFunctor (WriterT w m) Source # 

Associated Types

type CFunctorCts (WriterT w m :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (WriterT w m) a b => (a -> b) -> WriterT w m a -> WriterT w m b Source #

(<$) :: CFunctorCts (WriterT w m) b a => a -> WriterT w m b -> WriterT w m a Source #

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

Associated Types

type CFunctorCts (IdentityT * m :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (IdentityT * m) a b => (a -> b) -> IdentityT * m a -> IdentityT * m b Source #

(<$) :: CFunctorCts (IdentityT * m) b a => a -> IdentityT * m b -> IdentityT * m a Source #

(CFunctor f, CFunctor g) => CFunctor (Product * f g) Source # 

Associated Types

type CFunctorCts (Product * f g :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (Product * f g) a b => (a -> b) -> Product * f g a -> Product * f g b Source #

(<$) :: CFunctorCts (Product * f g) b a => a -> Product * f g b -> Product * f g a Source #

CFunctor (ContT * r m) Source #

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

Associated Types

type CFunctorCts (ContT * r m :: * -> *) a b :: Constraint Source #

Methods

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

(<$) :: CFunctorCts (ContT * r m) b a => a -> ContT * r m b -> ContT * r m a Source #

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

Associated Types

type CFunctorCts (ReaderT * r m :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (ReaderT * r m) a b => (a -> b) -> ReaderT * r m a -> ReaderT * r m b Source #

(<$) :: CFunctorCts (ReaderT * r m) b a => a -> ReaderT * r m b -> ReaderT * r m a Source #

CFunctor m => CFunctor (RWST r w s m) Source # 

Associated Types

type CFunctorCts (RWST r w s m :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (RWST r w s m) a b => (a -> b) -> RWST r w s m a -> RWST r w s m b Source #

(<$) :: CFunctorCts (RWST r w s m) b a => a -> RWST r w s m b -> RWST r w s m a Source #

CFunctor m => CFunctor (RWST r w s m) Source # 

Associated Types

type CFunctorCts (RWST r w s m :: * -> *) a b :: Constraint Source #

Methods

fmap :: CFunctorCts (RWST r w s m) a b => (a -> b) -> RWST r w s m a -> RWST r w s m b Source #

(<$) :: CFunctorCts (RWST r w s m) b a => a -> RWST r w s m b -> 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)