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

Safe HaskellNone
LanguageHaskell2010

Numeric.PrimBytes

Synopsis

Documentation

class PrimTagged a => PrimBytes a where Source #

Facilities to convert to and from raw byte array.

Methods

getBytes :: a -> ByteArray# Source #

Store content of a data type in a primitive byte array Should be used together with byteOffset function.

fromBytes Source #

Arguments

:: Int#

offset in bytes

-> ByteArray# 
-> a 

Load content of a data type from a primitive byte array

readBytes Source #

Arguments

:: MutableByteArray# s

source array

-> Int#

byte offset of the source array

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

Read data from a mutable byte array given an offset in bytes

writeBytes Source #

Arguments

:: MutableByteArray# s

destination array

-> Int#

byte offset of the destination array

-> a

data to write into array

-> State# s 
-> State# s 

Write data into a mutable byte array at a given position (offset in bytes)

readAddr :: Addr# -> State# s -> (#State# s, a#) Source #

Read data from a specified address

writeAddr :: a -> Addr# -> State# s -> State# s Source #

Write data to a specified address

byteSize :: a -> Int# Source #

Size of a data type in bytes

byteAlign :: a -> Int# Source #

Alignment of a data type in bytes. byteOffset should be multiple of this value.

byteOffset :: a -> Int# Source #

Offset of the data in a byte array used to store the data, measured in bytes. Should be used together with getBytes function. Unless in case of special data types represented by ByteArrays, it is equal to zero.

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

Index array given an element offset.

indexArray arr i = fromBytes ( i *# byteSize t) arr

readArray :: MutableByteArray# s -> Int# -> State# s -> (#State# s, a#) Source #

Read a mutable array given an element offset.

readArray arr i = readBytes arr ( i *# byteSize t)

writeArray :: MutableByteArray# s -> Int# -> a -> State# s -> State# s Source #

Write a mutable array given an element offset.

writeArray arr i = writeBytes arr ( i *# byteSize t)

getBytes :: (Generic a, GPrimBytes (Rep a)) => a -> ByteArray# Source #

Store content of a data type in a primitive byte array Should be used together with byteOffset function.

fromBytes Source #

Arguments

:: (Generic a, GPrimBytes (Rep a)) 
=> Int#

offset in bytes

-> ByteArray# 
-> a 

Load content of a data type from a primitive byte array

readBytes Source #

Arguments

:: (Generic a, GPrimBytes (Rep a)) 
=> MutableByteArray# s

source array

-> Int#

byte offset of the source array

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

Read data from a mutable byte array given an offset in bytes

writeBytes Source #

Arguments

:: (Generic a, GPrimBytes (Rep a)) 
=> MutableByteArray# s

destination array

-> Int#

byte offset of the destination array

-> a

data to write into array

-> State# s 
-> State# s 

Write data into a mutable byte array at a given position (offset in bytes)

readAddr :: (Generic a, GPrimBytes (Rep a)) => Addr# -> State# s -> (#State# s, a#) Source #

Read data from a specified address

writeAddr :: (Generic a, GPrimBytes (Rep a)) => a -> Addr# -> State# s -> State# s Source #

Write data to a specified address

byteSize :: (Generic a, GPrimBytes (Rep a)) => a -> Int# Source #

Size of a data type in bytes

byteAlign :: (Generic a, GPrimBytes (Rep a)) => a -> Int# Source #

Alignment of a data type in bytes. byteOffset should be multiple of this value.

byteOffset :: (Generic a, GPrimBytes (Rep a)) => a -> Int# Source #

Offset of the data in a byte array used to store the data, measured in bytes. Should be used together with getBytes function. Unless in case of special data types represented by ByteArrays, it is equal to zero.

Instances
PrimBytes Double Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes Float Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes Int Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes Int8 Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes Int16 Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes Int32 Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes Int64 Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes Word Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes Word8 Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes Word16 Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes Word32 Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes Word64 Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes FloatX4 Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.FloatX4

PrimBytes FloatX3 Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.FloatX3

PrimBytes FloatX2 Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.FloatX2

PrimBytes DoubleX4 Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.DoubleX4

PrimBytes DoubleX3 Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.DoubleX3

PrimBytes DoubleX2 Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.DoubleX2

PrimBytes a => PrimBytes [a] Source # 
Instance details

Defined in Numeric.PrimBytes

Methods

getBytes :: [a] -> ByteArray# Source #

fromBytes :: Int# -> ByteArray# -> [a] Source #

readBytes :: MutableByteArray# s -> Int# -> State# s -> (#State# s, [a]#) Source #

writeBytes :: MutableByteArray# s -> Int# -> [a] -> State# s -> State# s Source #

readAddr :: Addr# -> State# s -> (#State# s, [a]#) Source #

writeAddr :: [a] -> Addr# -> State# s -> State# s Source #

byteSize :: [a] -> Int# Source #

byteAlign :: [a] -> Int# Source #

byteOffset :: [a] -> Int# Source #

indexArray :: ByteArray# -> Int# -> [a] Source #

readArray :: MutableByteArray# s -> Int# -> State# s -> (#State# s, [a]#) Source #

writeArray :: MutableByteArray# s -> Int# -> [a] -> State# s -> State# s Source #

PrimBytes a => PrimBytes (Maybe a) Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes (Ptr a) Source # 
Instance details

Defined in Numeric.PrimBytes

(RepresentableList xs, All PrimBytes xs) => PrimBytes (Tuple xs) Source # 
Instance details

Defined in Numeric.PrimBytes

(RepresentableList xs, All PrimBytes xs) => PrimBytes (Tuple xs) Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes t => PrimBytes (ScalarBase t) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ScalarBase

PrimBytes (Quater Double) Source # 
Instance details

Defined in Numeric.Quaternion.QDouble

PrimBytes (Quater Float) Source # 
Instance details

Defined in Numeric.Quaternion.QFloat

(PrimBytes a, PrimBytes b) => PrimBytes (Either a b) Source # 
Instance details

Defined in Numeric.PrimBytes

PrimBytes (Idx x) Source # 
Instance details

Defined in Numeric.PrimBytes

RepresentableList xs => PrimBytes (Idxs xs) Source # 
Instance details

Defined in Numeric.PrimBytes

(PrimBytes t, Dimensions ds) => PrimBytes (ArrayBase t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Internal.Array.Family.ArrayBase

PrimBytes (Array t ds) => PrimBytes (DataFrame t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Type

primTag :: PrimBytes a => a -> PrimTag a Source #

This function allows to find out a type by comparing its tag. This is needed for array overloading, to infer array instances. For non-basic types it defaults to PTagOther