sdp-0.2: Simple Data Processing
Copyright(c) Andrey Mulik 2019
LicenseBSD-style
Maintainerwork.a.mulik@gmail.com
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

SDP.Unboxed

Contents

Description

SDP.Unboxed provide service class Unboxed, that needed for SDP.Prim.SBytes-based structures.

Synopsis

Unboxed

class Eq e => Unboxed e where Source #

Unboxed is a layer between untyped raw data and parameterized unboxed data structures. Also it prevents direct interaction with primitives.

Minimal complete definition

(sizeof# | sizeof), (!#), (!>#), writeByteArray#, newUnboxed

Methods

sizeof :: e -> Int -> Int Source #

sizeof e n returns the length (in bytes) of primitive, where n - count of elements, e - type parameter.

sizeof# :: e -> Int# -> Int# Source #

sizeof# is unboxed sizeof.

(!#) :: ByteArray# -> Int# -> e Source #

Unsafe ByteArray# reader with overloaded result type.

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

Unsafe MutableByteArray# reader with overloaded result type.

writeByteArray# :: MutableByteArray# s -> Int# -> e -> State# s -> State# s Source #

Unsafe MutableByteArray# writer.

fillByteArray# :: MutableByteArray# s -> Int# -> e -> State# s -> State# s Source #

Procedure for filling the array with the default value (like calloc).

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

newUnboxed creates new MutableByteArray# of given count of elements. First argument used as type variable.

newUnboxed' :: e -> Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #

newUnboxed' is version of newUnboxed, that use first argument as initial value. May fail when trying to write error or undefined.

copyUnboxed# :: e -> ByteArray# -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #

copyUnboxed# e bytes# o1# mbytes# o2# n# unsafely writes elements from bytes# to mbytes#, where o1# and o2# - offsets (element count), n# - count of elements to copy.

copyUnboxedM# :: e -> MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #

copyUnboxedM# e msrc# o1# mbytes# o2# n# unsafely writes elements from msrc# to mbytes#, where o1# and o2# - offsets (element count), n# - count of elements to copy.

hashUnboxedWith :: e -> Int# -> Int# -> ByteArray# -> Int# -> Int# Source #

hashUnboxedWith e len bytes# salt returns bytes# FNV-1 hash, where off# and len# is offset and length (in elements).

Note: the standard definition of this function is written in Haskell using low-level functions, but this implementation mayn't be as efficient as the foreign procedure in the hashable package.

Instances

Instances details
Unboxed Bool Source # 
Instance details

Defined in SDP.Unboxed

Unboxed Char Source # 
Instance details

Defined in SDP.Unboxed

Unboxed Double Source # 
Instance details

Defined in SDP.Unboxed

Unboxed Float Source # 
Instance details

Defined in SDP.Unboxed

Unboxed Int Source # 
Instance details

Defined in SDP.Unboxed

Unboxed Int8 Source # 
Instance details

Defined in SDP.Unboxed

Unboxed Int16 Source # 
Instance details

Defined in SDP.Unboxed

Unboxed Int32 Source # 
Instance details

Defined in SDP.Unboxed

Unboxed Int64 Source # 
Instance details

Defined in SDP.Unboxed

Unboxed Word Source # 
Instance details

Defined in SDP.Unboxed

Unboxed Word8 Source # 
Instance details

Defined in SDP.Unboxed

Unboxed Word16 Source # 
Instance details

Defined in SDP.Unboxed

Unboxed Word32 Source # 
Instance details

Defined in SDP.Unboxed

Unboxed Word64 Source # 
Instance details

Defined in SDP.Unboxed

Unboxed () Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CChar Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CSChar Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CShort Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CUShort Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CInt Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CUInt Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CLong Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CULong Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CLLong Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CULLong Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CBool Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CFloat Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CDouble Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CPtrdiff Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CSize Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CWchar Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CSigAtomic Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CClock Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CTime Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CUSeconds Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CSUSeconds Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CIntPtr Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CUIntPtr Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CIntMax Source # 
Instance details

Defined in SDP.Unboxed

Unboxed CUIntMax Source # 
Instance details

Defined in SDP.Unboxed

Unboxed IntAs64 Source # 
Instance details

Defined in SDP.Unboxed.IntAs

Unboxed IntAs32 Source # 
Instance details

Defined in SDP.Unboxed.IntAs

Unboxed IntAs16 Source # 
Instance details

Defined in SDP.Unboxed.IntAs

Unboxed IntAs8 Source # 
Instance details

Defined in SDP.Unboxed.IntAs

Unboxed WordAs64 Source # 
Instance details

Defined in SDP.Unboxed.WordAs

Unboxed WordAs32 Source # 
Instance details

Defined in SDP.Unboxed.WordAs

Unboxed WordAs16 Source # 
Instance details

Defined in SDP.Unboxed.WordAs

Unboxed WordAs8 Source # 
Instance details

Defined in SDP.Unboxed.WordAs

(Unboxed a, Integral a) => Unboxed (Ratio a) Source # 
Instance details

Defined in SDP.Unboxed

Unboxed (StablePtr a) Source # 
Instance details

Defined in SDP.Unboxed

Unboxed (Ptr a) Source # 
Instance details

Defined in SDP.Unboxed

Unboxed (FunPtr a) Source # 
Instance details

Defined in SDP.Unboxed

(Unboxed a, Num a) => Unboxed (Complex a) Source # 
Instance details

Defined in SDP.Unboxed

cloneUnboxed# :: Unboxed e => e -> ByteArray# -> Int# -> Int# -> ByteArray# Source #

cloneUnboxed# e o# c# creates byte array with c# elements of same type as e beginning from o# elements.

cloneUnboxed1# :: Unboxed e => proxy e -> ByteArray# -> Int# -> Int# -> ByteArray# Source #

(* -> *) kind proxy version if cloneUnboxed#.

Proxy

psizeof :: Unboxed e => proxy e -> Int -> Int Source #

psizeof is Proxy sizeof.

pnewUnboxed :: Unboxed e => proxy e -> Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #

(* -> *) kind proxy version of newUnboxed.

pcopyUnboxed :: Unboxed e => proxy e -> ByteArray# -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #

(* -> *) kind proxy version if copyUnboxed#.

pcopyUnboxedM :: Unboxed e => proxy e -> MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #

Proxy version if copyUnboxedM#.

fromProxy :: proxy e -> e Source #

Returns undefined of suitable type.

pnewUnboxed1 :: Unboxed e => m (proxy e) -> Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #

(* -> * -> *) kind proxy version of newUnboxed.

pcopyUnboxed1 :: Unboxed e => m (proxy e) -> ByteArray# -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #

(* -> * -> *) kind proxy version if copyUnboxed#.

pcopyUnboxedM1 :: Unboxed e => m (proxy e) -> MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #

(* -> * -> *) kind proxy version if copyUnboxedM#.

fromProxy1 :: m (proxy e) -> e Source #

Returns undefined of suitable type.