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

Safe HaskellNone
LanguageHaskell2010

Numeric.DataFrame.Internal.PrimArray

Synopsis

Documentation

class PrimBytes t => PrimArray t a | a -> t where Source #

Minimal complete definition

broadcast, ix#, gen#, upd#, arrayContent#, fromElems

Methods

broadcast :: t -> a Source #

Broadcast element into array

ix# :: Int# -> a -> t Source #

Index an array given an offset

gen# Source #

Arguments

:: CumulDims

Dimensionality of the result array; Be careful! ns depends on a, but this is not reflected in types and is not checked at runtime.

-> (s -> (#s, t#)) 
-> s 
-> (#s, a#) 

Generate an array using an accumulator funtion

upd# Source #

Arguments

:: CumulDims

Dimensionality of the result array; Be careful! ns depends on a, but this is not reflected in types and is not checked at runtime.

-> Int# 
-> t 
-> a 
-> a 

update a single element in an array given an offset

arrayContent# :: a -> (#t | (#CumulDims, Int#, ByteArray##)#) Source #

If the array represented as a single broadcasted value, return this value. Otherwise, return full array content: CumulDims, array offset (elements), byte array with the content.

offsetElems :: a -> Int# Source #

Offset of an array as a number of elements

uniqueOrCumulDims :: a -> Either t CumulDims Source #

Normally, this returns a cumulative totalDims. However, if a particular implementation does not have the dimensionality information, it cannot return CumulDims; In this case, it is a sign that all elements of an array are same. Thus, it is possible to return the single element value instead.

Note, this function returns the only unique element only if it is a such by construction (there is no equality checks involved).

fromElems :: CumulDims -> Int# -> ByteArray# -> a Source #

Get array by its offset and cumulative dims in a ByteArray. Both offset and dims are given in element number (not in bytes).

It is better to use this function instead of fromBytes to avoid recalculating CumulDims for implementations that require it.

Instances
PrimArray Double (Quater Double) Source # 
Instance details

Defined in Numeric.Quaternion.Internal.QDouble

PrimArray Float (Quater Float) Source # 
Instance details

Defined in Numeric.Quaternion.Internal.QFloat

(PrimArray t (DFBackend t ds), PrimBytes t) => PrimArray t (DataFrame t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

broadcast :: t -> DataFrame t ds Source #

ix# :: Int# -> DataFrame t ds -> t Source #

gen# :: CumulDims -> (s -> (#s, t#)) -> s -> (#s, DataFrame t ds#) Source #

upd# :: CumulDims -> Int# -> t -> DataFrame t ds -> DataFrame t ds Source #

arrayContent# :: DataFrame t ds -> (#|#) t (#CumulDims, Int#, ByteArray##) Source #

offsetElems :: DataFrame t ds -> Int# Source #

uniqueOrCumulDims :: DataFrame t ds -> Either t CumulDims Source #

fromElems :: CumulDims -> Int# -> ByteArray# -> DataFrame t ds Source #

newtype CumulDims Source #

Given Dims ns, CumulativeDims is a list of length Length ns + 1; which cumulative totalDim accumulated on the right. In particular, its first element is totalDim ds, its last element is always is always 1.

Constructors

CumulDims 

Fields

cumulDims :: Dims (ns :: [k]) -> CumulDims Source #

Calculate cumulative dims

cdTotalDim :: CumulDims -> Word Source #

Get the total number of elements

cdIx :: CumulDims -> Idxs ns -> Int Source #

Calculate offset of an Idxs

Note, you can take offset of subspace with CumulDims of larger space - very convenient!

ixOff :: PrimArray t a => Int -> a -> t Source #

Index array by an integer offset (starting from 0).

unsafeFromFlatList :: PrimArray t a => Dims ns -> t -> [t] -> a Source #

Construct an array from a flat list and Dims; Be careful! ns depends on a, but this is not reflected in types and is not checked at runtime.

getSteps :: PrimArray t a => Dims (ns :: [k]) -> a -> CumulDims Source #

Try to get CumulDims from an array, and create it using Dims if failed.

fromSteps :: CumulDims -> SomeDims Source #

Get Dims by "de-accumulating" CumulDims.