memory-0.14.18: memory and related abstraction stuff

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilitystable
PortabilityGood
Safe HaskellNone
LanguageHaskell2010

Data.ByteArray

Contents

Description

Simple and efficient byte array types

This module should be imported qualified.

Synopsis

ByteArray Classes

class ByteArrayAccess ba where Source #

Class to Access size properties and data of a ByteArray

Minimal complete definition

length, withByteArray

Methods

length :: ba -> Int Source #

Return the length in bytes of a bytearray

withByteArray :: ba -> (Ptr p -> IO a) -> IO a Source #

Allow to use using a pointer

copyByteArrayToPtr :: ba -> Ptr p -> IO () Source #

Copy the data of a bytearray to a ptr

Instances
ByteArrayAccess String Source # 
Instance details

Defined in Data.ByteArray.Types

Methods

length :: String -> Int Source #

withByteArray :: String -> (Ptr p -> IO a) -> IO a Source #

copyByteArrayToPtr :: String -> Ptr p -> IO () Source #

ByteArrayAccess ByteString Source # 
Instance details

Defined in Data.ByteArray.Types

ByteArrayAccess MemView Source # 
Instance details

Defined in Data.ByteArray.MemView

ByteArrayAccess ScrubbedBytes Source # 
Instance details

Defined in Data.ByteArray.ScrubbedBytes

ByteArrayAccess Bytes Source # 
Instance details

Defined in Data.ByteArray.Bytes

Methods

length :: Bytes -> Int Source #

withByteArray :: Bytes -> (Ptr p -> IO a) -> IO a Source #

copyByteArrayToPtr :: Bytes -> Ptr p -> IO () Source #

PrimType ty => ByteArrayAccess (UArray ty) Source # 
Instance details

Defined in Data.ByteArray.Types

Methods

length :: UArray ty -> Int Source #

withByteArray :: UArray ty -> (Ptr p -> IO a) -> IO a Source #

copyByteArrayToPtr :: UArray ty -> Ptr p -> IO () Source #

PrimType ty => ByteArrayAccess (Block ty) Source # 
Instance details

Defined in Data.ByteArray.Types

Methods

length :: Block ty -> Int Source #

withByteArray :: Block ty -> (Ptr p -> IO a) -> IO a Source #

copyByteArrayToPtr :: Block ty -> Ptr p -> IO () Source #

ByteArrayAccess bytes => ByteArrayAccess (View bytes) Source # 
Instance details

Defined in Data.ByteArray.View

Methods

length :: View bytes -> Int Source #

withByteArray :: View bytes -> (Ptr p -> IO a) -> IO a Source #

copyByteArrayToPtr :: View bytes -> Ptr p -> IO () Source #

(KnownNat n, PrimType ty, Countable ty n) => ByteArrayAccess (BlockN n ty) Source # 
Instance details

Defined in Data.ByteArray.Types

Methods

length :: BlockN n ty -> Int Source #

withByteArray :: BlockN n ty -> (Ptr p -> IO a) -> IO a Source #

copyByteArrayToPtr :: BlockN n ty -> Ptr p -> IO () Source #

(ByteArrayAccess ba, KnownNat n) => ByteArrayAccess (SizedByteArray n ba) Source # 
Instance details

Defined in Data.ByteArray.Sized

Methods

length :: SizedByteArray n ba -> Int Source #

withByteArray :: SizedByteArray n ba -> (Ptr p -> IO a) -> IO a Source #

copyByteArrayToPtr :: SizedByteArray n ba -> Ptr p -> IO () Source #

class (Eq ba, Ord ba, Monoid ba, ByteArrayAccess ba) => ByteArray ba where Source #

Class to allocate new ByteArray of specific size

Minimal complete definition

allocRet

Methods

allocRet Source #

Arguments

:: Int

number of bytes to allocate. i.e. might not match the size of the given type ba.

-> (Ptr p -> IO a) 
-> IO (a, ba) 

allocate n bytes and perform the given operation

Instances
ByteArray ByteString Source # 
Instance details

Defined in Data.ByteArray.Types

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, ByteString) Source #

ByteArray ScrubbedBytes Source # 
Instance details

Defined in Data.ByteArray.ScrubbedBytes

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, ScrubbedBytes) Source #

ByteArray Bytes Source # 
Instance details

Defined in Data.ByteArray.Bytes

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, Bytes) Source #

(Ord ty, PrimType ty) => ByteArray (UArray ty) Source # 
Instance details

Defined in Data.ByteArray.Types

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, UArray ty) Source #

(Ord ty, PrimType ty) => ByteArray (Block ty) Source # 
Instance details

Defined in Data.ByteArray.Types

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, Block ty) Source #

ByteArray built-in types

data Bytes Source #

Simplest Byte Array

Instances
Eq Bytes Source # 
Instance details

Defined in Data.ByteArray.Bytes

Methods

(==) :: Bytes -> Bytes -> Bool #

(/=) :: Bytes -> Bytes -> Bool #

Ord Bytes Source # 
Instance details

Defined in Data.ByteArray.Bytes

Methods

compare :: Bytes -> Bytes -> Ordering #

(<) :: Bytes -> Bytes -> Bool #

(<=) :: Bytes -> Bytes -> Bool #

(>) :: Bytes -> Bytes -> Bool #

(>=) :: Bytes -> Bytes -> Bool #

max :: Bytes -> Bytes -> Bytes #

min :: Bytes -> Bytes -> Bytes #

Show Bytes Source # 
Instance details

Defined in Data.ByteArray.Bytes

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

Semigroup Bytes Source # 
Instance details

Defined in Data.ByteArray.Bytes

Methods

(<>) :: Bytes -> Bytes -> Bytes #

sconcat :: NonEmpty Bytes -> Bytes #

stimes :: Integral b => b -> Bytes -> Bytes #

Monoid Bytes Source # 
Instance details

Defined in Data.ByteArray.Bytes

Methods

mempty :: Bytes #

mappend :: Bytes -> Bytes -> Bytes #

mconcat :: [Bytes] -> Bytes #

NormalForm Bytes Source # 
Instance details

Defined in Data.ByteArray.Bytes

Methods

toNormalForm :: Bytes -> () #

NFData Bytes Source # 
Instance details

Defined in Data.ByteArray.Bytes

Methods

rnf :: Bytes -> () #

ByteArray Bytes Source # 
Instance details

Defined in Data.ByteArray.Bytes

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, Bytes) Source #

ByteArrayAccess Bytes Source # 
Instance details

Defined in Data.ByteArray.Bytes

Methods

length :: Bytes -> Int Source #

withByteArray :: Bytes -> (Ptr p -> IO a) -> IO a Source #

copyByteArrayToPtr :: Bytes -> Ptr p -> IO () Source #

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
Instances
Eq ScrubbedBytes Source # 
Instance details

Defined in Data.ByteArray.ScrubbedBytes

Ord ScrubbedBytes Source # 
Instance details

Defined in Data.ByteArray.ScrubbedBytes

Show ScrubbedBytes Source # 
Instance details

Defined in Data.ByteArray.ScrubbedBytes

IsString ScrubbedBytes Source # 
Instance details

Defined in Data.ByteArray.ScrubbedBytes

Semigroup ScrubbedBytes Source # 
Instance details

Defined in Data.ByteArray.ScrubbedBytes

Monoid ScrubbedBytes Source # 
Instance details

Defined in Data.ByteArray.ScrubbedBytes

NormalForm ScrubbedBytes Source # 
Instance details

Defined in Data.ByteArray.ScrubbedBytes

Methods

toNormalForm :: ScrubbedBytes -> () #

NFData ScrubbedBytes Source # 
Instance details

Defined in Data.ByteArray.ScrubbedBytes

Methods

rnf :: ScrubbedBytes -> () #

ByteArray ScrubbedBytes Source # 
Instance details

Defined in Data.ByteArray.ScrubbedBytes

Methods

allocRet :: Int -> (Ptr p -> IO a) -> IO (a, ScrubbedBytes) Source #

ByteArrayAccess ScrubbedBytes Source # 
Instance details

Defined in Data.ByteArray.ScrubbedBytes

data MemView Source #

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)

Constructors

MemView !(Ptr Word8) !Int 
Instances
Eq MemView Source # 
Instance details

Defined in Data.ByteArray.MemView

Methods

(==) :: MemView -> MemView -> Bool #

(/=) :: MemView -> MemView -> Bool #

Show MemView Source # 
Instance details

Defined in Data.ByteArray.MemView

ByteArrayAccess MemView Source # 
Instance details

Defined in Data.ByteArray.MemView

data View bytes Source #

a view on a given bytes

Equality test in constant time

Instances
ByteArrayAccess bytes => Eq (View bytes) Source # 
Instance details

Defined in Data.ByteArray.View

Methods

(==) :: View bytes -> View bytes -> Bool #

(/=) :: View bytes -> View bytes -> Bool #

ByteArrayAccess bytes => Ord (View bytes) Source # 
Instance details

Defined in Data.ByteArray.View

Methods

compare :: View bytes -> View bytes -> Ordering #

(<) :: View bytes -> View bytes -> Bool #

(<=) :: View bytes -> View bytes -> Bool #

(>) :: View bytes -> View bytes -> Bool #

(>=) :: View bytes -> View bytes -> Bool #

max :: View bytes -> View bytes -> View bytes #

min :: View bytes -> View bytes -> View bytes #

ByteArrayAccess bytes => Show (View bytes) Source # 
Instance details

Defined in Data.ByteArray.View

Methods

showsPrec :: Int -> View bytes -> ShowS #

show :: View bytes -> String #

showList :: [View bytes] -> ShowS #

ByteArrayAccess bytes => ByteArrayAccess (View bytes) Source # 
Instance details

Defined in Data.ByteArray.View

Methods

length :: View bytes -> Int Source #

withByteArray :: View bytes -> (Ptr p -> IO a) -> IO a Source #

copyByteArrayToPtr :: View bytes -> Ptr p -> IO () Source #

view Source #

Arguments

:: 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

takeView Source #

Arguments

:: ByteArrayAccess bytes 
=> bytes

byte aray

-> Int

size of the view

-> View bytes 

create a view from the given bytearray

dropView Source #

Arguments

:: 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

pack :: ByteArray a => [Word8] -> a Source #

Pack a list of bytes into a bytearray

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

empty :: ByteArray a => a Source #

Create an empty byte array

singleton :: ByteArray a => Word8 -> a Source #

Create a byte array from a single byte

cons :: ByteArray a => Word8 -> a -> a Source #

prepend a single byte to a byte array

snoc :: ByteArray a => a -> Word8 -> a Source #

append a single byte to a byte array

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

zero :: ByteArray ba => Int -> ba Source #

Create a bytearray of a specific size initialized to 0

copy :: (ByteArrayAccess bs1, ByteArray bs2) => bs1 -> (Ptr p -> IO ()) -> IO bs2 Source #

Duplicate a bytearray into another bytearray, and run an initializer on it

take :: ByteArray bs => Int -> bs -> bs Source #

Take the first n byte of a bytearray

drop :: ByteArray bs => Int -> bs -> bs Source #

drop the first n byte of a bytearray

span :: ByteArray bs => (Word8 -> Bool) -> bs -> (bs, bs) Source #

Split a bytearray at the point where pred becomes invalid

reverse :: ByteArray bs => bs -> bs Source #

Reverse a bytearray

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

append :: ByteArray bs => bs -> bs -> bs Source #

append one bytearray to the other

concat :: (ByteArrayAccess bin, ByteArray bout) => [bin] -> bout Source #

Concatenate bytearray into a larger bytearray