-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Fast, compact, strict and lazy byte strings with a list interface -- -- An efficient compact, immutable byte string type (both strict and -- lazy) suitable for binary or 8-bit character data. -- -- The ByteString type represents sequences of bytes or 8-bit -- characters. It is suitable for high performance use, both in terms of -- large data quantities, or high speed requirements. The -- ByteString functions follow the same style as Haskell's -- ordinary lists, so it is easy to convert code from using String -- to ByteString. -- -- Two ByteString variants are provided: -- -- -- -- The Char8 modules provide a character-based view of the same -- underlying ByteString types. This makes it convenient to handle -- mixed binary and 8-bit character content (which is common in many file -- formats and network protocols). -- -- The Builder module provides an efficient way to build up -- ByteStrings in an ad-hoc way by repeated concatenation. This is -- ideal for fast serialisation or pretty printing. -- -- There is also a ShortByteString type which has a lower memory -- overhead and can can be converted to or from a ByteString, but -- supports very few other operations. It is suitable for keeping many -- short strings in memory. -- -- ByteStrings are not designed for Unicode. For Unicode strings -- you should use the Text type from the text package. -- -- These modules are intended to be imported qualified, to avoid name -- clashes with Prelude functions, e.g. -- --
--   import qualified Data.ByteString as BS
--   
@package bytestring @version 0.10.6.0 -- | A module containing unsafe ByteString operations. -- -- While these functions have a stable API and you may use these -- functions in applications, do carefully consider the documented -- pre-conditions; incorrect use can break referential transparency or -- worse. module Data.ByteString.Unsafe -- | A variety of head for non-empty ByteStrings. unsafeHead -- omits the check for the empty case, so there is an obligation on the -- programmer to provide a proof that the ByteString is non-empty. unsafeHead :: ByteString -> Word8 -- | A variety of tail for non-empty ByteStrings. unsafeTail -- omits the check for the empty case. As with unsafeHead, the -- programmer must provide a separate proof that the ByteString is -- non-empty. unsafeTail :: ByteString -> ByteString -- | A variety of init for non-empty ByteStrings. unsafeInit -- omits the check for the empty case. As with unsafeHead, the -- programmer must provide a separate proof that the ByteString is -- non-empty. unsafeInit :: ByteString -> ByteString -- | A variety of last for non-empty ByteStrings. unsafeLast -- omits the check for the empty case. As with unsafeHead, the -- programmer must provide a separate proof that the ByteString is -- non-empty. unsafeLast :: ByteString -> Word8 -- | Unsafe ByteString index (subscript) operator, starting from 0, -- returning a Word8 This omits the bounds check, which means -- there is an accompanying obligation on the programmer to ensure the -- bounds are checked in some other way. unsafeIndex :: ByteString -> Int -> Word8 -- | A variety of take which omits the checks on n so there -- is an obligation on the programmer to provide a proof that 0 <= -- n <= length xs. unsafeTake :: Int -> ByteString -> ByteString -- | A variety of drop which omits the checks on n so there -- is an obligation on the programmer to provide a proof that 0 <= -- n <= length xs. unsafeDrop :: Int -> ByteString -> ByteString -- | O(1) construction Use a ByteString with a function -- requiring a CString. -- -- This function does zero copying, and merely unwraps a -- ByteString to appear as a CString. It is -- unsafe in two ways: -- -- unsafeUseAsCString :: ByteString -> (CString -> IO a) -> IO a -- | O(1) construction Use a ByteString with a function -- requiring a CStringLen. -- -- This function does zero copying, and merely unwraps a -- ByteString to appear as a CStringLen. It is -- unsafe: -- -- unsafeUseAsCStringLen :: ByteString -> (CStringLen -> IO a) -> IO a -- | O(n) Build a ByteString from a CString. This -- value will have no finalizer associated to it, and will not be -- garbage collected by Haskell. The ByteString length is calculated -- using strlen(3), and thus the complexity is a O(n). -- -- This function is unsafe. If the CString is later -- modified, this change will be reflected in the resulting -- ByteString, breaking referential transparency. unsafePackCString :: CString -> IO ByteString -- | O(1) Build a ByteString from a CStringLen. -- This value will have no finalizer associated with it, and will -- not be garbage collected by Haskell. This operation has O(1) -- complexity as we already know the final size, so no strlen(3) -- is required. -- -- This function is unsafe. If the original CStringLen is -- later modified, this change will be reflected in the resulting -- ByteString, breaking referential transparency. unsafePackCStringLen :: CStringLen -> IO ByteString -- | O(n) Build a ByteString from a malloced -- CString. This value will have a free(3) finalizer -- associated to it. -- -- This function is unsafe. If the original CString is -- later modified, this change will be reflected in the resulting -- ByteString, breaking referential transparency. -- -- This function is also unsafe if you call its finalizer twice, which -- will result in a double free error, or if you pass it a CString -- not allocated with malloc. unsafePackMallocCString :: CString -> IO ByteString -- | O(1) Build a ByteString from a malloced -- CStringLen. This value will have a free(3) finalizer -- associated to it. -- -- This function is unsafe. If the original CString is -- later modified, this change will be reflected in the resulting -- ByteString, breaking referential transparency. -- -- This function is also unsafe if you call its finalizer twice, which -- will result in a double free error, or if you pass it a CString -- not allocated with malloc. unsafePackMallocCStringLen :: CStringLen -> IO ByteString -- | O(n) Pack a null-terminated sequence of bytes, pointed to by an -- Addr# (an arbitrary machine address assumed to point outside the -- garbage-collected heap) into a ByteString. A much faster way -- to create an Addr# is with an unboxed string literal, than to pack a -- boxed string. A unboxed string literal is compiled to a static -- char [] by GHC. Establishing the length of the string -- requires a call to strlen(3), so the Addr# must point to a -- null-terminated buffer (as is the case with "string"# literals in -- GHC). Use unsafePackAddressLen if you know the length of the -- string statically. -- -- An example: -- --
--   literalFS = unsafePackAddress "literal"#
--   
-- -- This function is unsafe. If you modify the buffer pointed to by -- the original Addr# this modification will be reflected in the -- resulting ByteString, breaking referential transparency. -- -- Note this also won't work if your Addr# has embedded '\0' characters -- in the string, as strlen will return too short a length. unsafePackAddress :: Addr# -> IO ByteString -- | O(1) unsafePackAddressLen provides constant-time -- construction of ByteStrings, which is ideal for string -- literals. It packs a sequence of bytes into a ByteString, -- given a raw Addr# to the string, and the length of the string. -- -- This function is unsafe in two ways: -- -- -- -- If in doubt, don't use this function. unsafePackAddressLen :: Int -> Addr# -> IO ByteString -- | O(1) Construct a ByteString given a Ptr Word8 to a -- buffer, a length, and an IO action representing a finalizer. This -- function is not available on Hugs. -- -- This function is unsafe, it is possible to break referential -- transparency by modifying the underlying buffer pointed to by the -- first argument. Any changes to the original buffer will be reflected -- in the resulting ByteString. unsafePackCStringFinalizer :: Ptr Word8 -> Int -> IO () -> IO ByteString -- | Explicitly run the finaliser associated with a ByteString. -- References to this value after finalisation may generate invalid -- memory references. -- -- This function is unsafe, as there may be other -- ByteStrings referring to the same underlying pages. If you -- use this, you need to have a proof of some kind that all -- ByteStrings ever generated from the underlying byte array are -- no longer live. unsafeFinalize :: ByteString -> IO () -- | A compact representation suitable for storing short byte strings in -- memory. -- -- In typical use cases it can be imported alongside -- Data.ByteString, e.g. -- --
--   import qualified Data.ByteString       as B
--   import qualified Data.ByteString.Short as B
--            (ShortByteString, toShort, fromShort)
--   
-- -- Other ShortByteString operations clash with -- Data.ByteString or Prelude functions however, so they -- should be imported qualified with a different alias e.g. -- --
--   import qualified Data.ByteString.Short as B.Short
--   
module Data.ByteString.Short -- | A compact representation of a Word8 vector. -- -- It has a lower memory overhead than a ByteString and 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. -- -- It is suitable for use as an internal representation for code that -- needs to keep many short strings in memory, but it should not -- be used as an interchange type. That is, it should not generally be -- used in public APIs. The ByteString type is usually more -- suitable for use in interfaces; it is more flexible and it supports a -- wide range of operations. data ShortByteString -- | O(n). Convert a ByteString into a -- ShortByteString. -- -- This makes a copy, so does not retain the input string. toShort :: ByteString -> ShortByteString -- | O(n). Convert a ShortByteString into a -- ByteString. fromShort :: ShortByteString -> ByteString -- | O(n). Convert a list into a ShortByteString pack :: [Word8] -> ShortByteString -- | O(n). Convert a ShortByteString into a list. unpack :: ShortByteString -> [Word8] -- | O(1). The empty ShortByteString. empty :: ShortByteString -- | O(1) Test whether a ShortByteString is empty. null :: ShortByteString -> Bool -- | O(1) The length of a ShortByteString. length :: ShortByteString -> Int -- | O(1) ShortByteString index (subscript) operator, -- starting from 0. index :: ShortByteString -> Int -> Word8 -- | A time and space-efficient implementation of byte vectors using packed -- Word8 arrays, suitable for high performance use, both in terms of -- large data quantities, or high speed requirements. Byte vectors are -- encoded as strict Word8 arrays of bytes, held in a -- ForeignPtr, and can be passed between C and Haskell with little -- effort. -- -- The recomended way to assemble ByteStrings from smaller parts is to -- use the builder monoid from Data.ByteString.Builder. -- -- This module is intended to be imported qualified, to avoid -- name clashes with Prelude functions. eg. -- --
--   import qualified Data.ByteString as B
--   
-- -- Original GHC implementation by Bryan O'Sullivan. Rewritten to use -- UArray by Simon Marlow. Rewritten to support slices and use -- ForeignPtr by David Roundy. Rewritten again and extended by Don -- Stewart and Duncan Coutts. module Data.ByteString -- | A space-efficient representation of a Word8 vector, supporting -- many efficient operations. -- -- A ByteString contains 8-bit bytes, or by using the operations -- from Data.ByteString.Char8 it can be interpreted as containing -- 8-bit characters. data ByteString -- | O(1) The empty ByteString empty :: ByteString -- | O(1) Convert a Word8 into a ByteString singleton :: Word8 -> ByteString -- | O(n) Convert a '[Word8]' into a ByteString. -- -- For applications with large numbers of string literals, pack can be a -- bottleneck. In such cases, consider using packAddress (GHC only). pack :: [Word8] -> ByteString -- | O(n) Converts a ByteString to a '[Word8]'. unpack :: ByteString -> [Word8] -- | O(n) cons is analogous to (:) for lists, but of -- different complexity, as it requires making a copy. cons :: Word8 -> ByteString -> ByteString -- | O(n) Append a byte to the end of a ByteString snoc :: ByteString -> Word8 -> ByteString -- | O(n) Append two ByteStrings append :: ByteString -> ByteString -> ByteString -- | O(1) Extract the first element of a ByteString, which must be -- non-empty. An exception will be thrown in the case of an empty -- ByteString. head :: ByteString -> Word8 -- | O(1) Extract the head and tail of a ByteString, returning -- Nothing if it is empty. uncons :: ByteString -> Maybe (Word8, ByteString) -- | O(1) Extract the init and last of a ByteString, -- returning Nothing if it is empty. unsnoc :: ByteString -> Maybe (ByteString, Word8) -- | O(1) Extract the last element of a ByteString, which must be -- finite and non-empty. An exception will be thrown in the case of an -- empty ByteString. last :: ByteString -> Word8 -- | O(1) Extract the elements after the head of a ByteString, which -- must be non-empty. An exception will be thrown in the case of an empty -- ByteString. tail :: ByteString -> ByteString -- | O(1) Return all the elements of a ByteString except the -- last one. An exception will be thrown in the case of an empty -- ByteString. init :: ByteString -> ByteString -- | O(1) Test whether a ByteString is empty. null :: ByteString -> Bool -- | O(1) length returns the length of a ByteString as an -- Int. length :: ByteString -> Int -- | O(n) map f xs is the ByteString obtained by -- applying f to each element of xs. map :: (Word8 -> Word8) -> ByteString -> ByteString -- | O(n) reverse xs efficiently returns the -- elements of xs in reverse order. reverse :: ByteString -> ByteString -- | O(n) The intersperse function takes a Word8 and a -- ByteString and `intersperses' that byte between the elements of -- the ByteString. It is analogous to the intersperse function on -- Lists. intersperse :: Word8 -> ByteString -> ByteString -- | O(n) The intercalate function takes a ByteString -- and a list of ByteStrings and concatenates the list after -- interspersing the first argument between each element of the list. intercalate :: ByteString -> [ByteString] -> ByteString -- | The transpose function transposes the rows and columns of its -- ByteString argument. transpose :: [ByteString] -> [ByteString] -- | foldl, applied to a binary operator, a starting value -- (typically the left-identity of the operator), and a ByteString, -- reduces the ByteString using the binary operator, from left to right. foldl :: (a -> Word8 -> a) -> a -> ByteString -> a -- | foldl' is like foldl, but strict in the accumulator. foldl' :: (a -> Word8 -> a) -> a -> ByteString -> a -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty ByteStrings. -- An exception will be thrown in the case of an empty ByteString. foldl1 :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8 -- | 'foldl1\'' is like foldl1, but strict in the accumulator. An -- exception will be thrown in the case of an empty ByteString. foldl1' :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8 -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a ByteString, -- reduces the ByteString using the binary operator, from right to left. foldr :: (Word8 -> a -> a) -> a -> ByteString -> a -- | foldr' is like foldr, but strict in the accumulator. foldr' :: (Word8 -> a -> a) -> a -> ByteString -> a -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty ByteStrings An -- exception will be thrown in the case of an empty ByteString. foldr1 :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8 -- | 'foldr1\'' is a variant of foldr1, but is strict in the -- accumulator. foldr1' :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8 -- | O(n) Concatenate a list of ByteStrings. concat :: [ByteString] -> ByteString -- | Map a function over a ByteString and concatenate the results concatMap :: (Word8 -> ByteString) -> ByteString -> ByteString -- | O(n) Applied to a predicate and a ByteString, any -- determines if any element of the ByteString satisfies the -- predicate. any :: (Word8 -> Bool) -> ByteString -> Bool -- | O(n) Applied to a predicate and a ByteString, all -- determines if all elements of the ByteString satisfy the -- predicate. all :: (Word8 -> Bool) -> ByteString -> Bool -- | O(n) maximum returns the maximum value from a -- ByteString This function will fuse. An exception will be thrown -- in the case of an empty ByteString. maximum :: ByteString -> Word8 -- | O(n) minimum returns the minimum value from a -- ByteString This function will fuse. An exception will be thrown -- in the case of an empty ByteString. minimum :: ByteString -> Word8 -- | scanl is similar to foldl, but returns a list of -- successive reduced values from the left. This function will fuse. -- --
--   scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
--   
-- -- Note that -- --
--   last (scanl f z xs) == foldl f z xs.
--   
scanl :: (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString -- | scanl1 is a variant of scanl that has no starting value -- argument. This function will fuse. -- --
--   scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--   
scanl1 :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString -- | scanr is the right-to-left dual of scanl. scanr :: (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString -- | scanr1 is a variant of scanr that has no starting value -- argument. scanr1 :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a -- ByteString, passing an accumulating parameter from left to right, and -- returning a final value of this accumulator together with the new -- list. mapAccumL :: (acc -> Word8 -> (acc, Word8)) -> acc -> ByteString -> (acc, ByteString) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a -- ByteString, passing an accumulating parameter from right to left, and -- returning a final value of this accumulator together with the new -- ByteString. mapAccumR :: (acc -> Word8 -> (acc, Word8)) -> acc -> ByteString -> (acc, ByteString) -- | O(n) replicate n x is a ByteString of length -- n with x the value of every element. The following -- holds: -- --
--   replicate w c = unfoldr w (\u -> Just (u,u)) c
--   
-- -- This implemenation uses memset(3) replicate :: Int -> Word8 -> ByteString -- | O(n), where n is the length of the result. The -- unfoldr function is analogous to the List 'unfoldr'. -- unfoldr builds a ByteString from a seed value. The function -- takes the element and returns Nothing if it is done producing -- the ByteString 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. -- -- Examples: -- --
--      unfoldr (\x -> if x <= 5 then Just (x, x + 1) else Nothing) 0
--   == pack [0, 1, 2, 3, 4, 5]
--   
unfoldr :: (a -> Maybe (Word8, a)) -> a -> ByteString -- | O(n) Like unfoldr, unfoldrN builds a ByteString -- 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)
--   
unfoldrN :: Int -> (a -> Maybe (Word8, a)) -> a -> (ByteString, Maybe a) -- | O(1) take n, applied to a ByteString -- xs, returns the prefix of xs of length n, -- or xs itself if n > length xs. take :: Int -> ByteString -> ByteString -- | O(1) drop n xs returns the suffix of -- xs after the first n elements, or [] if -- n > length xs. drop :: Int -> ByteString -> ByteString -- | O(1) splitAt n xs is equivalent to -- (take n xs, drop n xs). splitAt :: Int -> ByteString -> (ByteString, ByteString) -- | takeWhile, applied to a predicate p and a ByteString -- xs, returns the longest prefix (possibly empty) of -- xs of elements that satisfy p. takeWhile :: (Word8 -> Bool) -> ByteString -> ByteString -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs. dropWhile :: (Word8 -> Bool) -> ByteString -> ByteString -- | span p xs breaks the ByteString into two segments. It -- is equivalent to (takeWhile p xs, dropWhile p -- xs) span :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) -- | spanEnd behaves like span but from the end of the -- ByteString. We have -- --
--   spanEnd (not.isSpace) "x y z" == ("x y ","z")
--   
-- -- and -- --
--   spanEnd (not . isSpace) ps
--      == 
--   let (x,y) = span (not.isSpace) (reverse ps) in (reverse y, reverse x) 
--   
spanEnd :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) -- | break p is equivalent to span (not . -- p). -- -- Under GHC, a rewrite rule will transform break (==) into a call to the -- specialised breakByte: -- --
--   break ((==) x) = breakByte x
--   break (==x) = breakByte x
--   
break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) -- | breakEnd behaves like break but from the end of the -- ByteString -- -- breakEnd p == spanEnd (not.p) breakEnd :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) -- | The group function takes a ByteString and returns a list of -- ByteStrings such that the concatenation of the result is equal to the -- argument. Moreover, each sublist in the result contains only equal -- elements. For example, -- --
--   group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]
--   
-- -- It is a special case of groupBy, which allows the programmer to -- supply their own equality test. It is about 40% faster than groupBy -- (==) group :: ByteString -> [ByteString] -- | The groupBy function is the non-overloaded version of -- group. groupBy :: (Word8 -> Word8 -> Bool) -> ByteString -> [ByteString] -- | O(n) Return all initial segments of the given -- ByteString, shortest first. inits :: ByteString -> [ByteString] -- | O(n) Return all final segments of the given ByteString, -- longest first. tails :: ByteString -> [ByteString] -- | O(n) Break a ByteString into pieces separated by the -- byte argument, consuming the delimiter. I.e. -- --
--   split '\n' "a\nb\nd\ne" == ["a","b","d","e"]
--   split 'a'  "aXaXaXa"    == ["","X","X","X",""]
--   split 'x'  "x"          == ["",""]
--   
-- -- and -- --
--   intercalate [c] . split c == id
--   split == splitWith . (==)
--   
-- -- As for all splitting functions in this library, this function does not -- copy the substrings, it just constructs new ByteStrings that -- are slices of the original. split :: Word8 -> ByteString -> [ByteString] -- | O(n) Splits a ByteString 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 (=='a') "aabbaca" == ["","","bb","c",""]
--   splitWith (=='a') []        == []
--   
splitWith :: (Word8 -> Bool) -> ByteString -> [ByteString] -- | O(n) The isPrefixOf function takes two ByteStrings and -- returns True iff the first is a prefix of the second. isPrefixOf :: ByteString -> ByteString -> Bool -- | O(n) The isSuffixOf function takes two ByteStrings and -- returns True iff the first is a suffix of the second. -- -- The following holds: -- --
--   isSuffixOf x y == reverse x `isPrefixOf` reverse y
--   
-- -- However, the real implemenation uses memcmp to compare the end of the -- string only, with no reverse required.. isSuffixOf :: ByteString -> ByteString -> Bool -- | Check whether one string is a substring of another. isInfixOf p -- s is equivalent to not (null (findSubstrings p s)). isInfixOf :: ByteString -> ByteString -> Bool -- | 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
--   
-- -- and: -- --
--   findSubstring s l ==
--      if null s then Just 0
--                else case breakSubstring s l of
--                         (x,y) | null y    -> Nothing
--                               | otherwise -> Just (length x)
--   
-- -- 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 occurence of a string: -- --
--   snd (breakSubstring x y) 
--   
-- -- To take the parts of a string before a delimiter: -- --
--   fst (breakSubstring x y) 
--   
breakSubstring :: ByteString -> ByteString -> (ByteString, ByteString) -- | Get the first index of a substring in another string, or -- Nothing if the string is not found. findSubstring p s -- is equivalent to listToMaybe (findSubstrings p s). -- | Deprecated: findSubstring is deprecated in favour of -- breakSubstring. findSubstring :: ByteString -> ByteString -> Maybe Int -- | Find the indexes of all (possibly overlapping) occurances of a -- substring in a string. -- | Deprecated: findSubstrings is deprecated in favour of -- breakSubstring. findSubstrings :: ByteString -> ByteString -> [Int] -- | O(n) elem is the ByteString membership predicate. elem :: Word8 -> ByteString -> Bool -- | O(n) notElem is the inverse of elem notElem :: Word8 -> ByteString -> Bool -- | O(n) The find function takes a predicate and a -- ByteString, 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
--   
find :: (Word8 -> Bool) -> ByteString -> Maybe Word8 -- | O(n) filter, applied to a predicate and a ByteString, -- returns a ByteString containing those characters that satisfy the -- predicate. filter :: (Word8 -> Bool) -> ByteString -> ByteString -- | O(n) The partition function takes a predicate a -- ByteString and returns the pair of ByteStrings with elements which do -- and do not satisfy the predicate, respectively; i.e., -- --
--   partition p bs == (filter p xs, filter (not . p) xs)
--   
partition :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) -- | O(1) ByteString index (subscript) operator, starting -- from 0. index :: ByteString -> Int -> Word8 -- | O(n) The elemIndex function returns the index of the -- first element in the given ByteString which is equal to the -- query element, or Nothing if there is no such element. This -- implementation uses memchr(3). elemIndex :: Word8 -> ByteString -> Maybe Int -- | O(n) The elemIndices function extends elemIndex, -- by returning the indices of all elements equal to the query element, -- in ascending order. This implementation uses memchr(3). elemIndices :: Word8 -> ByteString -> [Int] -- | O(n) The elemIndexEnd function returns the last index of -- the element in the given ByteString which is equal to the query -- element, or Nothing if there is no such element. The following -- holds: -- --
--   elemIndexEnd c xs == 
--   (-) (length xs - 1) `fmap` elemIndex c (reverse xs)
--   
elemIndexEnd :: Word8 -> ByteString -> Maybe Int -- | The findIndex function takes a predicate and a -- ByteString and returns the index of the first element in the -- ByteString satisfying the predicate. findIndex :: (Word8 -> Bool) -> ByteString -> Maybe Int -- | The findIndices function extends findIndex, by returning -- the indices of all elements satisfying the predicate, in ascending -- order. findIndices :: (Word8 -> Bool) -> ByteString -> [Int] -- | count returns the number of times its argument appears in the -- ByteString -- --
--   count = length . elemIndices
--   
-- -- But more efficiently than using length on the intermediate list. count :: Word8 -> ByteString -> Int -- | O(n) zip takes two ByteStrings and returns a list of -- corresponding pairs of bytes. If one input ByteString is short, excess -- elements of the longer ByteString are discarded. This is equivalent to -- a pair of unpack operations. zip :: ByteString -> ByteString -> [(Word8, Word8)] -- | zipWith generalises zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, zipWith (+) is applied to two ByteStrings to -- produce the list of corresponding sums. zipWith :: (Word8 -> Word8 -> a) -> ByteString -> ByteString -> [a] -- | O(n) unzip transforms a list of pairs of bytes into a -- pair of ByteStrings. Note that this performs two pack -- operations. unzip :: [(Word8, Word8)] -> (ByteString, ByteString) -- | O(n) Sort a ByteString efficiently, using counting sort. sort :: ByteString -> ByteString -- | O(n) Make a copy of the ByteString with its own storage. -- This is mainly useful to allow the rest of the data pointed to by the -- ByteString to be garbage collected, for example if a large -- string has been read in, and only a small part of it is needed in the -- rest of the program. copy :: ByteString -> ByteString -- | O(n). Construct a new ByteString from a -- CString. The resulting ByteString is an immutable -- copy of the original CString, and is managed on the Haskell -- heap. The original CString must be null terminated. packCString :: CString -> IO ByteString -- | O(n). Construct a new ByteString from a -- CStringLen. The resulting ByteString is an immutable -- copy of the original CStringLen. The ByteString is a -- normal Haskell value and will be managed on the Haskell heap. packCStringLen :: CStringLen -> IO ByteString -- | O(n) construction Use a ByteString with a function -- requiring a null-terminated CString. The CString is -- a copy and will be freed automatically. useAsCString :: ByteString -> (CString -> IO a) -> IO a -- | O(n) construction Use a ByteString with a function -- requiring a CStringLen. As for useAsCString this -- function makes a copy of the original ByteString. useAsCStringLen :: ByteString -> (CStringLen -> IO a) -> IO a -- | Read a line from stdin. getLine :: IO ByteString -- | getContents. Read stdin strictly. Equivalent to hGetContents stdin The -- Handle is closed after the contents have been read. getContents :: IO ByteString -- | Write a ByteString to stdout putStr :: ByteString -> IO () -- | Write a ByteString to stdout, appending a newline byte -- | Deprecated: Use Data.ByteString.Char8.putStrLn instead. (Functions -- that rely on ASCII encodings belong in Data.ByteString.Char8) putStrLn :: ByteString -> IO () -- | The interact function takes a function of type ByteString -> -- ByteString as its argument. The entire input from the standard -- input device is passed to this function as its argument, and the -- resulting string is output on the standard output device. interact :: (ByteString -> ByteString) -> IO () -- | Read an entire file strictly into a ByteString. readFile :: FilePath -> IO ByteString -- | Write a ByteString to a file. writeFile :: FilePath -> ByteString -> IO () -- | Append a ByteString to a file. appendFile :: FilePath -> ByteString -> IO () -- | Read a line from a handle hGetLine :: Handle -> IO ByteString -- | Read a handle's entire contents strictly into a ByteString. -- -- This function reads chunks at a time, increasing the chunk size on -- each read. The final string is then realloced to the appropriate size. -- For files > half of available memory, this may lead to memory -- exhaustion. Consider using readFile in this case. -- -- The Handle is closed once the contents have been read, or if an -- exception is thrown. hGetContents :: Handle -> IO ByteString -- | Read a ByteString directly from the specified Handle. -- This is far more efficient than reading the characters into a -- String and then using pack. First argument is the Handle -- to read from, and the second is the number of bytes to read. It -- returns the bytes read, up to n, or empty if EOF has been -- reached. -- -- hGet is implemented in terms of hGetBuf. -- -- If the handle is a pipe or socket, and the writing end is closed, -- hGet will behave as if EOF was reached. hGet :: Handle -> Int -> IO ByteString -- | Like hGet, except that a shorter ByteString may be -- returned if there are not enough bytes immediately available to -- satisfy the whole request. hGetSome only blocks if there is no -- data available, and EOF has not yet been reached. hGetSome :: Handle -> Int -> IO ByteString -- | hGetNonBlocking is similar to hGet, except that it will never -- block waiting for data to become available, instead it returns only -- whatever data is available. If there is no data available to be read, -- hGetNonBlocking returns empty. -- -- Note: on Windows and with Haskell implementation other than GHC, this -- function does not work correctly; it behaves identically to -- hGet. hGetNonBlocking :: Handle -> Int -> IO ByteString -- | Outputs a ByteString to the specified Handle. hPut :: Handle -> ByteString -> IO () -- | Similar to hPut except that it will never block. Instead it -- returns any tail that did not get written. This tail may be -- empty in the case that the whole string was written, or the -- whole original string if nothing was written. Partial writes are also -- possible. -- -- Note: on Windows and with Haskell implementation other than GHC, this -- function does not work correctly; it behaves identically to -- hPut. hPutNonBlocking :: Handle -> ByteString -> IO ByteString -- | A synonym for hPut, for compatibility hPutStr :: Handle -> ByteString -> IO () -- | Write a ByteString to a handle, appending a newline byte -- | Deprecated: Use Data.ByteString.Char8.hPutStrLn instead. (Functions -- that rely on ASCII encodings belong in Data.ByteString.Char8) hPutStrLn :: Handle -> ByteString -> IO () -- | breakByte breaks its ByteString argument at the first occurence -- of the specified byte. It is more efficient than break as it is -- implemented with memchr(3). I.e. -- --
--   break (=='c') "abcd" == breakByte 'c' "abcd"
--   
-- | Deprecated: It is an internal function and should never have been -- exported. Use 'break (== x)' instead. (There are rewrite rules that -- handle this special case of break.) breakByte :: Word8 -> ByteString -> (ByteString, ByteString) -- | Manipulate ByteStrings using Char operations. All Chars -- will be truncated to 8 bits. It can be expected that these functions -- will run at identical speeds to their Word8 equivalents in -- Data.ByteString. -- -- More specifically these byte strings are taken to be in the subset of -- Unicode covered by code points 0-255. This covers Unicode Basic Latin, -- Latin-1 Supplement and C0+C1 Controls. -- -- See: -- -- -- -- This module is intended to be imported qualified, to avoid -- name clashes with Prelude functions. eg. -- --
--   import qualified Data.ByteString.Char8 as C
--   
-- -- The Char8 interface to bytestrings provides an instance of IsString -- for the ByteString type, enabling you to use string literals, and have -- them implicitly packed to ByteStrings. Use {-# LANGUAGE -- OverloadedStrings #-} to enable this. module Data.ByteString.Char8 -- | A space-efficient representation of a Word8 vector, supporting -- many efficient operations. -- -- A ByteString contains 8-bit bytes, or by using the operations -- from Data.ByteString.Char8 it can be interpreted as containing -- 8-bit characters. data ByteString -- | O(1) The empty ByteString empty :: ByteString -- | O(1) Convert a Char into a ByteString singleton :: Char -> ByteString -- | O(n) Convert a String into a ByteString -- -- For applications with large numbers of string literals, pack can be a -- bottleneck. pack :: String -> ByteString -- | O(n) Converts a ByteString to a String. unpack :: ByteString -> [Char] -- | O(n) cons is analogous to (:) for lists, but of -- different complexity, as it requires a memcpy. cons :: Char -> ByteString -> ByteString -- | O(n) Append a Char to the end of a ByteString. Similar -- to cons, this function performs a memcpy. snoc :: ByteString -> Char -> ByteString -- | O(n) Append two ByteStrings append :: ByteString -> ByteString -> ByteString -- | O(1) Extract the first element of a ByteString, which must be -- non-empty. head :: ByteString -> Char -- | O(1) Extract the head and tail of a ByteString, returning -- Nothing if it is empty. uncons :: ByteString -> Maybe (Char, ByteString) -- | O(1) Extract the init and last of a ByteString, -- returning Nothing if it is empty. unsnoc :: ByteString -> Maybe (ByteString, Char) -- | O(1) Extract the last element of a packed string, which must be -- non-empty. last :: ByteString -> Char -- | O(1) Extract the elements after the head of a ByteString, which -- must be non-empty. An exception will be thrown in the case of an empty -- ByteString. tail :: ByteString -> ByteString -- | O(1) Return all the elements of a ByteString except the -- last one. An exception will be thrown in the case of an empty -- ByteString. init :: ByteString -> ByteString -- | O(1) Test whether a ByteString is empty. null :: ByteString -> Bool -- | O(1) length returns the length of a ByteString as an -- Int. length :: ByteString -> Int -- | O(n) map f xs is the ByteString obtained by -- applying f to each element of xs map :: (Char -> Char) -> ByteString -> ByteString -- | O(n) reverse xs efficiently returns the -- elements of xs in reverse order. reverse :: ByteString -> ByteString -- | O(n) The intersperse function takes a Char and a -- ByteString and `intersperses' that Char between the elements of -- the ByteString. It is analogous to the intersperse function on -- Lists. intersperse :: Char -> ByteString -> ByteString -- | O(n) The intercalate function takes a ByteString -- and a list of ByteStrings and concatenates the list after -- interspersing the first argument between each element of the list. intercalate :: ByteString -> [ByteString] -> ByteString -- | The transpose function transposes the rows and columns of its -- ByteString argument. transpose :: [ByteString] -> [ByteString] -- | foldl, applied to a binary operator, a starting value -- (typically the left-identity of the operator), and a ByteString, -- reduces the ByteString using the binary operator, from left to right. foldl :: (a -> Char -> a) -> a -> ByteString -> a -- | 'foldl\'' is like foldl, but strict in the accumulator. foldl' :: (a -> Char -> a) -> a -> ByteString -> a -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty ByteStrings. foldl1 :: (Char -> Char -> Char) -> ByteString -> Char -- | A strict version of foldl1 foldl1' :: (Char -> Char -> Char) -> ByteString -> Char -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a packed string, -- reduces the packed string using the binary operator, from right to -- left. foldr :: (Char -> a -> a) -> a -> ByteString -> a -- | 'foldr\'' is a strict variant of foldr foldr' :: (Char -> a -> a) -> a -> ByteString -> a -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty ByteStrings foldr1 :: (Char -> Char -> Char) -> ByteString -> Char -- | A strict variant of foldr1 foldr1' :: (Char -> Char -> Char) -> ByteString -> Char -- | O(n) Concatenate a list of ByteStrings. concat :: [ByteString] -> ByteString -- | Map a function over a ByteString and concatenate the results concatMap :: (Char -> ByteString) -> ByteString -> ByteString -- | Applied to a predicate and a ByteString, any determines if any -- element of the ByteString satisfies the predicate. any :: (Char -> Bool) -> ByteString -> Bool -- | Applied to a predicate and a ByteString, all determines -- if all elements of the ByteString satisfy the predicate. all :: (Char -> Bool) -> ByteString -> Bool -- | maximum returns the maximum value from a ByteString maximum :: ByteString -> Char -- | minimum returns the minimum value from a ByteString minimum :: ByteString -> Char -- | scanl is similar to foldl, but returns a list of -- successive reduced values from the left: -- --
--   scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
--   
-- -- Note that -- --
--   last (scanl f z xs) == foldl f z xs.
--   
scanl :: (Char -> Char -> Char) -> Char -> ByteString -> ByteString -- | scanl1 is a variant of scanl that has no starting value -- argument: -- --
--   scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--   
scanl1 :: (Char -> Char -> Char) -> ByteString -> ByteString -- | scanr is the right-to-left dual of scanl. scanr :: (Char -> Char -> Char) -> Char -> ByteString -> ByteString -- | scanr1 is a variant of scanr that has no starting value -- argument. scanr1 :: (Char -> Char -> Char) -> ByteString -> ByteString -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a -- ByteString, passing an accumulating parameter from left to right, and -- returning a final value of this accumulator together with the new -- list. mapAccumL :: (acc -> Char -> (acc, Char)) -> acc -> ByteString -> (acc, ByteString) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a -- ByteString, passing an accumulating parameter from right to left, and -- returning a final value of this accumulator together with the new -- ByteString. mapAccumR :: (acc -> Char -> (acc, Char)) -> acc -> ByteString -> (acc, ByteString) -- | O(n) replicate n x is a ByteString of length -- n with x the value of every element. The following -- holds: -- --
--   replicate w c = unfoldr w (\u -> Just (u,u)) c
--   
-- -- This implemenation uses memset(3) replicate :: Int -> Char -> ByteString -- | O(n), where n is the length of the result. The -- unfoldr function is analogous to the List 'unfoldr'. -- unfoldr builds a ByteString from a seed value. The function -- takes the element and returns Nothing if it is done producing -- the ByteString or returns Just (a,b), in which case, -- a is the next character in the string, and b is the -- seed value for further production. -- -- Examples: -- --
--   unfoldr (\x -> if x <= '9' then Just (x, succ x) else Nothing) '0' == "0123456789"
--   
unfoldr :: (a -> Maybe (Char, a)) -> a -> ByteString -- | O(n) Like unfoldr, unfoldrN builds a ByteString -- 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: -- --
--   unfoldrN n f s == take n (unfoldr f s)
--   
unfoldrN :: Int -> (a -> Maybe (Char, a)) -> a -> (ByteString, Maybe a) -- | O(1) take n, applied to a ByteString -- xs, returns the prefix of xs of length n, -- or xs itself if n > length xs. take :: Int -> ByteString -> ByteString -- | O(1) drop n xs returns the suffix of -- xs after the first n elements, or [] if -- n > length xs. drop :: Int -> ByteString -> ByteString -- | O(1) splitAt n xs is equivalent to -- (take n xs, drop n xs). splitAt :: Int -> ByteString -> (ByteString, ByteString) -- | takeWhile, applied to a predicate p and a ByteString -- xs, returns the longest prefix (possibly empty) of -- xs of elements that satisfy p. takeWhile :: (Char -> Bool) -> ByteString -> ByteString -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs. dropWhile :: (Char -> Bool) -> ByteString -> ByteString -- | span p xs breaks the ByteString into two segments. It -- is equivalent to (takeWhile p xs, dropWhile p -- xs) span :: (Char -> Bool) -> ByteString -> (ByteString, ByteString) -- | spanEnd behaves like span but from the end of the -- ByteString. We have -- --
--   spanEnd (not.isSpace) "x y z" == ("x y ","z")
--   
-- -- and -- --
--   spanEnd (not . isSpace) ps
--      == 
--   let (x,y) = span (not.isSpace) (reverse ps) in (reverse y, reverse x) 
--   
spanEnd :: (Char -> Bool) -> ByteString -> (ByteString, ByteString) -- | break p is equivalent to span (not . -- p). break :: (Char -> Bool) -> ByteString -> (ByteString, ByteString) -- | breakEnd behaves like break but from the end of the -- ByteString -- -- breakEnd p == spanEnd (not.p) breakEnd :: (Char -> Bool) -> ByteString -> (ByteString, ByteString) -- | The group function takes a ByteString and returns a list of -- ByteStrings such that the concatenation of the result is equal to the -- argument. Moreover, each sublist in the result contains only equal -- elements. For example, -- --
--   group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]
--   
-- -- It is a special case of groupBy, which allows the programmer to -- supply their own equality test. It is about 40% faster than groupBy -- (==) group :: ByteString -> [ByteString] -- | The groupBy function is the non-overloaded version of -- group. groupBy :: (Char -> Char -> Bool) -> ByteString -> [ByteString] -- | O(n) Return all initial segments of the given -- ByteString, shortest first. inits :: ByteString -> [ByteString] -- | O(n) Return all final segments of the given ByteString, -- longest first. tails :: ByteString -> [ByteString] -- | O(n) Break a ByteString into pieces separated by the -- byte argument, consuming the delimiter. I.e. -- --
--   split '\n' "a\nb\nd\ne" == ["a","b","d","e"]
--   split 'a'  "aXaXaXa"    == ["","X","X","X",""]
--   split 'x'  "x"          == ["",""]
--   
-- -- and -- --
--   intercalate [c] . split c == id
--   split == splitWith . (==)
--   
-- -- As for all splitting functions in this library, this function does not -- copy the substrings, it just constructs new ByteStrings that -- are slices of the original. split :: Char -> ByteString -> [ByteString] -- | O(n) Splits a ByteString 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 (=='a') "aabbaca" == ["","","bb","c",""]
--   
splitWith :: (Char -> Bool) -> ByteString -> [ByteString] -- | lines breaks a ByteString up into a list of ByteStrings at -- newline Chars. The resulting strings do not contain newlines. lines :: ByteString -> [ByteString] -- | words breaks a ByteString up into a list of words, which were -- delimited by Chars representing white space. words :: ByteString -> [ByteString] -- | unlines is an inverse operation to lines. It joins -- lines, after appending a terminating newline to each. unlines :: [ByteString] -> ByteString -- | The unwords function is analogous to the unlines -- function, on words. unwords :: [ByteString] -> ByteString -- | O(n) The isPrefixOf function takes two ByteStrings and -- returns True iff the first is a prefix of the second. isPrefixOf :: ByteString -> ByteString -> Bool -- | O(n) The isSuffixOf function takes two ByteStrings and -- returns True iff the first is a suffix of the second. -- -- The following holds: -- --
--   isSuffixOf x y == reverse x `isPrefixOf` reverse y
--   
-- -- However, the real implemenation uses memcmp to compare the end of the -- string only, with no reverse required.. isSuffixOf :: ByteString -> ByteString -> Bool -- | Check whether one string is a substring of another. isInfixOf p -- s is equivalent to not (null (findSubstrings p s)). isInfixOf :: ByteString -> ByteString -> Bool -- | 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
--   
-- -- and: -- --
--   findSubstring s l ==
--      if null s then Just 0
--                else case breakSubstring s l of
--                         (x,y) | null y    -> Nothing
--                               | otherwise -> Just (length x)
--   
-- -- 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 occurence of a string: -- --
--   snd (breakSubstring x y) 
--   
-- -- To take the parts of a string before a delimiter: -- --
--   fst (breakSubstring x y) 
--   
breakSubstring :: ByteString -> ByteString -> (ByteString, ByteString) -- | Get the first index of a substring in another string, or -- Nothing if the string is not found. findSubstring p s -- is equivalent to listToMaybe (findSubstrings p s). -- | Deprecated: findSubstring is deprecated in favour of -- breakSubstring. findSubstring :: ByteString -> ByteString -> Maybe Int -- | Find the indexes of all (possibly overlapping) occurances of a -- substring in a string. -- | Deprecated: findSubstrings is deprecated in favour of -- breakSubstring. findSubstrings :: ByteString -> ByteString -> [Int] -- | O(n) elem is the ByteString membership predicate. -- This implementation uses memchr(3). elem :: Char -> ByteString -> Bool -- | O(n) notElem is the inverse of elem notElem :: Char -> ByteString -> Bool -- | O(n) The find function takes a predicate and a -- ByteString, and returns the first element in matching the predicate, -- or Nothing if there is no such element. find :: (Char -> Bool) -> ByteString -> Maybe Char -- | O(n) filter, applied to a predicate and a ByteString, -- returns a ByteString containing those characters that satisfy the -- predicate. filter :: (Char -> Bool) -> ByteString -> ByteString -- | O(1) ByteString index (subscript) operator, starting -- from 0. index :: ByteString -> Int -> Char -- | O(n) The elemIndex function returns the index of the -- first element in the given ByteString which is equal (by -- memchr) to the query element, or Nothing if there is no such -- element. elemIndex :: Char -> ByteString -> Maybe Int -- | O(n) The elemIndices function extends elemIndex, -- by returning the indices of all elements equal to the query element, -- in ascending order. elemIndices :: Char -> ByteString -> [Int] -- | O(n) The elemIndexEnd function returns the last index of -- the element in the given ByteString which is equal to the query -- element, or Nothing if there is no such element. The following -- holds: -- --
--   elemIndexEnd c xs == 
--   (-) (length xs - 1) `fmap` elemIndex c (reverse xs)
--   
elemIndexEnd :: Char -> ByteString -> Maybe Int -- | The findIndex function takes a predicate and a -- ByteString and returns the index of the first element in the -- ByteString satisfying the predicate. findIndex :: (Char -> Bool) -> ByteString -> Maybe Int -- | The findIndices function extends findIndex, by returning -- the indices of all elements satisfying the predicate, in ascending -- order. findIndices :: (Char -> Bool) -> ByteString -> [Int] -- | count returns the number of times its argument appears in the -- ByteString -- --
--   count = length . elemIndices
--   
-- -- Also -- --
--   count '\n' == length . lines
--   
-- -- But more efficiently than using length on the intermediate list. count :: Char -> ByteString -> Int -- | O(n) zip takes two ByteStrings and returns a list of -- corresponding pairs of Chars. If one input ByteString is short, excess -- elements of the longer ByteString are discarded. This is equivalent to -- a pair of unpack operations, and so space usage may be large -- for multi-megabyte ByteStrings zip :: ByteString -> ByteString -> [(Char, Char)] -- | zipWith generalises zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, zipWith (+) is applied to two ByteStrings to -- produce the list of corresponding sums. zipWith :: (Char -> Char -> a) -> ByteString -> ByteString -> [a] -- | unzip transforms a list of pairs of Chars into a pair of -- ByteStrings. Note that this performs two pack operations. unzip :: [(Char, Char)] -> (ByteString, ByteString) -- | O(n) Sort a ByteString efficiently, using counting sort. sort :: ByteString -> ByteString -- | readInt reads an Int from the beginning of the ByteString. If there is -- no integer at the beginning of the string, it returns Nothing, -- otherwise it just returns the int read, and the rest of the string. readInt :: ByteString -> Maybe (Int, ByteString) -- | readInteger reads an Integer from the beginning of the ByteString. If -- there is no integer at the beginning of the string, it returns -- Nothing, otherwise it just returns the int read, and the rest of the -- string. readInteger :: ByteString -> Maybe (Integer, ByteString) -- | O(n) Make a copy of the ByteString with its own storage. -- This is mainly useful to allow the rest of the data pointed to by the -- ByteString to be garbage collected, for example if a large -- string has been read in, and only a small part of it is needed in the -- rest of the program. copy :: ByteString -> ByteString -- | O(n). Construct a new ByteString from a -- CString. The resulting ByteString is an immutable -- copy of the original CString, and is managed on the Haskell -- heap. The original CString must be null terminated. packCString :: CString -> IO ByteString -- | O(n). Construct a new ByteString from a -- CStringLen. The resulting ByteString is an immutable -- copy of the original CStringLen. The ByteString is a -- normal Haskell value and will be managed on the Haskell heap. packCStringLen :: CStringLen -> IO ByteString -- | O(n) construction Use a ByteString with a function -- requiring a null-terminated CString. The CString is -- a copy and will be freed automatically. useAsCString :: ByteString -> (CString -> IO a) -> IO a -- | O(n) construction Use a ByteString with a function -- requiring a CStringLen. As for useAsCString this -- function makes a copy of the original ByteString. useAsCStringLen :: ByteString -> (CStringLen -> IO a) -> IO a -- | Read a line from stdin. getLine :: IO ByteString -- | getContents. Read stdin strictly. Equivalent to hGetContents stdin The -- Handle is closed after the contents have been read. getContents :: IO ByteString -- | Write a ByteString to stdout putStr :: ByteString -> IO () -- | Write a ByteString to stdout, appending a newline byte putStrLn :: ByteString -> IO () -- | The interact function takes a function of type ByteString -> -- ByteString as its argument. The entire input from the standard -- input device is passed to this function as its argument, and the -- resulting string is output on the standard output device. interact :: (ByteString -> ByteString) -> IO () -- | Read an entire file strictly into a ByteString. This is far -- more efficient than reading the characters into a String and -- then using pack. It also may be more efficient than opening the -- file and reading it using hGet. readFile :: FilePath -> IO ByteString -- | Write a ByteString to a file. writeFile :: FilePath -> ByteString -> IO () -- | Append a ByteString to a file. appendFile :: FilePath -> ByteString -> IO () -- | Read a line from a handle hGetLine :: Handle -> IO ByteString -- | Read a handle's entire contents strictly into a ByteString. -- -- This function reads chunks at a time, increasing the chunk size on -- each read. The final string is then realloced to the appropriate size. -- For files > half of available memory, this may lead to memory -- exhaustion. Consider using readFile in this case. -- -- The Handle is closed once the contents have been read, or if an -- exception is thrown. hGetContents :: Handle -> IO ByteString -- | Read a ByteString directly from the specified Handle. -- This is far more efficient than reading the characters into a -- String and then using pack. First argument is the Handle -- to read from, and the second is the number of bytes to read. It -- returns the bytes read, up to n, or empty if EOF has been -- reached. -- -- hGet is implemented in terms of hGetBuf. -- -- If the handle is a pipe or socket, and the writing end is closed, -- hGet will behave as if EOF was reached. hGet :: Handle -> Int -> IO ByteString -- | Like hGet, except that a shorter ByteString may be -- returned if there are not enough bytes immediately available to -- satisfy the whole request. hGetSome only blocks if there is no -- data available, and EOF has not yet been reached. hGetSome :: Handle -> Int -> IO ByteString -- | hGetNonBlocking is similar to hGet, except that it will never -- block waiting for data to become available, instead it returns only -- whatever data is available. If there is no data available to be read, -- hGetNonBlocking returns empty. -- -- Note: on Windows and with Haskell implementation other than GHC, this -- function does not work correctly; it behaves identically to -- hGet. hGetNonBlocking :: Handle -> Int -> IO ByteString -- | Outputs a ByteString to the specified Handle. hPut :: Handle -> ByteString -> IO () -- | Similar to hPut except that it will never block. Instead it -- returns any tail that did not get written. This tail may be -- empty in the case that the whole string was written, or the -- whole original string if nothing was written. Partial writes are also -- possible. -- -- Note: on Windows and with Haskell implementation other than GHC, this -- function does not work correctly; it behaves identically to -- hPut. hPutNonBlocking :: Handle -> ByteString -> IO ByteString -- | A synonym for hPut, for compatibility hPutStr :: Handle -> ByteString -> IO () -- | Write a ByteString to a handle, appending a newline byte hPutStrLn :: Handle -> ByteString -> IO () -- | A time and space-efficient implementation of lazy byte vectors using -- lists of packed Word8 arrays, suitable for high performance -- use, both in terms of large data quantities, or high speed -- requirements. Lazy ByteStrings are encoded as lazy lists of strict -- chunks of bytes. -- -- A key feature of lazy ByteStrings is the means to manipulate large or -- unbounded streams of data without requiring the entire sequence to be -- resident in memory. To take advantage of this you have to write your -- functions in a lazy streaming style, e.g. classic pipeline -- composition. The default I/O chunk size is 32k, which should be good -- in most circumstances. -- -- Some operations, such as concat, append, reverse -- and cons, have better complexity than their -- Data.ByteString equivalents, due to optimisations resulting -- from the list spine structure. For other operations lazy ByteStrings -- are usually within a few percent of strict ones. -- -- The recomended way to assemble lazy ByteStrings from smaller parts is -- to use the builder monoid from Data.ByteString.Builder. -- -- This module is intended to be imported qualified, to avoid -- name clashes with Prelude functions. eg. -- --
--   import qualified Data.ByteString.Lazy as B
--   
-- -- Original GHC implementation by Bryan O'Sullivan. Rewritten to use -- UArray by Simon Marlow. Rewritten to support slices and use -- ForeignPtr by David Roundy. Rewritten again and extended by Don -- Stewart and Duncan Coutts. Lazy variant by Duncan Coutts and Don -- Stewart. module Data.ByteString.Lazy -- | A space-efficient representation of a Word8 vector, supporting -- many efficient operations. -- -- A lazy ByteString contains 8-bit bytes, or by using the -- operations from Data.ByteString.Lazy.Char8 it can be -- interpreted as containing 8-bit characters. data ByteString -- | O(1) The empty ByteString empty :: ByteString -- | O(1) Convert a Word8 into a ByteString singleton :: Word8 -> ByteString -- | O(n) Convert a '[Word8]' into a ByteString. pack :: [Word8] -> ByteString -- | O(n) Converts a ByteString to a '[Word8]'. unpack :: ByteString -> [Word8] -- | O(1) Convert a strict ByteString into a lazy -- ByteString. fromStrict :: ByteString -> ByteString -- | O(n) Convert a lazy ByteString into a strict -- ByteString. -- -- Note that this is an expensive operation that forces the whole -- lazy ByteString into memory and then copies all the data. If possible, -- try to avoid converting back and forth between strict and lazy -- bytestrings. toStrict :: ByteString -> ByteString -- | O(c) Convert a list of strict ByteString into a lazy -- ByteString fromChunks :: [ByteString] -> ByteString -- | O(c) Convert a lazy ByteString into a list of strict -- ByteString toChunks :: ByteString -> [ByteString] -- | Consume the chunks of a lazy ByteString with a natural right fold. foldrChunks :: (ByteString -> a -> a) -> a -> ByteString -> a -- | Consume the chunks of a lazy ByteString with a strict, tail-recursive, -- accumulating left fold. foldlChunks :: (a -> ByteString -> a) -> a -> ByteString -> a -- | O(1) cons is analogous to '(:)' for lists. cons :: Word8 -> ByteString -> ByteString -- | O(1) Unlike cons, 'cons\'' is strict in the ByteString -- that we are consing onto. More precisely, it forces the head and the -- first chunk. It does this because, for space efficiency, it may -- coalesce the new byte onto the first 'chunk' rather than starting a -- new 'chunk'. -- -- So that means you can't use a lazy recursive contruction like this: -- --
--   let xs = cons\' c xs in xs
--   
-- -- You can however use cons, as well as repeat and -- cycle, to build infinite lazy ByteStrings. cons' :: Word8 -> ByteString -> ByteString -- | O(n/c) Append a byte to the end of a ByteString snoc :: ByteString -> Word8 -> ByteString -- | O(n/c) Append two ByteStrings append :: ByteString -> ByteString -> ByteString -- | O(1) Extract the first element of a ByteString, which must be -- non-empty. head :: ByteString -> Word8 -- | O(1) Extract the head and tail of a ByteString, returning -- Nothing if it is empty. uncons :: ByteString -> Maybe (Word8, ByteString) -- | O(n/c) Extract the init and last of a ByteString, -- returning Nothing if it is empty. -- -- unsnoc :: ByteString -> Maybe (ByteString, Word8) -- | O(n/c) Extract the last element of a ByteString, which must be -- finite and non-empty. last :: ByteString -> Word8 -- | O(1) Extract the elements after the head of a ByteString, which -- must be non-empty. tail :: ByteString -> ByteString -- | O(n/c) Return all the elements of a ByteString except -- the last one. init :: ByteString -> ByteString -- | O(1) Test whether a ByteString is empty. null :: ByteString -> Bool -- | O(n/c) length returns the length of a ByteString as an -- Int64 length :: ByteString -> Int64 -- | O(n) map f xs is the ByteString obtained by -- applying f to each element of xs. map :: (Word8 -> Word8) -> ByteString -> ByteString -- | O(n) reverse xs returns the elements of -- xs in reverse order. reverse :: ByteString -> ByteString -- | The intersperse function takes a Word8 and a -- ByteString and `intersperses' that byte between the elements of -- the ByteString. It is analogous to the intersperse function on -- Lists. intersperse :: Word8 -> ByteString -> ByteString -- | O(n) The intercalate function takes a ByteString -- and a list of ByteStrings and concatenates the list after -- interspersing the first argument between each element of the list. intercalate :: ByteString -> [ByteString] -> ByteString -- | The transpose function transposes the rows and columns of its -- ByteString argument. transpose :: [ByteString] -> [ByteString] -- | foldl, applied to a binary operator, a starting value -- (typically the left-identity of the operator), and a ByteString, -- reduces the ByteString using the binary operator, from left to right. foldl :: (a -> Word8 -> a) -> a -> ByteString -> a -- | 'foldl\'' is like foldl, but strict in the accumulator. foldl' :: (a -> Word8 -> a) -> a -> ByteString -> a -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty ByteStrings. foldl1 :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8 -- | 'foldl1\'' is like foldl1, but strict in the accumulator. foldl1' :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8 -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a ByteString, -- reduces the ByteString using the binary operator, from right to left. foldr :: (Word8 -> a -> a) -> a -> ByteString -> a -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty ByteStrings foldr1 :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8 -- | O(n) Concatenate a list of ByteStrings. concat :: [ByteString] -> ByteString -- | Map a function over a ByteString and concatenate the results concatMap :: (Word8 -> ByteString) -> ByteString -> ByteString -- | O(n) Applied to a predicate and a ByteString, any -- determines if any element of the ByteString satisfies the -- predicate. any :: (Word8 -> Bool) -> ByteString -> Bool -- | O(n) Applied to a predicate and a ByteString, all -- determines if all elements of the ByteString satisfy the -- predicate. all :: (Word8 -> Bool) -> ByteString -> Bool -- | O(n) maximum returns the maximum value from a -- ByteString maximum :: ByteString -> Word8 -- | O(n) minimum returns the minimum value from a -- ByteString minimum :: ByteString -> Word8 -- | scanl is similar to foldl, but returns a list of -- successive reduced values from the left. This function will fuse. -- --
--   scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
--   
-- -- Note that -- --
--   last (scanl f z xs) == foldl f z xs.
--   
scanl :: (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a -- ByteString, passing an accumulating parameter from left to right, and -- returning a final value of this accumulator together with the new -- ByteString. mapAccumL :: (acc -> Word8 -> (acc, Word8)) -> acc -> ByteString -> (acc, ByteString) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a -- ByteString, passing an accumulating parameter from right to left, and -- returning a final value of this accumulator together with the new -- ByteString. mapAccumR :: (acc -> Word8 -> (acc, Word8)) -> acc -> ByteString -> (acc, ByteString) -- | repeat x is an infinite ByteString, with x -- the value of every element. repeat :: Word8 -> ByteString -- | O(n) replicate n x is a ByteString of length -- n with x the value of every element. replicate :: Int64 -> Word8 -> ByteString -- | cycle ties a finite ByteString into a circular one, or -- equivalently, the infinite repetition of the original ByteString. cycle :: ByteString -> ByteString -- | iterate f x returns an infinite ByteString of repeated -- applications of f to x: -- --
--   iterate f x == [x, f x, f (f x), ...]
--   
iterate :: (Word8 -> Word8) -> Word8 -> ByteString -- | O(n) The unfoldr function is analogous to the List -- 'unfoldr'. unfoldr builds a ByteString from a seed value. The -- function takes the element and returns Nothing if it is done -- producing the ByteString or returns Just (a,b), in -- which case, a is a prepending to the ByteString and -- b is used as the next element in a recursive call. unfoldr :: (a -> Maybe (Word8, a)) -> a -> ByteString -- | O(n/c) take n, applied to a ByteString -- xs, returns the prefix of xs of length n, -- or xs itself if n > length xs. take :: Int64 -> ByteString -> ByteString -- | O(n/c) drop n xs returns the suffix of -- xs after the first n elements, or [] if -- n > length xs. drop :: Int64 -> ByteString -> ByteString -- | O(n/c) splitAt n xs is equivalent to -- (take n xs, drop n xs). splitAt :: Int64 -> ByteString -> (ByteString, ByteString) -- | takeWhile, applied to a predicate p and a ByteString -- xs, returns the longest prefix (possibly empty) of -- xs of elements that satisfy p. takeWhile :: (Word8 -> Bool) -> ByteString -> ByteString -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs. dropWhile :: (Word8 -> Bool) -> ByteString -> ByteString -- | span p xs breaks the ByteString into two segments. It -- is equivalent to (takeWhile p xs, dropWhile p -- xs) span :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) -- | break p is equivalent to span (not . -- p). break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) -- | The group function takes a ByteString and returns a list of -- ByteStrings such that the concatenation of the result is equal to the -- argument. Moreover, each sublist in the result contains only equal -- elements. For example, -- --
--   group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]
--   
-- -- It is a special case of groupBy, which allows the programmer to -- supply their own equality test. group :: ByteString -> [ByteString] -- | The groupBy function is the non-overloaded version of -- group. groupBy :: (Word8 -> Word8 -> Bool) -> ByteString -> [ByteString] -- | O(n) Return all initial segments of the given -- ByteString, shortest first. inits :: ByteString -> [ByteString] -- | O(n) Return all final segments of the given ByteString, -- longest first. tails :: ByteString -> [ByteString] -- | O(n) Break a ByteString into pieces separated by the -- byte argument, consuming the delimiter. I.e. -- --
--   split '\n' "a\nb\nd\ne" == ["a","b","d","e"]
--   split 'a'  "aXaXaXa"    == ["","X","X","X",""]
--   split 'x'  "x"          == ["",""]
--   
-- -- and -- --
--   intercalate [c] . split c == id
--   split == splitWith . (==)
--   
-- -- As for all splitting functions in this library, this function does not -- copy the substrings, it just constructs new ByteStrings that -- are slices of the original. split :: Word8 -> ByteString -> [ByteString] -- | O(n) Splits a ByteString 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 (=='a') "aabbaca" == ["","","bb","c",""]
--   splitWith (=='a') []        == []
--   
splitWith :: (Word8 -> Bool) -> ByteString -> [ByteString] -- | O(n) The isPrefixOf function takes two ByteStrings and -- returns True iff the first is a prefix of the second. isPrefixOf :: ByteString -> ByteString -> Bool -- | O(n) The isSuffixOf function takes two ByteStrings and -- returns True iff the first is a suffix of the second. -- -- The following holds: -- --
--   isSuffixOf x y == reverse x `isPrefixOf` reverse y
--   
isSuffixOf :: ByteString -> ByteString -> Bool -- | O(n) elem is the ByteString membership predicate. elem :: Word8 -> ByteString -> Bool -- | O(n) notElem is the inverse of elem notElem :: Word8 -> ByteString -> Bool -- | O(n) The find function takes a predicate and a -- ByteString, 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
--   
find :: (Word8 -> Bool) -> ByteString -> Maybe Word8 -- | O(n) filter, applied to a predicate and a ByteString, -- returns a ByteString containing those characters that satisfy the -- predicate. filter :: (Word8 -> Bool) -> ByteString -> ByteString -- | O(n) The partition function takes a predicate a -- ByteString and returns the pair of ByteStrings with elements which do -- and do not satisfy the predicate, respectively; i.e., -- --
--   partition p bs == (filter p xs, filter (not . p) xs)
--   
partition :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString) -- | O(c) ByteString index (subscript) operator, starting -- from 0. index :: ByteString -> Int64 -> Word8 -- | O(n) The elemIndex function returns the index of the -- first element in the given ByteString which is equal to the -- query element, or Nothing if there is no such element. This -- implementation uses memchr(3). elemIndex :: Word8 -> ByteString -> Maybe Int64 -- | O(n) The elemIndexEnd function returns the last index of -- the element in the given ByteString which is equal to the query -- element, or Nothing if there is no such element. The following -- holds: -- --
--   elemIndexEnd c xs ==
--   (-) (length xs - 1) `fmap` elemIndex c (reverse xs)
--   
elemIndexEnd :: Word8 -> ByteString -> Maybe Int64 -- | O(n) The elemIndices function extends elemIndex, -- by returning the indices of all elements equal to the query element, -- in ascending order. This implementation uses memchr(3). elemIndices :: Word8 -> ByteString -> [Int64] -- | The findIndex function takes a predicate and a -- ByteString and returns the index of the first element in the -- ByteString satisfying the predicate. findIndex :: (Word8 -> Bool) -> ByteString -> Maybe Int64 -- | The findIndices function extends findIndex, by returning -- the indices of all elements satisfying the predicate, in ascending -- order. findIndices :: (Word8 -> Bool) -> ByteString -> [Int64] -- | count returns the number of times its argument appears in the -- ByteString -- --
--   count = length . elemIndices
--   
-- -- But more efficiently than using length on the intermediate list. count :: Word8 -> ByteString -> Int64 -- | O(n) zip takes two ByteStrings and returns a list of -- corresponding pairs of bytes. If one input ByteString is short, excess -- elements of the longer ByteString are discarded. This is equivalent to -- a pair of unpack operations. zip :: ByteString -> ByteString -> [(Word8, Word8)] -- | zipWith generalises zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, zipWith (+) is applied to two ByteStrings to -- produce the list of corresponding sums. zipWith :: (Word8 -> Word8 -> a) -> ByteString -> ByteString -> [a] -- | O(n) unzip transforms a list of pairs of bytes into a -- pair of ByteStrings. Note that this performs two pack -- operations. unzip :: [(Word8, Word8)] -> (ByteString, ByteString) -- | O(n) Make a copy of the ByteString with its own storage. -- This is mainly useful to allow the rest of the data pointed to by the -- ByteString to be garbage collected, for example if a large -- string has been read in, and only a small part of it is needed in the -- rest of the program. copy :: ByteString -> ByteString -- | getContents. Equivalent to hGetContents stdin. Will read lazily getContents :: IO ByteString -- | Write a ByteString to stdout putStr :: ByteString -> IO () -- | Write a ByteString to stdout, appending a newline byte -- | Deprecated: Use Data.ByteString.Lazy.Char8.putStrLn instead. -- (Functions that rely on ASCII encodings belong in -- Data.ByteString.Lazy.Char8) putStrLn :: ByteString -> IO () -- | The interact function takes a function of type ByteString -> -- ByteString as its argument. The entire input from the standard -- input device is passed to this function as its argument, and the -- resulting string is output on the standard output device. interact :: (ByteString -> ByteString) -> IO () -- | Read an entire file lazily into a ByteString. The Handle -- will be held open until EOF is encountered. readFile :: FilePath -> IO ByteString -- | Write a ByteString to a file. writeFile :: FilePath -> ByteString -> IO () -- | Append a ByteString to a file. appendFile :: FilePath -> ByteString -> IO () -- | Read entire handle contents lazily into a ByteString. -- Chunks are read on demand, using the default chunk size. -- -- Once EOF is encountered, the Handle is closed. -- -- Note: the Handle should be placed in binary mode with -- hSetBinaryMode for hGetContents to work correctly. hGetContents :: Handle -> IO ByteString -- | Read n bytes into a ByteString, directly from the -- specified Handle. hGet :: Handle -> Int -> IO ByteString -- | hGetNonBlocking is similar to hGet, except that it will never -- block waiting for data to become available, instead it returns only -- whatever data is available. If there is no data available to be read, -- hGetNonBlocking returns empty. -- -- Note: on Windows and with Haskell implementation other than GHC, this -- function does not work correctly; it behaves identically to -- hGet. hGetNonBlocking :: Handle -> Int -> IO ByteString -- | Outputs a ByteString to the specified Handle. hPut :: Handle -> ByteString -> IO () -- | Similar to hPut except that it will never block. Instead it -- returns any tail that did not get written. This tail may be -- empty in the case that the whole string was written, or the -- whole original string if nothing was written. Partial writes are also -- possible. -- -- Note: on Windows and with Haskell implementation other than GHC, this -- function does not work correctly; it behaves identically to -- hPut. hPutNonBlocking :: Handle -> ByteString -> IO ByteString -- | A synonym for hPut, for compatibility hPutStr :: Handle -> ByteString -> IO () -- | Manipulate lazy ByteStrings using Char -- operations. All Chars will be truncated to 8 bits. It can be expected -- that these functions will run at identical speeds to their -- Word8 equivalents in Data.ByteString.Lazy. -- -- This module is intended to be imported qualified, to avoid -- name clashes with Prelude functions. eg. -- --
--   import qualified Data.ByteString.Lazy.Char8 as C
--   
-- -- The Char8 interface to bytestrings provides an instance of IsString -- for the ByteString type, enabling you to use string literals, and have -- them implicitly packed to ByteStrings. Use {-# LANGUAGE -- OverloadedStrings #-} to enable this. module Data.ByteString.Lazy.Char8 -- | A space-efficient representation of a Word8 vector, supporting -- many efficient operations. -- -- A lazy ByteString contains 8-bit bytes, or by using the -- operations from Data.ByteString.Lazy.Char8 it can be -- interpreted as containing 8-bit characters. data ByteString -- | O(1) The empty ByteString empty :: ByteString -- | O(1) Convert a Char into a ByteString singleton :: Char -> ByteString -- | O(n) Convert a String into a ByteString. pack :: [Char] -> ByteString -- | O(n) Converts a ByteString to a String. unpack :: ByteString -> [Char] -- | O(c) Convert a list of strict ByteString into a lazy -- ByteString fromChunks :: [ByteString] -> ByteString -- | O(c) Convert a lazy ByteString into a list of strict -- ByteString toChunks :: ByteString -> [ByteString] -- | O(1) Convert a strict ByteString into a lazy -- ByteString. fromStrict :: ByteString -> ByteString -- | O(n) Convert a lazy ByteString into a strict -- ByteString. -- -- Note that this is an expensive operation that forces the whole -- lazy ByteString into memory and then copies all the data. If possible, -- try to avoid converting back and forth between strict and lazy -- bytestrings. toStrict :: ByteString -> ByteString -- | O(1) cons is analogous to '(:)' for lists. cons :: Char -> ByteString -> ByteString -- | O(1) Unlike cons, 'cons\'' is strict in the ByteString -- that we are consing onto. More precisely, it forces the head and the -- first chunk. It does this because, for space efficiency, it may -- coalesce the new byte onto the first 'chunk' rather than starting a -- new 'chunk'. -- -- So that means you can't use a lazy recursive contruction like this: -- --
--   let xs = cons\' c xs in xs
--   
-- -- You can however use cons, as well as repeat and -- cycle, to build infinite lazy ByteStrings. cons' :: Char -> ByteString -> ByteString -- | O(n) Append a Char to the end of a ByteString. Similar -- to cons, this function performs a memcpy. snoc :: ByteString -> Char -> ByteString -- | O(n/c) Append two ByteStrings append :: ByteString -> ByteString -> ByteString -- | O(1) Extract the first element of a ByteString, which must be -- non-empty. head :: ByteString -> Char -- | O(1) Extract the head and tail of a ByteString, returning -- Nothing if it is empty. uncons :: ByteString -> Maybe (Char, ByteString) -- | O(1) Extract the last element of a packed string, which must be -- non-empty. last :: ByteString -> Char -- | O(1) Extract the elements after the head of a ByteString, which -- must be non-empty. tail :: ByteString -> ByteString -- | O(n/c) Extract the init and last of a ByteString, -- returning Nothing if it is empty. unsnoc :: ByteString -> Maybe (ByteString, Char) -- | O(n/c) Return all the elements of a ByteString except -- the last one. init :: ByteString -> ByteString -- | O(1) Test whether a ByteString is empty. null :: ByteString -> Bool -- | O(n/c) length returns the length of a ByteString as an -- Int64 length :: ByteString -> Int64 -- | O(n) map f xs is the ByteString obtained by -- applying f to each element of xs map :: (Char -> Char) -> ByteString -> ByteString -- | O(n) reverse xs returns the elements of -- xs in reverse order. reverse :: ByteString -> ByteString -- | O(n) The intersperse function takes a Char and a -- ByteString and `intersperses' that Char between the elements of -- the ByteString. It is analogous to the intersperse function on -- Lists. intersperse :: Char -> ByteString -> ByteString -- | O(n) The intercalate function takes a ByteString -- and a list of ByteStrings and concatenates the list after -- interspersing the first argument between each element of the list. intercalate :: ByteString -> [ByteString] -> ByteString -- | The transpose function transposes the rows and columns of its -- ByteString argument. transpose :: [ByteString] -> [ByteString] -- | foldl, applied to a binary operator, a starting value -- (typically the left-identity of the operator), and a ByteString, -- reduces the ByteString using the binary operator, from left to right. foldl :: (a -> Char -> a) -> a -> ByteString -> a -- | 'foldl\'' is like foldl, but strict in the accumulator. foldl' :: (a -> Char -> a) -> a -> ByteString -> a -- | foldl1 is a variant of foldl that has no starting value -- argument, and thus must be applied to non-empty ByteStrings. foldl1 :: (Char -> Char -> Char) -> ByteString -> Char -- | 'foldl1\'' is like foldl1, but strict in the accumulator. foldl1' :: (Char -> Char -> Char) -> ByteString -> Char -- | foldr, applied to a binary operator, a starting value -- (typically the right-identity of the operator), and a packed string, -- reduces the packed string using the binary operator, from right to -- left. foldr :: (Char -> a -> a) -> a -> ByteString -> a -- | foldr1 is a variant of foldr that has no starting value -- argument, and thus must be applied to non-empty ByteStrings foldr1 :: (Char -> Char -> Char) -> ByteString -> Char -- | O(n) Concatenate a list of ByteStrings. concat :: [ByteString] -> ByteString -- | Map a function over a ByteString and concatenate the results concatMap :: (Char -> ByteString) -> ByteString -> ByteString -- | Applied to a predicate and a ByteString, any determines if any -- element of the ByteString satisfies the predicate. any :: (Char -> Bool) -> ByteString -> Bool -- | Applied to a predicate and a ByteString, all determines -- if all elements of the ByteString satisfy the predicate. all :: (Char -> Bool) -> ByteString -> Bool -- | maximum returns the maximum value from a ByteString maximum :: ByteString -> Char -- | minimum returns the minimum value from a ByteString minimum :: ByteString -> Char -- | scanl is similar to foldl, but returns a list of -- successive reduced values from the left. This function will fuse. -- --
--   scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
--   
-- -- Note that -- --
--   last (scanl f z xs) == foldl f z xs.
--   
scanl :: (Char -> Char -> Char) -> Char -> ByteString -> ByteString -- | The mapAccumL function behaves like a combination of map -- and foldl; it applies a function to each element of a -- ByteString, passing an accumulating parameter from left to right, and -- returning a final value of this accumulator together with the new -- ByteString. mapAccumL :: (acc -> Char -> (acc, Char)) -> acc -> ByteString -> (acc, ByteString) -- | The mapAccumR function behaves like a combination of map -- and foldr; it applies a function to each element of a -- ByteString, passing an accumulating parameter from right to left, and -- returning a final value of this accumulator together with the new -- ByteString. mapAccumR :: (acc -> Char -> (acc, Char)) -> acc -> ByteString -> (acc, ByteString) -- | repeat x is an infinite ByteString, with x -- the value of every element. repeat :: Char -> ByteString -- | O(n) replicate n x is a ByteString of length -- n with x the value of every element. replicate :: Int64 -> Char -> ByteString -- | cycle ties a finite ByteString into a circular one, or -- equivalently, the infinite repetition of the original ByteString. cycle :: ByteString -> ByteString -- | iterate f x returns an infinite ByteString of repeated -- applications of f to x: -- --
--   iterate f x == [x, f x, f (f x), ...]
--   
iterate :: (Char -> Char) -> Char -> ByteString -- | O(n) The unfoldr function is analogous to the List -- 'unfoldr'. unfoldr builds a ByteString from a seed value. The -- function takes the element and returns Nothing if it is done -- producing the ByteString or returns Just (a,b), in -- which case, a is a prepending to the ByteString and -- b is used as the next element in a recursive call. unfoldr :: (a -> Maybe (Char, a)) -> a -> ByteString -- | O(n/c) take n, applied to a ByteString -- xs, returns the prefix of xs of length n, -- or xs itself if n > length xs. take :: Int64 -> ByteString -> ByteString -- | O(n/c) drop n xs returns the suffix of -- xs after the first n elements, or [] if -- n > length xs. drop :: Int64 -> ByteString -> ByteString -- | O(n/c) splitAt n xs is equivalent to -- (take n xs, drop n xs). splitAt :: Int64 -> ByteString -> (ByteString, ByteString) -- | takeWhile, applied to a predicate p and a ByteString -- xs, returns the longest prefix (possibly empty) of -- xs of elements that satisfy p. takeWhile :: (Char -> Bool) -> ByteString -> ByteString -- | dropWhile p xs returns the suffix remaining after -- takeWhile p xs. dropWhile :: (Char -> Bool) -> ByteString -> ByteString -- | span p xs breaks the ByteString into two segments. It -- is equivalent to (takeWhile p xs, dropWhile p -- xs) span :: (Char -> Bool) -> ByteString -> (ByteString, ByteString) -- | break p is equivalent to span (not . -- p). break :: (Char -> Bool) -> ByteString -> (ByteString, ByteString) -- | The group function takes a ByteString and returns a list of -- ByteStrings such that the concatenation of the result is equal to the -- argument. Moreover, each sublist in the result contains only equal -- elements. For example, -- --
--   group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]
--   
-- -- It is a special case of groupBy, which allows the programmer to -- supply their own equality test. group :: ByteString -> [ByteString] -- | The groupBy function is the non-overloaded version of -- group. groupBy :: (Char -> Char -> Bool) -> ByteString -> [ByteString] -- | O(n) Return all initial segments of the given -- ByteString, shortest first. inits :: ByteString -> [ByteString] -- | O(n) Return all final segments of the given ByteString, -- longest first. tails :: ByteString -> [ByteString] -- | O(n) Break a ByteString into pieces separated by the -- byte argument, consuming the delimiter. I.e. -- --
--   split '\n' "a\nb\nd\ne" == ["a","b","d","e"]
--   split 'a'  "aXaXaXa"    == ["","X","X","X"]
--   split 'x'  "x"          == ["",""]
--   
-- -- and -- --
--   intercalate [c] . split c == id
--   split == splitWith . (==)
--   
-- -- As for all splitting functions in this library, this function does not -- copy the substrings, it just constructs new ByteStrings that -- are slices of the original. split :: Char -> ByteString -> [ByteString] -- | O(n) Splits a ByteString 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 (=='a') "aabbaca" == ["","","bb","c",""]
--   
splitWith :: (Char -> Bool) -> ByteString -> [ByteString] -- | lines breaks a ByteString up into a list of ByteStrings at -- newline Chars. The resulting strings do not contain newlines. -- -- As of bytestring 0.9.0.3, this function is stricter than its list -- cousin. lines :: ByteString -> [ByteString] -- | words breaks a ByteString up into a list of words, which were -- delimited by Chars representing white space. And -- --
--   tokens isSpace = words
--   
words :: ByteString -> [ByteString] -- | unlines is an inverse operation to lines. It joins -- lines, after appending a terminating newline to each. unlines :: [ByteString] -> ByteString -- | The unwords function is analogous to the unlines -- function, on words. unwords :: [ByteString] -> ByteString -- | O(n) The isPrefixOf function takes two ByteStrings and -- returns True iff the first is a prefix of the second. isPrefixOf :: ByteString -> ByteString -> Bool -- | O(n) The isSuffixOf function takes two ByteStrings and -- returns True iff the first is a suffix of the second. -- -- The following holds: -- --
--   isSuffixOf x y == reverse x `isPrefixOf` reverse y
--   
isSuffixOf :: ByteString -> ByteString -> Bool -- | O(n) elem is the ByteString membership predicate. -- This implementation uses memchr(3). elem :: Char -> ByteString -> Bool -- | O(n) notElem is the inverse of elem notElem :: Char -> ByteString -> Bool -- | O(n) The find function takes a predicate and a -- ByteString, and returns the first element in matching the predicate, -- or Nothing if there is no such element. find :: (Char -> Bool) -> ByteString -> Maybe Char -- | O(n) filter, applied to a predicate and a ByteString, -- returns a ByteString containing those characters that satisfy the -- predicate. filter :: (Char -> Bool) -> ByteString -> ByteString -- | O(1) ByteString index (subscript) operator, starting -- from 0. index :: ByteString -> Int64 -> Char -- | O(n) The elemIndex function returns the index of the -- first element in the given ByteString which is equal (by -- memchr) to the query element, or Nothing if there is no such -- element. elemIndex :: Char -> ByteString -> Maybe Int64 -- | O(n) The elemIndices function extends elemIndex, -- by returning the indices of all elements equal to the query element, -- in ascending order. elemIndices :: Char -> ByteString -> [Int64] -- | The findIndex function takes a predicate and a -- ByteString and returns the index of the first element in the -- ByteString satisfying the predicate. findIndex :: (Char -> Bool) -> ByteString -> Maybe Int64 -- | The findIndices function extends findIndex, by returning -- the indices of all elements satisfying the predicate, in ascending -- order. findIndices :: (Char -> Bool) -> ByteString -> [Int64] -- | count returns the number of times its argument appears in the -- ByteString -- --
--   count      == length . elemIndices
--   count '\n' == length . lines
--   
-- -- But more efficiently than using length on the intermediate list. count :: Char -> ByteString -> Int64 -- | O(n) zip takes two ByteStrings and returns a list of -- corresponding pairs of Chars. If one input ByteString is short, excess -- elements of the longer ByteString are discarded. This is equivalent to -- a pair of unpack operations, and so space usage may be large -- for multi-megabyte ByteStrings zip :: ByteString -> ByteString -> [(Char, Char)] -- | zipWith generalises zip by zipping with the function -- given as the first argument, instead of a tupling function. For -- example, zipWith (+) is applied to two ByteStrings to -- produce the list of corresponding sums. zipWith :: (Char -> Char -> a) -> ByteString -> ByteString -> [a] -- | O(n) Make a copy of the ByteString with its own storage. -- This is mainly useful to allow the rest of the data pointed to by the -- ByteString to be garbage collected, for example if a large -- string has been read in, and only a small part of it is needed in the -- rest of the program. copy :: ByteString -> ByteString -- | readInt reads an Int from the beginning of the ByteString. If there is -- no integer at the beginning of the string, it returns Nothing, -- otherwise it just returns the int read, and the rest of the string. readInt :: ByteString -> Maybe (Int, ByteString) -- | readInteger reads an Integer from the beginning of the ByteString. If -- there is no integer at the beginning of the string, it returns -- Nothing, otherwise it just returns the int read, and the rest of the -- string. readInteger :: ByteString -> Maybe (Integer, ByteString) -- | getContents. Equivalent to hGetContents stdin. Will read lazily getContents :: IO ByteString -- | Write a ByteString to stdout putStr :: ByteString -> IO () -- | Write a ByteString to stdout, appending a newline byte putStrLn :: ByteString -> IO () -- | The interact function takes a function of type ByteString -> -- ByteString as its argument. The entire input from the standard -- input device is passed to this function as its argument, and the -- resulting string is output on the standard output device. interact :: (ByteString -> ByteString) -> IO () -- | Read an entire file lazily into a ByteString. readFile :: FilePath -> IO ByteString -- | Write a ByteString to a file. writeFile :: FilePath -> ByteString -> IO () -- | Append a ByteString to a file. appendFile :: FilePath -> ByteString -> IO () -- | Read entire handle contents lazily into a ByteString. -- Chunks are read on demand, using the default chunk size. -- -- Once EOF is encountered, the Handle is closed. -- -- Note: the Handle should be placed in binary mode with -- hSetBinaryMode for hGetContents to work correctly. hGetContents :: Handle -> IO ByteString -- | Read n bytes into a ByteString, directly from the -- specified Handle. hGet :: Handle -> Int -> IO ByteString -- | hGetNonBlocking is similar to hGet, except that it will never -- block waiting for data to become available, instead it returns only -- whatever data is available. If there is no data available to be read, -- hGetNonBlocking returns empty. -- -- Note: on Windows and with Haskell implementation other than GHC, this -- function does not work correctly; it behaves identically to -- hGet. hGetNonBlocking :: Handle -> Int -> IO ByteString -- | Outputs a ByteString to the specified Handle. hPut :: Handle -> ByteString -> IO () -- | Similar to hPut except that it will never block. Instead it -- returns any tail that did not get written. This tail may be -- empty in the case that the whole string was written, or the -- whole original string if nothing was written. Partial writes are also -- possible. -- -- Note: on Windows and with Haskell implementation other than GHC, this -- function does not work correctly; it behaves identically to -- hPut. hPutNonBlocking :: Handle -> ByteString -> IO ByteString -- | A synonym for hPut, for compatibility hPutStr :: Handle -> ByteString -> IO () -- | Write a ByteString to a handle, appending a newline byte hPutStrLn :: Handle -> ByteString -> IO () -- | This module provides Builder primitives, which are lower -- level building blocks for constructing Builders. You don't need -- to go down to this level but it can be slightly faster. -- -- Morally, builder primitives are like functions a -> -- Builder, that is they take a value and encode it as a sequence of -- bytes, represented as a Builder. Of course their implementation -- is a bit more specialised. -- -- Builder primitives come in two forms: fixed-size and bounded-size. -- -- -- -- Note that fixed primitives can be considered as a special case of -- bounded primitives, and we can lift from fixed to bounded. -- -- Because bounded primitives are the more general case, in this -- documentation we only refer to fixed size primitives where it matters -- that the resulting sequence of bytes is of a fixed length. Otherwise, -- we just refer to bounded size primitives. -- -- The purpose of using builder primitives is to improve the performance -- of Builders. These improvements stem from making the two most -- common steps performed by a Builder more efficient. We explain -- these two steps in turn. -- -- The first most common step is the concatenation of two -- Builders. Internally, concatenation corresponds to function -- composition. (Note that Builders can be seen as -- difference-lists of buffer-filling functions; cf. -- http://hackage.haskell.org/cgi-bin/hackage-scripts/package/dlist. -- ) Function composition is a fast O(1) operation. However, we -- can use bounded primitives to remove some of these function -- compositions altogether, which is more efficient. -- -- The second most common step performed by a Builder is to fill a -- buffer using a bounded primitives, which works as follows. The -- Builder checks whether there is enough space left to execute -- the bounded primitive. If there is, then the Builder executes -- the bounded primitive and calls the next Builder with the -- updated buffer. Otherwise, the Builder signals its driver that -- it requires a new buffer. This buffer must be at least as large as the -- bound of the primitive. We can use bounded primitives to reduce the -- number of buffer-free checks by fusing the buffer-free checks of -- consecutive Builders. We can also use bounded primitives to -- simplify the control flow for signalling that a buffer is full by -- ensuring that we check first that there is enough space left and only -- then decide on how to encode a given value. -- -- Let us illustrate these improvements on the CSV-table rendering -- example from Data.ByteString.Builder. Its "hot code" is the -- rendering of a table's cells, which we implement as follows using only -- the functions from the Builder API. -- --
--   import Data.ByteString.Builder as B
--   
--   renderCell :: Cell -> Builder
--   renderCell (StringC cs) = renderString cs
--   renderCell (IntC i)     = B.intDec i
--   
--   renderString :: String -> Builder
--   renderString cs = B.charUtf8 '"' <> foldMap escape cs <> B.charUtf8 '"'
--     where
--       escape '\\' = B.charUtf8 '\\' <> B.charUtf8 '\\'
--       escape '\"' = B.charUtf8 '\\' <> B.charUtf8 '\"'
--       escape c    = B.charUtf8 c
--   
-- -- Efficient encoding of Ints as decimal numbers is performed by -- intDec. Optimization potential exists for the escaping of -- Strings. The above implementation has two optimization -- opportunities. First, the buffer-free checks of the Builders -- for escaping double quotes and backslashes can be fused. Second, the -- concatenations performed by foldMap can be eliminated. The -- following implementation exploits these optimizations. -- --
--   import qualified Data.ByteString.Builder.Prim  as P
--   import           Data.ByteString.Builder.Prim
--                    ( condB, liftFixedToBounded, (>*<), (>$<) )
--   
--   renderString :: String -> Builder
--   renderString cs =
--       B.charUtf8 '"' <> E.encodeListWithB escape cs <> B.charUtf8 '"'
--     where
--       escape :: E.BoundedPrim Char
--       escape =
--         condB (== '\\') (fixed2 ('\\', '\\')) $
--         condB (== '\"') (fixed2 ('\\', '\"')) $
--         E.charUtf8
--        
--       {-# INLINE fixed2 #-}
--       fixed2 x = liftFixedToBounded $ const x >$< E.char7 >*< E.char7
--   
-- -- The code should be mostly self-explanatory. The slightly awkward -- syntax is because the combinators are written such that the size-bound -- of the resulting BoundedPrim can be computed at compile time. -- We also explicitly inline the fixed2 primitive, which encodes -- a fixed tuple of characters, to ensure that the bound computation -- happens at compile time. When encoding the following list of -- Strings, the optimized implementation of renderString -- is two times faster. -- --
--   maxiStrings :: [String]
--   maxiStrings = take 1000 $ cycle ["hello", "\"1\"", "λ-wörld"]
--   
-- -- Most of the performance gain stems from using -- primMapListBounded, which encodes a list of values from -- left-to-right with a BoundedPrim. It exploits the -- Builder internals to avoid unnecessary function compositions -- (i.e., concatenations). In the future, we might expect the compiler to -- perform the optimizations implemented in primMapListBounded. -- However, it seems that the code is currently to complicated for the -- compiler to see through. Therefore, we provide the BoundedPrim -- escape hatch, which allows data structures to provide very efficient -- encoding traversals, like primMapListBounded for lists. -- -- Note that BoundedPrims are a bit verbose, but quite versatile. -- Here is an example of a BoundedPrim for combined HTML escaping -- and UTF-8 encoding. It exploits that the escaped character with the -- maximal Unicode codepoint is '>'. -- --
--   {-# INLINE charUtf8HtmlEscaped #-}
--   charUtf8HtmlEscaped :: E.BoundedPrim Char
--   charUtf8HtmlEscaped =
--       condB (>  '>' ) E.charUtf8 $
--       condB (== '<' ) (fixed4 ('&',('l',('t',';')))) $        -- &lt;
--       condB (== '>' ) (fixed4 ('&',('g',('t',';')))) $        -- &gt;
--       condB (== '&' ) (fixed5 ('&',('a',('m',('p',';'))))) $  -- &amp;
--       condB (== '"' ) (fixed5 ('&',('#',('3',('4',';'))))) $  -- &#34;
--       condB (== '\'') (fixed5 ('&',('#',('3',('9',';'))))) $  -- &#39;
--       (liftFixedToBounded E.char7)         -- fallback for Chars smaller than '>'
--     where
--       {-# INLINE fixed4 #-}
--       fixed4 x = liftFixedToBounded $ const x >$<
--         E.char7 >*< E.char7 >*< E.char7 >*< E.char7
--        
--       {-# INLINE fixed5 #-}
--       fixed5 x = liftFixedToBounded $ const x >$<
--         E.char7 >*< E.char7 >*< E.char7 >*< E.char7 >*< E.char7
--   
-- -- This module currently does not expose functions that require the -- special properties of fixed-size primitives. They are useful for -- prefixing Builders with their size or for implementing chunked -- encodings. We will expose the corresponding functions in future -- releases of this library. module Data.ByteString.Builder.Prim -- | A builder primitive that always results in sequence of bytes that is -- no longer than a pre-determined bound. data BoundedPrim a -- | The BoundedPrim that always results in the zero-length -- sequence. emptyB :: BoundedPrim a -- | A pairing/concatenation operator for builder primitives, both bounded -- and fixed size. -- -- For example, -- --
--   toLazyByteString (primFixed (char7 >*< char7) ('x','y')) = "xy"
--   
-- -- We can combine multiple primitives using >*< multiple -- times. -- --
--   toLazyByteString (primFixed (char7 >*< char7 >*< char7) ('x',('y','z'))) = "xyz"
--   
(>*<) :: Monoidal f => f a -> f b -> f (a, b) -- | A fmap-like operator for builder primitives, both bounded and fixed -- size. -- -- Builder primitives are contravariant so it's like the normal fmap, but -- backwards (look at the type). (If it helps to remember, the operator -- symbol is like ($) but backwards.) -- -- We can use it for example to prepend and/or append fixed values to an -- primitive. -- --
--   showEncoding ((\x -> ('\'', (x, '\''))) >$< fixed3) 'x' = "'x'"
--     where
--       fixed3 = char7 >*< char7 >*< char7
--   
-- -- Note that the rather verbose syntax for composition stems from the -- requirement to be able to compute the size / size bound at compile -- time. (>$<) :: Contravariant f => (b -> a) -> f a -> f b -- | Encode an Either value using the first BoundedPrim for -- Left values and the second BoundedPrim for Right -- values. -- -- Note that the functions eitherB, pairB, and -- contramapB (written below using >$<) suffice to -- construct BoundedPrims for all non-recursive algebraic -- datatypes. For example, -- --
--   maybeB :: BoundedPrim () -> BoundedPrim a -> BoundedPrim (Maybe a)
--   maybeB nothing just = maybe (Left ()) Right >$< eitherB nothing just
--    
--   
eitherB :: BoundedPrim a -> BoundedPrim b -> BoundedPrim (Either a b) -- | Conditionally select a BoundedPrim. For example, we can -- implement the ASCII primitive that drops characters with Unicode -- codepoints above 127 as follows. -- --
--   charASCIIDrop = condB (< '\128') (fromF char7) emptyB
--    
--   
condB :: (a -> Bool) -> BoundedPrim a -> BoundedPrim a -> BoundedPrim a -- | Create a Builder that encodes values with the given -- BoundedPrim. -- -- We rewrite consecutive uses of primBounded such that the -- bound-checks are fused. For example, -- --
--   primBounded (word32 c1) `mappend` primBounded (word32 c2)
--   
-- -- is rewritten such that the resulting Builder checks only once, -- if ther are at 8 free bytes, instead of checking twice, if there are 4 -- free bytes. This optimization is not observationally equivalent in a -- strict sense, as it influences the boundaries of the generated chunks. -- However, for a user of this library it is observationally equivalent, -- as chunk boundaries of a lazy ByteString can only be observed -- through the internal interface. Morevoer, we expect that all -- primitives write much fewer than 4kb (the default short buffer size). -- Hence, it is safe to ignore the additional memory spilled due to the -- more agressive buffer wrapping introduced by this optimization. primBounded :: BoundedPrim a -> (a -> Builder) -- | Create a Builder that encodes a list of values consecutively -- using a BoundedPrim for each element. This function is more -- efficient than the canonical -- --
--   filter p =
--    B.toLazyByteString .
--    E.encodeLazyByteStringWithF (E.ifF p E.word8) E.emptyF)
--   
-- --
--   mconcat . map (primBounded w)
--   
-- -- or -- --
--   foldMap (primBounded w)
--   
-- -- because it moves several variables out of the inner loop. primMapListBounded :: BoundedPrim a -> [a] -> Builder -- | Create a Builder that encodes a sequence generated from a seed -- value using a BoundedPrim for each sequence element. primUnfoldrBounded :: BoundedPrim b -> (a -> Maybe (b, a)) -> a -> Builder -- | Create a Builder that encodes each Word8 of a strict -- ByteString using a BoundedPrim. For example, we can -- write a Builder that filters a strict ByteString as -- follows. -- --
--   import Data.ByteString.Builder.Primas P (word8, condB, emptyB)
--   
-- --
--   filterBS p = P.condB p P.word8 P.emptyB
--   
primMapByteStringBounded :: BoundedPrim Word8 -> ByteString -> Builder -- | Chunk-wise application of primMapByteStringBounded. primMapLazyByteStringBounded :: BoundedPrim Word8 -> ByteString -> Builder -- | A builder primitive that always results in a sequence of bytes of a -- pre-determined, fixed size. data FixedPrim a -- | The FixedPrim that always results in the zero-length sequence. emptyF :: FixedPrim a -- | Lift a FixedPrim to a BoundedPrim. liftFixedToBounded :: FixedPrim a -> BoundedPrim a -- | Encode a value with a FixedPrim. primFixed :: FixedPrim a -> (a -> Builder) -- | Encode a list of values from left-to-right with a FixedPrim. primMapListFixed :: FixedPrim a -> ([a] -> Builder) -- | Encode a list of values represented as an unfoldr with a -- FixedPrim. primUnfoldrFixed :: FixedPrim b -> (a -> Maybe (b, a)) -> a -> Builder -- | Heavy inlining. Encode all bytes of a strict ByteString -- from left-to-right with a FixedPrim. This function is quite -- versatile. For example, we can use it to construct a Builder -- that maps every byte before copying it to the buffer to be filled. -- --
--   mapToBuilder :: (Word8 -> Word8) -> S.ByteString -> Builder
--   mapToBuilder f = encodeByteStringWithF (contramapF f word8)
--   
-- -- We can also use it to hex-encode a strict ByteString as shown -- by the byteStringHex example above. primMapByteStringFixed :: FixedPrim Word8 -> (ByteString -> Builder) -- | Heavy inlining. Encode all bytes of a lazy ByteString -- from left-to-right with a FixedPrim. primMapLazyByteStringFixed :: FixedPrim Word8 -> (ByteString -> Builder) -- | Encoding single signed bytes as-is. int8 :: FixedPrim Int8 -- | Encoding single unsigned bytes as-is. word8 :: FixedPrim Word8 -- | Encoding Int16s in big endian format. int16BE :: FixedPrim Int16 -- | Encoding Int32s in big endian format. int32BE :: FixedPrim Int32 -- | Encoding Int64s in big endian format. int64BE :: FixedPrim Int64 -- | Encoding Word16s in big endian format. word16BE :: FixedPrim Word16 -- | Encoding Word32s in big endian format. word32BE :: FixedPrim Word32 -- | Encoding Word64s in big endian format. word64BE :: FixedPrim Word64 -- | Encode a Float in big endian format. floatBE :: FixedPrim Float -- | Encode a Double in big endian format. doubleBE :: FixedPrim Double -- | Encoding Int16s in little endian format. int16LE :: FixedPrim Int16 -- | Encoding Int32s in little endian format. int32LE :: FixedPrim Int32 -- | Encoding Int64s in little endian format. int64LE :: FixedPrim Int64 -- | Encoding Word16s in little endian format. word16LE :: FixedPrim Word16 -- | Encoding Word32s in little endian format. word32LE :: FixedPrim Word32 -- | Encoding Word64s in little endian format. word64LE :: FixedPrim Word64 -- | Encode a Float in little endian format. floatLE :: FixedPrim Float -- | Encode a Double in little endian format. doubleLE :: FixedPrim Double -- | Encode a single native machine Int. The Ints is encoded -- in host order, host endian form, for the machine you are on. On a 64 -- bit machine the Int is an 8 byte value, on a 32 bit machine, 4 -- bytes. Values encoded this way are not portable to different endian or -- integer sized machines, without conversion. intHost :: FixedPrim Int -- | Encoding Int16s in native host order and host endianness. int16Host :: FixedPrim Int16 -- | Encoding Int32s in native host order and host endianness. int32Host :: FixedPrim Int32 -- | Encoding Int64s in native host order and host endianness. int64Host :: FixedPrim Int64 -- | Encode a single native machine Word. The Words is -- encoded in host order, host endian form, for the machine you are on. -- On a 64 bit machine the Word is an 8 byte value, on a 32 bit -- machine, 4 bytes. Values encoded this way are not portable to -- different endian or word sized machines, without conversion. wordHost :: FixedPrim Word -- | Encoding Word16s in native host order and host endianness. word16Host :: FixedPrim Word16 -- | Encoding Word32s in native host order and host endianness. word32Host :: FixedPrim Word32 -- | Encoding Word64s in native host order and host endianness. word64Host :: FixedPrim Word64 -- | Encode a Float in native host order and host endianness. Values -- written this way are not portable to different endian machines, -- without conversion. floatHost :: FixedPrim Float -- | Encode a Double in native host order and host endianness. doubleHost :: FixedPrim Double -- | Encode the least 7-bits of a Char using the ASCII encoding. char7 :: FixedPrim Char -- | Decimal encoding of an Int8. int8Dec :: BoundedPrim Int8 -- | Decimal encoding of an Int16. int16Dec :: BoundedPrim Int16 -- | Decimal encoding of an Int32. int32Dec :: BoundedPrim Int32 -- | Decimal encoding of an Int64. int64Dec :: BoundedPrim Int64 -- | Decimal encoding of an Int. intDec :: BoundedPrim Int -- | Decimal encoding of a Word8. word8Dec :: BoundedPrim Word8 -- | Decimal encoding of a Word16. word16Dec :: BoundedPrim Word16 -- | Decimal encoding of a Word32. word32Dec :: BoundedPrim Word32 -- | Decimal encoding of a Word64. word64Dec :: BoundedPrim Word64 -- | Decimal encoding of a Word. wordDec :: BoundedPrim Word -- | Hexadecimal encoding of a Word8. word8Hex :: BoundedPrim Word8 -- | Hexadecimal encoding of a Word16. word16Hex :: BoundedPrim Word16 -- | Hexadecimal encoding of a Word32. word32Hex :: BoundedPrim Word32 -- | Hexadecimal encoding of a Word64. word64Hex :: BoundedPrim Word64 -- | Hexadecimal encoding of a Word. wordHex :: BoundedPrim Word -- | Encode a Int8 using 2 nibbles (hexadecimal digits). int8HexFixed :: FixedPrim Int8 -- | Encode a Int16 using 4 nibbles. int16HexFixed :: FixedPrim Int16 -- | Encode a Int32 using 8 nibbles. int32HexFixed :: FixedPrim Int32 -- | Encode a Int64 using 16 nibbles. int64HexFixed :: FixedPrim Int64 -- | Encode a Word8 using 2 nibbles (hexadecimal digits). word8HexFixed :: FixedPrim Word8 -- | Encode a Word16 using 4 nibbles. word16HexFixed :: FixedPrim Word16 -- | Encode a Word32 using 8 nibbles. word32HexFixed :: FixedPrim Word32 -- | Encode a Word64 using 16 nibbles. word64HexFixed :: FixedPrim Word64 -- | Encode an IEEE Float using 8 nibbles. floatHexFixed :: FixedPrim Float -- | Encode an IEEE Double using 16 nibbles. doubleHexFixed :: FixedPrim Double -- | Char8 encode a Char. char8 :: FixedPrim Char -- | UTF-8 encode a Char. charUtf8 :: BoundedPrim Char -- | Builders are used to efficiently construct sequences of bytes -- from smaller parts. Typically, such a construction is part of the -- implementation of an encoding, i.e., a function for converting -- Haskell values to sequences of bytes. Examples of encodings are the -- generation of the sequence of bytes representing a HTML document to be -- sent in a HTTP response by a web application or the serialization of a -- Haskell value using a fixed binary format. -- -- For an efficient implementation of an encoding, it is important -- that (a) little time is spent on converting the Haskell values to the -- resulting sequence of bytes and (b) that the representation of -- the resulting sequence is such that it can be consumed efficiently. -- Builders support (a) by providing an O(1) concatentation -- operation and efficient implementations of basic encodings for -- Chars, Ints, and other standard Haskell values. They -- support (b) by providing their result as a lazy ByteString, -- which is internally just a linked list of pointers to chunks of -- consecutive raw memory. Lazy ByteStrings can be efficiently -- consumed by functions that write them to a file or send them over a -- network socket. Note that each chunk boundary incurs expensive extra -- work (e.g., a system call) that must be amortized over the work spent -- on consuming the chunk body. Builders therefore take special -- care to ensure that the average chunk size is large enough. The -- precise meaning of large enough is application dependent. The current -- implementation is tuned for an average chunk size between 4kb and -- 32kb, which should suit most applications. -- -- As a simple example of an encoding implementation, we show how to -- efficiently convert the following representation of mixed-data tables -- to an UTF-8 encoded Comma-Separated-Values (CSV) table. -- --
--   data Cell = StringC String
--             | IntC Int
--             deriving( Eq, Ord, Show )
--   
--   type Row   = [Cell]
--   type Table = [Row]
--   
-- -- We use the following imports and abbreviate mappend to simplify -- reading. -- --
--   import qualified Data.ByteString.Lazy               as L
--   import           Data.ByteString.Builder
--   import           Data.Monoid
--   import           Data.Foldable                        (foldMap)
--   import           Data.List                            (intersperse)
--   
--   infixr 4 <>
--   (<>) :: Monoid m => m -> m -> m
--   (<>) = mappend
--   
-- -- CSV is a character-based representation of tables. For maximal -- modularity, we could first render Tables as Strings -- and then encode this String using some Unicode character -- encoding. However, this sacrifices performance due to the intermediate -- String representation being built and thrown away right -- afterwards. We get rid of this intermediate String -- representation by fixing the character encoding to UTF-8 and using -- Builders to convert Tables directly to UTF-8 encoded -- CSV tables represented as lazy ByteStrings. -- --
--   encodeUtf8CSV :: Table -> L.ByteString
--   encodeUtf8CSV = toLazyByteString . renderTable
--   
--   renderTable :: Table -> Builder
--   renderTable rs = mconcat [renderRow r <> charUtf8 '\n' | r <- rs]
--   
--   renderRow :: Row -> Builder
--   renderRow []     = mempty
--   renderRow (c:cs) =
--       renderCell c <> mconcat [ charUtf8 ',' <> renderCell c' | c' <- cs ]
--   
--   renderCell :: Cell -> Builder
--   renderCell (StringC cs) = renderString cs
--   renderCell (IntC i)     = intDec i
--   
--   renderString :: String -> Builder
--   renderString cs = charUtf8 '"' <> foldMap escape cs <> charUtf8 '"'
--     where
--       escape '\\' = charUtf8 '\\' <> charUtf8 '\\'
--       escape '\"' = charUtf8 '\\' <> charUtf8 '\"'
--       escape c    = charUtf8 c
--   
-- -- Note that the ASCII encoding is a subset of the UTF-8 encoding, which -- is why we can use the optimized function intDec to encode an -- Int as a decimal number with UTF-8 encoded digits. Using -- intDec is more efficient than stringUtf8 . -- show, as it avoids constructing an intermediate -- String. Avoiding this intermediate data structure significantly -- improves performance because encoding Cells is the core -- operation for rendering CSV-tables. See -- Data.ByteString.Builder.Prim for further information on how to -- improve the performance of renderString. -- -- We demonstrate our UTF-8 CSV encoding function on the following table. -- --
--   strings :: [String]
--   strings =  ["hello", "\"1\"", "λ-wörld"]
--   
--   table :: Table
--   table = [map StringC strings, map IntC [-3..3]]
--   
-- -- The expression encodeUtf8CSV table results in the following -- lazy ByteString. -- --
--   Chunk "\"hello\",\"\\\"1\\\"\",\"\206\187-w\195\182rld\"\n-3,-2,-1,0,1,2,3\n" Empty
--   
-- -- We can clearly see that we are converting to a binary format. -- The 'λ' and 'ö' characters, which have a Unicode codepoint above 127, -- are expanded to their corresponding UTF-8 multi-byte representation. -- -- We use the criterion library -- (http://hackage.haskell.org/package/criterion) to benchmark the -- efficiency of our encoding function on the following table. -- --
--   import Criterion.Main     -- add this import to the ones above
--   
--   maxiTable :: Table
--   maxiTable = take 1000 $ cycle table
--   
--   main :: IO ()
--   main = defaultMain
--     [ bench "encodeUtf8CSV maxiTable (original)" $
--         whnf (L.length . encodeUtf8CSV) maxiTable
--     ]
--   
-- -- On a Core2 Duo 2.20GHz on a 32-bit Linux, the above code takes 1ms to -- generate the 22'500 bytes long lazy ByteString. Looking again -- at the definitions above, we see that we took care to avoid -- intermediate data structures, as otherwise we would sacrifice -- performance. For example, the following (arguably simpler) definition -- of renderRow is about 20% slower. -- --
--   renderRow :: Row -> Builder
--   renderRow  = mconcat . intersperse (charUtf8 ',') . map renderCell
--   
-- -- Similarly, using O(n) concatentations like ++ or the -- equivalent concat operations on strict and lazy -- ByteStrings should be avoided. The following definition of -- renderString is also about 20% slower. -- --
--   renderString :: String -> Builder
--   renderString cs = charUtf8 $ "\"" ++ concatMap escape cs ++ "\""
--     where
--       escape '\\' = "\\"
--       escape '\"' = "\\\""
--       escape c    = return c
--   
-- -- Apart from removing intermediate data-structures, encodings can be -- optimized further by fine-tuning their execution parameters using the -- functions in Data.ByteString.Builder.Extra and their "inner -- loops" using the functions in Data.ByteString.Builder.Prim. module Data.ByteString.Builder -- | Builders denote sequences of bytes. They are Monoids -- where mempty is the zero-length sequence and mappend is -- concatenation, which runs in O(1). data Builder -- | Execute a Builder and return the generated chunks as a lazy -- ByteString. The work is performed lazy, i.e., only when a chunk -- of the lazy ByteString is forced. toLazyByteString :: Builder -> ByteString -- | Output a Builder to a Handle. The Builder is -- executed directly on the buffer of the Handle. If the buffer is -- too small (or not present), then it is replaced with a large enough -- buffer. -- -- It is recommended that the Handle is set to binary and -- BlockBuffering mode. See hSetBinaryMode and -- hSetBuffering. -- -- This function is more efficient than hPut . -- toLazyByteString because in many cases no buffer -- allocation has to be done. Moreover, the results of several executions -- of short Builders are concatenated in the Handles -- buffer, therefore avoiding unnecessary buffer flushes. hPutBuilder :: Handle -> Builder -> IO () -- | Create a Builder denoting the same sequence of bytes as a -- strict ByteString. The Builder inserts large -- ByteStrings directly, but copies small ones to ensure that the -- generated chunks are large on average. byteString :: ByteString -> Builder -- | Create a Builder denoting the same sequence of bytes as a lazy -- ByteString. The Builder inserts large chunks of the lazy -- ByteString directly, but copies small ones to ensure that the -- generated chunks are large on average. lazyByteString :: ByteString -> Builder -- | Construct a Builder that copies the ShortByteString. shortByteString :: ShortByteString -> Builder -- | Encode a single signed byte as-is. int8 :: Int8 -> Builder -- | Encode a single unsigned byte as-is. word8 :: Word8 -> Builder -- | Encode an Int16 in big endian format. int16BE :: Int16 -> Builder -- | Encode an Int32 in big endian format. int32BE :: Int32 -> Builder -- | Encode an Int64 in big endian format. int64BE :: Int64 -> Builder -- | Encode a Word16 in big endian format. word16BE :: Word16 -> Builder -- | Encode a Word32 in big endian format. word32BE :: Word32 -> Builder -- | Encode a Word64 in big endian format. word64BE :: Word64 -> Builder -- | Encode a Float in big endian format. floatBE :: Float -> Builder -- | Encode a Double in big endian format. doubleBE :: Double -> Builder -- | Encode an Int16 in little endian format. int16LE :: Int16 -> Builder -- | Encode an Int32 in little endian format. int32LE :: Int32 -> Builder -- | Encode an Int64 in little endian format. int64LE :: Int64 -> Builder -- | Encode a Word16 in little endian format. word16LE :: Word16 -> Builder -- | Encode a Word32 in little endian format. word32LE :: Word32 -> Builder -- | Encode a Word64 in little endian format. word64LE :: Word64 -> Builder -- | Encode a Float in little endian format. floatLE :: Float -> Builder -- | Encode a Double in little endian format. doubleLE :: Double -> Builder -- | Char7 encode a Char. char7 :: Char -> Builder -- | Char7 encode a String. string7 :: String -> Builder -- | Char8 encode a Char. char8 :: Char -> Builder -- | Char8 encode a String. string8 :: String -> Builder -- | UTF-8 encode a Char. charUtf8 :: Char -> Builder -- | UTF-8 encode a String. stringUtf8 :: String -> Builder -- | Decimal encoding of an Int8 using the ASCII digits. -- -- e.g. -- --
--   toLazyByteString (int8Dec 42)   = "42"
--   toLazyByteString (int8Dec (-1)) = "-1"
--   
int8Dec :: Int8 -> Builder -- | Decimal encoding of an Int16 using the ASCII digits. int16Dec :: Int16 -> Builder -- | Decimal encoding of an Int32 using the ASCII digits. int32Dec :: Int32 -> Builder -- | Decimal encoding of an Int64 using the ASCII digits. int64Dec :: Int64 -> Builder -- | Decimal encoding of an Int using the ASCII digits. intDec :: Int -> Builder -- | Decimal encoding of an Integer using the ASCII digits. integerDec :: Integer -> Builder -- | Decimal encoding of a Word8 using the ASCII digits. word8Dec :: Word8 -> Builder -- | Decimal encoding of a Word16 using the ASCII digits. word16Dec :: Word16 -> Builder -- | Decimal encoding of a Word32 using the ASCII digits. word32Dec :: Word32 -> Builder -- | Decimal encoding of a Word64 using the ASCII digits. word64Dec :: Word64 -> Builder -- | Decimal encoding of a Word using the ASCII digits. wordDec :: Word -> Builder -- | Currently slow. Decimal encoding of an IEEE Float. floatDec :: Float -> Builder -- | Currently slow. Decimal encoding of an IEEE Double. doubleDec :: Double -> Builder -- | Shortest hexadecimal encoding of a Word8 using lower-case -- characters. word8Hex :: Word8 -> Builder -- | Shortest hexadecimal encoding of a Word16 using lower-case -- characters. word16Hex :: Word16 -> Builder -- | Shortest hexadecimal encoding of a Word32 using lower-case -- characters. word32Hex :: Word32 -> Builder -- | Shortest hexadecimal encoding of a Word64 using lower-case -- characters. word64Hex :: Word64 -> Builder -- | Shortest hexadecimal encoding of a Word using lower-case -- characters. wordHex :: Word -> Builder -- | Encode a Int8 using 2 nibbles (hexadecimal digits). int8HexFixed :: Int8 -> Builder -- | Encode a Int16 using 4 nibbles. int16HexFixed :: Int16 -> Builder -- | Encode a Int32 using 8 nibbles. int32HexFixed :: Int32 -> Builder -- | Encode a Int64 using 16 nibbles. int64HexFixed :: Int64 -> Builder -- | Encode a Word8 using 2 nibbles (hexadecimal digits). word8HexFixed :: Word8 -> Builder -- | Encode a Word16 using 4 nibbles. word16HexFixed :: Word16 -> Builder -- | Encode a Word32 using 8 nibbles. word32HexFixed :: Word32 -> Builder -- | Encode a Word64 using 16 nibbles. word64HexFixed :: Word64 -> Builder -- | Encode an IEEE Float using 8 nibbles. floatHexFixed :: Float -> Builder -- | Encode an IEEE Double using 16 nibbles. doubleHexFixed :: Double -> Builder -- | Encode each byte of a ByteString using its fixed-width hex -- encoding. byteStringHex :: ByteString -> Builder -- | Encode each byte of a lazy ByteString using its fixed-width hex -- encoding. lazyByteStringHex :: ByteString -> Builder instance Data.String.IsString Data.ByteString.Builder.Internal.Builder -- | We decided to rename the Builder modules. Sorry about that. -- -- The old names will hang about for at least once release cycle before -- we deprecate them and then later remove them. module Data.ByteString.Lazy.Builder -- | We decided to rename the Builder modules. Sorry about that. -- -- In additon, the ASCII module has been merged into the main -- Data.ByteString.Builder module. -- -- The old names will hang about for at least once release cycle before -- we deprecate them and then later remove them. module Data.ByteString.Lazy.Builder.ASCII byteStringHexFixed :: ByteString -> Builder lazyByteStringHexFixed :: ByteString -> Builder -- | Extra functions for creating and executing Builders. They are -- intended for application-specific fine-tuning the performance of -- Builders. module Data.ByteString.Builder.Extra -- | Heavy inlining. Execute a Builder with custom execution -- parameters. -- -- This function is inlined despite its heavy code-size to allow fusing -- with the allocation strategy. For example, the default Builder -- execution function toLazyByteString is defined as follows. -- --
--   {-# NOINLINE toLazyByteString #-}
--   toLazyByteString =
--     toLazyByteStringWith (safeStrategy smallChunkSize defaultChunkSize) L.empty
--   
-- -- where L.empty is the zero-length lazy ByteString. -- -- In most cases, the parameters used by toLazyByteString give -- good performance. A sub-performing case of toLazyByteString -- is executing short (<128 bytes) Builders. In this case, the -- allocation overhead for the first 4kb buffer and the trimming cost -- dominate the cost of executing the Builder. You can avoid this -- problem using -- --
--   toLazyByteStringWith (safeStrategy 128 smallChunkSize) L.empty
--   
-- -- This reduces the allocation and trimming overhead, as all generated -- ByteStrings fit into the first buffer and there is no trimming -- required, if more than 64 bytes and less than 128 bytes are written. toLazyByteStringWith :: AllocationStrategy -> ByteString -> Builder -> ByteString -- | A buffer allocation strategy for executing Builders. data AllocationStrategy -- | Use this strategy for generating lazy ByteStrings whose chunks -- are likely to survive one garbage collection. This strategy trims -- buffers that are filled less than half in order to avoid spilling too -- much memory. safeStrategy :: Int -> Int -> AllocationStrategy -- | Use this strategy for generating lazy ByteStrings whose chunks -- are discarded right after they are generated. For example, if you just -- generate them to write them to a network socket. untrimmedStrategy :: Int -> Int -> AllocationStrategy -- | The recommended chunk size. Currently set to 4k, less the memory -- management overhead smallChunkSize :: Int -- | The chunk size used for I/O. Currently set to 32k, less the memory -- management overhead defaultChunkSize :: Int -- | Construct a Builder that copies the strict ByteString. -- -- Use this function to create Builders from smallish (<= -- 4kb) ByteStrings or if you need to guarantee that the -- ByteString is not shared with the chunks generated by the -- Builder. byteStringCopy :: ByteString -> Builder -- | Construct a Builder that always inserts the strict -- ByteString directly as a chunk. -- -- This implies flushing the output buffer, even if it contains just a -- single byte. You should therefore use byteStringInsert only for -- large (> 8kb) ByteStrings. Otherwise, the generated -- chunks are too fragmented to be processed efficiently afterwards. byteStringInsert :: ByteString -> Builder -- | Construct a Builder that copies the strict ByteStrings, -- if it is smaller than the treshold, and inserts it directly otherwise. -- -- For example, byteStringThreshold 1024 copies strict -- ByteStrings whose size is less or equal to 1kb, and inserts -- them directly otherwise. This implies that the average chunk-size of -- the generated lazy ByteString may be as low as 513 bytes, as -- there could always be just a single byte between the directly inserted -- 1025 byte, strict ByteStrings. byteStringThreshold :: Int -> ByteString -> Builder -- | Construct a Builder that copies the lazy ByteString. lazyByteStringCopy :: ByteString -> Builder -- | Construct a Builder that inserts all chunks of the lazy -- ByteString directly. lazyByteStringInsert :: ByteString -> Builder -- | Construct a Builder that uses the thresholding strategy of -- byteStringThreshold for each chunk of the lazy -- ByteString. lazyByteStringThreshold :: Int -> ByteString -> Builder -- | Flush the current buffer. This introduces a chunk boundary. flush :: Builder -- | A BufferWriter represents the result of running a -- Builder. It unfolds as a sequence of chunks of data. These -- chunks come in two forms: -- -- -- -- While this is rather low level, it provides you with full flexibility -- in how the data is written out. -- -- The BufferWriter itself is an IO action: you supply it with a -- buffer (as a pointer and length) and it will write data into the -- buffer. It returns a number indicating how many bytes were actually -- written (which can be 0). It also returns a Next which -- describes what comes next. type BufferWriter = Ptr Word8 -> Int -> IO (Int, Next) -- | After running a BufferWriter action there are three -- possibilities for what comes next: data Next -- | This means we're all done. All the builder data has now been written. Done :: Next -- | This indicates that there may be more data to write. It gives you the -- next BufferWriter action. You should call that action with an -- appropriate buffer. The int indicates the minimum buffer size -- required by the next BufferWriter action. That is, if you call -- the next action you must supply it with a buffer length of at -- least this size. More :: !Int -> BufferWriter -> Next -- | In addition to the data that has just been written into your buffer by -- the BufferWriter action, it gives you a pre-existing chunk of -- data as a ByteString. It also gives you the following -- BufferWriter action. It is safe to run this following action -- using a buffer with as much free space as was left by the previous run -- action. Chunk :: !ByteString -> BufferWriter -> Next -- | Turn a Builder into its initial BufferWriter action. runBuilder :: Builder -> BufferWriter -- | Encode a single native machine Int. The Int is encoded -- in host order, host endian form, for the machine you're on. On a 64 -- bit machine the Int is an 8 byte value, on a 32 bit machine, 4 -- bytes. Values encoded this way are not portable to different endian or -- int sized machines, without conversion. intHost :: Int -> Builder -- | Encode a Int16 in native host order and host endianness. int16Host :: Int16 -> Builder -- | Encode a Int32 in native host order and host endianness. int32Host :: Int32 -> Builder -- | Encode a Int64 in native host order and host endianness. int64Host :: Int64 -> Builder -- | Encode a single native machine Word. The Word is encoded -- in host order, host endian form, for the machine you're on. On a 64 -- bit machine the Word is an 8 byte value, on a 32 bit machine, 4 -- bytes. Values encoded this way are not portable to different endian or -- word sized machines, without conversion. wordHost :: Word -> Builder -- | Encode a Word16 in native host order and host endianness. word16Host :: Word16 -> Builder -- | Encode a Word32 in native host order and host endianness. word32Host :: Word32 -> Builder -- | Encode a Word64 in native host order and host endianness. word64Host :: Word64 -> Builder -- | Encode a Float in native host order. Values encoded this way -- are not portable to different endian machines, without conversion. floatHost :: Float -> Builder -- | Encode a Double in native host order. doubleHost :: Double -> Builder -- | We decided to rename the Builder modules. Sorry about that. -- -- The old names will hang about for at least once release cycle before -- we deprecate them and then later remove them. module Data.ByteString.Lazy.Builder.Extras