easytensor-2.1.1.1: Pure, type-indexed haskell vector, matrix, and tensor library.
Copyright(c) Artem Chirkin
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Numeric.PrimBytes

Description

Facilities for converting Haskell data to and from raw bytes.

The main purpose of this module is to support the implementation of the DataFrame Backend. However, it also comes very useful for writing FFI. To that end, the PrimBytes class is similar to the Storable class: it provides means to write your data to and read from a raw memory area. Though, it is more flexible in that it can work with both, foreign pointers and primitive byte arrays, and it provides means to get data field offsets by their selector names. On top of that, a PrimBytes instance can be derived via the Generic machinery.

A derived PrimBytes instance tries to pack the data as dense as possible, while respecting the alignment requirements. In all cases known to me, the resulting data layout coincides with a corresponding C struct, allowing to marshal the data without any boilerplate. However, this is not guaranteed, but you can write a PrimBytes instance manually if necessary (and report an issue plz).

Note about alignment, size, and padding of the data. There are two basic sanity assumptions about these, which are not checked in this module at all:

  • the alignment is always a power of 2;
  • the size is always rounded up to a multiple of the alignment.

Generated instances of PrimBytes meet these assumptions if all components of a data meet these assumptions too. You are strongly advised to provide all byte offset arguments to the PrimBytes functions respecting the alignment of the data; otherwise, the data may be written or read incorrectly.

Synopsis

PrimBytes API

class PrimTagged a => PrimBytes a where Source #

Defines how to read and write your data to and from Haskell unboxed byte arrays and plain pointers.

Similarly to Storable, this class provides functions to get the size and alignment of a data via phantom arguments. Thus, the size and alignment of the data must not depend on the data content (they depend only on the type of the data). In particular, this means that dynamically sized structures like Haskell lists or maps are not allowed.

This module provides default implementations for all methods of this class via Generic. Hence, to make your data an instance of PrimBytes, it is sufficient to write the instance head:

data MyData a b = ...
  deriving Generic

instance (PrimBytes a, PrimBytes b) => PrimBytes (MyData a b)

.. or use the DeriveAnyClass extension to make it even shorter:

data MyData a b = ...
  deriving (Generic, PrimBytes)

The derived instance tries to pack the data as dense as possible, but sometimes it is better to write the instance by hand. If a derived type has more than one constructor, the derived instance puts a Word32 tag at the beginning of the byte representation. All fields of a constructor are packed in a C-like fashion next to each other, while respecting their alignments.

Minimal complete definition

Nothing

Associated Types

type PrimFields a :: [Symbol] Source #

List of field names.

It is used to get field offsets using byteFieldOffset function.

A Generic-derived instance has this list non-empty only if two obvious conditions are met:

  1. The data has only one constructor.
  2. The data uses record syntax to define its fields.

type PrimFields a = GPrimFields (Rep a)

Methods

getBytes :: a -> ByteArray# Source #

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

Note, the default implementation of this function returns a not pinned array, which is aligned to 8. Thus, it ignores the alignment of the underlying data type if it is larger. However, alignment calculation still makes sense for data types that are smaller than 8 bytes: they are packed more densely.

getBytesPinned :: a -> ByteArray# Source #

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

In contrast to getBytes, this function returns a pinned byte array, aligned to the byteAlign bytes of this data.

Note, GC guarantees not to move the created array. While this is very useful sometimes, it incurs a certain performance penalty.

fromBytes Source #

Arguments

:: Int#

Offset in bytes

-> ByteArray#

Source array

-> a 

Load content of a data type from a primitive byte array given an offset in bytes.

default fromBytes :: (Generic a, GPrimBytes (Rep a)) => Int# -> ByteArray# -> a Source #

readBytes Source #

Arguments

:: MutableByteArray# s

Source array

-> Int#

Byte offset in the source array

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

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

default readBytes :: (Generic a, GPrimBytes (Rep a)) => MutableByteArray# s -> Int# -> State# s -> (# State# s, a #) Source #

writeBytes Source #

Arguments

:: MutableByteArray# s

Destination array

-> Int#

Byte offset in the destination array

-> a

Data to write into the array

-> State# s 
-> State# s 

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

default writeBytes :: (Generic a, GPrimBytes (Rep a)) => MutableByteArray# s -> Int# -> a -> State# s -> State# s Source #

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

Read data from a specified address.

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

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

Write data to a specified address.

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

byteSize :: a -> Int# Source #

Size of a data type in bytes. It should be a multiple of byteAlign for indexing functions to operate correctly.

Implementation of this function must not inspect the argument value; a caller may provide undefined in place of the argument.

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

byteAlign :: a -> Int# Source #

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

Implementation of this function must not inspect the argument value; a caller may provide undefined in place of the argument.

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

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.

Implementation of this function may inspect the argument value; a caller must not provide undefined in place of the argument.

byteFieldOffset :: (Elem name (PrimFields a), KnownSymbol name) => Proxy# name -> a -> Int# Source #

Offset of a data record within the data type in bytes.

Implementation of this function must not inspect the argument value; a caller may provide undefined in place of the argument.

The default (generic) implementation of this fucntion looks for the leftmost occurrence of a given field name (in case of multiple constructors). If a field with the given name is not found, it returns -1, but this is not possible thanks to Elem name (PrimFields a) constraint.

default byteFieldOffset :: (Generic a, GPrimBytes (Rep a), KnownSymbol name) => Proxy# name -> a -> Int# Source #

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

Index array given an element offset (which is byteSize a and should be a multiple of byteAlign a).

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

Read a mutable array given an element offset (which is byteSize a and should be a multiple of byteAlign a).

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

Write a mutable array given an element offset (which is byteSize a and should be a multiple of byteAlign a).

Instances

Instances details
PrimBytes Char Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields Char :: [Symbol] Source #

PrimBytes Double Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields Double :: [Symbol] Source #

PrimBytes Float Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields Float :: [Symbol] Source #

PrimBytes Int Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields Int :: [Symbol] Source #

PrimBytes Int8 Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields Int8 :: [Symbol] Source #

PrimBytes Int16 Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields Int16 :: [Symbol] Source #

PrimBytes Int32 Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields Int32 :: [Symbol] Source #

PrimBytes Int64 Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields Int64 :: [Symbol] Source #

PrimBytes Word Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields Word :: [Symbol] Source #

PrimBytes Word8 Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields Word8 :: [Symbol] Source #

PrimBytes Word16 Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields Word16 :: [Symbol] Source #

PrimBytes Word32 Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields Word32 :: [Symbol] Source #

PrimBytes Word64 Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields Word64 :: [Symbol] Source #

PrimBytes () Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields () :: [Symbol] Source #

Methods

getBytes :: () -> ByteArray# Source #

getBytesPinned :: () -> ByteArray# Source #

fromBytes :: Int# -> ByteArray# -> () Source #

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

writeBytes :: MutableByteArray# s -> Int# -> () -> State# s -> State# s Source #

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

writeAddr :: () -> Addr# -> State# s -> State# s Source #

byteSize :: () -> Int# Source #

byteAlign :: () -> Int# Source #

byteOffset :: () -> Int# Source #

byteFieldOffset :: forall (name :: Symbol). (Elem name (PrimFields ()), KnownSymbol name) => Proxy# name -> () -> Int# Source #

indexArray :: ByteArray# -> Int# -> () Source #

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

writeArray :: MutableByteArray# s -> Int# -> () -> State# s -> State# s Source #

PrimBytes CChar Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CChar :: [Symbol] Source #

PrimBytes CSChar Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CSChar :: [Symbol] Source #

PrimBytes CUChar Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CUChar :: [Symbol] Source #

PrimBytes CShort Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CShort :: [Symbol] Source #

PrimBytes CUShort Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CUShort :: [Symbol] Source #

PrimBytes CInt Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CInt :: [Symbol] Source #

PrimBytes CUInt Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CUInt :: [Symbol] Source #

PrimBytes CLong Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CLong :: [Symbol] Source #

PrimBytes CULong Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CULong :: [Symbol] Source #

PrimBytes CLLong Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CLLong :: [Symbol] Source #

PrimBytes CULLong Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CULLong :: [Symbol] Source #

PrimBytes CBool Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CBool :: [Symbol] Source #

PrimBytes CFloat Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CFloat :: [Symbol] Source #

PrimBytes CDouble Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CDouble :: [Symbol] Source #

PrimBytes CPtrdiff Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CPtrdiff :: [Symbol] Source #

PrimBytes CSize Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CSize :: [Symbol] Source #

PrimBytes CWchar Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CWchar :: [Symbol] Source #

PrimBytes CSigAtomic Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CSigAtomic :: [Symbol] Source #

PrimBytes CClock Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CClock :: [Symbol] Source #

PrimBytes CTime Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CTime :: [Symbol] Source #

PrimBytes CUSeconds Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CUSeconds :: [Symbol] Source #

PrimBytes CSUSeconds Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CSUSeconds :: [Symbol] Source #

PrimBytes CIntPtr Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CIntPtr :: [Symbol] Source #

PrimBytes CUIntPtr Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CUIntPtr :: [Symbol] Source #

PrimBytes CIntMax Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CIntMax :: [Symbol] Source #

PrimBytes CUIntMax Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields CUIntMax :: [Symbol] Source #

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

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (Maybe a) :: [Symbol] Source #

PrimBytes (StablePtr a) Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (StablePtr a) :: [Symbol] Source #

PrimBytes (Ptr a) Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (Ptr a) :: [Symbol] Source #

PrimBytes (FunPtr a) Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (FunPtr a) :: [Symbol] Source #

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

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (Tuple xs) :: [Symbol] Source #

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

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (Tuple xs) :: [Symbol] Source #

PrimBytes (Quater Double) Source # 
Instance details

Defined in Numeric.Quaternion.Internal.QDouble

Associated Types

type PrimFields (Quater Double) :: [Symbol] Source #

PrimBytes (Quater Float) Source # 
Instance details

Defined in Numeric.Quaternion.Internal.QFloat

Associated Types

type PrimFields (Quater Float) :: [Symbol] Source #

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

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (Either a b) :: [Symbol] Source #

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

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (a, b) :: [Symbol] Source #

Methods

getBytes :: (a, b) -> ByteArray# Source #

getBytesPinned :: (a, b) -> ByteArray# Source #

fromBytes :: Int# -> ByteArray# -> (a, b) Source #

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

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

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

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

byteSize :: (a, b) -> Int# Source #

byteAlign :: (a, b) -> Int# Source #

byteOffset :: (a, b) -> Int# Source #

byteFieldOffset :: forall (name :: Symbol). (Elem name (PrimFields (a, b)), KnownSymbol name) => Proxy# name -> (a, b) -> Int# Source #

indexArray :: ByteArray# -> Int# -> (a, b) Source #

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

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

PrimBytes (Idx x) Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (Idx x) :: [Symbol] Source #

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

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (Idxs xs) :: [Symbol] Source #

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

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (a, b, c) :: [Symbol] Source #

Methods

getBytes :: (a, b, c) -> ByteArray# Source #

getBytesPinned :: (a, b, c) -> ByteArray# Source #

fromBytes :: Int# -> ByteArray# -> (a, b, c) Source #

readBytes :: MutableByteArray# s -> Int# -> State# s -> (# State# s, (a, b, c) #) Source #

writeBytes :: MutableByteArray# s -> Int# -> (a, b, c) -> State# s -> State# s Source #

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

writeAddr :: (a, b, c) -> Addr# -> State# s -> State# s Source #

byteSize :: (a, b, c) -> Int# Source #

byteAlign :: (a, b, c) -> Int# Source #

byteOffset :: (a, b, c) -> Int# Source #

byteFieldOffset :: forall (name :: Symbol). (Elem name (PrimFields (a, b, c)), KnownSymbol name) => Proxy# name -> (a, b, c) -> Int# Source #

indexArray :: ByteArray# -> Int# -> (a, b, c) Source #

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

writeArray :: MutableByteArray# s -> Int# -> (a, b, c) -> State# s -> State# s Source #

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

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (a, b, c, d) :: [Symbol] Source #

Methods

getBytes :: (a, b, c, d) -> ByteArray# Source #

getBytesPinned :: (a, b, c, d) -> ByteArray# Source #

fromBytes :: Int# -> ByteArray# -> (a, b, c, d) Source #

readBytes :: MutableByteArray# s -> Int# -> State# s -> (# State# s, (a, b, c, d) #) Source #

writeBytes :: MutableByteArray# s -> Int# -> (a, b, c, d) -> State# s -> State# s Source #

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

writeAddr :: (a, b, c, d) -> Addr# -> State# s -> State# s Source #

byteSize :: (a, b, c, d) -> Int# Source #

byteAlign :: (a, b, c, d) -> Int# Source #

byteOffset :: (a, b, c, d) -> Int# Source #

byteFieldOffset :: forall (name :: Symbol). (Elem name (PrimFields (a, b, c, d)), KnownSymbol name) => Proxy# name -> (a, b, c, d) -> Int# Source #

indexArray :: ByteArray# -> Int# -> (a, b, c, d) Source #

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

writeArray :: MutableByteArray# s -> Int# -> (a, b, c, d) -> State# s -> State# s Source #

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

Defined in Numeric.DataFrame.Type

Associated Types

type PrimFields (DataFrame t ds) :: [Symbol] Source #

(Dimensions xns, KnownBackends ts (DimsBound xns), PrimBytes (DataFrame ts (DimsBound xns))) => PrimBytes (DataFrame ts xns) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Associated Types

type PrimFields (DataFrame ts xns) :: [Symbol] Source #

(PrimBytes a, PrimBytes b, PrimBytes c, PrimBytes d, PrimBytes e) => PrimBytes (a, b, c, d, e) Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (a, b, c, d, e) :: [Symbol] Source #

Methods

getBytes :: (a, b, c, d, e) -> ByteArray# Source #

getBytesPinned :: (a, b, c, d, e) -> ByteArray# Source #

fromBytes :: Int# -> ByteArray# -> (a, b, c, d, e) Source #

readBytes :: MutableByteArray# s -> Int# -> State# s -> (# State# s, (a, b, c, d, e) #) Source #

writeBytes :: MutableByteArray# s -> Int# -> (a, b, c, d, e) -> State# s -> State# s Source #

readAddr :: Addr# -> State# s -> (# State# s, (a, b, c, d, e) #) Source #

writeAddr :: (a, b, c, d, e) -> Addr# -> State# s -> State# s Source #

byteSize :: (a, b, c, d, e) -> Int# Source #

byteAlign :: (a, b, c, d, e) -> Int# Source #

byteOffset :: (a, b, c, d, e) -> Int# Source #

byteFieldOffset :: forall (name :: Symbol). (Elem name (PrimFields (a, b, c, d, e)), KnownSymbol name) => Proxy# name -> (a, b, c, d, e) -> Int# Source #

indexArray :: ByteArray# -> Int# -> (a, b, c, d, e) Source #

readArray :: MutableByteArray# s -> Int# -> State# s -> (# State# s, (a, b, c, d, e) #) Source #

writeArray :: MutableByteArray# s -> Int# -> (a, b, c, d, e) -> State# s -> State# s Source #

(PrimBytes a, PrimBytes b, PrimBytes c, PrimBytes d, PrimBytes e, PrimBytes f) => PrimBytes (a, b, c, d, e, f) Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (a, b, c, d, e, f) :: [Symbol] Source #

Methods

getBytes :: (a, b, c, d, e, f) -> ByteArray# Source #

getBytesPinned :: (a, b, c, d, e, f) -> ByteArray# Source #

fromBytes :: Int# -> ByteArray# -> (a, b, c, d, e, f) Source #

readBytes :: MutableByteArray# s -> Int# -> State# s -> (# State# s, (a, b, c, d, e, f) #) Source #

writeBytes :: MutableByteArray# s -> Int# -> (a, b, c, d, e, f) -> State# s -> State# s Source #

readAddr :: Addr# -> State# s -> (# State# s, (a, b, c, d, e, f) #) Source #

writeAddr :: (a, b, c, d, e, f) -> Addr# -> State# s -> State# s Source #

byteSize :: (a, b, c, d, e, f) -> Int# Source #

byteAlign :: (a, b, c, d, e, f) -> Int# Source #

byteOffset :: (a, b, c, d, e, f) -> Int# Source #

byteFieldOffset :: forall (name :: Symbol). (Elem name (PrimFields (a, b, c, d, e, f)), KnownSymbol name) => Proxy# name -> (a, b, c, d, e, f) -> Int# Source #

indexArray :: ByteArray# -> Int# -> (a, b, c, d, e, f) Source #

readArray :: MutableByteArray# s -> Int# -> State# s -> (# State# s, (a, b, c, d, e, f) #) Source #

writeArray :: MutableByteArray# s -> Int# -> (a, b, c, d, e, f) -> State# s -> State# s Source #

(PrimBytes a, PrimBytes b, PrimBytes c, PrimBytes d, PrimBytes e, PrimBytes f, PrimBytes g) => PrimBytes (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Numeric.PrimBytes

Associated Types

type PrimFields (a, b, c, d, e, f, g) :: [Symbol] Source #

Methods

getBytes :: (a, b, c, d, e, f, g) -> ByteArray# Source #

getBytesPinned :: (a, b, c, d, e, f, g) -> ByteArray# Source #

fromBytes :: Int# -> ByteArray# -> (a, b, c, d, e, f, g) Source #

readBytes :: MutableByteArray# s -> Int# -> State# s -> (# State# s, (a, b, c, d, e, f, g) #) Source #

writeBytes :: MutableByteArray# s -> Int# -> (a, b, c, d, e, f, g) -> State# s -> State# s Source #

readAddr :: Addr# -> State# s -> (# State# s, (a, b, c, d, e, f, g) #) Source #

writeAddr :: (a, b, c, d, e, f, g) -> Addr# -> State# s -> State# s Source #

byteSize :: (a, b, c, d, e, f, g) -> Int# Source #

byteAlign :: (a, b, c, d, e, f, g) -> Int# Source #

byteOffset :: (a, b, c, d, e, f, g) -> Int# Source #

byteFieldOffset :: forall (name :: Symbol). (Elem name (PrimFields (a, b, c, d, e, f, g)), KnownSymbol name) => Proxy# name -> (a, b, c, d, e, f, g) -> Int# Source #

indexArray :: ByteArray# -> Int# -> (a, b, c, d, e, f, g) Source #

readArray :: MutableByteArray# s -> Int# -> State# s -> (# State# s, (a, b, c, d, e, f, g) #) Source #

writeArray :: MutableByteArray# s -> Int# -> (a, b, c, d, e, f, g) -> State# s -> State# s Source #

bSizeOf :: (PrimBytes a, Num b) => a -> b Source #

A wrapper on byteSize

bAlignOf :: (PrimBytes a, Num b) => a -> b Source #

A wrapper on byteAlign

bFieldOffsetOf :: forall (name :: Symbol) (a :: Type) (b :: Type). (PrimBytes a, Elem name (PrimFields a), KnownSymbol name, Num b) => a -> b Source #

A wrapper on byteFieldOffset.

Storable API

Storable can be defined in terms of PrimBytes by doing something like the following for your data type:

  instance PrimBytes a => Storable a where
      sizeOf = bSizeOf
      alignment = bAlignOf
      peekElemOff = bPeekElemOff
      pokeElemOff = bPokeElemOff
      peekByteOff = bPeekByteOff
      pokeByteOff = bPokeByteOff
      peek = bPeek
      poke = bPoke

bPeekElemOff :: forall (a :: Type). PrimBytes a => Ptr a -> Int -> IO a Source #

Same as peekElemOff: peek an element a by the offset measured in byteSize a.

Note: the size of the element must be a multiple of its alignment for a correct operation of this function.

bPokeElemOff :: forall (a :: Type). PrimBytes a => Ptr a -> Int -> a -> IO () Source #

Same as pokeElemOff: poke an element a by the offset measured in byteSize a.

Note: the size of the element must be a multiple of its alignment for a correct operation of this function.

bPeekByteOff :: forall (a :: Type) (b :: Type). PrimBytes a => Ptr b -> Int -> IO a Source #

Same as peekByteOff: peek an element a by the offset measured in bytes.

Note: you'd better be sure the address is a multiple of the data alignment (peek).

bPokeByteOff :: forall (a :: Type) (b :: Type). PrimBytes a => Ptr b -> Int -> a -> IO () Source #

Same as pokeByteOff: poke an element a by the offset measured in bytes.

Note: you'd better be sure the address is a multiple of the data alignment (peek).

bPeek :: forall (a :: Type). PrimBytes a => Ptr a -> IO a Source #

Same as peek: read a data from a pointer.

Note: you'd better be sure the address is a multiple of the data alignment (peek).

bPoke :: forall (a :: Type). PrimBytes a => Ptr a -> a -> IO () Source #

Same as poke: write a data to a pointer.

Note: you'd better be sure the address is a multiple of the data alignment (peek).

Specialization tools

data PrimTag a where Source #

Find out which basic GHC type it is at runtime. It is used for DataFrame backend specialization: by matching a PrimTag a against its constructors, you can figure out a specific implementation of Backend a ds (e.g. whether this is a specialized float array, or a generic polymorphic array). For non-basic types it defaults to PTagOther.

Instances

Instances details
Show (PrimTag a) Source # 
Instance details

Defined in Numeric.PrimBytes

Methods

showsPrec :: Int -> PrimTag a -> ShowS #

show :: PrimTag a -> String #

showList :: [PrimTag a] -> ShowS #

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

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