one-liner-0.5.1: Constraint-based generics

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

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

Synopsis

Re-exports

data Constraint :: BOX

Instances

The kind of constraints

The ADT1 type class

class ADT1 t where Source

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

ctorIndex :: t a -> Int Source

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

ctorInfo :: t a -> 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 a).

buildsA Source

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)) 
-> [f (t b)] 

buildsRecA Source

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)) 
-> [f (t b)] 

Instances

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.

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) -> a infixl 9 Source

(!~) :: t a -> FieldInfo (t :~> s) -> s a infixl 9 Source

at :: ADT1 t => [a] -> t b -> a Source

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) -> [t b] Source

buildsA specialized to the Identity applicative functor.

mbuilds :: forall t c m for. (ADT1 t, Constraints t c, Monoid m) => for c -> (FieldInfo (Extract t) -> m) -> (forall s. c s => FieldInfo (t :~> s) -> m) -> [m] Source

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

build :: (ADT1Record t, Constraints t c) => for c -> (FieldInfo (Extract t) -> b) -> (forall s. c s => FieldInfo (t :~> s) -> s b) -> t b Source

builds for data types with exactly one constructor