easytensor-2.1.1.1: Pure, type-indexed haskell vector, matrix, and tensor library.
Copyright(c) Artem Chirkin
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Numeric.DataFrame.Internal.Mutable

Description

Interface to perform primitive stateful operations on mutable frames.

Synopsis

Documentation

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

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

castDataFrame# :: forall (t :: Type) (xns :: [XNat]) (ns :: [Nat]) s. FixedDims xns ns => MDataFrame s t ns -> MDataFrame s t xns Source #

Allow coercing between XNat-indexed and Nat-indexed Mutable DataFrames.

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

Create a new mutable DataFrame.

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

Create a new mutable DataFrame.

oneMoreDataFrame# :: forall (t :: Type) (k :: Type) (ns :: [k]) s. MDataFrame s t ns -> State# s -> (# State# s, MDataFrame s t ns #) Source #

Create a new mutable DataFrame of the same size.

subDataFrameView# :: forall (t :: Type) (k :: Type) (b :: k) (bi :: k) (bd :: k) (as :: [k]) (bs :: [k]) (asbs :: [k]) s. (SubFrameIndexCtx b bi bd, KnownDim bd, ConcatList as (b :+ bs) asbs) => Idxs (as +: bi) -> MDataFrame s t asbs -> MDataFrame s t (bd :+ bs) Source #

View a part of a DataFrame.

This function does not perform a copy. All changes to a new DataFrame will be reflected in the original DataFrame as well.

If any of the dims in as or b is unknown (a ~ XN m), then this function is unsafe and can throw an OutOfDimBounds exception. Otherwise, its safety is guaranteed by the type system.

subDataFrameView'# :: forall (t :: Type) (k :: Type) (as :: [k]) (bs :: [k]) (asbs :: [k]) s. ConcatList as bs asbs => Idxs as -> MDataFrame s t asbs -> MDataFrame s t bs Source #

View a part of a DataFrame.

This function does not perform a copy. All changes to a new DataFrame will be reflected in the original DataFrame as well.

This is a simpler version of subDataFrameView that allows to view over one index at a time.

If any of the dims in as is unknown (a ~ XN m), then this function is unsafe and can throw an OutOfDimBounds exception. Otherwise, its safety is guaranteed by the type system.

copyDataFrame# :: forall (t :: Type) (k :: Type) (b :: k) (bi :: k) (bd :: k) (as :: [k]) (bs :: [k]) (asbs :: [k]) s. (SubFrameIndexCtx b bi bd, KnownDim bd, ExactDims bs, PrimArray t (DataFrame t (bd :+ bs)), ConcatList as (b :+ bs) asbs) => Idxs (as +: bi) -> DataFrame t (bd :+ bs) -> MDataFrame s t asbs -> State# s -> (# State# s, () #) Source #

Copy one DataFrame into another mutable DataFrame at specified position.

In contrast to copyDataFrame', this function allows to copy over a range of contiguous indices over a single dimension. For example, you can write a 3x4 matrix into a 7x4 matrix, starting at indices 0..3.

This function is safe (no OutOfDimBounds exception possible). If any of the dims in as is unknown (a ~ XN m), you may happen to write data beyond dataframe bounds. In this case, this function does nothing. If (b ~ XN m) and (Idx bi + Dim bd > Dim b), this function copies only as many elements as fits into the dataframe along this dimension (possibly none).

copyMDataFrame# :: forall (t :: Type) (k :: Type) (b :: k) (bi :: k) (bd :: k) (as :: [k]) (bs :: [k]) (asbs :: [k]) s. (SubFrameIndexCtx b bi bd, ExactDims bs, PrimBytes t, ConcatList as (b :+ bs) asbs) => Idxs (as +: bi) -> MDataFrame s t (bd :+ bs) -> MDataFrame s t asbs -> State# s -> (# State# s, () #) Source #

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

In contrast to copyMutableDataFrame', this function allows to copy over a range of contiguous indices over a single dimension. For example, you can write a 3x4 matrix into a 7x4 matrix, starting at indices 0..3.

This function is safe (no OutOfDimBounds exception possible). If any of the dims in as is unknown (a ~ XN m), you may happen to write data beyond dataframe bounds. In this case, this function does nothing. If (b ~ XN m) and (Idx bi + Dim bd > Dim b), this function copies only as many elements as fits into the dataframe along this dimension (possibly none).

copyDataFrame'# :: forall (t :: Type) (k :: Type) (as :: [k]) (bs :: [k]) (asbs :: [k]) s. (ExactDims bs, PrimArray t (DataFrame t bs), ConcatList as bs asbs) => Idxs as -> DataFrame t bs -> MDataFrame s t asbs -> State# s -> (# State# s, () #) Source #

Copy one DataFrame into another mutable DataFrame at specified position.

This is a simpler version of copyDataFrame that allows to copy over one index at a time.

This function is safe (no OutOfDimBounds exception possible). If any of the dims in as is unknown (a ~ XN m), you may happen to write data beyond dataframe bounds. In this case, this function does nothing.

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

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

This is a simpler version of copyMutableDataFrame that allows to copy over one index at a time.

This function is safe (no OutOfDimBounds exception possible). If any of the dims in as is unknown (a ~ XN m), you may happen to write data beyond dataframe bounds. In this case, this function does nothing.

copyDataFrameOff# :: forall (t :: Type) (k :: Type) (as :: [k]) (bs :: [k]) (asbs :: [k]) s. (Dimensions bs, PrimArray t (DataFrame t bs), ConcatList as bs asbs) => Int -> DataFrame t bs -> MDataFrame s t asbs -> State# s -> (# State# s, () #) Source #

Copy one DataFrame into another mutable DataFrame by offset in primitive elements.

This is a low-level copy function; you have to keep in mind the row-major layout of Mutable DataFrames. Offset bounds are not checked. You will get an undefined behavior if you write beyond the DataFrame bounds.

copyMDataFrameOff# :: forall (t :: Type) (k :: Type) (as :: [k]) (bs :: [k]) (asbs :: [k]) s. (ExactDims bs, PrimBytes t, ConcatList as bs asbs) => Int -> MDataFrame s t bs -> MDataFrame s t asbs -> State# s -> (# State# s, () #) Source #

Copy one mutable DataFrame into another mutable DataFrame by offset in primitive elements.

This is a low-level copy function; you have to keep in mind the row-major layout of Mutable DataFrames. Offset bounds are not checked. You will get an undefined behavior if you write beyond the DataFrame bounds.

freezeDataFrame# :: forall (t :: Type) (k :: Type) (ns :: [k]) 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) (k :: Type) (ns :: [k]) 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) (k :: Type) (ns :: [k]) s. (Dimensions ns, PrimArray t (DataFrame t ns)) => 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) (k :: Type) (ns :: [k]) s. (Dimensions ns, PrimArray t (DataFrame t ns)) => 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) (k :: Type) (ns :: [k]) s. (Dimensions ns, PrimArray t (DataFrame t ns)) => DataFrame t ns -> State# s -> (# State# s, MDataFrame s t ns #) Source #

UnsafeCoerces an underlying byte array.

withThawDataFrame# Source #

Arguments

:: forall (t :: Type) (k :: Type) (ns :: [k]) (r :: Type) s. PrimArray t (DataFrame t ns) 
=> (t -> State# s -> (# State# s, r #))

f

-> (MDataFrame s t ns -> State# s -> (# State# s, r #))

g

-> DataFrame t ns 
-> State# s 
-> (# State# s, r #) 

Given two continuations f and g. If the input DataFrame is a single broadcast value, use it in f. Otherwise, create a new mutable DataFrame and copy content of immutable one in there; then use it in g.

This function is useful when thawDataFrame cannot be used due to Dimensions ns constraint being not available.

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

Write a single element at the specified index.

This function is safe (no OutOfDimBounds exception possible). If any of the dims in ns is unknown (n ~ XN m), you may happen to write data beyond dataframe bounds. In this case, this function does nothing.

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

Write a single element at the specified element offset.

This is a low-level write function; you have to keep in mind the row-major layout of Mutable DataFrames. Offset bounds are not checked. You will get an undefined behavior if you write beyond the DataFrame bounds.

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

Read a single element at the specified index.

If any of the dims in ns is unknown (n ~ XN m), then this function is unsafe and can throw an OutOfDimBounds exception. Otherwise, its safety is guaranteed by the type system.

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

Read a single element at the specified element offset.

This is a low-level read function; you have to keep in mind the row-major layout of Mutable DataFrames. Offset bounds are not checked. You will get an undefined behavior if you read beyond the DataFrame bounds.

withDataFramePtr# :: forall (t :: Type) (k :: Type) (ns :: [k]) (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) (k :: Type) (ns :: [k]) 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.

getDataFrameSteps# :: forall (t :: Type) (k :: Type) (ns :: [k]) s. MDataFrame s t ns -> CumulDims Source #

Get cumulative dimensions ns of a MDataFrame s t ns