one-liner-0: Constraint-based generics

Portabilitynon-portable
Stabilityexperimental
Maintainersjoerd@w3future.com
Safe HaskellNone

Generics.OneLiner.ADT1

Contents

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)
 instance ADT1 T where
   ctorIndex A{} = 0
   ctorIndex B{} = 1
   type Constraints T c = (c [], c T)
   buildsRecA For par sub rec = 
     [ (ctor "A", A <$> sub (component (\(A l) -> l))
     , (ctor "B", B <$> par (param (\(B a _) -> a)) <*> rec (component (\(B _ t) -> t)))
     ]

Synopsis

Re-exports

The kind of constraints

The ADT1 type class

class ADT1 t whereSource

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

ctorIndex :: t a -> IntSource

Gives the index of the constructor of the given value in the list returned by buildsA and buildsRecA.

buildsASource

Arguments

:: (Constraints t c, Applicative f) 
=> For c

Witness for the constraint c.

-> (FieldInfo (Extract t) -> f b) 
-> (forall s. c s => FieldInfo (t :~> s) -> f (s b)) 
-> [(CtorInfo, f (t b))] 

buildsRecASource

Arguments

:: (Constraints t c, Applicative f) 
=> For c

Witness for the constraint c.

-> (FieldInfo (Extract t) -> f b) 
-> (forall s. c s => FieldInfo (t :~> s) -> f (s b)) 
-> (FieldInfo (t :~> t) -> f (t b)) 
-> [(CtorInfo, f (t b))] 

Instances

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 

newtype Extract f Source

Constructors

Extract 

Fields

getExtract :: forall x. f x -> x
 

newtype f :~> g Source

Constructors

Nat 

Fields

getNat :: forall x. f x -> g x
 

Helper functions

(!) :: t a -> FieldInfo (Extract t) -> aSource

(!~) :: t a -> FieldInfo (t :~> s) -> s aSource

at :: ADT1 t => [(c, a)] -> t b -> aSource

Get the value from the result of one of the builds functions that matches the constructor of t.

param :: (forall a. t a -> a) -> FieldInfo (Extract t)Source

component :: (forall a. t a -> s a) -> FieldInfo (t :~> s)Source

Derived traversal schemes

builds :: (ADT1 t, Constraints t c) => For c -> (FieldInfo (Extract t) -> b) -> (forall s. c s => FieldInfo (t :~> s) -> s b) -> [(CtorInfo, t b)]Source

buildsA specialized to the Identity applicative functor.

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) -> [(CtorInfo, m)]Source

buildsA specialized to the Constant applicative functor, which collects monoid values m.