barbies-0.1.3.1: Classes for working with types that can change clothes.

Safe HaskellNone
LanguageHaskell2010

Data.Barbie.Internal.Functor

Synopsis

Documentation

class FunctorB b where Source #

Barbie-types that can be mapped over. Instances of FunctorB should satisfy the following laws:

  bmap id = id
  bmap f . bmap g = bmap (f . g)

There is a default bmap implementation for Generic types, so instances can derived automatically.

Methods

bmap :: (forall a. f a -> g a) -> b f -> b g Source #

bmap :: CanDeriveGenericInstance b => (forall a. f a -> g a) -> b f -> b g Source #

Instances
FunctorB b => FunctorB (Barbie b) Source # 
Instance details

Defined in Data.Barbie.Internal.Instances

Methods

bmap :: (forall a. f a -> g a) -> Barbie b f -> Barbie b g Source #

class GFunctorB b Source #

Minimal complete definition

gbmap

Instances
GFunctorB (V1 :: * -> *) Source # 
Instance details

Defined in Data.Barbie.Internal.Functor

Methods

gbmap :: (forall a. f a -> g a) -> V1 x -> Repl (Target F) (Target G) V1 x

GFunctorB (U1 :: * -> *) Source # 
Instance details

Defined in Data.Barbie.Internal.Functor

Methods

gbmap :: (forall a. f a -> g a) -> U1 x -> Repl (Target F) (Target G) U1 x

(K1 i c :: * -> *) ~ Repl (Target F) (Target G) (K1 i c :: * -> *) => GFunctorB (K1 i c :: * -> *) Source # 
Instance details

Defined in Data.Barbie.Internal.Functor

Methods

gbmap :: (forall a. f a -> g a) -> K1 i c x -> Repl (Target F) (Target G) (K1 i c) x

(GFunctorB l, GFunctorB r) => GFunctorB (l :+: r) Source # 
Instance details

Defined in Data.Barbie.Internal.Functor

Methods

gbmap :: (forall a. f a -> g a) -> (l :+: r) x -> Repl (Target F) (Target G) (l :+: r) x

(GFunctorB l, GFunctorB r) => GFunctorB (l :*: r) Source # 
Instance details

Defined in Data.Barbie.Internal.Functor

Methods

gbmap :: (forall a. f a -> g a) -> (l :*: r) x -> Repl (Target F) (Target G) (l :*: r) x

GFunctorB x => GFunctorB (M1 i c x) Source # 
Instance details

Defined in Data.Barbie.Internal.Functor

Methods

gbmap :: (forall a. f a -> g a) -> M1 i c x x0 -> Repl (Target F) (Target G) (M1 i c x) x0

gbmapDefault :: CanDeriveGenericInstance b => (forall a. f a -> g a) -> b f -> b g Source #

Default implementation of bmap based on Generic.

type CanDeriveGenericInstance b = (Generic (b (Target F)), Generic (b (Target G)), GFunctorB (Rep (b (Target F))), Rep (b (Target G)) ~ Repl (Target F) (Target G) (Rep (b (Target F)))) Source #

Intuivively, the requirements to have FunctorB B derived are:

  • There is an instance of Generic (B f) for every f
  • If f is used as argument to some type in the definition of B, it is only on a Barbie-type with a FunctorB instance.
  • Recursive usages of B f are allowed to appear as argument to a Functor (e.g. @Maybe (B f)')