one-liner-1.0: Constraint-based generics

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

Generics.OneLiner.Binary

Contents

Description

These generic functions allow changing the types of the constant leaves. They require type classes with 2 parameters, the first for the input type and the second for the output type.

All functions without postfix are for instances of Generic, and functions with postfix 1 are for instances of Generic1 (with kind * -> *) which get an extra argument to specify how to deal with the parameter. Functions with postfix 01 are also for Generic1 but they get yet another argument that, like the Generic functions, allows handling of constant leaves.

Synopsis

Traversing values

gmap :: forall c t t'. (ADT t t', Constraints t t' c) => (forall s s'. c s s' => s -> s') -> t -> t' Source #

Map over a structure, updating each component.

gmap is generic specialized to (->).

gtraverse :: forall c t t' f. (ADT t t', Constraints t t' c, Applicative f) => (forall s s'. c s s' => s -> f s') -> t -> f t' Source #

Map each component of a structure to an action, evaluate these actions from left to right, and collect the results.

gtraverse is generic specialized to Star.

gmap1 :: forall c t t' a b. (ADT1 t t', Constraints1 t t' c) => (forall d e s s'. c s s' => (d -> e) -> s d -> s' e) -> (a -> b) -> t a -> t' b Source #

gmap1 is generic1 specialized to (->).

gtraverse1 :: forall c t t' f a b. (ADT1 t t', Constraints1 t t' c, Applicative f) => (forall d e s s'. c s s' => (d -> f e) -> s d -> f (s' e)) -> (a -> f b) -> t a -> f (t' b) Source #

gtraverse1 is generic1 specialized to Star.

Combining values

zipWithA :: forall c t t' f. (ADT t t', Constraints t t' c, Alternative f) => (forall s s'. c s s' => s -> s -> f s') -> t -> t -> f t' Source #

Combine two values by combining each component of the structures with the given function, under an applicative effect. Returns empty if the constructors don't match.

zipWithA is generic specialized to Zip

zipWithA1 :: forall c t t' f a b. (ADT1 t t', Constraints1 t t' c, Alternative f) => (forall d e s s'. c s s' => (d -> d -> f e) -> s d -> s d -> f (s' e)) -> (a -> a -> f b) -> t a -> t a -> f (t' b) Source #

zipWithA1 is generic1 specialized to Zip

Functions for records

These functions only work for single constructor data types.

unaryOp :: forall c t t'. (ADTRecord t t', Constraints t t' c) => (forall s s'. c s s' => s -> s') -> t -> t' Source #

Implement a unary operator by calling the operator on the components. This is here for consistency, it is the same as record.

negate = unaryOp @Num negate

binaryOp :: forall c t t'. (ADTRecord t t', Constraints t t' c) => (forall s s'. c s s' => s -> s -> s') -> t -> t -> t' Source #

Implement a binary operator by calling the operator on the components.

mappend = binaryOp @Monoid mappend
(+) = binaryOp @Num (+)

binaryOp is algebra specialized to pairs.

algebra :: forall c t t' f. (ADTRecord t t', Constraints t t' c, Functor f) => (forall s s'. c s s' => f s -> s') -> f t -> t' Source #

Create an F-algebra, given an F-algebra for each of the components.

binaryOp f l r = algebra @c (\(Pair a b) -> f a b) (Pair l r)

algebra is record specialized to Costar.

dialgebra :: forall c t t' f g. (ADTRecord t t', Constraints t t' c, Functor f, Applicative g) => (forall s s'. c s s' => f s -> g s') -> f t -> g t' Source #

dialgebra is record specialized to Biff (->).

gcotraverse1 :: forall c t t' f a b. (ADTRecord1 t t', Constraints1 t t' c, Functor f) => (forall d e s s'. c s s' => (f d -> e) -> f (s d) -> s' e) -> (f a -> b) -> f (t a) -> t' b Source #

gcotraverse1 is record1 specialized to Costar.

Generic programming with profunctors

All the above functions have been implemented using these functions, using different profunctors.

record :: forall c p t t'. (ADTRecord t t', Constraints t t' c, GenericRecordProfunctor p) => (forall s s'. c s s' => p s s') -> p t t' Source #

nonEmpty :: forall c p t t'. (ADTNonEmpty t t', Constraints t t' c, GenericNonEmptyProfunctor p) => (forall s s'. c s s' => p s s') -> p t t' Source #

generic :: forall c p t t'. (ADT t t', Constraints t t' c, GenericProfunctor p) => (forall s s'. c s s' => p s s') -> p t t' Source #

record1 :: forall c p t t' a b. (ADTRecord1 t t', Constraints1 t t' c, GenericRecordProfunctor p) => (forall d e s s'. c s s' => p d e -> p (s d) (s' e)) -> p a b -> p (t a) (t' b) Source #

nonEmpty1 :: forall c p t t' a b. (ADTNonEmpty1 t t', Constraints1 t t' c, GenericNonEmptyProfunctor p) => (forall d e s s'. c s s' => p d e -> p (s d) (s' e)) -> p a b -> p (t a) (t' b) Source #

generic1 :: forall c p t t' a b. (ADT1 t t', Constraints1 t t' c, GenericProfunctor p) => (forall d e s s'. c s s' => p d e -> p (s d) (s' e)) -> p a b -> p (t a) (t' b) Source #

record01 :: forall c0 c1 p t t' a b. (ADTRecord1 t t', Constraints01 t t' c0 c1, GenericRecordProfunctor p) => (forall s s'. c0 s s' => p s s') -> (forall d e s s'. c1 s s' => p d e -> p (s d) (s' e)) -> p a b -> p (t a) (t' b) Source #

nonEmpty01 :: forall c0 c1 p t t' a b. (ADTNonEmpty1 t t', Constraints01 t t' c0 c1, GenericNonEmptyProfunctor p) => (forall s s'. c0 s s' => p s s') -> (forall d e s s'. c1 s s' => p d e -> p (s d) (s' e)) -> p a b -> p (t a) (t' b) Source #

generic01 :: forall c0 c1 p t t' a b. (ADT1 t t', Constraints01 t t' c0 c1, GenericProfunctor p) => (forall s s'. c0 s s' => p s s') -> (forall d e s s'. c1 s s' => p d e -> p (s d) (s' e)) -> p a b -> p (t a) (t' b) Source #

Classes

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 #

Types

type ADT t t' = (Generic t, Generic t', ADT' (Rep t) (Rep t'), Constraints t t' AnyType) Source #

ADT is a constraint type synonym. The Generic instance can be derived, and any generic representation will be an instance of ADT' and AnyType.

type ADTNonEmpty t t' = (Generic t, Generic t', ADTNonEmpty' (Rep t) (Rep t'), Constraints t t' AnyType) Source #

ADTNonEmpty is a constraint type synonym. An instance is an ADT with *at least* one constructor.

type ADTRecord t t' = (Generic t, Generic t', ADTRecord' (Rep t) (Rep t'), Constraints t t' AnyType) Source #

ADTRecord is a constraint type synonym. An instance is an ADT with *exactly* one constructor.

type Constraints t t' c = Constraints' (Rep t) (Rep t') c AnyType Source #

Constraints is a constraint type synonym, containing the constraint requirements for an instance for t of class c. It requires an instance of class c for each component of t.

type ADT1 t t' = (Generic1 t, Generic1 t', ADT1' (Rep1 t) (Rep1 t'), Constraints1 t t' AnyType) Source #

type Constraints1 t t' c = Constraints' (Rep1 t) (Rep1 t') AnyType c Source #

type Constraints01 t t' c0 c1 = Constraints' (Rep1 t) (Rep1 t') c0 c1 Source #

class FunConstraints c t Source #

Automatically apply a lifted function to a polymorphic argument as many times as possible.

A constraint `FunConstraint c t` is equivalent to the conjunction of constraints `c s` for every argument type of t.

If r is not a function type:

c a :- FunConstraints c (a -> r)
(c a, c b) :- FunConstraints c (a -> b -> r)
(c a, c b, c d) :- FunConstraints c (a -> b -> d -> r)

Minimal complete definition

autoApply

Instances

(~) * (FunResult r) r => FunConstraints c r Source # 

Methods

autoApply :: Applicative f => (forall s. c s => f s) -> f r -> f (FunResult r) Source #

(c a, FunConstraints c b) => FunConstraints c (a -> b) Source # 

Methods

autoApply :: Applicative f => (forall s. c s => f s) -> f (a -> b) -> f (FunResult (a -> b)) Source #

type family FunResult t where ... Source #

The result type of a curried function.

If r is not a function type (i.e., does not unify with `_ -> _`):

FunResult (a -> r) ~ r
FunResult (a -> b -> r) ~ r
FunResult (a -> b -> c -> r) ~ r

Equations

FunResult (a -> b) = FunResult b 
FunResult r = r 

class AnyType a b Source #

Instances

AnyType k2 k1 a b Source #