vinyl-0.8.1: Extensible Records

Safe HaskellNone
LanguageHaskell2010

Data.Vinyl.Derived

Contents

Description

Commonly used Rec instantiations.

Synopsis

Documentation

type (:::) a b = '(a, b) Source #

Alias for Field spec

data ElField (field :: (Symbol, *)) where Source #

Constructors

Field :: KnownSymbol s => !t -> ElField '(s, t) 

Instances

Eq t => Eq (ElField ((,) Symbol * s t)) Source # 

Methods

(==) :: ElField ((Symbol, *) s t) -> ElField ((Symbol, *) s t) -> Bool #

(/=) :: ElField ((Symbol, *) s t) -> ElField ((Symbol, *) s t) -> Bool #

Ord t => Ord (ElField ((,) Symbol * s t)) Source # 

Methods

compare :: ElField ((Symbol, *) s t) -> ElField ((Symbol, *) s t) -> Ordering #

(<) :: ElField ((Symbol, *) s t) -> ElField ((Symbol, *) s t) -> Bool #

(<=) :: ElField ((Symbol, *) s t) -> ElField ((Symbol, *) s t) -> Bool #

(>) :: ElField ((Symbol, *) s t) -> ElField ((Symbol, *) s t) -> Bool #

(>=) :: ElField ((Symbol, *) s t) -> ElField ((Symbol, *) s t) -> Bool #

max :: ElField ((Symbol, *) s t) -> ElField ((Symbol, *) s t) -> ElField ((Symbol, *) s t) #

min :: ElField ((Symbol, *) s t) -> ElField ((Symbol, *) s t) -> ElField ((Symbol, *) s t) #

Show t => Show (ElField ((,) Symbol * s t)) Source # 

Methods

showsPrec :: Int -> ElField ((Symbol, *) s t) -> ShowS #

show :: ElField ((Symbol, *) s t) -> String #

showList :: [ElField ((Symbol, *) s t)] -> ShowS #

(KnownSymbol s, Storable t) => Storable (ElField ((,) Symbol * s t)) Source # 

Methods

sizeOf :: ElField ((Symbol, *) s t) -> Int #

alignment :: ElField ((Symbol, *) s t) -> Int #

peekElemOff :: Ptr (ElField ((Symbol, *) s t)) -> Int -> IO (ElField ((Symbol, *) s t)) #

pokeElemOff :: Ptr (ElField ((Symbol, *) s t)) -> Int -> ElField ((Symbol, *) s t) -> IO () #

peekByteOff :: Ptr b -> Int -> IO (ElField ((Symbol, *) s t)) #

pokeByteOff :: Ptr b -> Int -> ElField ((Symbol, *) s t) -> IO () #

peek :: Ptr (ElField ((Symbol, *) s t)) -> IO (ElField ((Symbol, *) s t)) #

poke :: Ptr (ElField ((Symbol, *) s t)) -> ElField ((Symbol, *) s t) -> IO () #

type FieldRec = Rec ElField Source #

A record of named fields.

type AFieldRec ts = ARec ElField ts Source #

An ARec of named fields to provide constant-time field access.

type HList = Rec Identity Source #

Heterogeneous list whose elements are evaluated during list construction.

type LazyHList = Rec Thunk Source #

Heterogeneous list whose elements are left as-is during list construction (cf. HList).

getField :: ElField '(s, t) -> t Source #

Get the data payload of an ElField.

getLabel :: forall s t. ElField '(s, t) -> String Source #

Get the label name of an ElField.

fieldMap :: (a -> b) -> ElField '(s, a) -> ElField '(s, b) Source #

ElField is isomorphic to a functor something like Compose ElField ('(,) s).

rfield :: Functor f => (a -> f b) -> ElField '(s, a) -> f (ElField '(s, b)) Source #

Lens for an ElField's data payload.

(=:) :: KnownSymbol l => Label (l :: Symbol) -> (v :: *) -> ElField (l ::: v) infix 8 Source #

Operator for creating an ElField. With the -XOverloadedLabels extension, this permits usage such as, #foo =: 23 to produce a value of type ElField ("foo" ::: Int).

rgetf :: forall l f v record us. HasField record l us v => Label l -> record f us -> f (l ::: v) Source #

Get a named field from a record.

rvalf :: HasField record l us v => Label l -> record ElField us -> v Source #

Get the value associated with a named field from a record.

rputf :: forall l v record us. (HasField record l us v, KnownSymbol l) => Label l -> v -> record ElField us -> record ElField us Source #

Set a named field. rputf #foo 23 sets the field named #foo to 23.

rlensf' :: forall l v record g f us. (Functor g, HasField record l us v) => Label l -> (f (l ::: v) -> g (f (l ::: v))) -> record f us -> g (record f us) Source #

A lens into a Rec identified by a Label.

rlensf :: forall l v record g f us. (Functor g, HasField record l us v) => Label l -> (v -> g v) -> record ElField us -> g (record ElField us) Source #

A lens into the payload value of a Rec field identified by a Label.

(=:=) :: KnownSymbol s => proxy '(s, a) -> a -> FieldRec '['(s, a)] Source #

Shorthand for a FieldRec with a single field.

data SField (field :: k) Source #

A proxy for field types.

Constructors

SField 

Instances

Eq (SField k a) Source # 

Methods

(==) :: SField k a -> SField k a -> Bool #

(/=) :: SField k a -> SField k a -> Bool #

Ord (SField k a) Source # 

Methods

compare :: SField k a -> SField k a -> Ordering #

(<) :: SField k a -> SField k a -> Bool #

(<=) :: SField k a -> SField k a -> Bool #

(>) :: SField k a -> SField k a -> Bool #

(>=) :: SField k a -> SField k a -> Bool #

max :: SField k a -> SField k a -> SField k a #

min :: SField k a -> SField k a -> SField k a #

KnownSymbol s => Show (SField (Symbol, k) ((,) Symbol k s t)) Source # 

Methods

showsPrec :: Int -> SField (Symbol, k) ((Symbol, k) s t) -> ShowS #

show :: SField (Symbol, k) ((Symbol, k) s t) -> String #

showList :: [SField (Symbol, k) ((Symbol, k) s t)] -> ShowS #

type family FieldType l fs where ... Source #

Equations

FieldType l '[] = TypeError ((Text "Cannot find label " :<>: ShowType l) :<>: Text " in fields") 
FieldType l ((l ::: v) ': fs) = v 
FieldType l ((l' ::: v') ': fs) = FieldType l fs 

type HasField record l fs v = (RecElem record (l ::: v) fs (RIndex (l ::: v) fs), FieldType l fs ~ v) Source #

Constraint that a label is associated with a particular type in a record.

data Label (a :: Symbol) Source #

Proxy for label type

Constructors

Label 

Instances

(~) Symbol s s' => IsLabel s (Label s') Source # 

Methods

fromLabel :: Label s' #

Eq (Label a) Source # 

Methods

(==) :: Label a -> Label a -> Bool #

(/=) :: Label a -> Label a -> Bool #

Show (Label a) Source # 

Methods

showsPrec :: Int -> Label a -> ShowS #

show :: Label a -> String #

showList :: [Label a] -> ShowS #

class (KnownSymbol (Fst a), a ~ '(Fst a, Snd a)) => KnownField a Source #

Defines a constraint that lets us extract the label from an ElField. Used in rmapf and rpuref.

Instances

type AllFields fs = (AllConstrained KnownField fs, RecApplicative fs) Source #

Shorthand for working with records of fields as in rmapf and rpuref.

rmapf :: AllFields fs => (forall a. KnownField a => f a -> g a) -> Rec f fs -> Rec g fs Source #

Map a function between functors across a Rec taking advantage of knowledge that each element is an ElField.

rpuref :: AllFields fs => (forall a. KnownField a => f a) -> Rec f fs Source #

Construct a Rec with ElField elements.

(<<$$>>) :: AllFields fs => (forall a. KnownField a => f a -> g a) -> Rec f fs -> Rec g fs Source #

Operator synonym for rmapf.

rlabels :: AllFields fs => Rec (Const String) fs Source #

Produce a Rec of the labels of a Rec of ElFields.

Specializations for working with an ARec of named fields.