Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data Bytes
- null :: Bytes -> Bool
- length :: Bytes -> Int
- takeWhile :: (Word8 -> Bool) -> Bytes -> Bytes
- dropWhile :: (Word8 -> Bool) -> Bytes -> Bytes
- takeWhileEnd :: (Word8 -> Bool) -> Bytes -> Bytes
- dropWhileEnd :: (Word8 -> Bool) -> Bytes -> Bytes
- foldl :: (a -> Word8 -> a) -> a -> Bytes -> a
- foldl' :: (a -> Word8 -> a) -> a -> Bytes -> a
- foldr :: (Word8 -> a -> a) -> a -> Bytes -> a
- foldr' :: (Word8 -> a -> a) -> a -> Bytes -> a
- elem :: Word8 -> Bytes -> Bool
- split :: Word8 -> Bytes -> [Bytes]
- splitInit :: Word8 -> Bytes -> [Bytes]
- splitFirst :: Word8 -> Bytes -> Maybe (Bytes, Bytes)
- count :: Word8 -> Bytes -> Int
- isPrefixOf :: Bytes -> Bytes -> Bool
- isSuffixOf :: Bytes -> Bytes -> Bool
- stripPrefix :: Bytes -> Bytes -> Maybe Bytes
- stripOptionalPrefix :: Bytes -> Bytes -> Bytes
- stripSuffix :: Bytes -> Bytes -> Maybe Bytes
- stripOptionalSuffix :: Bytes -> Bytes -> Bytes
- unsafeTake :: Int -> Bytes -> Bytes
- unsafeDrop :: Int -> Bytes -> Bytes
- unsafeIndex :: Bytes -> Int -> Word8
- copy :: PrimMonad m => MutableByteArray (PrimState m) -> Int -> Bytes -> m ()
- pin :: Bytes -> Bytes
- contents :: Bytes -> Ptr Word8
- touch :: PrimMonad m => Bytes -> m ()
- toByteArray :: Bytes -> ByteArray
- toByteArrayClone :: Bytes -> ByteArray
- fromAsciiString :: String -> Bytes
- fromByteArray :: ByteArray -> Bytes
- toLatinString :: Bytes -> String
Types
A slice of a ByteArray
.
Properties
Filtering
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.
Common Folds
Splitting
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.
splitInit :: Word8 -> Bytes -> [Bytes] Source #
Variant of split
that drops the trailing element. This behaves
correctly even if the byte sequence is empty.
splitFirst :: 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:
>>>
splitOnce 0xA [0x1,0x2,0xA,0xB]
Just ([0x1,0x2],[0xB])
Counting
Prefix and Suffix
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.
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
:: 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 #
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
.
fromAsciiString :: String -> Bytes Source #
Convert a String
consisting of only characters
in the ASCII block.
fromByteArray :: ByteArray -> Bytes Source #
Create a slice of Bytes
that spans the entire argument array.
toLatinString :: Bytes -> String Source #
Interpret a byte sequence as text encoded by ISO-8859-1.