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

Copyright(c) Artem Chirkin
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Numeric.DataFrame.ST

Description

Mutable DataFrames living in ST.

Synopsis

Documentation

data STDataFrame s (t :: Type) (ns :: [k]) where Source #

Mutable DataFrame that lives in ST. Internal representation is always a MutableByteArray.

Bundled Patterns

pattern XSTFrame :: forall s (t :: Type) (xns :: [XNat]). () => forall (ns :: [Nat]). (FixedDims xns ns, Dimensions ns) => STDataFrame s t ns -> STDataFrame s t xns

Data frame with some dimensions missing at compile time. Pattern-match against its constructor to get a Nat-indexed mutable data frame.

data SomeSTDataFrame s (t :: Type) Source #

Mutable DataFrame of unknown dimensionality

Constructors

Dimensions ns => SomeSTDataFrame (STDataFrame s t ns) 

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

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

newDataFrame :: forall (t :: Type) ns s. (PrimBytes t, Dimensions ns) => ST s (STDataFrame s t ns) Source #

Create a new mutable DataFrame.

newPinnedDataFrame :: forall (t :: Type) ns s. (PrimBytes t, Dimensions ns) => ST s (STDataFrame s t ns) Source #

Create a new mutable DataFrame.

oneMoreDataFrame :: forall (t :: Type) ns s. STDataFrame s t ns -> ST s (STDataFrame s t ns) Source #

Create a new mutable DataFrame of the same size.

subDataFrameView :: forall (t :: Type) b bi bd as bs asbs s. (SubFrameIndexCtx b bi bd, KnownDim bd, ConcatList as (b :+ bs) asbs) => Idxs (as +: bi) -> STDataFrame s t asbs -> STDataFrame 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) as bs asbs s. ConcatList as bs asbs => Idxs as -> STDataFrame s t asbs -> STDataFrame 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) b bi bd as bs asbs 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) -> STDataFrame s t asbs -> ST 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).

copyMutableDataFrame :: forall (t :: Type) b bi bd as bs asbs s. (SubFrameIndexCtx b bi bd, ExactDims bs, PrimBytes t, ConcatList as (b :+ bs) asbs) => Idxs (as +: bi) -> STDataFrame s t (bd :+ bs) -> STDataFrame s t asbs -> ST 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) as bs asbs s. (ExactDims bs, PrimArray t (DataFrame t bs), ConcatList as bs asbs) => Idxs as -> DataFrame t bs -> STDataFrame s t asbs -> ST 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.

copyMutableDataFrame' :: forall (t :: Type) as bs asbs s. (ExactDims bs, PrimBytes t, ConcatList as bs asbs) => Idxs as -> STDataFrame s t bs -> STDataFrame s t asbs -> ST 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) as bs asbs s. (Dimensions bs, PrimArray t (DataFrame t bs), ConcatList as bs asbs) => Int -> DataFrame t bs -> STDataFrame s t asbs -> ST 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.

copyMutableDataFrameOff :: forall (t :: Type) as bs asbs s. (ExactDims bs, PrimBytes t, ConcatList as bs asbs) => Int -> STDataFrame s t bs -> STDataFrame s t asbs -> ST 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) ns s. PrimArray t (DataFrame t ns) => STDataFrame s t ns -> ST s (DataFrame t ns) Source #

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

unsafeFreezeDataFrame :: forall (t :: Type) ns s. PrimArray t (DataFrame t ns) => STDataFrame s t ns -> ST s (DataFrame t ns) Source #

Make a mutable DataFrame immutable, without copying.

thawDataFrame :: forall (t :: Type) ns s. (Dimensions ns, PrimArray t (DataFrame t ns)) => DataFrame t ns -> ST s (STDataFrame s t ns) Source #

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

thawPinDataFrame :: forall (t :: Type) ns s. (Dimensions ns, PrimArray t (DataFrame t ns)) => DataFrame t ns -> ST s (STDataFrame 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 s. (Dimensions ns, PrimArray t (DataFrame t ns)) => DataFrame t ns -> ST s (STDataFrame s t ns) Source #

UnsafeCoerces an underlying byte array.

withThawDataFrame :: forall (t :: Type) ns r s. PrimArray t (DataFrame t ns) => (t -> ST s r) -> (STDataFrame s t ns -> ST s r) -> DataFrame t ns -> ST s r Source #

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) ns s. PrimBytes (DataFrame t ('[] :: KindOf ns)) => STDataFrame s t ns -> Idxs ns -> DataFrame t ('[] :: KindOf ns) -> ST 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) ns s. PrimBytes (DataFrame t ('[] :: KindOf ns)) => STDataFrame s t ns -> Int -> DataFrame t ('[] :: KindOf ns) -> ST 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) ns s. PrimBytes (DataFrame t ('[] :: KindOf ns)) => STDataFrame s t ns -> Idxs ns -> ST s (DataFrame t ('[] :: KindOf ns)) 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) ns s. PrimBytes (DataFrame t ('[] :: KindOf ns)) => STDataFrame s t ns -> Int -> ST s (DataFrame t ('[] :: KindOf ns)) 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.

isDataFramePinned :: forall (t :: Type) ns s. STDataFrame 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) ns s. STDataFrame s t ns -> CumulDims Source #

Get cumulative dimensions ns of a STDataFrame s t ns