has-0.5.0.1: Entity based records

Portabilityunknown
Stabilityexperimental
Maintainernonowarn@gmail.com

Data.Has

Contents

Description

Entiry based records. To use this module, you have to write LANGUGAGE pragma

 {-# LANGUAGE TypeFamilies,TypeOperators,FlexibleContexts #-}

Or OPTIONS_GHC pragma if you are lazy.

 {-# OPTIONS_GHC -fglasgow-exts #-}

Synopsis

Has constraint

class Knows e (TypeOf e) r => Has e r Source

Meaning of this constraint is "This record s has a field of entity e." Here, I use the word "constraint" for class which is useful on writing type signitures.

Holds v == (e .^ (e ^= v $ s)) where e :: e; v :: TypeOf e; s :: s for all e with TypeOf e and s.

Same as Knows e (TypeOf e) s.

Instances

Knows e (TypeOf e) r => Has e r 

Fields in Records

type Field a = a ::: TyNilSource

Field a is a type list which contains only one element of a. And every field in the records should be this type.

If you concatenate fields with (:&:) at type-level, (&) at value-level, it becomes a record can be manipulated by functions in this module.

field :: a -> Field aSource

Creates a Field of a.

fieldOf :: TypeOf a -> FieldOf aSource

Creates a field labelled by a

Useful Operators

(^=) :: Knows e (TypeOf e) r => e -> TypeOf e -> r -> rSource

Writes field of e in r with TypeOf e.

(^.) :: Knows e (TypeOf e) r => e -> r -> TypeOf eSource

Reads TypeOf e from field of e in r.

(^:) :: Knows e (TypeOf e) r => e -> (TypeOf e -> TypeOf e) -> r -> rSource

Modifies field of e in r with given function TypeOf e -> | TypeOf e.

(^-) :: e -> TypeOf e -> FieldOf eSource

Creates field of e with given value TypeOf e. Stealed from Chris Done's blog post: http://chrisdone.com/posts/2010-11-22-duck-typing-in-haskell.html

Knows == Generalized version of Has

class Contains (Labelled e v) r => Knows e v r | e r -> v whereSource

Injects and projects a value of v a corresponding field in records a along entity e.

Holds v == prjl e (injl e v r).

Methods

injl :: e -> v -> r -> rSource

Injects a value v into record a along e.

prjl :: e -> r -> vSource

Projects a value v into record a along e.

Instances

Contains (Labelled e v) r => Knows e v r 

updl :: Knows e v r => e -> (v -> v) -> r -> rSource

Updates a value of v in a record r using function of v -> v.

Labelled Fields

data Labelled lab a Source

Represents labelled value.

Instances

Typeable2 Labelled 
Bounded a => Bounded (Labelled lab a) 
Eq a => Eq (Labelled lab a) 
(Data lab, Data a) => Data (Labelled lab a) 
Ord a => Ord (Labelled lab a) 
Read a => Read (Labelled lab a) 
Show a => Show (Labelled lab a) 
Arbitrary a => Arbitrary (Labelled lab a) 
CoArbitrary a => CoArbitrary (Labelled lab a) 
Monoid a => Monoid (Labelled lab a) 

type :> lab a = Field (Labelled lab a)Source

Represents labelled field.

(.>) :: lab -> a -> lab :> aSource

Makes a labelled field.

Defining Entities and Records

type family TypeOf a Source

TypeOf a should indicate a type labelled by a. When defining entities, declare instance of this family. If you want Foo entity points to Int, you write

 data Foo = Foo; type instance TypeOf Foo = Int

type family FieldOf a Source

Field labelled with a, and contains TypeOf a.

(&) :: Append a b => a -> b -> a :&: bSource

Concatenates between Fields or records. Records are concatenated rows. For example, Following expressions are valid.

 -- Concatenation of rows (i.e. record)
 field "string" & field True
 -- Concatenation of records
 (field 'c' & field ()) & (field False & field "string")
 -- ... And concatenations between a field and a record
 field () & (field False & field "string")
 (field 'c' & field ()) & field False

type family a :&: b Source

Represents concatenated rows or records.

Reading error messages easier

data a ::: b Source

Cons a type onto type-list.

Instances

Typeable2 ::: 
Contains e r => Contains e (::: h r) 
Contains e (::: e r) 
(Bounded a, Bounded b) => Bounded (::: a b) 
(Eq a, Eq b) => Eq (::: a b) 
(Data a, Data b) => Data (::: a b) 
(Ord a, Ord b) => Ord (::: a b) 
(Read a, Read b) => Read (::: a b) 
(Show a, Show b) => Show (::: a b) 
(Arbitrary a, Arbitrary b) => Arbitrary (::: a b) 
(CoArbitrary a, CoArbitrary b) => CoArbitrary (::: a b) 
(Monoid a, Monoid b) => Monoid (::: a b) 
Append y b => Append (::: x y) b 

class Contains e s Source

Provides injection and projection into type lists.

Holds e == prj (inj e s) for all s and e.

Instances

Contains e r => Contains e (::: h r) 
Contains e (::: e r)