| Copyright | (c) Andrey Mulik 2019 |
|---|---|
| License | BSD-style |
| Maintainer | work.a.mulik@gmail.com |
| Portability | portable |
| Safe Haskell | Trustworthy |
| Language | Haskell2010 |
SDP.Unboxed
Description
SDP.Unboxed provide service class Unboxed, that needed for
SDP.Prim.SBytes-based structures.
Synopsis
- class Eq e => Unboxed e where
- sizeof :: e -> Int -> Int
- sizeof# :: e -> Int# -> Int#
- (!#) :: ByteArray# -> Int# -> e
- (!>#) :: MutableByteArray# s -> Int# -> State# s -> (# State# s, e #)
- writeByteArray# :: MutableByteArray# s -> Int# -> e -> State# s -> State# s
- fillByteArray# :: MutableByteArray# s -> Int# -> e -> State# s -> State# s
- newUnboxed :: e -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
- newUnboxed' :: e -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
- copyUnboxed# :: e -> ByteArray# -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- copyUnboxedM# :: e -> MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- hashUnboxedWith :: e -> Int# -> Int# -> ByteArray# -> Int# -> Int#
- cloneUnboxed# :: Unboxed e => e -> ByteArray# -> Int# -> Int# -> ByteArray#
- cloneUnboxed1# :: Unboxed e => proxy e -> ByteArray# -> Int# -> Int# -> ByteArray#
- psizeof :: Unboxed e => proxy e -> Int -> Int
- pnewUnboxed :: Unboxed e => proxy e -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
- pcopyUnboxed :: Unboxed e => proxy e -> ByteArray# -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- pcopyUnboxedM :: Unboxed e => proxy e -> MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- fromProxy :: proxy e -> e
- pnewUnboxed1 :: Unboxed e => m (proxy e) -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
- pcopyUnboxed1 :: Unboxed e => m (proxy e) -> ByteArray# -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- pcopyUnboxedM1 :: Unboxed e => m (proxy e) -> MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- fromProxy1 :: m (proxy e) -> e
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 #
(!#) :: 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 #
unsafely writes elements
from copyUnboxed# e bytes# o1# mbytes# o2# n#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 #
unsafely writes elements
from copyUnboxedM# e msrc# o1# mbytes# o2# n#msrc# to mbytes#, where o1# and o2# - offsets (element
count), n# - count of elements to copy.
hashUnboxedWith :: e -> Int# -> Int# -> ByteArray# -> Int# -> Int# Source #
returns hashUnboxedWith e len bytes# saltbytes# 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
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
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#.
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.