one-liner-0.4.1: Constraint-based generics

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

Generics.OneLiner

Contents

Description

This module is for writing generic functions on algebraic data types of kind *. These data types must be an instance of the Generic type class, which can be derived.

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

createA :: (ADT t, Constraints t c, Applicative 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

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

Note that this assumes a straightforward Monoid instance of Put which binary unfortunately does not provide.

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.

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)

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.

Combining values

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

Combine two values by combining each component of the structures with the given function. Returns Nothing if the constructors don't match.

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

zipWithA :: (ADT t, Constraints t c, Applicative f) => for c -> (forall s. c s => s -> s -> f s) -> t -> t -> Maybe (f t) Source

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

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.

Single constructor functions

op0 :: (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 = op0 (For :: For Monoid) mempty
fromInteger i = op0 (For :: For Num) (fromInteger i)

op1 :: (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 gmap.

negate = op1 (For :: For Num) negate

op2 :: (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 = op2 (For :: For Monoid) mappend
(+) = op2 (For :: For Num) (+)

Types

type ADT t = (Generic t, ADT' (Rep t)) Source

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

type ADTRecord t = (ADT t, ADTRecord' (Rep t)) 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 DeepConstraint c t => Deep c t Source

Deep c recursively requires all parts of the datatype to be an instance of c and of Generic.

Instances

DeepConstraint c t => Deep c t 

type family DeepConstraint c t :: Constraint Source

A trick to avoid GHC from detecting a cycle.

Instances

type DeepConstraint c t = (c t, ADT t, Constraints t (Deep c), Constraints t c) 

isAtom :: forall t proxy. (ADT t, Typeable t, Constraints t Typeable) => proxy t -> Bool Source

For primitive values like Int, Float, Double and Char, the generic representation of a value contains itself. If you use generics recursively (f.e. using Deep), use isAtom to detect primitive values and prevent an infinite loop.