functor-monad-0.1.1.0: FFunctor: functors on (the usual) Functors
Safe HaskellSafe-Inferred
LanguageHaskell2010

FFunctor

Description

Functors on the category of Functor s.

Synopsis

Documentation

type (~>) f g = forall x. f x -> g x Source #

Natural transformation arrow

class (forall g. Functor g => Functor (ff g)) => FFunctor ff where Source #

Endofunctors on the category of Functors.

Functor fFFunctor ff
TakesA type aA Functor g
MakesA type f aA Functor (ff g)
Feature fmap :: (a -> b) -> f a -> f b ffmap :: (Functor g, Functor h) => (g ~> h) -> (ff g ~> ff h)

FFunctor laws:

Identity
 ffmap id = id
Composition
 ffmap f . ffmap g = ffmap (f . g)

Examples

This is the FFunctor instance of Sum f. Just like the fmap from Functor (Either a) instance which applies a function to the "Right" value, ffmap applies gh :: g ~> h to the InR (g a) value.

data Sum f g a = InL (f a) | InR (g a)
instance (Functor f) => FFunctor (Sum f) where
    ffmap gh fgx = case fgx of
        InL fx -> InL fx
        InR gx -> InR (gh gx)

Like Sum f, some instances of FFunctor are modified Functors in such a way that its parameter is swapped for g a. But not every instance of FFunctor is like this. The following data type Foo g a is a FFunctor which uses a Functor g and a type parameter a separately.

data Foo g a = Foo (String -> a) (g String)

instance Functor (Foo g) where
  fmap :: (a -> b) -> Foo g a -> Foo g b
  fmap f (Foo strToA gStr) = Foo (f . strToA) gStr

instance FFunctor Foo where
  ffmap :: (g ~> h) -> Foo g a -> Foo h a
  ffmap gh (Foo strToA gStr) = Foo strToA (gh gStr)

An FFunctor instance can use its Functor parameter nested. The following Bar g a example uses g nested twice.

newtype Bar g a = Bar (g (g a))

instance Functor g => Functor (Bar g) where
  fmap f (Bar gga) = Bar $ fmap (fmap f gga)

instance FFunctor Bar where
  ffmap gh (Bar gga) = Bar $ fmap gh (gh gga)

Non-example

ContT r has the right kind to be an FFunctor, that is, (Type -> Type) -> Type -> Type. But there can be no instances of FFunctor (ContT r), because ContT r m uses m in negative position.

newtype ContT r m a = ContT {
    runContT :: (a -> m r) -> m r
    --                ^       ^ positive position
    --                | negative position
  }

Methods

ffmap :: (Functor g, Functor h) => (g ~> h) -> ff g x -> ff h x Source #

Instances

Instances details
FFunctor Ap Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Ap g x -> Ap h x Source #

FFunctor Ap Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Ap g x -> Ap h x Source #

FFunctor Cofree Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Cofree g x -> Cofree h x Source #

FFunctor Free Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Free g x -> Free h x Source #

FFunctor F Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> F g x -> F h x Source #

FFunctor Lift Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Lift g x -> Lift h x Source #

FFunctor (Rec1 :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Rec1 g x -> Rec1 h x Source #

FFunctor (EnvT e) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> EnvT e g x -> EnvT e h x Source #

FFunctor (StoreT s) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> StoreT s g x -> StoreT s h x Source #

FFunctor (TracedT m) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> TracedT m g x -> TracedT m h x Source #

Functor f => FFunctor (FreeT f) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> FreeT f g x -> FreeT f h x Source #

FFunctor (ApT f) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> ApT f g x -> ApT f h x Source #

FFunctor (Exp1 f) Source # 
Instance details

Defined in Data.Functor.Exp

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Exp1 f g x -> Exp1 f h x Source #

FFunctor (Cont k) Source # 
Instance details

Defined in FMonad.Cont.Curried

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Cont k g x -> Cont k h x Source #

FFunctor (Cont k) Source # 
Instance details

Defined in FMonad.Cont.Exp

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Cont k g x -> Cont k h x Source #

FFunctor ff => FFunctor (FFree ff) Source # 
Instance details

Defined in FMonad.FFree

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> FFree ff g x -> FFree ff h x Source #

Functor m => FFunctor (FreeT' m) Source # 
Instance details

Defined in FMonad.FreeT

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> FreeT' m g x -> FreeT' m h x Source #

FFunctor (Day f) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Day f g x -> Day f h x Source #

Functor f => FFunctor (Curried f) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Curried f g x -> Curried f h x Source #

FFunctor (IdentityT :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> IdentityT g x -> IdentityT h x Source #

FFunctor (ReaderT e) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> ReaderT e g x -> ReaderT e h x Source #

FFunctor (StateT s) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> StateT s g x -> StateT s h x Source #

FFunctor (WriterT m) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> WriterT m g x -> WriterT m h x Source #

Functor f => FFunctor (Product f) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Product f g x -> Product f h x Source #

Functor f => FFunctor (Sum f) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Sum f g x -> Sum f h x Source #

Functor f => FFunctor ((:*:) f) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> (f :*: g) x -> (f :*: h) x Source #

Functor f => FFunctor ((:+:) f) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> (f :+: g) x -> (f :+: h) x Source #

(FFunctor ff, FFunctor gg) => FFunctor (FCompose ff gg) Source # 
Instance details

Defined in FFunctor.FCompose

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> FCompose ff gg g x -> FCompose ff gg h x Source #

(FFunctor mm, Functor s) => FFunctor (StateT s mm) Source # 
Instance details

Defined in FMonad.State.Day

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> StateT s mm g x -> StateT s mm h x Source #

(FFunctor mm, Functor s) => FFunctor (StateT s mm) Source # 
Instance details

Defined in FMonad.State.Lan

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> StateT s mm g x -> StateT s mm h x Source #

(FFunctor mm, Functor s) => FFunctor (StateT s mm) Source # 
Instance details

Defined in FMonad.State.Ran

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> StateT s mm g x -> StateT s mm h x Source #

FFunctor mm => FFunctor (StateT s1 mm) Source # 
Instance details

Defined in FMonad.State.Simple.Inner

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> StateT s1 mm g x -> StateT s1 mm h x Source #

FFunctor mm => FFunctor (StateT s0 mm) Source # 
Instance details

Defined in FMonad.State.Simple.Outer

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> StateT s0 mm g x -> StateT s0 mm h x Source #

FFunctor (Lan f) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Lan f g x -> Lan f h x Source #

FFunctor (Ran f) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Ran f g x -> Ran f h x Source #

Functor f => FFunctor (Compose f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Compose f g x -> Compose f h x Source #

Functor f => FFunctor ((:.:) f :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> (f :.: g) x -> (f :.: h) x Source #

FFunctor (M1 c m :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> M1 c m g x -> M1 c m h x Source #

Functor f => FFunctor (Precompose f) Source # 
Instance details

Defined in Data.Functor.Precompose

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Precompose f g x -> Precompose f h x Source #

(FFunctor ff, FFunctor gg) => FFunctor (Product ff gg) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Product ff gg g x -> Product ff gg h x Source #

(FFunctor ff, FFunctor gg) => FFunctor (Sum ff gg) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> Sum ff gg g x -> Sum ff gg h x Source #

(Functor f, Functor g) => FFunctor (Bicompose f g) Source # 
Instance details

Defined in Data.Functor.Bicompose

Methods

ffmap :: forall (g0 :: Type -> Type) (h :: Type -> Type) x. (Functor g0, Functor h) => (g0 ~> h) -> Bicompose f g g0 x -> Bicompose f g h x Source #

Functor g => FFunctor (Flip1 ApT g) Source # 
Instance details

Defined in FFunctor

Methods

ffmap :: forall (g0 :: Type -> Type) (h :: Type -> Type) x. (Functor g0, Functor h) => (g0 ~> h) -> Flip1 ApT g g0 x -> Flip1 ApT g h x Source #

(FFunctor ff, FFunctor ww, FFunctor uu) => FFunctor (AdjointT ff uu ww) Source # 
Instance details

Defined in FComonad.Adjoint

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> AdjointT ff uu ww g x -> AdjointT ff uu ww h x Source #

(FFunctor ff, FFunctor mm, FFunctor uu) => FFunctor (AdjointT ff uu mm) Source # 
Instance details

Defined in FMonad.Adjoint

Methods

ffmap :: forall (g :: Type -> Type) (h :: Type -> Type) x. (Functor g, Functor h) => (g ~> h) -> AdjointT ff uu mm g x -> AdjointT ff uu mm h x Source #

Utilities to kind-annotate FFunctor instances

type FUNCTOR = Type -> Type Source #

The kind of a Functor

type FF = FUNCTOR -> FUNCTOR Source #

The kind of a FFunctor.