extensible-0.3.5: 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.Field

Contents

Description

Synopsis

Documentation

newtype Field h kv Source

A Field h (k ':> v) is h v, but is along with the index k.

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

Constructors

Field 

Fields

getField :: h (AssocValue kv)
 

Instances

Wrapper k h => Wrapper (Assoc k k) (Field k k h) 
(KnownSymbol k1, Wrapper k h, Show (Repr k h v)) => Show (Field k Symbol h ((:>) Symbol k k v))

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

type Repr (Assoc k1 k) (Field k k1 h) kv = Repr k h (AssocValue k k1 kv) 

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

Annotate a value by the field name.

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

Lifted (@=)

type FieldOptic k = forall f p t xs h v. (Extensible f p t, Associate k v xs, Labelling k p, Wrapper h) => Optic' p f (t (Field h) xs) (Repr h v) Source

FieldOptic s is a type of optics that points a field/constructor named s.

The yielding fields can be Lenses for Records and Prisms for Variants.

FieldOptic "foo" = Associate "foo" a xs => Lens' (Record xs) a
FieldOptic "foo" = Associate "foo" a xs => Prism' (Variant xs) a

FieldOptics can be generated using mkField defined in the Data.Extensible.TH module.

type FieldName k = Optic' (LabelPhantom k) Proxy (Inextensible (Field Proxy) `[k :> ()]`) () 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.

Records and variants

type RecordOf h = (:*) (Field h) Source

The type of records which contain several fields.

RecordOf :: (v -> *) -> [Assoc k v] -> *

type Record = RecordOf Identity Source

Simple record

type VariantOf h = (:|) (Field h) Source

The dual of RecordOf

VariantOf :: (v -> *) -> [Assoc k v] -> *

type Variant = VariantOf Identity Source

Simple variant

Matching

matchWithField :: (forall x. f x -> g x -> r) -> RecordOf f xs -> VariantOf g xs -> r Source

matchField :: RecordOf (Match h r) xs -> VariantOf h xs -> r Source

Constraint

type family AssocKey kv :: k Source

Equations

AssocKey (k :> v) = k 

type family AssocValue kv :: v Source

Equations

AssocValue (k :> v) = v 

class (pk (AssocKey kv), pv (AssocValue kv)) => KeyValue pk pv kv Source

Instances

(pk k2, pv v) => KeyValue k k pk pv ((:>) k k k v) 

Internal

data LabelPhantom s a b Source

A ghostly type which spells the field name

Instances

type family Labelling s p :: Constraint Source

Equations

Labelling s (LabelPhantom t) = s ~ t 
Labelling s p = () 

data Inextensible h xs Source

The trivial inextensible data type

Instances