one-liner-1.0: Constraint-based generics

LicenseBSD-style (see the file LICENSE)
Maintainersjoerd@w3future.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe
LanguageHaskell98

Generics.OneLiner.Classes

Description

 

Synopsis

Documentation

class (Profunctor p, GenericUnitProfunctor p, GenericProductProfunctor p) => GenericRecordProfunctor p Source #

A generic function using a GenericRecordProfunctor works on any data type with exactly one constructor, a.k.a. records, with multiple fields (mult) or no fields (unit).

GenericRecordProfunctor is similar to ProductProfuctor from the product-profunctor package, but using types from GHC.Generics.

class (GenericRecordProfunctor p, GenericSumProfunctor p) => GenericNonEmptyProfunctor p Source #

A generic function using a GenericNonEmptyProfunctor works on any data type with at least one constructor.

class (GenericNonEmptyProfunctor p, GenericEmptyProfunctor p) => GenericProfunctor p Source #

A generic function using a GenericProfunctor works on any algebraic data type, including those with no constructors and constants.

class Profunctor p => GenericUnitProfunctor p where Source #

Minimal complete definition

unit

Methods

unit :: p (U1 a) (U1 a') Source #

class Profunctor p => GenericProductProfunctor p where Source #

Minimal complete definition

mult

Methods

mult :: p (f a) (f' a') -> p (g a) (g' a') -> p ((f :*: g) a) ((f' :*: g') a') Source #

Instances

Applicative f => GenericProductProfunctor (Star f) Source # 

Methods

mult :: Star f (f a) (f' a') -> Star f (g a) (g' a') -> Star f ((* :*: f) g a) ((* :*: f') g' a') Source #

Functor f => GenericProductProfunctor (Costar f) Source # 

Methods

mult :: Costar f (f a) (f' a') -> Costar f (g a) (g' a') -> Costar f ((* :*: f) g a) ((* :*: f') g' a') Source #

GenericProductProfunctor (Tagged *) Source # 

Methods

mult :: Tagged * (f a) (f' a') -> Tagged * (g a) (g' a') -> Tagged * ((* :*: f) g a) ((* :*: f') g' a') Source #

Applicative f => GenericProductProfunctor (Zip f) Source # 

Methods

mult :: Zip f (f a) (f' a') -> Zip f (g a) (g' a') -> Zip f ((* :*: f) g a) ((* :*: f') g' a') Source #

GenericProductProfunctor (Ctor *) Source # 

Methods

mult :: Ctor * (f a) (f' a') -> Ctor * (g a) (g' a') -> Ctor * ((* :*: f) g a) ((* :*: f') g' a') Source #

GenericProductProfunctor ((->) LiftedRep LiftedRep) Source # 

Methods

mult :: (LiftedRep -> LiftedRep) (f a) (f' a') -> (LiftedRep -> LiftedRep) (g a) (g' a') -> (LiftedRep -> LiftedRep) ((* :*: f) g a) ((* :*: f') g' a') Source #

Applicative f => GenericProductProfunctor (Joker * * f) Source # 

Methods

mult :: Joker * * f (f a) (f' a') -> Joker * * f (g a) (g' a') -> Joker * * f ((* :*: f) g a) ((* :*: f') g' a') Source #

Divisible f => GenericProductProfunctor (Clown * * f) Source # 

Methods

mult :: Clown * * f (f a) (f' a') -> Clown * * f (g a) (g' a') -> Clown * * f ((* :*: f) g a) ((* :*: f') g' a') Source #

(GenericProductProfunctor p, GenericProductProfunctor q) => GenericProductProfunctor (Product * * p q) Source # 

Methods

mult :: Product * * p q (f a) (f' a') -> Product * * p q (g a) (g' a') -> Product * * p q ((* :*: f) g a) ((* :*: f') g' a') Source #

(Applicative f, GenericProductProfunctor p) => GenericProductProfunctor (Tannen * * * f p) Source # 

Methods

mult :: Tannen * * * f p (f a) (f' a') -> Tannen * * * f p (g a) (g' a') -> Tannen * * * f p ((* :*: f) g a) ((* :*: f') g' a') Source #

(Functor f, Applicative g, Profunctor p, GenericProductProfunctor p) => GenericProductProfunctor (Biff * * * * p f g) Source # 

Methods

mult :: Biff * * * * p f g (f a) (f' a') -> Biff * * * * p f g (g a) (g' a') -> Biff * * * * p f g ((* :*: f) g a) ((* :*: f') g' a') Source #

class Profunctor p => GenericSumProfunctor p where Source #

Minimal complete definition

plus

Methods

plus :: p (f a) (f' a') -> p (g a) (g' a') -> p ((f :+: g) a) ((f' :+: g') a') Source #

Instances

Applicative f => GenericSumProfunctor (Star f) Source # 

Methods

plus :: Star f (f a) (f' a') -> Star f (g a) (g' a') -> Star f ((* :+: f) g a) ((* :+: f') g' a') Source #

Alternative f => GenericSumProfunctor (Zip f) Source # 

Methods

plus :: Zip f (f a) (f' a') -> Zip f (g a) (g' a') -> Zip f ((* :+: f) g a) ((* :+: f') g' a') Source #

GenericSumProfunctor (Ctor *) Source # 

Methods

plus :: Ctor * (f a) (f' a') -> Ctor * (g a) (g' a') -> Ctor * ((* :+: f) g a) ((* :+: f') g' a') Source #

GenericSumProfunctor ((->) LiftedRep LiftedRep) Source # 

Methods

plus :: (LiftedRep -> LiftedRep) (f a) (f' a') -> (LiftedRep -> LiftedRep) (g a) (g' a') -> (LiftedRep -> LiftedRep) ((* :+: f) g a) ((* :+: f') g' a') Source #

Alternative f => GenericSumProfunctor (Joker * * f) Source # 

Methods

plus :: Joker * * f (f a) (f' a') -> Joker * * f (g a) (g' a') -> Joker * * f ((* :+: f) g a) ((* :+: f') g' a') Source #

Decidable f => GenericSumProfunctor (Clown * * f) Source # 

Methods

plus :: Clown * * f (f a) (f' a') -> Clown * * f (g a) (g' a') -> Clown * * f ((* :+: f) g a) ((* :+: f') g' a') Source #

(GenericSumProfunctor p, GenericSumProfunctor q) => GenericSumProfunctor (Product * * p q) Source # 

Methods

plus :: Product * * p q (f a) (f' a') -> Product * * p q (g a) (g' a') -> Product * * p q ((* :+: f) g a) ((* :+: f') g' a') Source #

(Applicative f, GenericSumProfunctor p) => GenericSumProfunctor (Tannen * * * f p) Source # 

Methods

plus :: Tannen * * * f p (f a) (f' a') -> Tannen * * * f p (g a) (g' a') -> Tannen * * * f p ((* :+: f) g a) ((* :+: f') g' a') Source #

class Profunctor p => GenericEmptyProfunctor p where Source #

Minimal complete definition

identity, zero

Methods

identity :: p a a Source #

zero :: p (V1 a) (V1 a') Source #

newtype Zip f a b Source #

Constructors

Zip 

Fields

Instances

Functor f => Profunctor (Zip f) Source # 

Methods

dimap :: (a -> b) -> (c -> d) -> Zip f b c -> Zip f a d #

lmap :: (a -> b) -> Zip f b c -> Zip f a c #

rmap :: (b -> c) -> Zip f a b -> Zip f a c #

(#.) :: Coercible * c b => (b -> c) -> Zip f a b -> Zip f a c #

(.#) :: Coercible * b a => Zip f b c -> (a -> b) -> Zip f a c #

Alternative f => GenericEmptyProfunctor (Zip f) Source # 

Methods

identity :: Zip f a a Source #

zero :: Zip f (V1 * a) (V1 * a') Source #

Alternative f => GenericSumProfunctor (Zip f) Source # 

Methods

plus :: Zip f (f a) (f' a') -> Zip f (g a) (g' a') -> Zip f ((* :+: f) g a) ((* :+: f') g' a') Source #

Applicative f => GenericProductProfunctor (Zip f) Source # 

Methods

mult :: Zip f (f a) (f' a') -> Zip f (g a) (g' a') -> Zip f ((* :*: f) g a) ((* :*: f') g' a') Source #

Applicative f => GenericUnitProfunctor (Zip f) Source # 

Methods

unit :: Zip f (U1 * a) (U1 * a') Source #

absurd :: V1 a -> b Source #

e1 :: (f a -> b) -> (g a -> b) -> (f :+: g) a -> b Source #

fst1 :: (f :*: g) a -> f a Source #

snd1 :: (f :*: g) a -> g a Source #