| Portability | non-portable |
|---|---|
| Stability | experimental |
| Maintainer | sjoerd@w3future.com |
| Safe Haskell | None |
Generics.OneLiner
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.
- create :: (ADT t, Constraints t c) => for c -> (forall s. c s => s) -> [t]
- createA :: (ADT t, Constraints t c, Applicative f) => for c -> (forall s. c s => f s) -> [f t]
- ctorIndex :: ADT t => t -> Int
- gmap :: (ADT t, Constraints t c) => for c -> (forall s. c s => s -> s) -> t -> t
- gfoldMap :: (ADT t, Constraints t c, Monoid m) => for c -> (forall s. c s => s -> m) -> t -> m
- gtraverse :: (ADT t, Constraints t c, Applicative f) => for c -> (forall s. c s => s -> f s) -> t -> f t
- gzipWith :: (ADT t, Constraints t c) => for c -> (forall s. c s => s -> s -> s) -> t -> t -> Maybe t
- mzipWith :: (ADT t, Constraints t c, Monoid m) => for c -> (forall s. c s => s -> s -> m) -> t -> t -> m
- zipWithA :: (ADT t, Constraints t c, Applicative f) => for c -> (forall s. c s => s -> s -> f s) -> t -> t -> Maybe (f t)
- op0 :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s) -> t
- op1 :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s -> s) -> t -> t
- op2 :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s -> s -> s) -> t -> t -> t
- type ADT t = (Generic t, ADT' (Rep t))
- type ADTRecord t = (ADT t, ADTRecord' (Rep t))
- type Constraints t c = Constraints' (Rep t) c
- data For c = For
Producing values
create :: (ADT t, Constraints t c) => for c -> (forall s. c s => s) -> [t]Source
createA :: (ADT t, Constraints t c, Applicative f) => for c -> (forall s. c s => f s) -> [f t]Source
ctorIndex :: ADT t => t -> IntSource
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:
putt =putWord8(toEnum(ctorIndext))<>gfoldMap(For::ForBinary)putt
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 -> tSource
Map over a structure, updating each component.
gfoldMap :: (ADT t, Constraints t c, Monoid m) => for c -> (forall s. c s => s -> m) -> t -> mSource
gtraverse :: (ADT t, Constraints t c, Applicative f) => for c -> (forall s. c s => s -> f s) -> t -> f tSource
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 tSource
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 -> mSource
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.
Single constructor functions
op0 :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s) -> tSource
op1 :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s -> s) -> t -> tSource
op2 :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s -> s -> s) -> t -> t -> tSource
Types
type Constraints t c = Constraints' (Rep t) cSource
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.