vinyl-0.5.2: Extensible Records

Safe HaskellNone
LanguageHaskell2010

Data.Vinyl.Notation

Synopsis

Documentation

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

A shorthand for rappend.

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

A shorthand for rapply.

(<<$>>) :: (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.

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

(:&) :: !(f r) -> !(Rec f rs) -> Rec f (r : rs) infixr 7 

Instances

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

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)) Source 
Storable (Rec k f ([] k)) Source 
(Monoid (f r), Monoid (Rec k f rs)) => Monoid (Rec k f ((:) k r rs)) Source 
Monoid (Rec k f ([] k)) Source 

type (∈) r rs = RElem r rs (RIndex r rs) Source

A shorthand for RElem which supplies its index.

type (⊆) rs ss = RSubset rs ss (RImage rs ss) Source

A shorthand for RSubset which supplies its image.

type (≅) rs ss = REquivalent rs ss (RImage rs ss) (RImage ss rs) Source

A shorthand for REquivalent which supplies its images.

type (<:) rs ss = rs ss Source

A non-unicode equivalent of (⊆).

type (:~:) rs ss = rs ss Source

A non-unicode equivalent of (≅).