byteslice-0.2.6.0: Slicing managed and unmanaged memory
Safe HaskellNone
LanguageHaskell2010

Data.Bytes

Description

If you are interested in sub-arrays of ByteArrays (e.g. writing a binary search), it would be grossly inefficient to make a copy of the sub-array. On the other hand, it'd be really annoying to track limit indices by hand.

This module defines the Bytes type which exposes a standard array interface for a sub-arrays without copying and without manual index manipulation. -- For mutable arrays, see Mutable.

Synopsis

Types

data Bytes Source #

A slice of a ByteArray.

Instances

Instances details
IsList Bytes Source # 
Instance details

Defined in Data.Bytes.Internal

Associated Types

type Item Bytes #

Eq Bytes Source # 
Instance details

Defined in Data.Bytes.Internal

Methods

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

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

Ord Bytes Source # 
Instance details

Defined in Data.Bytes.Internal

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.Bytes.Internal

Methods

showsPrec :: Int -> Bytes -> ShowS #

show :: Bytes -> String #

showList :: [Bytes] -> ShowS #

Semigroup Bytes Source # 
Instance details

Defined in Data.Bytes.Internal

Methods

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

sconcat :: NonEmpty Bytes -> Bytes #

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

Monoid Bytes Source # 
Instance details

Defined in Data.Bytes.Internal

Methods

mempty :: Bytes #

mappend :: Bytes -> Bytes -> Bytes #

mconcat :: [Bytes] -> Bytes #

type Item Bytes Source # 
Instance details

Defined in Data.Bytes.Internal

Constants

empty :: Bytes Source #

The empty byte sequence.

emptyPinned :: Bytes Source #

The empty pinned byte sequence.

emptyPinnedU :: ByteArray Source #

The empty pinned byte sequence.

Properties

null :: Bytes -> Bool Source #

Is the byte sequence empty?

length :: Bytes -> Int Source #

The length of a slice of bytes.

Decompose

uncons :: Bytes -> Maybe (Word8, Bytes) Source #

Extract the head and tail of the Bytes, returning Nothing if it is empty.

unsnoc :: Bytes -> Maybe (Bytes, Word8) Source #

Extract the init and last of the Bytes, returning Nothing if it is empty.

Predicates

any :: (Word8 -> Bool) -> Bytes -> Bool Source #

O(n) Returns true if any byte in the sequence satisfies the predicate.

all :: (Word8 -> Bool) -> Bytes -> Bool Source #

O(n) Returns true if all bytes in the sequence satisfy the predicate.

Create

Sliced

singleton :: Word8 -> Bytes Source #

Create a byte sequence with one byte.

doubleton :: Word8 -> Word8 -> Bytes Source #

Create a byte sequence with two bytes.

tripleton :: Word8 -> Word8 -> Word8 -> Bytes Source #

Create a byte sequence with three bytes.

replicate Source #

Arguments

:: Int

Desired length n

-> Word8

Byte to replicate

-> Bytes 

Replicate a byte n times.

Unsliced

singletonU :: Word8 -> ByteArray Source #

Create an unsliced byte sequence with one byte.

doubletonU :: Word8 -> Word8 -> ByteArray Source #

Create an unsliced byte sequence with two bytes.

tripletonU :: Word8 -> Word8 -> Word8 -> ByteArray Source #

Create an unsliced byte sequence with three bytes.

replicateU :: Int -> Word8 -> ByteArray Source #

Variant of replicate that returns a unsliced byte array.

Filtering

takeWhile :: (Word8 -> Bool) -> Bytes -> Bytes Source #

Take bytes while the predicate is true.

dropWhile :: (Word8 -> Bool) -> Bytes -> Bytes Source #

Drop bytes while the predicate is true.

takeWhileEnd :: (Word8 -> Bool) -> Bytes -> Bytes Source #

O(n) takeWhileEnd p b returns the longest suffix of elements that satisfy predicate p.

dropWhileEnd :: (Word8 -> Bool) -> Bytes -> Bytes Source #

O(n) dropWhileEnd p b returns the prefix remaining after dropping characters that satisfy the predicate p from the end of t.

Folds

foldl :: (a -> Word8 -> a) -> a -> Bytes -> a Source #

Left fold over bytes, non-strict in the accumulator.

foldl' :: (a -> Word8 -> a) -> a -> Bytes -> a Source #

Left fold over bytes, strict in the accumulator.

foldr :: (Word8 -> a -> a) -> a -> Bytes -> a Source #

Right fold over bytes, non-strict in the accumulator.

foldr' :: (Word8 -> a -> a) -> a -> Bytes -> a Source #

Right fold over bytes, strict in the accumulator.

Folds with Indices

ifoldl' :: (a -> Int -> Word8 -> a) -> a -> Bytes -> a Source #

Left fold over bytes, strict in the accumulator. The reduction function is applied to each element along with its index.

Common Folds

elem :: Word8 -> Bytes -> Bool Source #

Is the byte a member of the byte sequence?

Splitting

Unlimited

split :: Word8 -> Bytes -> [Bytes] Source #

Break a byte sequence into pieces separated by the byte argument, consuming the delimiter. This function is a good producer for list fusion. It is common to immidiately consume the results of split with foldl', traverse_, foldlM, and being a good producer helps in this situation.

Note: this function differs from its counterpart in bytestring. If the byte sequence is empty, this returns a singleton list with the empty byte sequence.

splitU :: Word8 -> Bytes -> UnliftedArray ByteArray Source #

Variant of split that returns an array of unsliced byte sequences. Unlike split, this is not a good producer for list fusion. (It does not return a list, so it could not be.) Prefer split if the result is going to be consumed exactly once by a good consumer. Prefer splitU if the result of the split is going to be around for a while and inspected multiple times.

splitInit :: Word8 -> Bytes -> [Bytes] Source #

Variant of split that drops the trailing element. This behaves correctly even if the byte sequence is empty. This is a good producer for list fusion. This is useful when splitting a text file into lines. POSIX mandates that text files end with a newline, so the list resulting from split always has an empty byte sequence as its last element. With splitInit, that unwanted element is discarded.

splitInitU :: Word8 -> Bytes -> UnliftedArray ByteArray Source #

Variant of splitU that drops the trailing element. See splitInit for an explanation of why this may be useful.

splitNonEmpty :: Word8 -> Bytes -> NonEmpty Bytes Source #

Variant of split that returns the result as a NonEmpty instead of []. This is also eligible for stream fusion.

splitStream :: forall m. Applicative m => Word8 -> Bytes -> Stream m Bytes Source #

Variant of split that intended for use with stream fusion rather than build-foldr fusion.

Fixed from Beginning

split1 :: Word8 -> Bytes -> Maybe (Bytes, Bytes) Source #

Split a byte sequence on the first occurrence of the target byte. The target is removed from the result. For example:

>>> split1 0xA [0x1,0x2,0xA,0xB]
Just ([0x1,0x2],[0xB])

split2 :: Word8 -> Bytes -> Maybe (Bytes, Bytes, Bytes) Source #

Split a byte sequence on the first and second occurrences of the target byte. The target is removed from the result. For example:

>>> split2 0xA [0x1,0x2,0xA,0xB,0xA,0xA,0xA]
Just ([0x1,0x2],[0xB],[0xA,0xA])

split3 :: Word8 -> Bytes -> Maybe (Bytes, Bytes, Bytes, Bytes) Source #

Split a byte sequence on the first, second, and third occurrences of the target byte. The target is removed from the result. For example:

>>> split3 0xA [0x1,0x2,0xA,0xB,0xA,0xA,0xA]
Just ([0x1,0x2],[0xB],[],[0xA])

split4 :: Word8 -> Bytes -> Maybe (Bytes, Bytes, Bytes, Bytes, Bytes) Source #

Split a byte sequence on the first, second, third, and fourth occurrences of the target byte. The target is removed from the result. For example:

>>> split4 0xA [0x1,0x2,0xA,0xB,0xA,0xA,0xA]
Just ([0x1,0x2],[0xB],[],[],[])

Fixed from End

splitEnd1 :: Word8 -> Bytes -> Maybe (Bytes, Bytes) Source #

Split a byte sequence on the last occurrence of the target byte. The target is removed from the result. For example:

>>> split1 0xA [0x1,0x2,0xA,0xB,0xA,0xC]
Just ([0x1,0x2,0xA,0xB],[0xC])

Combining

intercalate Source #

Arguments

:: Bytes

Separator (interspersed into the list)

-> [Bytes]

List

-> Bytes 

O(n) The intercalate function takes a separator Bytes and a list of Bytes and concatenates the list elements by interspersing the separator between each element.

intercalateByte2 Source #

Arguments

:: Word8

Separator

-> Bytes

First byte sequence

-> Bytes

Second byte sequence

-> Bytes 

Specialization of intercalate where the separator is a single byte and there are exactly two byte sequences that are being concatenated.

Counting

count :: Word8 -> Bytes -> Int Source #

Count the number of times the byte appears in the sequence.

Prefix and Suffix

Byte Sequence

isPrefixOf :: Bytes -> Bytes -> Bool Source #

Is the first argument a prefix of the second argument?

isSuffixOf :: Bytes -> Bytes -> Bool Source #

Is the first argument a suffix of the second argument?

isInfixOf Source #

Arguments

:: Bytes

String to search for

-> Bytes

String to search in

-> Bool 

Is the first argument an infix of the second argument?

Uses the Rabin-Karp algorithm: expected time O(n+m), worst-case O(nm).

stripPrefix :: Bytes -> Bytes -> Maybe Bytes Source #

O(n) Return the suffix of the second string if its prefix matches the entire first string.

stripOptionalPrefix :: Bytes -> Bytes -> Bytes Source #

O(n) Return the suffix of the second string if its prefix matches the entire first string. Otherwise, return the second string unchanged.

stripSuffix :: Bytes -> Bytes -> Maybe Bytes Source #

O(n) Return the prefix of the second string if its suffix matches the entire first string.

stripOptionalSuffix :: Bytes -> Bytes -> Bytes Source #

O(n) Return the prefix of the second string if its suffix matches the entire first string. Otherwise, return the second string unchanged.

longestCommonPrefix :: Bytes -> Bytes -> Bytes Source #

Find the longest string which is a prefix of both arguments.

C Strings

stripCStringPrefix :: CString -> Bytes -> Maybe Bytes Source #

O(n) Variant of stripPrefix that takes a NUL-terminated C String as the prefix to test for.

Single Byte

isBytePrefixOf :: Word8 -> Bytes -> Bool Source #

Does the byte sequence begin with the given byte? False if the byte sequence is empty.

isByteSuffixOf :: Word8 -> Bytes -> Bool Source #

Does the byte sequence end with the given byte? False if the byte sequence is empty.

Equality

Fixed Characters

equalsLatin1 :: Char -> Bytes -> Bool Source #

Deprecated: use Data.Bytes.Text.Latin1.equals1 instead

Is the byte sequence, when interpreted as ISO-8859-1-encoded text, a singleton whose element matches the character?

equalsLatin2 :: Char -> Char -> Bytes -> Bool Source #

Deprecated: use Data.Bytes.Text.Latin1.equals2 instead

Is the byte sequence, when interpreted as ISO-8859-1-encoded text, a doubleton whose elements match the characters?

equalsLatin3 :: Char -> Char -> Char -> Bytes -> Bool Source #

Deprecated: use Data.Bytes.Text.Latin1.equals3 instead

Is the byte sequence, when interpreted as ISO-8859-1-encoded text, a tripleton whose elements match the characters?

equalsLatin4 :: Char -> Char -> Char -> Char -> Bytes -> Bool Source #

Deprecated: use Data.Bytes.Text.Latin1.equals4 instead

Is the byte sequence, when interpreted as ISO-8859-1-encoded text, a quadrupleton whose elements match the characters?

equalsLatin5 :: Char -> Char -> Char -> Char -> Char -> Bytes -> Bool Source #

Deprecated: use Data.Bytes.Text.Latin1.equals5 instead

Is the byte sequence, when interpreted as ISO-8859-1-encoded text, a quintupleton whose elements match the characters?

equalsLatin6 :: Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool Source #

Deprecated: use Data.Bytes.Text.Latin1.equals6 instead

Is the byte sequence, when interpreted as ISO-8859-1-encoded text, a sextupleton whose elements match the characters?

equalsLatin7 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool Source #

Deprecated: use Data.Bytes.Text.Latin1.equals7 instead

Is the byte sequence, when interpreted as ISO-8859-1-encoded text, a septupleton whose elements match the characters?

equalsLatin8 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool Source #

Deprecated: use Data.Bytes.Text.Latin1.equals8 instead

Is the byte sequence, when interpreted as ISO-8859-1-encoded text, an octupleton whose elements match the characters?

equalsLatin9 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool Source #

Deprecated: use Data.Bytes.Text.Latin1.equals9 instead

Is the byte sequence, when interpreted as ISO-8859-1-encoded text, a 9-tuple whose elements match the characters?

equalsLatin10 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool Source #

Deprecated: use Data.Bytes.Text.Latin1.equals10 instead

Is the byte sequence, when interpreted as ISO-8859-1-encoded text, a 10-tuple whose elements match the characters?

equalsLatin11 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool Source #

Deprecated: use Data.Bytes.Text.Latin1.equals11 instead

Is the byte sequence, when interpreted as ISO-8859-1-encoded text, a 11-tuple whose elements match the characters?

equalsLatin12 :: Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Char -> Bytes -> Bool Source #

Deprecated: use Data.Bytes.Text.Latin1.equals12 instead

Is the byte sequence, when interpreted as ISO-8859-1-encoded text, a 12-tuple whose elements match the characters?

C Strings

equalsCString :: CString -> Bytes -> Bool Source #

Is the byte sequence equal to the NUL-terminated C String? The C string must be a constant.

Hashing

fnv1a32 :: Bytes -> Word32 Source #

Hash byte sequence with 32-bit variant of FNV-1a.

fnv1a64 :: Bytes -> Word64 Source #

Hash byte sequence with 64-bit variant of FNV-1a.

Unsafe Slicing

unsafeTake :: Int -> Bytes -> Bytes Source #

Take the first n bytes from the argument. Precondition: n ≤ len

unsafeDrop :: Int -> Bytes -> Bytes Source #

Drop the first n bytes from the argument. Precondition: n ≤ len

unsafeIndex :: Bytes -> Int -> Word8 Source #

Index into the byte sequence at the given position. This index must be less than the length.

Copying

unsafeCopy Source #

Arguments

:: PrimMonad m 
=> MutableByteArray (PrimState m)

Destination

-> Int

Destination Offset

-> Bytes

Source

-> m () 

Copy the byte sequence into a mutable buffer. The buffer must have enough space to accomodate the byte sequence, but this this is not checked.

Pointers

pin :: Bytes -> Bytes Source #

Yields a pinned byte sequence whose contents are identical to those of the original byte sequence. If the ByteArray backing the argument was already pinned, this simply aliases the argument and does not perform any copying.

contents :: Bytes -> Ptr Word8 Source #

Yields a pointer to the beginning of the byte sequence. It is only safe to call this on a Bytes backed by a pinned ByteArray.

touch :: PrimMonad m => Bytes -> m () Source #

Touch the byte array backing the byte sequence. This sometimes needed after calling contents so that the ByteArray does not get garbage collected.

Conversion

toByteArray :: Bytes -> ByteArray Source #

Convert the sliced Bytes to an unsliced ByteArray. This reuses the array backing the sliced Bytes if the slicing metadata implies that all of the bytes are used. Otherwise, it makes a copy.

toByteArrayClone :: Bytes -> ByteArray Source #

Variant of toByteArray that unconditionally makes a copy of the array backing the sliced Bytes even if the original array could be reused. Prefer toByteArray.

toPinnedByteArray :: Bytes -> ByteArray Source #

Convert the sliced Bytes to an unsliced ByteArray. This reuses the array backing the sliced Bytes if the slicing metadata implies that all of the bytes are used and they are already pinned. Otherwise, it makes a copy.

toPinnedByteArrayClone :: Bytes -> ByteArray Source #

Variant of toPinnedByteArray that unconditionally makes a copy of the array backing the sliced Bytes even if the original array could be reused. Prefer toPinnedByteArray.

fromAsciiString :: String -> Bytes Source #

Deprecated: use Data.Bytes.Ascii.fromString instead

Convert a String consisting of only characters in the ASCII block to a byte sequence. Any character with a codepoint above U+007F is replaced by U+0000.

fromLatinString :: String -> Bytes Source #

Deprecated: use Data.Bytes.Latin1.fromString instead

Convert a String consisting of only characters representable by ISO-8859-1. These are encoded with ISO-8859-1. Any character with a codepoint above U+00FF is replaced by an unspecified byte.

fromByteArray :: ByteArray -> Bytes Source #

Create a slice of Bytes that spans the entire argument array.

toLatinString :: Bytes -> String Source #

Deprecated: use Data.Bytes.Latin1.toString instead

Interpret a byte sequence as text encoded by ISO-8859-1.

fromCString# :: Addr# -> Bytes Source #

Copy a primitive string literal into managed memory.

toByteString :: Bytes -> ByteString Source #

O(n) when unpinned, O(1) when pinned. Create a ByteString from a byte sequence. This only copies the byte sequence if it is not pinned.

pinnedToByteString :: Bytes -> ByteString Source #

Convert a pinned Bytes to a ByteString O(1) Precondition: bytes are pinned. Behavior is undefined otherwise.

fromByteString :: ByteString -> Bytes Source #

O(n) Copy a ByteString to a byte sequence.

toShortByteString :: Bytes -> ShortByteString Source #

Convert the sliced Bytes to an unsliced ShortByteString. This reuses the array backing the sliced Bytes if the slicing metadata implies that all of the bytes are used. Otherwise, it makes a copy.

toShortByteStringClone :: Bytes -> ShortByteString Source #

Variant of toShortByteString that unconditionally makes a copy of the array backing the sliced Bytes even if the original array could be reused. Prefer toShortByteString.

toLowerAsciiByteArrayClone :: Bytes -> ByteArray Source #

Deprecated: use Data.BytesTextAsciiExt.toLowerU

O(n) Interpreting the bytes an ASCII-encoded characters, convert the string to lowercase. This adds 0x20 to bytes in the range [0x41,0x5A] and leaves all other bytes alone. Unconditionally copies the bytes.

I/O with Handles

hGet :: Handle -> Int -> IO Bytes Source #

Read Bytes directly from the specified Handle. The resulting Bytes are pinned. This is implemented with hGetBuf.

readFile :: FilePath -> IO Bytes Source #

Read an entire file strictly into a Bytes.

hPut :: Handle -> Bytes -> IO () Source #

Outputs Bytes to the specified Handle. This is implemented with hPutBuf.

Unlifted Types