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

Safe HaskellNone
LanguageHaskell2010

Control.Super.Monad.Constrained

Contents

Description

Definition of supermonads that support constrained monads.

Synopsis

Supermonads

class (Functor m, Functor n, Functor 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 infixl 1 Source #

(>>) :: BindCts m n p a b => m a -> n b -> p b infixl 1 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 Complex Complex Complex Source # 

Associated Types

type BindCts (Complex :: * -> *) (Complex :: * -> *) (Complex :: * -> *) 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 Identity Identity Identity Source # 

Associated Types

type BindCts (Identity :: * -> *) (Identity :: * -> *) (Identity :: * -> *) 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 (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 (U1 *) (U1 *) (U1 *) Source # 

Associated Types

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

Methods

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

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

Associated Types

type BindCts (WrappedMonad m :: * -> *) (WrappedMonad n :: * -> *) (WrappedMonad p :: * -> *) 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 (Rec1 * m) (Rec1 * n) (Rec1 * p) Source # 

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

(Bind f g h, Bind f' g' h') => Bind ((:*:) * f f') ((:*:) * g g') ((:*:) * h h') Source # 

Associated Types

type BindCts ((* :*: f) f' :: * -> *) ((* :*: g) g' :: * -> *) ((* :*: h) h' :: * -> *) a b :: Constraint Source #

Methods

(>>=) :: BindCts ((* :*: f) f') ((* :*: g) g') ((* :*: h) h') a b => (* :*: f) f' a -> (a -> (* :*: g) g' b) -> (* :*: h) h' b Source #

(>>) :: BindCts ((* :*: f) f') ((* :*: g) g') ((* :*: h) h') a b => (* :*: f) f' a -> (* :*: g) g' b -> (* :*: h) h' 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 #

Bind f g h => Bind (M1 * i c f) (M1 * i c g) (M1 * i c h) Source # 

Associated Types

type BindCts (M1 * i c f :: * -> *) (M1 * i c g :: * -> *) (M1 * i c h :: * -> *) a b :: Constraint Source #

Methods

(>>=) :: BindCts (M1 * i c f) (M1 * i c g) (M1 * i c h) a b => M1 * i c f a -> (a -> M1 * i c g b) -> M1 * i c h b Source #

(>>) :: BindCts (M1 * i c f) (M1 * i c g) (M1 * i c h) a b => M1 * i c f a -> M1 * i c g b -> M1 * i c h 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 Functor 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 Complex Source # 

Associated Types

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

Methods

return :: ReturnCts Complex a => a -> Complex 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 Identity Source # 

Associated Types

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

Methods

return :: ReturnCts Identity a => a -> Identity 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 (Either e) Source # 

Associated Types

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

Methods

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

Return (U1 *) Source # 

Associated Types

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

Methods

return :: ReturnCts (U1 *) a => a -> U1 * 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 (Rec1 * m) Source # 

Associated Types

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

Methods

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

Associated Types

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

Methods

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

(Return f, Return g) => Return ((:*:) * f g) Source # 

Associated Types

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

Methods

return :: ReturnCts ((* :*: f) g) a => a -> (* :*: f) g 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 #

Return f => Return (M1 * i c f) Source # 

Associated Types

type ReturnCts (M1 * i c f :: * -> *) a :: Constraint Source #

Methods

return :: ReturnCts (M1 * i c f) a => a -> M1 * i c f a Source #

(Return f, Return g) => Return ((:.:) * * f g) Source # 

Associated Types

type ReturnCts ((* :.: *) f g :: * -> *) a :: Constraint Source #

Methods

return :: ReturnCts ((* :.: *) f g) a => a -> (* :.: *) f g a Source #

(Return f, Return f') => Return (Compose * * f f') Source # 

Associated Types

type ReturnCts (Compose * * f f' :: * -> *) a :: Constraint Source #

Methods

return :: ReturnCts (Compose * * f f') a => a -> Compose * * f f' 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 Complex Source # 

Associated Types

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

Methods

fail :: FailCts Complex a => String -> Complex a 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 Identity Source # 

Associated Types

type FailCts (Identity :: * -> *) a :: Constraint 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 (Either e) Source # 

Associated Types

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

Methods

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

Fail (U1 *) Source # 

Associated Types

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

Methods

fail :: FailCts (U1 *) a => String -> U1 * 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 #

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

Associated Types

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

Methods

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

Associated Types

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

Methods

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

(Fail f, Fail g) => Fail ((:*:) * f g) Source # 

Associated Types

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

Methods

fail :: FailCts ((* :*: f) g) a => String -> (* :*: f) g 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 #

Fail f => Fail (M1 * i c f) Source # 

Associated Types

type FailCts (M1 * i c f :: * -> *) a :: Constraint Source #

Methods

fail :: FailCts (M1 * i c f) a => String -> M1 * i c f 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 #

Super-Applicatives

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

TODO

Minimal complete definition

(<*>), (*>), (<*)

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts m n p a b => m (a -> b) -> n a -> p b infixl 4 Source #

(*>) :: ApplicativeCtsR m n p a b => m a -> n b -> p b infixl 4 Source #

(<*) :: ApplicativeCtsL m n p a b => m a -> n b -> p a infixl 4 Source #

Instances

Applicative [] [] [] Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts [] [] [] a b => [a -> b] -> [a] -> [b] Source #

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

(<*) :: ApplicativeCtsL [] [] [] a b => [a] -> [b] -> [a] Source #

Applicative Maybe Maybe Maybe Source # 

Associated Types

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

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

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

Applicative IO IO IO Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts IO IO IO a b => IO (a -> b) -> IO a -> IO b Source #

(*>) :: ApplicativeCtsR IO IO IO a b => IO a -> IO b -> IO b Source #

(<*) :: ApplicativeCtsL IO IO IO a b => IO a -> IO b -> IO a Source #

Applicative Complex Complex Complex Source # 

Associated Types

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

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

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

Applicative Min Min Min Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts Min Min Min a b => Min (a -> b) -> Min a -> Min b Source #

(*>) :: ApplicativeCtsR Min Min Min a b => Min a -> Min b -> Min b Source #

(<*) :: ApplicativeCtsL Min Min Min a b => Min a -> Min b -> Min a Source #

Applicative Max Max Max Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts Max Max Max a b => Max (a -> b) -> Max a -> Max b Source #

(*>) :: ApplicativeCtsR Max Max Max a b => Max a -> Max b -> Max b Source #

(<*) :: ApplicativeCtsL Max Max Max a b => Max a -> Max b -> Max a Source #

Applicative First First First Source # 

Associated Types

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

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

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

Applicative Last Last Last Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts Last Last Last a b => Last (a -> b) -> Last a -> Last b Source #

(*>) :: ApplicativeCtsR Last Last Last a b => Last a -> Last b -> Last b Source #

(<*) :: ApplicativeCtsL Last Last Last a b => Last a -> Last b -> Last a Source #

Applicative Option Option Option Source # 

Associated Types

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

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

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

Applicative NonEmpty NonEmpty NonEmpty Source # 
Applicative Identity Identity Identity Source # 
Applicative STM STM STM Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts STM STM STM a b => STM (a -> b) -> STM a -> STM b Source #

(*>) :: ApplicativeCtsR STM STM STM a b => STM a -> STM b -> STM b Source #

(<*) :: ApplicativeCtsL STM STM STM a b => STM a -> STM b -> STM a Source #

Applicative Dual Dual Dual Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts Dual Dual Dual a b => Dual (a -> b) -> Dual a -> Dual b Source #

(*>) :: ApplicativeCtsR Dual Dual Dual a b => Dual a -> Dual b -> Dual b Source #

(<*) :: ApplicativeCtsL Dual Dual Dual a b => Dual a -> Dual b -> Dual a Source #

Applicative Sum Sum Sum Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts Sum Sum Sum a b => Sum (a -> b) -> Sum a -> Sum b Source #

(*>) :: ApplicativeCtsR Sum Sum Sum a b => Sum a -> Sum b -> Sum b Source #

(<*) :: ApplicativeCtsL Sum Sum Sum a b => Sum a -> Sum b -> Sum a Source #

Applicative Product Product Product Source # 

Associated Types

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

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

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

Applicative First First First Source # 

Associated Types

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

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

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

Applicative Last Last Last Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts Last Last Last a b => Last (a -> b) -> Last a -> Last b Source #

(*>) :: ApplicativeCtsR Last Last Last a b => Last a -> Last b -> Last b Source #

(<*) :: ApplicativeCtsL Last Last Last a b => Last a -> Last b -> Last a Source #

Applicative ReadPrec ReadPrec ReadPrec Source # 
Applicative ReadP ReadP ReadP Source # 

Associated Types

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

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

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

Applicative Set Set Set Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts Set Set Set a b => Set (a -> b) -> Set a -> Set b Source #

(*>) :: ApplicativeCtsR Set Set Set a b => Set a -> Set b -> Set b Source #

(<*) :: ApplicativeCtsL Set Set Set a b => Set a -> Set b -> Set a Source #

Applicative (Either e) (Either e) (Either e) Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts (Either e) (Either e) (Either e) a b => Either e (a -> b) -> Either e a -> Either e b Source #

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

(<*) :: ApplicativeCtsL (Either e) (Either e) (Either e) a b => Either e a -> Either e b -> Either e a Source #

Applicative (U1 *) (U1 *) (U1 *) Source # 

Associated Types

type ApplicativeCts (U1 * :: * -> *) (U1 * :: * -> *) (U1 * :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR (U1 * :: * -> *) (U1 * :: * -> *) (U1 * :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL (U1 * :: * -> *) (U1 * :: * -> *) (U1 * :: * -> *) a b :: Constraint Source #

Methods

(<*>) :: ApplicativeCts (U1 *) (U1 *) (U1 *) a b => U1 * (a -> b) -> U1 * a -> U1 * b Source #

(*>) :: ApplicativeCtsR (U1 *) (U1 *) (U1 *) a b => U1 * a -> U1 * b -> U1 * b Source #

(<*) :: ApplicativeCtsL (U1 *) (U1 *) (U1 *) a b => U1 * a -> U1 * b -> U1 * a Source #

Applicative (ST s) (ST s) (ST s) Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts (ST s) (ST s) (ST s) a b => ST s (a -> b) -> ST s a -> ST s b Source #

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

(<*) :: ApplicativeCtsL (ST s) (ST s) (ST s) a b => ST s a -> ST s b -> ST s a Source #

Applicative (ST s) (ST s) (ST s) Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts (ST s) (ST s) (ST s) a b => ST s (a -> b) -> ST s a -> ST s b Source #

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

(<*) :: ApplicativeCtsL (ST s) (ST s) (ST s) a b => ST s a -> ST s b -> ST s a Source #

Applicative m n p => Applicative (WrappedMonad m) (WrappedMonad n) (WrappedMonad p) Source # 
(Arrow a, ArrowApply a) => Applicative (ArrowMonad a) (ArrowMonad a) (ArrowMonad a) Source # 

Associated Types

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

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

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

Applicative (Proxy *) (Proxy *) (Proxy *) Source # 

Associated Types

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

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

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

Methods

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

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

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

Applicative m n p => Applicative (MaybeT m) (MaybeT n) (MaybeT p) Source # 

Associated Types

type ApplicativeCts (MaybeT m :: * -> *) (MaybeT n :: * -> *) (MaybeT p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR (MaybeT m :: * -> *) (MaybeT n :: * -> *) (MaybeT p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL (MaybeT m :: * -> *) (MaybeT n :: * -> *) (MaybeT p :: * -> *) a b :: Constraint Source #

Methods

(<*>) :: ApplicativeCts (MaybeT m) (MaybeT n) (MaybeT p) a b => MaybeT m (a -> b) -> MaybeT n a -> MaybeT p b Source #

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

(<*) :: ApplicativeCtsL (MaybeT m) (MaybeT n) (MaybeT p) a b => MaybeT m a -> MaybeT n b -> MaybeT p a Source #

Applicative f g h => Applicative (Rec1 * f) (Rec1 * g) (Rec1 * h) Source # 

Associated Types

type ApplicativeCts (Rec1 * f :: * -> *) (Rec1 * g :: * -> *) (Rec1 * h :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR (Rec1 * f :: * -> *) (Rec1 * g :: * -> *) (Rec1 * h :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL (Rec1 * f :: * -> *) (Rec1 * g :: * -> *) (Rec1 * h :: * -> *) a b :: Constraint Source #

Methods

(<*>) :: ApplicativeCts (Rec1 * f) (Rec1 * g) (Rec1 * h) a b => Rec1 * f (a -> b) -> Rec1 * g a -> Rec1 * h b Source #

(*>) :: ApplicativeCtsR (Rec1 * f) (Rec1 * g) (Rec1 * h) a b => Rec1 * f a -> Rec1 * g b -> Rec1 * h b Source #

(<*) :: ApplicativeCtsL (Rec1 * f) (Rec1 * g) (Rec1 * h) a b => Rec1 * f a -> Rec1 * g b -> Rec1 * h a Source #

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

Associated Types

type ApplicativeCts (Alt * m :: * -> *) (Alt * n :: * -> *) (Alt * p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR (Alt * m :: * -> *) (Alt * n :: * -> *) (Alt * p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL (Alt * m :: * -> *) (Alt * n :: * -> *) (Alt * p :: * -> *) a b :: Constraint Source #

Methods

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

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

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

Applicative m n p => Applicative (ExceptT e m) (ExceptT e n) (ExceptT e p) Source # 

Associated Types

type ApplicativeCts (ExceptT e m :: * -> *) (ExceptT e n :: * -> *) (ExceptT e p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR (ExceptT e m :: * -> *) (ExceptT e n :: * -> *) (ExceptT e p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL (ExceptT e m :: * -> *) (ExceptT e n :: * -> *) (ExceptT e p :: * -> *) a b :: Constraint Source #

Methods

(<*>) :: ApplicativeCts (ExceptT e m) (ExceptT e n) (ExceptT e p) a b => ExceptT e m (a -> b) -> ExceptT e n a -> ExceptT e p b Source #

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

(<*) :: ApplicativeCtsL (ExceptT e m) (ExceptT e n) (ExceptT e p) a b => ExceptT e m a -> ExceptT e n b -> ExceptT e p a Source #

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

Associated Types

type ApplicativeCts (StateT s m :: * -> *) (StateT s n :: * -> *) (StateT s p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR (StateT s m :: * -> *) (StateT s n :: * -> *) (StateT s p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL (StateT s m :: * -> *) (StateT s n :: * -> *) (StateT s p :: * -> *) a b :: Constraint Source #

Methods

(<*>) :: ApplicativeCts (StateT s m) (StateT s n) (StateT s p) a b => StateT s m (a -> b) -> StateT s n a -> StateT s p b Source #

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

(<*) :: ApplicativeCtsL (StateT s m) (StateT s n) (StateT s p) a b => StateT s m a -> StateT s n b -> StateT s p a Source #

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

Associated Types

type ApplicativeCts (StateT s m :: * -> *) (StateT s n :: * -> *) (StateT s p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR (StateT s m :: * -> *) (StateT s n :: * -> *) (StateT s p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL (StateT s m :: * -> *) (StateT s n :: * -> *) (StateT s p :: * -> *) a b :: Constraint Source #

Methods

(<*>) :: ApplicativeCts (StateT s m) (StateT s n) (StateT s p) a b => StateT s m (a -> b) -> StateT s n a -> StateT s p b Source #

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

(<*) :: ApplicativeCtsL (StateT s m) (StateT s n) (StateT s p) a b => StateT s m a -> StateT s n b -> StateT s p a Source #

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

Associated Types

type ApplicativeCts (WriterT w m :: * -> *) (WriterT w n :: * -> *) (WriterT w p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR (WriterT w m :: * -> *) (WriterT w n :: * -> *) (WriterT w p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL (WriterT w m :: * -> *) (WriterT w n :: * -> *) (WriterT w p :: * -> *) a b :: Constraint Source #

Methods

(<*>) :: ApplicativeCts (WriterT w m) (WriterT w n) (WriterT w p) a b => WriterT w m (a -> b) -> WriterT w n a -> WriterT w p b Source #

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

(<*) :: ApplicativeCtsL (WriterT w m) (WriterT w n) (WriterT w p) a b => WriterT w m a -> WriterT w n b -> WriterT w p a Source #

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

Associated Types

type ApplicativeCts (WriterT w m :: * -> *) (WriterT w n :: * -> *) (WriterT w p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR (WriterT w m :: * -> *) (WriterT w n :: * -> *) (WriterT w p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL (WriterT w m :: * -> *) (WriterT w n :: * -> *) (WriterT w p :: * -> *) a b :: Constraint Source #

Methods

(<*>) :: ApplicativeCts (WriterT w m) (WriterT w n) (WriterT w p) a b => WriterT w m (a -> b) -> WriterT w n a -> WriterT w p b Source #

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

(<*) :: ApplicativeCtsL (WriterT w m) (WriterT w n) (WriterT w p) a b => WriterT w m a -> WriterT w n b -> WriterT w p a Source #

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

Associated Types

type ApplicativeCts (IdentityT * m :: * -> *) (IdentityT * n :: * -> *) (IdentityT * p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR (IdentityT * m :: * -> *) (IdentityT * n :: * -> *) (IdentityT * p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL (IdentityT * m :: * -> *) (IdentityT * n :: * -> *) (IdentityT * p :: * -> *) a b :: Constraint Source #

Methods

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

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

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

Applicative ((->) LiftedRep LiftedRep r) ((->) LiftedRep LiftedRep r) ((->) LiftedRep LiftedRep r) Source # 

Associated Types

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

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

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

Methods

(<*>) :: ApplicativeCts ((LiftedRep -> LiftedRep) r) ((LiftedRep -> LiftedRep) r) ((LiftedRep -> LiftedRep) r) a b => (LiftedRep -> LiftedRep) r (a -> b) -> (LiftedRep -> LiftedRep) r a -> (LiftedRep -> LiftedRep) r b Source #

(*>) :: ApplicativeCtsR ((LiftedRep -> LiftedRep) r) ((LiftedRep -> LiftedRep) r) ((LiftedRep -> LiftedRep) r) a b => (LiftedRep -> LiftedRep) r a -> (LiftedRep -> LiftedRep) r b -> (LiftedRep -> LiftedRep) r b Source #

(<*) :: ApplicativeCtsL ((LiftedRep -> LiftedRep) r) ((LiftedRep -> LiftedRep) r) ((LiftedRep -> LiftedRep) r) a b => (LiftedRep -> LiftedRep) r a -> (LiftedRep -> LiftedRep) r b -> (LiftedRep -> LiftedRep) r a Source #

(Applicative f g h, Applicative f' g' h') => Applicative ((:*:) * f f') ((:*:) * g g') ((:*:) * h h') Source # 

Associated Types

type ApplicativeCts ((* :*: f) f' :: * -> *) ((* :*: g) g' :: * -> *) ((* :*: h) h' :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR ((* :*: f) f' :: * -> *) ((* :*: g) g' :: * -> *) ((* :*: h) h' :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL ((* :*: f) f' :: * -> *) ((* :*: g) g' :: * -> *) ((* :*: h) h' :: * -> *) a b :: Constraint Source #

Methods

(<*>) :: ApplicativeCts ((* :*: f) f') ((* :*: g) g') ((* :*: h) h') a b => (* :*: f) f' (a -> b) -> (* :*: g) g' a -> (* :*: h) h' b Source #

(*>) :: ApplicativeCtsR ((* :*: f) f') ((* :*: g) g') ((* :*: h) h') a b => (* :*: f) f' a -> (* :*: g) g' b -> (* :*: h) h' b Source #

(<*) :: ApplicativeCtsL ((* :*: f) f') ((* :*: g) g') ((* :*: h) h') a b => (* :*: f) f' a -> (* :*: g) g' b -> (* :*: h) h' a Source #

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

Associated Types

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

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

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

Methods

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

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

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

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

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

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

Methods

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

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

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

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

Associated Types

type ApplicativeCts (ReaderT * r m :: * -> *) (ReaderT * r n :: * -> *) (ReaderT * r p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR (ReaderT * r m :: * -> *) (ReaderT * r n :: * -> *) (ReaderT * r p :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL (ReaderT * r m :: * -> *) (ReaderT * r n :: * -> *) (ReaderT * r p :: * -> *) a b :: Constraint Source #

Methods

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

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

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

Applicative f g h => Applicative (M1 * i c f) (M1 * i c g) (M1 * i c h) Source # 

Associated Types

type ApplicativeCts (M1 * i c f :: * -> *) (M1 * i c g :: * -> *) (M1 * i c h :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR (M1 * i c f :: * -> *) (M1 * i c g :: * -> *) (M1 * i c h :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL (M1 * i c f :: * -> *) (M1 * i c g :: * -> *) (M1 * i c h :: * -> *) a b :: Constraint Source #

Methods

(<*>) :: ApplicativeCts (M1 * i c f) (M1 * i c g) (M1 * i c h) a b => M1 * i c f (a -> b) -> M1 * i c g a -> M1 * i c h b Source #

(*>) :: ApplicativeCtsR (M1 * i c f) (M1 * i c g) (M1 * i c h) a b => M1 * i c f a -> M1 * i c g b -> M1 * i c h b Source #

(<*) :: ApplicativeCtsL (M1 * i c f) (M1 * i c g) (M1 * i c h) a b => M1 * i c f a -> M1 * i c g b -> M1 * i c h a Source #

(Applicative f g h, Applicative f' g' h') => Applicative ((:.:) * * f f') ((:.:) * * g g') ((:.:) * * h h') Source # 

Associated Types

type ApplicativeCts ((* :.: *) f f' :: * -> *) ((* :.: *) g g' :: * -> *) ((* :.: *) h h' :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR ((* :.: *) f f' :: * -> *) ((* :.: *) g g' :: * -> *) ((* :.: *) h h' :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL ((* :.: *) f f' :: * -> *) ((* :.: *) g g' :: * -> *) ((* :.: *) h h' :: * -> *) a b :: Constraint Source #

Methods

(<*>) :: ApplicativeCts ((* :.: *) f f') ((* :.: *) g g') ((* :.: *) h h') a b => (* :.: *) f f' (a -> b) -> (* :.: *) g g' a -> (* :.: *) h h' b Source #

(*>) :: ApplicativeCtsR ((* :.: *) f f') ((* :.: *) g g') ((* :.: *) h h') a b => (* :.: *) f f' a -> (* :.: *) g g' b -> (* :.: *) h h' b Source #

(<*) :: ApplicativeCtsL ((* :.: *) f f') ((* :.: *) g g') ((* :.: *) h h') a b => (* :.: *) f f' a -> (* :.: *) g g' b -> (* :.: *) h h' a Source #

(Applicative f g h, Applicative f' g' h') => Applicative (Compose * * f f') (Compose * * g g') (Compose * * h h') Source # 

Associated Types

type ApplicativeCts (Compose * * f f' :: * -> *) (Compose * * g g' :: * -> *) (Compose * * h h' :: * -> *) a b :: Constraint Source #

type ApplicativeCtsR (Compose * * f f' :: * -> *) (Compose * * g g' :: * -> *) (Compose * * h h' :: * -> *) a b :: Constraint Source #

type ApplicativeCtsL (Compose * * f f' :: * -> *) (Compose * * g g' :: * -> *) (Compose * * h h' :: * -> *) a b :: Constraint Source #

Methods

(<*>) :: ApplicativeCts (Compose * * f f') (Compose * * g g') (Compose * * h h') a b => Compose * * f f' (a -> b) -> Compose * * g g' a -> Compose * * h h' b Source #

(*>) :: ApplicativeCtsR (Compose * * f f') (Compose * * g g') (Compose * * h h') a b => Compose * * f f' a -> Compose * * g g' b -> Compose * * h h' b Source #

(<*) :: ApplicativeCtsL (Compose * * f f') (Compose * * g g') (Compose * * h h') a b => Compose * * f f' a -> Compose * * g g' b -> Compose * * h h' a Source #

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

Associated Types

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

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

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

Methods

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

(*>) :: ApplicativeCtsR (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 #

(<*) :: ApplicativeCtsL (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 a Source #

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

Associated Types

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

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

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

Methods

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

(*>) :: ApplicativeCtsR (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 #

(<*) :: ApplicativeCtsL (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 a Source #

pure :: (Return f, ReturnCts f a) => a -> f a Source #

pure is defined in terms of return.

class Functor 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 FunctorCts f (a :: *) (b :: *) :: Constraint Source #

Methods

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

(<$) :: FunctorCts f b a => a -> f b -> f a infixl 4 Source #

Instances

Functor [] Source # 

Associated Types

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

Methods

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

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

Functor Maybe Source # 

Associated Types

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

Methods

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

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

Functor IO Source # 

Associated Types

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

Methods

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

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

Functor Complex Source # 

Associated Types

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

Methods

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

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

Functor Min Source # 

Associated Types

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

Methods

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

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

Functor Max Source # 

Associated Types

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

Methods

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

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

Functor First Source # 

Associated Types

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

Methods

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

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

Functor Last Source # 

Associated Types

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

Methods

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

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

Functor Option Source # 

Associated Types

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

Methods

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

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

Functor NonEmpty Source # 

Associated Types

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

Methods

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

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

Functor Identity Source # 

Associated Types

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

Methods

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

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

Functor STM Source # 

Associated Types

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

Methods

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

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

Functor Dual Source # 

Associated Types

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

Methods

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

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

Functor Sum Source # 

Associated Types

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

Methods

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

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

Functor Product Source # 

Associated Types

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

Methods

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

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

Functor First Source # 

Associated Types

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

Methods

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

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

Functor Last Source # 

Associated Types

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

Methods

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

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

Functor ReadPrec Source # 

Associated Types

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

Methods

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

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

Functor ReadP Source # 

Associated Types

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

Methods

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

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

Functor Set Source # 

Associated Types

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

Methods

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

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

Functor (Either e) Source # 

Associated Types

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

Methods

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

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

Functor (U1 *) Source # 

Associated Types

type FunctorCts (U1 * :: * -> *) a b :: Constraint Source #

Methods

fmap :: FunctorCts (U1 *) a b => (a -> b) -> U1 * a -> U1 * b Source #

(<$) :: FunctorCts (U1 *) b a => a -> U1 * b -> U1 * a Source #

Functor (ST s) Source # 

Associated Types

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

Methods

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

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

Functor (ST s) Source # 

Associated Types

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

Methods

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

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

Functor m => Functor (WrappedMonad m) Source # 

Associated Types

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

Methods

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

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

ArrowApply a => Functor (ArrowMonad a) Source # 

Associated Types

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

Methods

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

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

Functor (Proxy *) Source # 

Associated Types

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

Methods

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

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

Functor m => Functor (MaybeT m) Source # 

Associated Types

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

Methods

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

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

Functor f => Functor (Rec1 * f) Source # 

Associated Types

type FunctorCts (Rec1 * f :: * -> *) a b :: Constraint Source #

Methods

fmap :: FunctorCts (Rec1 * f) a b => (a -> b) -> Rec1 * f a -> Rec1 * f b Source #

(<$) :: FunctorCts (Rec1 * f) b a => a -> Rec1 * f b -> Rec1 * f a Source #

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

Functor ((->) LiftedRep LiftedRep r) Source # 

Associated Types

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

Methods

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

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

(Functor f, Functor g) => Functor ((:*:) * f g) Source # 

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

Functor (ContT * r m) Source #

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

Functor f => Functor (M1 * i c f) Source # 

Associated Types

type FunctorCts (M1 * i c f :: * -> *) a b :: Constraint Source #

Methods

fmap :: FunctorCts (M1 * i c f) a b => (a -> b) -> M1 * i c f a -> M1 * i c f b Source #

(<$) :: FunctorCts (M1 * i c f) b a => a -> M1 * i c f b -> M1 * i c f a Source #

(Functor f, Functor g) => Functor ((:.:) * * f g) Source # 

Associated Types

type FunctorCts ((* :.: *) f g :: * -> *) a b :: Constraint Source #

Methods

fmap :: FunctorCts ((* :.: *) f g) a b => (a -> b) -> (* :.: *) f g a -> (* :.: *) f g b Source #

(<$) :: FunctorCts ((* :.: *) f g) b a => a -> (* :.: *) f g b -> (* :.: *) f g a Source #

(Functor f, Functor g) => Functor (Compose * * f g) Source # 

Associated Types

type FunctorCts (Compose * * f g :: * -> *) a b :: Constraint Source #

Methods

fmap :: FunctorCts (Compose * * f g) a b => (a -> b) -> Compose * * f g a -> Compose * * f g b Source #

(<$) :: FunctorCts (Compose * * f g) b a => a -> Compose * * f g b -> Compose * * f g a Source #

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

(<$) :: FunctorCts (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)