Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
Tradeoffs:
- No sharing of the spine (i.e. when you change elements in the front of the record the tail can't be re-used)
- ARec requires (4 + n) words + size of the fields
- 1 for the ARec constructor
- 1 for the pointer to the SmallArray#
- The SmallArray# has 2 words as header (1 for GC, 1 for number of elements)
- 1 pointer per element to the actual data
- Rec requires (2n) words + size of Fields
- 1 word per (:&) constructor
- 1 word for the pointer to the element
Synopsis
- newtype ARec (f :: k -> *) (ts :: [k]) = ARec SmallArray
- class ToARec (us :: [k])
- class NatToInt (RIndex t ts) => IndexableField ts t
- arec :: forall k (us :: [k]) f. NatToInt (RLength us) => ARecBuilder f us -> ARec f us
- newtype ARecBuilder f us = ARecBuilder (forall s. Int -> SmallMutableArray s -> ST s ())
- arcons :: f u -> ARecBuilder f us -> ARecBuilder f (u ': us)
- arnil :: ARecBuilder f '[]
- toARec :: forall f ts. (NatToInt (RLength ts), ToARec 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
- unsafeAput :: forall t t' f ts ts'. NatToInt (RIndex t ts) => f t' -> ARec f ts -> ARec f ts'
- unsafeAlens :: 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
newtype 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 type RecSubsetFCtx ARec f Source # 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 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 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 # | |
Defined in Data.Vinyl.ARec.Internal | |
(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 ToARec (us :: [k]) Source #
aRecValues
Instances
ToARec ('[] :: [k]) Source # | |
Defined in Data.Vinyl.ARec.Internal aRecValues :: forall (f :: k0 -> Type). Rec f '[] -> ARecBuilder f '[] | |
ToARec us => ToARec (u ': us :: [k]) Source # | |
Defined in Data.Vinyl.ARec.Internal aRecValues :: forall (f :: k0 -> Type). Rec f (u ': us) -> ARecBuilder f (u ': us) |
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 |
arec :: forall k (us :: [k]) f. NatToInt (RLength us) => ARecBuilder f us -> ARec f us Source #
Turn an ARecBuilder into an ARec
See ARecBuilder
newtype ARecBuilder f us Source #
An efficient builder for ARec values
Use the pseudo-constructors arcons
and arnil
to construct an
ARecBuilder
and then turn it into an ARec
with arec
Example: (requires -XOverloadedLabels and )
user :: ARec ElField '[ "name" ::: String , "age" ::: Int , "active" ::: Bool] user = arec ( #name =: "Peter" `arcons` #age =: 4 `arcons` #active =: True `arcons` arnil )
ARecBuilder (forall s. Int -> SmallMutableArray s -> ST s ()) |
arcons :: f u -> ARecBuilder f us -> ARecBuilder f (u ': us) infixr 1 Source #
arnil :: ARecBuilder f '[] Source #
fromARec :: forall f ts. (RecApplicative ts, RPureConstrained (IndexableField ts) ts) => ARec f ts -> Rec f ts Source #
unsafeAput :: 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
.
unsafeAlens :: 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 #