vinyl-0.6.0: 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 7 

Instances

TestCoercion u f => TestCoercion [u] (Rec u f) Source # 

Methods

testCoercion :: f a -> f b -> Maybe (Coercion (Rec u f) a b) #

TestEquality u f => TestEquality [u] (Rec u f) Source # 

Methods

testEquality :: f a -> f b -> Maybe ((Rec u f :~: a) b) #

(Eq (f r), Eq (Rec a f rs)) => Eq (Rec a f ((:) a r rs)) Source # 

Methods

(==) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

(/=) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

Eq (Rec u f ([] u)) Source # 

Methods

(==) :: Rec u f [u] -> Rec u f [u] -> Bool #

(/=) :: Rec u f [u] -> Rec u f [u] -> Bool #

(Ord (f r), Ord (Rec a f rs)) => Ord (Rec a f ((:) a r rs)) Source # 

Methods

compare :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Ordering #

(<) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

(<=) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

(>) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

(>=) :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Bool #

max :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) #

min :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) #

Ord (Rec u f ([] u)) Source # 

Methods

compare :: Rec u f [u] -> Rec u f [u] -> Ordering #

(<) :: Rec u f [u] -> Rec u f [u] -> Bool #

(<=) :: Rec u f [u] -> Rec u f [u] -> Bool #

(>) :: Rec u f [u] -> Rec u f [u] -> Bool #

(>=) :: Rec u f [u] -> Rec u f [u] -> Bool #

max :: Rec u f [u] -> Rec u f [u] -> Rec u f [u] #

min :: Rec u f [u] -> Rec u f [u] -> Rec u f [u] #

RecAll u f rs Show => Show (Rec u f rs) Source #

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

Methods

showsPrec :: Int -> Rec u f rs -> ShowS #

show :: Rec u f rs -> String #

showList :: [Rec u f rs] -> ShowS #

(Monoid (f r), Monoid (Rec a f rs)) => Monoid (Rec a f ((:) a r rs)) Source # 

Methods

mempty :: Rec a f ((a ': r) rs) #

mappend :: Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) -> Rec a f ((a ': r) rs) #

mconcat :: [Rec a f ((a ': r) rs)] -> Rec a f ((a ': r) rs) #

Monoid (Rec u f ([] u)) Source # 

Methods

mempty :: Rec u f [u] #

mappend :: Rec u f [u] -> Rec u f [u] -> Rec u f [u] #

mconcat :: [Rec u f [u]] -> Rec u f [u] #

(Storable (f r), Storable (Rec a f rs)) => Storable (Rec a f ((:) a r rs)) Source # 

Methods

sizeOf :: Rec a f ((a ': r) rs) -> Int #

alignment :: Rec a f ((a ': r) rs) -> Int #

peekElemOff :: Ptr (Rec a f ((a ': r) rs)) -> Int -> IO (Rec a f ((a ': r) rs)) #

pokeElemOff :: Ptr (Rec a f ((a ': r) rs)) -> Int -> Rec a f ((a ': r) rs) -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec a f ((a ': r) rs)) #

pokeByteOff :: Ptr b -> Int -> Rec a f ((a ': r) rs) -> IO () #

peek :: Ptr (Rec a f ((a ': r) rs)) -> IO (Rec a f ((a ': r) rs)) #

poke :: Ptr (Rec a f ((a ': r) rs)) -> Rec a f ((a ': r) rs) -> IO () #

Storable (Rec u f ([] u)) Source # 

Methods

sizeOf :: Rec u f [u] -> Int #

alignment :: Rec u f [u] -> Int #

peekElemOff :: Ptr (Rec u f [u]) -> Int -> IO (Rec u f [u]) #

pokeElemOff :: Ptr (Rec u f [u]) -> Int -> Rec u f [u] -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Rec u f [u]) #

pokeByteOff :: Ptr b -> Int -> Rec u f [u] -> IO () #

peek :: Ptr (Rec u f [u]) -> IO (Rec u f [u]) #

poke :: Ptr (Rec u f [u]) -> Rec u f [u] -> IO () #

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.

Minimal complete definition

rpure

Methods

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

Instances

RecApplicative u ([] u) Source # 

Methods

rpure :: (forall x. f x) -> Rec [u] f rs Source #

RecApplicative u rs => RecApplicative u ((:) u r rs) Source # 

Methods

rpure :: (forall x. f x) -> Rec ((u ': r) rs) f rs Source #

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.

rzipWith :: (forall x. f x -> g x -> h x) -> forall xs. Rec f xs -> Rec g xs -> Rec h xs Source #

Given a natural transformation from the product of f and g to h, we have a natural transformation from the product of Rec f and Rec g to Rec h. You can also think about this operation as zipping two records with the same element types but different interpretations.

rfoldMap :: forall f m rs. Monoid m => (forall x. f x -> m) -> Rec f rs -> m Source #

Map each element of a record to a monoid and combine the results.

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.

rpureConstrained :: forall c f proxy ts. (AllConstrained c ts, RecApplicative ts) => proxy c -> (forall a. c a => f a) -> Rec f ts Source #

Build a record whose elements are derived solely from a constraint satisfied by each.

rpureConstraints :: forall cs f proxy ts. (AllAllSat cs ts, RecApplicative ts) => proxy cs -> (forall a. AllSatisfied cs a => f a) -> Rec f ts Source #

Build a record whose elements are derived solely from a list of constraint constructors satisfied by each.