bytestring-0.12.0.2: Fast, compact, strict and lazy byte strings with a list interface
Copyright(c) Duncan Coutts 2012-2013 Julian Ospald 2022
LicenseBSD-style
Maintainerhasufell@posteo.de
Stabilitystable
Portabilityghc only
Safe HaskellUnsafe
LanguageHaskell2010

Data.ByteString.Short.Internal

Description

Internal representation of ShortByteString

Synopsis

The ShortByteString type and representation

newtype ShortByteString Source #

A compact representation of a Word8 vector.

It has a lower memory overhead than a ByteString and does not contribute to heap fragmentation. It can be converted to or from a ByteString (at the cost of copying the string data). It supports very few other operations.

Constructors

ShortByteString

Since: 0.12.0.0

Fields

Bundled Patterns

pattern SBS :: ByteArray# -> ShortByteString

Prior to bytestring-0.12 SBS was a genuine constructor of ShortByteString , but now it is a bundled pattern synonym, provided as a compatibility shim.

Instances

Instances details
Instance details

Defined in Data.ByteString.Short.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ShortByteString -> c ShortByteString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ShortByteString #

toConstr :: ShortByteString -> Constr #

dataTypeOf :: ShortByteString -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ShortByteString) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ShortByteString) #

gmapT :: (forall b. Data b => b -> b) -> ShortByteString -> ShortByteString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ShortByteString -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ShortByteString -> r #

gmapQ :: (forall d. Data d => d -> u) -> ShortByteString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ShortByteString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ShortByteString -> m ShortByteString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ShortByteString -> m ShortByteString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ShortByteString -> m ShortByteString #

IsString ShortByteString Source #

Beware: fromString truncates multi-byte characters to octets. e.g. "枯朶に烏のとまりけり秋の暮" becomes �6k�nh~�Q��n�

Instance details

Defined in Data.ByteString.Short.Internal

IsList ShortByteString Source #

Since: 0.10.12.0

Instance details

Defined in Data.ByteString.Short.Internal

Associated Types

Instance details

Defined in Data.ByteString.Short.Internal

Read ShortByteString Source #
Instance details

Defined in Data.ByteString.Short.Internal

Show ShortByteString Source #
Instance details

Defined in Data.ByteString.Short.Internal

NFData ShortByteString Source #
Instance details

Defined in Data.ByteString.Short.Internal

Methods

rnf :: ShortByteString -> () #

Eq ShortByteString Source #
Instance details

Defined in Data.ByteString.Short.Internal

Ord ShortByteString Source #

Lexicographic order.

Instance details

Defined in Data.ByteString.Short.Internal

Lift ShortByteString Source #
Instance details

Defined in Data.ByteString.Short.Internal

Methods

lift :: Quote m => ShortByteString -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ShortByteString -> Code m ShortByteString #

type Item ShortByteString Source #
Instance details

Defined in Data.ByteString.Short.Internal

Introducing and eliminating ShortByteStrings

empty :: ShortByteString Source #

O(1). The empty ShortByteString .

singleton :: Word8 -> ShortByteString Source #

O(1) Convert a Word8 into a ShortByteString

Since: 0.11.3.0

pack :: [Word8] -> ShortByteString Source #

O(n). Convert a list into a ShortByteString

unpack :: ShortByteString -> [Word8] Source #

O(n). Convert a ShortByteString into a list.

fromShort :: ShortByteString -> ByteString Source #

O(n). Convert a ShortByteString into a ByteString .

toShort :: ByteString -> ShortByteString Source #

O(n). Convert a ByteString into a ShortByteString .

This makes a copy, so does not retain the input string.

Basic interface

snoc :: ShortByteString -> Word8 -> ShortByteString infixl 5 Source #

O(n) Append a byte to the end of a ShortByteString

Note: copies the entire byte array

Since: 0.11.3.0

cons :: Word8 -> ShortByteString -> ShortByteString infixr 5 Source #

O(n) cons is analogous to (:) for lists.

Note: copies the entire byte array

Since: 0.11.3.0

append :: ShortByteString -> ShortByteString -> ShortByteString Source #

last :: HasCallStack => ShortByteString -> Word8 Source #

O(1) Extract the last element of a ShortByteString, which must be finite and non-empty. An exception will be thrown in the case of an empty ShortByteString.

This is a partial function, consider using unsnoc instead.

Since: 0.11.3.0

tail :: HasCallStack => ShortByteString -> ShortByteString Source #

O(n) Extract the elements after the head of a ShortByteString, which must be non-empty. An exception will be thrown in the case of an empty ShortByteString.

This is a partial function, consider using uncons instead.

Note: copies the entire byte array

Since: 0.11.3.0

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

O(n) Extract the head and tail of a ShortByteString, returning Nothing if it is empty.

Since: 0.11.3.0

head :: HasCallStack => ShortByteString -> Word8 Source #

O(1) Extract the first element of a ShortByteString, which must be non-empty. An exception will be thrown in the case of an empty ShortByteString.

This is a partial function, consider using uncons instead.

Since: 0.11.3.0

init :: HasCallStack => ShortByteString -> ShortByteString Source #

O(n) Return all the elements of a ShortByteString except the last one. An exception will be thrown in the case of an empty ShortByteString.

This is a partial function, consider using unsnoc instead.

Note: copies the entire byte array

Since: 0.11.3.0

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

O(n) Extract the init and last of a ShortByteString, returning Nothing if it is empty.

Since: 0.11.3.0

null :: ShortByteString -> Bool Source #

O(1) Test whether a ShortByteString is empty.

length :: ShortByteString -> Int Source #

O(1) The length of a ShortByteString .

Transforming ShortByteStrings

map :: (Word8 -> Word8) -> ShortByteString -> ShortByteString Source #

O(n) map f xs is the ShortByteString obtained by applying f to each element of xs.

Since: 0.11.3.0

reverse :: ShortByteString -> ShortByteString Source #

O(n) reverse xs efficiently returns the elements of xs in reverse order.

Since: 0.11.3.0

intercalate :: ShortByteString -> [ShortByteString] -> ShortByteString Source #

O(n) The intercalate function takes a ShortByteString and a list of ShortByteString s and concatenates the list after interspersing the first argument between each element of the list.

Since: 0.11.3.0

Reducing ShortByteStrings (folds)

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

foldl , applied to a binary operator, a starting value (typically the left-identity of the operator), and a ShortByteString, reduces the ShortByteString using the binary operator, from left to right.

Since: 0.11.3.0

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

foldl' is like foldl , but strict in the accumulator.

Since: 0.11.3.0

foldl1 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8 Source #

foldl1 is a variant of foldl that has no starting value argument, and thus must be applied to non-empty ShortByteString s. An exception will be thrown in the case of an empty ShortByteString.

Since: 0.11.3.0

foldl1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8 Source #

foldl1' is like foldl1 , but strict in the accumulator. An exception will be thrown in the case of an empty ShortByteString.

Since: 0.11.3.0

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

foldr , applied to a binary operator, a starting value (typically the right-identity of the operator), and a ShortByteString, reduces the ShortByteString using the binary operator, from right to left.

Since: 0.11.3.0

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

foldr' is like foldr , but strict in the accumulator.

Since: 0.11.3.0

foldr1 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8 Source #

foldr1 is a variant of foldr that has no starting value argument, and thus must be applied to non-empty ShortByteString s An exception will be thrown in the case of an empty ShortByteString.

Since: 0.11.3.0

foldr1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8 Source #

foldr1' is a variant of foldr1 , but is strict in the accumulator.

Since: 0.11.3.0

Special folds

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

O(n) Applied to a predicate and a ShortByteString , all determines if all elements of the ShortByteString satisfy the predicate.

Since: 0.11.3.0

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

O(n) Applied to a predicate and a ShortByteString , any determines if any element of the ShortByteString satisfies the predicate.

Since: 0.11.3.0

concat :: [ShortByteString] -> ShortByteString Source #

Generating and unfolding ShortByteStrings

replicate :: Int -> Word8 -> ShortByteString Source #

O(n) replicate n x is a ShortByteString of length n with x the value of every element. The following holds:

replicate w c = unfoldr w (\u -> Just (u,u)) c

Since: 0.11.3.0

unfoldr :: (a -> Maybe (Word8, a)) -> a -> ShortByteString Source #

O(n), where n is the length of the result. The unfoldr function is analogous to the List 'unfoldr'. unfoldr builds a ShortByteString from a seed value. The function takes the element and returns Nothing if it is done producing the ShortByteString or returns Just (a,b), in which case, a is the next byte in the string, and b is the seed value for further production.

This function is not efficient/safe. It will build a list of [Word8] and run the generator until it returns Nothing , otherwise recurse infinitely, then finally create a ShortByteString .

If you know the maximum length, consider using unfoldrN .

Examples:

 unfoldr (\x -> if x <= 5 then Just (x, x + 1) else Nothing) 0
== pack [0, 1, 2, 3, 4, 5]

Since: 0.11.3.0

unfoldrN :: Int -> (a -> Maybe (Word8, a)) -> a -> (ShortByteString, Maybe a) Source #

O(n) Like unfoldr , unfoldrN builds a ShortByteString from a seed value. However, the length of the result is limited by the first argument to unfoldrN . This function is more efficient than unfoldr when the maximum length of the result is known.

The following equation relates unfoldrN and unfoldr :

fst (unfoldrN n f s) == take n (unfoldr f s)

Since: 0.11.3.0

Substrings

Breaking strings

take :: Int -> ShortByteString -> ShortByteString Source #

O(n) take n, applied to a ShortByteString xs, returns the prefix of xs of length n, or xs itself if n > length xs.

Note: copies the entire byte array

Since: 0.11.3.0

takeEnd :: Int -> ShortByteString -> ShortByteString Source #

O(n) takeEnd n xs is equivalent to drop (length xs - n) xs. Takes n elements from end of bytestring.

>>> takeEnd 3 "abcdefg"
"efg"
>>> takeEnd 0 "abcdefg"
""
>>> takeEnd 4 "abc"
"abc"

Since: 0.11.3.0

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

Returns the longest (possibly empty) suffix of elements satisfying the predicate.

takeWhileEnd p is equivalent to reverse . takeWhile p . reverse .

Since: 0.11.3.0

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

Similar to takeWhile , returns the longest (possibly empty) prefix of elements satisfying the predicate.

Since: 0.11.3.0

drop :: Int -> ShortByteString -> ShortByteString Source #

O(n) drop n xs returns the suffix of xs after the first n elements, or empty if n > length xs.

Note: copies the entire byte array

Since: 0.11.3.0

dropEnd :: Int -> ShortByteString -> ShortByteString Source #

O(n) dropEnd n xs is equivalent to take (length xs - n) xs. Drops n elements from end of bytestring.

>>> dropEnd 3 "abcdefg"
"abcd"
>>> dropEnd 0 "abcdefg"
"abcdefg"
>>> dropEnd 4 "abc"
""

Since: 0.11.3.0

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

Similar to dropWhile , drops the longest (possibly empty) prefix of elements satisfying the predicate and returns the remainder.

Note: copies the entire byte array

Since: 0.11.3.0

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

Similar to dropWhileEnd , drops the longest (possibly empty) suffix of elements satisfying the predicate and returns the remainder.

dropWhileEnd p is equivalent to reverse . dropWhile p . reverse .

Since: 0.11.3.0

breakEnd :: (Word8 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString) Source #

Returns the longest (possibly empty) suffix of elements which do not satisfy the predicate and the remainder of the string.

breakEnd p is equivalent to spanEnd (not . p) and to (takeWhileEnd (not . p) &&& dropWhileEnd (not . p)).

Since: 0.11.3.0

break :: (Word8 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString) Source #

Similar to break , returns the longest (possibly empty) prefix of elements which do not satisfy the predicate and the remainder of the string.

break p is equivalent to span (not . p) and to (takeWhile (not . p) &&& dropWhile (not . p)).

Since: 0.11.3.0

span :: (Word8 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString) Source #

Similar to span , returns the longest (possibly empty) prefix of elements satisfying the predicate and the remainder of the string.

span p is equivalent to break (not . p) and to (takeWhile p &&& dropWhile p).

Since: 0.11.3.0

spanEnd :: (Word8 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString) Source #

Returns the longest (possibly empty) suffix of elements satisfying the predicate and the remainder of the string.

spanEnd p is equivalent to breakEnd (not . p) and to (takeWhileEnd p &&& dropWhileEnd p).

We have

spanEnd (not . isSpace) "x y z" == ("x y ", "z")

and

spanEnd (not . isSpace) sbs
 ==
let (x, y) = span (not . isSpace) (reverse sbs) in (reverse y, reverse x)

Since: 0.11.3.0

splitAt :: Int -> ShortByteString -> (ShortByteString, ShortByteString) Source #

O(n) splitAt n sbs is equivalent to (take n sbs, drop n sbs).

Note: copies the substrings

Since: 0.11.3.0

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

O(n) Break a ShortByteString into pieces separated by the byte argument, consuming the delimiter. I.e.

split 10 "a\nb\nd\ne" == ["a","b","d","e"] -- fromEnum '\n' == 10
split 97 "aXaXaXa" == ["","X","X","X",""] -- fromEnum 'a' == 97
split 120 "x" == ["",""] -- fromEnum 'x' == 120
split undefined "" == [] -- and not [""]

and

intercalate [c] . split c == id
split == splitWith . (==)

Note: copies the substrings

Since: 0.11.3.0

splitWith :: (Word8 -> Bool) -> ShortByteString -> [ShortByteString] Source #

O(n) Splits a ShortByteString into components delimited by separators, where the predicate returns True for a separator element. The resulting components do not contain the separators. Two adjacent separators result in an empty component in the output. eg.

splitWith (==97) "aabbaca" == ["","","bb","c",""] -- fromEnum 'a' == 97
splitWith undefined "" == [] -- and not [""]

Since: 0.11.3.0

stripSuffix :: ShortByteString -> ShortByteString -> Maybe ShortByteString Source #

O(n) The stripSuffix function takes two ShortByteStrings and returns Just the remainder of the second iff the first is its suffix, and otherwise Nothing .

Since: 0.11.3.0

stripPrefix :: ShortByteString -> ShortByteString -> Maybe ShortByteString Source #

O(n) The stripPrefix function takes two ShortByteStrings and returns Just the remainder of the second iff the first is its prefix, and otherwise Nothing .

Since: 0.11.3.0

Predicates

isInfixOf :: ShortByteString -> ShortByteString -> Bool Source #

Check whether one string is a substring of another.

Since: 0.11.3.0

isPrefixOf :: ShortByteString -> ShortByteString -> Bool Source #

O(n) The isPrefixOf function takes two ShortByteStrings and returns True

Since: 0.11.3.0

isSuffixOf :: ShortByteString -> ShortByteString -> Bool Source #

O(n) The isSuffixOf function takes two ShortByteStrings and returns True iff the first is a suffix of the second.

The following holds:

isSuffixOf x y == reverse x `isPrefixOf` reverse y

Since: 0.11.3.0

Search for arbitrary substrings

breakSubstring Source #

Arguments

:: ShortByteString

String to search for

-> ShortByteString

String to search in

-> (ShortByteString, ShortByteString)

Head and tail of string broken at substring

Break a string on a substring, returning a pair of the part of the string prior to the match, and the rest of the string.

The following relationships hold:

break (== c) l == breakSubstring (singleton c) l

For example, to tokenise a string, dropping delimiters:

tokenise x y = h : if null t then [] else tokenise x (drop (length x) t)
 where (h,t) = breakSubstring x y

To skip to the first occurrence of a string:

snd (breakSubstring x y)

To take the parts of a string before a delimiter:

fst (breakSubstring x y)

Note that calling `breakSubstring x` does some preprocessing work, so you should avoid unnecessarily duplicating breakSubstring calls with the same pattern.

Since: 0.11.3.0

Searching ShortByteStrings

Searching by equality

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

O(n) elem is the ShortByteString membership predicate.

Since: 0.11.3.0

Searching with a predicate

find :: (Word8 -> Bool) -> ShortByteString -> Maybe Word8 Source #

O(n) The find function takes a predicate and a ShortByteString, and returns the first element in matching the predicate, or Nothing if there is no such element.

find f p = case findIndex f p of Just n -> Just (p ! n) ; _ -> Nothing

Since: 0.11.3.0

filter :: (Word8 -> Bool) -> ShortByteString -> ShortByteString Source #

O(n) filter , applied to a predicate and a ShortByteString, returns a ShortByteString containing those characters that satisfy the predicate.

Since: 0.11.3.0

partition :: (Word8 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString) Source #

O(n) The partition function takes a predicate a ShortByteString and returns the pair of ShortByteStrings with elements which do and do not satisfy the predicate, respectively; i.e.,

partition p bs == (filter p sbs, filter (not . p) sbs)

Since: 0.11.3.0

Indexing ShortByteStrings

index :: HasCallStack => ShortByteString -> Int -> Word8 Source #

O(1) ShortByteString index (subscript) operator, starting from 0.

This is a partial function, consider using indexMaybe instead.

indexMaybe :: ShortByteString -> Int -> Maybe Word8 Source #

O(1) ShortByteString index, starting from 0, that returns Just if:

0 <= n < length bs

Since: 0.11.0.0

(!?) :: ShortByteString -> Int -> Maybe Word8 Source #

O(1) ShortByteString index, starting from 0, that returns Just if:

0 <= n < length bs

Since: 0.11.0.0

elemIndex :: Word8 -> ShortByteString -> Maybe Int Source #

O(n) The elemIndex function returns the index of the first element in the given ShortByteString which is equal to the query element, or Nothing if there is no such element.

Since: 0.11.3.0

elemIndices :: Word8 -> ShortByteString -> [Int] Source #

O(n) The elemIndices function extends elemIndex , by returning the indices of all elements equal to the query element, in ascending order.

Since: 0.11.3.0

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

count returns the number of times its argument appears in the ShortByteString

Since: 0.11.3.0

findIndex :: (Word8 -> Bool) -> ShortByteString -> Maybe Int Source #

O(n) The findIndex function takes a predicate and a ShortByteString and returns the index of the first element in the ShortByteString satisfying the predicate.

Since: 0.11.3.0

findIndices :: (Word8 -> Bool) -> ShortByteString -> [Int] Source #

O(n) The findIndices function extends findIndex , by returning the indices of all elements satisfying the predicate, in ascending order.

Since: 0.11.3.0

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

O(1) Unsafe indexing without bounds checking.

Low level operations

createFromPtr Source #

Arguments

:: Ptr a

source data

-> Int

number of bytes to copy

copyToPtr Source #

Arguments

:: ShortByteString

source data

-> Int

offset into source

-> Ptr a

destination

-> Int

number of bytes to copy

-> IO ()

Encoding validation

isValidUtf8 :: ShortByteString -> Bool Source #

O(n) Check whether a ShortByteString represents valid UTF-8.

Since: 0.11.3.0

Low level conversions

Packing CString s and pointers

packCString :: CString -> IO ShortByteString Source #

O(n). Construct a new ShortByteString from a CString. The resulting ShortByteString is an immutable copy of the original CString, and is managed on the Haskell heap. The original CString must be null terminated.

Since: 0.10.10.0

packCStringLen :: CStringLen -> IO ShortByteString Source #

O(n). Construct a new ShortByteString from a CStringLen. The resulting ShortByteString is an immutable copy of the original CStringLen. The ShortByteString is a normal Haskell value and will be managed on the Haskell heap.

Since: 0.10.10.0

Using ShortByteStrings as CString s

useAsCString :: ShortByteString -> (CString -> IO a) -> IO a Source #

O(n) construction. Use a ShortByteString with a function requiring a null-terminated CString. The CString is a copy and will be freed automatically; it must not be stored or used after the subcomputation finishes.

Since: 0.10.10.0

useAsCStringLen :: ShortByteString -> (CStringLen -> IO a) -> IO a Source #

O(n) construction. Use a ShortByteString with a function requiring a CStringLen. As for useAsCString this function makes a copy of the original ShortByteString. It must not be stored or used after the subcomputation finishes.

Since: 0.10.10.0

AltStyle によって変換されたページ (->オリジナル) /