-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Fast, packed, strict and lazy byte arrays with a list interface -- -- 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, and lazy lists of -- strict chunks, held in a ForeignPtr, and can be passed between -- C and Haskell with little effort. -- -- Test coverage data for this library is available at: -- http://code.haskell.org/~dons/tests/bytestring/hpc_index.html @package bytestring @version 0.9.2.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 -- | 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 funtion 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 funtion 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(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 you Add# has embedded '\0' characters in -- the string (strlen will fail). 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 these functions. 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 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. -- -- 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 -- Data.Array.Unboxed.UArray by Simon Marlow. Rewritten to -- support slices and use ForeignPtr by David Roundy. Polished and -- extended by Don Stewart. module Data.ByteString -- | A space-efficient representation of a Word8 vector, supporting many -- efficient operations. A ByteString contains 8-bit characters -- only. -- -- Instances of Eq, Ord, Read, Show, Data, Typeable 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 a memcpy. 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 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. This function is -- subject to array fusion. 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. -- -- This function is subject to array fusion. foldl :: (a -> Word8 -> a) -> a -> ByteString -> a -- | 'foldl\'' is like foldl, but strict in the accumulator. -- However, for ByteStrings, all left folds are 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. -- This function is subject to array fusion. 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: -- --
--   snd (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). findSubstring :: ByteString -> ByteString -> Maybe Int -- | Find the indexes of all (possibly overlapping) occurances of a -- substring in a string. 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. This function is subject to array fusion. 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 -- will be freed automatically. This is a memcpy(3). 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. Files are read using 'binary mode' on -- Windows, for 'text mode' use the Char8 version of this function. 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 entire handle contents strictly into a ByteString. -- -- This function reads chunks at a time, doubling the chunksize on each -- read. The final buffer 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. -- -- As with hGet, the string representation in the file is assumed -- to be ISO-8859-1. -- -- 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 null 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 () -- | 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"
--   
breakByte :: Word8 -> ByteString -> (ByteString, ByteString) instance Monoid ByteString instance Ord ByteString instance Eq 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 B
--   
-- -- 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 -XOverloadedStrings to -- enable this. module Data.ByteString.Char8 -- | A space-efficient representation of a Word8 vector, supporting many -- efficient operations. A ByteString contains 8-bit characters -- only. -- -- Instances of Eq, Ord, Read, Show, Data, Typeable 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 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). findSubstring :: ByteString -> ByteString -> Maybe Int -- | Find the indexes of all (possibly overlapping) occurances of a -- substring in a string. 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 -- will be freed automatically. This is a memcpy(3). 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 entire handle contents strictly into a ByteString. -- -- This function reads chunks at a time, doubling the chunksize on each -- read. The final buffer 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. -- -- As with hGet, the string representation in the file is assumed -- to be ISO-8859-1. -- -- 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 null 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 -- | 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 () instance IsString ByteString -- | 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. Byte vectors are encoded as lazy lists of strict -- Word8 arrays of bytes. They provide a means to manipulate large -- byte vectors without requiring the entire vector be resident in -- memory. -- -- 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. And for other -- operations lazy ByteStrings are usually within a few percent of strict -- ones, but with better heap usage. For data larger than the available -- memory, or if you have tight memory constraints, this module will be -- the only option. The default chunk size is 64k, which should be good -- in most circumstances. For people with large L2 caches, you may want -- to increase this to fit your cache. -- -- 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 -- Data.Array.Unboxed.UArray by Simon Marlow. Rewritten to -- support slices and use Foreign.ForeignPtr.ForeignPtr by David -- Roundy. Polished and extended by Don Stewart. 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 ByteString contains 8-bit characters -- only. -- -- Instances of Eq, Ord, Read, Show, Data, Typeable 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(c) Convert a list of strict ByteString into a lazy -- ByteString fromChunks :: [ByteString] -> ByteString -- | O(n) Convert a lazy ByteString into a list of strict -- ByteString toChunks :: ByteString -> [ByteString] -- | 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 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. -- This function is subject to array fusion. 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 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 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 -- System.IO.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 () instance Monoid ByteString instance Ord ByteString instance Eq ByteString -- | 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 -- Data.Word.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
--   
module Data.ByteString.Lazy.Char8 -- | A space-efficient representation of a Word8 vector, supporting many -- efficient operations. A ByteString contains 8-bit characters -- only. -- -- Instances of Eq, Ord, Read, Show, Data, Typeable 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(n) Convert a lazy ByteString into a list of strict -- ByteString toChunks :: 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)/ 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) 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. Use 'text -- mode' on Windows to interpret newlines 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 -- System.IO.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 () instance IsString ByteString