microgroove-0.1.0.0: Array-backed extensible records

Safe HaskellNone
LanguageHaskell2010

Data.Microgroove.Rec

Synopsis

Documentation

newtype Rec f us Source #

A heterogeneous record represented by an untyped vector

Constructors

Rec# (Vector Any) 

Instances

(Show (f x), Show (Rec a f xs)) => Show (Rec a f ((:) a x xs)) Source # 

Methods

showsPrec :: Int -> Rec a f ((a ': x) xs) -> ShowS #

show :: Rec a f ((a ': x) xs) -> String #

showList :: [Rec a f ((a ': x) xs)] -> ShowS #

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

Methods

showsPrec :: Int -> Rec u f [u] -> ShowS #

show :: Rec u f [u] -> String #

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

newtype MRec s f us Source #

A mutable heterogeneous record represented by an untyped mutable vector

Constructors

MRec# (MVector s Any) 

data RIndex xs x Source #

A prepared index into a record, allowing fast access

Instances

Show (RIndex u xs x) Source # 

Methods

showsPrec :: Int -> RIndex u xs x -> ShowS #

show :: RIndex u xs x -> String #

showList :: [RIndex u xs x] -> ShowS #

mkIndex :: forall n xs. (KnownNat n, n <= (Length xs - 1)) => RIndex xs (xs !! n) Source #

Construct a statically known index into a record O(1)

index :: forall n f xs. KnownNat n => Rec f xs -> f (xs !! n) Source #

Index into a statically known element of a record O(1)

(!) :: Rec f us -> RIndex us u -> f u Source #

Index into a record with a prepared index O(1)

checkIndex :: forall xs f. KnownNat (Length xs) => Rec f xs -> Int -> MaybeSome (RIndex xs) Source #

Prepare a dynamically known index into a statically known record O(n)

checkIndex' :: forall xs f. Rec f xs -> Int -> MaybeSome (RIndex xs) Source #

Prepare a dynamically known index O(n)

splitCons :: Rec f (x ': xs) -> (f x, Rec f xs) Source #

Split a record into a head element, and the remaining record must be statically known to be nonempty O(1)

rappend :: Rec f as -> Rec f bs -> Rec f (as ++ bs) Source #

Append two records O(n+m)

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

Transform a mutable record in by mapping a natural tranformation. O(n)

crmap :: forall c g f xs. AllF c f xs => (forall x. c (f x) => f x -> g x) -> Rec f xs -> Rec g xs Source #

Transform a record in by mapping a natural tranformation that can make use of the provided constraint. Ex: `crmap @Show (K . show) :: (Rec f xs) -> (MRec (K String) xs)` O(n)

toVector :: (forall x. f x -> r) -> Rec f xs -> Vector r Source #

Convert a record to a vector by mapping to a homogeneous type O(n)

ctoVector :: forall c r f xs. AllF c f xs => (forall x. c (f x) => f x -> r) -> Rec f xs -> Vector r Source #

Convert a record to a vector by mapping to a homogeneous type, making use of provided constraint O(n)

fromVectorN :: forall n f x. KnownNat n => Vector (f x) -> Maybe (Rec f (Replicate n x)) Source #

Convert a vector into a homogeneous record of statically known size O(1)

fromVector :: forall f x. Vector (f x) -> Some (Rec f) Source #

Convert a vector into a homogeneous record with dynamically known size O(n)

replicate :: forall n f x. KnownNat n => f x -> Rec f (Replicate n x) Source #

Create a record of statically known size by replicating a single element O(n)

thaw :: PrimMonad m => Rec f us -> m (MRec (PrimState m) f us) Source #

Copy a record into a fresh mutable record O(n)

thaw# :: PrimMonad m => Rec f us -> m (MRec (PrimState m) f us) Source #

unsafely thaw a record. The original record should no longer be used, but this is not checked O(1)

freeze :: PrimMonad m => MRec (PrimState m) f us -> m (Rec f us) Source #

Copy a mutable record into a fresh record O(n)

freeze# :: PrimMonad m => MRec (PrimState m) f us -> m (Rec f us) Source #

Unsafely freeze a mutable record. The original record should no longer be modified, but this is not checked O(1)

modify :: forall n xs fx f. (fx ~ f (xs !! n), KnownNat n) => (fx -> fx) -> Rec f xs -> Rec f xs Source #

Transform a record by appling an endofunctor at the index. O(n)

setAt :: forall n x xs f. KnownNat n => f x -> Rec f xs -> Rec f (SetAt n xs x) Source #

Transform a record by setting its value at an index, may change the record type. O(n)