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

Safe HaskellNone
LanguageHaskell2010

Control.Super.Monad

Contents

Description

Representation of supermonads in Haskell.

Synopsis

Supermonads

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

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

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

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

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

For supermonads we expect the usual monad laws to hold:

Minimal complete definition

(>>=)

Associated Types

type BindCts m n p :: Constraint Source #

Methods

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

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

Instances

Bind [] [] [] Source # 

Associated Types

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

Methods

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

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

Bind Maybe Maybe Maybe Source # 

Associated Types

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

Methods

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

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

Bind IO IO IO Source # 

Associated Types

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

Methods

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

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

Bind Complex Complex Complex Source # 

Associated Types

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

Bind Min Min Min Source # 

Associated Types

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

Methods

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

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

Bind Max Max Max Source # 

Associated Types

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

Methods

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

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

Bind First First First Source # 

Associated Types

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

Methods

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

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

Bind Last Last Last Source # 

Associated Types

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

Methods

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

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

Bind Option Option Option Source # 

Associated Types

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

Bind NonEmpty NonEmpty NonEmpty Source # 

Associated Types

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

Bind Identity Identity Identity Source # 

Associated Types

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

Bind STM STM STM Source # 

Associated Types

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

Methods

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

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

Bind Dual Dual Dual Source # 

Associated Types

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

Methods

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

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

Bind Sum Sum Sum Source # 

Associated Types

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

Methods

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

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

Bind Product Product Product Source # 

Associated Types

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

Bind First First First Source # 

Associated Types

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

Methods

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

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

Bind Last Last Last Source # 

Associated Types

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

Methods

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

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

Bind ReadPrec ReadPrec ReadPrec Source # 

Associated Types

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

Bind ReadP ReadP ReadP Source # 

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

Bind (U1 *) (U1 *) (U1 *) Source # 

Associated Types

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

Methods

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

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

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

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

Associated Types

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

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

Associated Types

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

Methods

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

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

Methods

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

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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 :: * -> *) :: Constraint Source #

Methods

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

Methods

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

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

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

Associated Types

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

Methods

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

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

class Functor m => Return m where Source #

See Bind or Ap for details on laws and requirements.

Minimal complete definition

return

Associated Types

type ReturnCts m :: Constraint Source #

Methods

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

Instances

Return [] Source # 

Associated Types

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

Methods

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

Return Maybe Source # 

Associated Types

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

Methods

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

Return IO Source # 

Associated Types

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

Methods

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

Return Complex Source # 

Associated Types

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

Methods

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

Return Min Source # 

Associated Types

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

Methods

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

Return Max Source # 

Associated Types

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

Methods

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

Return First Source # 

Associated Types

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

Methods

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

Return Last Source # 

Associated Types

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

Methods

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

Return Option Source # 

Associated Types

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

Methods

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

Return NonEmpty Source # 

Associated Types

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

Return Identity Source # 

Associated Types

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

Return STM Source # 

Associated Types

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

Methods

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

Return Dual Source # 

Associated Types

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

Methods

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

Return Sum Source # 

Associated Types

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

Methods

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

Return Product Source # 

Associated Types

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

Methods

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

Return First Source # 

Associated Types

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

Methods

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

Return Last Source # 

Associated Types

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

Methods

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

Return ReadPrec Source # 

Associated Types

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

Return ReadP Source # 

Associated Types

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

Methods

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

Return (Either e) Source # 

Associated Types

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

Methods

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

Return (U1 *) Source # 

Associated Types

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

Methods

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

Return (ST s) Source # 

Associated Types

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

Methods

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

Return (ST s) Source # 

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

ArrowApply a => Return (ArrowMonad a) Source # 

Associated Types

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

Methods

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

Return (Proxy *) Source # 

Associated Types

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

Methods

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

Return m => Return (MaybeT m) Source # 

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

Return (ContT * r m) Source # 

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

Methods

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

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

Associated Types

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

Methods

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

class Fail m where Source #

See Bind for details on laws and requirements.

Minimal complete definition

fail

Associated Types

type FailCts m :: Constraint Source #

Methods

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

Instances

Fail [] Source # 

Associated Types

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

Methods

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

Fail Maybe Source # 

Associated Types

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

Methods

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

Fail IO Source # 

Associated Types

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

Methods

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

Fail Complex Source # 

Associated Types

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

Fail Min Source # 

Associated Types

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

Methods

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

Fail Max Source # 

Associated Types

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

Methods

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

Fail First Source # 

Associated Types

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

Methods

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

Fail Last Source # 

Associated Types

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

Methods

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

Fail Option Source # 

Associated Types

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

Methods

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

Fail NonEmpty Source # 

Associated Types

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

Fail Identity Source # 

Associated Types

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

Fail STM Source # 

Associated Types

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

Methods

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

Fail Dual Source # 

Associated Types

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

Methods

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

Fail Sum Source # 

Associated Types

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

Methods

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

Fail Product Source # 

Associated Types

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

Fail First Source # 

Associated Types

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

Methods

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

Fail Last Source # 

Associated Types

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

Methods

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

Fail ReadPrec Source # 

Associated Types

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

Fail ReadP Source # 

Associated Types

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

Methods

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

Fail (Either e) Source # 

Associated Types

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

Methods

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

Fail (U1 *) Source # 

Associated Types

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

Methods

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

Fail (ST s) Source # 

Associated Types

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

Methods

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

Fail (ST s) Source # 

Associated Types

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

Methods

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

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

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

Associated Types

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

ArrowApply a => Fail (ArrowMonad a) Source # 

Associated Types

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

Methods

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

Fail (Proxy *) Source # 

Associated Types

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

Methods

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

Return m => Fail (MaybeT m) Source # 

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

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

Associated Types

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

Methods

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

Methods

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

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

Associated Types

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

Methods

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

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 :: Constraint Source #

Methods

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

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

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

Instances

Applicative [] [] [] Source # 

Associated Types

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

Methods

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

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

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

Applicative Maybe Maybe Maybe Source # 

Associated Types

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

Applicative IO IO IO Source # 

Associated Types

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

Methods

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

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

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

Applicative Complex Complex Complex Source # 
Applicative Min Min Min Source # 

Associated Types

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

Methods

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

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

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

Applicative Max Max Max Source # 

Associated Types

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

Methods

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

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

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

Applicative First First First Source # 

Associated Types

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

Applicative Last Last Last Source # 

Associated Types

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

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

Associated Types

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

Methods

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

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

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

Applicative Dual Dual Dual Source # 

Associated Types

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

Applicative Sum Sum Sum Source # 

Associated Types

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

Methods

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

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

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

Applicative Product Product Product Source # 
Applicative First First First Source # 

Associated Types

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

Applicative Last Last Last Source # 

Associated Types

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

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

Associated Types

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

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

Associated Types

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

Methods

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

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

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

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

Associated Types

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

Methods

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

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

(<*) :: ApplicativeCts (U1 *) (U1 *) (U1 *) => 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 :: * -> *) :: Constraint Source #

Methods

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

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

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

Methods

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

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

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

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

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

instance (Functor m) => Functor (App.WrappedMonad m) where
  fmap f m = App.WrapMonad $ fmap (App.unwrapMonad m) f
Arrow a => Applicative (ArrowMonad a) (ArrowMonad a) (ArrowMonad a) Source # 

Associated Types

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

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

Associated Types

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

(<*) :: ApplicativeCts (Rec1 * f) (Rec1 * g) (Rec1 * h) => 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 :: * -> *) :: Constraint Source #

Methods

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

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

(<*) :: ApplicativeCts (Alt * m) (Alt * n) (Alt * p) => 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 :: * -> *) :: Constraint Source #

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

(<*) :: ApplicativeCts ((* :*: f) f') ((* :*: g) g') ((* :*: h) h') => (* :*: 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 :: * -> *) :: Constraint Source #

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

(<*) :: ApplicativeCts (M1 * i c f) (M1 * i c g) (M1 * i c h) => 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' :: * -> *) :: Constraint Source #

Methods

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

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

(<*) :: ApplicativeCts ((* :.: *) f f') ((* :.: *) g g') ((* :.: *) h h') => (* :.: *) 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' :: * -> *) :: Constraint Source #

Methods

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

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

(<*) :: ApplicativeCts (Compose * * f f') (Compose * * g g') (Compose * * h h') => 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 :: * -> *) :: Constraint Source #

Methods

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

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

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

Methods

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

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

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

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

pure is defined in terms of return.

class Functor (f :: * -> *) where #

The Functor class is used for types that can be mapped over. Instances of Functor should satisfy the following laws:

fmap id  ==  id
fmap (f . g)  ==  fmap f . fmap g

The instances of Functor for lists, Maybe and IO satisfy these laws.

Minimal complete definition

fmap

Methods

fmap :: (a -> b) -> f a -> f b #

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

Replace all locations in the input with the same value. The default definition is fmap . const, but this may be overridden with a more efficient version.

Instances

Functor []

Since: 2.1

Methods

fmap :: (a -> b) -> [a] -> [b] #

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

Functor Maybe

Since: 2.1

Methods

fmap :: (a -> b) -> Maybe a -> Maybe b #

(<$) :: a -> Maybe b -> Maybe a #

Functor IO

Since: 2.1

Methods

fmap :: (a -> b) -> IO a -> IO b #

(<$) :: a -> IO b -> IO a #

Functor Par1 

Methods

fmap :: (a -> b) -> Par1 a -> Par1 b #

(<$) :: a -> Par1 b -> Par1 a #

Functor Q 

Methods

fmap :: (a -> b) -> Q a -> Q b #

(<$) :: a -> Q b -> Q a #

Functor P 

Methods

fmap :: (a -> b) -> P a -> P b #

(<$) :: a -> P b -> P a #

Functor Complex 

Methods

fmap :: (a -> b) -> Complex a -> Complex b #

(<$) :: a -> Complex b -> Complex a #

Functor Min

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Min a -> Min b #

(<$) :: a -> Min b -> Min a #

Functor Max

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Max a -> Max b #

(<$) :: a -> Max b -> Max a #

Functor First

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> First a -> First b #

(<$) :: a -> First b -> First a #

Functor Last

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Last a -> Last b #

(<$) :: a -> Last b -> Last a #

Functor Option

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Option a -> Option b #

(<$) :: a -> Option b -> Option a #

Functor NonEmpty

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> NonEmpty a -> NonEmpty b #

(<$) :: a -> NonEmpty b -> NonEmpty a #

Functor ZipList 

Methods

fmap :: (a -> b) -> ZipList a -> ZipList b #

(<$) :: a -> ZipList b -> ZipList a #

Functor Identity

Since: 4.8.0.0

Methods

fmap :: (a -> b) -> Identity a -> Identity b #

(<$) :: a -> Identity b -> Identity a #

Functor STM

Since: 4.3.0.0

Methods

fmap :: (a -> b) -> STM a -> STM b #

(<$) :: a -> STM b -> STM a #

Functor Dual

Since: 4.8.0.0

Methods

fmap :: (a -> b) -> Dual a -> Dual b #

(<$) :: a -> Dual b -> Dual a #

Functor Sum

Since: 4.8.0.0

Methods

fmap :: (a -> b) -> Sum a -> Sum b #

(<$) :: a -> Sum b -> Sum a #

Functor Product

Since: 4.8.0.0

Methods

fmap :: (a -> b) -> Product a -> Product b #

(<$) :: a -> Product b -> Product a #

Functor First 

Methods

fmap :: (a -> b) -> First a -> First b #

(<$) :: a -> First b -> First a #

Functor Last 

Methods

fmap :: (a -> b) -> Last a -> Last b #

(<$) :: a -> Last b -> Last a #

Functor ReadPrec

Since: 2.1

Methods

fmap :: (a -> b) -> ReadPrec a -> ReadPrec b #

(<$) :: a -> ReadPrec b -> ReadPrec a #

Functor ReadP

Since: 2.1

Methods

fmap :: (a -> b) -> ReadP a -> ReadP b #

(<$) :: a -> ReadP b -> ReadP a #

Functor Put 

Methods

fmap :: (a -> b) -> Put a -> Put b #

(<$) :: a -> Put b -> Put a #

Functor IntMap 

Methods

fmap :: (a -> b) -> IntMap a -> IntMap b #

(<$) :: a -> IntMap b -> IntMap a #

Functor SCC 

Methods

fmap :: (a -> b) -> SCC a -> SCC b #

(<$) :: a -> SCC b -> SCC a #

Functor Tree 

Methods

fmap :: (a -> b) -> Tree a -> Tree b #

(<$) :: a -> Tree b -> Tree a #

Functor Seq 

Methods

fmap :: (a -> b) -> Seq a -> Seq b #

(<$) :: a -> Seq b -> Seq a #

Functor FingerTree 

Methods

fmap :: (a -> b) -> FingerTree a -> FingerTree b #

(<$) :: a -> FingerTree b -> FingerTree a #

Functor Digit 

Methods

fmap :: (a -> b) -> Digit a -> Digit b #

(<$) :: a -> Digit b -> Digit a #

Functor Node 

Methods

fmap :: (a -> b) -> Node a -> Node b #

(<$) :: a -> Node b -> Node a #

Functor Elem 

Methods

fmap :: (a -> b) -> Elem a -> Elem b #

(<$) :: a -> Elem b -> Elem a #

Functor ViewL 

Methods

fmap :: (a -> b) -> ViewL a -> ViewL b #

(<$) :: a -> ViewL b -> ViewL a #

Functor ViewR 

Methods

fmap :: (a -> b) -> ViewR a -> ViewR b #

(<$) :: a -> ViewR b -> ViewR a #

Functor NormM 

Methods

fmap :: (a -> b) -> NormM a -> NormM b #

(<$) :: a -> NormM b -> NormM a #

Functor UM 

Methods

fmap :: (a -> b) -> UM a -> UM b #

(<$) :: a -> UM b -> UM a #

Functor TaggedVal 

Methods

fmap :: (a -> b) -> TaggedVal a -> TaggedVal b #

(<$) :: a -> TaggedVal b -> TaggedVal a #

Functor CoreM 

Methods

fmap :: (a -> b) -> CoreM a -> CoreM b #

(<$) :: a -> CoreM b -> CoreM a #

Functor TcPluginM 

Methods

fmap :: (a -> b) -> TcPluginM a -> TcPluginM b #

(<$) :: a -> TcPluginM b -> TcPluginM a #

Functor Hsc 

Methods

fmap :: (a -> b) -> Hsc a -> Hsc b #

(<$) :: a -> Hsc b -> Hsc a #

Functor UnifyResultM 

Methods

fmap :: (a -> b) -> UnifyResultM a -> UnifyResultM b #

(<$) :: a -> UnifyResultM b -> UnifyResultM a #

Functor UniqDFM 

Methods

fmap :: (a -> b) -> UniqDFM a -> UniqDFM b #

(<$) :: a -> UniqDFM b -> UniqDFM a #

Functor UniqFM 

Methods

fmap :: (a -> b) -> UniqFM a -> UniqFM b #

(<$) :: a -> UniqFM b -> UniqFM a #

Functor UniqSM 

Methods

fmap :: (a -> b) -> UniqSM a -> UniqSM b #

(<$) :: a -> UniqSM b -> UniqSM a #

Functor SizedSeq 

Methods

fmap :: (a -> b) -> SizedSeq a -> SizedSeq b #

(<$) :: a -> SizedSeq b -> SizedSeq a #

Functor Doc 

Methods

fmap :: (a -> b) -> Doc a -> Doc b #

(<$) :: a -> Doc b -> Doc a #

Functor AnnotDetails 

Methods

fmap :: (a -> b) -> AnnotDetails a -> AnnotDetails b #

(<$) :: a -> AnnotDetails b -> AnnotDetails a #

Functor Span 

Methods

fmap :: (a -> b) -> Span a -> Span b #

(<$) :: a -> Span b -> Span a #

Functor (Either a)

Since: 3.0

Methods

fmap :: (a -> b) -> Either a a -> Either a b #

(<$) :: a -> Either a b -> Either a a #

Functor (V1 *) 

Methods

fmap :: (a -> b) -> V1 * a -> V1 * b #

(<$) :: a -> V1 * b -> V1 * a #

Functor (U1 *)

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> U1 * a -> U1 * b #

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

Functor ((,) a)

Since: 2.1

Methods

fmap :: (a -> b) -> (a, a) -> (a, b) #

(<$) :: a -> (a, b) -> (a, a) #

Functor (ST s)

Since: 2.1

Methods

fmap :: (a -> b) -> ST s a -> ST s b #

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

Functor (Array i)

Since: 2.1

Methods

fmap :: (a -> b) -> Array i a -> Array i b #

(<$) :: a -> Array i b -> Array i a #

Functor (Arg a)

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Arg a a -> Arg a b #

(<$) :: a -> Arg a b -> Arg a a #

Functor (ST s)

Since: 2.1

Methods

fmap :: (a -> b) -> ST s a -> ST s b #

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

Monad m => Functor (WrappedMonad m)

Since: 2.1

Methods

fmap :: (a -> b) -> WrappedMonad m a -> WrappedMonad m b #

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

Arrow a => Functor (ArrowMonad a)

Since: 4.6.0.0

Methods

fmap :: (a -> b) -> ArrowMonad a a -> ArrowMonad a b #

(<$) :: a -> ArrowMonad a b -> ArrowMonad a a #

Functor (Proxy *)

Since: 4.7.0.0

Methods

fmap :: (a -> b) -> Proxy * a -> Proxy * b #

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

Functor (SetM s) 

Methods

fmap :: (a -> b) -> SetM s a -> SetM s b #

(<$) :: a -> SetM s b -> SetM s a #

Functor (State s) 

Methods

fmap :: (a -> b) -> State s a -> State s b #

(<$) :: a -> State s b -> State s a #

Functor (Map k) 

Methods

fmap :: (a -> b) -> Map k a -> Map k b #

(<$) :: a -> Map k b -> Map k a #

Functor (IOEnv m) 

Methods

fmap :: (a -> b) -> IOEnv m a -> IOEnv m b #

(<$) :: a -> IOEnv m b -> IOEnv m a #

Functor (GenLocated l) 

Methods

fmap :: (a -> b) -> GenLocated l a -> GenLocated l b #

(<$) :: a -> GenLocated l b -> GenLocated l a #

Functor m => Functor (MaybeT m) 

Methods

fmap :: (a -> b) -> MaybeT m a -> MaybeT m b #

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

Functor (DbOpenMode mode) 

Methods

fmap :: (a -> b) -> DbOpenMode mode a -> DbOpenMode mode b #

(<$) :: a -> DbOpenMode mode b -> DbOpenMode mode a #

Functor m => Functor (ListT m) 

Methods

fmap :: (a -> b) -> ListT m a -> ListT m b #

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

Functor f => Functor (Rec1 * f) 

Methods

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

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

Functor (URec * Char) 

Methods

fmap :: (a -> b) -> URec * Char a -> URec * Char b #

(<$) :: a -> URec * Char b -> URec * Char a #

Functor (URec * Double) 

Methods

fmap :: (a -> b) -> URec * Double a -> URec * Double b #

(<$) :: a -> URec * Double b -> URec * Double a #

Functor (URec * Float) 

Methods

fmap :: (a -> b) -> URec * Float a -> URec * Float b #

(<$) :: a -> URec * Float b -> URec * Float a #

Functor (URec * Int) 

Methods

fmap :: (a -> b) -> URec * Int a -> URec * Int b #

(<$) :: a -> URec * Int b -> URec * Int a #

Functor (URec * Word) 

Methods

fmap :: (a -> b) -> URec * Word a -> URec * Word b #

(<$) :: a -> URec * Word b -> URec * Word a #

Functor (URec * (Ptr ())) 

Methods

fmap :: (a -> b) -> URec * (Ptr ()) a -> URec * (Ptr ()) b #

(<$) :: a -> URec * (Ptr ()) b -> URec * (Ptr ()) a #

Arrow a => Functor (WrappedArrow a b)

Since: 2.1

Methods

fmap :: (a -> b) -> WrappedArrow a b a -> WrappedArrow a b b #

(<$) :: a -> WrappedArrow a b b -> WrappedArrow a b a #

Functor (Const * m)

Since: 2.1

Methods

fmap :: (a -> b) -> Const * m a -> Const * m b #

(<$) :: a -> Const * m b -> Const * m a #

Functor f => Functor (Alt * f) 

Methods

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

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

(Applicative f, Monad f) => Functor (WhenMissing f x) 

Methods

fmap :: (a -> b) -> WhenMissing f x a -> WhenMissing f x b #

(<$) :: a -> WhenMissing f x b -> WhenMissing f x a #

Functor m => Functor (ErrorT e m) 

Methods

fmap :: (a -> b) -> ErrorT e m a -> ErrorT e m b #

(<$) :: a -> ErrorT e m b -> ErrorT e m a #

Functor m => Functor (ExceptT e m) 

Methods

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

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

Functor m => Functor (StateT s m) 

Methods

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

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

Functor m => Functor (StateT s m) 

Methods

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

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

Functor m => Functor (WriterT w m) 

Methods

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

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

Functor m => Functor (WriterT w m) 

Methods

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

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

Functor m => Functor (IdentityT * m) 

Methods

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

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

Functor ((->) LiftedRep LiftedRep r)

Since: 2.1

Methods

fmap :: (a -> b) -> (LiftedRep -> LiftedRep) r a -> (LiftedRep -> LiftedRep) r b #

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

Functor (K1 * i c) 

Methods

fmap :: (a -> b) -> K1 * i c a -> K1 * i c b #

(<$) :: a -> K1 * i c b -> K1 * i c a #

(Functor g, Functor f) => Functor ((:+:) * f g) 

Methods

fmap :: (a -> b) -> (* :+: f) g a -> (* :+: f) g b #

(<$) :: a -> (* :+: f) g b -> (* :+: f) g a #

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

Methods

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

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

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

Since: 4.9.0.0

Methods

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

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

(Functor f, Functor g) => Functor (Sum * f g)

Since: 4.9.0.0

Methods

fmap :: (a -> b) -> Sum * f g a -> Sum * f g b #

(<$) :: a -> Sum * f g b -> Sum * f g a #

Functor f => Functor (WhenMatched f x y) 

Methods

fmap :: (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b #

(<$) :: a -> WhenMatched f x y b -> WhenMatched f x y a #

(Applicative f, Monad f) => Functor (WhenMissing f k x) 

Methods

fmap :: (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b #

(<$) :: a -> WhenMissing f k x b -> WhenMissing f k x a #

Functor (ContT k r m) 

Methods

fmap :: (a -> b) -> ContT k r m a -> ContT k r m b #

(<$) :: a -> ContT k r m b -> ContT k r m a #

Functor m => Functor (ReaderT * r m) 

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Since: 4.9.0.0

Methods

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

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

Functor f => Functor (WhenMatched f k x y) 

Methods

fmap :: (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b #

(<$) :: a -> WhenMatched f k x y b -> WhenMatched f k x y a #

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

Methods

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

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

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

Methods

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

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

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)