License | BSD-style |
---|---|
Maintainer | Nicolas Di Prima <nicolas@primetype.co.uk> |
Stability | stable |
Portability | Good |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class (ByteArrayAccess c, KnownNat n) => ByteArrayN (n :: Nat) c | c -> n where
- data SizedByteArray (n :: Nat) ba
- unSizedByteArray :: SizedByteArray n ba -> ba
- sizedByteArray :: forall n ba. (KnownNat n, ByteArrayAccess ba) => ba -> Maybe (SizedByteArray n ba)
- unsafeSizedByteArray :: forall n ba. (ByteArrayAccess ba, KnownNat n) => ba -> SizedByteArray n ba
- alloc :: forall n ba p. (ByteArrayN n ba, KnownNat n) => (Ptr p -> IO ()) -> IO ba
- create :: forall n ba p. (ByteArrayN n ba, KnownNat n) => (Ptr p -> IO ()) -> IO ba
- allocAndFreeze :: forall n ba p. (ByteArrayN n ba, KnownNat n) => (Ptr p -> IO ()) -> ba
- unsafeCreate :: forall n ba p. (ByteArrayN n ba, KnownNat n) => (Ptr p -> IO ()) -> ba
- inlineUnsafeCreate :: forall n ba p. (ByteArrayN n ba, KnownNat n) => (Ptr p -> IO ()) -> ba
- empty :: forall ba. ByteArrayN 0 ba => ba
- pack :: forall n ba. (ByteArrayN n ba, KnownNat n) => ListN n Word8 -> ba
- unpack :: forall n ba. (ByteArrayN n ba, KnownNat n, NatWithinBound Int n, ByteArrayAccess ba) => ba -> ListN n Word8
- cons :: forall ni no bi bo. (ByteArrayN ni bi, ByteArrayN no bo, ByteArrayAccess bi, KnownNat ni, KnownNat no, (ni + 1) ~ no) => Word8 -> bi -> bo
- snoc :: forall bi bo ni no. (ByteArrayN ni bi, ByteArrayN no bo, ByteArrayAccess bi, KnownNat ni, KnownNat no, (ni + 1) ~ no) => bi -> Word8 -> bo
- xor :: forall n a b c. (ByteArrayN n a, ByteArrayN n b, ByteArrayN n c, ByteArrayAccess a, ByteArrayAccess b, KnownNat n) => a -> b -> c
- index :: forall n na ba. (ByteArrayN na ba, ByteArrayAccess ba, KnownNat na, KnownNat n, n <= na) => ba -> Proxy n -> Word8
- splitAt :: forall nblhs nbi nbrhs bi blhs brhs. (ByteArrayN nbi bi, ByteArrayN nblhs blhs, ByteArrayN nbrhs brhs, ByteArrayAccess bi, KnownNat nbi, KnownNat nblhs, KnownNat nbrhs, nblhs <= nbi, (nbrhs + nblhs) ~ nbi) => bi -> (blhs, brhs)
- take :: forall nbo nbi bi bo. (ByteArrayN nbi bi, ByteArrayN nbo bo, ByteArrayAccess bi, KnownNat nbi, KnownNat nbo, nbo <= nbi) => bi -> bo
- drop :: forall n nbi nbo bi bo. (ByteArrayN nbi bi, ByteArrayN nbo bo, ByteArrayAccess bi, KnownNat n, KnownNat nbi, KnownNat nbo, (nbo + n) ~ nbi) => Proxy n -> bi -> bo
- append :: forall nblhs nbrhs nbout blhs brhs bout. (ByteArrayN nblhs blhs, ByteArrayN nbrhs brhs, ByteArrayN nbout bout, ByteArrayAccess blhs, ByteArrayAccess brhs, KnownNat nblhs, KnownNat nbrhs, KnownNat nbout, (nbrhs + nblhs) ~ nbout) => blhs -> brhs -> bout
- copy :: forall n bs1 bs2 p. (ByteArrayN n bs1, ByteArrayN n bs2, ByteArrayAccess bs1, KnownNat n) => bs1 -> (Ptr p -> IO ()) -> IO bs2
- copyRet :: forall n bs1 bs2 p a. (ByteArrayN n bs1, ByteArrayN n bs2, ByteArrayAccess bs1, KnownNat n) => bs1 -> (Ptr p -> IO a) -> IO (a, bs2)
- copyAndFreeze :: forall n bs1 bs2 p. (ByteArrayN n bs1, ByteArrayN n bs2, ByteArrayAccess bs1, KnownNat n) => bs1 -> (Ptr p -> IO ()) -> bs2
- replicate :: forall n ba. (ByteArrayN n ba, KnownNat n) => Word8 -> ba
- zero :: forall n ba. (ByteArrayN n ba, KnownNat n) => ba
- convert :: forall n bin bout. (ByteArrayN n bin, ByteArrayN n bout, KnownNat n) => bin -> bout
- fromByteArrayAccess :: forall n bin bout. (ByteArrayAccess bin, ByteArrayN n bout, KnownNat n) => bin -> Maybe bout
- unsafeFromByteArrayAccess :: forall n bin bout. (ByteArrayAccess bin, ByteArrayN n bout, KnownNat n) => bin -> bout
Documentation
class (ByteArrayAccess c, KnownNat n) => ByteArrayN (n :: Nat) c | c -> n where Source #
Type class to emulate exactly the behaviour of ByteArray
but with
a known length at compile time
allocRet :: forall p a. Proxy n -> (Ptr p -> IO a) -> IO (a, c) Source #
just like allocRet
but with the size at the type level
Instances
(ByteArrayAccess (BlockN n ty), PrimType ty, KnownNat n, Countable ty n, KnownNat nbytes, nbytes ~ (PrimSize ty * n)) => ByteArrayN nbytes (BlockN n ty) Source # | |
(KnownNat n, ByteArray ba) => ByteArrayN n (SizedByteArray n ba) Source # | |
Defined in Data.ByteArray.Sized |
data SizedByteArray (n :: Nat) ba Source #
Wrapper around any collection type with the size as type parameter
Instances
unSizedByteArray :: SizedByteArray n ba -> ba Source #
sizedByteArray :: forall n ba. (KnownNat n, ByteArrayAccess ba) => ba -> Maybe (SizedByteArray n ba) Source #
create a SizedByteArray
from the given ByteArrayAccess
if the
size is the same as the target size.
unsafeSizedByteArray :: forall n ba. (ByteArrayAccess ba, KnownNat n) => ba -> SizedByteArray n ba Source #
just like the sizedByteArray
function but throw an exception if
the size is invalid.
ByteArrayN operators
alloc :: forall n ba p. (ByteArrayN n ba, KnownNat n) => (Ptr p -> IO ()) -> IO ba Source #
Allocate a new bytearray of specific size, and run the initializer on this memory
create :: forall n ba p. (ByteArrayN n ba, KnownNat n) => (Ptr p -> IO ()) -> IO ba Source #
Allocate a new bytearray of specific size, and run the initializer on this memory
allocAndFreeze :: forall n ba p. (ByteArrayN n ba, KnownNat n) => (Ptr p -> IO ()) -> ba Source #
similar to allocN
but hide the allocation and initializer in a pure context
unsafeCreate :: forall n ba p. (ByteArrayN n ba, KnownNat n) => (Ptr p -> IO ()) -> ba Source #
similar to createN
but hide the allocation and initializer in a pure context
inlineUnsafeCreate :: forall n ba p. (ByteArrayN n ba, KnownNat n) => (Ptr p -> IO ()) -> ba Source #
empty :: forall ba. ByteArrayN 0 ba => ba Source #
Create an empty byte array
pack :: forall n ba. (ByteArrayN n ba, KnownNat n) => ListN n Word8 -> ba Source #
Pack a list of bytes into a bytearray
unpack :: forall n ba. (ByteArrayN n ba, KnownNat n, NatWithinBound Int n, ByteArrayAccess ba) => ba -> ListN n Word8 Source #
Un-pack a bytearray into a list of bytes
cons :: forall ni no bi bo. (ByteArrayN ni bi, ByteArrayN no bo, ByteArrayAccess bi, KnownNat ni, KnownNat no, (ni + 1) ~ no) => Word8 -> bi -> bo Source #
prepend a single byte to a byte array
snoc :: forall bi bo ni no. (ByteArrayN ni bi, ByteArrayN no bo, ByteArrayAccess bi, KnownNat ni, KnownNat no, (ni + 1) ~ no) => bi -> Word8 -> bo Source #
append a single byte to a byte array
xor :: forall n a b c. (ByteArrayN n a, ByteArrayN n b, ByteArrayN n c, ByteArrayAccess a, ByteArrayAccess b, KnownNat n) => a -> b -> c Source #
Create a xor of bytes between a and b.
the returns byte array is the size of the smallest input.
index :: forall n na ba. (ByteArrayN na ba, ByteArrayAccess ba, KnownNat na, KnownNat n, n <= na) => ba -> Proxy n -> Word8 Source #
return a specific byte indexed by a number from 0 in a bytearray
unsafe, no bound checking are done
splitAt :: forall nblhs nbi nbrhs bi blhs brhs. (ByteArrayN nbi bi, ByteArrayN nblhs blhs, ByteArrayN nbrhs brhs, ByteArrayAccess bi, KnownNat nbi, KnownNat nblhs, KnownNat nbrhs, nblhs <= nbi, (nbrhs + nblhs) ~ nbi) => bi -> (blhs, brhs) Source #
Split a bytearray at a specific length in two bytearray
take :: forall nbo nbi bi bo. (ByteArrayN nbi bi, ByteArrayN nbo bo, ByteArrayAccess bi, KnownNat nbi, KnownNat nbo, nbo <= nbi) => bi -> bo Source #
Take the first n
byte of a bytearray
drop :: forall n nbi nbo bi bo. (ByteArrayN nbi bi, ByteArrayN nbo bo, ByteArrayAccess bi, KnownNat n, KnownNat nbi, KnownNat nbo, (nbo + n) ~ nbi) => Proxy n -> bi -> bo Source #
drop the first n
byte of a bytearray
append :: forall nblhs nbrhs nbout blhs brhs bout. (ByteArrayN nblhs blhs, ByteArrayN nbrhs brhs, ByteArrayN nbout bout, ByteArrayAccess blhs, ByteArrayAccess brhs, KnownNat nblhs, KnownNat nbrhs, KnownNat nbout, (nbrhs + nblhs) ~ nbout) => blhs -> brhs -> bout Source #
append one bytearray to the other
copy :: forall n bs1 bs2 p. (ByteArrayN n bs1, ByteArrayN n bs2, ByteArrayAccess bs1, KnownNat n) => bs1 -> (Ptr p -> IO ()) -> IO bs2 Source #
Duplicate a bytearray into another bytearray, and run an initializer on it
copyRet :: forall n bs1 bs2 p a. (ByteArrayN n bs1, ByteArrayN n bs2, ByteArrayAccess bs1, KnownNat n) => bs1 -> (Ptr p -> IO a) -> IO (a, bs2) Source #
Similar to copy
but also provide a way to return a value from the initializer
copyAndFreeze :: forall n bs1 bs2 p. (ByteArrayN n bs1, ByteArrayN n bs2, ByteArrayAccess bs1, KnownNat n) => bs1 -> (Ptr p -> IO ()) -> bs2 Source #
Similiar to copy
but expect the resulting bytearray in a pure context
replicate :: forall n ba. (ByteArrayN n ba, KnownNat n) => Word8 -> ba Source #
Create a bytearray of a specific size containing a repeated byte value
zero :: forall n ba. (ByteArrayN n ba, KnownNat n) => ba Source #
Create a bytearray of a specific size initialized to 0
convert :: forall n bin bout. (ByteArrayN n bin, ByteArrayN n bout, KnownNat n) => bin -> bout Source #
Convert a bytearray to another type of bytearray
fromByteArrayAccess :: forall n bin bout. (ByteArrayAccess bin, ByteArrayN n bout, KnownNat n) => bin -> Maybe bout Source #
Convert a ByteArrayAccess to another type of bytearray
This function returns nothing if the size is not compatible
unsafeFromByteArrayAccess :: forall n bin bout. (ByteArrayAccess bin, ByteArrayN n bout, KnownNat n) => bin -> bout Source #
Convert a ByteArrayAccess to another type of bytearray