| License | BSD-style (see the file LICENSE) |
|---|---|
| Maintainer | sjoerd@w3future.com |
| Stability | experimental |
| Portability | non-portable |
| Safe Haskell | None |
| Language | Haskell98 |
Generics.OneLiner.ADT
Contents
Description
This module is for writing generic functions on algebraic data types
of kind *. These data types must be an instance of the ADT type class.
Here's an example how to write such an instance for this data type:
data T a = A Int a | B a (T a)
instanceADT(T a) wherectorIndexA{} = 0ctorIndexB{} = 1ctorInfo_ 0 =ctor"A"ctorInfo_ 1 =ctor"B" typeConstraints(T a) c = (c Int, c a, c (T a))buildsRecA_ sub rec = [ A<$>sub (FieldInfo(\(A i _) -> i))<*>sub (FieldInfo(\(A _ a) -> a)) , B<$>sub (FieldInfo(\(B a _) -> a))<*>rec (FieldInfo(\(B _ t) -> t)) ]
And this is how you would write generic equality, using the All monoid:
eqADT :: (ADTt,ConstraintstEq) => t -> t ->BooleqADT s t =ctorIndexs ==ctorIndext&&getAll(mbuilds(For::ForEq) (\fld ->All$ s!fld==t!fld) `at` s)
- module Generics.OneLiner.Info
- data Constraint :: BOX
- class ADT t where
- type Constraints t c :: Constraint
- ctorIndex :: t -> Int
- ctorInfo :: t -> Int -> CtorInfo
- buildsA :: (Constraints t c, Applicative f) => for c -> (forall s. c s => FieldInfo (t -> s) -> f s) -> [f t]
- buildsRecA :: (Constraints t c, Applicative f) => for c -> (forall s. c s => FieldInfo (t -> s) -> f s) -> (FieldInfo (t -> t) -> f t) -> [f t]
- class ADT t => ADTRecord t
- data For c = For
- (!) :: t -> FieldInfo (t -> s) -> s
- at :: ADT t => [a] -> t -> a
- builds :: (ADT t, Constraints t c) => for c -> (forall s. c s => FieldInfo (t -> s) -> s) -> [t]
- mbuilds :: forall t c m for. (ADT t, Constraints t c, Monoid m) => for c -> (forall s. c s => FieldInfo (t -> s) -> m) -> [m]
- 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
- build :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => FieldInfo (t -> s) -> s) -> 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
Re-exports
module Generics.OneLiner.Info
data Constraint :: BOX
Instances
| Typeable ((* -> *) -> Constraint) Alternative | |
| Typeable ((* -> *) -> Constraint) Applicative | |
| Typeable (* -> Constraint) Monoid |
The kind of constraints
The ADT type class
Type class for algebraic data types of kind *. Implement either buildsA
if the type t is not recursive, or buildsRecA if the type t is recursive.
Minimal complete definition
ctorInfo, (buildsA | buildsRecA)
Associated Types
type Constraints t c :: Constraint Source
The constraints needed to run buildsA and buildsRecA.
It should be a list of all the types of the subcomponents of t, each applied to c.
Methods
Gives the index of the constructor of the given value in the list returned by buildsA and buildsRecA.
ctorInfo :: t -> Int -> CtorInfo Source
ctorInfo n gives constructor information, f.e. its name, for the nth constructor.
The first argument is a dummy argument and can be (undefined :: t).
Arguments
| :: (Constraints t c, Applicative f) | |
| => for c | Witness for the constraint |
| -> (forall s. c s => FieldInfo (t -> s) -> f s) | This function should return a value
for each subcomponent of |
| -> [f t] | A list of results, one for each constructor of type |
Arguments
| :: (Constraints t c, Applicative f) | |
| => for c | Witness for the constraint |
| -> (forall s. c s => FieldInfo (t -> s) -> f s) | This function should return a value
for each subcomponent of |
| -> (FieldInfo (t -> t) -> f t) | This function should return a value
for each subcomponent of |
| -> [f t] | A list of results, one for each constructor of type |
class ADT t => ADTRecord t Source
Add an instance for this class if the data type has exactly one constructor.
This class has no methods.
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 |
Helper functions
(!) :: t -> FieldInfo (t -> s) -> s infixl 9 Source
Get the subcomponent by using the projector from the field information.
at :: ADT t => [a] -> t -> a Source
Get the value from the result of one of the builds functions that matches the constructor of t.
Derived traversal schemes
builds :: (ADT t, Constraints t c) => for c -> (forall s. c s => FieldInfo (t -> s) -> s) -> [t] Source
mbuilds :: forall t c m for. (ADT t, Constraints t c, Monoid m) => for c -> (forall s. c s => FieldInfo (t -> s) -> m) -> [m] Source
gmap :: (ADT t, Constraints t c) => for c -> (forall s. c s => s -> s) -> t -> t Source
Transform a value by transforming each subcomponent.
gfoldMap :: (ADT t, Constraints t c, Monoid m) => for c -> (forall s. c s => s -> m) -> t -> m Source
Fold a value, by mapping each subcomponent to a monoid value and collecting those.
gtraverse :: (ADT t, Constraints t c, Applicative f) => for c -> (forall s. c s => s -> f s) -> t -> f t Source
Applicative traversal given a way to traverse each subcomponent.
...for single constructor data types
build :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => FieldInfo (t -> s) -> s) -> t Source
builds for data types with exactly one constructor
op0 :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s) -> t Source
Derive a 0-ary operation by applying the operation to every subcomponent.
op1 :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s -> s) -> t -> t Source
Derive a unary operation by applying the operation to every subcomponent.
op2 :: (ADTRecord t, Constraints t c) => for c -> (forall s. c s => s -> s -> s) -> t -> t -> t Source
Derive a binary operation by applying the operation to every subcomponent.