easytensor-2.1.1.1: 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#, gen#, upd#, withArrayContent#, fromElems#

Methods

broadcast# :: t -> a Source #

Broadcast element into array

Warning: do not use this function at the call site; use broadcast instead. Otherwise you will miss some rewrite rules.

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

withArrayContent# :: forall (rep :: RuntimeRep) (r :: TYPE rep). (t -> r) -> (CumulDims -> Int# -> ByteArray# -> r) -> a -> r Source #

Warning: Please, use withArrayContent instead.

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

Warning: never use this function directly. Use withArrayContent instead. There is a bug in GHC 8.6, such that certain optimizations (probably, instance specialization/rewrite rules) break the code, which is only observable at runtime. The effect is that the content of a ByteArray# becomes a garbage. The workaround is to use a non-inlinable wrapper to disable these optimizations. In addition, the wrapper function has some rewrite rules, which can potentially improve performance with other GHC versions.

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 #

Warning: Please, use fromElems instead.

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

Warning: never use this function directly. Use fromElems instead. There is a bug in GHC 8.6, such that certain optimizations (probably, instance specialization/rewrite rules) break the code, which is only observable at runtime. The effect is that the content of a ByteArray# becomes a garbage. The workaround is to use a non-inlinable wrapper to disable these optimizations. In addition, the wrapper function has some rewrite rules, which can potentially improve performance with other GHC versions.

Instances

Instances details
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

(Dimensions xns, KnownBackend t (DimsBound xns), PrimArray t (DataFrame t (DimsBound xns)), PrimBytes t) => PrimArray t (DataFrame t xns) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

broadcast# :: t -> DataFrame t xns Source #

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

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

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

withArrayContent# :: forall (rep :: RuntimeRep) (r :: TYPE rep). (t -> r) -> (CumulDims -> Int# -> ByteArray# -> r) -> DataFrame t xns -> r Source #

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

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

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

(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 #

withArrayContent# :: forall (rep :: RuntimeRep) (r :: TYPE rep). (t -> r) -> (CumulDims -> Int# -> ByteArray# -> r) -> DataFrame t ds -> r 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!

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.

cdIxSub :: CumulDims -> Idxs (ns +: idxN) -> Dim subN -> Int Source #

Calculate offset of an Idxs.

Also check if the last index plus dimVal of subN is not bigger than the corresponding dim inside CumulDims; throw an OutOfDimBounds otherwise.

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.

getOffAndSteps Source #

Arguments

:: Int

Initial offset

-> CumulDims 
-> Idxs ns 
-> (Int, CumulDims) 

Calculate offset of an Idxs and return remaining CumulDims.

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.

getOffAndStepsSub Source #

Arguments

:: Int

Initial offset

-> CumulDims 
-> Idxs (ns +: idxN) 
-> Dim subN 
-> (Int, CumulDims) 

Calculate offset of an Idxs and return remaining CumulDims.

Also check if the last index plus dimVal of subN is not bigger than the corresponding dim inside CumulDims; throw an OutOfDimBounds otherwise.

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.

cdIxM :: CumulDims -> Idxs ns -> Maybe Int Source #

Same as cdIx, but safe; returns Nothing if out of bounds.

getOffAndStepsM Source #

Arguments

:: Int

Initial offset

-> CumulDims 
-> Idxs ns 
-> Maybe (Int, CumulDims) 

Same as getOffAndSteps, but safe; returns Nothing if out of bounds. Trims the first (slicing) dimension of the returned CumulDims to fit the original dataframe if necessary.

getOffAndStepsSubM Source #

Arguments

:: Int

Initial offset

-> CumulDims 
-> Idxs (ns +: idxN) 
-> Dim subN 
-> Maybe (Int, CumulDims) 

Same as getOffAndStepsSub, but safe; returns Nothing if out of bounds. Trims the first (slicing) dimension of the returned CumulDims to fit the original dataframe if necessary.

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.

withArrayContent :: forall (t :: Type) (a :: Type) (rep :: RuntimeRep) (r :: TYPE rep). PrimArray t a => (t -> r) -> (CumulDims -> Int# -> ByteArray# -> r) -> a -> r Source #

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

fromElems :: forall (t :: Type) (a :: Type). PrimArray t a => CumulDims -> Int# -> ByteArray# -> a Source #

Define an 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.

broadcast :: forall (t :: Type) (a :: Type). PrimArray t a => t -> a Source #

Broadcast element into array