Copyright | (c) Andrey Mulik 2019 |
---|---|
License | BSD-style |
Maintainer | work.a.mulik@gmail.com |
Portability | non-portable (GHC extensions) |
Safe Haskell | Trustworthy |
Language | Haskell2010 |
SDP.Prim.SBytes provides strict unboxed array pseudo-primitive types
SBytes#
, STBytes#
and IOBytes#
.
Synopsis
- module SDP.IndexedM
- module SDP.Unboxed
- module SDP.SortM
- module SDP.Sort
- newtype MIOBytes# (io :: Type -> Type) e = MIOBytes# (STBytes# RealWorld e)
- type IOBytes# = MIOBytes# IO
- data STBytes# s e
- data SBytes# e
- fromSBytes# :: Unboxed e => SBytes# e -> ByteArray#
- packSBytes# :: Unboxed e => Int -> ByteArray# -> SBytes# e
- unpackSBytes# :: Unboxed e => SBytes# e -> ByteArray#
- offsetSBytes# :: Unboxed e => SBytes# e -> Int
- fromSTBytes# :: Unboxed e => STBytes# s e -> State# s -> (# State# s, MutableByteArray# s #)
- packSTBytes# :: Unboxed e => Int -> MutableByteArray# s -> STBytes# s e
- unpackSTBytes# :: Unboxed e => STBytes# s e -> MutableByteArray# s
- offsetSTBytes# :: Unboxed e => STBytes# s e -> Int#
- unsafeCoerceSBytes# :: (Unboxed a, Unboxed b) => SBytes# a -> SBytes# b
- unsafeCoerceSTBytes# :: (Unboxed a, Unboxed b) => STBytes# s a -> STBytes# s b
- unsafeSBytesToPtr# :: Unboxed e => SBytes# e -> IO (Int, Ptr e)
- unsafePtrToSBytes# :: Unboxed e => (Int, Ptr e) -> IO (SBytes# e)
- hashSBytesWith# :: Unboxed e => Int -> SBytes# e -> Int
Exports
module SDP.IndexedM
module SDP.Unboxed
module SDP.SortM
module SDP.Sort
Preudo-primitive types
newtype MIOBytes# (io :: Type -> Type) e Source #
Instances
Instances
SBytes#
is immutable pseudo-primitive Int
-indexed strict unboxed array
type.
SBytes#
isn't real Haskell primitive (like GHC.Exts types) but for
reliability and stability, I made it inaccessible to direct work.
Instances
Unpack unboxed arrays
fromSBytes# :: Unboxed e => SBytes# e -> ByteArray# Source #
fromSBytes#
returns new ByteArray#
.
packSBytes# :: Unboxed e => Int -> ByteArray# -> SBytes# e Source #
packSBytes#
creates new SBytes#
from sized ByteArray#
.
unpackSBytes# :: Unboxed e => SBytes# e -> ByteArray# Source #
unpackSBytes#
returns ByteArray#
field of SBytes#
.
offsetSBytes# :: Unboxed e => SBytes# e -> Int Source #
offsetSBytes#
returns SBytes#
offset in elements.
fromSTBytes# :: Unboxed e => STBytes# s e -> State# s -> (# State# s, MutableByteArray# s #) Source #
fromSTBytes#
returns new MutableByteArray#
.
packSTBytes# :: Unboxed e => Int -> MutableByteArray# s -> STBytes# s e Source #
packSTBytes#
creates new STBytes#
from sized MutableByteArray#
.
unpackSTBytes# :: Unboxed e => STBytes# s e -> MutableByteArray# s Source #
unpackSTBytes#
returns MutableByteArray#
field of STBytes#
.
offsetSTBytes# :: Unboxed e => STBytes# s e -> Int# Source #
offsetSTBytes#
returns STBytes#
offset in bytes.
Coerce unboxed arrays
unsafeCoerceSBytes# :: (Unboxed a, Unboxed b) => SBytes# a -> SBytes# b Source #
unsafeCoerceSBytes#
is unsafe low-lowel coerce of an array with recounting
the number of elements and offset (with possible rounding).
unsafeCoerceSTBytes# :: (Unboxed a, Unboxed b) => STBytes# s a -> STBytes# s b Source #
unsafeCoerceSTBytes#
is unsafe low-lowel coerce of an mutable array with
recounting the number of elements and offset (with possible rounding).
Unsafe pointer conversions
unsafeSBytesToPtr# :: Unboxed e => SBytes# e -> IO (Int, Ptr e) Source #
byte-wise stores unsafeSBytesToPtr#
esSBytes#
content to Ptr
. Returns
the number of overwritten elements and a pointer to psizeof es (sizeOf es)
bytes of allocated memory.
unsafePtrToSBytes# :: Unboxed e => (Int, Ptr e) -> IO (SBytes# e) Source #
byte-wise stores unsafePtrToSBytes#
n ptrn
elements of Ptr
ptr
to
SBytes#
.
Hash
hashSBytesWith# :: Unboxed e => Int -> SBytes# e -> Int Source #
Calculate hash SBytes#
using hashUnboxedWith
.