| Safe Haskell | Trustworthy | 
|---|---|
| Language | Haskell2010 | 
Data.Vinyl.ARec
Description
Constant-time field accessors for extensible records. The trade-off is the usual lists vs arrays one: it is fast to add an element to the head of a list, but element access is linear time; array access time is uniform, but extending the array is more slower.
Synopsis
- data ARec (f :: k -> *) (ts :: [k])
- class NatToInt (RIndex t ts) => IndexableField ts t
- toARec :: forall f ts. NatToInt (RLength ts) => Rec f ts -> ARec f ts
- fromARec :: forall f ts. (RecApplicative ts, RPureConstrained (IndexableField ts) ts) => ARec f ts -> Rec f ts
- aget :: forall t f ts. NatToInt (RIndex t ts) => ARec f ts -> f t
- aput :: forall t t' f ts ts'. NatToInt (RIndex t ts) => f t' -> ARec f ts -> ARec f ts'
- alens :: forall f g t t' ts ts'. (Functor g, NatToInt (RIndex t ts)) => (f t -> g (f t')) -> ARec f ts -> g (ARec f ts')
- arecGetSubset :: forall rs ss f. (IndexWitnesses (RImage rs ss), NatToInt (RLength rs)) => ARec f ss -> ARec f rs
- arecSetSubset :: forall rs ss f. IndexWitnesses (RImage rs ss) => ARec f ss -> ARec f rs -> ARec f ss
- arecRepsMatchCoercion :: AllRepsMatch f xs g ys => Coercion (ARec f xs) (ARec g ys)
- arecConsMatchCoercion :: (forall (x :: k). Coercible (f x) (g x)) => Coercion (ARec f xs) (ARec g xs)
Documentation
data ARec (f :: k -> *) (ts :: [k]) Source #
An array-backed extensible record with constant-time field access.
Instances
| (is ~ RImage rs ss, IndexWitnesses is, NatToInt (RLength rs)) => RecSubset (ARec :: (k -> Type) -> [k] -> Type) (rs :: [k]) (ss :: [k]) is Source # | |
| Defined in Data.Vinyl.ARec.Internal Associated Types type RecSubsetFCtx ARec f Source # Methods rsubsetC :: forall g (f :: k0 -> Type). (Functor g, RecSubsetFCtx ARec f) => (ARec f rs -> g (ARec f rs)) -> ARec f ss -> g (ARec f ss) Source # rcastC :: forall (f :: k0 -> Type). RecSubsetFCtx ARec f => ARec f ss -> ARec f rs Source # rreplaceC :: forall (f :: k0 -> Type). RecSubsetFCtx ARec f => ARec f rs -> ARec f ss -> ARec f ss Source # | |
| RecElem (ARec :: (a -> Type) -> [a] -> Type) (t :: a) (t' :: a) (t ': ts :: [a]) (t' ': ts :: [a]) 'Z Source # | |
| Defined in Data.Vinyl.ARec.Internal Associated Types type RecElemFCtx ARec f Source # | |
| (RIndex t (s ': ts) ~ 'S i, NatToInt i, RecElem (ARec :: (a -> Type) -> [a] -> Type) t t' ts ts' i) => RecElem (ARec :: (a -> Type) -> [a] -> Type) (t :: a) (t' :: a) (s ': ts :: [a]) (s ': ts' :: [a]) ('S i) Source # | |
| Defined in Data.Vinyl.ARec.Internal Associated Types type RecElemFCtx ARec f Source # | |
| (RPureConstrained (IndexableField rs) rs, RecApplicative rs, Eq (Rec f rs)) => Eq (ARec f rs) Source # | |
| (RPureConstrained (IndexableField rs) rs, RecApplicative rs, Ord (Rec f rs)) => Ord (ARec f rs) Source # | |
| (RPureConstrained (IndexableField rs) rs, RecApplicative rs, Show (Rec f rs)) => Show (ARec f rs) Source # | |
| type RecSubsetFCtx (ARec :: (k -> Type) -> [k] -> Type) (f :: k -> Type) Source # | |
| Defined in Data.Vinyl.ARec.Internal | |
| type RecElemFCtx (ARec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) Source # | |
| Defined in Data.Vinyl.ARec.Internal | |
| type RecElemFCtx (ARec :: (a -> Type) -> [a] -> Type) (f :: a -> Type) Source # | |
| Defined in Data.Vinyl.ARec.Internal | |
class NatToInt (RIndex t ts) => IndexableField ts t Source #
Instances
| NatToInt (RIndex t ts) => IndexableField (ts :: [k]) (t :: k) Source # | |
| Defined in Data.Vinyl.ARec.Internal | |
fromARec :: forall f ts. (RecApplicative ts, RPureConstrained (IndexableField ts) ts) => ARec f ts -> Rec f ts Source #
aput :: forall t t' f ts ts'. NatToInt (RIndex t ts) => f t' -> ARec f ts -> ARec f ts' Source #
Set a field in an ARec.
alens :: forall f g t t' ts ts'. (Functor g, NatToInt (RIndex t ts)) => (f t -> g (f t')) -> ARec f ts -> g (ARec f ts') Source #
Define a lens for a field of an ARec.
arecGetSubset :: forall rs ss f. (IndexWitnesses (RImage rs ss), NatToInt (RLength rs)) => ARec f ss -> ARec f rs Source #
Get a subset of a record's fields.
arecSetSubset :: forall rs ss f. IndexWitnesses (RImage rs ss) => ARec f ss -> ARec f rs -> ARec f ss Source #
Set a subset of a larger record's fields to all of the fields of a smaller record.
arecRepsMatchCoercion :: AllRepsMatch f xs g ys => Coercion (ARec f xs) (ARec g ys) Source #