yaya-0.4.2.1: Total recursion schemes.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Yaya.Functor

Description

This should probably be a separate library, but it provides a number of functor type classes between various categories.

Synopsis
  • class DFunctor (d :: (* -> *) -> *) where
    • dmap :: (forall x. f x -> g x) -> d f -> d g
  • firstMap :: (DFunctor d, Bifunctor f) => (a -> b) -> d (f a) -> d (f b)
  • class HFunctor (h :: (* -> *) -> * -> *) where
    • hmap :: (forall x. f x -> g x) -> h f a -> h g a

Documentation

class DFunctor (d :: (* -> *) -> *) where Source #

A functor from the category of endofunctors to *Hask*. The D is meant to be a mnemonic for “down”, as we’re “lowering” from endofunctors to types.

Methods

dmap :: (forall x. f x -> g x) -> d f -> d g Source #

Instances

Instances details
DFunctor Nu Source # 
Instance details

Defined in Yaya.Fold

Methods

dmap :: (forall x. f x -> g x) -> Nu f -> Nu g Source #

DFunctor Mu Source # 
Instance details

Defined in Yaya.Fold

Methods

dmap :: (forall x. f x -> g x) -> Mu f -> Mu g Source #

firstMap :: (DFunctor d, Bifunctor f) => (a -> b) -> d (f a) -> d (f b) Source #

This isn’t a Functor instance because of the position of the a, but you can use it like: > newtype List a = List (Mu (XNor a)) > instance Functor List where > fmap f (List mu) = List (firstMap f mu)

class HFunctor (h :: (* -> *) -> * -> *) where Source #

An endofunctor in the category of endofunctors.

NB: This is similar to MFunctor / hoist from mmorph, but without the Monad constraint on f.

Methods

hmap :: (forall x. f x -> g x) -> h f a -> h g a Source #

Instances

Instances details
HFunctor MaybeT Source # 
Instance details

Defined in Yaya.Functor

Methods

hmap :: (forall x. f x -> g x) -> MaybeT f a -> MaybeT g a Source #

HFunctor Lift Source # 
Instance details

Defined in Yaya.Functor

Methods

hmap :: (forall x. f x -> g x) -> Lift f a -> Lift g a Source #

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

Defined in Yaya.Functor

Methods

hmap :: (forall x. f x -> g x) -> IdentityT f a -> IdentityT g a Source #

HFunctor (ExceptT e) Source # 
Instance details

Defined in Yaya.Functor

Methods

hmap :: (forall x. f x -> g x) -> ExceptT e f a -> ExceptT e g a Source #

HFunctor (StateT s) Source # 
Instance details

Defined in Yaya.Functor

Methods

hmap :: (forall x. f x -> g x) -> StateT s f a -> StateT s g a Source #

HFunctor (Backwards :: (Type -> Type) -> Type -> Type) Source # 
Instance details

Defined in Yaya.Functor

Methods

hmap :: (forall x. f x -> g x) -> Backwards f a -> Backwards g a Source #

HFunctor (ReaderT r) Source # 
Instance details

Defined in Yaya.Functor

Methods

hmap :: (forall x. f x -> g x) -> ReaderT r f a -> ReaderT r g a Source #

HFunctor (StateT s) Source # 
Instance details

Defined in Yaya.Functor

Methods

hmap :: (forall x. f x -> g x) -> StateT s f a -> StateT s g a Source #

HFunctor (WriterT w) Source # 
Instance details

Defined in Yaya.Functor

Methods

hmap :: (forall x. f x -> g x) -> WriterT w f a -> WriterT w g a Source #

HFunctor (WriterT w) Source # 
Instance details

Defined in Yaya.Functor

Methods

hmap :: (forall x. f x -> g x) -> WriterT w f a -> WriterT w g a Source #

HFunctor (Product f) Source # 
Instance details

Defined in Yaya.Functor

Methods

hmap :: (forall x. f0 x -> g x) -> Product f f0 a -> Product f g a Source #

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

Defined in Yaya.Functor

Methods

hmap :: (forall x. f0 x -> g x) -> Compose f f0 a -> Compose f g a Source #

HFunctor (RWST r w s) Source # 
Instance details

Defined in Yaya.Functor

Methods

hmap :: (forall x. f x -> g x) -> RWST r w s f a -> RWST r w s g a Source #

HFunctor (RWST r w s) Source # 
Instance details

Defined in Yaya.Functor

Methods

hmap :: (forall x. f x -> g x) -> RWST r w s f a -> RWST r w s g a Source #