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

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

Numeric.DataFrame.IO

Description

Mutable DataFrames living in IO.

Synopsis

Documentation

data family IODataFrame (t :: Type) (ns :: [k]) Source #

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

Instances

data IODataFrame Nat Source #

Pure wrapper on a mutable byte array

data IODataFrame XNat Source #

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

data SomeIODataFrame (t :: Type) Source #

Mutable DataFrame of unknown dimensionality

Constructors

Dimensions ns => SomeIODataFrame (IODataFrame t ns) 

newDataFrame :: forall t (ns :: [Nat]). (PrimBytes t, Dimensions ns) => IO (IODataFrame t ns) Source #

Create a new mutable DataFrame.

newPinnedDataFrame :: forall t (ns :: [Nat]). (PrimBytes t, Dimensions ns) => IO (IODataFrame t ns) Source #

Create a new mutable DataFrame.

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

Copy one DataFrame into another mutable DataFrame at specified position.

copyMutableDataFrame :: forall (t :: Type) (as :: [Nat]) (b' :: Nat) (b :: Nat) (bs :: [Nat]) (asbs :: [Nat]). (PrimBytes t, ConcatList as (b :+ bs) asbs, Dimensions (b :+ bs)) => IODataFrame t (as +: b') -> Idxs (b :+ bs) -> IODataFrame t asbs -> IO () Source #

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

freezeDataFrame :: forall (t :: Type) (ns :: [Nat]). PrimArray t (DataFrame t ns) => IODataFrame t ns -> IO (DataFrame t ns) Source #

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

unsafeFreezeDataFrame :: forall (t :: Type) (ns :: [Nat]). PrimArray t (DataFrame t ns) => IODataFrame t ns -> IO (DataFrame t ns) Source #

Make a mutable DataFrame immutable, without copying.

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

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

thawPinDataFrame :: forall (t :: Type) (ns :: [Nat]). (PrimBytes (DataFrame t ns), PrimBytes t) => DataFrame t ns -> IO (IODataFrame 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]). (PrimBytes (DataFrame t ns), PrimBytes t) => DataFrame t ns -> IO (IODataFrame t ns) Source #

UnsafeCoerces an underlying byte array.

writeDataFrame :: forall t (ns :: [Nat]). (PrimBytes t, Dimensions ns) => IODataFrame t ns -> Idxs ns -> DataFrame t ('[] :: [Nat]) -> IO () Source #

Write a single element at the specified index

writeDataFrameOff :: forall (t :: Type) (ns :: [Nat]). PrimBytes t => IODataFrame t ns -> Int -> DataFrame t ('[] :: [Nat]) -> IO () Source #

Write a single element at the specified element offset

readDataFrame :: forall (t :: Type) (ns :: [Nat]). (PrimBytes t, Dimensions ns) => IODataFrame t ns -> Idxs ns -> IO (DataFrame t ('[] :: [Nat])) Source #

Read a single element at the specified index

readDataFrameOff :: forall (t :: Type) (ns :: [Nat]). PrimBytes t => IODataFrame t ns -> Int -> IO (DataFrame t ('[] :: [Nat])) Source #

Read a single element at the specified element offset

withDataFramePtr :: forall (t :: Type) (ns :: [k]) (r :: Type). (PrimBytes t, KnownDimKind k) => IODataFrame t ns -> (Ptr t -> IO r) -> IO r Source #

Allow arbitrary IO operations on a pointer to the beginning of the data keeping the data from garbage collecting until the arg function returns.

Warning: do not let Ptr t leave the scope of the arg function, the data may be garbage-collected by then.

Warning: use this function on a pinned DataFrame only; otherwise, the data may be relocated before the arg fun finishes.

isDataFramePinned :: forall (t :: Type) (ns :: [k]). KnownDimKind k => IODataFrame t ns -> Bool Source #

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