| Portability | non-portable |
|---|---|
| Stability | experimental |
| Maintainer | sjoerd@w3future.com |
| Safe Haskell | None |
Generics.OneLiner.ADT1
Description
This module is for writing generic functions on algebraic data types
of kind * -> *.
These data types must be an instance of the ADT1 type class.
Here's an example how to write such an instance for this data type:
data T a = A [a] | B a (T a)
instanceADT1T wherectorIndexA{} = 0ctorIndexB{} = 1ctorInfo_ 0 =ctor"A"ctorInfo_ 1 =ctor"B" typeConstraintsT c = (c [], c T)buildsRecAForpar sub rec = [ A<$>sub (component(\(A l) -> l) , B<$>par (param(\(B a _) -> a))<*>rec (component(\(B _ t) -> t)) ]
- module Generics.OneLiner.Info
- data Constraint
- class ADT1 t where
- type Constraints t c :: Constraint
- ctorIndex :: t a -> Int
- ctorInfo :: t a -> Int -> CtorInfo
- buildsA :: (Constraints t c, Applicative f) => For c -> (FieldInfo (Extract t) -> f b) -> (forall s. c s => FieldInfo (t :~> s) -> f (s b)) -> [f (t b)]
- buildsRecA :: (Constraints t c, Applicative f) => For c -> (FieldInfo (Extract t) -> f b) -> (forall s. c s => FieldInfo (t :~> s) -> f (s b)) -> (FieldInfo (t :~> t) -> f (t b)) -> [f (t b)]
- class ADT1 t => ADT1Record t
- data For c = For
- newtype Extract f = Extract {
- getExtract :: forall x. f x -> x
- newtype f :~> g = Nat {
- getNat :: forall x. f x -> g x
- (!) :: t a -> FieldInfo (Extract t) -> a
- (!~) :: t a -> FieldInfo (t :~> s) -> s a
- at :: ADT1 t => [a] -> t b -> a
- param :: (forall a. t a -> a) -> FieldInfo (Extract t)
- component :: (forall a. t a -> s a) -> FieldInfo (t :~> s)
- builds :: (ADT1 t, Constraints t c) => For c -> (FieldInfo (Extract t) -> b) -> (forall s. c s => FieldInfo (t :~> s) -> s b) -> [t b]
- mbuilds :: forall t c m. (ADT1 t, Constraints t c, Monoid m) => For c -> (FieldInfo (Extract t) -> m) -> (forall s. c s => FieldInfo (t :~> s) -> m) -> [m]
- build :: (ADT1Record t, Constraints t c) => For c -> (FieldInfo (Extract t) -> b) -> (forall s. c s => FieldInfo (t :~> s) -> s b) -> t b
Re-exports
module Generics.OneLiner.Info
data Constraint
The kind of constraints
The ADT1 type class
Type class for algebraic data types of kind * -> *. Minimal implementation: ctorIndex and either buildsA
if the type t is not recursive, or buildsRecA if the type t is recursive.
Associated Types
type Constraints t c :: ConstraintSource
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 a -> Int -> CtorInfoSource
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 a).
Arguments
| :: (Constraints t c, Applicative f) | |
| => For c | Witness for the constraint |
| -> (FieldInfo (Extract t) -> f b) | |
| -> (forall s. c s => FieldInfo (t :~> s) -> f (s b)) | |
| -> [f (t b)] |
Arguments
| :: (Constraints t c, Applicative f) | |
| => For c | Witness for the constraint |
| -> (FieldInfo (Extract t) -> f b) | |
| -> (forall s. c s => FieldInfo (t :~> s) -> f (s b)) | |
| -> (FieldInfo (t :~> t) -> f (t b)) | |
| -> [f (t b)] |
class ADT1 t => ADT1Record 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 |
Constructors
| Extract | |
Fields
| |
Helper functions
at :: ADT1 t => [a] -> t b -> aSource
Get the value from the result of one of the builds functions that matches the constructor of t.
Derived traversal schemes
builds :: (ADT1 t, Constraints t c) => For c -> (FieldInfo (Extract t) -> b) -> (forall s. c s => FieldInfo (t :~> s) -> s b) -> [t b]Source
mbuilds :: forall t c m. (ADT1 t, Constraints t c, Monoid m) => For c -> (FieldInfo (Extract t) -> m) -> (forall s. c s => FieldInfo (t :~> s) -> m) -> [m]Source
build :: (ADT1Record t, Constraints t c) => For c -> (FieldInfo (Extract t) -> b) -> (forall s. c s => FieldInfo (t :~> s) -> s b) -> t bSource
builds for data types with exactly one constructor