{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE TupleSections #-}
{-# OPTIONS_HADDOCK prune #-}
{-# LANGUAGE Trustworthy #-}

-- |
-- Module      : Data.ByteString
-- Copyright   : (c) The University of Glasgow 2001,
--               (c) David Roundy 2003-2005,
--               (c) Simon Marlow 2005,
--               (c) Bjorn Bringert 2006,
--               (c) Don Stewart 2005-2008,
--               (c) Duncan Coutts 2006-2013
-- License     : BSD-style
--
-- Maintainer  : dons00@gmail.com, duncan@community.haskell.org
-- Stability   : stable
-- Portability : portable
--
-- A time- and space-efficient implementation of byte vectors using
-- packed Word8 arrays, suitable for high performance use, both in terms
-- of large data quantities and high speed requirements. Byte vectors
-- are encoded as strict 'Word8' arrays of bytes, held in a 'ForeignPtr',
-- and can be passed between C and Haskell with little effort.
--
-- The recomended way to assemble ByteStrings from smaller parts
-- is to use the builder monoid from "Data.ByteString.Builder".
--
-- This module is intended to be imported @qualified@, to avoid name
-- clashes with "Prelude" functions.  eg.
--
-- > import qualified Data.ByteString as B
--
-- Original GHC implementation by Bryan O\'Sullivan.
-- Rewritten to use 'Data.Array.Unboxed.UArray' by Simon Marlow.
-- Rewritten to support slices and use 'ForeignPtr' by David Roundy.
-- Rewritten again and extended by Don Stewart and Duncan Coutts.
--

module Data.ByteString (

        -- * Strict @ByteString@
        ByteString,
        StrictByteString,

        -- * Introducing and eliminating 'ByteString's
        empty,
        singleton,
        pack,
        unpack,
        fromStrict,
        toStrict,
        fromFilePath,
        toFilePath,

        -- * Basic interface
        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,

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

        -- ** Accumulating maps
        mapAccumL,
        mapAccumR,

        -- ** Generating and unfolding ByteStrings
        replicate,
        unfoldr,
        unfoldrN,

        -- * 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,

        -- ** Encoding validation
        isValidUtf8,

        -- ** Search for arbitrary substrings
        breakSubstring,

        -- * Searching ByteStrings

        -- ** Searching by equality
        elem,
        notElem,

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

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

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

        -- * Ordered ByteStrings
        sort,

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

        -- ** Packing 'CString's and pointers
        packCString,
        packCStringLen,

        -- ** Using ByteStrings as 'CString's
        useAsCString,
        useAsCStringLen,

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

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

        -- ** Files
        readFile,
        writeFile,
        appendFile,

        -- ** I\/O with Handles
        hGetLine,
        hGetContents,
        hGet,
        hGetSome,
        hGetNonBlocking,
        hPut,
        hPutNonBlocking,
        hPutStr,
  ) where

import qualified Prelude as P
import Prelude hiding           (reverse,head,tail,last,init,null
                                ,length,map,lines,foldl,foldr,unlines
                                ,concat,any,take,drop,splitAt,takeWhile
                                ,dropWhile,span,break,elem,filter,maximum
                                ,minimum,all,concatMap,foldl1,foldr1
                                ,scanl,scanl1,scanr,scanr1
                                ,readFile,writeFile,appendFile,replicate
                                ,getContents,getLine,putStr,putStrLn,interact
                                ,zip,zipWith,unzip,notElem
                                )

import Data.Bits                (finiteBitSize, shiftL, (.|.), (.&.))

import Data.ByteString.Internal.Type
import Data.ByteString.Lazy.Internal (fromStrict, toStrict)
import Data.ByteString.Unsafe

import qualified Data.List as List
import qualified Data.List.NonEmpty as NE
import Data.List.NonEmpty (NonEmpty(..))

import Data.Word                (Word8)

import Control.Exception        (IOException, catch, finally, assert, throwIO)
import Control.Monad            (when, void)

import Foreign.C.String         (CString, CStringLen)
import Foreign.C.Types          (CSize (CSize), CInt (CInt))
import Foreign.ForeignPtr       (ForeignPtr, touchForeignPtr)
import Foreign.ForeignPtr.Unsafe(unsafeForeignPtrToPtr)
import Foreign.Marshal.Alloc    (allocaBytes)
import Foreign.Marshal.Array    (allocaArray)
import Foreign.Ptr
import Foreign.Storable         (Storable(..))

-- hGetBuf and hPutBuf not available in yhc or nhc
import System.IO                (stdin,stdout,hClose,hFileSize
                                ,hGetBuf,hPutBuf,hGetBufNonBlocking
                                ,hPutBufNonBlocking,withBinaryFile
                                ,IOMode(..),hGetBufSome)
import System.IO.Error          (mkIOError, illegalOperationErrorType)

import Data.IORef
import GHC.IO.Handle.Internals
import GHC.IO.Handle.Types
import GHC.IO.Buffer
import GHC.IO.BufferedIO as Buffered
import GHC.IO.Encoding          (getFileSystemEncoding)
import GHC.IO                   (unsafePerformIO, unsafeDupablePerformIO)
import GHC.Foreign              (newCStringLen, peekCStringLen)
import GHC.Stack.Types          (HasCallStack)
import Data.Char                (ord)

import GHC.Base                 (build)
import GHC.Word hiding (Word8)

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

-- | /O(1)/ Convert a 'Word8' into a 'ByteString'
singleton :: Word8 -> ByteString
-- Taking a slice of some static data rather than allocating a new
-- buffer for each call is nice for several reasons. Since it doesn't
-- involve any side effects hidden in a 'GHC.Magic.runRW#' call, it
-- can be simplified to a constructor application. This may enable GHC
-- to perform further optimizations after inlining, and also causes a
-- fresh singleton to take only 4 words of heap space instead of 9.
-- (The buffer object itself would take up 3 words: header, size, and
-- 1 word of content. The ForeignPtrContents object used to keep the
-- buffer alive would need two more.)
singleton :: Word8 -> ByteString
singleton Word8
c = Int -> ByteString -> ByteString
unsafeTake Int
1 forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString
unsafeDrop (forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
c) ByteString
allBytes
{-# INLINE singleton #-}

-- | A static blob of all possible bytes (0x00 to 0xff) in order
allBytes :: ByteString
allBytes :: ByteString
allBytes = Int -> Addr# -> ByteString
unsafePackLenLiteral Int
0x100
  Addr#
"\x00\x01\x02\x03\x04\x05\x06\x07\x08\x09\x0a\x0b\x0c\x0d\x0e\x0f\x10\x11\x12\x13\x14\x15\x16\x17\x18\x19\x1a\x1b\x1c\x1d\x1e\x1f\x20\x21\x22\x23\x24\x25\x26\x27\x28\x29\x2a\x2b\x2c\x2d\x2e\x2f\x30\x31\x32\x33\x34\x35\x36\x37\x38\x39\x3a\x3b\x3c\x3d\x3e\x3f\x40\x41\x42\x43\x44\x45\x46\x47\x48\x49\x4a\x4b\x4c\x4d\x4e\x4f\x50\x51\x52\x53\x54\x55\x56\x57\x58\x59\x5a\x5b\x5c\x5d\x5e\x5f\x60\x61\x62\x63\x64\x65\x66\x67\x68\x69\x6a\x6b\x6c\x6d\x6e\x6f\x70\x71\x72\x73\x74\x75\x76\x77\x78\x79\x7a\x7b\x7c\x7d\x7e\x7f\x80\x81\x82\x83\x84\x85\x86\x87\x88\x89\x8a\x8b\x8c\x8d\x8e\x8f\x90\x91\x92\x93\x94\x95\x96\x97\x98\x99\x9a\x9b\x9c\x9d\x9e\x9f\xa0\xa1\xa2\xa3\xa4\xa5\xa6\xa7\xa8\xa9\xaa\xab\xac\xad\xae\xaf\xb0\xb1\xb2\xb3\xb4\xb5\xb6\xb7\xb8\xb9\xba\xbb\xbc\xbd\xbe\xbf\xc0\xc1\xc2\xc3\xc4\xc5\xc6\xc7\xc8\xc9\xca\xcb\xcc\xcd\xce\xcf\xd0\xd1\xd2\xd3\xd4\xd5\xd6\xd7\xd8\xd9\xda\xdb\xdc\xdd\xde\xdf\xe0\xe1\xe2\xe3\xe4\xe5\xe6\xe7\xe8\xe9\xea\xeb\xec\xed\xee\xef\xf0\xf1\xf2\xf3\xf4\xf5\xf6\xf7\xf8\xf9\xfa\xfb\xfc\xfd\xfe\xff"#

-- | /O(n)/ Convert a @['Word8']@ into a 'ByteString'.
--
-- For applications with large numbers of string literals, 'pack' can be a
-- bottleneck. In such cases, consider using 'unsafePackAddress' (GHC only).
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
bs = forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
build (forall a. ByteString -> (Word8 -> a -> a) -> a -> a
unpackFoldr ByteString
bs)
{-# INLINE unpack #-}

--
-- Have unpack fuse with good list consumers
--
unpackFoldr :: ByteString -> (Word8 -> a -> a) -> a -> a
unpackFoldr :: forall a. ByteString -> (Word8 -> a -> a) -> a -> a
unpackFoldr ByteString
bs Word8 -> a -> a
k a
z = forall a. (Word8 -> a -> a) -> a -> ByteString -> a
foldr Word8 -> a -> a
k a
z ByteString
bs
{-# INLINE [0] unpackFoldr #-}

{-# RULES
"ByteString unpack-list" [1]  forall bs .
    unpackFoldr bs (:) [] = unpackBytes bs
 #-}

-- | Convert a 'FilePath' to a 'ByteString'.
--
-- The 'FilePath' type is expected to use the file system encoding
-- as reported by 'GHC.IO.Encoding.getFileSystemEncoding'. This
-- encoding allows for round-tripping of arbitrary data on platforms
-- that allow arbitrary bytes in their paths. This conversion
-- function does the same thing that `System.IO.openFile` would
-- do when decoding the 'FilePath'.
--
-- This function is in 'IO' because the file system encoding can be
-- changed. If the encoding can be assumed to be constant in your
-- use case, you may invoke this function via 'unsafePerformIO'.
--
-- @since 0.11.2.0
fromFilePath :: FilePath -> IO ByteString
fromFilePath :: FilePath -> IO ByteString
fromFilePath FilePath
path = do
    TextEncoding
enc <- IO TextEncoding
getFileSystemEncoding
    TextEncoding -> FilePath -> IO CStringLen
newCStringLen TextEncoding
enc FilePath
path forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= CStringLen -> IO ByteString
unsafePackMallocCStringLen

-- | Convert a 'ByteString' to a 'FilePath'.
--
-- This function uses the file system encoding, and resulting 'FilePath's
-- can be safely used with standard IO functions and will reference the
-- correct path in the presence of arbitrary non-UTF-8 encoded paths.
--
-- This function is in 'IO' because the file system encoding can be
-- changed. If the encoding can be assumed to be constant in your
-- use case, you may invoke this function via 'unsafePerformIO'.
--
-- @since 0.11.2.0
toFilePath :: ByteString -> IO FilePath
toFilePath :: ByteString -> IO FilePath
toFilePath ByteString
path = do
    TextEncoding
enc <- IO TextEncoding
getFileSystemEncoding
    forall a. ByteString -> (CStringLen -> IO a) -> IO a
useAsCStringLen ByteString
path (TextEncoding -> CStringLen -> IO FilePath
peekCStringLen TextEncoding
enc)

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

-- | /O(1)/ Test whether a ByteString is empty.
null :: ByteString -> Bool
null :: ByteString -> Bool
null (BS ForeignPtr Word8
_ Int
l) = forall a. HasCallStack => Bool -> a -> a
assert (Int
l forall a. Ord a => a -> a -> Bool
>= Int
0) forall a b. (a -> b) -> a -> b
$ Int
l forall a. Ord a => a -> a -> Bool
<= Int
0
{-# INLINE null #-}

-- ---------------------------------------------------------------------
-- | /O(1)/ 'length' returns the length of a ByteString as an 'Int'.
length :: ByteString -> Int
length :: ByteString -> Int
length (BS ForeignPtr Word8
_ Int
l) = forall a. HasCallStack => Bool -> a -> a
assert (Int
l forall a. Ord a => a -> a -> Bool
>= Int
0) Int
l
{-# INLINE length #-}

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

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

-- | /O(n)/ 'cons' is analogous to (:) for lists, but of different
-- complexity, as it requires making a copy.
cons :: Word8 -> ByteString -> ByteString
cons :: Word8 -> ByteString -> ByteString
cons Word8
c (BS ForeignPtr Word8
x Int
l) = Int -> (ForeignPtr Word8 -> IO ()) -> ByteString
unsafeCreateFp (Int
lforall a. Num a => a -> a -> a
+Int
1) forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
p -> do
        forall a. Storable a => ForeignPtr a -> a -> IO ()
pokeFp ForeignPtr Word8
p Word8
c
        ForeignPtr Word8 -> ForeignPtr Word8 -> Int -> IO ()
memcpyFp (ForeignPtr Word8
p forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
1) ForeignPtr Word8
x Int
l
{-# INLINE cons #-}

-- | /O(n)/ Append a byte to the end of a 'ByteString'
snoc :: ByteString -> Word8 -> ByteString
snoc :: ByteString -> Word8 -> ByteString
snoc (BS ForeignPtr Word8
x Int
l) Word8
c = Int -> (ForeignPtr Word8 -> IO ()) -> ByteString
unsafeCreateFp (Int
lforall a. Num a => a -> a -> a
+Int
1) forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
p -> do
        ForeignPtr Word8 -> ForeignPtr Word8 -> Int -> IO ()
memcpyFp ForeignPtr Word8
p ForeignPtr Word8
x Int
l
        forall a. Storable a => ForeignPtr a -> a -> IO ()
pokeFp (ForeignPtr Word8
p forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
l) Word8
c
{-# INLINE snoc #-}

-- | /O(1)/ Extract the first element of a ByteString, which must be non-empty.
-- An exception will be thrown in the case of an empty ByteString.
--
-- This is a partial function, consider using 'uncons' instead.
head :: HasCallStack => ByteString -> Word8
head :: HasCallStack => ByteString -> Word8
head (BS ForeignPtr Word8
x Int
l)
    | Int
l forall a. Ord a => a -> a -> Bool
<= Int
0    = forall a. HasCallStack => FilePath -> a
errorEmptyList FilePath
"head"
    | Bool
otherwise = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
p
{-# INLINE head #-}

-- | /O(1)/ Extract the elements after the head of a ByteString, which must be non-empty.
-- An exception will be thrown in the case of an empty ByteString.
--
-- This is a partial function, consider using 'uncons' instead.
tail :: HasCallStack => ByteString -> ByteString
tail :: HasCallStack => ByteString -> ByteString
tail (BS ForeignPtr Word8
p Int
l)
    | Int
l forall a. Ord a => a -> a -> Bool
<= Int
0    = forall a. HasCallStack => FilePath -> a
errorEmptyList FilePath
"tail"
    | Bool
otherwise = ForeignPtr Word8 -> Int -> ByteString
BS (forall a b. ForeignPtr a -> Int -> ForeignPtr b
plusForeignPtr ForeignPtr Word8
p Int
1) (Int
lforall a. Num a => a -> a -> a
-Int
1)
{-# INLINE tail #-}

-- | /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 (BS ForeignPtr Word8
x Int
l)
    | Int
l forall a. Ord a => a -> a -> Bool
<= Int
0    = forall a. Maybe a
Nothing
    | Bool
otherwise = forall a. a -> Maybe a
Just (forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x
                                                     forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
p,
                        ForeignPtr Word8 -> Int -> ByteString
BS (forall a b. ForeignPtr a -> Int -> ForeignPtr b
plusForeignPtr ForeignPtr Word8
x Int
1) (Int
lforall a. Num a => a -> a -> a
-Int
1))
{-# INLINE uncons #-}

-- | /O(1)/ Extract the last element of a ByteString, which must be finite and non-empty.
-- An exception will be thrown in the case of an empty ByteString.
--
-- This is a partial function, consider using 'unsnoc' instead.
last :: HasCallStack => ByteString -> Word8
last :: HasCallStack => ByteString -> Word8
last ps :: ByteString
ps@(BS ForeignPtr Word8
x Int
l)
    | ByteString -> Bool
null ByteString
ps   = forall a. HasCallStack => FilePath -> a
errorEmptyList FilePath
"last"
    | Bool
otherwise = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$
                    forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
p (Int
lforall a. Num a => a -> a -> a
-Int
1)
{-# INLINE last #-}

-- | /O(1)/ Returns all the elements of a 'ByteString' except the last one.
-- An exception will be thrown in the case of an empty ByteString.
--
-- This is a partial function, consider using 'unsnoc' instead.
init :: HasCallStack => ByteString -> ByteString
init :: HasCallStack => ByteString -> ByteString
init ps :: ByteString
ps@(BS ForeignPtr Word8
p Int
l)
    | ByteString -> Bool
null ByteString
ps   = forall a. HasCallStack => FilePath -> a
errorEmptyList FilePath
"init"
    | Bool
otherwise = ForeignPtr Word8 -> Int -> ByteString
BS ForeignPtr Word8
p (Int
lforall a. Num a => a -> a -> a
-Int
1)
{-# INLINE init #-}

-- | /O(1)/ Extract the 'init' and 'last' of a ByteString, returning 'Nothing'
-- if it is empty.
unsnoc :: ByteString -> Maybe (ByteString, Word8)
unsnoc :: ByteString -> Maybe (ByteString, Word8)
unsnoc (BS ForeignPtr Word8
x Int
l)
    | Int
l forall a. Ord a => a -> a -> Bool
<= Int
0    = forall a. Maybe a
Nothing
    | Bool
otherwise = forall a. a -> Maybe a
Just (ForeignPtr Word8 -> Int -> ByteString
BS ForeignPtr Word8
x (Int
lforall a. Num a => a -> a -> a
-Int
1),
                        forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$
                          forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
p (Int
lforall a. Num a => a -> a -> a
-Int
1))
{-# INLINE unsnoc #-}

-- | /O(n)/ Append two ByteStrings
append :: ByteString -> ByteString -> ByteString
append :: ByteString -> ByteString -> ByteString
append = 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 (BS ForeignPtr Word8
srcPtr Int
len) = Int -> (ForeignPtr Word8 -> IO ()) -> ByteString
unsafeCreateFp Int
len forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
dstPtr -> forall {b}. ForeignPtr Word8 -> ForeignPtr b -> IO ()
m ForeignPtr Word8
srcPtr ForeignPtr Word8
dstPtr
  where
    m :: ForeignPtr Word8 -> ForeignPtr b -> IO ()
m !ForeignPtr Word8
p1 !ForeignPtr b
p2 = Int -> IO ()
map_ Int
0
      where
      map_ :: Int -> IO ()
      map_ :: Int -> IO ()
map_ !Int
n
         | Int
n forall a. Ord a => a -> a -> Bool
>= Int
len = forall (m :: * -> *) a. Monad m => a -> m a
return ()
         | Bool
otherwise = do
              Word8
x <- forall a. Storable a => ForeignPtr a -> Int -> IO a
peekFpByteOff ForeignPtr Word8
p1 Int
n
              forall a b. Storable a => ForeignPtr b -> Int -> a -> IO ()
pokeFpByteOff ForeignPtr b
p2 Int
n (Word8 -> Word8
f Word8
x)
              Int -> IO ()
map_ (Int
nforall a. Num a => a -> a -> a
+Int
1)
{-# INLINE map #-}

-- | /O(n)/ 'reverse' @xs@ efficiently returns the elements of @xs@ in reverse order.
reverse :: ByteString -> ByteString
reverse :: ByteString -> ByteString
reverse (BS ForeignPtr Word8
x Int
l) = Int -> (ForeignPtr Word8 -> IO ()) -> ByteString
unsafeCreateFp Int
l forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
fp ->
  forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
    forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x  forall a b. (a -> b) -> a -> b
$ \Ptr Word8
f ->
      Ptr Word8 -> Ptr Word8 -> CSize -> IO ()
c_reverse Ptr Word8
p Ptr Word8
f (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l)

-- | /O(n)/ The 'intersperse' function takes a 'Word8' and a
-- 'ByteString' and \`intersperses\' that byte between the elements of
-- the 'ByteString'.  It is analogous to the intersperse function on
-- Lists.
intersperse :: Word8 -> ByteString -> ByteString
intersperse :: Word8 -> ByteString -> ByteString
intersperse Word8
c ps :: ByteString
ps@(BS ForeignPtr Word8
x Int
l)
    | ByteString -> Int
length ByteString
ps forall a. Ord a => a -> a -> Bool
< Int
2  = ByteString
ps
    | Bool
otherwise      = Int -> (ForeignPtr Word8 -> IO ()) -> ByteString
unsafeCreateFp (Int
2forall a. Num a => a -> a -> a
*Int
lforall a. Num a => a -> a -> a
-Int
1) forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
fp ->
      forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
        forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x forall a b. (a -> b) -> a -> b
$ \Ptr Word8
f ->
          Ptr Word8 -> Ptr Word8 -> CSize -> Word8 -> IO ()
c_intersperse Ptr Word8
p Ptr Word8
f (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l) Word8
c

-- | The 'transpose' function transposes the rows and columns of its
-- 'ByteString' argument.
transpose :: [ByteString] -> [ByteString]
transpose :: [ByteString] -> [ByteString]
transpose = forall a b. (a -> b) -> [a] -> [b]
P.map [Word8] -> ByteString
pack forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. [[a]] -> [[a]]
List.transpose forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
P.map ByteString -> [Word8]
unpack

-- ---------------------------------------------------------------------
-- 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
z = \(BS ForeignPtr Word8
fp Int
len) ->
  let
    end :: Ptr b
end = forall a. ForeignPtr a -> Ptr a
unsafeForeignPtrToPtr ForeignPtr Word8
fp forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (-Int
1)
    -- not tail recursive; traverses array right to left
    go :: Ptr Word8 -> a
go !Ptr Word8
p | Ptr Word8
p forall a. Eq a => a -> a -> Bool
== forall {b}. Ptr b
end  = a
z
          | Bool
otherwise = let !x :: Word8
x = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ do
                                   Word8
x' <- forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
p
                                   forall a. ForeignPtr a -> IO ()
touchForeignPtr ForeignPtr Word8
fp
                                   forall (m :: * -> *) a. Monad m => a -> m a
return Word8
x'
                        in a -> Word8 -> a
f (Ptr Word8 -> a
go (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (-Int
1))) Word8
x

  in
    Ptr Word8 -> a
go (forall {b}. Ptr b
end forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
len)
{-# INLINE foldl #-}

{-
Note [fold inlining]:

GHC will only inline a function marked INLINE
if it is fully saturated (meaning the number of
arguments provided at the call site is at least
equal to the number of lhs arguments).

-}
-- | '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
v = \(BS ForeignPtr Word8
fp Int
len) ->
          -- see fold inlining
  let
    g :: ForeignPtr Word8 -> IO a
g ForeignPtr Word8
ptr = a -> ForeignPtr Word8 -> IO a
go a
v ForeignPtr Word8
ptr
      where
        end :: ForeignPtr b
end  = ForeignPtr Word8
ptr forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
len
        -- tail recursive; traverses array left to right
        go :: a -> ForeignPtr Word8 -> IO a
go !a
z !ForeignPtr Word8
p | ForeignPtr Word8
p forall a. Eq a => a -> a -> Bool
== forall {b}. ForeignPtr b
end  = forall (m :: * -> *) a. Monad m => a -> m a
return a
z
                 | Bool
otherwise = do Word8
x <- forall a. Storable a => ForeignPtr a -> IO a
peekFp ForeignPtr Word8
p
                                  a -> ForeignPtr Word8 -> IO a
go (a -> Word8 -> a
f a
z Word8
x) (ForeignPtr Word8
p forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
1)
  in
    forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> IO a
g ForeignPtr Word8
fp
{-# 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 a
z = \(BS ForeignPtr Word8
fp Int
len) ->
          -- see fold inlining
  let
    ptr :: Ptr Word8
ptr = forall a. ForeignPtr a -> Ptr a
unsafeForeignPtrToPtr ForeignPtr Word8
fp
    end :: Ptr b
end = Ptr Word8
ptr forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
len
    -- not tail recursive; traverses array left to right
    go :: Ptr Word8 -> a
go !Ptr Word8
p | Ptr Word8
p forall a. Eq a => a -> a -> Bool
== forall {b}. Ptr b
end  = a
z
          | Bool
otherwise = let !x :: Word8
x = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ do
                                   Word8
x' <- forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
p
                                   forall a. ForeignPtr a -> IO ()
touchForeignPtr ForeignPtr Word8
fp
                                   forall (m :: * -> *) a. Monad m => a -> m a
return Word8
x'
                         in Word8 -> a -> a
k Word8
x (Ptr Word8 -> a
go (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1))
  in
    Ptr Word8 -> a
go Ptr Word8
ptr
{-# INLINE foldr #-}

-- | 'foldr'' is like 'foldr', but strict in the accumulator.
foldr' :: (Word8 -> a -> a) -> a -> ByteString -> a
foldr' :: forall a. (Word8 -> a -> a) -> a -> ByteString -> a
foldr' Word8 -> a -> a
k a
v = \(BS ForeignPtr Word8
fp Int
len) ->
          -- see fold inlining
  let
    g :: ForeignPtr a -> IO a
g ForeignPtr a
ptr = a -> ForeignPtr Word8 -> IO a
go a
v (forall {b}. ForeignPtr b
end forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
len)
      where
        end :: ForeignPtr b
end = ForeignPtr a
ptr forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` (-Int
1)
        -- tail recursive; traverses array right to left
        go :: a -> ForeignPtr Word8 -> IO a
go !a
z !ForeignPtr Word8
p | ForeignPtr Word8
p forall a. Eq a => a -> a -> Bool
== forall {b}. ForeignPtr b
end  = forall (m :: * -> *) a. Monad m => a -> m a
return a
z
                 | Bool
otherwise = do Word8
x <- forall a. Storable a => ForeignPtr a -> IO a
peekFp ForeignPtr Word8
p
                                  a -> ForeignPtr Word8 -> IO a
go (Word8 -> a -> a
k Word8
x a
z) (ForeignPtr Word8
p forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` (-Int
1))
  in
    forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall {a}. ForeignPtr a -> IO a
g ForeignPtr Word8
fp

{-# INLINE foldr' #-}

-- | 'foldl1' is a variant of 'foldl' that has no starting value
-- argument, and thus must be applied to non-empty 'ByteString's.
-- An exception will be thrown in the case of an empty ByteString.
foldl1 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldl1 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldl1 Word8 -> Word8 -> Word8
f ByteString
ps = case ByteString -> Maybe (Word8, ByteString)
uncons ByteString
ps of
  Maybe (Word8, ByteString)
Nothing     -> forall a. HasCallStack => FilePath -> a
errorEmptyList FilePath
"foldl1"
  Just (Word8
h, ByteString
t) -> forall a. (a -> Word8 -> a) -> a -> ByteString -> a
foldl Word8 -> Word8 -> Word8
f Word8
h ByteString
t
{-# INLINE foldl1 #-}

-- | 'foldl1'' is like 'foldl1', but strict in the accumulator.
-- An exception will be thrown in the case of an empty ByteString.
foldl1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldl1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldl1' Word8 -> Word8 -> Word8
f ByteString
ps = case ByteString -> Maybe (Word8, ByteString)
uncons ByteString
ps of
  Maybe (Word8, ByteString)
Nothing     -> forall a. HasCallStack => FilePath -> a
errorEmptyList FilePath
"foldl1'"
  Just (Word8
h, ByteString
t) -> forall a. (a -> Word8 -> a) -> a -> ByteString -> a
foldl' Word8 -> Word8 -> Word8
f Word8
h ByteString
t
{-# INLINE foldl1' #-}

-- | 'foldr1' is a variant of 'foldr' that has no starting value argument,
-- and thus must be applied to non-empty 'ByteString's
-- An exception will be thrown in the case of an empty ByteString.
foldr1 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldr1 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldr1 Word8 -> Word8 -> Word8
f ByteString
ps = case ByteString -> Maybe (ByteString, Word8)
unsnoc ByteString
ps of
  Maybe (ByteString, Word8)
Nothing -> forall a. HasCallStack => FilePath -> a
errorEmptyList FilePath
"foldr1"
  Just (ByteString
b, Word8
c) -> forall a. (Word8 -> a -> a) -> a -> ByteString -> a
foldr Word8 -> Word8 -> Word8
f Word8
c ByteString
b
{-# INLINE foldr1 #-}

-- | 'foldr1'' is a variant of 'foldr1', but is strict in the
-- accumulator.
foldr1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldr1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldr1' Word8 -> Word8 -> Word8
f ByteString
ps = case ByteString -> Maybe (ByteString, Word8)
unsnoc ByteString
ps of
  Maybe (ByteString, Word8)
Nothing -> forall a. HasCallStack => FilePath -> a
errorEmptyList FilePath
"foldr1'"
  Just (ByteString
b, Word8
c) -> forall a. (Word8 -> a -> a) -> a -> ByteString -> a
foldr' Word8 -> Word8 -> Word8
f Word8
c ByteString
b
{-# INLINE foldr1' #-}

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

-- | /O(n)/ Concatenate a list of ByteStrings.
concat :: [ByteString] -> ByteString
concat :: [ByteString] -> ByteString
concat = 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
f = [ByteString] -> ByteString
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (Word8 -> a -> a) -> a -> ByteString -> a
foldr ((:) forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> ByteString
f) []

-- foldr (append . f) empty

-- | /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
_ (BS ForeignPtr Word8
_ Int
0)   = Bool
False
any Word8 -> Bool
f (BS ForeignPtr Word8
x Int
len) = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> IO Bool
g ForeignPtr Word8
x
  where
    g :: ForeignPtr Word8 -> IO Bool
g ForeignPtr Word8
ptr = ForeignPtr Word8 -> IO Bool
go ForeignPtr Word8
ptr
      where
        end :: ForeignPtr b
end = ForeignPtr Word8
ptr forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
len
        go :: ForeignPtr Word8 -> IO Bool
go !ForeignPtr Word8
p | ForeignPtr Word8
p forall a. Eq a => a -> a -> Bool
== forall {b}. ForeignPtr b
end  = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
              | Bool
otherwise = do Word8
c <- forall a. Storable a => ForeignPtr a -> IO a
peekFp ForeignPtr Word8
p
                               if Word8 -> Bool
f Word8
c then forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
                                      else ForeignPtr Word8 -> IO Bool
go (ForeignPtr Word8
p forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
1)
{-# INLINE [1] any #-}

{-# RULES
"ByteString specialise any (x ==)" forall x.
    any (x `eqWord8`) = anyByte x
"ByteString specialise any (== x)" forall x.
    any (`eqWord8` x) = anyByte x
  #-}

-- | Is any element of 'ByteString' equal to c?
anyByte :: Word8 -> ByteString -> Bool
anyByte :: Word8 -> ByteString -> Bool
anyByte Word8
c (BS ForeignPtr Word8
x Int
l) = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> do
    Ptr Word8
q <- Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
memchr Ptr Word8
p Word8
c (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l)
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! Ptr Word8
q forall a. Eq a => a -> a -> Bool
/= forall {b}. Ptr b
nullPtr
{-# INLINE anyByte #-}

-- | /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
_ (BS ForeignPtr Word8
_ Int
0)   = Bool
True
all Word8 -> Bool
f (BS ForeignPtr Word8
x Int
len) = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> IO Bool
g ForeignPtr Word8
x
  where
    g :: ForeignPtr Word8 -> IO Bool
g ForeignPtr Word8
ptr = ForeignPtr Word8 -> IO Bool
go ForeignPtr Word8
ptr
      where
        end :: ForeignPtr b
end = ForeignPtr Word8
ptr forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
len
        go :: ForeignPtr Word8 -> IO Bool
go !ForeignPtr Word8
p | ForeignPtr Word8
p forall a. Eq a => a -> a -> Bool
== forall {b}. ForeignPtr b
end  = forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True  -- end of list
              | Bool
otherwise = do Word8
c <- forall a. Storable a => ForeignPtr a -> IO a
peekFp ForeignPtr Word8
p
                               if Word8 -> Bool
f Word8
c
                                  then ForeignPtr Word8 -> IO Bool
go (ForeignPtr Word8
p forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
1)
                                  else forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
{-# INLINE [1] all #-}

{-# RULES
"ByteString specialise all (x /=)" forall x.
    all (x `neWord8`) = not . anyByte x
"ByteString specialise all (/= x)" forall x.
    all (`neWord8` x) = not . anyByte x
  #-}

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

-- | /O(n)/ 'maximum' returns the maximum value from a 'ByteString'
-- An exception will be thrown in the case of an empty ByteString.
maximum :: HasCallStack => ByteString -> Word8
maximum :: HasCallStack => ByteString -> Word8
maximum xs :: ByteString
xs@(BS ForeignPtr Word8
x Int
l)
    | ByteString -> Bool
null ByteString
xs   = forall a. HasCallStack => FilePath -> a
errorEmptyList FilePath
"maximum"
    | Bool
otherwise = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
                      Ptr Word8 -> CSize -> IO Word8
c_maximum Ptr Word8
p (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l)
{-# INLINE maximum #-}

-- | /O(n)/ 'minimum' returns the minimum value from a 'ByteString'
-- An exception will be thrown in the case of an empty ByteString.
minimum :: HasCallStack => ByteString -> Word8
minimum :: HasCallStack => ByteString -> Word8
minimum xs :: ByteString
xs@(BS ForeignPtr Word8
x Int
l)
    | ByteString -> Bool
null ByteString
xs   = forall a. HasCallStack => FilePath -> a
errorEmptyList FilePath
"minimum"
    | Bool
otherwise = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
                      Ptr Word8 -> CSize -> IO Word8
c_minimum Ptr Word8
p (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l)
{-# INLINE minimum #-}

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

-- | 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
acc = \(BS ForeignPtr Word8
a Int
len) -> forall a. IO a -> a
unsafeDupablePerformIO forall a b. (a -> b) -> a -> b
$ do
               -- see fold inlining
    ForeignPtr Word8
gp   <- forall a. Int -> IO (ForeignPtr a)
mallocByteString Int
len
    let
      go :: ForeignPtr Word8 -> ForeignPtr b -> IO acc
go ForeignPtr Word8
src ForeignPtr b
dst = acc -> Int -> IO acc
mapAccumL_ acc
acc Int
0
        where
          mapAccumL_ :: acc -> Int -> IO acc
mapAccumL_ !acc
s !Int
n
             | Int
n forall a. Ord a => a -> a -> Bool
>= Int
len = forall (m :: * -> *) a. Monad m => a -> m a
return acc
s
             | Bool
otherwise = do
                  Word8
x <- forall a. Storable a => ForeignPtr a -> Int -> IO a
peekFpByteOff ForeignPtr Word8
src Int
n
                  let (acc
s', Word8
y) = acc -> Word8 -> (acc, Word8)
f acc
s Word8
x
                  forall a b. Storable a => ForeignPtr b -> Int -> a -> IO ()
pokeFpByteOff ForeignPtr b
dst Int
n Word8
y
                  acc -> Int -> IO acc
mapAccumL_ acc
s' (Int
nforall a. Num a => a -> a -> a
+Int
1)
    acc
acc' <- forall {b}. ForeignPtr Word8 -> ForeignPtr b -> IO acc
go ForeignPtr Word8
a ForeignPtr Word8
gp
    forall (m :: * -> *) a. Monad m => a -> m a
return (acc
acc', ForeignPtr Word8 -> Int -> ByteString
BS ForeignPtr Word8
gp Int
len)
{-# INLINE mapAccumL #-}

-- | 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
acc = \(BS ForeignPtr Word8
a Int
len) -> forall a. IO a -> a
unsafeDupablePerformIO forall a b. (a -> b) -> a -> b
$ do
               -- see fold inlining
    ForeignPtr Word8
gp   <- forall a. Int -> IO (ForeignPtr a)
mallocByteString Int
len
    let
      go :: ForeignPtr Word8 -> ForeignPtr b -> IO acc
go ForeignPtr Word8
src ForeignPtr b
dst = acc -> Int -> IO acc
mapAccumR_ acc
acc (Int
lenforall a. Num a => a -> a -> a
-Int
1)
        where
          mapAccumR_ :: acc -> Int -> IO acc
mapAccumR_ !acc
s (-1) = forall (m :: * -> *) a. Monad m => a -> m a
return acc
s
          mapAccumR_ !acc
s !Int
n   = do
              Word8
x  <- forall a. Storable a => ForeignPtr a -> Int -> IO a
peekFpByteOff ForeignPtr Word8
src Int
n
              let (acc
s', Word8
y) = acc -> Word8 -> (acc, Word8)
f acc
s Word8
x
              forall a b. Storable a => ForeignPtr b -> Int -> a -> IO ()
pokeFpByteOff ForeignPtr b
dst Int
n Word8
y
              acc -> Int -> IO acc
mapAccumR_ acc
s' (Int
nforall a. Num a => a -> a -> a
-Int
1)
    acc
acc' <- forall {b}. ForeignPtr Word8 -> ForeignPtr b -> IO acc
go ForeignPtr Word8
a ForeignPtr Word8
gp
    forall (m :: * -> *) a. Monad m => a -> m a
return (acc
acc', ForeignPtr Word8 -> Int -> ByteString
BS ForeignPtr Word8
gp Int
len)
{-# INLINE mapAccumR #-}

-- ---------------------------------------------------------------------
-- 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
f Word8
v = \(BS ForeignPtr Word8
a Int
len) -> Int -> (ForeignPtr Word8 -> IO ()) -> ByteString
unsafeCreateFp (Int
lenforall a. Num a => a -> a -> a
+Int
1) forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
q -> do
         -- see fold inlining
        forall a. Storable a => ForeignPtr a -> a -> IO ()
pokeFp ForeignPtr Word8
q Word8
v
        let
          go :: ForeignPtr Word8 -> ForeignPtr b -> IO ()
go ForeignPtr Word8
src ForeignPtr b
dst = Word8 -> Int -> IO ()
scanl_ Word8
v Int
0
            where
              scanl_ :: Word8 -> Int -> IO ()
scanl_ !Word8
z !Int
n
                  | Int
n forall a. Ord a => a -> a -> Bool
>= Int
len  = forall (m :: * -> *) a. Monad m => a -> m a
return ()
                  | Bool
otherwise = do
                      Word8
x <- forall a. Storable a => ForeignPtr a -> Int -> IO a
peekFpByteOff ForeignPtr Word8
src Int
n
                      let z' :: Word8
z' = Word8 -> Word8 -> Word8
f Word8
z Word8
x
                      forall a b. Storable a => ForeignPtr b -> Int -> a -> IO ()
pokeFpByteOff ForeignPtr b
dst Int
n Word8
z'
                      Word8 -> Int -> IO ()
scanl_ Word8
z' (Int
nforall a. Num a => a -> a -> a
+Int
1)
        forall {b}. ForeignPtr Word8 -> ForeignPtr b -> IO ()
go ForeignPtr Word8
a (ForeignPtr Word8
q forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
1)
{-# INLINE scanl #-}

-- | 'scanl1' is a variant of 'scanl' that has no starting value argument.
--
-- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
scanl1 :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString
scanl1 :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString
scanl1 Word8 -> Word8 -> Word8
f ByteString
ps = case ByteString -> Maybe (Word8, ByteString)
uncons ByteString
ps of
  Maybe (Word8, ByteString)
Nothing     -> ByteString
empty
  Just (Word8
h, ByteString
t) -> (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
scanl Word8 -> Word8 -> Word8
f Word8
h ByteString
t
{-# INLINE scanl1 #-}

-- | '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
--
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
f Word8
v = \(BS ForeignPtr Word8
a Int
len) -> Int -> (ForeignPtr Word8 -> IO ()) -> ByteString
unsafeCreateFp (Int
lenforall a. Num a => a -> a -> a
+Int
1) forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
b -> do
         -- see fold inlining
        forall a b. Storable a => ForeignPtr b -> Int -> a -> IO ()
pokeFpByteOff ForeignPtr Word8
b Int
len Word8
v
        let
          go :: ForeignPtr Word8 -> ForeignPtr b -> IO ()
go ForeignPtr Word8
p ForeignPtr b
q = Word8 -> Int -> IO ()
scanr_ Word8
v (Int
lenforall a. Num a => a -> a -> a
-Int
1)
            where
              scanr_ :: Word8 -> Int -> IO ()
scanr_ !Word8
z !Int
n
                  | Int
n forall a. Ord a => a -> a -> Bool
< Int
0     = forall (m :: * -> *) a. Monad m => a -> m a
return ()
                  | Bool
otherwise = do
                      Word8
x <- forall a. Storable a => ForeignPtr a -> Int -> IO a
peekFpByteOff ForeignPtr Word8
p Int
n
                      let z' :: Word8
z' = Word8 -> Word8 -> Word8
f Word8
x Word8
z
                      forall a b. Storable a => ForeignPtr b -> Int -> a -> IO ()
pokeFpByteOff ForeignPtr b
q Int
n Word8
z'
                      Word8 -> Int -> IO ()
scanr_ Word8
z' (Int
nforall a. Num a => a -> a -> a
-Int
1)
        forall {b}. ForeignPtr Word8 -> ForeignPtr b -> IO ()
go ForeignPtr Word8
a ForeignPtr Word8
b
{-# INLINE scanr #-}

-- | 'scanr1' is a variant of 'scanr' that has no starting value argument.
scanr1 :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString
scanr1 :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString
scanr1 Word8 -> Word8 -> Word8
f ByteString
ps = case ByteString -> Maybe (ByteString, Word8)
unsnoc ByteString
ps of
  Maybe (ByteString, Word8)
Nothing -> ByteString
empty
  Just (ByteString
b, Word8
c) -> (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
scanr Word8 -> Word8 -> Word8
f Word8
c ByteString
b
{-# INLINE scanr1 #-}

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

-- | /O(n)/ 'replicate' @n x@ is a ByteString of length @n@ with @x@
-- the value of every element. The following holds:
--
-- > replicate w c = unfoldr w (\u -> Just (u,u)) c
--
-- This implementation uses @memset(3)@
replicate :: Int -> Word8 -> ByteString
replicate :: Int -> Word8 -> ByteString
replicate Int
w Word8
c
    | Int
w forall a. Ord a => a -> a -> Bool
<= Int
0    = ByteString
empty
    | Bool
otherwise = Int -> (ForeignPtr Word8 -> IO ()) -> ByteString
unsafeCreateFp Int
w forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
fptr ->
        forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fptr forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr ->
                      forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
memset Ptr Word8
ptr Word8
c (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
w)
{-# INLINE replicate #-}

-- | /O(n)/, where /n/ is the length of the result.  The 'unfoldr'
-- function is analogous to the List \'unfoldr\'.  'unfoldr' builds a
-- ByteString from a seed value.  The function takes the element and
-- returns 'Nothing' if it is done producing the ByteString or returns
-- 'Just' @(a,b)@, in which case, @a@ is the next byte in the string,
-- and @b@ is the seed value for further production.
--
-- Examples:
--
-- >    unfoldr (\x -> if x <= 5 then Just (x, x + 1) else Nothing) 0
-- > == pack [0, 1, 2, 3, 4, 5]
--
unfoldr :: (a -> Maybe (Word8, a)) -> a -> ByteString
unfoldr :: forall a. (a -> Maybe (Word8, a)) -> a -> ByteString
unfoldr a -> Maybe (Word8, a)
f = [ByteString] -> ByteString
concat forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Int -> a -> [ByteString]
unfoldChunk Int
32 Int
64
  where unfoldChunk :: Int -> Int -> a -> [ByteString]
unfoldChunk Int
n Int
n' a
x =
          case forall a.
Int -> (a -> Maybe (Word8, a)) -> a -> (ByteString, Maybe a)
unfoldrN Int
n a -> Maybe (Word8, a)
f a
x of
            (ByteString
s, Maybe a
Nothing) -> [ByteString
s]
            (ByteString
s, Just a
x') -> ByteString
s forall a. a -> [a] -> [a]
: Int -> Int -> a -> [ByteString]
unfoldChunk Int
n' (Int
nforall a. Num a => a -> a -> a
+Int
n') a
x'
{-# INLINE unfoldr #-}

-- | /O(n)/ Like 'unfoldr', 'unfoldrN' builds a ByteString from a seed
-- value.  However, the length of the result is limited by the first
-- argument to 'unfoldrN'.  This function is more efficient than 'unfoldr'
-- when the maximum length of the result is known.
--
-- The following equation relates 'unfoldrN' and 'unfoldr':
--
-- > fst (unfoldrN n f s) == take n (unfoldr f s)
--
unfoldrN :: Int -> (a -> Maybe (Word8, a)) -> a -> (ByteString, Maybe a)
unfoldrN :: forall a.
Int -> (a -> Maybe (Word8, a)) -> a -> (ByteString, Maybe a)
unfoldrN Int
i a -> Maybe (Word8, a)
f a
x0
    | Int
i forall a. Ord a => a -> a -> Bool
< Int
0     = (ByteString
empty, forall a. a -> Maybe a
Just a
x0)
    | Bool
otherwise = forall a. IO a -> a
unsafePerformIO forall a b. (a -> b) -> a -> b
$ forall a.
Int -> (ForeignPtr Word8 -> IO (Int, Int, a)) -> IO (ByteString, a)
createFpAndTrim' Int
i forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
p -> forall {a} {b}.
Num a =>
ForeignPtr b -> a -> Int -> IO (a, Int, Maybe a)
go ForeignPtr Word8
p a
x0 Int
0
  where
    go :: ForeignPtr b -> a -> Int -> IO (a, Int, Maybe a)
go !ForeignPtr b
p !a
x !Int
n = forall {a}. Num a => a -> Int -> IO (a, Int, Maybe a)
go' a
x Int
n
      where
        go' :: a -> Int -> IO (a, Int, Maybe a)
go' !a
x' !Int
n'
          | Int
n' forall a. Eq a => a -> a -> Bool
== Int
i    = forall (m :: * -> *) a. Monad m => a -> m a
return (a
0, Int
n', forall a. a -> Maybe a
Just a
x')
          | Bool
otherwise = case a -> Maybe (Word8, a)
f a
x' of
                          Maybe (Word8, a)
Nothing      -> forall (m :: * -> *) a. Monad m => a -> m a
return (a
0, Int
n', forall a. Maybe a
Nothing)
                          Just (Word8
w,a
x'') -> do forall a b. Storable a => ForeignPtr b -> Int -> a -> IO ()
pokeFpByteOff ForeignPtr b
p Int
n' Word8
w
                                             a -> Int -> IO (a, Int, Maybe a)
go' a
x'' (Int
n'forall a. Num a => a -> a -> a
+Int
1)
{-# INLINE unfoldrN #-}

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

-- | /O(1)/ 'take' @n@, applied to a ByteString @xs@, returns the prefix
-- of @xs@ of length @n@, or @xs@ itself if @n > 'length' xs@.
take :: Int -> ByteString -> ByteString
take :: Int -> ByteString -> ByteString
take Int
n ps :: ByteString
ps@(BS ForeignPtr Word8
x Int
l)
    | Int
n forall a. Ord a => a -> a -> Bool
<= Int
0    = ByteString
empty
    | Int
n forall a. Ord a => a -> a -> Bool
>= Int
l    = ByteString
ps
    | Bool
otherwise = ForeignPtr Word8 -> Int -> ByteString
BS ForeignPtr Word8
x Int
n
{-# INLINE take #-}

-- | /O(1)/ @'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.1.0
takeEnd :: Int -> ByteString -> ByteString
takeEnd :: Int -> ByteString -> ByteString
takeEnd Int
n ps :: ByteString
ps@(BS ForeignPtr Word8
x Int
len)
  | Int
n forall a. Ord a => a -> a -> Bool
>= Int
len  = ByteString
ps
  | Int
n forall a. Ord a => a -> a -> Bool
<= Int
0    = ByteString
empty
  | Bool
otherwise = ForeignPtr Word8 -> Int -> ByteString
BS (forall a b. ForeignPtr a -> Int -> ForeignPtr b
plusForeignPtr ForeignPtr Word8
x (Int
len forall a. Num a => a -> a -> a
- Int
n)) Int
n
{-# INLINE takeEnd #-}

-- | /O(1)/ 'drop' @n xs@ returns the suffix of @xs@ after the first @n@
-- elements, or 'empty' if @n > 'length' xs@.
drop  :: Int -> ByteString -> ByteString
drop :: Int -> ByteString -> ByteString
drop Int
n ps :: ByteString
ps@(BS ForeignPtr Word8
x Int
l)
    | Int
n forall a. Ord a => a -> a -> Bool
<= Int
0    = ByteString
ps
    | Int
n forall a. Ord a => a -> a -> Bool
>= Int
l    = ByteString
empty
    | Bool
otherwise = ForeignPtr Word8 -> Int -> ByteString
BS (forall a b. ForeignPtr a -> Int -> ForeignPtr b
plusForeignPtr ForeignPtr Word8
x Int
n) (Int
lforall a. Num a => a -> a -> a
-Int
n)
{-# INLINE drop #-}

-- | /O(1)/ @'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.1.0
dropEnd :: Int -> ByteString -> ByteString
dropEnd :: Int -> ByteString -> ByteString
dropEnd Int
n ps :: ByteString
ps@(BS ForeignPtr Word8
x Int
len)
    | Int
n forall a. Ord a => a -> a -> Bool
<= Int
0    = ByteString
ps
    | Int
n forall a. Ord a => a -> a -> Bool
>= Int
len  = ByteString
empty
    | Bool
otherwise = ForeignPtr Word8 -> Int -> ByteString
BS ForeignPtr Word8
x (Int
len forall a. Num a => a -> a -> a
- Int
n)
{-# INLINE dropEnd #-}

-- | /O(1)/ 'splitAt' @n xs@ is equivalent to @('take' n xs, 'drop' n xs)@.
splitAt :: Int -> ByteString -> (ByteString, ByteString)
splitAt :: Int -> ByteString -> (ByteString, ByteString)
splitAt Int
n ps :: ByteString
ps@(BS ForeignPtr Word8
x Int
l)
    | Int
n forall a. Ord a => a -> a -> Bool
<= Int
0    = (ByteString
empty, ByteString
ps)
    | Int
n forall a. Ord a => a -> a -> Bool
>= Int
l    = (ByteString
ps, ByteString
empty)
    | Bool
otherwise = (ForeignPtr Word8 -> Int -> ByteString
BS ForeignPtr Word8
x Int
n, ForeignPtr Word8 -> Int -> ByteString
BS (forall a b. ForeignPtr a -> Int -> ForeignPtr b
plusForeignPtr ForeignPtr Word8
x Int
n) (Int
lforall a. Num a => a -> a -> a
-Int
n))
{-# INLINE splitAt #-}

-- | 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
ps = Int -> ByteString -> ByteString
unsafeTake ((Word8 -> Bool) -> ByteString -> Int
findIndexOrLength (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
f) ByteString
ps) ByteString
ps
{-# INLINE [1] takeWhile #-}

{-# RULES
"ByteString specialise takeWhile (x /=)" forall x.
    takeWhile (x `neWord8`) = fst . breakByte x
"ByteString specialise takeWhile (/= x)" forall x.
    takeWhile (`neWord8` x) = fst . breakByte x
"ByteString specialise takeWhile (x ==)" forall x.
    takeWhile (x `eqWord8`) = fst . spanByte x
"ByteString specialise takeWhile (== x)" forall x.
    takeWhile (`eqWord8` x) = fst . spanByte x
  #-}

-- | Returns the longest (possibly empty) suffix of elements
-- satisfying the predicate.
--
-- @'takeWhileEnd' p@ is equivalent to @'reverse' . 'takeWhile' p . 'reverse'@.
--
-- @since 0.10.12.0
takeWhileEnd :: (Word8 -> Bool) -> ByteString -> ByteString
takeWhileEnd :: (Word8 -> Bool) -> ByteString -> ByteString
takeWhileEnd Word8 -> Bool
f ByteString
ps = Int -> ByteString -> ByteString
unsafeDrop ((Word8 -> Bool) -> ByteString -> Int
findFromEndUntil (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
f) ByteString
ps) ByteString
ps
{-# INLINE takeWhileEnd #-}

-- | 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
ps = Int -> ByteString -> ByteString
unsafeDrop ((Word8 -> Bool) -> ByteString -> Int
findIndexOrLength (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
f) ByteString
ps) ByteString
ps
{-# INLINE [1] dropWhile #-}

{-# RULES
"ByteString specialise dropWhile (x /=)" forall x.
    dropWhile (x `neWord8`) = snd . breakByte x
"ByteString specialise dropWhile (/= x)" forall x.
    dropWhile (`neWord8` x) = snd . breakByte x
"ByteString specialise dropWhile (x ==)" forall x.
    dropWhile (x `eqWord8`) = snd . spanByte x
"ByteString specialise dropWhile (== x)" forall x.
    dropWhile (`eqWord8` x) = snd . spanByte x
  #-}

-- | 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'@.
--
-- @since 0.10.12.0
dropWhileEnd :: (Word8 -> Bool) -> ByteString -> ByteString
dropWhileEnd :: (Word8 -> Bool) -> ByteString -> ByteString
dropWhileEnd Word8 -> Bool
f ByteString
ps = Int -> ByteString -> ByteString
unsafeTake ((Word8 -> Bool) -> ByteString -> Int
findFromEndUntil (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
f) ByteString
ps) ByteString
ps
{-# INLINE dropWhileEnd #-}

-- | 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))@.
--
-- Under GHC, a rewrite rule will transform break (==) into a
-- call to the specialised breakByte:
--
-- > break ((==) x) = breakByte x
-- > break (==x) = breakByte x
--
break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
break Word8 -> Bool
p ByteString
ps = case (Word8 -> Bool) -> ByteString -> Int
findIndexOrLength Word8 -> Bool
p ByteString
ps of Int
n -> (Int -> ByteString -> ByteString
unsafeTake Int
n ByteString
ps, Int -> ByteString -> ByteString
unsafeDrop Int
n ByteString
ps)
{-# INLINE [1] break #-}

-- See bytestring #70
{-# RULES
"ByteString specialise break (x ==)" forall x.
    break (x `eqWord8`) = breakByte x
"ByteString specialise break (== x)" forall x.
    break (`eqWord8` x) = breakByte x
  #-}

-- INTERNAL:

-- | '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 :: Word8 -> ByteString -> (ByteString, ByteString)
breakByte Word8
c ByteString
p = case Word8 -> ByteString -> Maybe Int
elemIndex Word8
c ByteString
p of
    Maybe Int
Nothing -> (ByteString
p,ByteString
empty)
    Just Int
n  -> (Int -> ByteString -> ByteString
unsafeTake Int
n ByteString
p, Int -> ByteString -> ByteString
unsafeDrop Int
n ByteString
p)
{-# INLINE breakByte #-}

-- | 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))@.
--
breakEnd :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
breakEnd :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
breakEnd  Word8 -> Bool
p ByteString
ps = Int -> ByteString -> (ByteString, ByteString)
splitAt ((Word8 -> Bool) -> ByteString -> Int
findFromEndUntil Word8 -> Bool
p ByteString
ps) ByteString
ps

-- | 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 forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
p)
{-# INLINE [1] span #-}

-- | '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 :: Word8 -> ByteString -> (ByteString, ByteString)
spanByte Word8
c ps :: ByteString
ps@(BS ForeignPtr Word8
x Int
l) =
    forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$  forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x forall {b}. Ptr b -> IO (ByteString, ByteString)
g
  where
    g :: Ptr b -> IO (ByteString, ByteString)
g Ptr b
p = Int -> IO (ByteString, ByteString)
go Int
0
      where
        go :: Int -> IO (ByteString, ByteString)
go !Int
i | Int
i forall a. Ord a => a -> a -> Bool
>= Int
l    = forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
ps, ByteString
empty)
              | Bool
otherwise = do Word8
c' <- forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p Int
i
                               if Word8
c forall a. Eq a => a -> a -> Bool
/= Word8
c'
                                   then forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> ByteString -> ByteString
unsafeTake Int
i ByteString
ps, Int -> ByteString -> ByteString
unsafeDrop Int
i ByteString
ps)
                                   else Int -> IO (ByteString, ByteString)
go (Int
iforall a. Num a => a -> a -> a
+Int
1)
{-# INLINE spanByte #-}

-- See bytestring #70
{-# RULES
"ByteString specialise span (x ==)" forall x.
    span (x `eqWord8`) = spanByte x
"ByteString specialise span (== x)" forall x.
    span (`eqWord8` x) = spanByte x
  #-}

-- | 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)
--
spanEnd :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
spanEnd :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
spanEnd  Word8 -> Bool
p ByteString
ps = Int -> ByteString -> (ByteString, ByteString)
splitAt ((Word8 -> Bool) -> ByteString -> Int
findFromEndUntil (Bool -> Bool
notforall b c a. (b -> c) -> (a -> b) -> a -> c
.Word8 -> Bool
p) ByteString
ps) ByteString
ps

-- | /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
_ (BS ForeignPtr Word8
_  Int
0) = []
splitWith Word8 -> Bool
predicate (BS ForeignPtr Word8
fp Int
len) = Int -> Int -> ForeignPtr Word8 -> [ByteString]
splitWith0 Int
0 Int
len ForeignPtr Word8
fp
  where splitWith0 :: Int -> Int -> ForeignPtr Word8 -> [ByteString]
splitWith0 !Int
off' !Int
len' !ForeignPtr Word8
fp' =
          forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$
              ForeignPtr Word8
-> Int -> Int -> Int -> ForeignPtr Word8 -> IO [ByteString]
splitLoop ForeignPtr Word8
fp Int
0 Int
off' Int
len' ForeignPtr Word8
fp'

        splitLoop :: ForeignPtr Word8
                  -> Int -> Int -> Int
                  -> ForeignPtr Word8
                  -> IO [ByteString]
        splitLoop :: ForeignPtr Word8
-> Int -> Int -> Int -> ForeignPtr Word8 -> IO [ByteString]
splitLoop ForeignPtr Word8
p Int
idx2 Int
off' Int
len' ForeignPtr Word8
fp' = Int -> IO [ByteString]
go Int
idx2
          where
            go :: Int -> IO [ByteString]
go Int
idx'
                | Int
idx' forall a. Ord a => a -> a -> Bool
>= Int
len'  = forall (m :: * -> *) a. Monad m => a -> m a
return [ForeignPtr Word8 -> Int -> ByteString
BS (forall a b. ForeignPtr a -> Int -> ForeignPtr b
plusForeignPtr ForeignPtr Word8
fp' Int
off') Int
idx']
                | Bool
otherwise = do
                    Word8
w <- forall a. Storable a => ForeignPtr a -> Int -> IO a
peekFpByteOff ForeignPtr Word8
p (Int
off'forall a. Num a => a -> a -> a
+Int
idx')
                    if Word8 -> Bool
predicate Word8
w
                       then forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8 -> Int -> ByteString
BS (forall a b. ForeignPtr a -> Int -> ForeignPtr b
plusForeignPtr ForeignPtr Word8
fp' Int
off') Int
idx' forall a. a -> [a] -> [a]
:
                                  Int -> Int -> ForeignPtr Word8 -> [ByteString]
splitWith0 (Int
off'forall a. Num a => a -> a -> a
+Int
idx'forall a. Num a => a -> a -> a
+Int
1) (Int
len'forall a. Num a => a -> a -> a
-Int
idx'forall a. Num a => a -> a -> a
-Int
1) ForeignPtr Word8
fp')
                       else Int -> IO [ByteString]
go (Int
idx'forall a. Num a => a -> a -> a
+Int
1)
{-# 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
_ (BS ForeignPtr Word8
_ Int
0) = []
split Word8
w (BS ForeignPtr Word8
x Int
l) = Int -> [ByteString]
loop Int
0
    where
        loop :: Int -> [ByteString]
loop !Int
n =
            let q :: Ptr Word8
q = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
                      Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
memchr (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
n)
                             Word8
w (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
lforall a. Num a => a -> a -> a
-Int
n))
            in if Ptr Word8
q forall a. Eq a => a -> a -> Bool
== forall {b}. Ptr b
nullPtr
                then [ForeignPtr Word8 -> Int -> ByteString
BS (forall a b. ForeignPtr a -> Int -> ForeignPtr b
plusForeignPtr ForeignPtr Word8
x Int
n) (Int
lforall a. Num a => a -> a -> a
-Int
n)]
                else let i :: Int
i = Ptr Word8
q forall a b. Ptr a -> Ptr b -> Int
`minusPtr` forall a. ForeignPtr a -> Ptr a
unsafeForeignPtrToPtr ForeignPtr Word8
x
                      in ForeignPtr Word8 -> Int -> ByteString
BS (forall a b. ForeignPtr a -> Int -> ForeignPtr b
plusForeignPtr ForeignPtr Word8
x Int
n) (Int
iforall a. Num a => a -> a -> a
-Int
n) forall a. a -> [a] -> [a]
: Int -> [ByteString]
loop (Int
iforall a. Num a => a -> a -> a
+Int
1)

{-# 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. It is about 40% faster than
-- /groupBy (==)/
group :: ByteString -> [ByteString]
group :: ByteString -> [ByteString]
group ByteString
xs = case ByteString -> Maybe (Word8, ByteString)
uncons ByteString
xs of
  Maybe (Word8, ByteString)
Nothing     -> []
  Just (Word8
h, ByteString
_) -> ByteString
ys forall a. a -> [a] -> [a]
: ByteString -> [ByteString]
group ByteString
zs
    where
        (ByteString
ys, ByteString
zs) = Word8 -> ByteString -> (ByteString, ByteString)
spanByte Word8
h ByteString
xs

-- | 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
xs = case ByteString -> Maybe (Word8, ByteString)
uncons ByteString
xs of
  Maybe (Word8, ByteString)
Nothing     -> []
  Just (Word8
h, ByteString
t) -> Int -> ByteString -> ByteString
unsafeTake Int
n ByteString
xs forall a. a -> [a] -> [a]
: (Word8 -> Word8 -> Bool) -> ByteString -> [ByteString]
groupBy Word8 -> Word8 -> Bool
k (Int -> ByteString -> ByteString
unsafeDrop Int
n ByteString
xs)
    where
        n :: Int
n = Int
1 forall a. Num a => a -> a -> a
+ (Word8 -> Bool) -> ByteString -> Int
findIndexOrLength (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Word8 -> Bool
k Word8
h) ByteString
t

-- | /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
_ [] = forall a. Monoid a => a
mempty
intercalate ByteString
_ [ByteString
x] = ByteString
x -- This branch exists for laziness, not speed
intercalate (BS ForeignPtr Word8
sepPtr Int
sepLen) (BS ForeignPtr Word8
hPtr Int
hLen : [ByteString]
t) =
  Int -> (ForeignPtr Word8 -> IO ()) -> ByteString
unsafeCreateFp Int
totalLen forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
dstPtr0 -> do
      ForeignPtr Word8 -> ForeignPtr Word8 -> Int -> IO ()
memcpyFp ForeignPtr Word8
dstPtr0 ForeignPtr Word8
hPtr Int
hLen
      let go :: ForeignPtr Word8 -> [ByteString] -> IO ()
go ForeignPtr Word8
_ [] = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
          go ForeignPtr Word8
dstPtr (BS ForeignPtr Word8
chunkPtr Int
chunkLen : [ByteString]
chunks) = do
            ForeignPtr Word8 -> ForeignPtr Word8 -> Int -> IO ()
memcpyFp ForeignPtr Word8
dstPtr ForeignPtr Word8
sepPtr Int
sepLen
            let destPtr' :: ForeignPtr b
destPtr' = ForeignPtr Word8
dstPtr forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
sepLen
            ForeignPtr Word8 -> ForeignPtr Word8 -> Int -> IO ()
memcpyFp forall {b}. ForeignPtr b
destPtr' ForeignPtr Word8
chunkPtr Int
chunkLen
            ForeignPtr Word8 -> [ByteString] -> IO ()
go (forall {b}. ForeignPtr b
destPtr' forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
chunkLen) [ByteString]
chunks
      ForeignPtr Word8 -> [ByteString] -> IO ()
go (ForeignPtr Word8
dstPtr0 forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
hLen) [ByteString]
t
  where
  totalLen :: Int
totalLen = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' (\Int
acc (BS ForeignPtr Word8
_ Int
chunkLen) -> Int
acc forall a. Num a => a -> a -> a
+ Int
chunkLen forall a. Num a => a -> a -> a
+ Int
sepLen) Int
hLen [ByteString]
t
{-# INLINE intercalate #-}

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

-- | /O(1)/ 'ByteString' index (subscript) operator, starting from 0.
--
-- This is a partial function, consider using 'indexMaybe' instead.
index :: HasCallStack => ByteString -> Int -> Word8
index :: HasCallStack => ByteString -> Int -> Word8
index ByteString
ps Int
n
    | Int
n forall a. Ord a => a -> a -> Bool
< Int
0          = forall a. HasCallStack => FilePath -> FilePath -> a
moduleError FilePath
"index" (FilePath
"negative index: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show Int
n)
    | Int
n forall a. Ord a => a -> a -> Bool
>= ByteString -> Int
length ByteString
ps = forall a. HasCallStack => FilePath -> FilePath -> a
moduleError FilePath
"index" (FilePath
"index too large: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show Int
n
                                         forall a. [a] -> [a] -> [a]
++ FilePath
", length = " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show (ByteString -> Int
length ByteString
ps))
    | Bool
otherwise      = ByteString
ps ByteString -> Int -> Word8
`unsafeIndex` Int
n
{-# INLINE index #-}

-- | /O(1)/ 'ByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
indexMaybe :: ByteString -> Int -> Maybe Word8
indexMaybe :: ByteString -> Int -> Maybe Word8
indexMaybe ByteString
ps Int
n
    | Int
n forall a. Ord a => a -> a -> Bool
< Int
0          = forall a. Maybe a
Nothing
    | Int
n forall a. Ord a => a -> a -> Bool
>= ByteString -> Int
length ByteString
ps = forall a. Maybe a
Nothing
    | Bool
otherwise      = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$! ByteString
ps ByteString -> Int -> Word8
`unsafeIndex` Int
n
{-# INLINE indexMaybe #-}

-- | /O(1)/ 'ByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
(!?) :: ByteString -> Int -> Maybe Word8
!? :: ByteString -> Int -> Maybe Word8
(!?) = ByteString -> Int -> 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 Int
elemIndex :: Word8 -> ByteString -> Maybe Int
elemIndex Word8
c (BS ForeignPtr Word8
x Int
l) = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> do
    Ptr Word8
q <- Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
memchr Ptr Word8
p Word8
c (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l)
    forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! if Ptr Word8
q forall a. Eq a => a -> a -> Bool
== forall {b}. Ptr b
nullPtr then forall a. Maybe a
Nothing else forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$! Ptr Word8
q forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
p
{-# INLINE elemIndex #-}

-- | /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)
--
elemIndexEnd :: Word8 -> ByteString -> Maybe Int
elemIndexEnd :: Word8 -> ByteString -> Maybe Int
elemIndexEnd = (Word8 -> Bool) -> ByteString -> Maybe Int
findIndexEnd forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 -> [Int]
elemIndices :: Word8 -> ByteString -> [Int]
elemIndices Word8
w (BS ForeignPtr Word8
x Int
l) = Int -> [Int]
loop Int
0
    where
        loop :: Int -> [Int]
loop !Int
n = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> do
            Ptr Word8
q <- Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
memchr (Ptr Word8
p forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
n) Word8
w (forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
l forall a. Num a => a -> a -> a
- Int
n))
            if Ptr Word8
q forall a. Eq a => a -> a -> Bool
== forall {b}. Ptr b
nullPtr
                then forall (m :: * -> *) a. Monad m => a -> m a
return []
                else let !i :: Int
i = Ptr Word8
q forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
p
                      in forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Int
i forall a. a -> [a] -> [a]
: Int -> [Int]
loop (Int
i forall a. Num a => a -> a -> a
+ Int
1)
{-# INLINE elemIndices #-}

-- | count returns the number of times its argument appears in the ByteString
--
-- > count = length . elemIndices
--
-- But more efficiently than using length on the intermediate list.
count :: Word8 -> ByteString -> Int
count :: Word8 -> ByteString -> Int
count Word8
w (BS ForeignPtr Word8
x Int
m) = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
    forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr Word8 -> CSize -> Word8 -> IO CSize
c_count Ptr Word8
p (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
m) Word8
w
{-# INLINE count #-}

-- | /O(n)/ The 'findIndex' function takes a predicate and a 'ByteString' and
-- returns the index of the first element in the ByteString
-- satisfying the predicate.
findIndex :: (Word8 -> Bool) -> ByteString -> Maybe Int
findIndex :: (Word8 -> Bool) -> ByteString -> Maybe Int
findIndex Word8 -> Bool
k (BS ForeignPtr Word8
x Int
l) = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall {a}. ForeignPtr a -> IO (Maybe Int)
g ForeignPtr Word8
x
  where
    g :: ForeignPtr a -> IO (Maybe Int)
g !ForeignPtr a
ptr = Int -> IO (Maybe Int)
go Int
0
      where
        go :: Int -> IO (Maybe Int)
go !Int
n | Int
n forall a. Ord a => a -> a -> Bool
>= Int
l    = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
              | Bool
otherwise = do Word8
w <- forall a. Storable a => ForeignPtr a -> IO a
peekFp forall a b. (a -> b) -> a -> b
$ ForeignPtr a
ptr forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
n
                               if Word8 -> Bool
k Word8
w
                                 then forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just Int
n)
                                 else Int -> IO (Maybe Int)
go (Int
nforall a. Num a => a -> a -> a
+Int
1)
{-# INLINE [1] findIndex #-}

-- | /O(n)/ 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 Int
findIndexEnd :: (Word8 -> Bool) -> ByteString -> Maybe Int
findIndexEnd Word8 -> Bool
k (BS ForeignPtr Word8
x Int
l) = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> IO (Maybe Int)
g ForeignPtr Word8
x
  where
    g :: ForeignPtr Word8 -> IO (Maybe Int)
g !ForeignPtr Word8
ptr = Int -> IO (Maybe Int)
go (Int
lforall a. Num a => a -> a -> a
-Int
1)
      where
        go :: Int -> IO (Maybe Int)
go !Int
n | Int
n forall a. Ord a => a -> a -> Bool
< Int
0     = forall (m :: * -> *) a. Monad m => a -> m a
return forall a. Maybe a
Nothing
              | Bool
otherwise = do Word8
w <- forall a. Storable a => ForeignPtr a -> Int -> IO a
peekFpByteOff ForeignPtr Word8
ptr Int
n
                               if Word8 -> Bool
k Word8
w
                                 then forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. a -> Maybe a
Just Int
n)
                                 else Int -> IO (Maybe Int)
go (Int
nforall a. Num a => a -> a -> a
-Int
1)
{-# INLINE findIndexEnd #-}

-- | /O(n)/ The 'findIndices' function extends 'findIndex', by returning the
-- indices of all elements satisfying the predicate, in ascending order.
findIndices :: (Word8 -> Bool) -> ByteString -> [Int]
findIndices :: (Word8 -> Bool) -> ByteString -> [Int]
findIndices Word8 -> Bool
p = Int -> ByteString -> [Int]
loop Int
0
   where
     loop :: Int -> ByteString -> [Int]
loop !Int
n !ByteString
qs = case (Word8 -> Bool) -> ByteString -> Maybe Int
findIndex Word8 -> Bool
p ByteString
qs of
                     Just !Int
i ->
                        let !j :: Int
j = Int
nforall a. Num a => a -> a -> a
+Int
i
                         in Int
j forall a. a -> [a] -> [a]
: Int -> ByteString -> [Int]
loop (Int
jforall a. Num a => a -> a -> a
+Int
1) (Int -> ByteString -> ByteString
unsafeDrop (Int
iforall a. Num a => a -> a -> a
+Int
1) ByteString
qs)
                     Maybe Int
Nothing -> []
{-# INLINE [1] findIndices #-}


{-# RULES
"ByteString specialise findIndex (x ==)" forall x. findIndex (x`eqWord8`) = elemIndex x
"ByteString specialise findIndex (== x)" forall x. findIndex (`eqWord8`x) = elemIndex x
"ByteString specialise findIndices (x ==)" forall x. findIndices (x`eqWord8`) = elemIndices x
"ByteString specialise findIndices (== x)" forall x. findIndices (`eqWord8`x) = elemIndices x
  #-}

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

-- | /O(n)/ 'elem' is the 'ByteString' membership predicate.
elem :: Word8 -> ByteString -> Bool
elem :: Word8 -> ByteString -> Bool
elem Word8
c ByteString
ps = case Word8 -> ByteString -> Maybe Int
elemIndex Word8
c ByteString
ps of Maybe Int
Nothing -> Bool
False ; Maybe Int
_ -> Bool
True
{-# INLINE elem #-}

-- | /O(n)/ 'notElem' is the inverse of 'elem'
notElem :: Word8 -> ByteString -> Bool
notElem :: Word8 -> ByteString -> Bool
notElem Word8
c ByteString
ps = Bool -> Bool
not (Word8
c Word8 -> ByteString -> Bool
`elem` ByteString
ps)
{-# INLINE notElem #-}

-- | /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
k = \ps :: ByteString
ps@(BS ForeignPtr Word8
pIn Int
l) ->
        -- see fold inlining.
  if ByteString -> Bool
null ByteString
ps
    then ByteString
ps
    else
      forall a. IO a -> a
unsafeDupablePerformIO forall a b. (a -> b) -> a -> b
$ Int -> (ForeignPtr Word8 -> IO Int) -> IO ByteString
createFpAndTrim Int
l forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
pOut -> do
        let
          go' :: ForeignPtr Word8 -> ForeignPtr Word8 -> IO (ForeignPtr Word8)
go' ForeignPtr Word8
pf ForeignPtr Word8
pt = ForeignPtr Word8 -> ForeignPtr Word8 -> IO (ForeignPtr Word8)
go ForeignPtr Word8
pf ForeignPtr Word8
pt
            where
              end :: ForeignPtr b
end = ForeignPtr Word8
pf forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
l
              go :: ForeignPtr Word8 -> ForeignPtr Word8 -> IO (ForeignPtr Word8)
go !ForeignPtr Word8
f !ForeignPtr Word8
t | ForeignPtr Word8
f forall a. Eq a => a -> a -> Bool
== forall {b}. ForeignPtr b
end  = forall (m :: * -> *) a. Monad m => a -> m a
return ForeignPtr Word8
t
                       | Bool
otherwise = do
                           Word8
w <- forall a. Storable a => ForeignPtr a -> IO a
peekFp ForeignPtr Word8
f
                           if Word8 -> Bool
k Word8
w
                             then forall a. Storable a => ForeignPtr a -> a -> IO ()
pokeFp ForeignPtr Word8
t Word8
w
                               forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> ForeignPtr Word8 -> ForeignPtr Word8 -> IO (ForeignPtr Word8)
go (ForeignPtr Word8
f forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
1) (ForeignPtr Word8
t forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
1)
                             else ForeignPtr Word8 -> ForeignPtr Word8 -> IO (ForeignPtr Word8)
go (ForeignPtr Word8
f forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
1) ForeignPtr Word8
t
        ForeignPtr Word8
t <- ForeignPtr Word8 -> ForeignPtr Word8 -> IO (ForeignPtr Word8)
go' ForeignPtr Word8
pIn ForeignPtr Word8
pOut
        forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! ForeignPtr Word8
t forall a b. ForeignPtr a -> ForeignPtr b -> Int
`minusForeignPtr` ForeignPtr Word8
pOut -- actual length
{-# INLINE filter #-}

{-
--
-- | /O(n)/ 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)/ 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
p = case (Word8 -> Bool) -> ByteString -> Maybe Int
findIndex Word8 -> Bool
f ByteString
p of
                    Just Int
n -> forall a. a -> Maybe a
Just (ByteString
p ByteString -> Int -> Word8
`unsafeIndex` Int
n)
                    Maybe Int
_      -> forall a. Maybe a
Nothing
{-# INLINE find #-}

-- | /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
f ByteString
s = forall a. IO a -> a
unsafeDupablePerformIO forall a b. (a -> b) -> a -> b
$
    do        ForeignPtr Word8
p <- forall a. Int -> IO (ForeignPtr a)
mallocByteString Int
len
              let end :: ForeignPtr b
end = ForeignPtr Word8
p forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` (Int
len forall a. Num a => a -> a -> a
- Int
1)
              ForeignPtr Word8
mid <- Int
-> ForeignPtr Word8 -> ForeignPtr Word8 -> IO (ForeignPtr Word8)
sep Int
0 ForeignPtr Word8
p forall {b}. ForeignPtr b
end
              forall {b}. Storable b => ForeignPtr b -> ForeignPtr b -> IO ()
rev ForeignPtr Word8
mid forall {b}. ForeignPtr b
end
              let i :: Int
i = ForeignPtr Word8
mid forall a b. ForeignPtr a -> ForeignPtr b -> Int
`minusForeignPtr` ForeignPtr Word8
p
              forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8 -> Int -> ByteString
BS ForeignPtr Word8
p Int
i,
                      ForeignPtr Word8 -> Int -> ByteString
BS (ForeignPtr Word8
p forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
i) (Int
len forall a. Num a => a -> a -> a
- Int
i))
  where
    len :: Int
len  = ByteString -> Int
length ByteString
s
    incr :: ForeignPtr a -> ForeignPtr b
incr = (forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
1)
    decr :: ForeignPtr a -> ForeignPtr b
decr = (forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` (-Int
1))

    sep :: Int
-> ForeignPtr Word8 -> ForeignPtr Word8 -> IO (ForeignPtr Word8)
sep !Int
i !ForeignPtr Word8
p1 !ForeignPtr Word8
p2
       | Int
i forall a. Eq a => a -> a -> Bool
== Int
len  = forall (m :: * -> *) a. Monad m => a -> m a
return ForeignPtr Word8
p1
       | Word8 -> Bool
f Word8
w       = do forall a. Storable a => ForeignPtr a -> a -> IO ()
pokeFp ForeignPtr Word8
p1 Word8
w
                        Int
-> ForeignPtr Word8 -> ForeignPtr Word8 -> IO (ForeignPtr Word8)
sep (Int
i forall a. Num a => a -> a -> a
+ Int
1) (forall {a} {b}. ForeignPtr a -> ForeignPtr b
incr ForeignPtr Word8
p1) ForeignPtr Word8
p2
       | Bool
otherwise = do forall a. Storable a => ForeignPtr a -> a -> IO ()
pokeFp ForeignPtr Word8
p2 Word8
w
                        Int
-> ForeignPtr Word8 -> ForeignPtr Word8 -> IO (ForeignPtr Word8)
sep (Int
i forall a. Num a => a -> a -> a
+ Int
1) ForeignPtr Word8
p1 (forall {a} {b}. ForeignPtr a -> ForeignPtr b
decr ForeignPtr Word8
p2)
      where
        w :: Word8
w = ByteString
s ByteString -> Int -> Word8
`unsafeIndex` Int
i

    rev :: ForeignPtr b -> ForeignPtr b -> IO ()
rev !ForeignPtr b
p1 !ForeignPtr b
p2 -- fixme: surely there are faster ways to do this
      | ForeignPtr b
p1 forall a. Ord a => a -> a -> Bool
>= ForeignPtr b
p2  = forall (m :: * -> *) a. Monad m => a -> m a
return ()
      | Bool
otherwise = do b
a <- forall a. Storable a => ForeignPtr a -> IO a
peekFp ForeignPtr b
p1
                       b
b <- forall a. Storable a => ForeignPtr a -> IO a
peekFp ForeignPtr b
p2
                       forall a. Storable a => ForeignPtr a -> a -> IO ()
pokeFp ForeignPtr b
p1 b
b
                       forall a. Storable a => ForeignPtr a -> a -> IO ()
pokeFp ForeignPtr b
p2 b
a
                       ForeignPtr b -> ForeignPtr b -> IO ()
rev (forall {a} {b}. ForeignPtr a -> ForeignPtr b
incr ForeignPtr b
p1) (forall {a} {b}. ForeignPtr a -> ForeignPtr b
decr ForeignPtr b
p2)

-- --------------------------------------------------------------------
-- Sarching for substrings

-- |/O(n)/ The 'isPrefixOf' function takes two ByteStrings and returns 'True'
-- if the first is a prefix of the second.
isPrefixOf :: ByteString -> ByteString -> Bool
isPrefixOf :: ByteString -> ByteString -> Bool
isPrefixOf (BS ForeignPtr Word8
x1 Int
l1) (BS ForeignPtr Word8
x2 Int
l2)
    | Int
l1 forall a. Eq a => a -> a -> Bool
== Int
0   = Bool
True
    | Int
l2 forall a. Ord a => a -> a -> Bool
< Int
l1   = Bool
False
    | Bool
otherwise = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x1 forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p1 ->
        forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x2 forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p2 -> do
            CInt
i <- Ptr Word8 -> Ptr Word8 -> Int -> IO CInt
memcmp Ptr Word8
p1 Ptr Word8
p2 (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l1)
            forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! CInt
i forall a. Eq a => a -> a -> Bool
== CInt
0

-- | /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 bs1 :: ByteString
bs1@(BS ForeignPtr Word8
_ Int
l1) ByteString
bs2
   | ByteString
bs1 ByteString -> ByteString -> Bool
`isPrefixOf` ByteString
bs2 = forall a. a -> Maybe a
Just (Int -> ByteString -> ByteString
unsafeDrop Int
l1 ByteString
bs2)
   | Bool
otherwise = forall a. Maybe a
Nothing

-- | /O(n)/ The 'isSuffixOf' function takes two ByteStrings and returns 'True'
-- iff the first is a suffix of the second.
--
-- The following holds:
--
-- > isSuffixOf x y == reverse x `isPrefixOf` reverse y
--
-- However, the real implementation uses memcmp to compare the end of the
-- string only, with no reverse required..
isSuffixOf :: ByteString -> ByteString -> Bool
isSuffixOf :: ByteString -> ByteString -> Bool
isSuffixOf (BS ForeignPtr Word8
x1 Int
l1) (BS ForeignPtr Word8
x2 Int
l2)
    | Int
l1 forall a. Eq a => a -> a -> Bool
== Int
0   = Bool
True
    | Int
l2 forall a. Ord a => a -> a -> Bool
< Int
l1   = Bool
False
    | Bool
otherwise = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x1 forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p1 ->
        forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x2 forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p2 -> do
            CInt
i <- Ptr Word8 -> Ptr Word8 -> Int -> IO CInt
memcmp Ptr Word8
p1 (Ptr Word8
p2 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
l2 forall a. Num a => a -> a -> a
- Int
l1)) (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l1)
            forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! CInt
i forall a. Eq a => a -> a -> Bool
== CInt
0

-- | /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 bs1 :: ByteString
bs1@(BS ForeignPtr Word8
_ Int
l1) bs2 :: ByteString
bs2@(BS ForeignPtr Word8
_ Int
l2)
   | ByteString
bs1 ByteString -> ByteString -> Bool
`isSuffixOf` ByteString
bs2 = forall a. a -> Maybe a
Just (Int -> ByteString -> ByteString
unsafeTake (Int
l2 forall a. Num a => a -> a -> a
- Int
l1) ByteString
bs2)
   | Bool
otherwise = forall a. Maybe a
Nothing

-- | Check whether one string is a substring of another.
isInfixOf :: ByteString -> ByteString -> Bool
isInfixOf :: ByteString -> ByteString -> Bool
isInfixOf ByteString
p ByteString
s = ByteString -> Bool
null ByteString
p Bool -> Bool -> Bool
|| Bool -> Bool
not (ByteString -> Bool
null forall a b. (a -> b) -> a -> b
$ forall a b. (a, b) -> b
snd forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString -> (ByteString, ByteString)
breakSubstring ByteString
p ByteString
s)

-- | /O(n)/ Check whether a 'ByteString' represents valid UTF-8.
--
-- @since 0.11.2.0
isValidUtf8 :: ByteString -> Bool
isValidUtf8 :: ByteString -> Bool
isValidUtf8 (BS ForeignPtr Word8
ptr Int
len) = forall a. IO a -> a
accursedUnutterablePerformIO forall a b. (a -> b) -> a -> b
$ forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
ptr forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> do
  -- Use a safe FFI call for large inputs to avoid GC synchronization pauses
  -- in multithreaded contexts.
  -- This specific limit was chosen based on results of a simple benchmark, see:
  -- https://github.com/haskell/bytestring/issues/451#issuecomment-991879338
  -- When changing this function, also consider changing the related function:
  -- Data.ByteString.Short.Internal.isValidUtf8
  CInt
i <- if Int
len forall a. Ord a => a -> a -> Bool
< Int
1000000
     then Ptr Word8 -> CSize -> IO CInt
cIsValidUtf8 Ptr Word8
p (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
     else Ptr Word8 -> CSize -> IO CInt
cIsValidUtf8Safe Ptr Word8
p (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
  forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ CInt
i forall a. Eq a => a -> a -> Bool
/= CInt
0

-- We import bytestring_is_valid_utf8 both unsafe and safe. For small inputs
-- we can use the unsafe version to get a bit more performance, but for large
-- inputs the safe version should be used to avoid GC synchronization pauses
-- in multithreaded contexts.

foreign import ccall unsafe "bytestring_is_valid_utf8" cIsValidUtf8
  :: Ptr Word8 -> CSize -> IO CInt

foreign import ccall safe "bytestring_is_valid_utf8" cIsValidUtf8Safe
  :: Ptr Word8 -> CSize -> IO CInt

-- | Break a string on a substring, returning a pair of the part of the
-- string prior to the match, and the rest of the string.
--
-- The following relationships hold:
--
-- > break (== c) l == breakSubstring (singleton c) l
--
-- For example, to tokenise a string, dropping delimiters:
--
-- > tokenise x y = h : if null t then [] else tokenise x (drop (length x) t)
-- >     where (h,t) = breakSubstring x y
--
-- To skip to the first occurrence of a string:
--
-- > snd (breakSubstring x y)
--
-- To take the parts of a string before a delimiter:
--
-- > fst (breakSubstring x y)
--
-- Note that calling `breakSubstring x` does some preprocessing work, so
-- you should avoid unnecessarily duplicating breakSubstring calls with the same
-- pattern.
--
breakSubstring :: ByteString -- ^ String to search for
               -> ByteString -- ^ String to search in
               -> (ByteString,ByteString) -- ^ Head and tail of string broken at substring
breakSubstring :: ByteString -> ByteString -> (ByteString, ByteString)
breakSubstring ByteString
pat =
  case Int
lp of
    Int
0 -> (ByteString
empty,)
    Int
1 -> Word8 -> ByteString -> (ByteString, ByteString)
breakByte (ByteString -> Word8
unsafeHead ByteString
pat)
    Int
_ -> if Int
lp forall a. Num a => a -> a -> a
* Int
8 forall a. Ord a => a -> a -> Bool
<= forall b. FiniteBits b => b -> Int
finiteBitSize (Word
0 :: Word)
             then ByteString -> (ByteString, ByteString)
shift
             else ByteString -> (ByteString, ByteString)
karpRabin
  where
    unsafeSplitAt :: Int -> ByteString -> (ByteString, ByteString)
unsafeSplitAt Int
i ByteString
s = (Int -> ByteString -> ByteString
unsafeTake Int
i ByteString
s, Int -> ByteString -> ByteString
unsafeDrop Int
i ByteString
s)
    lp :: Int
lp                = ByteString -> Int
length ByteString
pat
    karpRabin :: ByteString -> (ByteString, ByteString)
    karpRabin :: ByteString -> (ByteString, ByteString)
karpRabin ByteString
src
        | ByteString -> Int
length ByteString
src forall a. Ord a => a -> a -> Bool
< Int
lp = (ByteString
src,ByteString
empty)
        | Bool
otherwise = Word32 -> Int -> (ByteString, ByteString)
search (ByteString -> Word32
rollingHash forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString
unsafeTake Int
lp ByteString
src) Int
lp
      where
        k :: Word32
k           = Word32
2891336453 :: Word32
        rollingHash :: ByteString -> Word32
rollingHash = forall a. (a -> Word8 -> a) -> a -> ByteString -> a
foldl' (\Word32
h Word8
b -> Word32
h forall a. Num a => a -> a -> a
* Word32
k forall a. Num a => a -> a -> a
+ forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b) Word32
0
        hp :: Word32
hp          = ByteString -> Word32
rollingHash ByteString
pat
        m :: Word32
m           = Word32
k forall a b. (Num a, Integral b) => a -> b -> a
^ Int
lp
        get :: Int -> Word32
get = forall a b. (Integral a, Num b) => a -> b
fromIntegral forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> Int -> Word8
unsafeIndex ByteString
src
        search :: Word32 -> Int -> (ByteString, ByteString)
search !Word32
hs !Int
i
            | Word32
hp forall a. Eq a => a -> a -> Bool
== Word32
hs Bool -> Bool -> Bool
&& ByteString
pat forall a. Eq a => a -> a -> Bool
== Int -> ByteString -> ByteString
unsafeTake Int
lp ByteString
b = (ByteString, ByteString)
u
            | ByteString -> Int
length ByteString
src forall a. Ord a => a -> a -> Bool
<= Int
i                    = (ByteString
src,ByteString
empty) -- not found
            | Bool
otherwise                          = Word32 -> Int -> (ByteString, ByteString)
search Word32
hs' (Int
i forall a. Num a => a -> a -> a
+ Int
1)
          where
            u :: (ByteString, ByteString)
u@(ByteString
_, ByteString
b) = Int -> ByteString -> (ByteString, ByteString)
unsafeSplitAt (Int
i forall a. Num a => a -> a -> a
- Int
lp) ByteString
src
            hs' :: Word32
hs' = Word32
hs forall a. Num a => a -> a -> a
* Word32
k forall a. Num a => a -> a -> a
+
                  Int -> Word32
get Int
i forall a. Num a => a -> a -> a
-
                  Word32
m forall a. Num a => a -> a -> a
* Int -> Word32
get (Int
i forall a. Num a => a -> a -> a
- Int
lp)
    {-# INLINE karpRabin #-}

    shift :: ByteString -> (ByteString, ByteString)
    shift :: ByteString -> (ByteString, ByteString)
shift !ByteString
src
        | ByteString -> Int
length ByteString
src forall a. Ord a => a -> a -> Bool
< Int
lp = (ByteString
src,ByteString
empty)
        | Bool
otherwise       = Word -> Int -> (ByteString, ByteString)
search (ByteString -> Word
intoWord forall a b. (a -> b) -> a -> b
$ Int -> ByteString -> ByteString
unsafeTake Int
lp ByteString
src) Int
lp
      where
        intoWord :: ByteString -> Word
        intoWord :: ByteString -> Word
intoWord = forall a. (a -> Word8 -> a) -> a -> ByteString -> a
foldl' (\Word
w Word8
b -> (Word
w forall a. Bits a => a -> Int -> a
`shiftL` Int
8) forall a. Bits a => a -> a -> a
.|. forall a b. (Integral a, Num b) => a -> b
fromIntegral Word8
b) Word
0
        wp :: Word
wp   = ByteString -> Word
intoWord ByteString
pat
        mask :: Word
mask = (Word
1 forall a. Bits a => a -> Int -> a
`shiftL` (Int
8 forall a. Num a => a -> a -> a
* Int
lp)) forall a. Num a => a -> a -> a
- Word
1
        search :: Word -> Int -> (ByteString, ByteString)
search !Word
w !Int
i
            | Word
w forall a. Eq a => a -> a -> Bool
== Word
wp         = Int -> ByteString -> (ByteString, ByteString)
unsafeSplitAt (Int
i forall a. Num a => a -> a -> a
- Int
lp) ByteString
src
            | ByteString -> Int
length ByteString
src forall a. Ord a => a -> a -> Bool
<= Int
i = (ByteString
src, ByteString
empty)
            | Bool
otherwise       = Word -> Int -> (ByteString, ByteString)
search Word
w' (Int
i forall a. Num a => a -> a -> a
+ Int
1)
          where
            b :: Word
b  = forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int -> Word8
unsafeIndex ByteString
src Int
i)
            w' :: Word
w' = Word
mask forall a. Bits a => a -> a -> a
.&. ((Word
w forall a. Bits a => a -> Int -> a
`shiftL` Int
8) forall a. Bits a => a -> a -> a
.|. Word
b)
    {-# INLINE shift #-}

-- ---------------------------------------------------------------------
-- 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 ByteString
ps ByteString
qs = case ByteString -> Maybe (Word8, ByteString)
uncons ByteString
ps of
  Maybe (Word8, ByteString)
Nothing         -> []
  Just (Word8
psH, ByteString
psT) -> case ByteString -> Maybe (Word8, ByteString)
uncons ByteString
qs of
    Maybe (Word8, ByteString)
Nothing         -> []
    Just (Word8
qsH, ByteString
qsT) -> (Word8
psH, Word8
qsH) forall a. a -> [a] -> [a]
: ByteString -> ByteString -> [(Word8, Word8)]
zip ByteString
psT ByteString
qsT

-- | '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
f ByteString
ps ByteString
qs = case ByteString -> Maybe (Word8, ByteString)
uncons ByteString
ps of
  Maybe (Word8, ByteString)
Nothing         -> []
  Just (Word8
psH, ByteString
psT) -> case ByteString -> Maybe (Word8, ByteString)
uncons ByteString
qs of
    Maybe (Word8, ByteString)
Nothing         -> []
    Just (Word8
qsH, ByteString
qsT) -> Word8 -> Word8 -> a
f Word8
psH Word8
qsH forall a. a -> [a] -> [a]
: forall a. (Word8 -> Word8 -> a) -> ByteString -> ByteString -> [a]
zipWith Word8 -> Word8 -> a
f ByteString
psT ByteString
qsT
{-# NOINLINE [1] zipWith #-}

-- | 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
f (BS ForeignPtr Word8
a Int
l) (BS ForeignPtr Word8
b Int
m) = forall a. IO a -> a
unsafeDupablePerformIO forall a b. (a -> b) -> a -> b
$
    Int -> (ForeignPtr Word8 -> IO ()) -> IO ByteString
createFp Int
len forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> ForeignPtr Word8 -> ForeignPtr Word8 -> IO ()
go ForeignPtr Word8
a ForeignPtr Word8
b
  where
    go :: ForeignPtr Word8 -> ForeignPtr Word8 -> ForeignPtr Word8 -> IO ()
go ForeignPtr Word8
p1 ForeignPtr Word8
p2 = Int -> ForeignPtr Word8 -> IO ()
zipWith_ Int
0
      where
        zipWith_ :: Int -> ForeignPtr Word8 -> IO ()
        zipWith_ :: Int -> ForeignPtr Word8 -> IO ()
zipWith_ !Int
n !ForeignPtr Word8
r
           | Int
n forall a. Ord a => a -> a -> Bool
>= Int
len = forall (m :: * -> *) a. Monad m => a -> m a
return ()
           | Bool
otherwise = do
                Word8
x <- forall a. Storable a => ForeignPtr a -> Int -> IO a
peekFpByteOff ForeignPtr Word8
p1 Int
n
                Word8
y <- forall a. Storable a => ForeignPtr a -> Int -> IO a
peekFpByteOff ForeignPtr Word8
p2 Int
n
                forall a b. Storable a => ForeignPtr b -> Int -> a -> IO ()
pokeFpByteOff ForeignPtr Word8
r Int
n (Word8 -> Word8 -> Word8
f Word8
x Word8
y)
                Int -> ForeignPtr Word8 -> IO ()
zipWith_ (Int
nforall a. Num a => a -> a -> a
+Int
1) ForeignPtr Word8
r

    len :: Int
len = forall a. Ord a => a -> a -> a
min Int
l Int
m
{-# INLINE packZipWith #-}

{-# RULES
"ByteString specialise zipWith" forall (f :: Word8 -> Word8 -> Word8) p q .
    zipWith f p q = unpack (packZipWith f p q)
  #-}

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

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

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

-- | /O(n)/ Returns all initial segments of the given 'ByteString', shortest first.
--
-- @since 0.11.4.0
initsNE :: ByteString -> NonEmpty ByteString
-- see Note [Avoid NonEmpty combinators]
initsNE :: ByteString -> NonEmpty ByteString
initsNE (BS ForeignPtr Word8
x Int
len) = ByteString
empty forall a. a -> [a] -> NonEmpty a
:| [ForeignPtr Word8 -> Int -> ByteString
BS ForeignPtr Word8
x Int
n | Int
n <- [Int
1..Int
len]]

-- | /O(n)/ Returns all final segments of the given 'ByteString', longest first.
tails :: ByteString -> [ByteString]
-- see Note [Avoid NonEmpty combinators]
tails :: ByteString -> [ByteString]
tails ByteString
bs = forall a. NonEmpty a -> [a]
NE.toList 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]
tailsNE :: ByteString -> NonEmpty ByteString
tailsNE ByteString
p | ByteString -> Bool
null ByteString
p    = ByteString
empty forall a. a -> [a] -> NonEmpty a
:| []
          | Bool
otherwise = ByteString
p forall a. a -> [a] -> NonEmpty a
:| ByteString -> [ByteString]
tails (ByteString -> ByteString
unsafeTail ByteString
p)

-- less efficent spacewise: tails (BS x l) = [BS (plusForeignPtr x n) (l-n) | n <- [0..l]]

{-
Note [Avoid NonEmpty combinators]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~

As of base-4.17, most of the NonEmpty API is surprisingly lazy.
Using it without forcing the arguments yourself is just begging GHC
to make your code waste time allocating useless selector thunks.
This may change in the future. See also this CLC issue:
  https://github.com/haskell/core-libraries-committee/issues/107
But until then, "refactor" with care!
-}



-- ---------------------------------------------------------------------
-- ** Ordered 'ByteString's

-- | /O(n)/ Sort a ByteString efficiently, using counting sort.
sort :: ByteString -> ByteString
sort :: ByteString -> ByteString
sort (BS ForeignPtr Word8
input Int
l)
  -- qsort outperforms counting sort for small arrays
  | Int
l forall a. Ord a => a -> a -> Bool
<= Int
20 = Int -> (ForeignPtr Word8 -> IO ()) -> ByteString
unsafeCreateFp Int
l forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
destFP -> do
    ForeignPtr Word8 -> ForeignPtr Word8 -> Int -> IO ()
memcpyFp ForeignPtr Word8
destFP ForeignPtr Word8
input Int
l
    forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
destFP forall a b. (a -> b) -> a -> b
$ \Ptr Word8
dest -> Ptr Word8 -> CSize -> IO ()
c_sort Ptr Word8
dest (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l)
  | Bool
otherwise = Int -> (ForeignPtr Word8 -> IO ()) -> ByteString
unsafeCreateFp Int
l forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
p -> forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
256 forall a b. (a -> b) -> a -> b
$ \Ptr CSize
arr -> do

    Ptr Word8
_ <- Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
memset (forall a b. Ptr a -> Ptr b
castPtr Ptr CSize
arr) Word8
0 (CSize
256 forall a. Num a => a -> a -> a
* forall a b. (Integral a, Num b) => a -> b
fromIntegral (forall a. Storable a => a -> Int
sizeOf (forall a. HasCallStack => a
undefined :: CSize)))
    forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
input (\Ptr Word8
x -> Ptr CSize -> Ptr Word8 -> Int -> IO ()
countOccurrences Ptr CSize
arr Ptr Word8
x Int
l)

    let go :: Int -> Ptr Word8 -> IO ()
go Int
256 !Ptr Word8
_   = forall (m :: * -> *) a. Monad m => a -> m a
return ()
        go Int
i   !Ptr Word8
ptr = do CSize
n <- forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr CSize
arr Int
i
                         forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CSize
n forall a. Eq a => a -> a -> Bool
/= CSize
0) forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
memset Ptr Word8
ptr (forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) CSize
n
                         Int -> Ptr Word8 -> IO ()
go (Int
i forall a. Num a => a -> a -> a
+ Int
1) (Ptr Word8
ptr forall a b. Ptr a -> Int -> Ptr b
`plusPtr` forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
n)
    forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
p (Int -> Ptr Word8 -> IO ()
go Int
0)
  where
    -- Count the number of occurrences of each byte.
    -- Used by 'sort'
    countOccurrences :: Ptr CSize -> Ptr Word8 -> Int -> IO ()
    countOccurrences :: Ptr CSize -> Ptr Word8 -> Int -> IO ()
countOccurrences !Ptr CSize
counts !Ptr Word8
str !Int
len = Int -> IO ()
go Int
0
     where
        go :: Int -> IO ()
go !Int
i | Int
i forall a. Eq a => a -> a -> Bool
== Int
len    = forall (m :: * -> *) a. Monad m => a -> m a
return ()
              | Bool
otherwise = do Int
k <- forall a b. (Integral a, Num b) => a -> b
fromIntegral forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
str Int
i
                               CSize
x <- forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr CSize
counts Int
k
                               forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr CSize
counts Int
k (CSize
x forall a. Num a => a -> a -> a
+ CSize
1)
                               Int -> IO ()
go (Int
i forall a. Num a => a -> a -> a
+ Int
1)


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

-- | /O(n) construction/ Use a @ByteString@ with a function requiring a
-- null-terminated @CString@.  The @CString@ is a copy and will be freed
-- automatically; it must not be stored or used after the
-- subcomputation finishes.
useAsCString :: ByteString -> (CString -> IO a) -> IO a
useAsCString :: forall a. ByteString -> (CString -> IO a) -> IO a
useAsCString (BS ForeignPtr Word8
fp Int
l) CString -> IO a
action =
  forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Int
lforall a. Num a => a -> a -> a
+Int
1) forall a b. (a -> b) -> a -> b
$ \Ptr Word8
buf -> do
    forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Ptr Word8 -> Ptr Word8 -> Int -> IO ()
memcpy Ptr Word8
buf Ptr Word8
p Int
l
    forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
buf Int
l (Word8
0::Word8)
    CString -> IO a
action (forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
buf)

-- | /O(n) construction/ Use a @ByteString@ with a function requiring a @CStringLen@.
-- As for @useAsCString@ this function makes a copy of the original @ByteString@.
-- It must not be stored or used after the subcomputation finishes.
useAsCStringLen :: ByteString -> (CStringLen -> IO a) -> IO a
useAsCStringLen :: forall a. ByteString -> (CStringLen -> IO a) -> IO a
useAsCStringLen p :: ByteString
p@(BS ForeignPtr Word8
_ Int
l) CStringLen -> IO a
f = forall a. ByteString -> (CString -> IO a) -> IO a
useAsCString ByteString
p forall a b. (a -> b) -> a -> b
$ \CString
cstr -> CStringLen -> IO a
f (CString
cstr,Int
l)

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

-- | /O(n)./ Construct a new @ByteString@ from a @CString@. The
-- resulting @ByteString@ is an immutable copy of the original
-- @CString@, and is managed on the Haskell heap. The original
-- @CString@ must be null terminated.
packCString :: CString -> IO ByteString
packCString :: CString -> IO ByteString
packCString CString
cstr = do
    CSize
len <- CString -> IO CSize
c_strlen CString
cstr
    CStringLen -> IO ByteString
packCStringLen (CString
cstr, forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
len)

-- | /O(n)./ Construct a new @ByteString@ from a @CStringLen@. The
-- resulting @ByteString@ is an immutable copy of the original @CStringLen@.
-- The @ByteString@ is a normal Haskell value and will be managed on the
-- Haskell heap.
packCStringLen :: CStringLen -> IO ByteString
packCStringLen :: CStringLen -> IO ByteString
packCStringLen (CString
cstr, Int
len) | Int
len forall a. Ord a => a -> a -> Bool
>= Int
0 = Int -> (ForeignPtr Word8 -> IO ()) -> IO ByteString
createFp Int
len forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
fp ->
    forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Ptr Word8 -> Ptr Word8 -> Int -> IO ()
memcpy Ptr Word8
p (forall a b. Ptr a -> Ptr b
castPtr CString
cstr) Int
len
packCStringLen (CString
_, Int
len) =
    forall a. HasCallStack => FilePath -> FilePath -> IO a
moduleErrorIO FilePath
"packCStringLen" (FilePath
"negative length: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> FilePath
show Int
len)

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

-- | /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 (BS ForeignPtr Word8
x Int
l) = Int -> (ForeignPtr Word8 -> IO ()) -> ByteString
unsafeCreateFp Int
l forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
p -> ForeignPtr Word8 -> ForeignPtr Word8 -> Int -> IO ()
memcpyFp ForeignPtr Word8
p ForeignPtr Word8
x Int
l

-- ---------------------------------------------------------------------
-- Line IO

-- | Read a line from stdin.
getLine :: IO ByteString
getLine :: IO ByteString
getLine = Handle -> IO ByteString
hGetLine Handle
stdin

-- | Read a line from a handle

hGetLine :: Handle -> IO ByteString
hGetLine :: Handle -> IO ByteString
hGetLine Handle
h =
  forall a. FilePath -> Handle -> (Handle__ -> IO a) -> IO a
wantReadableHandle_ FilePath
"Data.ByteString.hGetLine" Handle
h forall a b. (a -> b) -> a -> b
$
    \ h_ :: Handle__
h_@Handle__{IORef (Buffer Word8)
haByteBuffer :: Handle__ -> IORef (Buffer Word8)
haByteBuffer :: IORef (Buffer Word8)
haByteBuffer} -> do
      Handle__ -> IO ()
flushCharReadBuffer Handle__
h_
      Buffer Word8
buf <- forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
      if forall e. Buffer e -> Bool
isEmptyBuffer Buffer Word8
buf
         then Handle__ -> Buffer Word8 -> Int -> [ByteString] -> IO ByteString
fill Handle__
h_ Buffer Word8
buf Int
0 []
         else Handle__ -> Buffer Word8 -> Int -> [ByteString] -> IO ByteString
haveBuf Handle__
h_ Buffer Word8
buf Int
0 []
 where

  fill :: Handle__ -> Buffer Word8 -> Int -> [ByteString] -> IO ByteString
fill h_ :: Handle__
h_@Handle__{IORef (Buffer Word8)
haByteBuffer :: IORef (Buffer Word8)
haByteBuffer :: Handle__ -> IORef (Buffer Word8)
haByteBuffer,dev
haDevice :: ()
haDevice :: dev
haDevice} Buffer Word8
buf !Int
len [ByteString]
xss = do
    (Int
r,Buffer Word8
buf') <- forall dev.
BufferedIO dev =>
dev -> Buffer Word8 -> IO (Int, Buffer Word8)
Buffered.fillReadBuffer dev
haDevice Buffer Word8
buf
    if Int
r forall a. Eq a => a -> a -> Bool
== Int
0
       then do forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
buf{ bufR :: Int
bufR=Int
0, bufL :: Int
bufL=Int
0 }
               if Int
len forall a. Ord a => a -> a -> Bool
> Int
0
                  then Int -> [ByteString] -> IO ByteString
mkBigPS Int
len [ByteString]
xss
                  else forall a. IO a
ioe_EOF
       else Handle__ -> Buffer Word8 -> Int -> [ByteString] -> IO ByteString
haveBuf Handle__
h_ Buffer Word8
buf' Int
len [ByteString]
xss

  haveBuf :: Handle__ -> Buffer Word8 -> Int -> [ByteString] -> IO ByteString
haveBuf h_ :: Handle__
h_@Handle__{IORef (Buffer Word8)
haByteBuffer :: IORef (Buffer Word8)
haByteBuffer :: Handle__ -> IORef (Buffer Word8)
haByteBuffer}
          buf :: Buffer Word8
buf@Buffer{ bufRaw :: forall e. Buffer e -> RawBuffer e
bufRaw=ForeignPtr Word8
raw, bufR :: forall e. Buffer e -> Int
bufR=Int
w, bufL :: forall e. Buffer e -> Int
bufL=Int
r }
          Int
len [ByteString]
xss =
    do
        Int
off <- Int -> Int -> ForeignPtr Word8 -> IO Int
findEOL Int
r Int
w ForeignPtr Word8
raw
        let new_len :: Int
new_len = Int
len forall a. Num a => a -> a -> a
+ Int
off forall a. Num a => a -> a -> a
- Int
r
        ByteString
xs <- ForeignPtr Word8 -> Int -> Int -> IO ByteString
mkPS ForeignPtr Word8
raw Int
r Int
off

      -- if eol == True, then off is the offset of the '\n'
      -- otherwise off == w and the buffer is now empty.
        if Int
off forall a. Eq a => a -> a -> Bool
/= Int
w
            then do if Int
w forall a. Eq a => a -> a -> Bool
== Int
off forall a. Num a => a -> a -> a
+ Int
1
                            then forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
buf{ bufL :: Int
bufL=Int
0, bufR :: Int
bufR=Int
0 }
                            else forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
buf{ bufL :: Int
bufL = Int
off forall a. Num a => a -> a -> a
+ Int
1 }
                    Int -> [ByteString] -> IO ByteString
mkBigPS Int
new_len (ByteString
xsforall a. a -> [a] -> [a]
:[ByteString]
xss)
            else Handle__ -> Buffer Word8 -> Int -> [ByteString] -> IO ByteString
fill Handle__
h_ Buffer Word8
buf{ bufL :: Int
bufL=Int
0, bufR :: Int
bufR=Int
0 } Int
new_len (ByteString
xsforall a. a -> [a] -> [a]
:[ByteString]
xss)

  -- find the end-of-line character, if there is one
  findEOL :: Int -> Int -> ForeignPtr Word8 -> IO Int
findEOL Int
r Int
w ForeignPtr Word8
raw
        | Int
r forall a. Eq a => a -> a -> Bool
== Int
w = forall (m :: * -> *) a. Monad m => a -> m a
return Int
w
        | Bool
otherwise =  do
            Word8
c <- ForeignPtr Word8 -> Int -> IO Word8
readWord8Buf ForeignPtr Word8
raw Int
r
            if Word8
c forall a. Eq a => a -> a -> Bool
== forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
'\n')
                then forall (m :: * -> *) a. Monad m => a -> m a
return Int
r -- NB. not r+1: don't include the '\n'
                else Int -> Int -> ForeignPtr Word8 -> IO Int
findEOL (Int
rforall a. Num a => a -> a -> a
+Int
1) Int
w ForeignPtr Word8
raw

mkPS :: RawBuffer Word8 -> Int -> Int -> IO ByteString
mkPS :: ForeignPtr Word8 -> Int -> Int -> IO ByteString
mkPS ForeignPtr Word8
buf Int
start Int
end =
 Int -> (ForeignPtr Word8 -> IO ()) -> IO ByteString
createFp Int
len forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
fp -> ForeignPtr Word8 -> ForeignPtr Word8 -> Int -> IO ()
memcpyFp ForeignPtr Word8
fp (ForeignPtr Word8
buf forall a b. ForeignPtr a -> Int -> ForeignPtr b
`plusForeignPtr` Int
start) Int
len
 where
   len :: Int
len = Int
end forall a. Num a => a -> a -> a
- Int
start

mkBigPS :: Int -> [ByteString] -> IO ByteString
mkBigPS :: Int -> [ByteString] -> IO ByteString
mkBigPS Int
_ [ByteString
ps] = forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
ps
mkBigPS Int
_ [ByteString]
pss = forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! [ByteString] -> ByteString
concat (forall a. [a] -> [a]
P.reverse [ByteString]
pss)

-- ---------------------------------------------------------------------
-- Block IO

-- | Outputs a 'ByteString' to the specified 'Handle'.
hPut :: Handle -> ByteString -> IO ()
hPut :: Handle -> ByteString -> IO ()
hPut Handle
_ (BS ForeignPtr Word8
_  Int
0) = forall (m :: * -> *) a. Monad m => a -> m a
return ()
hPut Handle
h (BS ForeignPtr Word8
ps Int
l) = forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
ps forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p-> forall a. Handle -> Ptr a -> Int -> IO ()
hPutBuf Handle
h Ptr Word8
p Int
l

-- | 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
h bs :: ByteString
bs@(BS ForeignPtr Word8
ps Int
l) = do
  Int
bytesWritten <- forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
ps forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p-> forall a. Handle -> Ptr a -> Int -> IO Int
hPutBufNonBlocking Handle
h Ptr Word8
p Int
l
  forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! Int -> ByteString -> ByteString
drop Int
bytesWritten ByteString
bs

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

-- | Write a ByteString to 'stdout'.
putStr :: ByteString -> IO ()
putStr :: ByteString -> IO ()
putStr = Handle -> ByteString -> IO ()
hPut Handle
stdout

------------------------------------------------------------------------
-- Low level IO

-- | Read a 'ByteString' directly from the specified 'Handle'.  This
-- is far more efficient than reading the characters into a 'String'
-- and then using 'pack'. First argument is the Handle to read from,
-- and the second is the number of bytes to read. It returns the bytes
-- read, up to n, or 'empty' if EOF has been reached.
--
-- 'hGet' is implemented in terms of 'hGetBuf'.
--
-- If the handle is a pipe or socket, and the writing end
-- is closed, 'hGet' will behave as if EOF was reached.
--
hGet :: Handle -> Int -> IO ByteString
hGet :: Handle -> Int -> IO ByteString
hGet Handle
h Int
i
    | Int
i forall a. Ord a => a -> a -> Bool
>  Int
0    = Int -> (ForeignPtr Word8 -> IO Int) -> IO ByteString
createFpAndTrim Int
i forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
fp ->
        forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> forall a. Handle -> Ptr a -> Int -> IO Int
hGetBuf Handle
h Ptr Word8
p Int
i
    | Int
i forall a. Eq a => a -> a -> Bool
== Int
0    = forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
empty
    | Bool
otherwise = forall a. Handle -> FilePath -> Int -> IO a
illegalBufferSize Handle
h FilePath
"hGet" Int
i

-- | 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 Handle
h Int
i
    | Int
i forall a. Ord a => a -> a -> Bool
>  Int
0    = Int -> (ForeignPtr Word8 -> IO Int) -> IO ByteString
createFpAndTrim Int
i forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
fp ->
        forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> forall a. Handle -> Ptr a -> Int -> IO Int
hGetBufNonBlocking Handle
h Ptr Word8
p Int
i
    | Int
i forall a. Eq a => a -> a -> Bool
== Int
0    = forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
empty
    | Bool
otherwise = forall a. Handle -> FilePath -> Int -> IO a
illegalBufferSize Handle
h FilePath
"hGetNonBlocking" Int
i

-- | Like 'hGet', except that a shorter 'ByteString' may be returned
-- if there are not enough bytes immediately available to satisfy the
-- whole request.  'hGetSome' only blocks if there is no data
-- available, and EOF has not yet been reached.
--
hGetSome :: Handle -> Int -> IO ByteString
hGetSome :: Handle -> Int -> IO ByteString
hGetSome Handle
hh Int
i
    | Int
i forall a. Ord a => a -> a -> Bool
>  Int
0    = Int -> (ForeignPtr Word8 -> IO Int) -> IO ByteString
createFpAndTrim Int
i forall a b. (a -> b) -> a -> b
$ \ForeignPtr Word8
fp ->
        forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> forall a. Handle -> Ptr a -> Int -> IO Int
hGetBufSome Handle
hh Ptr Word8
p Int
i
    | Int
i forall a. Eq a => a -> a -> Bool
== Int
0    = forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
empty
    | Bool
otherwise = forall a. Handle -> FilePath -> Int -> IO a
illegalBufferSize Handle
hh FilePath
"hGetSome" Int
i

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


-- | Read a handle's entire contents strictly into a 'ByteString'.
--
-- This function reads chunks at a time, increasing the chunk size on each
-- read. The final string is then reallocated to the appropriate size. For
-- files > half of available memory, this may lead to memory exhaustion.
-- Consider using 'readFile' in this case.
--
-- The Handle is closed once the contents have been read,
-- or if an exception is thrown.
--
hGetContents :: Handle -> IO ByteString
hGetContents :: Handle -> IO ByteString
hGetContents Handle
hnd = do
    ByteString
bs <- Handle -> Int -> Int -> IO ByteString
hGetContentsSizeHint Handle
hnd Int
1024 Int
2048
            forall a b. IO a -> IO b -> IO a
`finally` Handle -> IO ()
hClose Handle
hnd
    -- don't waste too much space for small files:
    if ByteString -> Int
length ByteString
bs forall a. Ord a => a -> a -> Bool
< Int
900
      then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! ByteString -> ByteString
copy ByteString
bs
      else forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
bs

hGetContentsSizeHint :: Handle
                     -> Int -- ^ first read size
                     -> Int -- ^ initial buffer size increment
                     -> IO ByteString
hGetContentsSizeHint :: Handle -> Int -> Int -> IO ByteString
hGetContentsSizeHint Handle
hnd =
    [ByteString] -> Int -> Int -> IO ByteString
readChunks []
  where
    readChunks :: [ByteString] -> Int -> Int -> IO ByteString
readChunks [ByteString]
chunks Int
sz Int
sz' = do
      ForeignPtr Word8
fp        <- forall a. Int -> IO (ForeignPtr a)
mallocByteString Int
sz
      Int
readcount <- forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp forall a b. (a -> b) -> a -> b
$ \Ptr Word8
buf -> forall a. Handle -> Ptr a -> Int -> IO Int
hGetBuf Handle
hnd Ptr Word8
buf Int
sz
      let chunk :: ByteString
chunk = ForeignPtr Word8 -> Int -> ByteString
BS ForeignPtr Word8
fp Int
readcount
      -- We rely on the hGetBuf behaviour (not hGetBufSome) where it reads up
      -- to the size we ask for, or EOF. So short reads indicate EOF.
      if Int
readcount forall a. Ord a => a -> a -> Bool
< Int
sz Bool -> Bool -> Bool
&& Int
sz forall a. Ord a => a -> a -> Bool
> Int
0
        then forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$! [ByteString] -> ByteString
concat (forall a. [a] -> [a]
P.reverse (ByteString
chunk forall a. a -> [a] -> [a]
: [ByteString]
chunks))
        else [ByteString] -> Int -> Int -> IO ByteString
readChunks (ByteString
chunk forall a. a -> [a] -> [a]
: [ByteString]
chunks) Int
sz' ((Int
szforall a. Num a => a -> a -> a
+Int
sz') forall a. Ord a => a -> a -> a
`min` Int
32752)
             -- we grow the buffer sizes, but not too huge
             -- we concatenate in the end anyway

-- | getContents. Read stdin strictly. Equivalent to hGetContents stdin
-- The 'Handle' is closed after the contents have been read.
--
getContents :: IO ByteString
getContents :: IO ByteString
getContents = Handle -> IO ByteString
hGetContents Handle
stdin

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

-- | Read an entire file strictly into a 'ByteString'.
--
readFile :: FilePath -> IO ByteString
readFile :: FilePath -> IO ByteString
readFile FilePath
f =
    forall r. FilePath -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile FilePath
f IOMode
ReadMode forall a b. (a -> b) -> a -> b
$ \Handle
h -> do
      -- hFileSize fails if file is not regular file (like
      -- /dev/null). Catch exception and try reading anyway.
      Integer
filesz <- forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch (Handle -> IO Integer
hFileSize Handle
h) IOException -> IO Integer
useZeroIfNotRegularFile
      let readsz :: Int
readsz = (forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
filesz forall a. Ord a => a -> a -> a
`max` Int
0) forall a. Num a => a -> a -> a
+ Int
1
      Handle -> Int -> Int -> IO ByteString
hGetContentsSizeHint Handle
h Int
readsz (Int
readsz forall a. Ord a => a -> a -> a
`max` Int
255)
      -- Our initial size is one bigger than the file size so that in the
      -- typical case we will read the whole file in one go and not have
      -- to allocate any more chunks. We'll still do the right thing if the
      -- file size is 0 or is changed before we do the read.
  where
    useZeroIfNotRegularFile :: IOException -> IO Integer
    useZeroIfNotRegularFile :: IOException -> IO Integer
useZeroIfNotRegularFile IOException
_ = forall (m :: * -> *) a. Monad m => a -> m a
return Integer
0

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

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

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

-- ---------------------------------------------------------------------
-- 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 => FilePath -> a
errorEmptyList FilePath
fun = forall a. HasCallStack => FilePath -> FilePath -> a
moduleError FilePath
fun FilePath
"empty ByteString"
{-# NOINLINE errorEmptyList #-}

moduleError :: HasCallStack => String -> String -> a
moduleError :: forall a. HasCallStack => FilePath -> FilePath -> a
moduleError FilePath
fun FilePath
msg = forall a. HasCallStack => FilePath -> a
error (FilePath -> ShowS
moduleErrorMsg FilePath
fun FilePath
msg)
{-# NOINLINE moduleError #-}

moduleErrorIO :: HasCallStack => String -> String -> IO a
moduleErrorIO :: forall a. HasCallStack => FilePath -> FilePath -> IO a
moduleErrorIO FilePath
fun FilePath
msg = forall e a. Exception e => e -> IO a
throwIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. FilePath -> IOException
userError forall a b. (a -> b) -> a -> b
$ FilePath -> ShowS
moduleErrorMsg FilePath
fun FilePath
msg
{-# NOINLINE moduleErrorIO #-}

moduleErrorMsg :: String -> String -> String
moduleErrorMsg :: FilePath -> ShowS
moduleErrorMsg FilePath
fun FilePath
msg = FilePath
"Data.ByteString." forall a. [a] -> [a] -> [a]
++ FilePath
fun forall a. [a] -> [a] -> [a]
++ Char
':'forall a. a -> [a] -> [a]
:Char
' 'forall a. a -> [a] -> [a]
:FilePath
msg

-- Find from the end of the string using predicate
findFromEndUntil :: (Word8 -> Bool) -> ByteString -> Int
findFromEndUntil :: (Word8 -> Bool) -> ByteString -> Int
findFromEndUntil Word8 -> Bool
f ps :: ByteString
ps@(BS ForeignPtr Word8
_ Int
l) = case ByteString -> Maybe (ByteString, Word8)
unsnoc ByteString
ps of
  Maybe (ByteString, Word8)
Nothing     -> Int
0
  Just (ByteString
b, Word8
c) ->
    if Word8 -> Bool
f Word8
c
      then Int
l
      else (Word8 -> Bool) -> ByteString -> Int
findFromEndUntil Word8 -> Bool
f ByteString
b