| Copyright | (c) Andrey Mulik 2019-2021 |
|---|---|
| License | BSD-style |
| Maintainer | work.a.mulik@gmail.com |
| Portability | non-portable (GHC extensions) |
| 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#
- cloneUnboxedM# :: Unboxed e => e -> MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
- thawUnboxed# :: Unboxed e => e -> ByteArray# -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
- freezeUnboxed# :: Unboxed e => e -> MutableByteArray# s -> Int# -> State# s -> (# State# s, ByteArray# #)
- fromProxy :: proxy e -> e
- psizeof# :: Unboxed e => proxy e -> Int# -> Int#
- 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
- pcloneUnboxed :: Unboxed e => proxy e -> ByteArray# -> Int# -> Int# -> ByteArray#
- pcloneUnboxedM :: Unboxed e => proxy e -> MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
- pthawUnboxed :: Unboxed e => proxy e -> ByteArray# -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
- pfreezeUnboxed :: Unboxed e => proxy e -> MutableByteArray# s -> Int# -> State# s -> (# State# s, ByteArray# #)
- fromProxy1 :: m (proxy e) -> e
- pnewUnboxed1 :: Unboxed e => p (proxy e) -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
- pcloneUnboxed1 :: Unboxed e => p (proxy e) -> ByteArray# -> Int# -> Int# -> ByteArray#
- pcopyUnboxed1 :: Unboxed e => p (proxy e) -> ByteArray# -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- pcopyUnboxedM1 :: Unboxed e => p (proxy e) -> MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
- cloneUnboxed1# :: Unboxed e => proxy e -> ByteArray# -> Int# -> Int# -> ByteArray#
- pcloneUnboxedM1 :: Unboxed e => p (proxy e) -> MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
- data Wrap = Wrap {
- unwrap :: ByteArray#
- lzero# :: Wrap
- single# :: Unboxed e => e -> ByteArray#
- fromList# :: Unboxed e => [e] -> ByteArray#
- fromFoldable# :: (Foldable f, Unboxed e) => f e -> (# Int, ByteArray# #)
- fromListN# :: Unboxed e => Int# -> [e] -> ByteArray#
- newLinear# :: Unboxed e => [e] -> State# s -> (# State# s, MutableByteArray# s #)
- newLinearN# :: Unboxed e => Int# -> [e] -> State# s -> (# State# s, MutableByteArray# s #)
- fromFoldableM# :: (Foldable f, Unboxed e) => f e -> State# s -> (# State# s, Int, MutableByteArray# s #)
- concat# :: Unboxed e => e -> ByteArray# -> Int# -> Int# -> ByteArray# -> Int# -> Int# -> State# s -> (# State# s, Int#, MutableByteArray# s #)
- pconcat :: Unboxed e => proxy e -> ByteArray# -> Int# -> Int# -> ByteArray# -> Int# -> Int# -> State# s -> (# State# s, Int#, MutableByteArray# s #)
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 #
cloneUnboxedM# :: Unboxed e => e -> MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #
thawUnboxed# :: Unboxed e => e -> ByteArray# -> Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #
creates new thawUnboxed# e bytessizeof bytes length
MutableByteArray# and copy bytes# to it.
Since: 0.2.1
freezeUnboxed# :: Unboxed e => e -> MutableByteArray# s -> Int# -> State# s -> (# State# s, ByteArray# #) Source #
creates new freezeUnboxed# e mbytessizeof bytes length
ByteArray# and copy mbytes# to it.
Since: 0.2.1
Kind (Type -> Type) proxies
pnewUnboxed :: Unboxed e => proxy e -> Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #
Kind (Type -> Type) proxy version of newUnboxed.
Since: 0.2
pcopyUnboxed :: Unboxed e => proxy e -> ByteArray# -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
Kind (Type -> Type) proxy version if copyUnboxed#.
Since: 0.2
pcopyUnboxedM :: Unboxed e => proxy e -> MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
Kind (Type -> Type) proxy version if copyUnboxedM#.
Since: 0.2
pcloneUnboxed :: Unboxed e => proxy e -> ByteArray# -> Int# -> Int# -> ByteArray# Source #
Same as sdp-0.2 cloneUnboxed1#. Use only if you don't need sdp-0.2
compatibility.
Since: 0.2.1
pcloneUnboxedM :: Unboxed e => proxy e -> MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #
Kind (Type -> Type) proxy version of cloneUnboxed#.
Since: 0.2.1
pthawUnboxed :: Unboxed e => proxy e -> ByteArray# -> Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #
Kind (Type -> Type) proxy version of thawUnboxed#.
Since: 0.2.1
pfreezeUnboxed :: Unboxed e => proxy e -> MutableByteArray# s -> Int# -> State# s -> (# State# s, ByteArray# #) Source #
Kind (Type -> Type) proxy version of pfreezeUnboxed.
Since: 0.2.1
Kind (Type -> Type -> Type) proxies
fromProxy1 :: m (proxy e) -> e Source #
Returns undefined of suitable type.
pnewUnboxed1 :: Unboxed e => p (proxy e) -> Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #
Kind (Type -> Type -> Type) proxy version of newUnboxed.
Since: 0.2
pcloneUnboxed1 :: Unboxed e => p (proxy e) -> ByteArray# -> Int# -> Int# -> ByteArray# Source #
Kind (Type -> Type -> Type) proxy version of cloneUnboxed#.
Since: 0.2.1
pcopyUnboxed1 :: Unboxed e => p (proxy e) -> ByteArray# -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
Kind (Type -> Type -> Type) proxy version of copyUnboxed#.
Since: 0.2
pcopyUnboxedM1 :: Unboxed e => p (proxy e) -> MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s Source #
Kind (Type -> Type -> Type) proxy version of copyUnboxedM#.
Since: 0.2.1
cloneUnboxed1# :: Unboxed e => proxy e -> ByteArray# -> Int# -> Int# -> ByteArray# Source #
Kind (Type -> Type) proxy version of cloneUnboxed#.
Since: 0.2
pcloneUnboxedM1 :: Unboxed e => p (proxy e) -> MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s, MutableByteArray# s #) Source #
Kind (Type -> Type -> Type) proxy version of cloneUnboxed#.
Since: 0.2.1
Wrapped empty ByteArray#.
Since: 0.2.1
single# :: Unboxed e => e -> ByteArray# Source #
ByteArray# singleton.
Since: 0.2.1
fromList# :: Unboxed e => [e] -> ByteArray# Source #
Create immutable Unboxed array from given list.
Since: 0.2.1
fromFoldable# :: (Foldable f, Unboxed e) => f e -> (# Int, ByteArray# #) Source #
fromListN# :: Unboxed e => Int# -> [e] -> ByteArray# Source #
Create immutable Unboxed array from known size list.
Since: 0.2.1
newLinear# :: Unboxed e => [e] -> State# s -> (# State# s, MutableByteArray# s #) Source #
Create mutable Unboxed array from given list.
Since: 0.2.1
newLinearN# :: Unboxed e => Int# -> [e] -> State# s -> (# State# s, MutableByteArray# s #) Source #
Create mutable Unboxed array from known size list.
Since: 0.2.1
fromFoldableM# :: (Foldable f, Unboxed e) => f e -> State# s -> (# State# s, Int, MutableByteArray# s #) Source #
concat# :: Unboxed e => e -> ByteArray# -> Int# -> Int# -> ByteArray# -> Int# -> Int# -> State# s -> (# State# s, Int#, MutableByteArray# s #) Source #
Concatenation of two Unboxed arrays.
Since: 0.2.1
pconcat :: Unboxed e => proxy e -> ByteArray# -> Int# -> Int# -> ByteArray# -> Int# -> Int# -> State# s -> (# State# s, Int#, MutableByteArray# s #) Source #
Proxy concatenation of two byte arrays representing Unboxed structures.