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

Safe HaskellNone
LanguageHaskell2010

Control.Supermonad.Constrained.Functor

Description

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

Synopsis

Documentation

class CFunctor f where Source #

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

Minimal complete definition

fmap

Associated Types

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

Methods

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

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

Instances

CFunctor [] Source # 

Associated Types

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

Methods

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

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

CFunctor Maybe Source # 

Associated Types

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

Methods

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

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

CFunctor IO Source # 

Associated Types

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

Methods

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

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

CFunctor Identity Source # 

Associated Types

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

Methods

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

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

CFunctor Min Source # 

Associated Types

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

Methods

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

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

CFunctor Max Source # 

Associated Types

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

Methods

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

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

CFunctor First Source # 

Associated Types

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

Methods

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

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

CFunctor Last Source # 

Associated Types

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

Methods

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

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

CFunctor Option Source # 

Associated Types

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

Methods

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

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

CFunctor NonEmpty Source # 

Associated Types

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

Methods

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

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

CFunctor Complex Source # 

Associated Types

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

Methods

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

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

CFunctor STM Source # 

Associated Types

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

Methods

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

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

CFunctor Dual Source # 

Associated Types

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

Methods

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

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

CFunctor Sum Source # 

Associated Types

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

Methods

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

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

CFunctor Product Source # 

Associated Types

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

Methods

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

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

CFunctor First Source # 

Associated Types

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

Methods

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

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

CFunctor Last Source # 

Associated Types

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

Methods

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

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

CFunctor ReadPrec Source # 

Associated Types

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

Methods

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

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

CFunctor ReadP Source # 

Associated Types

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

Methods

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

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

CFunctor Set Source # 

Associated Types

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

Methods

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

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

CFunctor ((->) r) Source # 

Associated Types

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

Methods

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

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

CFunctor (Either e) Source # 

Associated Types

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

Methods

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

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

CFunctor (ST s) Source # 

Associated Types

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

Methods

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

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

CFunctor (ST s) Source # 

Associated Types

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

Methods

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

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

CFunctor m => CFunctor (WrappedMonad m) Source # 

Associated Types

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

Methods

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

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

ArrowApply a => CFunctor (ArrowMonad a) Source # 

Associated Types

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

Methods

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

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

CFunctor (Proxy *) Source # 

Associated Types

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

Methods

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

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

CFunctor m => CFunctor (MaybeT m) Source # 

Associated Types

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

Methods

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

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

CFunctor m => CFunctor (ListT m) Source # 

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

CFunctor (ContT * r m) Source #

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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