microgroove-0.2.1.0: Array-backed extensible records

Safe HaskellNone
LanguageHaskell2010

Data.Microgroove.Mutable

Contents

Synopsis

Mutable Heterogeneous Records

newtype MRec s (f :: u -> *) (us :: [u]) Source #

A mutable heterogeneous record represented by an untyped mutable vector

Constructors

MRec# (MVector s Any) 

Bundled Patterns

pattern MRNil :: us ~ '[] => MRec s f us

Match an empty record, refining its type

pattern MRCons :: us' ~ (u ': us) => MVector s (f u) -> MRec s f us -> MRec s f us'

Match a nonempty record, refining its type. The head is vector of length one to preserve mutable identity. O(1)

Constructing Records

new# :: forall f xs m. (KnownNat (Length xs), PrimMonad m) => m (MRec (PrimState m) f xs) Source #

Create a mutable record of the given shape. The memory is not initialized

Indexing

index :: forall n m f xs. (KnownNat n, PrimMonad m) => MRec (PrimState m) f xs -> m (f (xs !! n)) Source #

Modifying Records

rmap :: forall g m f xs. PrimMonad m => (forall x. f x -> g x) -> MRec (PrimState m) f xs -> m (MRec (PrimState m) g xs) Source #

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

rmapM :: forall g m f xs. PrimMonad m => (forall x. f x -> m (g x)) -> MRec (PrimState m) f xs -> m (MRec (PrimState m) g xs) Source #

Traverse a mutable record in place by mapping an effectful constrained tranformation. O(n)

crmap :: forall (c :: * -> Constraint) g m f xs. (AllF c f xs, PrimMonad m) => (forall x. c (f x) => f x -> g x) -> MRec (PrimState m) f xs -> m (MRec (PrimState m) g xs) Source #

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

crmapM :: forall (c :: * -> Constraint) g m f xs. (AllF c f xs, PrimMonad m) => (forall x. c (f x) => f x -> m (g x)) -> MRec (PrimState m) f xs -> m (MRec (PrimState m) g xs) Source #

Traverse a mutable record in place by mapping an effectful natural tranformation. O(n)

Modifying Individual records

modify_ :: forall n m f xs. (KnownNat n, PrimMonad m) => (forall x. f x -> f x) -> MRec (PrimState m) f xs -> m () Source #

Modify a record in place by applying a natural transformation at the index. O(1)

cmodify_ :: forall (c :: * -> Constraint) n m f xs. (c (f (xs !! n)), KnownNat n, PrimMonad m) => (forall x. c (f x) => f x -> f x) -> MRec (PrimState m) f xs -> m () Source #

Modify a record in place by applying a constrained transformation at the index. O(1)

modify :: forall n m f xs y. (KnownNat n, PrimMonad m) => (f (xs !! n) -> f y) -> MRec (PrimState m) f xs -> m (MRec (PrimState m) f (SetAt n xs y)) Source #

Modify a record in place by applying a function at the index. O(1)

Combining Records

rzip :: forall h m (f :: k -> *) g (xs :: [k]). PrimMonad m => (forall x. f x -> g x -> h x) -> MRec (PrimState m) f xs -> MRec (PrimState m) g xs -> m (MRec (PrimState m) h xs) Source #

Combine two mutable records elementwise with a natural combiner, _into_ the second the second record.

Mutates only the second argument. O(n)

crzip :: forall (c :: * -> Constraint) h m (f :: k -> *) g (xs :: [k]). (AllF c f xs, AllF c g xs, PrimMonad m) => (forall x. (c (f x), c (g x)) => f x -> g x -> h x) -> MRec (PrimState m) f xs -> MRec (PrimState m) g xs -> m (MRec (PrimState m) h xs) Source #

Combine two mutable records elementwise with a constrained combiner, _into_ the second the second record.

Mutates only the second argument. O(n)

Deconstructing Records

toMVector :: forall r m f xs. PrimMonad m => (forall x. f x -> r) -> MRec (PrimState m) f xs -> m (MVector (PrimState m) r) Source #

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

ctoMVector :: forall (c :: * -> Constraint) r m f xs. (AllF c f xs, PrimMonad m) => (forall x. c (f x) => f x -> r) -> MRec (PrimState m) f xs -> m (MVector (PrimState m) r) Source #

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

Filtering Records

subRecord# :: forall ns m f xs. (KnownNat (Length ns), KnownNats ns, PrimMonad m) => MRec (PrimState m) f xs -> m (MRec (PrimState m) f (SubList# ns xs)) Source #

Choose a satically known ordered subset of the fields in a record. The list must be in ascending order. O(n)