one-liner-0.8: Constraint-based generics

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

Generics.OneLiner

Contents

Description

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.

Synopsis

Producing values

create :: (ADT t, Constraints t c) => for c -> (forall s. c s => [s]) -> [t] Source #

Create a value (one for each constructor), given how to construct the components.

minBound = head $ create (For :: For Bounded) [minBound]
maxBound = last $ create (For :: For Bounded) [maxBound]

create is createA specialized to lists.

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

Create a value (one for each constructor), given how to construct the components, under an applicative effect.

Here's how to implement get from the binary package:

get = getWord8 >>= \ix -> createA (For :: For Binary) [get] !! fromEnum ix

createA is generic specialized to Joker.

ctorIndex :: ADT t => t -> Int Source #

Get the index in the lists returned by create and createA of the constructor of the given value.

For example, this is the implementation of put that generates the binary data that the above implentation of get expects:

put t = putWord8 (toEnum (ctorIndex t)) <> gfoldMap (For :: For Binary) put t

create1 :: (ADT1 t, Constraints1 t c) => for c -> (forall b s. c s => [b] -> [s b]) -> [a] -> [t a] Source #

create1 is createA1 specialized to lists.

createA1 :: (ADT1 t, Constraints1 t c, Alternative f) => for c -> (forall b s. c s => f b -> f (s b)) -> f a -> f (t a) Source #

createA1 is generic1 specialized to Joker.

ctorIndex1 :: ADT1 t => t a -> Int Source #

Traversing values

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

Map over a structure, updating each component.

gmap is generic specialized to (->).

gfoldMap :: (ADT t, Constraints t c, Monoid m) => for c -> (forall s. c s => s -> m) -> t -> m Source #

Map each component of a structure to a monoid, and combine the results.

If you have a class Size, which measures the size of a structure, then this could be the default implementation:

size = succ . getSum . gfoldMap (For :: For Size) (Sum . size)

gfoldMap is gtraverse specialized to Const.

gtraverse :: (ADT t, Constraints t c, Applicative f) => for c -> (forall s. c 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 :: (ADT1 t, Constraints1 t c) => for c -> (forall d e s. c s => (d -> e) -> s d -> s e) -> (a -> b) -> t a -> t b Source #

fmap = gmap1 (For :: For Functor) fmap

gmap1 is generic1 specialized to (->).

gfoldMap1 :: (ADT1 t, Constraints1 t c, Monoid m) => for c -> (forall s b. c s => (b -> m) -> s b -> m) -> (a -> m) -> t a -> m Source #

foldMap = gfoldMap1 (For :: For Foldable) foldMap

gfoldMap1 is gtraverse1 specialized to Const.

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

traverse = gtraverse1 (For :: For Traversable) traverse

gtraverse1 is generic1 specialized to Star.

Combining values

mzipWith :: (ADT t, Constraints t c, Monoid m) => for c -> (forall s. c s => s -> s -> m) -> t -> t -> m Source #

Combine two values by combining each component of the structures to a monoid, and combine the results. Returns mempty if the constructors don't match.

compare s t = compare (ctorIndex s) (ctorIndex t) <> mzipWith (For :: For Ord) compare s t

mzipWith is zipWithA specialized to Compose Maybe (Const m)

zipWithA :: (ADT t, Constraints t c, Alternative f) => for c -> (forall s. c 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.

mzipWith1 :: (ADT1 t, Constraints1 t c, Monoid m) => for c -> (forall s b. c s => (b -> b -> m) -> s b -> s b -> m) -> (a -> a -> m) -> t a -> t a -> m Source #

liftCompare = mzipWith1 (For :: For Ord1) liftCompare

mzipWith1 is zipWithA1 specialized to Compose Maybe (Const m)

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

Consuming values

consume :: (ADT t, Constraints t c, Decidable f) => for c -> (forall s. c s => f s) -> f t Source #

Generate ways to consume values of type t. This is the contravariant version of createA.

consume is generic specialized to Clown.

consume1 :: (ADT1 t, Constraints1 t c, Decidable f) => for c -> (forall b s. c s => f b -> f (s b)) -> f a -> f (t a) Source #

consume1 is generic1 specialized to Clown.

Functions for records

These functions only work for single constructor data types.

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

Implement a nullary operator by calling the operator for each component.

mempty = nullaryOp (For :: For Monoid) mempty
fromInteger i = nullaryOp (For :: For Num) (fromInteger i)

nullaryOp is record specialized to Tagged.

unaryOp :: (ADTRecord t, Constraints t c) => for c -> (forall s. c 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 (For :: For Num) negate

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

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

mappend = binaryOp (For :: For Monoid) mappend
(+) = binaryOp (For :: For Num) (+)

binaryOp is algebra specialized to pairs.

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

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

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

algebra is record specialized to Costar.

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

dialgebra is record specialized to Biff (->).

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

cotraverse = gcotraverse1 (For :: For Distributive) cotraverse

gcotraverse1 is record1 specialized to Costar.

Generic programming with profunctors

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

class Profunctor p => GenericRecordProfunctor p where 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.

Minimal complete definition

unit, mult

Methods

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

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

Instances

GenericRecordProfunctor (->) Source # 

Methods

unit :: U1 a -> U1 a' Source #

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

Applicative f => GenericRecordProfunctor (Star f) Source # 

Methods

unit :: Star f (U1 a) (U1 a') Source #

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

Functor f => GenericRecordProfunctor (Costar f) Source # 

Methods

unit :: Costar f (U1 a) (U1 a') Source #

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

GenericRecordProfunctor (Tagged *) Source # 

Methods

unit :: Tagged * (U1 a) (U1 a') Source #

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

GenericRecordProfunctor (Ctor *) Source # 

Methods

unit :: Ctor * (U1 a) (U1 a') Source #

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

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

Methods

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

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

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

Methods

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

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

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

Methods

unit :: Product * * p q (U1 a) (U1 a') Source #

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, GenericRecordProfunctor p) => GenericRecordProfunctor (Tannen * * * f p) Source # 

Methods

unit :: Tannen * * * f p (U1 a) (U1 a') Source #

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) => GenericRecordProfunctor (Biff * * * * (->) f g) Source # 

Methods

unit :: Biff * * * * (->) f g (U1 a) (U1 a') Source #

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

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

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

class GenericRecordProfunctor p => GenericNonEmptyProfunctor p where Source #

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

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

GenericNonEmptyProfunctor (->) Source # 

Methods

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

Applicative f => GenericNonEmptyProfunctor (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 #

GenericNonEmptyProfunctor (Ctor *) Source # 

Methods

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

Alternative f => GenericNonEmptyProfunctor (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 => GenericNonEmptyProfunctor (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 #

(GenericNonEmptyProfunctor p, GenericNonEmptyProfunctor q) => GenericNonEmptyProfunctor (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, GenericNonEmptyProfunctor p) => GenericNonEmptyProfunctor (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 #

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

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

class GenericNonEmptyProfunctor p => GenericProfunctor p where Source #

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

Minimal complete definition

identity

Methods

identity :: p a a Source #

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

Instances

GenericProfunctor (->) Source # 

Methods

identity :: a -> a Source #

zero :: V1 a -> V1 a' Source #

Applicative f => GenericProfunctor (Star f) Source # 

Methods

identity :: Star f a a Source #

zero :: Star f (V1 a) (V1 a') Source #

GenericProfunctor (Ctor *) Source # 

Methods

identity :: Ctor * a a Source #

zero :: Ctor * (V1 a) (V1 a') Source #

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

Methods

identity :: Joker * * f a a Source #

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

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

Methods

identity :: Clown * * f a a Source #

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

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

Methods

identity :: Product * * p q a a Source #

zero :: Product * * p q (V1 a) (V1 a') Source #

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

Methods

identity :: Tannen * * * f p a a Source #

zero :: Tannen * * * f p (V1 a) (V1 a') Source #

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

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

Types

type ADT t = (Generic t, ADT' (Rep t), Constraints 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 = (Generic t, ADTNonEmpty' (Rep t), Constraints t AnyType) Source #

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

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

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

type Constraints t c = Constraints' (Rep t) c 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.

data For c Source #

Tell the compiler which class we want to use in the traversal. Should be used like this:

(For :: For Show)

Where Show can be any class.

Constructors

For 

class AnyType a Source #

Any type is instance of AnyType, you can use it with For :: For AnyType if you don't actually need a class constraint.

Instances