vinyl-0.5.1: Extensible Records

Safe HaskellNone
LanguageHaskell2010

Data.Vinyl.Core

Synopsis

Documentation

data Rec :: (u -> *) -> [u] -> * where Source

A record is parameterized by a universe u, an interpretation f and a list of rows rs. The labels or indices of the record are given by inhabitants of the kind u; the type of values at any label r :: u is given by its interpretation f r :: *.

Constructors

RNil :: Rec f [] 
(:&) :: !(f r) -> !(Rec f rs) -> Rec f (r : rs) infixr 9 

Instances

(Eq (f r), Eq (Rec k f rs)) => Eq (Rec k f ((:) k r rs)) 
Eq (Rec k f ([] k)) 
RecAll k f rs Show => Show (Rec k f rs)

Records may be shown insofar as their points may be shown. reifyConstraint is used to great effect here.

(Storable (f r), Storable (Rec k f rs)) => Storable (Rec k f ((:) k r rs)) 
Storable (Rec k f ([] k)) 
(Monoid (f r), Monoid (Rec k f rs)) => Monoid (Rec k f ((:) k r rs)) 
Monoid (Rec k f ([] k)) 

rappend :: Rec f as -> Rec f bs -> Rec f (as ++ bs) Source

Two records may be pasted together.

(<+>) :: Rec f as -> Rec f bs -> Rec f (as ++ bs) infixr 5 Source

A shorthand for rappend.

rmap :: (forall x. f x -> g x) -> Rec f rs -> Rec g rs Source

Rec _ rs with labels in kind u gives rise to a functor Hask^u -> Hask; that is, a natural transformation between two interpretation functors f,g may be used to transport a value from Rec f rs to Rec g rs.

(<<$>>) :: (forall x. f x -> g x) -> Rec f rs -> Rec g rs infixl 8 Source

A shorthand for rmap.

(<<&>>) :: Rec f rs -> (forall x. f x -> g x) -> Rec g rs Source

An inverted shorthand for rmap.

rapply :: Rec (Lift (->) f g) rs -> Rec f rs -> Rec g rs Source

A record of components f r -> g r may be applied to a record of f to get a record of g.

(<<*>>) :: Rec (Lift (->) f g) rs -> Rec f rs -> Rec g rs infixl 8 Source

A shorthand for rapply.

class RecApplicative rs where Source

Given a section of some functor, records in that functor of any size are inhabited.

Methods

rpure :: (forall x. f x) -> Rec f rs Source

Instances

RecApplicative k ([] k) 
RecApplicative k rs => RecApplicative k ((:) k r rs) 

rtraverse :: Applicative h => (forall x. f x -> h (g x)) -> Rec f rs -> h (Rec g rs) Source

A record may be traversed with respect to its interpretation functor. This can be used to yank (some or all) effects from the fields of the record to the outside of the record.

recordToList :: Rec (Const a) rs -> [a] Source

A record with uniform fields may be turned into a list.

data Dict c a where Source

Wrap up a value with a capability given by its type

Constructors

Dict :: c a => a -> Dict c a 

reifyConstraint :: RecAll f rs c => proxy c -> Rec f rs -> Rec (Dict c :. f) rs Source

Sometimes we may know something for all fields of a record, but when you expect to be able to each of the fields, you are then out of luck. Surely given ∀x:u.φ(x) we should be able to recover x:u ⊢ φ(x)! Sadly, the constraint solver is not quite smart enough to realize this and we must make it patently obvious by reifying the constraint pointwise with proof.