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

Safe HaskellNone
LanguageHaskell2010

Numeric.DataFrame.Internal.Array.Class

Synopsis

Documentation

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

Minimal complete definition

broadcast, ix#, gen#, upd#, elemOffset, elemSize0, fromElems

Methods

broadcast :: t -> a Source #

Broadcast element into array

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

Index an array given an offset

gen# Source #

Arguments

:: Int#

number of elements, not checked! Avoid using this argument if possible.

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

Generate an array using an accumulator funtion

upd# Source #

Arguments

:: Int#

number of elements, not checked! Avoid using this argument if possible.

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

update a single element in an array given an offset

elemOffset :: a -> Int# Source #

Offset of an array in number of elements

elemSize0 :: a -> Int# Source #

Number of elements in an array. Returns zero if this information is not available at runtime. This is possible only if all elements are same in an array.

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

Get array by its offset and size in a ByteArray. Both offset and size are given in element number.

Instances

PrimArray Double DoubleX4 Source # 
PrimArray Double DoubleX3 Source # 
PrimArray Double DoubleX2 Source # 
PrimArray Float FloatX4 Source # 
PrimArray Float FloatX3 Source # 
PrimArray Float FloatX2 Source # 
PrimBytes t => PrimArray t (ScalarBase t) Source # 
PrimBytes t => PrimArray t (ArrayBase t ds) Source # 

Methods

broadcast :: t -> ArrayBase t ds Source #

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

gen# :: Int# -> (s -> (#LiftedRep, LiftedRep, s, t#)) -> s -> (#LiftedRep, LiftedRep, s, ArrayBase t ds#) Source #

upd# :: Int# -> Int# -> t -> ArrayBase t ds -> ArrayBase t ds Source #

elemOffset :: ArrayBase t ds -> Int# Source #

elemSize0 :: ArrayBase t ds -> Int# Source #

fromElems :: Int# -> Int# -> ByteArray# -> ArrayBase t ds Source #

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

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

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

Construct an array from a flat list and length