License | BSD-style |
---|---|
Maintainer | Vincent Hanquez <vincent@snarc.org> |
Stability | stable |
Portability | Good |
Safe Haskell | None |
Language | Haskell2010 |
Simple and efficient byte array types
This module should be imported qualified.
- class ByteArrayAccess ba where
- class (Eq ba, Ord ba, Monoid ba, ByteArrayAccess ba) => ByteArray ba where
- data Bytes
- data ScrubbedBytes
- data MemView = MemView !(Ptr Word8) !Int
- memViewPlus :: MemView -> Int -> MemView
- data View bytes
- view :: ByteArrayAccess bytes => bytes -> Int -> Int -> View bytes
- takeView :: ByteArrayAccess bytes => bytes -> Int -> View bytes
- dropView :: ByteArrayAccess bytes => bytes -> Int -> View bytes
- alloc :: ByteArray ba => Int -> (Ptr p -> IO ()) -> IO ba
- allocAndFreeze :: ByteArray a => Int -> (Ptr p -> IO ()) -> a
- create :: ByteArray ba => Int -> (Ptr p -> IO ()) -> IO ba
- unsafeCreate :: ByteArray a => Int -> (Ptr p -> IO ()) -> a
- pack :: ByteArray a => [Word8] -> a
- unpack :: ByteArrayAccess a => a -> [Word8]
- uncons :: ByteArray a => a -> Maybe (Word8, a)
- empty :: ByteArray a => a
- singleton :: ByteArray a => Word8 -> a
- cons :: ByteArray a => Word8 -> a -> a
- snoc :: ByteArray a => a -> Word8 -> a
- null :: ByteArrayAccess a => a -> Bool
- replicate :: ByteArray ba => Int -> Word8 -> ba
- zero :: ByteArray ba => Int -> ba
- copy :: (ByteArrayAccess bs1, ByteArray bs2) => bs1 -> (Ptr p -> IO ()) -> IO bs2
- take :: ByteArray bs => Int -> bs -> bs
- drop :: ByteArray bs => Int -> bs -> bs
- span :: ByteArray bs => (Word8 -> Bool) -> bs -> (bs, bs)
- convert :: (ByteArrayAccess bin, ByteArray bout) => bin -> bout
- copyRet :: (ByteArrayAccess bs1, ByteArray bs2) => bs1 -> (Ptr p -> IO a) -> IO (a, bs2)
- copyAndFreeze :: (ByteArrayAccess bs1, ByteArray bs2) => bs1 -> (Ptr p -> IO ()) -> bs2
- splitAt :: ByteArray bs => Int -> bs -> (bs, bs)
- xor :: (ByteArrayAccess a, ByteArrayAccess b, ByteArray c) => a -> b -> c
- index :: ByteArrayAccess a => a -> Int -> Word8
- eq :: (ByteArrayAccess bs1, ByteArrayAccess bs2) => bs1 -> bs2 -> Bool
- constEq :: (ByteArrayAccess bs1, ByteArrayAccess bs2) => bs1 -> bs2 -> Bool
- any :: ByteArrayAccess ba => (Word8 -> Bool) -> ba -> Bool
- all :: ByteArrayAccess ba => (Word8 -> Bool) -> ba -> Bool
- append :: ByteArray bs => bs -> bs -> bs
- concat :: (ByteArrayAccess bin, ByteArray bout) => [bin] -> bout
ByteArray Classes
class ByteArrayAccess ba where Source
Class to Access size properties and data of a ByteArray
Return the length in bytes of a bytearray
withByteArray :: ba -> (Ptr p -> IO a) -> IO a Source
Allow to use using a pointer
class (Eq ba, Ord ba, Monoid ba, ByteArrayAccess ba) => ByteArray ba where Source
Class to allocate new ByteArray of specific size
ByteArray built-in types
Simplest Byte Array
data ScrubbedBytes Source
ScrubbedBytes is a memory chunk which have the properties of:
- Being scrubbed after its goes out of scope.
- A Show instance that doesn't actually show any content
- A Eq instance that is constant time
A simple abstraction to a piece of memory.
Do beware that garbage collection related to piece of memory could be triggered before this is used.
Only use with the appropriate handler has been used (e.g. withForeignPtr on ForeignPtr)
memViewPlus :: MemView -> Int -> MemView Source
Increase the memory view while reducing the size of the window
this is useful as an abtraction to represent the current offset in a buffer, and the remaining bytes left.
a view on a given bytes
Equality test in constant time
ByteArrayAccess bytes => Eq (View bytes) Source | |
ByteArrayAccess bytes => Ord (View bytes) Source | |
ByteArrayAccess bytes => Show (View bytes) Source | |
ByteArrayAccess bytes => ByteArrayAccess (View bytes) Source |
:: ByteArrayAccess bytes | |
=> bytes | the byte array we put a view on |
-> Int | the offset to start the byte array on |
-> Int | the size of the view |
-> View bytes |
create a view on a given bytearray
This function update the offset and the size in order to guarantee:
- offset >= 0
- size >= 0
- offset < length
- size =< length - offset
:: ByteArrayAccess bytes | |
=> bytes | byte aray |
-> Int | size of the view |
-> View bytes |
create a view from the given bytearray
:: ByteArrayAccess bytes | |
=> bytes | byte array |
-> Int | the number of bytes do dropped before creating the view |
-> View bytes |
create a view from the given byte array starting after having dropped the fist n bytes
ByteArray methods
alloc :: ByteArray ba => Int -> (Ptr p -> IO ()) -> IO ba Source
Allocate a new bytearray of specific size, and run the initializer on this memory
allocAndFreeze :: ByteArray a => Int -> (Ptr p -> IO ()) -> a Source
similar to alloc
but hide the allocation and initializer in a pure context
create :: ByteArray ba => Int -> (Ptr p -> IO ()) -> IO ba Source
Allocate a new bytearray of specific size, and run the initializer on this memory
unsafeCreate :: ByteArray a => Int -> (Ptr p -> IO ()) -> a Source
similar to create
but hide the allocation and initializer in a pure context
unpack :: ByteArrayAccess a => a -> [Word8] Source
Un-pack a bytearray into a list of bytes
uncons :: ByteArray a => a -> Maybe (Word8, a) Source
returns the first byte, and the remaining bytearray if the bytearray is not null
null :: ByteArrayAccess a => a -> Bool Source
Check if a byte array is empty
replicate :: ByteArray ba => Int -> Word8 -> ba Source
Create a bytearray of a specific size containing a repeated byte value
copy :: (ByteArrayAccess bs1, ByteArray bs2) => bs1 -> (Ptr p -> IO ()) -> IO bs2 Source
Duplicate a bytearray into another bytearray, and run an initializer on it
span :: ByteArray bs => (Word8 -> Bool) -> bs -> (bs, bs) Source
Split a bytearray at the point where pred
becomes invalid
convert :: (ByteArrayAccess bin, ByteArray bout) => bin -> bout Source
Convert a bytearray to another type of bytearray
copyRet :: (ByteArrayAccess bs1, ByteArray bs2) => 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 :: (ByteArrayAccess bs1, ByteArray bs2) => bs1 -> (Ptr p -> IO ()) -> bs2 Source
Similiar to copy
but expect the resulting bytearray in a pure context
splitAt :: ByteArray bs => Int -> bs -> (bs, bs) Source
Split a bytearray at a specific length in two bytearray
xor :: (ByteArrayAccess a, ByteArrayAccess b, ByteArray c) => 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 :: ByteArrayAccess a => a -> Int -> Word8 Source
return a specific byte indexed by a number from 0 in a bytearray
unsafe, no bound checking are done
eq :: (ByteArrayAccess bs1, ByteArrayAccess bs2) => bs1 -> bs2 -> Bool Source
Check if two bytearray are equals
This is not constant time, as soon some byte differs the function will
returns. use constEq
in sensitive context where timing matters.
constEq :: (ByteArrayAccess bs1, ByteArrayAccess bs2) => bs1 -> bs2 -> Bool Source
A constant time equality test for 2 ByteArrayAccess values.
If values are of 2 different sizes, the function will abort early without comparing any bytes.
compared to == , this function will go over all the bytes present before yielding a result even when knowing the overall result early in the processing.
any :: ByteArrayAccess ba => (Word8 -> Bool) -> ba -> Bool Source
Check if any element of a byte array satisfies a predicate
all :: ByteArrayAccess ba => (Word8 -> Bool) -> ba -> Bool Source
Check if all elements of a byte array satisfy a predicate
concat :: (ByteArrayAccess bin, ByteArray bout) => [bin] -> bout Source
Concatenate bytearray into a larger bytearray