easytensor-1.0.1.0: Pure, type-indexed haskell vector, matrix, and tensor library.

Copyright(c) Artem Chirkin
LicenseBSD3
Maintainerchirkin@arch.ethz.ch
Safe HaskellNone
LanguageHaskell2010

Numeric.DataFrame.Internal.Mutable

Description

Interfrace to perform primitive stateful operations on mutable frames.

Synopsis

Documentation

data MDataFrame s t (ns :: [Nat]) Source #

Mutable DataFrame type. Keeps element offset, number of elements, and a mutable byte storage

newDataFrame# :: forall t (ns :: [Nat]) s. (PrimBytes t, Dimensions ns) => State# s -> (#State# s, MDataFrame s t ns#) Source #

Create a new mutable DataFrame.

newPinnedDataFrame# :: forall t (ns :: [Nat]) s. (PrimBytes t, Dimensions ns) => State# s -> (#State# s, MDataFrame s t ns#) Source #

Create a new mutable DataFrame.

copyDataFrame# :: forall (t :: Type) (as :: [Nat]) (b' :: Nat) (b :: Nat) (bs :: [Nat]) (asbs :: [Nat]) s. (PrimBytes t, PrimBytes (DataFrame t (as +: b')), ConcatList as (b :+ bs) asbs, Dimensions (b :+ bs)) => DataFrame t (as +: b') -> Idxs (b :+ bs) -> MDataFrame s t asbs -> State# s -> (#State# s, ()#) Source #

Copy one DataFrame into another mutable DataFrame at specified position.

copyMDataFrame# :: forall (t :: Type) (as :: [Nat]) (b' :: Nat) (b :: Nat) (bs :: [Nat]) (asbs :: [Nat]) s. (PrimBytes t, ConcatList as (b :+ bs) asbs, Dimensions (b :+ bs)) => MDataFrame s t (as +: b') -> Idxs (b :+ bs) -> MDataFrame s t asbs -> State# s -> (#State# s, ()#) Source #

Copy one mutable DataFrame into another mutable DataFrame at specified position.

freezeDataFrame# :: forall (t :: Type) (ns :: [Nat]) s. PrimArray t (DataFrame t ns) => MDataFrame s t ns -> State# s -> (#State# s, DataFrame t ns#) Source #

Copy content of a mutable DataFrame into a new immutable DataFrame.

unsafeFreezeDataFrame# :: forall (t :: Type) (ns :: [Nat]) s. PrimArray t (DataFrame t ns) => MDataFrame s t ns -> State# s -> (#State# s, DataFrame t ns#) Source #

Make a mutable DataFrame immutable, without copying.

thawDataFrame# :: forall (t :: Type) (ns :: [Nat]) s. (PrimBytes (DataFrame t ns), PrimBytes t) => DataFrame t ns -> State# s -> (#State# s, MDataFrame s t ns#) Source #

Create a new mutable DataFrame and copy content of immutable one in there.

thawPinDataFrame# :: forall (t :: Type) (ns :: [Nat]) s. (PrimBytes (DataFrame t ns), PrimBytes t) => DataFrame t ns -> State# s -> (#State# s, MDataFrame s t ns#) Source #

Create a new mutable DataFrame and copy content of immutable one in there. The result array is pinned and aligned.

unsafeThawDataFrame# :: forall (t :: Type) (ns :: [Nat]) s. (PrimBytes (DataFrame t ns), PrimBytes t) => DataFrame t ns -> State# s -> (#State# s, MDataFrame s t ns#) Source #

UnsafeCoerces an underlying byte array.

writeDataFrame# :: forall (t :: Type) (ns :: [Nat]) s. (PrimBytes t, Dimensions ns) => MDataFrame s t ns -> Idxs ns -> t -> State# s -> (#State# s, ()#) Source #

Write a single element at the specified index

writeDataFrameOff# :: forall (t :: Type) (ns :: [Nat]) s. PrimBytes t => MDataFrame s t ns -> Int# -> t -> State# s -> (#State# s, ()#) Source #

Write a single element at the specified element offset

readDataFrame# :: forall (t :: Type) (ns :: [Nat]) s. (PrimBytes t, Dimensions ns) => MDataFrame s t ns -> Idxs ns -> State# s -> (#State# s, t#) Source #

Read a single element at the specified index

readDataFrameOff# :: forall (t :: Type) (ns :: [Nat]) s. PrimBytes t => MDataFrame s t ns -> Int# -> State# s -> (#State# s, t#) Source #

Read a single element at the specified element offset

withDataFramePtr# :: forall (t :: Type) (ns :: [Nat]) (r :: Type). PrimBytes t => MDataFrame RealWorld t ns -> (Addr# -> State# RealWorld -> (#State# RealWorld, r#)) -> State# RealWorld -> (#State# RealWorld, r#) Source #

Allow arbitrary operations on a pointer to the beginning of the data. Only possible with RealWord state (thus, in IO) due to semantics of touch# operation that keeps the data from being garbage collected.

isDataFramePinned# :: forall (t :: Type) (ns :: [Nat]) s. MDataFrame s t ns -> Bool Source #

Check if the byte array wrapped by this DataFrame is pinned, which means cannot be relocated by GC.