idiomatic-0.1.1.0: Deriving Applicative for sum types.. Idiomatically.
Safe HaskellNone
LanguageHaskell98

Generic.Applicative.Idiom

Synopsis

Documentation

class (Applicative f, Applicative g) => Idiom tag f g where Source #

An Idiom captures an "applicative homomorphism" between two applicatives, indexed by a tag.

An appliative homomorphism is a polymorphic function between two applicative functors that preserves the Applicative structure.

idiom (pure a) = pure a

idiom (liftA2 (·) as bs) = liftA2 (·) (idiom as) (idiom bs)

Based on: Abstracting with Applicatives.

Methods

idiom :: f ~> g Source #

Instances

Instances details
(Applicative f, Applicative g, IdiomDup (CheckIdiomDup g) f g) => Idiom Dup f g Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> g Source #

(Applicative outer, Applicative f, comp ~ Compose outer f) => Idiom Outer f comp Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> comp Source #

(Applicative f, Applicative inner, comp ~ Compose f inner) => Idiom Inner f comp Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> comp Source #

(Identity ~ id, Applicative f) => Idiom Initial id f Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: id ~> f Source #

(Applicative f, f ~ g) => Idiom Id f g Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> g Source #

(Applicative f, Monoid m) => Idiom Terminal f (Proxy :: Type -> Type) Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> Proxy Source #

(Applicative f, Monoid m) => Idiom Terminal f (Const m :: Type -> Type) Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> Const m Source #

(Applicative f, Applicative g) => Idiom Snd (Product f g) g Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: Product f g ~> g Source #

(Applicative f, Applicative g) => Idiom Fst (Product f g) f Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: Product f g ~> f Source #

(Idiom tag1 f g, Idiom tag2 g h) => Idiom (Comp tag1 tag2 :: Type) f h Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> h Source #

(Idiom tag1 f g, Idiom tag2 f h) => Idiom (tag1 &&& tag2 :: Type) f (Product g h) Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> Product g h Source #

data Id Source #

The identity applicative morphism.

idiom :: f ~> f
idiom = id

Instances

Instances details
(Applicative f, f ~ g) => Idiom Id f g Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> g Source #

data Comp tag1 tag2 infixr 7 Source #

The left-to-right composition of applicative morphisms.

Instances

Instances details
(Idiom tag1 f g, Idiom tag2 g h) => Idiom (Comp tag1 tag2 :: Type) f h Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> h Source #

data Initial Source #

The initial applicative morphism.

It turns Identity into any Applicative functor.

idiom :: Identity ~> f
idiom (Identity a) = pure a

Instances

Instances details
(Identity ~ id, Applicative f) => Idiom Initial id f Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: id ~> f Source #

data Terminal Source #

The terminal applicative morphism.

It turns any applicative into Const m, or Proxy

idiom :: f ~> Const m
idiom _ = Const mempty

idiom :: f ~> Proxy
idiom _ = Proxy

Instances

Instances details
(Applicative f, Monoid m) => Idiom Terminal f (Proxy :: Type -> Type) Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> Proxy Source #

(Applicative f, Monoid m) => Idiom Terminal f (Const m :: Type -> Type) Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> Const m Source #

data Inner Source #

This applicative morphism composes a functor on the _inside_.

idiom :: f ~> Compose f inner
idiom = Compose . fmap pure

Instances

Instances details
(Applicative f, Applicative inner, comp ~ Compose f inner) => Idiom Inner f comp Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> comp Source #

data Outer Source #

This applicative morphism composes a functor on the _outside_.

idiom :: f ~> Compose outer f
idiom = Compose . pure

Instances

Instances details
(Applicative outer, Applicative f, comp ~ Compose outer f) => Idiom Outer f comp Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> comp Source #

data Dup Source #

This applicative morphism duplicates a functor any number of times.

idiom :: f ~> f
idiom = id

idiom :: f ~> Product f f
idiom as = Pair as as

idiom :: f ~> Product f (Product f f)
idiom as = Pair as (Pair as as)

Instances

Instances details
(Applicative f, Applicative g, IdiomDup (CheckIdiomDup g) f g) => Idiom Dup f g Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> g Source #

data tag1 &&& tag2 Source #

An applicative functor for constructing a product.

idiom :: f ~> Product g h
idiom as = Pair (idiom as) (idiom as)

Instances

Instances details
(Idiom tag1 f g, Idiom tag2 f h) => Idiom (tag1 &&& tag2 :: Type) f (Product g h) Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: f ~> Product g h Source #

data Fst Source #

The applicative functor that gets the first component of a product.

idiom :: Product f g ~> f
idiom (Pair as _) = as

Instances

Instances details
(Applicative f, Applicative g) => Idiom Fst (Product f g) f Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: Product f g ~> f Source #

data Snd Source #

The applicative functor that gets the second component of a product.

idiom :: Product f g ~> g
idiom (Pair _ bs) = bs

Instances

Instances details
(Applicative f, Applicative g) => Idiom Snd (Product f g) g Source # 
Instance details

Defined in Generic.Applicative.Idiom

Methods

idiom :: Product f g ~> g Source #