{-# OPTIONS_GHC -fno-warn-incomplete-patterns #-}
{-# OPTIONS_HADDOCK prune #-}
{-# LANGUAGE Trustworthy #-}

{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ScopedTypeVariables #-}

-- |
-- Module      : Data.ByteString.Lazy
-- Copyright   : (c) Don Stewart 2006
--               (c) Duncan Coutts 2006-2011
-- License     : BSD-style
--
-- Maintainer  : dons00@gmail.com, duncan@community.haskell.org
-- Stability   : stable
-- Portability : portable
--
-- 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 'Data.Array.Unboxed.UArray' by Simon Marlow.
-- Rewritten to support slices and use 'Foreign.ForeignPtr.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 (

        -- * Lazy @ByteString@
        ByteString,
        LazyByteString,

        -- * Introducing and eliminating 'ByteString's
        empty,
        singleton,
        pack,
        unpack,
        fromStrict,
        toStrict,
        fromChunks,
        toChunks,
        foldrChunks,
        foldlChunks,

        -- * Basic interface
        cons,
        cons',
        snoc,
        append,
        head,
        uncons,
        unsnoc,
        last,
        tail,
        init,
        null,
        length,

        -- * Transforming ByteStrings
        map,
        reverse,
        intersperse,
        intercalate,
        transpose,

        -- * Reducing 'ByteString's (folds)
        foldl,
        foldl',
        foldl1,
        foldl1',
        foldr,
        foldr',
        foldr1,
        foldr1',

        -- ** Special folds
        concat,
        concatMap,
        any,
        all,
        maximum,
        minimum,
        compareLength,

        -- * Building ByteStrings
        -- ** Scans
        scanl,
        scanl1,
        scanr,
        scanr1,

        -- ** Accumulating maps
        mapAccumL,
        mapAccumR,

        -- ** Infinite ByteStrings
        repeat,
        replicate,
        cycle,
        iterate,

        -- ** Unfolding ByteStrings
        unfoldr,

        -- * Substrings

        -- ** Breaking strings
        take,
        takeEnd,
        drop,
        dropEnd,
        splitAt,
        takeWhile,
        takeWhileEnd,
        dropWhile,
        dropWhileEnd,
        span,
        spanEnd,
        break,
        breakEnd,
        group,
        groupBy,
        inits,
        tails,
        initsNE,
        tailsNE,
        stripPrefix,
        stripSuffix,

        -- ** Breaking into many substrings
        split,
        splitWith,

        -- * Predicates
        isPrefixOf,
        isSuffixOf,
--        isInfixOf,

        -- ** Search for arbitrary substrings
--        isSubstringOf,

        -- * Searching ByteStrings

        -- ** Searching by equality
        elem,
        notElem,

        -- ** Searching with a predicate
        find,
        filter,
        partition,

        -- * Indexing ByteStrings
        index,
        indexMaybe,
        (!?),
        elemIndex,
        elemIndexEnd,
        elemIndices,
        findIndex,
        findIndexEnd,
        findIndices,
        count,

        -- * Zipping and unzipping ByteStrings
        zip,
        zipWith,
        packZipWith,
        unzip,

        -- * Ordered ByteStrings
--        sort,

        -- * Low level conversions
        -- ** Copying ByteStrings
        copy,
--        defrag,

        -- * I\/O with 'ByteString's
        -- $IOChunk

        -- ** Standard input and output
        getContents,
        putStr,
        interact,

        -- ** Files
        readFile,
        writeFile,
        appendFile,

        -- ** I\/O with Handles
        hGetContents,
        hGet,
        hGetNonBlocking,
        hPut,
        hPutNonBlocking,
        hPutStr,

  ) where

import Prelude hiding
    (reverse,head,tail,last,init,Foldable(..),map,lines,unlines
    ,concat,any,take,drop,splitAt,takeWhile,dropWhile,span,break,filter
    ,all,concatMap,scanl, scanl1, scanr, scanr1
    ,repeat, cycle, interact, iterate,readFile,writeFile,appendFile,replicate
    ,getContents,getLine,putStr,putStrLn ,zip,zipWith,unzip,notElem)

import qualified Data.List              as List
import qualified Data.List.NonEmpty     as NE
import Data.List.NonEmpty (NonEmpty(..))
import qualified Data.Bifunctor         as BF
import qualified Data.ByteString        as P  (ByteString) -- type name only
import qualified Data.ByteString        as S  -- S for strict (hmm...)
import qualified Data.ByteString.Internal.Type as S
import qualified Data.ByteString.Unsafe as S
import Data.ByteString.Lazy.Internal

import Control.Exception        (assert)
import Control.Monad            (mplus)
import Data.Word                (Word8)
import Data.Int                 (Int64)
import GHC.Stack.Types          (HasCallStack)
import System.IO                (Handle,openBinaryFile,stdin,stdout,withBinaryFile,IOMode(..)
                                ,hClose)
import System.IO.Error          (mkIOError, illegalOperationErrorType)
import System.IO.Unsafe

import Foreign.Ptr
import Foreign.Storable


-- -----------------------------------------------------------------------------
-- Introducing and eliminating 'ByteString's

-- | /O(1)/ The empty 'ByteString'
empty :: ByteString
empty :: ByteString
empty = ByteString
Empty
{-# INLINE empty #-}

-- | /O(1)/ Convert a 'Word8' into a 'ByteString'
singleton :: Word8 -> ByteString
singleton :: Word8 -> ByteString
singleton Word8
w = StrictByteString -> ByteString -> ByteString
Chunk (Word8 -> StrictByteString
S.singleton Word8
w) ByteString
Empty
{-# INLINE singleton #-}

-- | /O(n)/ Convert a '[Word8]' into a 'ByteString'.
pack :: [Word8] -> ByteString
pack :: [Word8] -> ByteString
pack = [Word8] -> ByteString
packBytes

-- | /O(n)/ Converts a 'ByteString' to a '[Word8]'.
unpack :: ByteString -> [Word8]
unpack :: ByteString -> [Word8]
unpack = ByteString -> [Word8]
unpackBytes

-- | /O(c)/ Convert a list of 'S.StrictByteString' into a 'LazyByteString'
fromChunks :: [S.StrictByteString] -> LazyByteString
fromChunks :: [StrictByteString] -> ByteString
fromChunks = (StrictByteString -> ByteString -> ByteString)
-> ByteString -> [StrictByteString] -> ByteString
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
List.foldr StrictByteString -> ByteString -> ByteString
chunk ByteString
Empty

-- | /O(c)/ Convert a 'LazyByteString' into a list of 'S.StrictByteString'
toChunks :: LazyByteString -> [S.StrictByteString]
toChunks :: ByteString -> [StrictByteString]
toChunks = (StrictByteString -> [StrictByteString] -> [StrictByteString])
-> [StrictByteString] -> ByteString -> [StrictByteString]
forall a. (StrictByteString -> a -> a) -> a -> ByteString -> a
foldrChunks (:) []

------------------------------------------------------------------------

{-
-- | /O(n)/ Convert a '[a]' into a 'ByteString' using some
-- conversion function
packWith :: (a -> Word8) -> [a] -> ByteString
packWith k str = LPS $ L.map (P.packWith k) (chunk defaultChunkSize str)
{-# INLINE packWith #-}
{-# SPECIALIZE packWith :: (Char -> Word8) -> [Char] -> ByteString #-}

-- | /O(n)/ Converts a 'ByteString' to a '[a]', using a conversion function.
unpackWith :: (Word8 -> a) -> ByteString -> [a]
unpackWith k (LPS ss) = L.concatMap (S.unpackWith k) ss
{-# INLINE unpackWith #-}
{-# SPECIALIZE unpackWith :: (Word8 -> Char) -> ByteString -> [Char] #-}
-}

-- ---------------------------------------------------------------------
-- Basic interface

-- | /O(1)/ Test whether a ByteString is empty.
null :: ByteString -> Bool
null :: ByteString -> Bool
null ByteString
Empty = Bool
True
null ByteString
_     = Bool
False
{-# INLINE null #-}

-- | /O(c)/ 'length' returns the length of a ByteString as an 'Int64'
length :: ByteString -> Int64
length :: ByteString -> Int64
length = (Int64 -> StrictByteString -> Int64)
-> Int64 -> ByteString -> Int64
forall a. (a -> StrictByteString -> a) -> a -> ByteString -> a
foldlChunks (\Int64
n StrictByteString
c -> Int64
n Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c)) Int64
0
{-# INLINE [1] length #-}

infixr 5 `cons`, `cons'` --same as list (:)
infixl 5 `snoc`

-- | /O(1)/ 'cons' is analogous to '(Prelude.:)' for lists.
--
cons :: Word8 -> ByteString -> ByteString
cons :: Word8 -> ByteString -> ByteString
cons Word8
c = StrictByteString -> ByteString -> ByteString
Chunk (Word8 -> StrictByteString
S.singleton Word8
c)
{-# INLINE cons #-}

-- | /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
cons' :: Word8 -> ByteString -> ByteString
cons' Word8
w (Chunk StrictByteString
c ByteString
cs) | StrictByteString -> Int
S.length StrictByteString
c Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
16 = StrictByteString -> ByteString -> ByteString
Chunk (Word8 -> StrictByteString -> StrictByteString
S.cons Word8
w StrictByteString
c) ByteString
cs
cons' Word8
w ByteString
cs                             = StrictByteString -> ByteString -> ByteString
Chunk (Word8 -> StrictByteString
S.singleton Word8
w) ByteString
cs
{-# INLINE cons' #-}

-- | /O(n\/c)/ Append a byte to the end of a 'ByteString'
snoc :: ByteString -> Word8 -> ByteString
snoc :: ByteString -> Word8 -> ByteString
snoc ByteString
cs Word8
w = (StrictByteString -> ByteString -> ByteString)
-> ByteString -> ByteString -> ByteString
forall a. (StrictByteString -> a -> a) -> a -> ByteString -> a
foldrChunks StrictByteString -> ByteString -> ByteString
Chunk (Word8 -> ByteString
singleton Word8
w) ByteString
cs
{-# INLINE snoc #-}

-- | /O(1)/ Extract the first element of a ByteString, which must be non-empty.
--
-- This is a partial function, consider using 'uncons' instead.
head :: HasCallStack => ByteString -> Word8
head :: HasCallStack => ByteString -> Word8
head ByteString
Empty       = String -> Word8
forall a. HasCallStack => String -> a
errorEmptyList String
"head"
head (Chunk StrictByteString
c ByteString
_) = StrictByteString -> Word8
S.unsafeHead StrictByteString
c
{-# INLINE head #-}

-- | /O(1)/ Extract the 'head' and 'tail' of a ByteString, returning 'Nothing'
-- if it is empty.
uncons :: ByteString -> Maybe (Word8, ByteString)
uncons :: ByteString -> Maybe (Word8, ByteString)
uncons ByteString
Empty = Maybe (Word8, ByteString)
forall a. Maybe a
Nothing
uncons (Chunk StrictByteString
c ByteString
cs) = case StrictByteString -> Int
S.length StrictByteString
c of
  -- Don't move this test inside of the Just or (,).
  -- We don't want to allocate a thunk to put inside of the tuple!
  -- And if "let !tl = ... in Just (..., tl)" seems more appealing,
  -- remember that this function must remain lazy in cs.
  Int
1 -> (Word8, ByteString) -> Maybe (Word8, ByteString)
forall a. a -> Maybe a
Just (StrictByteString -> Word8
S.unsafeHead StrictByteString
c, ByteString
cs)
  Int
_ -> (Word8, ByteString) -> Maybe (Word8, ByteString)
forall a. a -> Maybe a
Just (StrictByteString -> Word8
S.unsafeHead StrictByteString
c, StrictByteString -> ByteString -> ByteString
Chunk (StrictByteString -> StrictByteString
S.unsafeTail StrictByteString
c) ByteString
cs)
{-# INLINE uncons #-}

-- | /O(1)/ Extract the elements after the head of a ByteString, which must be
-- non-empty.
--
-- This is a partial function, consider using 'uncons' instead.
tail :: HasCallStack => ByteString -> ByteString
tail :: HasCallStack => ByteString -> ByteString
tail ByteString
Empty          = String -> ByteString
forall a. HasCallStack => String -> a
errorEmptyList String
"tail"
tail (Chunk StrictByteString
c ByteString
cs)
  | StrictByteString -> Int
S.length StrictByteString
c Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = ByteString
cs
  | Bool
otherwise       = StrictByteString -> ByteString -> ByteString
Chunk (StrictByteString -> StrictByteString
S.unsafeTail StrictByteString
c) ByteString
cs
{-# INLINE tail #-}

-- | /O(n\/c)/ Extract the last element of a ByteString, which must be finite
-- and non-empty.
--
-- This is a partial function, consider using 'unsnoc' instead.
last :: HasCallStack => ByteString -> Word8
last :: HasCallStack => ByteString -> Word8
last ByteString
Empty          = String -> Word8
forall a. HasCallStack => String -> a
errorEmptyList String
"last"
last (Chunk StrictByteString
c0 ByteString
cs0) = StrictByteString -> ByteString -> Word8
go StrictByteString
c0 ByteString
cs0
  where go :: StrictByteString -> ByteString -> Word8
go StrictByteString
c ByteString
Empty        = StrictByteString -> Word8
S.unsafeLast StrictByteString
c
        go StrictByteString
_ (Chunk StrictByteString
c ByteString
cs) = StrictByteString -> ByteString -> Word8
go StrictByteString
c ByteString
cs
-- XXX Don't inline this. Something breaks with 6.8.2 (haven't investigated yet)

-- | /O(n\/c)/ Returns all the elements of a 'ByteString' except the last one.
--
-- This is a partial function, consider using 'unsnoc' instead.
init :: HasCallStack => ByteString -> ByteString
init :: HasCallStack => ByteString -> ByteString
init ByteString
Empty          = String -> ByteString
forall a. HasCallStack => String -> a
errorEmptyList String
"init"
init (Chunk StrictByteString
c0 ByteString
cs0) = StrictByteString -> ByteString -> ByteString
go StrictByteString
c0 ByteString
cs0
  where go :: StrictByteString -> ByteString -> ByteString
go StrictByteString
c ByteString
Empty | StrictByteString -> Int
S.length StrictByteString
c Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1 = ByteString
Empty
                   | Bool
otherwise       = StrictByteString -> ByteString -> ByteString
Chunk (StrictByteString -> StrictByteString
S.unsafeInit StrictByteString
c) ByteString
Empty
        go StrictByteString
c (Chunk StrictByteString
c' ByteString
cs)           = StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c (StrictByteString -> ByteString -> ByteString
go StrictByteString
c' ByteString
cs)

-- | /O(n\/c)/ Extract the 'init' and 'last' of a ByteString, returning 'Nothing'
-- if it is empty.
--
-- * It is no faster than using 'init' and 'last'
unsnoc :: ByteString -> Maybe (ByteString, Word8)
unsnoc :: ByteString -> Maybe (ByteString, Word8)
unsnoc ByteString
Empty        = Maybe (ByteString, Word8)
forall a. Maybe a
Nothing
unsnoc (Chunk StrictByteString
c ByteString
cs) = (ByteString, Word8) -> Maybe (ByteString, Word8)
forall a. a -> Maybe a
Just (HasCallStack => ByteString -> ByteString
ByteString -> ByteString
init (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c ByteString
cs), HasCallStack => ByteString -> Word8
ByteString -> Word8
last (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c ByteString
cs))

-- | /O(n\/c)/ Append two ByteStrings
append :: ByteString -> ByteString -> ByteString
append :: ByteString -> ByteString -> ByteString
append = ByteString -> ByteString -> ByteString
forall a. Monoid a => a -> a -> a
mappend
{-# INLINE append #-}

-- ---------------------------------------------------------------------
-- Transformations

-- | /O(n)/ 'map' @f xs@ is the ByteString obtained by applying @f@ to each
-- element of @xs@.
map :: (Word8 -> Word8) -> ByteString -> ByteString
map :: (Word8 -> Word8) -> ByteString -> ByteString
map Word8 -> Word8
f = ByteString -> ByteString
go
    where
        go :: ByteString -> ByteString
go ByteString
Empty        = ByteString
Empty
        go (Chunk StrictByteString
x ByteString
xs) = StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
y ByteString
ys
            where
                y :: StrictByteString
y  = (Word8 -> Word8) -> StrictByteString -> StrictByteString
S.map Word8 -> Word8
f StrictByteString
x
                ys :: ByteString
ys = ByteString -> ByteString
go ByteString
xs
{-# INLINE map #-}

-- | /O(n)/ 'reverse' @xs@ returns the elements of @xs@ in reverse order.
reverse :: ByteString -> ByteString
reverse :: ByteString -> ByteString
reverse = ByteString -> ByteString -> ByteString
rev ByteString
Empty
  where rev :: ByteString -> ByteString -> ByteString
rev ByteString
a ByteString
Empty        = ByteString
a
        rev ByteString
a (Chunk StrictByteString
c ByteString
cs) = ByteString -> ByteString -> ByteString
rev (StrictByteString -> ByteString -> ByteString
Chunk (StrictByteString -> StrictByteString
S.reverse StrictByteString
c) ByteString
a) ByteString
cs
{-# INLINE reverse #-}

-- | 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
intersperse :: Word8 -> ByteString -> ByteString
intersperse Word8
_ ByteString
Empty        = ByteString
Empty
intersperse Word8
w (Chunk StrictByteString
c ByteString
cs) = StrictByteString -> ByteString -> ByteString
Chunk (Word8 -> StrictByteString -> StrictByteString
S.intersperse Word8
w StrictByteString
c)
                                   ((StrictByteString -> ByteString -> ByteString)
-> ByteString -> ByteString -> ByteString
forall a. (StrictByteString -> a -> a) -> a -> ByteString -> a
foldrChunks (StrictByteString -> ByteString -> ByteString
Chunk (StrictByteString -> ByteString -> ByteString)
-> (StrictByteString -> StrictByteString)
-> StrictByteString
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> StrictByteString
intersperse') ByteString
Empty ByteString
cs)
  where intersperse' :: P.ByteString -> P.ByteString
        intersperse' :: StrictByteString -> StrictByteString
intersperse' (S.BS ForeignPtr Word8
fp Int
l) =
          Int -> (ForeignPtr Word8 -> IO ()) -> StrictByteString
S.unsafeCreateFp (Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
l) ((ForeignPtr Word8 -> IO ()) -> StrictByteString)
-> (ForeignPtr Word8 -> IO ()) -> StrictByteString
forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
fp' ->
            ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
S.unsafeWithForeignPtr ForeignPtr Word8
fp' ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p' ->
              ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
S.unsafeWithForeignPtr ForeignPtr Word8
fp ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> do
                Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
p' Word8
w
                Ptr Word8 -> Ptr Word8 -> CSize -> Word8 -> IO ()
S.c_intersperse (Ptr Word8
p' Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) Ptr Word8
p (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l) Word8
w

-- | The 'transpose' function transposes the rows and columns of its
-- 'ByteString' argument.
transpose :: [ByteString] -> [ByteString]
transpose :: [ByteString] -> [ByteString]
transpose [ByteString]
css = ([Word8] -> ByteString) -> [[Word8]] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
List.map (\[Word8]
ss -> StrictByteString -> ByteString -> ByteString
Chunk ([Word8] -> StrictByteString
S.pack [Word8]
ss) ByteString
Empty)
                      ([[Word8]] -> [[Word8]]
forall a. [[a]] -> [[a]]
List.transpose ((ByteString -> [Word8]) -> [ByteString] -> [[Word8]]
forall a b. (a -> b) -> [a] -> [b]
List.map ByteString -> [Word8]
unpack [ByteString]
css))
--TODO: make this fast

-- ---------------------------------------------------------------------
-- Reducing 'ByteString's

-- | '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 :: forall a. (a -> Word8 -> a) -> a -> ByteString -> a
foldl a -> Word8 -> a
f = a -> ByteString -> a
go
  where go :: a -> ByteString -> a
go a
a ByteString
Empty        = a
a
        go a
a (Chunk StrictByteString
c ByteString
cs) = a -> ByteString -> a
go ((a -> Word8 -> a) -> a -> StrictByteString -> a
forall a. (a -> Word8 -> a) -> a -> StrictByteString -> a
S.foldl a -> Word8 -> a
f a
a StrictByteString
c) ByteString
cs
{-# INLINE foldl #-}

-- | 'foldl'' is like 'foldl', but strict in the accumulator.
foldl' :: (a -> Word8 -> a) -> a -> ByteString -> a
foldl' :: forall a. (a -> Word8 -> a) -> a -> ByteString -> a
foldl' a -> Word8 -> a
f = a -> ByteString -> a
go
  where go :: a -> ByteString -> a
go !a
a ByteString
Empty        = a
a
        go !a
a (Chunk StrictByteString
c ByteString
cs) = a -> ByteString -> a
go ((a -> Word8 -> a) -> a -> StrictByteString -> a
forall a. (a -> Word8 -> a) -> a -> StrictByteString -> a
S.foldl' a -> Word8 -> a
f a
a StrictByteString
c) ByteString
cs
{-# INLINE foldl' #-}

-- | '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 :: forall a. (Word8 -> a -> a) -> a -> ByteString -> a
foldr Word8 -> a -> a
k = (StrictByteString -> a -> a) -> a -> ByteString -> a
forall a. (StrictByteString -> a -> a) -> a -> ByteString -> a
foldrChunks ((a -> StrictByteString -> a) -> StrictByteString -> a -> a
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((Word8 -> a -> a) -> a -> StrictByteString -> a
forall a. (Word8 -> a -> a) -> a -> StrictByteString -> a
S.foldr Word8 -> a -> a
k))
{-# INLINE foldr #-}

-- | 'foldr'' is like 'foldr', but strict in the accumulator.
--
-- @since 0.11.2.0
foldr' :: (Word8 -> a -> a) -> a -> ByteString -> a
foldr' :: forall a. (Word8 -> a -> a) -> a -> ByteString -> a
foldr' Word8 -> a -> a
f a
a = ByteString -> a
go
  where
    go :: ByteString -> a
go ByteString
Empty = a
a
    go (Chunk StrictByteString
c ByteString
cs) = (Word8 -> a -> a) -> a -> StrictByteString -> a
forall a. (Word8 -> a -> a) -> a -> StrictByteString -> a
S.foldr' Word8 -> a -> a
f ((Word8 -> a -> a) -> a -> ByteString -> a
forall a. (Word8 -> a -> a) -> a -> ByteString -> a
foldr' Word8 -> a -> a
f a
a ByteString
cs) StrictByteString
c
{-# INLINE foldr' #-}

-- | 'foldl1' is a variant of 'foldl' that has no starting value
-- argument, and thus must be applied to non-empty 'ByteString's.
foldl1 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldl1 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldl1 Word8 -> Word8 -> Word8
_ ByteString
Empty        = String -> Word8
forall a. HasCallStack => String -> a
errorEmptyList String
"foldl1"
foldl1 Word8 -> Word8 -> Word8
f (Chunk StrictByteString
c ByteString
cs) = Word8 -> StrictByteString -> ByteString -> Word8
go (StrictByteString -> Word8
S.unsafeHead StrictByteString
c) (StrictByteString -> StrictByteString
S.unsafeTail StrictByteString
c) ByteString
cs
  where
    go :: Word8 -> StrictByteString -> ByteString -> Word8
go Word8
v StrictByteString
x ByteString
xs = let v' :: Word8
v' = (Word8 -> Word8 -> Word8) -> Word8 -> StrictByteString -> Word8
forall a. (a -> Word8 -> a) -> a -> StrictByteString -> a
S.foldl Word8 -> Word8 -> Word8
f Word8
v StrictByteString
x
      in case ByteString
xs of
      ByteString
Empty -> Word8
v'
      Chunk StrictByteString
x' ByteString
xs' -> Word8 -> StrictByteString -> ByteString -> Word8
go Word8
v' StrictByteString
x' ByteString
xs'

-- | 'foldl1'' is like 'foldl1', but strict in the accumulator.
foldl1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldl1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldl1' Word8 -> Word8 -> Word8
_ ByteString
Empty        = String -> Word8
forall a. HasCallStack => String -> a
errorEmptyList String
"foldl1'"
foldl1' Word8 -> Word8 -> Word8
f (Chunk StrictByteString
c ByteString
cs) = Word8 -> StrictByteString -> ByteString -> Word8
go (StrictByteString -> Word8
S.unsafeHead StrictByteString
c) (StrictByteString -> StrictByteString
S.unsafeTail StrictByteString
c) ByteString
cs
  where
    go :: Word8 -> StrictByteString -> ByteString -> Word8
go !Word8
v StrictByteString
x ByteString
xs = let v' :: Word8
v' = (Word8 -> Word8 -> Word8) -> Word8 -> StrictByteString -> Word8
forall a. (a -> Word8 -> a) -> a -> StrictByteString -> a
S.foldl' Word8 -> Word8 -> Word8
f Word8
v StrictByteString
x
      in case ByteString
xs of
      ByteString
Empty -> Word8
v'
      Chunk StrictByteString
x' ByteString
xs' -> Word8 -> StrictByteString -> ByteString -> Word8
go Word8
v' StrictByteString
x' ByteString
xs'

-- | 'foldr1' is a variant of 'foldr' that has no starting value argument,
-- and thus must be applied to non-empty 'ByteString's
foldr1 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldr1 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldr1 Word8 -> Word8 -> Word8
_ ByteString
Empty          = String -> Word8
forall a. HasCallStack => String -> a
errorEmptyList String
"foldr1"
foldr1 Word8 -> Word8 -> Word8
f (Chunk StrictByteString
c0 ByteString
cs0) = StrictByteString -> ByteString -> Word8
go StrictByteString
c0 ByteString
cs0
  where go :: StrictByteString -> ByteString -> Word8
go StrictByteString
c ByteString
Empty         = HasCallStack =>
(Word8 -> Word8 -> Word8) -> StrictByteString -> Word8
(Word8 -> Word8 -> Word8) -> StrictByteString -> Word8
S.foldr1 Word8 -> Word8 -> Word8
f StrictByteString
c
        go StrictByteString
c (Chunk StrictByteString
c' ByteString
cs) = (Word8 -> Word8 -> Word8) -> Word8 -> StrictByteString -> Word8
forall a. (Word8 -> a -> a) -> a -> StrictByteString -> a
S.foldr  Word8 -> Word8 -> Word8
f (StrictByteString -> ByteString -> Word8
go StrictByteString
c' ByteString
cs) StrictByteString
c

-- | 'foldr1'' is like 'foldr1', but strict in the accumulator.
--
-- @since 0.11.2.0
foldr1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldr1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldr1' Word8 -> Word8 -> Word8
_ ByteString
Empty          = String -> Word8
forall a. HasCallStack => String -> a
errorEmptyList String
"foldr1'"
foldr1' Word8 -> Word8 -> Word8
f (Chunk StrictByteString
c0 ByteString
cs0) = StrictByteString -> ByteString -> Word8
go StrictByteString
c0 ByteString
cs0
  where go :: StrictByteString -> ByteString -> Word8
go StrictByteString
c ByteString
Empty         = HasCallStack =>
(Word8 -> Word8 -> Word8) -> StrictByteString -> Word8
(Word8 -> Word8 -> Word8) -> StrictByteString -> Word8
S.foldr1' Word8 -> Word8 -> Word8
f StrictByteString
c
        go StrictByteString
c (Chunk StrictByteString
c' ByteString
cs) = (Word8 -> Word8 -> Word8) -> Word8 -> StrictByteString -> Word8
forall a. (Word8 -> a -> a) -> a -> StrictByteString -> a
S.foldr'  Word8 -> Word8 -> Word8
f (StrictByteString -> ByteString -> Word8
go StrictByteString
c' ByteString
cs) StrictByteString
c

-- ---------------------------------------------------------------------
-- Special folds

-- | /O(n)/ Concatenate a list of ByteStrings.
concat :: [ByteString] -> ByteString
concat :: [ByteString] -> ByteString
concat = [ByteString] -> ByteString
forall a. Monoid a => [a] -> a
mconcat

-- | Map a function over a 'ByteString' and concatenate the results
concatMap :: (Word8 -> ByteString) -> ByteString -> ByteString
concatMap :: (Word8 -> ByteString) -> ByteString -> ByteString
concatMap Word8 -> ByteString
_ ByteString
Empty        = ByteString
Empty
concatMap Word8 -> ByteString
f (Chunk StrictByteString
c0 ByteString
cs0) = StrictByteString -> ByteString -> ByteString
to StrictByteString
c0 ByteString
cs0
  where
    go :: ByteString -> P.ByteString -> ByteString -> ByteString
    go :: ByteString -> StrictByteString -> ByteString -> ByteString
go ByteString
Empty        StrictByteString
c' ByteString
cs' = StrictByteString -> ByteString -> ByteString
to StrictByteString
c' ByteString
cs'
    go (Chunk StrictByteString
c ByteString
cs) StrictByteString
c' ByteString
cs' = StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c (ByteString -> StrictByteString -> ByteString -> ByteString
go ByteString
cs StrictByteString
c' ByteString
cs')

    to :: P.ByteString -> ByteString -> ByteString
    to :: StrictByteString -> ByteString -> ByteString
to StrictByteString
c ByteString
cs | StrictByteString -> Bool
S.null StrictByteString
c  = case ByteString
cs of
        ByteString
Empty          -> ByteString
Empty
        (Chunk StrictByteString
c' ByteString
cs') -> StrictByteString -> ByteString -> ByteString
to StrictByteString
c' ByteString
cs'
            | Bool
otherwise = ByteString -> StrictByteString -> ByteString -> ByteString
go (Word8 -> ByteString
f (StrictByteString -> Word8
S.unsafeHead StrictByteString
c)) (StrictByteString -> StrictByteString
S.unsafeTail StrictByteString
c) ByteString
cs

-- | /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
any :: (Word8 -> Bool) -> ByteString -> Bool
any Word8 -> Bool
f = (StrictByteString -> Bool -> Bool) -> Bool -> ByteString -> Bool
forall a. (StrictByteString -> a -> a) -> a -> ByteString -> a
foldrChunks (\StrictByteString
c Bool
rest -> (Word8 -> Bool) -> StrictByteString -> Bool
S.any Word8 -> Bool
f StrictByteString
c Bool -> Bool -> Bool
|| Bool
rest) Bool
False
{-# INLINE any #-}

-- | /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
all :: (Word8 -> Bool) -> ByteString -> Bool
all Word8 -> Bool
f = (StrictByteString -> Bool -> Bool) -> Bool -> ByteString -> Bool
forall a. (StrictByteString -> a -> a) -> a -> ByteString -> a
foldrChunks (\StrictByteString
c Bool
rest -> (Word8 -> Bool) -> StrictByteString -> Bool
S.all Word8 -> Bool
f StrictByteString
c Bool -> Bool -> Bool
&& Bool
rest) Bool
True
{-# INLINE all #-}

-- | /O(n)/ 'maximum' returns the maximum value from a 'ByteString'
maximum :: HasCallStack => ByteString -> Word8
maximum :: HasCallStack => ByteString -> Word8
maximum ByteString
Empty        = String -> Word8
forall a. HasCallStack => String -> a
errorEmptyList String
"maximum"
maximum (Chunk StrictByteString
c ByteString
cs) = (Word8 -> StrictByteString -> Word8)
-> Word8 -> ByteString -> Word8
forall a. (a -> StrictByteString -> a) -> a -> ByteString -> a
foldlChunks (\Word8
n StrictByteString
c' -> Word8
n Word8 -> Word8 -> Word8
forall a. Ord a => a -> a -> a
`max` HasCallStack => StrictByteString -> Word8
StrictByteString -> Word8
S.maximum StrictByteString
c')
                                   (HasCallStack => StrictByteString -> Word8
StrictByteString -> Word8
S.maximum StrictByteString
c) ByteString
cs
{-# INLINE maximum #-}

-- | /O(n)/ 'minimum' returns the minimum value from a 'ByteString'
minimum :: HasCallStack => ByteString -> Word8
minimum :: HasCallStack => ByteString -> Word8
minimum ByteString
Empty        = String -> Word8
forall a. HasCallStack => String -> a
errorEmptyList String
"minimum"
minimum (Chunk StrictByteString
c ByteString
cs) = (Word8 -> StrictByteString -> Word8)
-> Word8 -> ByteString -> Word8
forall a. (a -> StrictByteString -> a) -> a -> ByteString -> a
foldlChunks (\Word8
n StrictByteString
c' -> Word8
n Word8 -> Word8 -> Word8
forall a. Ord a => a -> a -> a
`min` HasCallStack => StrictByteString -> Word8
StrictByteString -> Word8
S.minimum StrictByteString
c')
                                     (HasCallStack => StrictByteString -> Word8
StrictByteString -> Word8
S.minimum StrictByteString
c) ByteString
cs
{-# INLINE minimum #-}

-- | /O(c)/ 'compareLength' compares the length of a 'ByteString'
-- to an 'Int64'
--
-- @since 0.11.1.0
compareLength :: ByteString -> Int64 -> Ordering
compareLength :: ByteString -> Int64 -> Ordering
compareLength ByteString
_ Int64
toCmp | Int64
toCmp Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
0 = Ordering
GT
compareLength ByteString
Empty Int64
toCmp         = Int64 -> Int64 -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int64
0 Int64
toCmp
compareLength (Chunk StrictByteString
c ByteString
cs) Int64
toCmp  = ByteString -> Int64 -> Ordering
compareLength ByteString
cs (Int64
toCmp Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c))
{-# INLINE compareLength #-}

{-# RULES
"ByteString.Lazy length/compareN -> compareLength" [~1] forall t n.
  compare (length t) n = compareLength t n
"ByteString.Lazy compareN/length -> compareLength" [~1] forall t n.
  -- compare EQ LT = GT and vice versa
  compare n (length t) = compare EQ $ compareLength t n
"ByteString.Lazy length/==N -> compareLength/==EQ" [~1] forall t n.
   length t == n = compareLength t n == EQ
"ByteString.Lazy N==/length -> compareLength/==EQ" [~1] forall t n.
   n == length t = compareLength t n == EQ
"ByteString.Lazy length//=N -> compareLength//=EQ" [~1] forall t n.
   length t /= n = compareLength t n /= EQ
"ByteString.Lazy N/=/length -> compareLength//=EQ" [~1] forall t n.
   n /= length t = compareLength t n /= EQ
"ByteString.Lazy length/<N -> compareLength/==LT" [~1] forall t n.
   length t < n = compareLength t n == LT
"ByteString.Lazy >N/length -> compareLength/==LT" [~1] forall t n.
   n > length t = compareLength t n == LT
"ByteString.Lazy length/<=N -> compareLength//=GT" [~1] forall t n.
   length t <= n = compareLength t n /= GT
"ByteString.Lazy <=N/length -> compareLength//=GT" [~1] forall t n.
   n >= length t = compareLength t n /= GT
"ByteString.Lazy length/>N -> compareLength/==GT" [~1] forall t n.
   length t > n = compareLength t n == GT
"ByteString.Lazy <N/length -> compareLength/==GT" [~1] forall t n.
   n < length t = compareLength t n == GT
"ByteString.Lazy length/>=N -> compareLength//=LT" [~1] forall t n.
   length t >= n = compareLength t n /= LT
"ByteString.Lazy >=N/length -> compareLength//=LT" [~1] forall t n.
   n <= length t = compareLength t n /= LT
  #-}

-- | 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)
mapAccumL :: forall acc.
(acc -> Word8 -> (acc, Word8))
-> acc -> ByteString -> (acc, ByteString)
mapAccumL acc -> Word8 -> (acc, Word8)
f = acc -> ByteString -> (acc, ByteString)
go
  where
    go :: acc -> ByteString -> (acc, ByteString)
go acc
s ByteString
Empty        = (acc
s, ByteString
Empty)
    go acc
s (Chunk StrictByteString
c ByteString
cs) = (acc
s'', StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c' ByteString
cs')
        where (acc
s',  StrictByteString
c')  = (acc -> Word8 -> (acc, Word8))
-> acc -> StrictByteString -> (acc, StrictByteString)
forall acc.
(acc -> Word8 -> (acc, Word8))
-> acc -> StrictByteString -> (acc, StrictByteString)
S.mapAccumL acc -> Word8 -> (acc, Word8)
f acc
s StrictByteString
c
              (acc
s'', ByteString
cs') = acc -> ByteString -> (acc, ByteString)
go acc
s' ByteString
cs

-- | 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)
mapAccumR :: forall acc.
(acc -> Word8 -> (acc, Word8))
-> acc -> ByteString -> (acc, ByteString)
mapAccumR acc -> Word8 -> (acc, Word8)
f = acc -> ByteString -> (acc, ByteString)
go
  where
    go :: acc -> ByteString -> (acc, ByteString)
go acc
s ByteString
Empty        = (acc
s, ByteString
Empty)
    go acc
s (Chunk StrictByteString
c ByteString
cs) = (acc
s'', StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c' ByteString
cs')
        where (acc
s'', StrictByteString
c') = (acc -> Word8 -> (acc, Word8))
-> acc -> StrictByteString -> (acc, StrictByteString)
forall acc.
(acc -> Word8 -> (acc, Word8))
-> acc -> StrictByteString -> (acc, StrictByteString)
S.mapAccumR acc -> Word8 -> (acc, Word8)
f acc
s' StrictByteString
c
              (acc
s', ByteString
cs') = acc -> ByteString -> (acc, ByteString)
go acc
s ByteString
cs

-- ---------------------------------------------------------------------
-- Building ByteStrings

-- | '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
--
-- > head (scanl f z xs) == z
-- > last (scanl f z xs) == foldl f z xs
--
scanl
    :: (Word8 -> Word8 -> Word8)
    -- ^ accumulator -> element -> new accumulator
    -> Word8
    -- ^ starting value of accumulator
    -> ByteString
    -- ^ input of length n
    -> ByteString
    -- ^ output of length n+1
scanl :: (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
scanl Word8 -> Word8 -> Word8
function = ((Word8, ByteString) -> ByteString)
-> (ByteString -> (Word8, ByteString)) -> ByteString -> ByteString
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Word8 -> ByteString -> ByteString)
-> (Word8, ByteString) -> ByteString
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((ByteString -> Word8 -> ByteString)
-> Word8 -> ByteString -> ByteString
forall a b c. (a -> b -> c) -> b -> a -> c
flip ByteString -> Word8 -> ByteString
snoc)) ((ByteString -> (Word8, ByteString)) -> ByteString -> ByteString)
-> (Word8 -> ByteString -> (Word8, ByteString))
-> Word8
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word8 -> (Word8, Word8))
-> Word8 -> ByteString -> (Word8, ByteString)
forall acc.
(acc -> Word8 -> (acc, Word8))
-> acc -> ByteString -> (acc, ByteString)
mapAccumL (\Word8
x Word8
y -> (Word8 -> Word8 -> Word8
function Word8
x Word8
y, Word8
x))
{-# INLINE scanl #-}

-- | 'scanl1' is a variant of 'scanl' that has no starting value argument.
--
-- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
--
-- @since 0.11.2.0
scanl1 :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString
scanl1 :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString
scanl1 Word8 -> Word8 -> Word8
function ByteString
byteStream = case ByteString -> Maybe (Word8, ByteString)
uncons ByteString
byteStream of
  Maybe (Word8, ByteString)
Nothing -> ByteString
Empty
  Just (Word8
firstByte, ByteString
remainingBytes) -> (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
scanl Word8 -> Word8 -> Word8
function Word8
firstByte ByteString
remainingBytes

-- | 'scanr' is similar to 'foldr', but returns a list of successive
-- reduced values from the right.
--
-- > scanr f z [..., x{n-1}, xn] == [..., x{n-1} `f` (xn `f` z), xn `f` z, z]
--
-- Note that
--
-- > head (scanr f z xs) == foldr f z xs
-- > last (scanr f z xs) == z
--
-- @since 0.11.2.0
scanr
    :: (Word8 -> Word8 -> Word8)
    -- ^ element -> accumulator -> new accumulator
    -> Word8
    -- ^ starting value of accumulator
    -> ByteString
    -- ^ input of length n
    -> ByteString
    -- ^ output of length n+1
scanr :: (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
scanr Word8 -> Word8 -> Word8
function = ((Word8, ByteString) -> ByteString)
-> (ByteString -> (Word8, ByteString)) -> ByteString -> ByteString
forall a b. (a -> b) -> (ByteString -> a) -> ByteString -> b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((Word8 -> ByteString -> ByteString)
-> (Word8, ByteString) -> ByteString
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Word8 -> ByteString -> ByteString
cons) ((ByteString -> (Word8, ByteString)) -> ByteString -> ByteString)
-> (Word8 -> ByteString -> (Word8, ByteString))
-> Word8
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Word8 -> (Word8, Word8))
-> Word8 -> ByteString -> (Word8, ByteString)
forall acc.
(acc -> Word8 -> (acc, Word8))
-> acc -> ByteString -> (acc, ByteString)
mapAccumR (\Word8
x Word8
y -> (Word8 -> Word8 -> Word8
function Word8
y Word8
x, Word8
x))

-- | 'scanr1' is a variant of 'scanr' that has no starting value argument.
--
-- @since 0.11.2.0
scanr1 :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString
scanr1 :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString
scanr1 Word8 -> Word8 -> Word8
function ByteString
byteStream = case ByteString -> Maybe (ByteString, Word8)
unsnoc ByteString
byteStream of
  Maybe (ByteString, Word8)
Nothing -> ByteString
Empty
  Just (ByteString
initialBytes, Word8
lastByte) -> (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
scanr Word8 -> Word8 -> Word8
function Word8
lastByte ByteString
initialBytes

-- ---------------------------------------------------------------------
-- Unfolds and replicates

-- | @'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
iterate :: (Word8 -> Word8) -> Word8 -> ByteString
iterate Word8 -> Word8
f = (Word8 -> Maybe (Word8, Word8)) -> Word8 -> ByteString
forall a. (a -> Maybe (Word8, a)) -> a -> ByteString
unfoldr (\Word8
x -> case Word8 -> Word8
f Word8
x of !Word8
x' -> (Word8, Word8) -> Maybe (Word8, Word8)
forall a. a -> Maybe a
Just (Word8
x', Word8
x'))

-- | @'repeat' x@ is an infinite ByteString, with @x@ the value of every
-- element.
--
repeat :: Word8 -> ByteString
repeat :: Word8 -> ByteString
repeat Word8
w = ByteString
cs where cs :: ByteString
cs = StrictByteString -> ByteString -> ByteString
Chunk (Int -> Word8 -> StrictByteString
S.replicate Int
smallChunkSize Word8
w) ByteString
cs

-- | /O(n)/ @'replicate' n x@ is a ByteString of length @n@ with @x@
-- the value of every element.
--
replicate :: Int64 -> Word8 -> ByteString
replicate :: Int64 -> Word8 -> ByteString
replicate Int64
n Word8
w
    | Int64
n Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0             = ByteString
Empty
    | Int64
n Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
smallChunkSize = StrictByteString -> ByteString -> ByteString
Chunk (Int -> Word8 -> StrictByteString
S.replicate (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
n) Word8
w) ByteString
Empty
    | Int64
r Int64 -> Int64 -> Bool
forall a. Eq a => a -> a -> Bool
== Int64
0             = ByteString
cs -- preserve invariant
    | Bool
otherwise          = StrictByteString -> ByteString -> ByteString
Chunk (Int -> StrictByteString -> StrictByteString
S.unsafeTake (Int64 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
r) StrictByteString
c) ByteString
cs
 where
    c :: StrictByteString
c      = Int -> Word8 -> StrictByteString
S.replicate Int
smallChunkSize Word8
w
    cs :: ByteString
cs     = Int64 -> ByteString
forall {t}. (Eq t, Num t) => t -> ByteString
nChunks Int64
q
    (Int64
q, Int64
r) = Int64 -> Int64 -> (Int64, Int64)
forall a. Integral a => a -> a -> (a, a)
quotRem Int64
n (Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
smallChunkSize)
    nChunks :: t -> ByteString
nChunks t
0 = ByteString
Empty
    nChunks t
m = StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c (t -> ByteString
nChunks (t
mt -> t -> t
forall a. Num a => a -> a -> a
-t
1))

-- | 'cycle' ties a finite ByteString into a circular one, or equivalently,
-- the infinite repetition of the original ByteString.
--
cycle :: HasCallStack => ByteString -> ByteString
cycle :: HasCallStack => ByteString -> ByteString
cycle ByteString
Empty = String -> ByteString
forall a. HasCallStack => String -> a
errorEmptyList String
"cycle"
cycle ByteString
cs    = ByteString
cs' where cs' :: ByteString
cs' = (StrictByteString -> ByteString -> ByteString)
-> ByteString -> ByteString -> ByteString
forall a. (StrictByteString -> a -> a) -> a -> ByteString -> a
foldrChunks StrictByteString -> ByteString -> ByteString
Chunk ByteString
cs' ByteString
cs

-- | /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
unfoldr :: forall a. (a -> Maybe (Word8, a)) -> a -> ByteString
unfoldr a -> Maybe (Word8, a)
f = Int -> a -> ByteString
unfoldChunk Int
32
  where unfoldChunk :: Int -> a -> ByteString
unfoldChunk Int
n a
x =
          case Int -> (a -> Maybe (Word8, a)) -> a -> (StrictByteString, Maybe a)
forall a.
Int -> (a -> Maybe (Word8, a)) -> a -> (StrictByteString, Maybe a)
S.unfoldrN Int
n a -> Maybe (Word8, a)
f a
x of
            (StrictByteString
c, Maybe a
Nothing)
              | StrictByteString -> Bool
S.null StrictByteString
c  -> ByteString
Empty
              | Bool
otherwise -> StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c ByteString
Empty
            (StrictByteString
c, Just a
x')  -> StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c (Int -> a -> ByteString
unfoldChunk (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
*Int
2) a
x')

-- ---------------------------------------------------------------------
-- Substrings

-- | /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
take :: Int64 -> ByteString -> ByteString
take Int64
i ByteString
_ | Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0 = ByteString
Empty
take Int64
i ByteString
cs0         = Int64 -> ByteString -> ByteString
forall {t}. Integral t => t -> ByteString -> ByteString
take' Int64
i ByteString
cs0
  where take' :: t -> ByteString -> ByteString
take' t
0 ByteString
_            = ByteString
Empty
        take' t
_ ByteString
Empty        = ByteString
Empty
        take' t
n (Chunk StrictByteString
c ByteString
cs) =
          if t
n t -> t -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c)
            then StrictByteString -> ByteString -> ByteString
Chunk (Int -> StrictByteString -> StrictByteString
S.take (t -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral t
n) StrictByteString
c) ByteString
Empty
            else StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c (t -> ByteString -> ByteString
take' (t
n t -> t -> t
forall a. Num a => a -> a -> a
- Int -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c)) ByteString
cs)

-- | /O(c)/ @'takeEnd' n xs@ is equivalent to @'drop' ('length' xs - n) xs@.
-- Takes @n@ elements from end of bytestring.
--
-- >>> takeEnd 3 "abcdefg"
-- "efg"
-- >>> takeEnd 0 "abcdefg"
-- ""
-- >>> takeEnd 4 "abc"
-- "abc"
--
-- @since 0.11.2.0
takeEnd :: Int64 -> ByteString -> ByteString
takeEnd :: Int64 -> ByteString -> ByteString
takeEnd Int64
i ByteString
bs
  | Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0 = ByteString
Empty
  | Bool
otherwise = (StrictByteString -> ByteString -> ByteString)
-> (ByteString -> ByteString) -> Int64 -> ByteString -> ByteString
forall result.
(StrictByteString -> result -> result)
-> (ByteString -> result) -> Int64 -> ByteString -> result
splitAtEndFold (\StrictByteString
_ ByteString
res -> ByteString
res) ByteString -> ByteString
forall a. a -> a
id Int64
i ByteString
bs

-- | Helper function for implementing 'takeEnd' and 'dropEnd'
splitAtEndFold
  :: forall result
  .  (S.StrictByteString -> result -> result)
  -- ^ What to do when one chunk of output is ready
  -- (The StrictByteString will not be empty.)
  -> (ByteString -> result)
  -- ^ What to do when the split-point is reached
  -> Int64
  -- ^ Number of bytes to leave at the end (must be strictly positive)
  -> ByteString -- ^ Input ByteString
  -> result
{-# INLINE splitAtEndFold #-}
splitAtEndFold :: forall result.
(StrictByteString -> result -> result)
-> (ByteString -> result) -> Int64 -> ByteString -> result
splitAtEndFold StrictByteString -> result -> result
step ByteString -> result
end Int64
len ByteString
bs0 = Bool -> result -> result
forall a. HasCallStack => Bool -> a -> a
assert (Int64
len Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> Int64
0) (result -> result) -> result -> result
forall a b. (a -> b) -> a -> b
$ case ByteString
bs0 of
  ByteString
Empty -> ByteString -> result
end ByteString
Empty
  Chunk StrictByteString
c ByteString
t -> Int64 -> StrictByteString -> ByteString -> ByteString -> result
goR Int64
len StrictByteString
c ByteString
t ByteString
t
 where
  -- Idea: Keep two references into the input ByteString:
  --   "toSplit" tracks the current split point,
  --   "toScan"  tracks the yet-unprocessed tail.
  -- When they are closer than "len" bytes apart, process more input.  ("goR")
  -- When they are  at  least  "len" bytes apart, produce more output. ("goL")
  -- We always have that "toScan" is a suffix of "toSplit",
  -- and "toSplit" is a suffix of the original input (bs0).
  goR :: Int64 -> S.StrictByteString -> ByteString -> ByteString -> result
  goR :: Int64 -> StrictByteString -> ByteString -> ByteString -> result
goR !Int64
undershoot nextOutput :: StrictByteString
nextOutput@(S.BS ForeignPtr Word8
noFp Int
noLen) ByteString
toSplit ByteString
toScan =
      Bool -> result -> result
forall a. HasCallStack => Bool -> a -> a
assert (Int64
undershoot Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> Int64
0) (result -> result) -> result -> result
forall a b. (a -> b) -> a -> b
$
      -- INVARIANT: length toSplit == length toScan + len - undershoot
      -- (not 'assert'ed because that would break our laziness properties)
      case ByteString
toScan of
    ByteString
Empty
      | Int64
undershoot Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
>= Int -> Int64
intToInt64 Int
noLen
        -> ByteString -> result
end (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
nextOutput ByteString
toSplit)
      | Int
undershootW <- forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int64 @Int Int64
undershoot
        -- conversion Int64->Int is OK because 0 < undershoot < noLen
      , Int
splitIndex <- Int
noLen Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
undershootW
      , StrictByteString
beforeSplit <- ForeignPtr Word8 -> Int -> StrictByteString
S.BS ForeignPtr Word8
noFp Int
splitIndex
      , StrictByteString
afterSplit <- ForeignPtr Word8 -> Int -> StrictByteString
S.BS (ForeignPtr Word8
noFp ForeignPtr Word8 -> Int -> ForeignPtr Word8
forall a b. ForeignPtr a -> Int -> ForeignPtr b
`S.plusForeignPtr` Int
splitIndex) Int
undershootW
        -> StrictByteString -> result -> result
step StrictByteString
beforeSplit (result -> result) -> result -> result
forall a b. (a -> b) -> a -> b
$ ByteString -> result
end (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
afterSplit ByteString
toSplit)

    Chunk (S.BS ForeignPtr Word8
_ Int
cLen) ByteString
newBsR
      | Int64
cLen64 <- Int -> Int64
intToInt64 Int
cLen
      , Int64
undershoot Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
> Int64
cLen64
        -> Int64 -> StrictByteString -> ByteString -> ByteString -> result
goR (Int64
undershoot Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
- Int64
cLen64) StrictByteString
nextOutput ByteString
toSplit ByteString
newBsR
      | Int
undershootW <- forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int64 @Int Int64
undershoot
        -> StrictByteString -> result -> result
step StrictByteString
nextOutput (result -> result) -> result -> result
forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString -> result
goL (Int
cLen Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
undershootW) ByteString
toSplit ByteString
newBsR

  goL :: Int -> ByteString -> ByteString -> result
  goL :: Int -> ByteString -> ByteString -> result
goL !Int
overshoot ByteString
toSplit ByteString
toScan =
      Bool -> result -> result
forall a. HasCallStack => Bool -> a -> a
assert (Int
overshoot Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0) (result -> result) -> result -> result
forall a b. (a -> b) -> a -> b
$
      -- INVARIANT: length toSplit == length toScan + len + intToInt64 overshoot
      -- (not 'assert'ed because that would break our laziness properties)
      case ByteString
toSplit of
    ByteString
Empty -> result
forall a. a
splitAtEndFoldInvariantFailed
    Chunk c :: StrictByteString
c@(S.BS ForeignPtr Word8
_ Int
cLen) ByteString
newBsL
      | Int
overshoot Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
cLen
        -> StrictByteString -> result -> result
step StrictByteString
c (result -> result) -> result -> result
forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString -> result
goL (Int
overshoot Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
cLen) ByteString
newBsL ByteString
toScan
      | Bool
otherwise
        -> Int64 -> StrictByteString -> ByteString -> ByteString -> result
goR (Int -> Int64
intToInt64 (Int -> Int64) -> Int -> Int64
forall a b. (a -> b) -> a -> b
$ Int
cLen Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
overshoot) StrictByteString
c ByteString
newBsL ByteString
toScan

splitAtEndFoldInvariantFailed :: a
-- See Note [Float error calls out of INLINABLE things] in D.B.Internal.Type
splitAtEndFoldInvariantFailed :: forall a. a
splitAtEndFoldInvariantFailed =
  String -> String -> a
forall a. HasCallStack => String -> String -> a
moduleError String
"splitAtEndFold"
              String
"internal error: toSplit not longer than toScan"

-- | /O(n\/c)/ 'drop' @n xs@ returns the suffix of @xs@ after the first @n@
-- elements, or 'empty' if @n > 'length' xs@.
drop  :: Int64 -> ByteString -> ByteString
drop :: Int64 -> ByteString -> ByteString
drop Int64
i ByteString
p | Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0 = ByteString
p
drop Int64
i ByteString
cs0 = Int64 -> ByteString -> ByteString
forall {t}. Integral t => t -> ByteString -> ByteString
drop' Int64
i ByteString
cs0
  where drop' :: t -> ByteString -> ByteString
drop' t
0 ByteString
cs           = ByteString
cs
        drop' t
_ ByteString
Empty        = ByteString
Empty
        drop' t
n (Chunk StrictByteString
c ByteString
cs) =
          if t
n t -> t -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c)
            then StrictByteString -> ByteString -> ByteString
Chunk (Int -> StrictByteString -> StrictByteString
S.drop (t -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral t
n) StrictByteString
c) ByteString
cs
            else t -> ByteString -> ByteString
drop' (t
n t -> t -> t
forall a. Num a => a -> a -> a
- Int -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c)) ByteString
cs

-- | /O(n)/ @'dropEnd' n xs@ is equivalent to @'take' ('length' xs - n) xs@.
-- Drops @n@ elements from end of bytestring.
--
-- >>> dropEnd 3 "abcdefg"
-- "abcd"
-- >>> dropEnd 0 "abcdefg"
-- "abcdefg"
-- >>> dropEnd 4 "abc"
-- ""
--
-- @since 0.11.2.0
dropEnd :: Int64 -> ByteString -> ByteString
dropEnd :: Int64 -> ByteString -> ByteString
dropEnd Int64
i ByteString
p
  | Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0 = ByteString
p
  | Bool
otherwise = (StrictByteString -> ByteString -> ByteString)
-> (ByteString -> ByteString) -> Int64 -> ByteString -> ByteString
forall result.
(StrictByteString -> result -> result)
-> (ByteString -> result) -> Int64 -> ByteString -> result
splitAtEndFold StrictByteString -> ByteString -> ByteString
Chunk (ByteString -> ByteString -> ByteString
forall a b. a -> b -> a
const ByteString
Empty) Int64
i ByteString
p

-- | /O(n\/c)/ 'splitAt' @n xs@ is equivalent to @('take' n xs, 'drop' n xs)@.
splitAt :: Int64 -> ByteString -> (ByteString, ByteString)
splitAt :: Int64 -> ByteString -> (ByteString, ByteString)
splitAt Int64
i ByteString
cs0 | Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
<= Int64
0 = (ByteString
Empty, ByteString
cs0)
splitAt Int64
i ByteString
cs0 = Int64 -> ByteString -> (ByteString, ByteString)
forall {a}.
Integral a =>
a -> ByteString -> (ByteString, ByteString)
splitAt' Int64
i ByteString
cs0
  where splitAt' :: a -> ByteString -> (ByteString, ByteString)
splitAt' a
0 ByteString
cs           = (ByteString
Empty, ByteString
cs)
        splitAt' a
_ ByteString
Empty        = (ByteString
Empty, ByteString
Empty)
        splitAt' a
n (Chunk StrictByteString
c ByteString
cs) =
          if a
n a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c)
            then (StrictByteString -> ByteString -> ByteString
Chunk (Int -> StrictByteString -> StrictByteString
S.take (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
n) StrictByteString
c) ByteString
Empty
                 ,StrictByteString -> ByteString -> ByteString
Chunk (Int -> StrictByteString -> StrictByteString
S.drop (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
n) StrictByteString
c) ByteString
cs)
            else let (ByteString
cs', ByteString
cs'') = a -> ByteString -> (ByteString, ByteString)
splitAt' (a
n a -> a -> a
forall a. Num a => a -> a -> a
- Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c)) ByteString
cs
                   in (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c ByteString
cs', ByteString
cs'')


-- | Similar to 'Prelude.takeWhile',
-- returns the longest (possibly empty) prefix of elements
-- satisfying the predicate.
takeWhile :: (Word8 -> Bool) -> ByteString -> ByteString
takeWhile :: (Word8 -> Bool) -> ByteString -> ByteString
takeWhile Word8 -> Bool
f = ByteString -> ByteString
takeWhile'
  where takeWhile' :: ByteString -> ByteString
takeWhile' ByteString
Empty        = ByteString
Empty
        takeWhile' (Chunk StrictByteString
c ByteString
cs) =
          case (Word8 -> Bool) -> StrictByteString -> Int
S.findIndexOrLength (Bool -> Bool
not (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
f) StrictByteString
c of
            Int
0                  -> ByteString
Empty
            Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< StrictByteString -> Int
S.length StrictByteString
c -> StrictByteString -> ByteString -> ByteString
Chunk (Int -> StrictByteString -> StrictByteString
S.take Int
n StrictByteString
c) ByteString
Empty
              | Bool
otherwise      -> StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c (ByteString -> ByteString
takeWhile' ByteString
cs)

-- | Returns the longest (possibly empty) suffix of elements
-- satisfying the predicate.
--
-- @'takeWhileEnd' p@ is equivalent to @'reverse' . 'takeWhile' p . 'reverse'@.
--
-- >>> {-# LANGUAGE OverloadedLists #-)
-- >>> takeWhileEnd even [1,2,3,4,6]
-- [4,6]
--
-- @since 0.11.2.0
takeWhileEnd :: (Word8 -> Bool) -> ByteString -> ByteString
takeWhileEnd :: (Word8 -> Bool) -> ByteString -> ByteString
takeWhileEnd Word8 -> Bool
f = ByteString -> ByteString
takeWhileEnd'
  where takeWhileEnd' :: ByteString -> ByteString
takeWhileEnd' ByteString
Empty = ByteString
Empty
        takeWhileEnd' ByteString
cs    =
            (Bool, ByteString) -> ByteString
forall a b. (a, b) -> b
snd ((Bool, ByteString) -> ByteString)
-> (Bool, ByteString) -> ByteString
forall a b. (a -> b) -> a -> b
$ (StrictByteString -> (Bool, ByteString) -> (Bool, ByteString))
-> (Bool, ByteString) -> ByteString -> (Bool, ByteString)
forall a. (StrictByteString -> a -> a) -> a -> ByteString -> a
foldrChunks StrictByteString -> (Bool, ByteString) -> (Bool, ByteString)
takeTuple (Bool
True,ByteString
Empty) ByteString
cs
        takeTuple :: StrictByteString -> (Bool, ByteString) -> (Bool, ByteString)
takeTuple StrictByteString
_ (Bool
False, ByteString
bs) = (Bool
False,ByteString
bs)
        takeTuple StrictByteString
c (Bool
True,ByteString
bs)   =
           case (Word8 -> Bool) -> StrictByteString -> StrictByteString
S.takeWhileEnd Word8 -> Bool
f StrictByteString
c of
                StrictByteString
c' | StrictByteString -> Int
S.length StrictByteString
c' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== StrictByteString -> Int
S.length StrictByteString
c -> (Bool
True, StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c ByteString
bs)
                   | Bool
otherwise                 -> (Bool
False, StrictByteString -> ByteString
fromStrict StrictByteString
c' ByteString -> ByteString -> ByteString
`append` ByteString
bs)

-- | Similar to 'Prelude.dropWhile',
-- drops the longest (possibly empty) prefix of elements
-- satisfying the predicate and returns the remainder.
dropWhile :: (Word8 -> Bool) -> ByteString -> ByteString
dropWhile :: (Word8 -> Bool) -> ByteString -> ByteString
dropWhile Word8 -> Bool
f = ByteString -> ByteString
dropWhile'
  where dropWhile' :: ByteString -> ByteString
dropWhile' ByteString
Empty        = ByteString
Empty
        dropWhile' (Chunk StrictByteString
c ByteString
cs) =
          case (Word8 -> Bool) -> StrictByteString -> Int
S.findIndexOrLength (Bool -> Bool
not (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
f) StrictByteString
c of
            Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< StrictByteString -> Int
S.length StrictByteString
c -> StrictByteString -> ByteString -> ByteString
Chunk (Int -> StrictByteString -> StrictByteString
S.drop Int
n StrictByteString
c) ByteString
cs
              | Bool
otherwise      -> ByteString -> ByteString
dropWhile' ByteString
cs

-- | Similar to 'Prelude.dropWhileEnd',
-- drops the longest (possibly empty) suffix of elements
-- satisfying the predicate and returns the remainder.
--
-- @'dropWhileEnd' p@ is equivalent to @'reverse' . 'dropWhile' p . 'reverse'@.
--
-- >>> {-# LANGUAGE OverloadedLists #-)
-- >>> dropWhileEnd even [1,2,3,4,6]
-- [1,2,3]
--
-- @since 0.11.2.0
dropWhileEnd :: (Word8 -> Bool) -> ByteString -> ByteString
dropWhileEnd :: (Word8 -> Bool) -> ByteString -> ByteString
dropWhileEnd Word8 -> Bool
f = [StrictByteString] -> ByteString -> ByteString
go []
  where go :: [StrictByteString] -> ByteString -> ByteString
go [StrictByteString]
acc (Chunk StrictByteString
c ByteString
cs)
            | Word8 -> Bool
f (HasCallStack => StrictByteString -> Word8
StrictByteString -> Word8
S.last StrictByteString
c) = [StrictByteString] -> ByteString -> ByteString
go (StrictByteString
c StrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
: [StrictByteString]
acc) ByteString
cs
            | Bool
otherwise    = (ByteString -> StrictByteString -> ByteString)
-> ByteString -> [StrictByteString] -> ByteString
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl ((StrictByteString -> ByteString -> ByteString)
-> ByteString -> StrictByteString -> ByteString
forall a b c. (a -> b -> c) -> b -> a -> c
flip StrictByteString -> ByteString -> ByteString
Chunk) ([StrictByteString] -> ByteString -> ByteString
go [] ByteString
cs) (StrictByteString
c StrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
: [StrictByteString]
acc)
        go [StrictByteString]
acc ByteString
Empty       = [StrictByteString] -> ByteString
dropEndBytes [StrictByteString]
acc
        dropEndBytes :: [StrictByteString] -> ByteString
dropEndBytes []         = ByteString
Empty
        dropEndBytes (StrictByteString
x : [StrictByteString]
xs)   =
            case (Word8 -> Bool) -> StrictByteString -> StrictByteString
S.dropWhileEnd Word8 -> Bool
f StrictByteString
x of
                 StrictByteString
x' | StrictByteString -> Bool
S.null StrictByteString
x' -> [StrictByteString] -> ByteString
dropEndBytes [StrictByteString]
xs
                    | Bool
otherwise -> (ByteString -> StrictByteString -> ByteString)
-> ByteString -> [StrictByteString] -> ByteString
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' ((StrictByteString -> ByteString -> ByteString)
-> ByteString -> StrictByteString -> ByteString
forall a b c. (a -> b -> c) -> b -> a -> c
flip StrictByteString -> ByteString -> ByteString
Chunk) ByteString
Empty (StrictByteString
x' StrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
: [StrictByteString]
xs)

-- | Similar to 'Prelude.break',
-- returns the longest (possibly empty) prefix of elements which __do not__
-- satisfy the predicate and the remainder of the string.
--
-- 'break' @p@ is equivalent to @'span' (not . p)@ and to @('takeWhile' (not . p) &&& 'dropWhile' (not . p))@.
--
break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
break Word8 -> Bool
f = ByteString -> (ByteString, ByteString)
break'
  where break' :: ByteString -> (ByteString, ByteString)
break' ByteString
Empty        = (ByteString
Empty, ByteString
Empty)
        break' (Chunk StrictByteString
c ByteString
cs) =
          case (Word8 -> Bool) -> StrictByteString -> Int
S.findIndexOrLength Word8 -> Bool
f StrictByteString
c of
            Int
0                  -> (ByteString
Empty, StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c ByteString
cs)
            Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< StrictByteString -> Int
S.length StrictByteString
c -> (StrictByteString -> ByteString -> ByteString
Chunk (Int -> StrictByteString -> StrictByteString
S.take Int
n StrictByteString
c) ByteString
Empty
                                  ,StrictByteString -> ByteString -> ByteString
Chunk (Int -> StrictByteString -> StrictByteString
S.drop Int
n StrictByteString
c) ByteString
cs)
              | Bool
otherwise      -> let (ByteString
cs', ByteString
cs'') = ByteString -> (ByteString, ByteString)
break' ByteString
cs
                                   in (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c ByteString
cs', ByteString
cs'')


-- | Returns the longest (possibly empty) suffix of elements which __do not__
-- satisfy the predicate and the remainder of the string.
--
-- 'breakEnd' @p@ is equivalent to @'spanEnd' (not . p)@ and to @('takeWhileEnd' (not . p) &&& 'dropWhileEnd' (not . p))@.
--
-- @since 0.11.2.0
breakEnd :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
breakEnd :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
breakEnd  Word8 -> Bool
f = [StrictByteString] -> ByteString -> (ByteString, ByteString)
go []
  where go :: [StrictByteString] -> ByteString -> (ByteString, ByteString)
go [StrictByteString]
acc (Chunk StrictByteString
c ByteString
cs)
            | Word8 -> Bool
f (HasCallStack => StrictByteString -> Word8
StrictByteString -> Word8
S.last StrictByteString
c) = ((ByteString, ByteString)
 -> StrictByteString -> (ByteString, ByteString))
-> (ByteString, ByteString)
-> [StrictByteString]
-> (ByteString, ByteString)
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl ((StrictByteString
 -> (ByteString, ByteString) -> (ByteString, ByteString))
-> (ByteString, ByteString)
-> StrictByteString
-> (ByteString, ByteString)
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((StrictByteString
  -> (ByteString, ByteString) -> (ByteString, ByteString))
 -> (ByteString, ByteString)
 -> StrictByteString
 -> (ByteString, ByteString))
-> (StrictByteString
    -> (ByteString, ByteString) -> (ByteString, ByteString))
-> (ByteString, ByteString)
-> StrictByteString
-> (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ (ByteString -> ByteString)
-> (ByteString, ByteString) -> (ByteString, ByteString)
forall a b c. (a -> b) -> (a, c) -> (b, c)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
BF.first ((ByteString -> ByteString)
 -> (ByteString, ByteString) -> (ByteString, ByteString))
-> (StrictByteString -> ByteString -> ByteString)
-> StrictByteString
-> (ByteString, ByteString)
-> (ByteString, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> ByteString -> ByteString
Chunk) ([StrictByteString] -> ByteString -> (ByteString, ByteString)
go [] ByteString
cs) (StrictByteString
c StrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
: [StrictByteString]
acc)
            | Bool
otherwise = [StrictByteString] -> ByteString -> (ByteString, ByteString)
go (StrictByteString
c StrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
: [StrictByteString]
acc) ByteString
cs
        go [StrictByteString]
acc ByteString
Empty = [StrictByteString] -> (ByteString, ByteString)
dropEndBytes [StrictByteString]
acc
        dropEndBytes :: [StrictByteString] -> (ByteString, ByteString)
dropEndBytes [] = (ByteString
Empty, ByteString
Empty)
        dropEndBytes (StrictByteString
x : [StrictByteString]
xs) =
            case (Word8 -> Bool)
-> StrictByteString -> (StrictByteString, StrictByteString)
S.breakEnd Word8 -> Bool
f StrictByteString
x of
                 (StrictByteString
x', StrictByteString
x'') | StrictByteString -> Bool
S.null StrictByteString
x' -> let (ByteString
y, ByteString
y') = [StrictByteString] -> (ByteString, ByteString)
dropEndBytes [StrictByteString]
xs
                                           in (ByteString
y, ByteString
y' ByteString -> ByteString -> ByteString
`append` StrictByteString -> ByteString
fromStrict StrictByteString
x)
                           | Bool
otherwise ->
                                ((ByteString, ByteString)
 -> StrictByteString -> (ByteString, ByteString))
-> (ByteString, ByteString)
-> [StrictByteString]
-> (ByteString, ByteString)
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' ((StrictByteString
 -> (ByteString, ByteString) -> (ByteString, ByteString))
-> (ByteString, ByteString)
-> StrictByteString
-> (ByteString, ByteString)
forall a b c. (a -> b -> c) -> b -> a -> c
flip ((StrictByteString
  -> (ByteString, ByteString) -> (ByteString, ByteString))
 -> (ByteString, ByteString)
 -> StrictByteString
 -> (ByteString, ByteString))
-> (StrictByteString
    -> (ByteString, ByteString) -> (ByteString, ByteString))
-> (ByteString, ByteString)
-> StrictByteString
-> (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ (ByteString -> ByteString)
-> (ByteString, ByteString) -> (ByteString, ByteString)
forall a b c. (a -> b) -> (a, c) -> (b, c)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
BF.first ((ByteString -> ByteString)
 -> (ByteString, ByteString) -> (ByteString, ByteString))
-> (StrictByteString -> ByteString -> ByteString)
-> StrictByteString
-> (ByteString, ByteString)
-> (ByteString, ByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> ByteString -> ByteString
Chunk) (StrictByteString -> ByteString
fromStrict StrictByteString
x', StrictByteString -> ByteString
fromStrict StrictByteString
x'') [StrictByteString]
xs


--
-- TODO
--
-- Add rules
--

{-
-- | 'breakByte' breaks its ByteString argument at the first occurrence
-- of the specified byte. It is more efficient than 'break' as it is
-- implemented with @memchr(3)@. I.e.
--
-- > break (==99) "abcd" == breakByte 99 "abcd" -- fromEnum 'c' == 99
--
breakByte :: Word8 -> ByteString -> (ByteString, ByteString)
breakByte c (LPS ps) = case (breakByte' ps) of (a,b) -> (LPS a, LPS b)
  where breakByte' []     = ([], [])
        breakByte' (x:xs) =
          case P.elemIndex c x of
            Just 0  -> ([], x : xs)
            Just n  -> (P.take n x : [], P.drop n x : xs)
            Nothing -> let (xs', xs'') = breakByte' xs
                        in (x : xs', xs'')

-- | 'spanByte' breaks its ByteString argument at the first
-- occurrence of a byte other than its argument. It is more efficient
-- than 'span (==)'
--
-- > span  (==99) "abcd" == spanByte 99 "abcd" -- fromEnum 'c' == 99
--
spanByte :: Word8 -> ByteString -> (ByteString, ByteString)
spanByte c (LPS ps) = case (spanByte' ps) of (a,b) -> (LPS a, LPS b)
  where spanByte' []     = ([], [])
        spanByte' (x:xs) =
          case P.spanByte c x of
            (x', x'') | P.null x'  -> ([], x : xs)
                      | P.null x'' -> let (xs', xs'') = spanByte' xs
                                       in (x : xs', xs'')
                      | otherwise  -> (x' : [], x'' : xs)
-}

-- | Similar to 'Prelude.span',
-- returns the longest (possibly empty) prefix of elements
-- satisfying the predicate and the remainder of the string.
--
-- 'span' @p@ is equivalent to @'break' (not . p)@ and to @('takeWhile' p &&& 'dropWhile' p)@.
--
span :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
span :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
span Word8 -> Bool
p = (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
break (Bool -> Bool
not (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
p)

-- | Returns the longest (possibly empty) suffix of elements
-- satisfying the predicate and the remainder of the string.
--
-- 'spanEnd' @p@ is equivalent to @'breakEnd' (not . p)@ and to @('takeWhileEnd' p &&& 'dropWhileEnd' p)@.
--
-- We have
--
-- > spanEnd (not . isSpace) "x y z" == ("x y ", "z")
--
-- and
--
-- > spanEnd (not . isSpace) ps
-- >    ==
-- > let (x, y) = span (not . isSpace) (reverse ps) in (reverse y, reverse x)
--
-- @since 0.11.2.0
spanEnd :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
spanEnd :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
spanEnd Word8 -> Bool
p = (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
breakEnd (Bool -> Bool
not (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
p)

-- | /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 (==97) "aabbaca" == ["","","bb","c",""] -- fromEnum 'a' == 97
-- > splitWith undefined ""     == []                  -- and not [""]
--
splitWith :: (Word8 -> Bool) -> ByteString -> [ByteString]
splitWith :: (Word8 -> Bool) -> ByteString -> [ByteString]
splitWith Word8 -> Bool
_ ByteString
Empty          = []
splitWith Word8 -> Bool
p (Chunk StrictByteString
c0 ByteString
cs0) = [StrictByteString]
-> [StrictByteString] -> ByteString -> [ByteString]
comb [] ((Word8 -> Bool) -> StrictByteString -> [StrictByteString]
S.splitWith Word8 -> Bool
p StrictByteString
c0) ByteString
cs0

  where comb :: [P.ByteString] -> [P.ByteString] -> ByteString -> [ByteString]
        comb :: [StrictByteString]
-> [StrictByteString] -> ByteString -> [ByteString]
comb [StrictByteString]
acc [StrictByteString
s] ByteString
Empty        = [[StrictByteString] -> ByteString
revChunks (StrictByteString
sStrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
:[StrictByteString]
acc)]
        comb [StrictByteString]
acc [StrictByteString
s] (Chunk StrictByteString
c ByteString
cs) = [StrictByteString]
-> [StrictByteString] -> ByteString -> [ByteString]
comb (StrictByteString
sStrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
:[StrictByteString]
acc) ((Word8 -> Bool) -> StrictByteString -> [StrictByteString]
S.splitWith Word8 -> Bool
p StrictByteString
c) ByteString
cs
        comb [StrictByteString]
acc (StrictByteString
s:[StrictByteString]
ss) ByteString
cs        = [StrictByteString] -> ByteString
revChunks (StrictByteString
sStrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
:[StrictByteString]
acc) ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: [StrictByteString]
-> [StrictByteString] -> ByteString -> [ByteString]
comb [] [StrictByteString]
ss ByteString
cs
{-# INLINE splitWith #-}

-- | /O(n)/ Break a 'ByteString' into pieces separated by the byte
-- argument, consuming the delimiter. I.e.
--
-- > split 10  "a\nb\nd\ne" == ["a","b","d","e"]   -- fromEnum '\n' == 10
-- > split 97  "aXaXaXa"    == ["","X","X","X",""] -- fromEnum 'a' == 97
-- > split 120 "x"          == ["",""]             -- fromEnum 'x' == 120
-- > split undefined ""     == []                  -- and not [""]
--
-- and
--
-- > intercalate [c] . split c == id
-- > split == splitWith . (==)
--
-- As for all splitting functions in this library, this function does
-- not copy the substrings, it just constructs new 'ByteString's that
-- are slices of the original.
--
split :: Word8 -> ByteString -> [ByteString]
split :: Word8 -> ByteString -> [ByteString]
split Word8
_ ByteString
Empty     = []
split Word8
w (Chunk StrictByteString
c0 ByteString
cs0) = [StrictByteString]
-> [StrictByteString] -> ByteString -> [ByteString]
comb [] (Word8 -> StrictByteString -> [StrictByteString]
S.split Word8
w StrictByteString
c0) ByteString
cs0

  where comb :: [P.ByteString] -> [P.ByteString] -> ByteString -> [ByteString]
        comb :: [StrictByteString]
-> [StrictByteString] -> ByteString -> [ByteString]
comb [StrictByteString]
acc [StrictByteString
s] ByteString
Empty        = [[StrictByteString] -> ByteString
revChunks (StrictByteString
sStrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
:[StrictByteString]
acc)]
        comb [StrictByteString]
acc [StrictByteString
s] (Chunk StrictByteString
c ByteString
cs) = [StrictByteString]
-> [StrictByteString] -> ByteString -> [ByteString]
comb (StrictByteString
sStrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
:[StrictByteString]
acc) (Word8 -> StrictByteString -> [StrictByteString]
S.split Word8
w StrictByteString
c) ByteString
cs
        comb [StrictByteString]
acc (StrictByteString
s:[StrictByteString]
ss) ByteString
cs        = [StrictByteString] -> ByteString
revChunks (StrictByteString
sStrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
:[StrictByteString]
acc) ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: [StrictByteString]
-> [StrictByteString] -> ByteString -> [ByteString]
comb [] [StrictByteString]
ss ByteString
cs
{-# INLINE split #-}

-- | 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 string 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]
group :: ByteString -> [ByteString]
group = ByteString -> [ByteString]
go
  where
    go :: ByteString -> [ByteString]
go ByteString
Empty        = []
    go (Chunk StrictByteString
c ByteString
cs)
      | StrictByteString -> Int
S.length StrictByteString
c Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1  = [StrictByteString] -> Word8 -> ByteString -> [ByteString]
to [StrictByteString
c] (StrictByteString -> Word8
S.unsafeHead StrictByteString
c) ByteString
cs
      | Bool
otherwise        = [StrictByteString] -> Word8 -> ByteString -> [ByteString]
to [Int -> StrictByteString -> StrictByteString
S.unsafeTake Int
1 StrictByteString
c] (StrictByteString -> Word8
S.unsafeHead StrictByteString
c) (StrictByteString -> ByteString -> ByteString
Chunk (StrictByteString -> StrictByteString
S.unsafeTail StrictByteString
c) ByteString
cs)

    to :: [StrictByteString] -> Word8 -> ByteString -> [ByteString]
to [StrictByteString]
acc !Word8
_ ByteString
Empty        = [[StrictByteString] -> ByteString
revNonEmptyChunks [StrictByteString]
acc]
    to [StrictByteString]
acc !Word8
w (Chunk StrictByteString
c ByteString
cs) =
      case (Word8 -> Bool) -> StrictByteString -> Int
S.findIndexOrLength (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word8
w) StrictByteString
c of
        Int
0                    -> [StrictByteString] -> ByteString
revNonEmptyChunks [StrictByteString]
acc
                              ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: ByteString -> [ByteString]
go (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c ByteString
cs)
        Int
n | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== StrictByteString -> Int
S.length StrictByteString
c  -> [StrictByteString] -> Word8 -> ByteString -> [ByteString]
to (Int -> StrictByteString -> StrictByteString
S.unsafeTake Int
n StrictByteString
c StrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
: [StrictByteString]
acc) Word8
w ByteString
cs
          | Bool
otherwise        -> [StrictByteString] -> ByteString
revNonEmptyChunks (Int -> StrictByteString -> StrictByteString
S.unsafeTake Int
n StrictByteString
c StrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
: [StrictByteString]
acc)
                              ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: ByteString -> [ByteString]
go (StrictByteString -> ByteString -> ByteString
Chunk (Int -> StrictByteString -> StrictByteString
S.unsafeDrop Int
n StrictByteString
c) ByteString
cs)

-- | The 'groupBy' function is the non-overloaded version of 'group'.
--
groupBy :: (Word8 -> Word8 -> Bool) -> ByteString -> [ByteString]
groupBy :: (Word8 -> Word8 -> Bool) -> ByteString -> [ByteString]
groupBy Word8 -> Word8 -> Bool
k = ByteString -> [ByteString]
go
  where
    go :: ByteString -> [ByteString]
go ByteString
Empty        = []
    go (Chunk StrictByteString
c ByteString
cs)
      | StrictByteString -> Int
S.length StrictByteString
c Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
1  = [StrictByteString] -> Word8 -> ByteString -> [ByteString]
to [StrictByteString
c] (StrictByteString -> Word8
S.unsafeHead StrictByteString
c) ByteString
cs
      | Bool
otherwise        = [StrictByteString] -> Word8 -> ByteString -> [ByteString]
to [Int -> StrictByteString -> StrictByteString
S.unsafeTake Int
1 StrictByteString
c] (StrictByteString -> Word8
S.unsafeHead StrictByteString
c) (StrictByteString -> ByteString -> ByteString
Chunk (StrictByteString -> StrictByteString
S.unsafeTail StrictByteString
c) ByteString
cs)

    to :: [StrictByteString] -> Word8 -> ByteString -> [ByteString]
to [StrictByteString]
acc !Word8
_ ByteString
Empty        = [[StrictByteString] -> ByteString
revNonEmptyChunks [StrictByteString]
acc]
    to [StrictByteString]
acc !Word8
w (Chunk StrictByteString
c ByteString
cs) =
      case (Word8 -> Bool) -> StrictByteString -> Int
S.findIndexOrLength (Bool -> Bool
not (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Word8 -> Bool
k Word8
w) StrictByteString
c of
        Int
0                    -> [StrictByteString] -> ByteString
revNonEmptyChunks [StrictByteString]
acc
                              ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: ByteString -> [ByteString]
go (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c ByteString
cs)
        Int
n | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== StrictByteString -> Int
S.length StrictByteString
c  -> [StrictByteString] -> Word8 -> ByteString -> [ByteString]
to (Int -> StrictByteString -> StrictByteString
S.unsafeTake Int
n StrictByteString
c StrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
: [StrictByteString]
acc) Word8
w ByteString
cs
          | Bool
otherwise        -> [StrictByteString] -> ByteString
revNonEmptyChunks (Int -> StrictByteString -> StrictByteString
S.unsafeTake Int
n StrictByteString
c StrictByteString -> [StrictByteString] -> [StrictByteString]
forall a. a -> [a] -> [a]
: [StrictByteString]
acc)
                              ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: ByteString -> [ByteString]
go (StrictByteString -> ByteString -> ByteString
Chunk (Int -> StrictByteString -> StrictByteString
S.unsafeDrop Int
n StrictByteString
c) ByteString
cs)

-- | /O(n)/ The 'intercalate' function takes a 'ByteString' and a list of
-- 'ByteString's and concatenates the list after interspersing the first
-- argument between each element of the list.
intercalate :: ByteString -> [ByteString] -> ByteString
intercalate :: ByteString -> [ByteString] -> ByteString
intercalate ByteString
s = [ByteString] -> ByteString
concat ([ByteString] -> ByteString)
-> ([ByteString] -> [ByteString]) -> [ByteString] -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
List.intersperse ByteString
s

-- ---------------------------------------------------------------------
-- Indexing ByteStrings

-- | /O(c)/ 'ByteString' index (subscript) operator, starting from 0.
--
-- This is a partial function, consider using 'indexMaybe' instead.
index :: HasCallStack => ByteString -> Int64 -> Word8
index :: HasCallStack => ByteString -> Int64 -> Word8
index ByteString
_  Int64
i | Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
0  = String -> String -> Word8
forall a. HasCallStack => String -> String -> a
moduleError String
"index" (String
"negative index: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int64 -> String
forall a. Show a => a -> String
show Int64
i)
index ByteString
cs0 Int64
i         = ByteString -> Int64 -> Word8
forall {a}. (Show a, Integral a) => ByteString -> a -> Word8
index' ByteString
cs0 Int64
i
  where index' :: ByteString -> a -> Word8
index' ByteString
Empty     a
n = String -> String -> Word8
forall a. HasCallStack => String -> String -> a
moduleError String
"index" (String
"index too large: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ a -> String
forall a. Show a => a -> String
show a
n)
        index' (Chunk StrictByteString
c ByteString
cs) a
n
          | a
n a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c) =
              ByteString -> a -> Word8
index' ByteString
cs (a
n a -> a -> a
forall a. Num a => a -> a -> a
- Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c))
          | Bool
otherwise       = StrictByteString -> Int -> Word8
S.unsafeIndex StrictByteString
c (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
n)

-- | /O(c)/ 'ByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
indexMaybe :: ByteString -> Int64 -> Maybe Word8
indexMaybe :: ByteString -> Int64 -> Maybe Word8
indexMaybe ByteString
_ Int64
i | Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Int64
0 = Maybe Word8
forall a. Maybe a
Nothing
indexMaybe ByteString
cs0 Int64
i       = ByteString -> Int64 -> Maybe Word8
forall {a}. Integral a => ByteString -> a -> Maybe Word8
index' ByteString
cs0 Int64
i
  where index' :: ByteString -> a -> Maybe Word8
index' ByteString
Empty a
_ = Maybe Word8
forall a. Maybe a
Nothing
        index' (Chunk StrictByteString
c ByteString
cs) a
n
          | a
n a -> a -> Bool
forall a. Ord a => a -> a -> Bool
>= Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c) =
              ByteString -> a -> Maybe Word8
index' ByteString
cs (a
n a -> a -> a
forall a. Num a => a -> a -> a
- Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c))
          | Bool
otherwise       = Word8 -> Maybe Word8
forall a. a -> Maybe a
Just (Word8 -> Maybe Word8) -> Word8 -> Maybe Word8
forall a b. (a -> b) -> a -> b
$! StrictByteString -> Int -> Word8
S.unsafeIndex StrictByteString
c (a -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral a
n)

-- | /O(1)/ 'ByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
(!?) :: ByteString -> Int64 -> Maybe Word8
!? :: ByteString -> Int64 -> Maybe Word8
(!?) = ByteString -> Int64 -> Maybe Word8
indexMaybe
{-# INLINE (!?) #-}

-- | /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
elemIndex :: Word8 -> ByteString -> Maybe Int64
elemIndex Word8
w = Int64 -> ByteString -> Maybe Int64
forall {a}. Num a => a -> ByteString -> Maybe a
elemIndex' Int64
0
  where elemIndex' :: a -> ByteString -> Maybe a
elemIndex' a
_ ByteString
Empty        = Maybe a
forall a. Maybe a
Nothing
        elemIndex' a
n (Chunk StrictByteString
c ByteString
cs) =
          case Word8 -> StrictByteString -> Maybe Int
S.elemIndex Word8
w StrictByteString
c of
            Maybe Int
Nothing -> a -> ByteString -> Maybe a
elemIndex' (a
n a -> a -> a
forall a. Num a => a -> a -> a
+ Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c)) ByteString
cs
            Just Int
i  -> a -> Maybe a
forall a. a -> Maybe a
Just (a
n a -> a -> a
forall a. Num a => a -> a -> a
+ Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i)

-- | /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 = case elemIndex c (reverse xs) of
-- >   Nothing -> Nothing
-- >   Just i  -> Just (length xs - 1 - i)
--
-- @since 0.10.6.0
elemIndexEnd :: Word8 -> ByteString -> Maybe Int64
elemIndexEnd :: Word8 -> ByteString -> Maybe Int64
elemIndexEnd = (Word8 -> Bool) -> ByteString -> Maybe Int64
findIndexEnd ((Word8 -> Bool) -> ByteString -> Maybe Int64)
-> (Word8 -> Word8 -> Bool) -> Word8 -> ByteString -> Maybe Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
(==)
{-# INLINE elemIndexEnd #-}

-- | /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]
elemIndices :: Word8 -> ByteString -> [Int64]
elemIndices Word8
w = Int64 -> ByteString -> [Int64]
forall {t}. Num t => t -> ByteString -> [t]
elemIndices' Int64
0
  where elemIndices' :: t -> ByteString -> [t]
elemIndices' t
_ ByteString
Empty        = []
        elemIndices' t
n (Chunk StrictByteString
c ByteString
cs) = (Int -> t) -> [Int] -> [t]
forall a b. (a -> b) -> [a] -> [b]
List.map ((t -> t -> t
forall a. Num a => a -> a -> a
+t
n)(t -> t) -> (Int -> t) -> Int -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Int -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral) (Word8 -> StrictByteString -> [Int]
S.elemIndices Word8
w StrictByteString
c)
                             [t] -> [t] -> [t]
forall a. [a] -> [a] -> [a]
++ t -> ByteString -> [t]
elemIndices' (t
n t -> t -> t
forall a. Num a => a -> a -> a
+ Int -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c)) ByteString
cs

-- | 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
count :: Word8 -> ByteString -> Int64
count Word8
w = (Int64 -> StrictByteString -> Int64)
-> Int64 -> ByteString -> Int64
forall a. (a -> StrictByteString -> a) -> a -> ByteString -> a
foldlChunks (\Int64
n StrictByteString
c -> Int64
n Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> StrictByteString -> Int
S.count Word8
w StrictByteString
c)) Int64
0

-- | 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
findIndex :: (Word8 -> Bool) -> ByteString -> Maybe Int64
findIndex Word8 -> Bool
k = Int64 -> ByteString -> Maybe Int64
forall {a}. Num a => a -> ByteString -> Maybe a
findIndex' Int64
0
  where findIndex' :: a -> ByteString -> Maybe a
findIndex' a
_ ByteString
Empty        = Maybe a
forall a. Maybe a
Nothing
        findIndex' a
n (Chunk StrictByteString
c ByteString
cs) =
          case (Word8 -> Bool) -> StrictByteString -> Maybe Int
S.findIndex Word8 -> Bool
k StrictByteString
c of
            Maybe Int
Nothing -> a -> ByteString -> Maybe a
findIndex' (a
n a -> a -> a
forall a. Num a => a -> a -> a
+ Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c)) ByteString
cs
            Just Int
i  -> a -> Maybe a
forall a. a -> Maybe a
Just (a
n a -> a -> a
forall a. Num a => a -> a -> a
+ Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i)
{-# INLINE findIndex #-}

-- | The 'findIndexEnd' function takes a predicate and a 'ByteString' and
-- returns the index of the last element in the ByteString
-- satisfying the predicate.
--
-- @since 0.10.12.0
findIndexEnd :: (Word8 -> Bool) -> ByteString -> Maybe Int64
findIndexEnd :: (Word8 -> Bool) -> ByteString -> Maybe Int64
findIndexEnd Word8 -> Bool
k = Int -> ByteString -> Maybe Int64
forall {a}. Num a => Int -> ByteString -> Maybe a
findIndexEnd' Int
0
  where
    findIndexEnd' :: Int -> ByteString -> Maybe a
findIndexEnd' Int
_ ByteString
Empty = Maybe a
forall a. Maybe a
Nothing
    findIndexEnd' Int
n (Chunk StrictByteString
c ByteString
cs) =
      let !n' :: Int
n' = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ StrictByteString -> Int
S.length StrictByteString
c
          !i :: Maybe a
i  = Int -> a
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> a) -> (Int -> Int) -> Int -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+) (Int -> a) -> Maybe Int -> Maybe a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Word8 -> Bool) -> StrictByteString -> Maybe Int
S.findIndexEnd Word8 -> Bool
k StrictByteString
c
      in Int -> ByteString -> Maybe a
findIndexEnd' Int
n' ByteString
cs Maybe a -> Maybe a -> Maybe a
forall a. Maybe a -> Maybe a -> Maybe a
forall (m :: * -> *) a. MonadPlus m => m a -> m a -> m a
`mplus` Maybe a
i
{-# INLINE findIndexEnd #-}

-- | /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
find :: (Word8 -> Bool) -> ByteString -> Maybe Word8
find Word8 -> Bool
f = ByteString -> Maybe Word8
find'
  where find' :: ByteString -> Maybe Word8
find' ByteString
Empty        = Maybe Word8
forall a. Maybe a
Nothing
        find' (Chunk StrictByteString
c ByteString
cs) = case (Word8 -> Bool) -> StrictByteString -> Maybe Word8
S.find Word8 -> Bool
f StrictByteString
c of
            Maybe Word8
Nothing -> ByteString -> Maybe Word8
find' ByteString
cs
            Just Word8
w  -> Word8 -> Maybe Word8
forall a. a -> Maybe a
Just Word8
w
{-# INLINE find #-}

-- | The 'findIndices' function extends 'findIndex', by returning the
-- indices of all elements satisfying the predicate, in ascending order.
findIndices :: (Word8 -> Bool) -> ByteString -> [Int64]
findIndices :: (Word8 -> Bool) -> ByteString -> [Int64]
findIndices Word8 -> Bool
k = Int64 -> ByteString -> [Int64]
forall {t}. Num t => t -> ByteString -> [t]
findIndices' Int64
0
  where findIndices' :: t -> ByteString -> [t]
findIndices' t
_ ByteString
Empty        = []
        findIndices' t
n (Chunk StrictByteString
c ByteString
cs) = (Int -> t) -> [Int] -> [t]
forall a b. (a -> b) -> [a] -> [b]
List.map ((t -> t -> t
forall a. Num a => a -> a -> a
+t
n)(t -> t) -> (Int -> t) -> Int -> t
forall b c a. (b -> c) -> (a -> b) -> a -> c
.Int -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral) ((Word8 -> Bool) -> StrictByteString -> [Int]
S.findIndices Word8 -> Bool
k StrictByteString
c)
                             [t] -> [t] -> [t]
forall a. [a] -> [a] -> [a]
++ t -> ByteString -> [t]
findIndices' (t
n t -> t -> t
forall a. Num a => a -> a -> a
+ Int -> t
forall a b. (Integral a, Num b) => a -> b
fromIntegral (StrictByteString -> Int
S.length StrictByteString
c)) ByteString
cs
{-# INLINE findIndices #-}

-- ---------------------------------------------------------------------
-- Searching ByteStrings

-- | /O(n)/ 'elem' is the 'ByteString' membership predicate.
elem :: Word8 -> ByteString -> Bool
elem :: Word8 -> ByteString -> Bool
elem Word8
w ByteString
cs = case Word8 -> ByteString -> Maybe Int64
elemIndex Word8
w ByteString
cs of Maybe Int64
Nothing -> Bool
False ; Maybe Int64
_ -> Bool
True

-- | /O(n)/ 'notElem' is the inverse of 'elem'
notElem :: Word8 -> ByteString -> Bool
notElem :: Word8 -> ByteString -> Bool
notElem Word8
w ByteString
cs = Bool -> Bool
not (Word8
w Word8 -> ByteString -> Bool
`elem` ByteString
cs)

-- | /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
filter :: (Word8 -> Bool) -> ByteString -> ByteString
filter Word8 -> Bool
p = ByteString -> ByteString
go
    where
        go :: ByteString -> ByteString
go ByteString
Empty        = ByteString
Empty
        go (Chunk StrictByteString
x ByteString
xs) = StrictByteString -> ByteString -> ByteString
chunk ((Word8 -> Bool) -> StrictByteString -> StrictByteString
S.filter Word8 -> Bool
p StrictByteString
x) (ByteString -> ByteString
go ByteString
xs)
{-# INLINE filter #-}

{-
-- | /O(n)/ and /O(n\/c) space/ A first order equivalent of /filter .
-- (==)/, for the common case of filtering a single byte. It is more
-- efficient to use /filterByte/ in this case.
--
-- > filterByte == filter . (==)
--
-- filterByte is around 10x faster, and uses much less space, than its
-- filter equivalent
filterByte :: Word8 -> ByteString -> ByteString
filterByte w ps = replicate (count w ps) w
{-# INLINE filterByte #-}

{-# RULES
"ByteString specialise filter (== x)" forall x.
  filter ((==) x) = filterByte x

"ByteString specialise filter (== x)" forall x.
 filter (== x) = filterByte x
  #-}
-}

{-
-- | /O(n)/ A first order equivalent of /filter . (\/=)/, for the common
-- case of filtering a single byte out of a list. It is more efficient
-- to use /filterNotByte/ in this case.
--
-- > filterNotByte == filter . (/=)
--
-- filterNotByte is around 2x faster than its filter equivalent.
filterNotByte :: Word8 -> ByteString -> ByteString
filterNotByte w (LPS xs) = LPS (filterMap (P.filterNotByte w) xs)
-}

-- | /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)
partition :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
partition Word8 -> Bool
_ ByteString
Empty = (ByteString
Empty, ByteString
Empty)
partition Word8 -> Bool
p (Chunk StrictByteString
x ByteString
xs) = (StrictByteString -> ByteString -> ByteString
chunk StrictByteString
t ByteString
ts, StrictByteString -> ByteString -> ByteString
chunk StrictByteString
f ByteString
fs)
  where
    (StrictByteString
t,   StrictByteString
f) = (Word8 -> Bool)
-> StrictByteString -> (StrictByteString, StrictByteString)
S.partition Word8 -> Bool
p StrictByteString
x
    (ByteString
ts, ByteString
fs) = (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
partition   Word8 -> Bool
p ByteString
xs

-- ---------------------------------------------------------------------
-- Searching for substrings

-- | /O(n)/ The 'isPrefixOf' function takes two ByteStrings and returns 'True'
-- iff the first is a prefix of the second.
isPrefixOf :: ByteString -> ByteString -> Bool
isPrefixOf :: ByteString -> ByteString -> Bool
isPrefixOf ByteString
Empty ByteString
_  = Bool
True
isPrefixOf ByteString
_ ByteString
Empty  = Bool
False
isPrefixOf (Chunk StrictByteString
x ByteString
xs) (Chunk StrictByteString
y ByteString
ys)
    | StrictByteString -> Int
S.length StrictByteString
x Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== StrictByteString -> Int
S.length StrictByteString
y = StrictByteString
x StrictByteString -> StrictByteString -> Bool
forall a. Eq a => a -> a -> Bool
== StrictByteString
y  Bool -> Bool -> Bool
&& ByteString -> ByteString -> Bool
isPrefixOf ByteString
xs ByteString
ys
    | StrictByteString -> Int
S.length StrictByteString
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<  StrictByteString -> Int
S.length StrictByteString
y = StrictByteString
x StrictByteString -> StrictByteString -> Bool
forall a. Eq a => a -> a -> Bool
== StrictByteString
yh Bool -> Bool -> Bool
&& ByteString -> ByteString -> Bool
isPrefixOf ByteString
xs (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
yt ByteString
ys)
    | Bool
otherwise                = StrictByteString
xh StrictByteString -> StrictByteString -> Bool
forall a. Eq a => a -> a -> Bool
== StrictByteString
y Bool -> Bool -> Bool
&& ByteString -> ByteString -> Bool
isPrefixOf (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
xt ByteString
xs) ByteString
ys
  where (StrictByteString
xh,StrictByteString
xt) = Int -> StrictByteString -> (StrictByteString, StrictByteString)
S.splitAt (StrictByteString -> Int
S.length StrictByteString
y) StrictByteString
x
        (StrictByteString
yh,StrictByteString
yt) = Int -> StrictByteString -> (StrictByteString, StrictByteString)
S.splitAt (StrictByteString -> Int
S.length StrictByteString
x) StrictByteString
y

-- | /O(n)/ The 'stripPrefix' function takes two ByteStrings and returns 'Just'
-- the remainder of the second iff the first is its prefix, and otherwise
-- 'Nothing'.
--
-- @since 0.10.8.0
stripPrefix :: ByteString -> ByteString -> Maybe ByteString
stripPrefix :: ByteString -> ByteString -> Maybe ByteString
stripPrefix ByteString
Empty ByteString
bs  = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just ByteString
bs
stripPrefix ByteString
_ ByteString
Empty  = Maybe ByteString
forall a. Maybe a
Nothing
stripPrefix (Chunk StrictByteString
x ByteString
xs) (Chunk StrictByteString
y ByteString
ys)
    | StrictByteString -> Int
S.length StrictByteString
x Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== StrictByteString -> Int
S.length StrictByteString
y = if StrictByteString
x StrictByteString -> StrictByteString -> Bool
forall a. Eq a => a -> a -> Bool
== StrictByteString
y then ByteString -> ByteString -> Maybe ByteString
stripPrefix ByteString
xs ByteString
ys else Maybe ByteString
forall a. Maybe a
Nothing
    | StrictByteString -> Int
S.length StrictByteString
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<  StrictByteString -> Int
S.length StrictByteString
y = do StrictByteString
yt <- StrictByteString -> StrictByteString -> Maybe StrictByteString
S.stripPrefix StrictByteString
x StrictByteString
y
                                    ByteString -> ByteString -> Maybe ByteString
stripPrefix ByteString
xs (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
yt ByteString
ys)
    | Bool
otherwise                = do StrictByteString
xt <- StrictByteString -> StrictByteString -> Maybe StrictByteString
S.stripPrefix StrictByteString
y StrictByteString
x
                                    ByteString -> ByteString -> Maybe ByteString
stripPrefix (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
xt ByteString
xs) ByteString
ys

-- | /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
isSuffixOf :: ByteString -> ByteString -> Bool
isSuffixOf ByteString
x ByteString
y = ByteString -> ByteString
reverse ByteString
x ByteString -> ByteString -> Bool
`isPrefixOf` ByteString -> ByteString
reverse ByteString
y
--TODO: a better implementation

-- | /O(n)/ The 'stripSuffix' function takes two ByteStrings and returns 'Just'
-- the remainder of the second iff the first is its suffix, and otherwise
-- 'Nothing'.
stripSuffix :: ByteString -> ByteString -> Maybe ByteString
stripSuffix :: ByteString -> ByteString -> Maybe ByteString
stripSuffix ByteString
x ByteString
y = ByteString -> ByteString
reverse (ByteString -> ByteString) -> Maybe ByteString -> Maybe ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> ByteString -> Maybe ByteString
stripPrefix (ByteString -> ByteString
reverse ByteString
x) (ByteString -> ByteString
reverse ByteString
y)
--TODO: a better implementation

-- ---------------------------------------------------------------------
-- Zipping

-- | /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)]
zip :: ByteString -> ByteString -> [(Word8, Word8)]
zip = (Word8 -> Word8 -> (Word8, Word8))
-> ByteString -> ByteString -> [(Word8, Word8)]
forall a. (Word8 -> Word8 -> a) -> ByteString -> ByteString -> [a]
zipWith (,)

-- | '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]
zipWith :: forall a. (Word8 -> Word8 -> a) -> ByteString -> ByteString -> [a]
zipWith Word8 -> Word8 -> a
_ ByteString
Empty     ByteString
_  = []
zipWith Word8 -> Word8 -> a
_ ByteString
_      ByteString
Empty = []
zipWith Word8 -> Word8 -> a
f (Chunk StrictByteString
a ByteString
as) (Chunk StrictByteString
b ByteString
bs) = StrictByteString
-> ByteString -> StrictByteString -> ByteString -> [a]
go StrictByteString
a ByteString
as StrictByteString
b ByteString
bs
  where
    go :: StrictByteString
-> ByteString -> StrictByteString -> ByteString -> [a]
go StrictByteString
x ByteString
xs StrictByteString
y ByteString
ys = Word8 -> Word8 -> a
f (StrictByteString -> Word8
S.unsafeHead StrictByteString
x) (StrictByteString -> Word8
S.unsafeHead StrictByteString
y)
                 a -> [a] -> [a]
forall a. a -> [a] -> [a]
: StrictByteString
-> ByteString -> StrictByteString -> ByteString -> [a]
to (StrictByteString -> StrictByteString
S.unsafeTail StrictByteString
x) ByteString
xs (StrictByteString -> StrictByteString
S.unsafeTail StrictByteString
y) ByteString
ys

    to :: StrictByteString
-> ByteString -> StrictByteString -> ByteString -> [a]
to StrictByteString
x ByteString
Empty         StrictByteString
_ ByteString
_             | StrictByteString -> Bool
S.null StrictByteString
x       = []
    to StrictByteString
_ ByteString
_             StrictByteString
y ByteString
Empty         | StrictByteString -> Bool
S.null StrictByteString
y       = []
    to StrictByteString
x ByteString
xs            StrictByteString
y ByteString
ys            | Bool -> Bool
not (StrictByteString -> Bool
S.null StrictByteString
x)
                                      Bool -> Bool -> Bool
&& Bool -> Bool
not (StrictByteString -> Bool
S.null StrictByteString
y) = StrictByteString
-> ByteString -> StrictByteString -> ByteString -> [a]
go StrictByteString
x  ByteString
xs StrictByteString
y  ByteString
ys
    to StrictByteString
x ByteString
xs            StrictByteString
_ (Chunk StrictByteString
y' ByteString
ys) | Bool -> Bool
not (StrictByteString -> Bool
S.null StrictByteString
x) = StrictByteString
-> ByteString -> StrictByteString -> ByteString -> [a]
go StrictByteString
x  ByteString
xs StrictByteString
y' ByteString
ys
    to StrictByteString
_ (Chunk StrictByteString
x' ByteString
xs) StrictByteString
y ByteString
ys            | Bool -> Bool
not (StrictByteString -> Bool
S.null StrictByteString
y) = StrictByteString
-> ByteString -> StrictByteString -> ByteString -> [a]
go StrictByteString
x' ByteString
xs StrictByteString
y  ByteString
ys
    to StrictByteString
_ (Chunk StrictByteString
x' ByteString
xs) StrictByteString
_ (Chunk StrictByteString
y' ByteString
ys)                  = StrictByteString
-> ByteString -> StrictByteString -> ByteString -> [a]
go StrictByteString
x' ByteString
xs StrictByteString
y' ByteString
ys

-- | A specialised version of `zipWith` for the common case of a
-- simultaneous map over two ByteStrings, to build a 3rd.
--
-- @since 0.11.1.0
packZipWith :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString -> ByteString
packZipWith :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString -> ByteString
packZipWith Word8 -> Word8 -> Word8
_ ByteString
Empty ByteString
_ = ByteString
Empty
packZipWith Word8 -> Word8 -> Word8
_ ByteString
_ ByteString
Empty = ByteString
Empty
packZipWith Word8 -> Word8 -> Word8
f (Chunk a :: StrictByteString
a@(S.BS ForeignPtr Word8
_ Int
al) ByteString
as) (Chunk b :: StrictByteString
b@(S.BS ForeignPtr Word8
_ Int
bl) ByteString
bs) = StrictByteString -> ByteString -> ByteString
Chunk ((Word8 -> Word8 -> Word8)
-> StrictByteString -> StrictByteString -> StrictByteString
S.packZipWith Word8 -> Word8 -> Word8
f StrictByteString
a StrictByteString
b) (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$
    case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Int
al Int
bl of
        Ordering
LT -> (Word8 -> Word8 -> Word8) -> ByteString -> ByteString -> ByteString
packZipWith Word8 -> Word8 -> Word8
f ByteString
as (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ StrictByteString -> ByteString -> ByteString
Chunk (Int -> StrictByteString -> StrictByteString
S.drop Int
al StrictByteString
b) ByteString
bs
        Ordering
EQ -> (Word8 -> Word8 -> Word8) -> ByteString -> ByteString -> ByteString
packZipWith Word8 -> Word8 -> Word8
f ByteString
as ByteString
bs
        Ordering
GT -> (Word8 -> Word8 -> Word8) -> ByteString -> ByteString -> ByteString
packZipWith Word8 -> Word8 -> Word8
f (StrictByteString -> ByteString -> ByteString
Chunk (Int -> StrictByteString -> StrictByteString
S.drop Int
bl StrictByteString
a) ByteString
as) ByteString
bs
{-# INLINE packZipWith #-}

-- | /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)
unzip :: [(Word8, Word8)] -> (ByteString, ByteString)
unzip [(Word8, Word8)]
ls = ([Word8] -> ByteString
pack (((Word8, Word8) -> Word8) -> [(Word8, Word8)] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
List.map (Word8, Word8) -> Word8
forall a b. (a, b) -> a
fst [(Word8, Word8)]
ls), [Word8] -> ByteString
pack (((Word8, Word8) -> Word8) -> [(Word8, Word8)] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
List.map (Word8, Word8) -> Word8
forall a b. (a, b) -> b
snd [(Word8, Word8)]
ls))
{-# INLINE unzip #-}

-- ---------------------------------------------------------------------
-- Special lists

-- | Returns all initial segments of the given 'ByteString', shortest first.
inits :: ByteString -> [ByteString]
-- see Note [Avoid NonEmpty combinators] in Data.ByteString
inits :: ByteString -> [ByteString]
inits ByteString
bs = NonEmpty ByteString -> [ByteString]
forall a. NonEmpty a -> [a]
NE.toList (NonEmpty ByteString -> [ByteString])
-> NonEmpty ByteString -> [ByteString]
forall a b. (a -> b) -> a -> b
$! ByteString -> NonEmpty ByteString
initsNE ByteString
bs

-- | Returns all initial segments of the given 'ByteString', shortest first.
--
-- @since 0.11.4.0
initsNE :: ByteString -> NonEmpty ByteString
-- see Note [Avoid NonEmpty combinators] in Data.ByteString
initsNE :: ByteString -> NonEmpty ByteString
initsNE = (ByteString
Empty ByteString -> [ByteString] -> NonEmpty ByteString
forall a. a -> [a] -> NonEmpty a
:|) ([ByteString] -> NonEmpty ByteString)
-> (ByteString -> [ByteString])
-> ByteString
-> NonEmpty ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> ByteString) -> ByteString -> [ByteString]
inits' ByteString -> ByteString
forall a. a -> a
id
  where
    inits' :: (ByteString -> ByteString) -> ByteString -> [ByteString]
    -- inits' f bs === map f (tail (inits bs))
    inits' :: (ByteString -> ByteString) -> ByteString -> [ByteString]
inits' ByteString -> ByteString
_ ByteString
Empty = []
    inits' ByteString -> ByteString
f (Chunk c :: StrictByteString
c@(S.BS ForeignPtr Word8
x Int
len) ByteString
cs)
      = [ByteString -> ByteString
f (ForeignPtr Word8 -> Int -> StrictByteString
S.BS ForeignPtr Word8
x Int
n StrictByteString -> ByteString -> ByteString
`Chunk` ByteString
Empty) | Int
n <- [Int
1..Int
len]]
      [ByteString] -> [ByteString] -> [ByteString]
forall a. [a] -> [a] -> [a]
++ (ByteString -> ByteString) -> ByteString -> [ByteString]
inits' (ByteString -> ByteString
f (ByteString -> ByteString)
-> (ByteString -> ByteString) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c) ByteString
cs

-- | /O(n)/ Returns all final segments of the given 'ByteString', longest first.
tails :: ByteString -> [ByteString]
-- see Note [Avoid NonEmpty combinators] in Data.ByteString
tails :: ByteString -> [ByteString]
tails ByteString
bs = NonEmpty ByteString -> [ByteString]
forall a. NonEmpty a -> [a]
NE.toList (NonEmpty ByteString -> [ByteString])
-> NonEmpty ByteString -> [ByteString]
forall a b. (a -> b) -> a -> b
$! ByteString -> NonEmpty ByteString
tailsNE ByteString
bs

-- | /O(n)/ Returns all final segments of the given 'ByteString', longest first.
--
-- @since 0.11.4.0
tailsNE :: ByteString -> NonEmpty ByteString
-- see Note [Avoid NonEmpty combinators] in Data.ByteString
tailsNE :: ByteString -> NonEmpty ByteString
tailsNE ByteString
bs = case ByteString -> Maybe (Word8, ByteString)
uncons ByteString
bs of
  Maybe (Word8, ByteString)
Nothing -> ByteString
Empty ByteString -> [ByteString] -> NonEmpty ByteString
forall a. a -> [a] -> NonEmpty a
:| []
  Just (Word8
_, ByteString
tl) -> ByteString
bs ByteString -> [ByteString] -> NonEmpty ByteString
forall a. a -> [a] -> NonEmpty a
:| ByteString -> [ByteString]
tails ByteString
tl


-- ---------------------------------------------------------------------
-- Low level constructors

-- | /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
copy :: ByteString -> ByteString
copy = (StrictByteString -> ByteString -> ByteString)
-> ByteString -> ByteString -> ByteString
forall a. (StrictByteString -> a -> a) -> a -> ByteString -> a
foldrChunks (StrictByteString -> ByteString -> ByteString
Chunk (StrictByteString -> ByteString -> ByteString)
-> (StrictByteString -> StrictByteString)
-> StrictByteString
-> ByteString
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StrictByteString -> StrictByteString
S.copy) ByteString
Empty
--TODO, we could coalese small blocks here
--FIXME: probably not strict enough, if we're doing this to avoid retaining
-- the parent blocks then we'd better copy strictly.

-- ---------------------------------------------------------------------

-- TODO defrag func that concatenates block together that are below a threshold
-- defrag :: ByteString -> ByteString

-- ---------------------------------------------------------------------
-- Lazy ByteString IO
--
-- Rule for when to close: is it expected to read the whole file?
-- If so, close when done.
--

-- | Read entire handle contents /lazily/ into a 'ByteString'. Chunks
-- are read on demand, in at most @k@-sized chunks. It does not block
-- waiting for a whole @k@-sized chunk, so if less than @k@ bytes are
-- available then they will be returned immediately as a smaller chunk.
--
-- The handle is closed on EOF.
--
hGetContentsN :: Int -> Handle -> IO ByteString
hGetContentsN :: Int -> Handle -> IO ByteString
hGetContentsN Int
k Handle
h = IO ByteString
lazyRead -- TODO close on exceptions
  where
    lazyRead :: IO ByteString
lazyRead = IO ByteString -> IO ByteString
forall a. IO a -> IO a
unsafeInterleaveIO IO ByteString
loop

    loop :: IO ByteString
loop = do
        StrictByteString
c <- Handle -> Int -> IO StrictByteString
S.hGetSome Handle
h Int
k -- only blocks if there is no data available
        if StrictByteString -> Bool
S.null StrictByteString
c
          then Handle -> IO ()
hClose Handle
h IO () -> IO ByteString -> IO ByteString
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
Empty
          else StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c (ByteString -> ByteString) -> IO ByteString -> IO ByteString
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO ByteString
lazyRead

-- | Read @n@ bytes into a 'ByteString', directly from the
-- specified 'Handle', in chunks of size @k@.
--
hGetN :: Int -> Handle -> Int -> IO ByteString
hGetN :: Int -> Handle -> Int -> IO ByteString
hGetN Int
k Handle
h Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 = Int -> IO ByteString
readChunks Int
n
  where
    readChunks :: Int -> IO ByteString
readChunks !Int
i = do
        StrictByteString
c <- Handle -> Int -> IO StrictByteString
S.hGet Handle
h (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
k Int
i)
        case StrictByteString -> Int
S.length StrictByteString
c of
            Int
0 -> ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
Empty
            Int
m -> do ByteString
cs <- Int -> IO ByteString
readChunks (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
m)
                    ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c ByteString
cs)

hGetN Int
_ Handle
_ Int
0 = ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
Empty
hGetN Int
_ Handle
h Int
n = Handle -> String -> Int -> IO ByteString
forall a. Handle -> String -> Int -> IO a
illegalBufferSize Handle
h String
"hGet" Int
n

-- | hGetNonBlockingN is similar to 'hGetContentsN', except that it will never block
-- waiting for data to become available, instead it returns only whatever data
-- is available. Chunks are read on demand, in @k@-sized chunks.
--
hGetNonBlockingN :: Int -> Handle -> Int -> IO ByteString
hGetNonBlockingN :: Int -> Handle -> Int -> IO ByteString
hGetNonBlockingN Int
k Handle
h Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0= Int -> IO ByteString
readChunks Int
n
  where
    readChunks :: Int -> IO ByteString
readChunks !Int
i = do
        StrictByteString
c <- Handle -> Int -> IO StrictByteString
S.hGetNonBlocking Handle
h (Int -> Int -> Int
forall a. Ord a => a -> a -> a
min Int
k Int
i)
        case StrictByteString -> Int
S.length StrictByteString
c of
            Int
0 -> ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
Empty
            Int
m -> do ByteString
cs <- Int -> IO ByteString
readChunks (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
m)
                    ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c ByteString
cs)

hGetNonBlockingN Int
_ Handle
_ Int
0 = ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
Empty
hGetNonBlockingN Int
_ Handle
h Int
n = Handle -> String -> Int -> IO ByteString
forall a. Handle -> String -> Int -> IO a
illegalBufferSize Handle
h String
"hGetNonBlocking" Int
n

illegalBufferSize :: Handle -> String -> Int -> IO a
illegalBufferSize :: forall a. Handle -> String -> Int -> IO a
illegalBufferSize Handle
handle String
fn Int
sz =
    IOError -> IO a
forall a. IOError -> IO a
ioError (IOErrorType -> String -> Maybe Handle -> Maybe String -> IOError
mkIOError IOErrorType
illegalOperationErrorType String
msg (Handle -> Maybe Handle
forall a. a -> Maybe a
Just Handle
handle) Maybe String
forall a. Maybe a
Nothing)
    --TODO: System.IO uses InvalidArgument here, but it's not exported :-(
    where
      msg :: String
msg = String
fn String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
": illegal ByteString size " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> Int -> String -> String
forall a. Show a => Int -> a -> String -> String
showsPrec Int
9 Int
sz []

-- | Read entire handle contents /lazily/ into a 'ByteString'. Chunks
-- are read on demand, using the default chunk size.
--
-- File handles are closed on EOF if all the file is read, or through
-- garbage collection otherwise.
--
hGetContents :: Handle -> IO ByteString
hGetContents :: Handle -> IO ByteString
hGetContents = Int -> Handle -> IO ByteString
hGetContentsN Int
defaultChunkSize

-- | Read @n@ bytes into a 'ByteString', directly from the specified 'Handle'.
--
hGet :: Handle -> Int -> IO ByteString
hGet :: Handle -> Int -> IO ByteString
hGet = Int -> Handle -> Int -> IO ByteString
hGetN Int
defaultChunkSize

-- | 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
hGetNonBlocking :: Handle -> Int -> IO ByteString
hGetNonBlocking = Int -> Handle -> Int -> IO ByteString
hGetNonBlockingN Int
defaultChunkSize

-- | Read an entire file /lazily/ into a 'ByteString'.
--
-- The 'Handle' will be held open until EOF is encountered.
--
-- Note that this function's implementation relies on 'hGetContents'.
-- The reader is advised to read its documentation.
--
readFile :: FilePath -> IO ByteString
readFile :: String -> IO ByteString
readFile String
f = String -> IOMode -> IO Handle
openBinaryFile String
f IOMode
ReadMode IO Handle -> (Handle -> IO ByteString) -> IO ByteString
forall a b. IO a -> (a -> IO b) -> IO b
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Handle -> IO ByteString
hGetContents

modifyFile :: IOMode -> FilePath -> ByteString -> IO ()
modifyFile :: IOMode -> String -> ByteString -> IO ()
modifyFile IOMode
mode String
f ByteString
txt = String -> IOMode -> (Handle -> IO ()) -> IO ()
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile String
f IOMode
mode (Handle -> ByteString -> IO ()
`hPut` ByteString
txt)

-- | Write a 'ByteString' to a file.
--
writeFile :: FilePath -> ByteString -> IO ()
writeFile :: String -> ByteString -> IO ()
writeFile = IOMode -> String -> ByteString -> IO ()
modifyFile IOMode
WriteMode

-- | Append a 'ByteString' to a file.
--
appendFile :: FilePath -> ByteString -> IO ()
appendFile :: String -> ByteString -> IO ()
appendFile = IOMode -> String -> ByteString -> IO ()
modifyFile IOMode
AppendMode

-- | getContents. Equivalent to hGetContents stdin. Will read /lazily/
--
getContents :: IO ByteString
getContents :: IO ByteString
getContents = Handle -> IO ByteString
hGetContents Handle
stdin

-- | Outputs a 'ByteString' to the specified 'Handle'.
--
-- The chunks will be
-- written one at a time. Other threads might write to the 'Handle' in between,
-- and hence 'hPut' alone is not suitable for concurrent writes.
--
hPut :: Handle -> ByteString -> IO ()
hPut :: Handle -> ByteString -> IO ()
hPut Handle
h = (StrictByteString -> IO () -> IO ())
-> IO () -> ByteString -> IO ()
forall a. (StrictByteString -> a -> a) -> a -> ByteString -> a
foldrChunks (\StrictByteString
c IO ()
rest -> Handle -> StrictByteString -> IO ()
S.hPut Handle
h StrictByteString
c IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> IO ()
rest) (() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ())

-- | 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
hPutNonBlocking :: Handle -> ByteString -> IO ByteString
hPutNonBlocking Handle
_ ByteString
Empty           = ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
Empty
hPutNonBlocking Handle
h bs :: ByteString
bs@(Chunk StrictByteString
c ByteString
cs) = do
  StrictByteString
c' <- Handle -> StrictByteString -> IO StrictByteString
S.hPutNonBlocking Handle
h StrictByteString
c
  case StrictByteString -> Int
S.length StrictByteString
c' of
    Int
l' | Int
l' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== StrictByteString -> Int
S.length StrictByteString
c -> Handle -> ByteString -> IO ByteString
hPutNonBlocking Handle
h ByteString
cs
    Int
0                     -> ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
bs
    Int
_                     -> ByteString -> IO ByteString
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (StrictByteString -> ByteString -> ByteString
Chunk StrictByteString
c' ByteString
cs)

-- | A synonym for 'hPut', for compatibility
--
hPutStr :: Handle -> ByteString -> IO ()
hPutStr :: Handle -> ByteString -> IO ()
hPutStr = Handle -> ByteString -> IO ()
hPut

-- | Write a ByteString to 'stdout'.
--
-- The chunks will be
-- written one at a time. Other threads might write to the 'stdout' in between,
-- and hence 'putStr' alone is not suitable for concurrent writes.
--
putStr :: ByteString -> IO ()
putStr :: ByteString -> IO ()
putStr = Handle -> ByteString -> IO ()
hPut Handle
stdout

-- | 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 ()
interact :: (ByteString -> ByteString) -> IO ()
interact ByteString -> ByteString
transformer = ByteString -> IO ()
putStr (ByteString -> IO ())
-> (ByteString -> ByteString) -> ByteString -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
transformer (ByteString -> IO ()) -> IO ByteString -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO ByteString
getContents

-- ---------------------------------------------------------------------
-- Internal utilities

-- Common up near identical calls to `error' to reduce the number
-- constant strings created when compiled:
errorEmptyList :: HasCallStack => String -> a
errorEmptyList :: forall a. HasCallStack => String -> a
errorEmptyList String
fun = String -> String -> a
forall a. HasCallStack => String -> String -> a
moduleError String
fun String
"empty ByteString"
{-# NOINLINE errorEmptyList #-}

moduleError :: HasCallStack => String -> String -> a
moduleError :: forall a. HasCallStack => String -> String -> a
moduleError String
fun String
msg = String -> a
forall a. HasCallStack => String -> a
error (String
"Data.ByteString.Lazy." String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
fun String -> String -> String
forall a. [a] -> [a] -> [a]
++ Char
':'Char -> String -> String
forall a. a -> [a] -> [a]
:Char
' 'Char -> String -> String
forall a. a -> [a] -> [a]
:String
msg)
{-# NOINLINE moduleError #-}


-- reverse a list of non-empty chunks into a lazy ByteString
revNonEmptyChunks :: [P.ByteString] -> ByteString
revNonEmptyChunks :: [StrictByteString] -> ByteString
revNonEmptyChunks = (ByteString -> StrictByteString -> ByteString)
-> ByteString -> [StrictByteString] -> ByteString
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' ((StrictByteString -> ByteString -> ByteString)
-> ByteString -> StrictByteString -> ByteString
forall a b c. (a -> b -> c) -> b -> a -> c
flip StrictByteString -> ByteString -> ByteString
Chunk) ByteString
Empty

-- reverse a list of possibly-empty chunks into a lazy ByteString
revChunks :: [P.ByteString] -> ByteString
revChunks :: [StrictByteString] -> ByteString
revChunks = (ByteString -> StrictByteString -> ByteString)
-> ByteString -> [StrictByteString] -> ByteString
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' ((StrictByteString -> ByteString -> ByteString)
-> ByteString -> StrictByteString -> ByteString
forall a b c. (a -> b -> c) -> b -> a -> c
flip StrictByteString -> ByteString -> ByteString
chunk) ByteString
Empty

intToInt64 :: Int -> Int64
intToInt64 :: Int -> Int64
intToInt64 = forall a b. (Integral a, Num b) => a -> b
fromIntegral @Int @Int64

-- $IOChunk
--
-- ⚠ Using lazy I\/O functions like 'readFile' or 'hGetContents'
-- means that the order of operations such as closing the file handle
-- is left at the discretion of the RTS.
-- Hence, the developer can face some issues when:
--
-- * The program reads a file and writes the same file. This means that the file
--   may be locked because the handler has not been released when 'writeFile' is executed.
-- * The program reads thousands of files, but due to lazy evaluation, the OS's file descriptor
--   limit is reached before the handlers can be released.
--
-- === Why?
--
-- Consider the following program:
--
-- > import qualified Data.ByteString.Lazy as BL
-- > main = do
-- >   _ <- BL.readFile "foo.txt"
-- >   BL.writeFile "foo.txt" mempty
--
-- Generally, in the 'IO' monad side effects happen
-- sequentially and in full. Therefore, one might reasonably expect that
-- reading the whole file via 'readFile' executes all three actions
-- (open the file handle, read its content, close the file handle) before
-- control moves to the following 'writeFile' action. This expectation holds
-- for the strict "Data.ByteString" API. However, the above 'LazyByteString' variant
-- of the program fails with @openBinaryFile: resource busy (file is locked)@.
--
-- The reason for this is that "Data.ByteString.Lazy" is specifically designed
-- to handle large or unbounded streams of data incrementally, without requiring all the data
-- to be resident in memory at the same time. Incremental processing would not be possible
-- if 'readFile' were to follow the usual rules of 'IO': evaluating all side effects
-- would require reading the file in full and closing its handle before returning from 'readFile'. This is why
-- 'readFile' (and 'hGetContents' in general) is implemented
-- via 'unsafeInterleaveIO', which allows 'IO' side effects to be delayed and
-- interleaved with subsequent processing of the return value.
-- That's exactly what happens
-- in the example above: 'readFile' opens a file handle, but since the content
-- is not fully consumed, the file handle remains open, allowing the content to
-- read __on demand__ (never in this case, since the return value is ignored).
-- So when 'writeFile' is executed next, @foo.txt@ is still open for reading and
-- the RTS takes care to avoid simultaneously opening it for writing, instead
-- returning the error shown above.
--
-- === How to enforce the order of effects?
--
-- If the content is small enough to fit in memory,
-- consider using strict 'Data.ByteString.readFile',
-- potentially applying 'fromStrict' afterwards. E. g.,
--
-- > import qualified Data.ByteString as BS
-- > import qualified Data.ByteString.Lazy as BL
-- > main = do
-- >   _ <- BS.readFile "foo.txt"
-- >   BL.writeFile "foo.txt" mempty
--
-- If you are dealing with large or unbounded data streams,
-- consider reaching out for a specialised package, such as
-- <http://hackage.haskell.org/package/conduit conduit>,
-- <http://hackage.haskell.org/package/machines-bytestring machines-bytestring>,
-- <http://hackage.haskell.org/package/pipes-bytestring pipes-bytestring>,
-- <http://hackage.haskell.org/package/streaming-bytestring streaming-bytestring>,
-- <http://hackage.haskell.org/package/streamly-bytestring streamly-bytestring>,
-- etc.