extensible-0.3.2: Extensible, efficient, lens-friendly data types

Copyright(c) Fumiaki Kinoshita 2015
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Extensible.Record

Contents

Description

Flexible records with well-typed fields. Example: https://github.com/fumieval/extensible/blob/master/examples/records.hs

Synopsis

Documentation

type Record = (:*) Field Source

The type of records which contain several fields.

(<:) :: h x -> (h :* xs) -> h :* (x : xs) infixr 0 Source

O(log n) Add an element to a product.

(<:*) :: forall h x xs. h x -> (h :* xs) -> h :* (x : xs) infixr 0 Source

An alias for (<:).

data h :* s where Source

The type of extensible products.

Constructors

Nil :: h :* [] 

Instances

Typeable ((k -> *) -> [k] -> *) ((:*) k) 
WrapForall k * Eq h xs => Eq ((:*) k h xs) 
(Eq ((:*) k h xs), WrapForall k * Ord h xs) => Ord ((:*) k h xs) 
WrapForall k * Show h xs => Show ((:*) k h xs) 
WrapForall k * Monoid h xs => Monoid ((:*) k h xs) 
WrapForall k * Binary h xs => Binary ((:*) k h xs) 

(@=) :: FieldName k -> v -> Field (k :> v) infix 1 Source

Annotate a value by the field name.

(<@=>) :: Functor f => FieldName k -> f v -> Comp f Field (k :> v) infix 1 Source

Lifted (@=)

mkField :: String -> DecsQ Source

Generate a field. mkField "foo bar" defines:

foo :: FieldLens "foo"
foo :: FieldLens "bar"

The yielding field is a Lens.

data Field kv where Source

The type of fields.

Constructors

Field :: v -> Field (k :> v) 

Instances

(KnownSymbol k, Show v) => Show (Field Symbol ((:>) Symbol * k v))

Shows in field @= value style instead of the derived one.

getField :: Field (k :> v) -> v Source

Get a value of a field.

type FieldLens k = forall f p xs v. (Functor f, Labelable k p, Associate k v xs) => p v (f v) -> Record xs -> f (Record xs) Source

FieldLens s is a type of lens that points a field named s.

FieldLens "foo" = Associate "foo" a xs => Lens' (Record xs) a

type FieldName k = forall v. LabelPhantom k v (Proxy v) -> Record `[k :> v]` -> Proxy (Record `[k :> v]`) Source

When you see this type as an argument, it expects a FieldLens. This type is used to resolve the name of the field internally.

Internal

class Labelable s p where Source

An internal class to characterize FieldLens

Methods

unlabel :: proxy s -> p a b -> a -> b Source

Instances

Labelable k s (->) 
(~) k s t => Labelable k s (LabelPhantom k * * t) 

data LabelPhantom s a b Source

A ghostly type which spells the field name

Instances

(~) k s t => Labelable k s (LabelPhantom k * * t)