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

Safe HaskellNone
LanguageHaskell2010

Control.Super.Monad.Constrained.Functor

Description

Definition of constrained functors as they are required to work with constrained monads and constrained supermonads.

Synopsis

Documentation

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 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 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 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 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 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 ((->) r) Source # 

Associated Types

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

Methods

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

(<$) :: FunctorCts ((->) r) b a => a -> (r -> b) -> r -> 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 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 (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 m => Functor (ListT m) Source # 

Associated Types

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

Methods

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

(<$) :: FunctorCts (ListT m) b a => a -> ListT m b -> ListT m 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 ((:.:) 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 (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 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 (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 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 #