{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash, UnboxedTuples,
            NamedFieldPuns, BangPatterns #-}
{-# OPTIONS_HADDOCK prune #-}
#if __GLASGOW_HASKELL__ >= 701
{-# LANGUAGE Trustworthy #-}
#endif

-- |
-- 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 (

        -- * The @ByteString@ type
        ByteString,             -- abstract, instances: Eq, Ord, Show, Read, Data, Typeable, Monoid

        -- * Introducing and eliminating 'ByteString's
        empty,                  -- :: ByteString
        singleton,              -- :: Word8   -> ByteString
        pack,                   -- :: [Word8] -> ByteString
        unpack,                 -- :: ByteString -> [Word8]

        -- * Basic interface
        cons,                   -- :: Word8 -> ByteString -> ByteString
        snoc,                   -- :: ByteString -> Word8 -> ByteString
        append,                 -- :: ByteString -> ByteString -> ByteString
        head,                   -- :: ByteString -> Word8
        uncons,                 -- :: ByteString -> Maybe (Word8, ByteString)
        unsnoc,                 -- :: ByteString -> Maybe (ByteString, Word8)
        last,                   -- :: ByteString -> Word8
        tail,                   -- :: ByteString -> ByteString
        init,                   -- :: ByteString -> ByteString
        null,                   -- :: ByteString -> Bool
        length,                 -- :: ByteString -> Int

        -- * Transforming ByteStrings
        map,                    -- :: (Word8 -> Word8) -> ByteString -> ByteString
        reverse,                -- :: ByteString -> ByteString
        intersperse,            -- :: Word8 -> ByteString -> ByteString
        intercalate,            -- :: ByteString -> [ByteString] -> ByteString
        transpose,              -- :: [ByteString] -> [ByteString]

        -- * Reducing 'ByteString's (folds)
        foldl,                  -- :: (a -> Word8 -> a) -> a -> ByteString -> a
        foldl',                 -- :: (a -> Word8 -> a) -> a -> ByteString -> a
        foldl1,                 -- :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8
        foldl1',                -- :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8

        foldr,                  -- :: (Word8 -> a -> a) -> a -> ByteString -> a
        foldr',                 -- :: (Word8 -> a -> a) -> a -> ByteString -> a
        foldr1,                 -- :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8
        foldr1',                -- :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8

        -- ** Special folds
        concat,                 -- :: [ByteString] -> ByteString
        concatMap,              -- :: (Word8 -> ByteString) -> ByteString -> ByteString
        any,                    -- :: (Word8 -> Bool) -> ByteString -> Bool
        all,                    -- :: (Word8 -> Bool) -> ByteString -> Bool
        maximum,                -- :: ByteString -> Word8
        minimum,                -- :: ByteString -> Word8

        -- * Building ByteStrings
        -- ** Scans
        scanl,                  -- :: (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
        scanl1,                 -- :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString
        scanr,                  -- :: (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
        scanr1,                 -- :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString

        -- ** Accumulating maps
        mapAccumL,              -- :: (acc -> Word8 -> (acc, Word8)) -> acc -> ByteString -> (acc, ByteString)
        mapAccumR,              -- :: (acc -> Word8 -> (acc, Word8)) -> acc -> ByteString -> (acc, ByteString)

        -- ** Generating and unfolding ByteStrings
        replicate,              -- :: Int -> Word8 -> ByteString
        unfoldr,                -- :: (a -> Maybe (Word8, a)) -> a -> ByteString
        unfoldrN,               -- :: Int -> (a -> Maybe (Word8, a)) -> a -> (ByteString, Maybe a)

        -- * Substrings

        -- ** Breaking strings
        take,                   -- :: Int -> ByteString -> ByteString
        drop,                   -- :: Int -> ByteString -> ByteString
        splitAt,                -- :: Int -> ByteString -> (ByteString, ByteString)
        takeWhile,              -- :: (Word8 -> Bool) -> ByteString -> ByteString
        takeWhileEnd,           -- :: (Word8 -> Bool) -> ByteString -> ByteString
        dropWhile,              -- :: (Word8 -> Bool) -> ByteString -> ByteString
        dropWhileEnd,           -- :: (Word8 -> Bool) -> ByteString -> ByteString
        span,                   -- :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
        spanEnd,                -- :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
        break,                  -- :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
        breakEnd,               -- :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
        group,                  -- :: ByteString -> [ByteString]
        groupBy,                -- :: (Word8 -> Word8 -> Bool) -> ByteString -> [ByteString]
        inits,                  -- :: ByteString -> [ByteString]
        tails,                  -- :: ByteString -> [ByteString]
        stripPrefix,            -- :: ByteString -> ByteString -> Maybe ByteString
        stripSuffix,            -- :: ByteString -> ByteString -> Maybe ByteString

        -- ** Breaking into many substrings
        split,                  -- :: Word8 -> ByteString -> [ByteString]
        splitWith,              -- :: (Word8 -> Bool) -> ByteString -> [ByteString]

        -- * Predicates
        isPrefixOf,             -- :: ByteString -> ByteString -> Bool
        isSuffixOf,             -- :: ByteString -> ByteString -> Bool
        isInfixOf,              -- :: ByteString -> ByteString -> Bool

        -- ** Search for arbitrary substrings
        breakSubstring,         -- :: ByteString -> ByteString -> (ByteString,ByteString)
        findSubstring,          -- :: ByteString -> ByteString -> Maybe Int
        findSubstrings,         -- :: ByteString -> ByteString -> [Int]

        -- * Searching ByteStrings

        -- ** Searching by equality
        elem,                   -- :: Word8 -> ByteString -> Bool
        notElem,                -- :: Word8 -> ByteString -> Bool

        -- ** Searching with a predicate
        find,                   -- :: (Word8 -> Bool) -> ByteString -> Maybe Word8
        filter,                 -- :: (Word8 -> Bool) -> ByteString -> ByteString
        partition,              -- :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)

        -- * Indexing ByteStrings
        index,                  -- :: ByteString -> Int -> Word8
        elemIndex,              -- :: Word8 -> ByteString -> Maybe Int
        elemIndices,            -- :: Word8 -> ByteString -> [Int]
        elemIndexEnd,           -- :: Word8 -> ByteString -> Maybe Int
        findIndex,              -- :: (Word8 -> Bool) -> ByteString -> Maybe Int
        findIndices,            -- :: (Word8 -> Bool) -> ByteString -> [Int]
        findIndexEnd,           -- :: (Word8 -> Bool) -> ByteString -> Maybe Int
        count,                  -- :: Word8 -> ByteString -> Int

        -- * Zipping and unzipping ByteStrings
        zip,                    -- :: ByteString -> ByteString -> [(Word8,Word8)]
        zipWith,                -- :: (Word8 -> Word8 -> c) -> ByteString -> ByteString -> [c]
        unzip,                  -- :: [(Word8,Word8)] -> (ByteString,ByteString)

        -- * Ordered ByteStrings
        sort,                   -- :: ByteString -> ByteString

        -- * Low level conversions
        -- ** Copying ByteStrings
        copy,                   -- :: ByteString -> ByteString

        -- ** Packing 'CString's and pointers
        packCString,            -- :: CString -> IO ByteString
        packCStringLen,         -- :: CStringLen -> IO ByteString

        -- ** Using ByteStrings as 'CString's
        useAsCString,           -- :: ByteString -> (CString    -> IO a) -> IO a
        useAsCStringLen,        -- :: ByteString -> (CStringLen -> IO a) -> IO a

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

        -- ** Standard input and output
        getLine,                -- :: IO ByteString
        getContents,            -- :: IO ByteString
        putStr,                 -- :: ByteString -> IO ()
        putStrLn,               -- :: ByteString -> IO ()
        interact,               -- :: (ByteString -> ByteString) -> IO ()

        -- ** Files
        readFile,               -- :: FilePath -> IO ByteString
        writeFile,              -- :: FilePath -> ByteString -> IO ()
        appendFile,             -- :: FilePath -> ByteString -> IO ()

        -- ** I\/O with Handles
        hGetLine,               -- :: Handle -> IO ByteString
        hGetContents,           -- :: Handle -> IO ByteString
        hGet,                   -- :: Handle -> Int -> IO ByteString
        hGetSome,               -- :: Handle -> Int -> IO ByteString
        hGetNonBlocking,        -- :: Handle -> Int -> IO ByteString
        hPut,                   -- :: Handle -> ByteString -> IO ()
        hPutNonBlocking,        -- :: Handle -> ByteString -> IO ByteString
        hPutStr,                -- :: Handle -> ByteString -> IO ()
        hPutStrLn,              -- :: Handle -> ByteString -> IO ()

        breakByte

  ) 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
#if !MIN_VERSION_base(4,6,0)
                                ,catch
#endif
                                )

#if MIN_VERSION_base(4,7,0)
import Data.Bits                (finiteBitSize, shiftL, (.|.), (.&.))
#else
import Data.Bits                (bitSize, shiftL, (.|.), (.&.))
#endif

import Data.ByteString.Internal
import Data.ByteString.Unsafe

import qualified Data.List as List

import Data.Word                (Word8)
import Data.Maybe               (isJust)

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

import Foreign.C.String         (CString, CStringLen)
import Foreign.C.Types          (CSize)
import Foreign.ForeignPtr       (ForeignPtr, withForeignPtr, touchForeignPtr)
#if MIN_VERSION_base(4,5,0)
import Foreign.ForeignPtr.Unsafe(unsafeForeignPtrToPtr)
#else
import Foreign.ForeignPtr       (unsafeForeignPtrToPtr)
#endif
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(..))
import System.IO.Error          (mkIOError, illegalOperationErrorType)

#if !(MIN_VERSION_base(4,8,0))
import Data.Monoid              (Monoid(..))
#endif

#if MIN_VERSION_base(4,3,0)
import System.IO                (hGetBufSome)
#else
import System.IO                (hWaitForInput, hIsEOF)
#endif

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                   (unsafePerformIO, unsafeDupablePerformIO)
import Data.Char                (ord)
import Foreign.Marshal.Utils    (copyBytes)

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

#if !(MIN_VERSION_base(4,7,0))
finiteBitSize = bitSize
#endif

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

-- | /O(1)/ The empty 'ByteString'
empty :: ByteString
empty :: ByteString
empty = ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
nullForeignPtr Int
0 Int
0

-- | /O(1)/ Convert a 'Word8' into a 'ByteString'
singleton :: Word8 -> ByteString
singleton :: Word8 -> ByteString
singleton Word8
c = Int -> (Ptr Word8 -> IO ()) -> ByteString
unsafeCreate Int
1 ((Ptr Word8 -> IO ()) -> ByteString)
-> (Ptr Word8 -> IO ()) -> ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
p Word8
c
{-# INLINE [1] singleton #-}

-- Inline [1] for intercalate rule

--
-- XXX The use of unsafePerformIO in allocating functions (unsafeCreate) is critical!
--
-- Otherwise:
--
--  singleton 255 `compare` singleton 127
--
-- is compiled to:
--
--  case mallocByteString 2 of
--      ForeignPtr f internals ->
--           case writeWord8OffAddr# f 0 255 of _ ->
--           case writeWord8OffAddr# f 0 127 of _ ->
--           case eqAddr# f f of
--                  False -> case compare (GHC.Prim.plusAddr# f 0)
--                                        (GHC.Prim.plusAddr# f 0)
--
--

-- | /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 b. (Word8 -> b -> b) -> b -> b) -> [Word8]
forall a. (forall b. (a -> b -> b) -> b -> b) -> [a]
build (ByteString -> (Word8 -> b -> b) -> b -> b
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 :: ByteString -> (Word8 -> a -> a) -> a -> a
unpackFoldr ByteString
bs Word8 -> a -> a
k a
z = (Word8 -> a -> a) -> a -> ByteString -> a
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
 #-}

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

-- | /O(1)/ Test whether a ByteString is empty.
null :: ByteString -> Bool
null :: ByteString -> Bool
null (PS ForeignPtr Word8
_ Int
_ Int
l) = Bool -> Bool -> Bool
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0) (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Int
l Int -> Int -> Bool
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 (PS ForeignPtr Word8
_ Int
_ Int
l) = Bool -> Int -> Int
forall a. (?callStack::CallStack) => Bool -> a -> a
assert (Int
l Int -> Int -> Bool
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 (PS ForeignPtr Word8
x Int
s Int
l) = Int -> (Ptr Word8 -> IO ()) -> ByteString
unsafeCreate (Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) ((Ptr Word8 -> IO ()) -> ByteString)
-> (Ptr Word8 -> IO ()) -> ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
f -> do
        Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
p Word8
c
        Ptr Word8 -> Ptr Word8 -> Int -> IO ()
memcpy (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) (Ptr Word8
f Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l)
{-# INLINE cons #-}

-- | /O(n)/ Append a byte to the end of a 'ByteString'
snoc :: ByteString -> Word8 -> ByteString
snoc :: ByteString -> Word8 -> ByteString
snoc (PS ForeignPtr Word8
x Int
s Int
l) Word8
c = Int -> (Ptr Word8 -> IO ()) -> ByteString
unsafeCreate (Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) ((Ptr Word8 -> IO ()) -> ByteString)
-> (Ptr Word8 -> IO ()) -> ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
f -> do
        Ptr Word8 -> Ptr Word8 -> Int -> IO ()
memcpy Ptr Word8
p (Ptr Word8
f Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l)
        Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
l) Word8
c
{-# INLINE snoc #-}

-- todo fuse

-- | /O(1)/ Extract the first element of a ByteString, which must be non-empty.
-- An exception will be thrown in the case of an empty ByteString.
head :: ByteString -> Word8
head :: ByteString -> Word8
head (PS ForeignPtr Word8
x Int
s Int
l)
    | Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0    = String -> Word8
forall a. String -> a
errorEmptyList String
"head"
    | Bool
otherwise = IO Word8 -> Word8
forall a. IO a -> a
accursedUnutterablePerformIO (IO Word8 -> Word8) -> IO Word8 -> Word8
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO Word8) -> IO Word8
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO Word8) -> IO Word8)
-> (Ptr Word8 -> IO Word8) -> IO Word8
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
p Int
s
{-# 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.
tail :: ByteString -> ByteString
tail :: ByteString -> ByteString
tail (PS ForeignPtr Word8
p Int
s Int
l)
    | Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0    = String -> ByteString
forall a. String -> a
errorEmptyList String
"tail"
    | Bool
otherwise = ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
p (Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Int
lInt -> Int -> Int
forall 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 (PS ForeignPtr Word8
x Int
s Int
l)
    | Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0    = Maybe (Word8, ByteString)
forall a. Maybe a
Nothing
    | Bool
otherwise = (Word8, ByteString) -> Maybe (Word8, ByteString)
forall a. a -> Maybe a
Just (IO Word8 -> Word8
forall a. IO a -> a
accursedUnutterablePerformIO (IO Word8 -> Word8) -> IO Word8 -> Word8
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO Word8) -> IO Word8
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x
                                                     ((Ptr Word8 -> IO Word8) -> IO Word8)
-> (Ptr Word8 -> IO Word8) -> IO Word8
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
p Int
s,
                        ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
x (Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Int
lInt -> Int -> Int
forall 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.
last :: ByteString -> Word8
last :: ByteString -> Word8
last ps :: ByteString
ps@(PS ForeignPtr Word8
x Int
s Int
l)
    | ByteString -> Bool
null ByteString
ps   = String -> Word8
forall a. String -> a
errorEmptyList String
"last"
    | Bool
otherwise = IO Word8 -> Word8
forall a. IO a -> a
accursedUnutterablePerformIO (IO Word8 -> Word8) -> IO Word8 -> Word8
forall a b. (a -> b) -> a -> b
$
                    ForeignPtr Word8 -> (Ptr Word8 -> IO Word8) -> IO Word8
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO Word8) -> IO Word8)
-> (Ptr Word8 -> IO Word8) -> IO Word8
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
p (Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
{-# INLINE last #-}

-- | /O(1)/ Return all the elements of a 'ByteString' except the last one.
-- An exception will be thrown in the case of an empty ByteString.
init :: ByteString -> ByteString
init :: ByteString -> ByteString
init ps :: ByteString
ps@(PS ForeignPtr Word8
p Int
s Int
l)
    | ByteString -> Bool
null ByteString
ps   = String -> ByteString
forall a. String -> a
errorEmptyList String
"init"
    | Bool
otherwise = ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
p Int
s (Int
lInt -> Int -> Int
forall 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 (PS ForeignPtr Word8
x Int
s Int
l)
    | Int
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0    = Maybe (ByteString, Word8)
forall a. Maybe a
Nothing
    | Bool
otherwise = (ByteString, Word8) -> Maybe (ByteString, Word8)
forall a. a -> Maybe a
Just (ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
x Int
s (Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1),
                        IO Word8 -> Word8
forall a. IO a -> a
accursedUnutterablePerformIO (IO Word8 -> Word8) -> IO Word8 -> Word8
forall a b. (a -> b) -> a -> b
$
                          ForeignPtr Word8 -> (Ptr Word8 -> IO Word8) -> IO Word8
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO Word8) -> IO Word8)
-> (Ptr Word8 -> IO Word8) -> IO Word8
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
p (Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1))
{-# INLINE unsnoc #-}

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

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

-- | /O(n)/ 'map' @f xs@ is the ByteString obtained by applying @f@ to each
-- element of @xs@.
map :: (Word8 -> Word8) -> ByteString -> ByteString
map :: (Word8 -> Word8) -> ByteString -> ByteString
map Word8 -> Word8
f (PS ForeignPtr Word8
fp Int
s Int
len) = IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO ByteString) -> IO ByteString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp ((Ptr Word8 -> IO ByteString) -> IO ByteString)
-> (Ptr Word8 -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
a ->
    Int -> (Ptr Word8 -> IO ()) -> IO ByteString
create Int
len ((Ptr Word8 -> IO ()) -> IO ByteString)
-> (Ptr Word8 -> IO ()) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Ptr Word8 -> Ptr Word8 -> IO ()
map_ Int
0 (Ptr Word8
a Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s)
  where
    map_ :: Int -> Ptr Word8 -> Ptr Word8 -> IO ()
    map_ :: Int -> Ptr Word8 -> Ptr Word8 -> IO ()
map_ !Int
n !Ptr Word8
p1 !Ptr Word8
p2
       | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
len = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
       | Bool
otherwise = do
            Word8
x <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
p1 Int
n
            Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
p2 Int
n (Word8 -> Word8
f Word8
x)
            Int -> Ptr Word8 -> Ptr Word8 -> IO ()
map_ (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Ptr Word8
p1 Ptr Word8
p2
{-# INLINE map #-}

-- | /O(n)/ 'reverse' @xs@ efficiently returns the elements of @xs@ in reverse order.
reverse :: ByteString -> ByteString
reverse :: ByteString -> ByteString
reverse (PS ForeignPtr Word8
x Int
s Int
l) = Int -> (Ptr Word8 -> IO ()) -> ByteString
unsafeCreate Int
l ((Ptr Word8 -> IO ()) -> ByteString)
-> (Ptr Word8 -> IO ()) -> ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
f ->
        Ptr Word8 -> Ptr Word8 -> CULong -> IO ()
c_reverse Ptr Word8
p (Ptr Word8
f Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) (Int -> CULong
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@(PS ForeignPtr Word8
x Int
s Int
l)
    | ByteString -> Int
length ByteString
ps Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
2  = ByteString
ps
    | Bool
otherwise      = Int -> (Ptr Word8 -> IO ()) -> ByteString
unsafeCreate (Int
2Int -> Int -> Int
forall a. Num a => a -> a -> a
*Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) ((Ptr Word8 -> IO ()) -> ByteString)
-> (Ptr Word8 -> IO ()) -> ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
f ->
        Ptr Word8 -> Ptr Word8 -> CULong -> Word8 -> IO ()
c_intersperse Ptr Word8
p (Ptr Word8
f Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) (Int -> CULong
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 [ByteString]
ps = ([Word8] -> ByteString) -> [[Word8]] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
P.map [Word8] -> ByteString
pack ([[Word8]] -> [ByteString])
-> ([ByteString] -> [[Word8]]) -> [ByteString] -> [ByteString]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[Word8]] -> [[Word8]]
forall a. [[a]] -> [[a]]
List.transpose ([[Word8]] -> [[Word8]])
-> ([ByteString] -> [[Word8]]) -> [ByteString] -> [[Word8]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ByteString -> [Word8]) -> [ByteString] -> [[Word8]]
forall a b. (a -> b) -> [a] -> [b]
P.map ByteString -> [Word8]
unpack ([ByteString] -> [ByteString]) -> [ByteString] -> [ByteString]
forall a b. (a -> b) -> a -> b
$ [ByteString]
ps

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

-- | 'foldl'' is like 'foldl', but strict in the accumulator.
--
foldl' :: (a -> Word8 -> a) -> a -> ByteString -> a
foldl' :: (a -> Word8 -> a) -> a -> ByteString -> a
foldl' a -> Word8 -> a
f a
v (PS ForeignPtr Word8
fp Int
off Int
len) =
      IO a -> a
forall a. IO a -> a
accursedUnutterablePerformIO (IO a -> a) -> IO a -> a
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp ((Ptr Word8 -> IO a) -> IO a) -> (Ptr Word8 -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
        a -> Ptr Word8 -> Ptr Word8 -> IO a
go a
v (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
off) (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len))
    where
      -- tail recursive; traverses array left to right
      go :: a -> Ptr Word8 -> Ptr Word8 -> IO a
go !a
z !Ptr Word8
p !Ptr Word8
q | Ptr Word8
p Ptr Word8 -> Ptr Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Word8
q    = a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
z
                  | Bool
otherwise = do Word8
x <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
p
                                   a -> Ptr Word8 -> Ptr Word8 -> IO a
go (a -> Word8 -> a
f a
z Word8
x) (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) Ptr Word8
q
{-# 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 :: (Word8 -> a -> a) -> a -> ByteString -> a
foldr Word8 -> a -> a
k a
z (PS ForeignPtr Word8
fp Int
off Int
len) =
      let p :: Ptr Word8
p = ForeignPtr Word8 -> Ptr Word8
forall a. ForeignPtr a -> Ptr a
unsafeForeignPtrToPtr ForeignPtr Word8
fp
       in Ptr Word8 -> Ptr Word8 -> a
go (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
off) (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
len))
    where
      -- not tail recursive; traverses array left to right
      go :: Ptr Word8 -> Ptr Word8 -> a
go !Ptr Word8
p !Ptr Word8
q | Ptr Word8
p Ptr Word8 -> Ptr Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Word8
q    = a
z
               | Bool
otherwise = let !x :: Word8
x = IO Word8 -> Word8
forall a. IO a -> a
accursedUnutterablePerformIO (IO Word8 -> Word8) -> IO Word8 -> Word8
forall a b. (a -> b) -> a -> b
$ do
                                        Word8
x' <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
p
                                        ForeignPtr Word8 -> IO ()
forall a. ForeignPtr a -> IO ()
touchForeignPtr ForeignPtr Word8
fp
                                        Word8 -> IO Word8
forall (m :: * -> *) a. Monad m => a -> m a
return Word8
x'
                              in Word8 -> a -> a
k Word8
x (Ptr Word8 -> Ptr Word8 -> a
go (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) Ptr Word8
q)
{-# INLINE foldr #-}

-- | 'foldr'' is like 'foldr', but strict in the accumulator.
foldr' :: (Word8 -> a -> a) -> a -> ByteString -> a
foldr' :: (Word8 -> a -> a) -> a -> ByteString -> a
foldr' Word8 -> a -> a
k a
v (PS ForeignPtr Word8
fp Int
off Int
len) =
      IO a -> a
forall a. IO a -> a
accursedUnutterablePerformIO (IO a -> a) -> IO a -> a
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp ((Ptr Word8 -> IO a) -> IO a) -> (Ptr Word8 -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
        a -> Ptr Word8 -> Ptr Word8 -> IO a
go a
v (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)) (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
offInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1))
    where
      -- tail recursive; traverses array right to left
      go :: a -> Ptr Word8 -> Ptr Word8 -> IO a
go !a
z !Ptr Word8
p !Ptr Word8
q | Ptr Word8
p Ptr Word8 -> Ptr Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Word8
q    = a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return a
z
                  | Bool
otherwise = do Word8
x <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
p
                                   a -> Ptr Word8 -> Ptr Word8 -> IO a
go (Word8 -> a -> a
k Word8
x a
z) (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (-Int
1)) Ptr Word8
q
{-# 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 :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldl1 :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldl1 Word8 -> Word8 -> Word8
f ByteString
ps
    | ByteString -> Bool
null ByteString
ps   = String -> Word8
forall a. String -> a
errorEmptyList String
"foldl1"
    | Bool
otherwise = (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> Word8
forall a. (a -> Word8 -> a) -> a -> ByteString -> a
foldl Word8 -> Word8 -> Word8
f (ByteString -> Word8
unsafeHead ByteString
ps) (ByteString -> ByteString
unsafeTail ByteString
ps)
{-# INLINE foldl1 #-}

-- | 'foldl1'' is like 'foldl1', but strict in the accumulator.
-- An exception will be thrown in the case of an empty ByteString.
foldl1' :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldl1' :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldl1' Word8 -> Word8 -> Word8
f ByteString
ps
    | ByteString -> Bool
null ByteString
ps   = String -> Word8
forall a. String -> a
errorEmptyList String
"foldl1'"
    | Bool
otherwise = (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> Word8
forall a. (a -> Word8 -> a) -> a -> ByteString -> a
foldl' Word8 -> Word8 -> Word8
f (ByteString -> Word8
unsafeHead ByteString
ps) (ByteString -> ByteString
unsafeTail ByteString
ps)
{-# 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 :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldr1 :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldr1 Word8 -> Word8 -> Word8
f ByteString
ps
    | ByteString -> Bool
null ByteString
ps        = String -> Word8
forall a. String -> a
errorEmptyList String
"foldr1"
    | Bool
otherwise      = (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> Word8
forall a. (Word8 -> a -> a) -> a -> ByteString -> a
foldr Word8 -> Word8 -> Word8
f (ByteString -> Word8
unsafeLast ByteString
ps) (ByteString -> ByteString
unsafeInit ByteString
ps)
{-# INLINE foldr1 #-}

-- | 'foldr1'' is a variant of 'foldr1', but is strict in the
-- accumulator.
foldr1' :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldr1' :: (Word8 -> Word8 -> Word8) -> ByteString -> Word8
foldr1' Word8 -> Word8 -> Word8
f ByteString
ps
    | ByteString -> Bool
null ByteString
ps        = String -> Word8
forall a. String -> a
errorEmptyList String
"foldr1"
    | Bool
otherwise      = (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> Word8
forall a. (Word8 -> a -> a) -> a -> ByteString -> a
foldr' Word8 -> Word8 -> Word8
f (ByteString -> Word8
unsafeLast ByteString
ps) (ByteString -> ByteString
unsafeInit ByteString
ps)
{-# INLINE foldr1' #-}

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

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

-- | Map a function over a 'ByteString' and concatenate the results
concatMap :: (Word8 -> ByteString) -> ByteString -> ByteString
concatMap :: (Word8 -> ByteString) -> ByteString -> ByteString
concatMap Word8 -> ByteString
f = [ByteString] -> ByteString
concat ([ByteString] -> ByteString)
-> (ByteString -> [ByteString]) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> [ByteString] -> [ByteString])
-> [ByteString] -> ByteString -> [ByteString]
forall a. (Word8 -> a -> a) -> a -> ByteString -> a
foldr ((:) (ByteString -> [ByteString] -> [ByteString])
-> (Word8 -> ByteString) -> Word8 -> [ByteString] -> [ByteString]
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
_ (PS ForeignPtr Word8
_ Int
_ Int
0) = Bool
False
any Word8 -> Bool
f (PS ForeignPtr Word8
x Int
s Int
l) = IO Bool -> Bool
forall a. IO a -> a
accursedUnutterablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO Bool) -> IO Bool)
-> (Ptr Word8 -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr ->
        Ptr Word8 -> Ptr Word8 -> IO Bool
go (Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) (Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
l))
    where
        go :: Ptr Word8 -> Ptr Word8 -> IO Bool
go !Ptr Word8
p !Ptr Word8
q | Ptr Word8
p Ptr Word8 -> Ptr Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Word8
q    = Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
                 | Bool
otherwise = do Word8
c <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
p
                                  if Word8 -> Bool
f Word8
c then Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True
                                         else Ptr Word8 -> Ptr Word8 -> IO Bool
go (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) Ptr Word8
q
{-# INLINE any #-}

-- todo fuse

-- | /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
_ (PS ForeignPtr Word8
_ Int
_ Int
0) = Bool
True
all Word8 -> Bool
f (PS ForeignPtr Word8
x Int
s Int
l) = IO Bool -> Bool
forall a. IO a -> a
accursedUnutterablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO Bool) -> IO Bool)
-> (Ptr Word8 -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr ->
        Ptr Word8 -> Ptr Word8 -> IO Bool
go (Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) (Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
l))
    where
        go :: Ptr Word8 -> Ptr Word8 -> IO Bool
go !Ptr Word8
p !Ptr Word8
q | Ptr Word8
p Ptr Word8 -> Ptr Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Word8
q     = Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
True  -- end of list
                 | Bool
otherwise  = do Word8
c <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
p
                                   if Word8 -> Bool
f Word8
c
                                      then Ptr Word8 -> Ptr Word8 -> IO Bool
go (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) Ptr Word8
q
                                      else Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return Bool
False
{-# INLINE all #-}

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

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

-- | /O(n)/ 'minimum' returns the minimum value from a 'ByteString'
-- This function will fuse.
-- An exception will be thrown in the case of an empty ByteString.
minimum :: ByteString -> Word8
minimum :: ByteString -> Word8
minimum xs :: ByteString
xs@(PS ForeignPtr Word8
x Int
s Int
l)
    | ByteString -> Bool
null ByteString
xs   = String -> Word8
forall a. String -> a
errorEmptyList String
"minimum"
    | Bool
otherwise = IO Word8 -> Word8
forall a. IO a -> a
accursedUnutterablePerformIO (IO Word8 -> Word8) -> IO Word8 -> Word8
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO Word8) -> IO Word8
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO Word8) -> IO Word8)
-> (Ptr Word8 -> IO Word8) -> IO Word8
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
                      Ptr Word8 -> CULong -> IO Word8
c_minimum (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) (Int -> CULong
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 list.
mapAccumL :: (acc -> Word8 -> (acc, Word8)) -> acc -> ByteString -> (acc, ByteString)
mapAccumL :: (acc -> Word8 -> (acc, Word8))
-> acc -> ByteString -> (acc, ByteString)
mapAccumL acc -> Word8 -> (acc, Word8)
f acc
acc (PS ForeignPtr Word8
fp Int
o Int
len) = IO (acc, ByteString) -> (acc, ByteString)
forall a. IO a -> a
unsafeDupablePerformIO (IO (acc, ByteString) -> (acc, ByteString))
-> IO (acc, ByteString) -> (acc, ByteString)
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8
-> (Ptr Word8 -> IO (acc, ByteString)) -> IO (acc, ByteString)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp ((Ptr Word8 -> IO (acc, ByteString)) -> IO (acc, ByteString))
-> (Ptr Word8 -> IO (acc, ByteString)) -> IO (acc, ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
a -> do
    ForeignPtr Word8
gp   <- Int -> IO (ForeignPtr Word8)
forall a. Int -> IO (ForeignPtr a)
mallocByteString Int
len
    acc
acc' <- ForeignPtr Word8 -> (Ptr Word8 -> IO acc) -> IO acc
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
gp ((Ptr Word8 -> IO acc) -> IO acc)
-> (Ptr Word8 -> IO acc) -> IO acc
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> acc -> Int -> Ptr Any -> Ptr Word8 -> IO acc
forall b b. acc -> Int -> Ptr b -> Ptr b -> IO acc
mapAccumL_ acc
acc Int
0 (Ptr Word8
a Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
o) Ptr Word8
p
    (acc, ByteString) -> IO (acc, ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (acc
acc', ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
gp Int
0 Int
len)
  where
    mapAccumL_ :: acc -> Int -> Ptr b -> Ptr b -> IO acc
mapAccumL_ !acc
s !Int
n !Ptr b
p1 !Ptr b
p2
       | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
len = acc -> IO acc
forall (m :: * -> *) a. Monad m => a -> m a
return acc
s
       | Bool
otherwise = do
            Word8
x <- Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p1 Int
n
            let (acc
s', Word8
y) = acc -> Word8 -> (acc, Word8)
f acc
s Word8
x
            Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
p2 Int
n Word8
y
            acc -> Int -> Ptr b -> Ptr b -> IO acc
mapAccumL_ acc
s' (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Ptr b
p1 Ptr b
p2
{-# 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 :: (acc -> Word8 -> (acc, Word8))
-> acc -> ByteString -> (acc, ByteString)
mapAccumR acc -> Word8 -> (acc, Word8)
f acc
acc (PS ForeignPtr Word8
fp Int
o Int
len) = IO (acc, ByteString) -> (acc, ByteString)
forall a. IO a -> a
unsafeDupablePerformIO (IO (acc, ByteString) -> (acc, ByteString))
-> IO (acc, ByteString) -> (acc, ByteString)
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8
-> (Ptr Word8 -> IO (acc, ByteString)) -> IO (acc, ByteString)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp ((Ptr Word8 -> IO (acc, ByteString)) -> IO (acc, ByteString))
-> (Ptr Word8 -> IO (acc, ByteString)) -> IO (acc, ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
a -> do
    ForeignPtr Word8
gp   <- Int -> IO (ForeignPtr Word8)
forall a. Int -> IO (ForeignPtr a)
mallocByteString Int
len
    acc
acc' <- ForeignPtr Word8 -> (Ptr Word8 -> IO acc) -> IO acc
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
gp ((Ptr Word8 -> IO acc) -> IO acc)
-> (Ptr Word8 -> IO acc) -> IO acc
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> acc -> Int -> Ptr Any -> Ptr Word8 -> IO acc
forall b b. acc -> Int -> Ptr b -> Ptr b -> IO acc
mapAccumR_ acc
acc (Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (Ptr Word8
a Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
o) Ptr Word8
p
    (acc, ByteString) -> IO (acc, ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return ((acc, ByteString) -> IO (acc, ByteString))
-> (acc, ByteString) -> IO (acc, ByteString)
forall a b. (a -> b) -> a -> b
$! (acc
acc', ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
gp Int
0 Int
len)
  where
    mapAccumR_ :: acc -> Int -> Ptr b -> Ptr b -> IO acc
mapAccumR_ !acc
s !Int
n !Ptr b
p !Ptr b
q
       | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<  Int
0    = acc -> IO acc
forall (m :: * -> *) a. Monad m => a -> m a
return acc
s
       | Bool
otherwise = do
            Word8
x  <- Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p Int
n
            let (acc
s', Word8
y) = acc -> Word8 -> (acc, Word8)
f acc
s Word8
x
            Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
q Int
n Word8
y
            acc -> Int -> Ptr b -> Ptr b -> IO acc
mapAccumR_ acc
s' (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Ptr b
p Ptr b
q
{-# INLINE mapAccumR #-}

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

-- | 'scanl' is similar to 'foldl', but returns a list of successive
-- reduced values from the left. This function will fuse.
--
-- > scanl f z [x1, x2, ...] == [z, z `f` x1, (z `f` x1) `f` x2, ...]
--
-- Note that
--
-- > last (scanl f z xs) == foldl f z xs.
--
scanl :: (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString

scanl :: (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
scanl Word8 -> Word8 -> Word8
f Word8
v (PS ForeignPtr Word8
fp Int
s Int
len) = IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO ByteString) -> IO ByteString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp ((Ptr Word8 -> IO ByteString) -> IO ByteString)
-> (Ptr Word8 -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
a ->
    Int -> (Ptr Word8 -> IO ()) -> IO ByteString
create (Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) ((Ptr Word8 -> IO ()) -> IO ByteString)
-> (Ptr Word8 -> IO ()) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
q -> do
        Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
q Word8
v
        Word8 -> Int -> Ptr Any -> Ptr Any -> IO ()
forall b b. Word8 -> Int -> Ptr b -> Ptr b -> IO ()
scanl_ Word8
v Int
0 (Ptr Word8
a Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) (Ptr Word8
q Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1)
  where
    scanl_ :: Word8 -> Int -> Ptr b -> Ptr b -> IO ()
scanl_ !Word8
z !Int
n !Ptr b
p !Ptr b
q
        | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
len  = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        | Bool
otherwise = do
            Word8
x <- Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p Int
n
            let z' :: Word8
z' = Word8 -> Word8 -> Word8
f Word8
z Word8
x
            Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
q Int
n Word8
z'
            Word8 -> Int -> Ptr b -> Ptr b -> IO ()
scanl_ Word8
z' (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Ptr b
p Ptr b
q
{-# INLINE scanl #-}

    -- n.b. haskell's List scan returns a list one bigger than the
    -- input, so we need to snoc here to get some extra space, however,
    -- it breaks map/up fusion (i.e. scanl . map no longer fuses)

-- | 'scanl1' is a variant of 'scanl' that has no starting value argument.
-- This function will fuse.
--
-- > scanl1 f [x1, x2, ...] == [x1, x1 `f` x2, ...]
scanl1 :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString
scanl1 :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString
scanl1 Word8 -> Word8 -> Word8
f ByteString
ps
    | ByteString -> Bool
null ByteString
ps   = ByteString
empty
    | Bool
otherwise = (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
scanl Word8 -> Word8 -> Word8
f (ByteString -> Word8
unsafeHead ByteString
ps) (ByteString -> ByteString
unsafeTail ByteString
ps)
{-# INLINE scanl1 #-}

-- | scanr is the right-to-left dual of scanl.
scanr :: (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
scanr :: (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
scanr Word8 -> Word8 -> Word8
f Word8
v (PS ForeignPtr Word8
fp Int
s Int
len) = IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO ByteString) -> IO ByteString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp ((Ptr Word8 -> IO ByteString) -> IO ByteString)
-> (Ptr Word8 -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
a ->
    Int -> (Ptr Word8 -> IO ()) -> IO ByteString
create (Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) ((Ptr Word8 -> IO ()) -> IO ByteString)
-> (Ptr Word8 -> IO ()) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
q -> do
        Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
q Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
len) Word8
v
        Word8 -> Int -> Ptr Any -> Ptr Word8 -> IO ()
forall b b. Word8 -> Int -> Ptr b -> Ptr b -> IO ()
scanr_ Word8
v (Int
lenInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) (Ptr Word8
a Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) Ptr Word8
q
  where
    scanr_ :: Word8 -> Int -> Ptr b -> Ptr b -> IO ()
scanr_ !Word8
z !Int
n !Ptr b
p !Ptr b
q
        | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<  Int
0    = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        | Bool
otherwise = do
            Word8
x <- Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p Int
n
            let z' :: Word8
z' = Word8 -> Word8 -> Word8
f Word8
x Word8
z
            Ptr b -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr b
q Int
n Word8
z'
            Word8 -> Int -> Ptr b -> Ptr b -> IO ()
scanr_ Word8
z' (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) Ptr b
p Ptr b
q
{-# 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
    | ByteString -> Bool
null ByteString
ps   = ByteString
empty
    | Bool
otherwise = (Word8 -> Word8 -> Word8) -> Word8 -> ByteString -> ByteString
scanr Word8 -> Word8 -> Word8
f (ByteString -> Word8
unsafeLast ByteString
ps) (ByteString -> ByteString
unsafeInit ByteString
ps)
{-# 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 implemenation uses @memset(3)@
replicate :: Int -> Word8 -> ByteString
replicate :: Int -> Word8 -> ByteString
replicate Int
w Word8
c
    | Int
w Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0    = ByteString
empty
    | Bool
otherwise = Int -> (Ptr Word8 -> IO ()) -> ByteString
unsafeCreate Int
w ((Ptr Word8 -> IO ()) -> ByteString)
-> (Ptr Word8 -> IO ()) -> ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr ->
                      Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
memset Ptr Word8
ptr Word8
c (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
w) IO (Ptr Word8) -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()

-- | /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 :: (a -> Maybe (Word8, a)) -> a -> ByteString
unfoldr a -> Maybe (Word8, a)
f = [ByteString] -> ByteString
concat ([ByteString] -> ByteString)
-> (a -> [ByteString]) -> a -> ByteString
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 Int -> (a -> Maybe (Word8, a)) -> a -> (ByteString, Maybe a)
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 -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: []
            (ByteString
s, Just a
x') -> ByteString
s ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: Int -> Int -> a -> [ByteString]
unfoldChunk Int
n' (Int
nInt -> Int -> Int
forall 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 :: Int -> (a -> Maybe (Word8, a)) -> a -> (ByteString, Maybe a)
unfoldrN Int
i a -> Maybe (Word8, a)
f a
x0
    | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0     = (ByteString
empty, a -> Maybe a
forall a. a -> Maybe a
Just a
x0)
    | Bool
otherwise = IO (ByteString, Maybe a) -> (ByteString, Maybe a)
forall a. IO a -> a
unsafePerformIO (IO (ByteString, Maybe a) -> (ByteString, Maybe a))
-> IO (ByteString, Maybe a) -> (ByteString, Maybe a)
forall a b. (a -> b) -> a -> b
$ Int
-> (Ptr Word8 -> IO (Int, Int, Maybe a))
-> IO (ByteString, Maybe a)
forall a.
Int -> (Ptr Word8 -> IO (Int, Int, a)) -> IO (ByteString, a)
createAndTrim' Int
i ((Ptr Word8 -> IO (Int, Int, Maybe a)) -> IO (ByteString, Maybe a))
-> (Ptr Word8 -> IO (Int, Int, Maybe a))
-> IO (ByteString, Maybe a)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Ptr Word8 -> a -> Int -> IO (Int, Int, Maybe a)
forall a. Num a => Ptr Word8 -> a -> Int -> IO (a, Int, Maybe a)
go Ptr Word8
p a
x0 Int
0
  where
    go :: Ptr Word8 -> a -> Int -> IO (a, Int, Maybe a)
go !Ptr Word8
p !a
x !Int
n
      | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
i    = (a, Int, Maybe a) -> IO (a, Int, Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
0, Int
n, a -> Maybe a
forall a. a -> Maybe a
Just a
x)
      | Bool
otherwise = case a -> Maybe (Word8, a)
f a
x of
                      Maybe (Word8, a)
Nothing     -> (a, Int, Maybe a) -> IO (a, Int, Maybe a)
forall (m :: * -> *) a. Monad m => a -> m a
return (a
0, Int
n, Maybe a
forall a. Maybe a
Nothing)
                      Just (Word8
w,a
x') -> do Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
p Word8
w
                                        Ptr Word8 -> a -> Int -> IO (a, Int, Maybe a)
go (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) a
x' (Int
nInt -> Int -> Int
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@(PS ForeignPtr Word8
x Int
s Int
l)
    | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0    = ByteString
empty
    | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l    = ByteString
ps
    | Bool
otherwise = ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
x Int
s Int
n
{-# INLINE take #-}

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

-- | /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@(PS ForeignPtr Word8
x Int
s Int
l)
    | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0    = (ByteString
empty, ByteString
ps)
    | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l    = (ByteString
ps, ByteString
empty)
    | Bool
otherwise = (ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
x Int
s Int
n, ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
x (Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n) (Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n))
{-# INLINE splitAt #-}

-- | 'takeWhile', applied to a predicate @p@ and a ByteString @xs@,
-- returns the longest prefix (possibly empty) of @xs@ of elements that
-- satisfy @p@.
takeWhile :: (Word8 -> Bool) -> ByteString -> ByteString
takeWhile :: (Word8 -> Bool) -> ByteString -> ByteString
takeWhile Word8 -> Bool
f ByteString
ps = Int -> ByteString -> ByteString
unsafeTake ((Word8 -> Bool) -> ByteString -> Int
findIndexOrEnd (Bool -> Bool
not (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
f) ByteString
ps) ByteString
ps
{-# INLINE takeWhile #-}

-- | 'takeWhileEnd', applied to a predicate @p@ and a ByteString @xs@, returns
-- the longest suffix (possibly empty) of @xs@ of elements that satisfy @p@.
--
-- @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 (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
f) ByteString
ps) ByteString
ps
{-# INLINE takeWhileEnd #-}

-- | 'dropWhile' @p xs@ returns the suffix remaining after 'takeWhile' @p xs@.
dropWhile :: (Word8 -> Bool) -> ByteString -> ByteString
dropWhile :: (Word8 -> Bool) -> ByteString -> ByteString
dropWhile Word8 -> Bool
f ByteString
ps = Int -> ByteString -> ByteString
unsafeDrop ((Word8 -> Bool) -> ByteString -> Int
findIndexOrEnd (Bool -> Bool
not (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
f) ByteString
ps) ByteString
ps
{-# INLINE dropWhile #-}

-- | 'dropWhileEnd' @p xs@ returns the prefix remaining after 'takeWhileEnd' @p
-- xs@.
--
-- @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 (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
f) ByteString
ps) ByteString
ps
{-# INLINE dropWhileEnd #-}

-- instead of findIndexOrEnd, we could use memchr here.

-- | 'break' @p@ is equivalent to @'span' ('not' . p)@.
--
-- Under GHC, a rewrite rule will transform break (==) into a
-- call to the specialised breakByte:
--
-- > break ((==) x) = breakByte x
-- > break (==x) = breakByte x
--
break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
break :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
break Word8 -> Bool
p ByteString
ps = case (Word8 -> Bool) -> ByteString -> Int
findIndexOrEnd 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
#if MIN_VERSION_base(4,9,0)
{-# RULES
"ByteString specialise break (x ==)" forall x.
    break (x `eqWord8`) = breakByte x
"ByteString specialise break (== x)" forall x.
    break (`eqWord8` x) = breakByte x
  #-}
#else
{-# RULES
"ByteString specialise break (x ==)" forall x.
    break (x ==) = breakByte x
"ByteString specialise break (== x)" forall x.
    break (== x) = breakByte x
  #-}
#endif

-- INTERNAL:

-- | 'breakByte' breaks its ByteString argument at the first occurence
-- of the specified byte. It is more efficient than 'break' as it is
-- implemented with @memchr(3)@. I.e.
--
-- > break (==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 #-}
{-# DEPRECATED breakByte "It is an internal function and should never have been exported. Use 'break (== x)' instead. (There are rewrite rules that handle this special case of 'break'.)" #-}

-- | 'breakEnd' behaves like 'break' but from the end of the 'ByteString'
--
-- breakEnd p == spanEnd (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

-- | 'span' @p xs@ breaks the ByteString into two segments. It is
-- equivalent to @('takeWhile' p xs, 'dropWhile' p xs)@
span :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
span :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
span Word8 -> Bool
p ByteString
ps = (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
break (Bool -> Bool
not (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
p) ByteString
ps
{-# INLINE [1] span #-}

-- | 'spanByte' breaks its ByteString argument at the first
-- occurence 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@(PS ForeignPtr Word8
x Int
s Int
l) =
    IO (ByteString, ByteString) -> (ByteString, ByteString)
forall a. IO a -> a
accursedUnutterablePerformIO (IO (ByteString, ByteString) -> (ByteString, ByteString))
-> IO (ByteString, ByteString) -> (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$
      ForeignPtr Word8
-> (Ptr Word8 -> IO (ByteString, ByteString))
-> IO (ByteString, ByteString)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO (ByteString, ByteString))
 -> IO (ByteString, ByteString))
-> (Ptr Word8 -> IO (ByteString, ByteString))
-> IO (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
        Ptr Any -> Int -> IO (ByteString, ByteString)
forall b. Ptr b -> Int -> IO (ByteString, ByteString)
go (Ptr Word8
p Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) Int
0
  where
    go :: Ptr b -> Int -> IO (ByteString, ByteString)
go !Ptr b
p !Int
i | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l    = (ByteString, ByteString) -> IO (ByteString, ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString
ps, ByteString
empty)
             | Bool
otherwise = do Word8
c' <- Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
p Int
i
                              if Word8
c Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
/= Word8
c'
                                  then (ByteString, ByteString) -> IO (ByteString, ByteString)
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 Ptr b -> Int -> IO (ByteString, ByteString)
go Ptr b
p (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
{-# INLINE spanByte #-}

-- See bytestring #70
#if MIN_VERSION_base(4,9,0)
{-# RULES
"ByteString specialise span (x ==)" forall x.
    span (x `eqWord8`) = spanByte x
"ByteString specialise span (== x)" forall x.
    span (`eqWord8` x) = spanByte x
  #-}
#else
{-# RULES
"ByteString specialise span (x ==)" forall x.
    span (x ==) = spanByte x
"ByteString specialise span (== x)" forall x.
    span (== x) = spanByte x
  #-}
#endif

-- | 'spanEnd' behaves like 'span' but from the end of the 'ByteString'.
-- We have
--
-- > spanEnd (not.isSpace) "x y z" == ("x y ","z")
--
-- and
--
-- > spanEnd (not . isSpace) ps
-- >    ==
-- > let (x,y) = span (not.isSpace) (reverse ps) in (reverse y, reverse x)
--
spanEnd :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
spanEnd :: (Word8 -> Bool) -> ByteString -> (ByteString, ByteString)
spanEnd  Word8 -> Bool
p ByteString
ps = Int -> ByteString -> (ByteString, ByteString)
splitAt ((Word8 -> Bool) -> ByteString -> Int
findFromEndUntil (Bool -> Bool
not(Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall 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 (==97) []        == []
--
splitWith :: (Word8 -> Bool) -> ByteString -> [ByteString]
splitWith :: (Word8 -> Bool) -> ByteString -> [ByteString]
splitWith Word8 -> Bool
_pred (PS ForeignPtr Word8
_  Int
_   Int
0) = []
splitWith Word8 -> Bool
pred_ (PS ForeignPtr Word8
fp Int
off Int
len) = (Word# -> Bool) -> Int -> Int -> ForeignPtr Word8 -> [ByteString]
splitWith0 Word# -> Bool
pred# Int
off Int
len ForeignPtr Word8
fp
  where pred# :: Word# -> Bool
pred# Word#
c# = Word8 -> Bool
pred_ (Word# -> Word8
W8# Word#
c#)

        splitWith0 :: (Word# -> Bool) -> Int -> Int -> ForeignPtr Word8 -> [ByteString]
splitWith0 !Word# -> Bool
pred' !Int
off' !Int
len' !ForeignPtr Word8
fp' =
          IO [ByteString] -> [ByteString]
forall a. IO a -> a
accursedUnutterablePerformIO (IO [ByteString] -> [ByteString])
-> IO [ByteString] -> [ByteString]
forall a b. (a -> b) -> a -> b
$
            ForeignPtr Word8
-> (Ptr Word8 -> IO [ByteString]) -> IO [ByteString]
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp ((Ptr Word8 -> IO [ByteString]) -> IO [ByteString])
-> (Ptr Word8 -> IO [ByteString]) -> IO [ByteString]
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
              (Word# -> Bool)
-> Ptr Word8
-> Int
-> Int
-> Int
-> ForeignPtr Word8
-> IO [ByteString]
splitLoop Word# -> Bool
pred' Ptr Word8
p Int
0 Int
off' Int
len' ForeignPtr Word8
fp'

        splitLoop :: (Word# -> Bool)
                  -> Ptr Word8
                  -> Int -> Int -> Int
                  -> ForeignPtr Word8
                  -> IO [ByteString]

        splitLoop :: (Word# -> Bool)
-> Ptr Word8
-> Int
-> Int
-> Int
-> ForeignPtr Word8
-> IO [ByteString]
splitLoop Word# -> Bool
pred' Ptr Word8
p Int
idx' Int
off' Int
len' ForeignPtr Word8
fp'
            | Int
idx' Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
len'  = [ByteString] -> IO [ByteString]
forall (m :: * -> *) a. Monad m => a -> m a
return [ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
fp' Int
off' Int
idx']
            | Bool
otherwise = do
                Word8
w <- Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
p (Int
off'Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
idx')
                if Word# -> Bool
pred' (case Word8
w of W8# Word#
w# -> Word#
w#)
                   then [ByteString] -> IO [ByteString]
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
fp' Int
off' Int
idx' ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
:
                              (Word# -> Bool) -> Int -> Int -> ForeignPtr Word8 -> [ByteString]
splitWith0 Word# -> Bool
pred' (Int
off'Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
idx'Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) (Int
len'Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
idx'Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1) ForeignPtr Word8
fp')
                   else (Word# -> Bool)
-> Ptr Word8
-> Int
-> Int
-> Int
-> ForeignPtr Word8
-> IO [ByteString]
splitLoop Word# -> Bool
pred' Ptr Word8
p (Int
idx'Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
off' Int
len' ForeignPtr Word8
fp'
{-# 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
--
-- 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
_ (PS ForeignPtr Word8
_ Int
_ Int
0) = []
split Word8
w (PS ForeignPtr Word8
x Int
s Int
l) = Int -> [ByteString]
loop Int
0
    where
        loop :: Int -> [ByteString]
loop !Int
n =
            let q :: Ptr Word8
q = IO (Ptr Word8) -> Ptr Word8
forall a. IO a -> a
accursedUnutterablePerformIO (IO (Ptr Word8) -> Ptr Word8) -> IO (Ptr Word8) -> Ptr Word8
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO (Ptr Word8)) -> IO (Ptr Word8)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO (Ptr Word8)) -> IO (Ptr Word8))
-> (Ptr Word8 -> IO (Ptr Word8)) -> IO (Ptr Word8)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
                      Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
memchr (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n))
                             Word8
w (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n))
            in if Ptr Word8
q Ptr Word8 -> Ptr Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Word8
forall a. Ptr a
nullPtr
                then [ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
x (Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n) (Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n)]
                else let i :: Int
i = IO Int -> Int
forall a. IO a -> a
accursedUnutterablePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO Int) -> IO Int
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO Int) -> IO Int)
-> (Ptr Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
                               Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Word8
q Ptr Word8 -> Ptr Any -> Int
forall a b. Ptr a -> Ptr b -> Int
`minusPtr` (Ptr Word8
p Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s))
                      in ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
x (Int
sInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n) (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
n) ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: Int -> [ByteString]
loop (Int
iInt -> Int -> Int
forall 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 sublist in the result contains only equal
-- elements.  For example,
--
-- > group "Mississippi" = ["M","i","ss","i","ss","i","pp","i"]
--
-- It is a special case of 'groupBy', which allows the programmer to
-- supply their own equality test. It is about 40% faster than
-- /groupBy (==)/
group :: ByteString -> [ByteString]
group :: ByteString -> [ByteString]
group ByteString
xs
    | ByteString -> Bool
null ByteString
xs   = []
    | Bool
otherwise = ByteString
ys ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: ByteString -> [ByteString]
group ByteString
zs
    where
        (ByteString
ys, ByteString
zs) = Word8 -> ByteString -> (ByteString, ByteString)
spanByte (ByteString -> Word8
unsafeHead ByteString
xs) 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
    | ByteString -> Bool
null ByteString
xs   = []
    | Bool
otherwise = Int -> ByteString -> ByteString
unsafeTake Int
n ByteString
xs ByteString -> [ByteString] -> [ByteString]
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 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ (Word8 -> Bool) -> ByteString -> Int
findIndexOrEnd (Bool -> Bool
not (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Word8 -> Bool
k (ByteString -> Word8
unsafeHead ByteString
xs)) (ByteString -> ByteString
unsafeTail ByteString
xs)

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

{-# RULES
"ByteString specialise intercalate c -> intercalateByte" forall c s1 s2 .
    intercalate (singleton c) [s1, s2] = intercalateWithByte c s1 s2
  #-}

-- | /O(n)/ intercalateWithByte. An efficient way to join to two ByteStrings
-- with a char. Around 4 times faster than the generalised join.
--
intercalateWithByte :: Word8 -> ByteString -> ByteString -> ByteString
intercalateWithByte :: Word8 -> ByteString -> ByteString -> ByteString
intercalateWithByte Word8
c f :: ByteString
f@(PS ForeignPtr Word8
ffp Int
s Int
l) g :: ByteString
g@(PS ForeignPtr Word8
fgp Int
t Int
m) = Int -> (Ptr Word8 -> IO ()) -> ByteString
unsafeCreate Int
len ((Ptr Word8 -> IO ()) -> ByteString)
-> (Ptr Word8 -> IO ()) -> ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
ptr ->
    ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
ffp ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
fp ->
    ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fgp ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
gp -> do
        Ptr Word8 -> Ptr Word8 -> Int -> IO ()
memcpy Ptr Word8
ptr (Ptr Word8
fp Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l)
        Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke (Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
l) Word8
c
        Ptr Word8 -> Ptr Word8 -> Int -> IO ()
memcpy (Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)) (Ptr Word8
gp Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
t) (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
m)
    where
      len :: Int
len = ByteString -> Int
length ByteString
f Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ByteString -> Int
length ByteString
g Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
{-# INLINE intercalateWithByte #-}

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

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

-- | /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 (PS ForeignPtr Word8
x Int
s Int
l) = IO (Maybe Int) -> Maybe Int
forall a. IO a -> a
accursedUnutterablePerformIO (IO (Maybe Int) -> Maybe Int) -> IO (Maybe Int) -> Maybe Int
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO (Maybe Int)) -> IO (Maybe Int)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO (Maybe Int)) -> IO (Maybe Int))
-> (Ptr Word8 -> IO (Maybe Int)) -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> do
    let p' :: Ptr b
p' = Ptr Word8
p Ptr Word8 -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s
    Ptr Word8
q <- Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
memchr Ptr Word8
forall a. Ptr a
p' Word8
c (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l)
    Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe Int -> IO (Maybe Int)) -> Maybe Int -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$! if Ptr Word8
q Ptr Word8 -> Ptr Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Word8
forall a. Ptr a
nullPtr then Maybe Int
forall a. Maybe a
Nothing else Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$! Ptr Word8
q Ptr Word8 -> Ptr Any -> Int
forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Any
forall a. Ptr a
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 ==
-- > (-) (length xs - 1) `fmap` elemIndex c (reverse xs)
--
elemIndexEnd :: Word8 -> ByteString -> Maybe Int
elemIndexEnd :: Word8 -> ByteString -> Maybe Int
elemIndexEnd = (Word8 -> Bool) -> ByteString -> Maybe Int
findIndexEnd ((Word8 -> Bool) -> ByteString -> Maybe Int)
-> (Word8 -> Word8 -> Bool) -> Word8 -> ByteString -> Maybe Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
(==)
{-# INLINE elemIndexEnd #-}

-- | /O(n)/ The 'elemIndices' function extends 'elemIndex', by returning
-- the indices of all elements equal to the query element, in ascending order.
-- This implementation uses memchr(3).
elemIndices :: Word8 -> ByteString -> [Int]
elemIndices :: Word8 -> ByteString -> [Int]
elemIndices Word8
w (PS ForeignPtr Word8
x Int
s Int
l) = Int -> [Int]
loop Int
0
    where
        loop :: Int -> [Int]
loop !Int
n = let q :: Ptr Word8
q = IO (Ptr Word8) -> Ptr Word8
forall a. IO a -> a
accursedUnutterablePerformIO (IO (Ptr Word8) -> Ptr Word8) -> IO (Ptr Word8) -> Ptr Word8
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO (Ptr Word8)) -> IO (Ptr Word8)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO (Ptr Word8)) -> IO (Ptr Word8))
-> (Ptr Word8 -> IO (Ptr Word8)) -> IO (Ptr Word8)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
                           Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
memchr (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
s))
                                                Word8
w (Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n))
                  in if Ptr Word8
q Ptr Word8 -> Ptr Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Word8
forall a. Ptr a
nullPtr
                        then []
                        else let i :: Int
i = IO Int -> Int
forall a. IO a -> a
accursedUnutterablePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO Int) -> IO Int
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO Int) -> IO Int)
-> (Ptr Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
                                       Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Ptr Word8
q Ptr Word8 -> Ptr Any -> Int
forall a b. Ptr a -> Ptr b -> Int
`minusPtr` (Ptr Word8
p Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s))
                             in Int
i Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: Int -> [Int]
loop (Int
iInt -> Int -> Int
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 (PS ForeignPtr Word8
x Int
s Int
m) = IO Int -> Int
forall a. IO a -> a
accursedUnutterablePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO Int) -> IO Int
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO Int) -> IO Int)
-> (Ptr Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
    (CULong -> Int) -> IO CULong -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap CULong -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (IO CULong -> IO Int) -> IO CULong -> IO Int
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> CULong -> Word8 -> IO CULong
c_count (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) (Int -> CULong
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 (PS ForeignPtr Word8
x Int
s Int
l) = IO (Maybe Int) -> Maybe Int
forall a. IO a -> a
accursedUnutterablePerformIO (IO (Maybe Int) -> Maybe Int) -> IO (Maybe Int) -> Maybe Int
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO (Maybe Int)) -> IO (Maybe Int)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO (Maybe Int)) -> IO (Maybe Int))
-> (Ptr Word8 -> IO (Maybe Int)) -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
f -> Ptr Word8 -> Int -> IO (Maybe Int)
go (Ptr Word8
f Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) Int
0
  where
    go :: Ptr Word8 -> Int -> IO (Maybe Int)
go !Ptr Word8
ptr !Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l    = Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Int
forall a. Maybe a
Nothing
               | Bool
otherwise = do Word8
w <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
ptr
                                if Word8 -> Bool
k Word8
w
                                  then Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
n)
                                  else Ptr Word8 -> Int -> IO (Maybe Int)
go (Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
{-# INLINE 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 (PS ForeignPtr Word8
x Int
s Int
l) = IO (Maybe Int) -> Maybe Int
forall a. IO a -> a
accursedUnutterablePerformIO (IO (Maybe Int) -> Maybe Int) -> IO (Maybe Int) -> Maybe Int
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO (Maybe Int)) -> IO (Maybe Int)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO (Maybe Int)) -> IO (Maybe Int))
-> (Ptr Word8 -> IO (Maybe Int)) -> IO (Maybe Int)
forall a b. (a -> b) -> a -> b
$ \ Ptr Word8
f -> Ptr Any -> Int -> IO (Maybe Int)
forall b. Ptr b -> Int -> IO (Maybe Int)
go (Ptr Word8
f Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) (Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)
  where
    go :: Ptr b -> Int -> IO (Maybe Int)
go !Ptr b
ptr !Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0     = Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe Int
forall a. Maybe a
Nothing
               | Bool
otherwise = do Word8
w <- Ptr b -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr b
ptr Int
n
                                if Word8 -> Bool
k Word8
w
                                  then Maybe Int -> IO (Maybe Int)
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
n)
                                  else Ptr b -> Int -> IO (Maybe Int)
go Ptr b
ptr (Int
nInt -> Int -> Int
forall 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 ByteString
ps = Int -> ByteString -> [Int]
forall a. Num a => a -> ByteString -> [a]
loop Int
0 ByteString
ps
   where
     loop :: a -> ByteString -> [a]
loop !a
n !ByteString
qs | ByteString -> Bool
null ByteString
qs           = []
                 | Word8 -> Bool
p (ByteString -> Word8
unsafeHead ByteString
qs) = a
n a -> [a] -> [a]
forall a. a -> [a] -> [a]
: a -> ByteString -> [a]
loop (a
na -> a -> a
forall a. Num a => a -> a -> a
+a
1) (ByteString -> ByteString
unsafeTail ByteString
qs)
                 | Bool
otherwise         =     a -> ByteString -> [a]
loop (a
na -> a -> a
forall a. Num a => a -> a -> a
+a
1) (ByteString -> ByteString
unsafeTail ByteString
qs)

-- ---------------------------------------------------------------------
-- 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 -> ByteString -> Bool
elem Word8
c 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@(PS ForeignPtr Word8
x Int
s Int
l)
    | ByteString -> Bool
null ByteString
ps   = ByteString
ps
    | Bool
otherwise = IO ByteString -> ByteString
forall a. IO a -> a
unsafePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Int -> (Ptr Word8 -> IO Int) -> IO ByteString
createAndTrim Int
l ((Ptr Word8 -> IO Int) -> IO ByteString)
-> (Ptr Word8 -> IO Int) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> ForeignPtr Word8 -> (Ptr Word8 -> IO Int) -> IO Int
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO Int) -> IO Int)
-> (Ptr Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
f -> do
        Ptr Word8
t <- Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO (Ptr Word8)
go (Ptr Word8
f Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) Ptr Word8
p (Ptr Word8
f Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
s Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
l))
        Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return (Int -> IO Int) -> Int -> IO Int
forall a b. (a -> b) -> a -> b
$! Ptr Word8
t Ptr Word8 -> Ptr Word8 -> Int
forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
p -- actual length
    where
        go :: Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO (Ptr Word8)
go !Ptr Word8
f !Ptr Word8
t !Ptr Word8
end | Ptr Word8
f Ptr Word8 -> Ptr Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Ptr Word8
end  = Ptr Word8 -> IO (Ptr Word8)
forall (m :: * -> *) a. Monad m => a -> m a
return Ptr Word8
t
                      | Bool
otherwise = do
                          Word8
w <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
f
                          if Word8 -> Bool
k Word8
w
                            then Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
t Word8
w IO () -> IO (Ptr Word8) -> IO (Ptr Word8)
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO (Ptr Word8)
go (Ptr Word8
f Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) (Ptr Word8
t Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) Ptr Word8
end
                            else             Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO (Ptr Word8)
go (Ptr Word8
f Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) Ptr Word8
t               Ptr Word8
end
{-# 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 -> Word8 -> Maybe Word8
forall a. a -> Maybe a
Just (ByteString
p ByteString -> Int -> Word8
`unsafeIndex` Int
n)
                    Maybe Int
_      -> Maybe Word8
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 = IO (ByteString, ByteString) -> (ByteString, ByteString)
forall a. IO a -> a
unsafeDupablePerformIO (IO (ByteString, ByteString) -> (ByteString, ByteString))
-> IO (ByteString, ByteString) -> (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$
    do ForeignPtr Word8
fp' <- Int -> IO (ForeignPtr Word8)
forall a. Int -> IO (ForeignPtr a)
mallocByteString Int
len
       ForeignPtr Word8
-> (Ptr Word8 -> IO (ByteString, ByteString))
-> IO (ByteString, ByteString)
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
fp' ((Ptr Word8 -> IO (ByteString, ByteString))
 -> IO (ByteString, ByteString))
-> (Ptr Word8 -> IO (ByteString, ByteString))
-> IO (ByteString, ByteString)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
           do let end :: Ptr b
end = Ptr Word8
p Ptr Word8 -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
              Ptr Word8
mid <- Int -> Ptr Word8 -> Ptr Word8 -> IO (Ptr Word8)
sep Int
0 Ptr Word8
p Ptr Word8
forall a. Ptr a
end
              Ptr Word8 -> Ptr Word8 -> IO ()
forall b. Storable b => Ptr b -> Ptr b -> IO ()
rev Ptr Word8
mid Ptr Word8
forall a. Ptr a
end
              let i :: Int
i = Ptr Word8
mid Ptr Word8 -> Ptr Word8 -> Int
forall a b. Ptr a -> Ptr b -> Int
`minusPtr` Ptr Word8
p
              (ByteString, ByteString) -> IO (ByteString, ByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
fp' Int
0 Int
i,
                      ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
fp' Int
i (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i))
  where
    len :: Int
len  = ByteString -> Int
length ByteString
s
    incr :: Ptr a -> Ptr b
incr = (Ptr a -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1)
    decr :: Ptr a -> Ptr b
decr = (Ptr a -> Int -> Ptr b
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (-Int
1))

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

    rev :: Ptr b -> Ptr b -> IO ()
rev !Ptr b
p1 !Ptr b
p2
      | Ptr b
p1 Ptr b -> Ptr b -> Bool
forall a. Ord a => a -> a -> Bool
>= Ptr b
p2  = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
      | Bool
otherwise = do b
a <- Ptr b -> IO b
forall a. Storable a => Ptr a -> IO a
peek Ptr b
p1
                       b
b <- Ptr b -> IO b
forall a. Storable a => Ptr a -> IO a
peek Ptr b
p2
                       Ptr b -> b -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr b
p1 b
b
                       Ptr b -> b -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr b
p2 b
a
                       Ptr b -> Ptr b -> IO ()
rev (Ptr b -> Ptr b
forall a b. Ptr a -> Ptr b
incr Ptr b
p1) (Ptr b -> Ptr b
forall a b. Ptr a -> Ptr b
decr Ptr 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 (PS ForeignPtr Word8
x1 Int
s1 Int
l1) (PS ForeignPtr Word8
x2 Int
s2 Int
l2)
    | Int
l1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0   = Bool
True
    | Int
l2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
l1   = Bool
False
    | Bool
otherwise = IO Bool -> Bool
forall a. IO a -> a
accursedUnutterablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x1 ((Ptr Word8 -> IO Bool) -> IO Bool)
-> (Ptr Word8 -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p1 ->
        ForeignPtr Word8 -> (Ptr Word8 -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x2 ((Ptr Word8 -> IO Bool) -> IO Bool)
-> (Ptr Word8 -> IO Bool) -> IO Bool
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 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s1) (Ptr Word8
p2 Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s2) (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l1)
            Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$! CInt
i CInt -> CInt -> Bool
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@(PS ForeignPtr Word8
_ Int
_ Int
l1) ByteString
bs2
   | ByteString
bs1 ByteString -> ByteString -> Bool
`isPrefixOf` ByteString
bs2 = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Int -> ByteString -> ByteString
unsafeDrop Int
l1 ByteString
bs2)
   | Bool
otherwise = Maybe ByteString
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 implemenation uses memcmp to compare the end of the
-- string only, with no reverse required..
isSuffixOf :: ByteString -> ByteString -> Bool
isSuffixOf :: ByteString -> ByteString -> Bool
isSuffixOf (PS ForeignPtr Word8
x1 Int
s1 Int
l1) (PS ForeignPtr Word8
x2 Int
s2 Int
l2)
    | Int
l1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0   = Bool
True
    | Int
l2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
l1   = Bool
False
    | Bool
otherwise = IO Bool -> Bool
forall a. IO a -> a
accursedUnutterablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ ForeignPtr Word8 -> (Ptr Word8 -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x1 ((Ptr Word8 -> IO Bool) -> IO Bool)
-> (Ptr Word8 -> IO Bool) -> IO Bool
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p1 ->
        ForeignPtr Word8 -> (Ptr Word8 -> IO Bool) -> IO Bool
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x2 ((Ptr Word8 -> IO Bool) -> IO Bool)
-> (Ptr Word8 -> IO Bool) -> IO Bool
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 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s1) (Ptr Word8
p2 Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s2 Ptr Any -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
l1)) (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l1)
            Bool -> IO Bool
forall (m :: * -> *) a. Monad m => a -> m a
return (Bool -> IO Bool) -> Bool -> IO Bool
forall a b. (a -> b) -> a -> b
$! CInt
i CInt -> CInt -> Bool
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@(PS ForeignPtr Word8
_ Int
_ Int
l1) bs2 :: ByteString
bs2@(PS ForeignPtr Word8
_ Int
_ Int
l2)
   | ByteString
bs1 ByteString -> ByteString -> Bool
`isSuffixOf` ByteString
bs2 = ByteString -> Maybe ByteString
forall a. a -> Maybe a
Just (Int -> ByteString -> ByteString
unsafeTake (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
l1) ByteString
bs2)
   | Bool
otherwise = Maybe ByteString
forall a. Maybe a
Nothing

-- | Check whether one string is a substring of another. @isInfixOf
-- p s@ is equivalent to @not (null (findSubstrings p s))@.
isInfixOf :: ByteString -> ByteString -> Bool
isInfixOf :: ByteString -> ByteString -> Bool
isInfixOf ByteString
p ByteString
s = Maybe Int -> Bool
forall a. Maybe a -> Bool
isJust (ByteString -> ByteString -> Maybe Int
findSubstring ByteString
p ByteString
s)

-- | Break a string on a substring, returning a pair of the part of the
-- string prior to the match, and the rest of the string.
--
-- The following relationships hold:
--
-- > break (== c) l == breakSubstring (singleton c) l
--
-- and:
--
-- > findSubstring s l ==
-- >    if null s then Just 0
-- >              else case breakSubstring s l of
-- >                       (x,y) | null y    -> Nothing
-- >                             | otherwise -> Just (length x)
--
-- For example, to tokenise a string, dropping delimiters:
--
-- > tokenise x y = h : if null t then [] else tokenise x (drop (length x) t)
-- >     where (h,t) = breakSubstring x y
--
-- To skip to the first occurence of a string:
--
-- > snd (breakSubstring x y)
--
-- To take the parts of a string before a delimiter:
--
-- > fst (breakSubstring x y)
--
-- 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
src -> (ByteString
empty,ByteString
src)
    Int
1 -> Word8 -> ByteString -> (ByteString, ByteString)
breakByte (ByteString -> Word8
unsafeHead ByteString
pat)
    Int
_ -> if Int
lp Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Word -> Int
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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
lp = (ByteString
src,ByteString
empty)
        | Bool
otherwise = Word32 -> Int -> (ByteString, ByteString)
search (ByteString -> Word32
rollingHash (ByteString -> Word32) -> ByteString -> Word32
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 = (Word32 -> Word8 -> Word32) -> Word32 -> ByteString -> Word32
forall a. (a -> Word8 -> a) -> a -> ByteString -> a
foldl' (\Word32
h Word8
b -> Word32
h Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
* Word32
k Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+ Word8 -> Word32
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 Word32 -> Int -> Word32
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
lp
        get :: Int -> Word32
get = Word8 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Word32) -> (Int -> Word8) -> Int -> Word32
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 Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
== Word32
hs Bool -> Bool -> Bool
&& ByteString
pat ByteString -> ByteString -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> ByteString -> ByteString
unsafeTake Int
lp ByteString
b = (ByteString, ByteString)
u
            | ByteString -> Int
length ByteString
src Int -> Int -> Bool
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 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
          where
            u :: (ByteString, ByteString)
u@(ByteString
_, ByteString
b) = Int -> ByteString -> (ByteString, ByteString)
unsafeSplitAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) ByteString
src
            hs' :: Word32
hs' = Word32
hs Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
* Word32
k Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
+
                  Int -> Word32
get Int
i Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
-
                  Word32
m Word32 -> Word32 -> Word32
forall a. Num a => a -> a -> a
* Int -> Word32
get (Int
i Int -> Int -> Int
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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
lp = (ByteString
src,ByteString
empty)
        | Bool
otherwise       = Word -> Int -> (ByteString, ByteString)
search (ByteString -> Word
intoWord (ByteString -> Word) -> ByteString -> Word
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 = (Word -> Word8 -> Word) -> Word -> ByteString -> Word
forall a. (a -> Word8 -> a) -> a -> ByteString -> a
foldl' (\Word
w Word8
b -> (Word
w Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`shiftL` Int
8) Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word8 -> Word
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 Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`shiftL` (Int
8 Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
lp)) Word -> Word -> Word
forall a. Num a => a -> a -> a
- Word
1
        search :: Word -> Int -> (ByteString, ByteString)
search !Word
w !Int
i
            | Word
w Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== Word
wp         = Int -> ByteString -> (ByteString, ByteString)
unsafeSplitAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) ByteString
src
            | ByteString -> Int
length ByteString
src Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i = (ByteString
src, ByteString
empty)
            | Bool
otherwise       = Word -> Int -> (ByteString, ByteString)
search Word
w' (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
          where
            b :: Word
b  = Word8 -> Word
forall a b. (Integral a, Num b) => a -> b
fromIntegral (ByteString -> Int -> Word8
unsafeIndex ByteString
src Int
i)
            w' :: Word
w' = Word
mask Word -> Word -> Word
forall a. Bits a => a -> a -> a
.&. ((Word
w Word -> Int -> Word
forall a. Bits a => a -> Int -> a
`shiftL` Int
8) Word -> Word -> Word
forall a. Bits a => a -> a -> a
.|. Word
b)
    {-# INLINE shift #-}

-- | Get the first index of a substring in another string,
--   or 'Nothing' if the string is not found.
--   @findSubstring p s@ is equivalent to @listToMaybe (findSubstrings p s)@.
findSubstring :: ByteString -- ^ String to search for.
              -> ByteString -- ^ String to seach in.
              -> Maybe Int
findSubstring :: ByteString -> ByteString -> Maybe Int
findSubstring ByteString
pat ByteString
src
    | ByteString -> Bool
null ByteString
pat Bool -> Bool -> Bool
&& ByteString -> Bool
null ByteString
src = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
0
    | ByteString -> Bool
null ByteString
b = Maybe Int
forall a. Maybe a
Nothing
    | Bool
otherwise = Int -> Maybe Int
forall a. a -> Maybe a
Just (ByteString -> Int
length ByteString
a)
  where (ByteString
a, ByteString
b) = ByteString -> ByteString -> (ByteString, ByteString)
breakSubstring ByteString
pat ByteString
src

{-# DEPRECATED findSubstring "findSubstring is deprecated in favour of breakSubstring." #-}

-- | Find the indices of all non-overlapping occurences of a substring in a
-- string.
--
-- Note, prior to @0.10.6.0@ this function returned the indices of all
-- possibly-overlapping matches.
findSubstrings :: ByteString -- ^ String to search for.
               -> ByteString -- ^ String to seach in.
               -> [Int]
findSubstrings :: ByteString -> ByteString -> [Int]
findSubstrings ByteString
pat ByteString
src
    | ByteString -> Bool
null ByteString
pat        = [Int
0 .. Int
ls]
    | Bool
otherwise       = Int -> [Int]
search Int
0
  where
    lp :: Int
lp = ByteString -> Int
length ByteString
pat
    ls :: Int
ls = ByteString -> Int
length ByteString
src
    search :: Int -> [Int]
search !Int
n
        | (Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
ls Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) Bool -> Bool -> Bool
|| ByteString -> Bool
null ByteString
b = []
        | Bool
otherwise = let k :: Int
k = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ ByteString -> Int
length ByteString
a
                      in  Int
k Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: Int -> [Int]
search (Int
k Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
lp)
      where
        (ByteString
a, ByteString
b) = ByteString -> ByteString -> (ByteString, ByteString)
breakSubstring ByteString
pat (Int -> ByteString -> ByteString
unsafeDrop Int
n ByteString
src)

-- In
-- [0.10.6.0](<https://github.com/haskell/bytestring/commit/2160e091e215fecc9177d55a37cd50fc253ba86a?w=1>)
-- 'findSubstrings' was refactored to call an improved 'breakString'
-- implementation, but the refactored code no longer matches overlapping
-- strings.  The behaviour change appears to be inadvertent, but the function
-- had already been deprecated for more than seven years.  At this time
-- (@0.10.10.1@), the deprecation was twelve years in the past.
--
{-# DEPRECATED findSubstrings "findSubstrings is deprecated in favour of breakSubstring." #-}

-- ---------------------------------------------------------------------
-- 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
    | ByteString -> Bool
null ByteString
ps Bool -> Bool -> Bool
|| ByteString -> Bool
null ByteString
qs = []
    | Bool
otherwise = (ByteString -> Word8
unsafeHead ByteString
ps, ByteString -> Word8
unsafeHead ByteString
qs) (Word8, Word8) -> [(Word8, Word8)] -> [(Word8, Word8)]
forall a. a -> [a] -> [a]
: ByteString -> ByteString -> [(Word8, Word8)]
zip (ByteString -> ByteString
unsafeTail ByteString
ps) (ByteString -> ByteString
unsafeTail ByteString
qs)

-- | '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 :: (Word8 -> Word8 -> a) -> ByteString -> ByteString -> [a]
zipWith Word8 -> Word8 -> a
f ByteString
ps ByteString
qs
    | ByteString -> Bool
null ByteString
ps Bool -> Bool -> Bool
|| ByteString -> Bool
null ByteString
qs = []
    | Bool
otherwise = Word8 -> Word8 -> a
f (ByteString -> Word8
unsafeHead ByteString
ps) (ByteString -> Word8
unsafeHead ByteString
qs) a -> [a] -> [a]
forall a. a -> [a] -> [a]
: (Word8 -> Word8 -> a) -> ByteString -> ByteString -> [a]
forall a. (Word8 -> Word8 -> a) -> ByteString -> ByteString -> [a]
zipWith Word8 -> Word8 -> a
f (ByteString -> ByteString
unsafeTail ByteString
ps) (ByteString -> ByteString
unsafeTail ByteString
qs)
{-# NOINLINE [1] zipWith #-}

--
-- | A specialised version of zipWith for the common case of a
-- simultaneous map over two bytestrings, to build a 3rd. Rewrite rules
-- are used to automatically covert zipWith into zipWith' when a pack is
-- performed on the result of zipWith.
--
zipWith' :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString -> ByteString
zipWith' :: (Word8 -> Word8 -> Word8) -> ByteString -> ByteString -> ByteString
zipWith' Word8 -> Word8 -> Word8
f (PS ForeignPtr Word8
fp Int
s Int
l) (PS ForeignPtr Word8
fq Int
t Int
m) = IO ByteString -> ByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO ByteString -> ByteString) -> IO ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$
    ForeignPtr Word8 -> (Ptr Word8 -> IO ByteString) -> IO ByteString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
fp ((Ptr Word8 -> IO ByteString) -> IO ByteString)
-> (Ptr Word8 -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
a ->
    ForeignPtr Word8 -> (Ptr Word8 -> IO ByteString) -> IO ByteString
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
fq ((Ptr Word8 -> IO ByteString) -> IO ByteString)
-> (Ptr Word8 -> IO ByteString) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
b ->
    Int -> (Ptr Word8 -> IO ()) -> IO ByteString
create Int
len ((Ptr Word8 -> IO ()) -> IO ByteString)
-> (Ptr Word8 -> IO ()) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ Int -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO ()
zipWith_ Int
0 (Ptr Word8
a Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) (Ptr Word8
b Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
t)
  where
    zipWith_ :: Int -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO ()
    zipWith_ :: Int -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO ()
zipWith_ !Int
n !Ptr Word8
p1 !Ptr Word8
p2 !Ptr Word8
r
       | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
len = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
       | Bool
otherwise = do
            Word8
x <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
p1 Int
n
            Word8
y <- Ptr Word8 -> Int -> IO Word8
forall a b. Storable a => Ptr b -> Int -> IO a
peekByteOff Ptr Word8
p2 Int
n
            Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
r Int
n (Word8 -> Word8 -> Word8
f Word8
x Word8
y)
            Int -> Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> IO ()
zipWith_ (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Ptr Word8
p1 Ptr Word8
p2 Ptr Word8
r

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

{-# RULES
"ByteString specialise zipWith" forall (f :: Word8 -> Word8 -> Word8) p q .
    zipWith f p q = unpack (zipWith' 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 (((Word8, Word8) -> Word8) -> [(Word8, Word8)] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
P.map (Word8, Word8) -> Word8
forall a b. (a, b) -> a
fst [(Word8, Word8)]
ls), [Word8] -> ByteString
pack (((Word8, Word8) -> Word8) -> [(Word8, Word8)] -> [Word8]
forall a b. (a -> b) -> [a] -> [b]
P.map (Word8, Word8) -> Word8
forall a b. (a, b) -> b
snd [(Word8, Word8)]
ls))
{-# INLINE unzip #-}

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

-- | /O(n)/ Return all initial segments of the given 'ByteString', shortest first.
inits :: ByteString -> [ByteString]
inits :: ByteString -> [ByteString]
inits (PS ForeignPtr Word8
x Int
s Int
l) = [ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
x Int
s Int
n | Int
n <- [Int
0..Int
l]]

-- | /O(n)/ Return all final segments of the given 'ByteString', longest first.
tails :: ByteString -> [ByteString]
tails :: ByteString -> [ByteString]
tails ByteString
p | ByteString -> Bool
null ByteString
p    = [ByteString
empty]
        | Bool
otherwise = ByteString
p ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: ByteString -> [ByteString]
tails (ByteString -> ByteString
unsafeTail ByteString
p)

-- less efficent spacewise: tails (PS x s l) = [PS x (s+n) (l-n) | n <- [0..l]]

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

-- | /O(n)/ Sort a ByteString efficiently, using counting sort.
sort :: ByteString -> ByteString
sort :: ByteString -> ByteString
sort (PS ForeignPtr Word8
input Int
s Int
l) = Int -> (Ptr Word8 -> IO ()) -> ByteString
unsafeCreate Int
l ((Ptr Word8 -> IO ()) -> ByteString)
-> (Ptr Word8 -> IO ()) -> ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Int -> (Ptr CSize -> IO ()) -> IO ()
forall a b. Storable a => Int -> (Ptr a -> IO b) -> IO b
allocaArray Int
256 ((Ptr CSize -> IO ()) -> IO ()) -> (Ptr CSize -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr CSize
arr -> do

    Ptr Word8
_ <- Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
memset (Ptr CSize -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr Ptr CSize
arr) Word8
0 (CSize
256 CSize -> CSize -> CSize
forall a. Num a => a -> a -> a
* Int -> CSize
forall a b. (Integral a, Num b) => a -> b
fromIntegral (CSize -> Int
forall a. Storable a => a -> Int
sizeOf (CSize
forall a. (?callStack::CallStack) => a
undefined :: CSize)))
    ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
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 Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) Int
l)

    let go :: Int -> Ptr Word8 -> IO ()
go Int
256 !Ptr Word8
_   = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
        go Int
i   !Ptr Word8
ptr = do CSize
n <- Ptr CSize -> Int -> IO CSize
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr CSize
arr Int
i
                         Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (CSize
n CSize -> CSize -> Bool
forall a. Eq a => a -> a -> Bool
/= CSize
0) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Ptr Word8 -> Word8 -> CSize -> IO (Ptr Word8)
memset Ptr Word8
ptr (Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i) CSize
n IO (Ptr Word8) -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
                         Int -> Ptr Word8 -> IO ()
go (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1) (Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` CSize -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CSize
n)
    Int -> Ptr Word8 -> IO ()
go Int
0 Ptr Word8
p
  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 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
len    = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
              | Bool
otherwise = do Int
k <- Word8 -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word8 -> Int) -> IO Word8 -> IO Int
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` Ptr Word8 -> Int -> IO Word8
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr Word8
str Int
i
                               CSize
x <- Ptr CSize -> Int -> IO CSize
forall a. Storable a => Ptr a -> Int -> IO a
peekElemOff Ptr CSize
counts Int
k
                               Ptr CSize -> Int -> CSize -> IO ()
forall a. Storable a => Ptr a -> Int -> a -> IO ()
pokeElemOff Ptr CSize
counts Int
k (CSize
x CSize -> CSize -> CSize
forall a. Num a => a -> a -> a
+ CSize
1)
                               Int -> IO ()
go (Int
i Int -> Int -> Int
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 :: ByteString -> (CString -> IO a) -> IO a
useAsCString (PS ForeignPtr Word8
fp Int
o Int
l) CString -> IO a
action =
 Int -> (Ptr Word8 -> IO a) -> IO a
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes (Int
lInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) ((Ptr Word8 -> IO a) -> IO a) -> (Ptr Word8 -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
buf ->
   ForeignPtr Word8 -> (Ptr Word8 -> IO a) -> IO a
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
fp ((Ptr Word8 -> IO a) -> IO a) -> (Ptr Word8 -> IO a) -> IO a
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> do
     Ptr Word8 -> Ptr Word8 -> Int -> IO ()
memcpy Ptr Word8
buf (Ptr Word8
p Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
o) (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l)
     Ptr Word8 -> Int -> Word8 -> IO ()
forall a b. Storable a => Ptr b -> Int -> a -> IO ()
pokeByteOff Ptr Word8
buf Int
l (Word8
0::Word8)
     CString -> IO a
action (Ptr Word8 -> CString
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 :: ByteString -> (CStringLen -> IO a) -> IO a
useAsCStringLen p :: ByteString
p@(PS ForeignPtr Word8
_ Int
_ Int
l) CStringLen -> IO a
f = ByteString -> (CString -> IO a) -> IO a
forall a. ByteString -> (CString -> IO a) -> IO a
useAsCString ByteString
p ((CString -> IO a) -> IO a) -> (CString -> IO a) -> IO a
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, CSize -> Int
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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 = Int -> (Ptr Word8 -> IO ()) -> IO ByteString
create Int
len ((Ptr Word8 -> IO ()) -> IO ByteString)
-> (Ptr Word8 -> IO ()) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
    Ptr Word8 -> Ptr Word8 -> Int -> IO ()
memcpy Ptr Word8
p (CString -> Ptr Word8
forall a b. Ptr a -> Ptr b
castPtr CString
cstr) (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len)
packCStringLen (CString
_, Int
len) =
    String -> String -> IO ByteString
forall a. String -> String -> IO a
moduleErrorIO String
"packCStringLen" (String
"negative length: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Int -> String
forall a. Show a => a -> String
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 (PS ForeignPtr Word8
x Int
s Int
l) = Int -> (Ptr Word8 -> IO ()) -> ByteString
unsafeCreate Int
l ((Ptr Word8 -> IO ()) -> ByteString)
-> (Ptr Word8 -> IO ()) -> ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
f ->
    Ptr Word8 -> Ptr Word8 -> Int -> IO ()
memcpy Ptr Word8
p (Ptr Word8
f Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral 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 =
  String -> Handle -> (Handle__ -> IO ByteString) -> IO ByteString
forall a. String -> Handle -> (Handle__ -> IO a) -> IO a
wantReadableHandle_ String
"Data.ByteString.hGetLine" Handle
h ((Handle__ -> IO ByteString) -> IO ByteString)
-> (Handle__ -> IO ByteString) -> IO ByteString
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 <- IORef (Buffer Word8) -> IO (Buffer Word8)
forall a. IORef a -> IO a
readIORef IORef (Buffer Word8)
haByteBuffer
      if Buffer Word8 -> Bool
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') <- dev -> Buffer Word8 -> IO (Int, Buffer Word8)
forall dev.
BufferedIO dev =>
dev -> Buffer Word8 -> IO (Int, Buffer Word8)
Buffered.fillReadBuffer dev
haDevice Buffer Word8
buf
    if Int
r Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
       then do IORef (Buffer Word8) -> Buffer Word8 -> IO ()
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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
                  then Int -> [ByteString] -> IO ByteString
mkBigPS Int
len [ByteString]
xss
                  else IO ByteString
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=raw, bufR=w, bufL=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 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
off Int -> Int -> Int
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 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
w
            then do if Int
w Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
                            then IORef (Buffer Word8) -> Buffer Word8 -> IO ()
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 IORef (Buffer Word8) -> Buffer Word8 -> IO ()
forall a. IORef a -> a -> IO ()
writeIORef IORef (Buffer Word8)
haByteBuffer Buffer Word8
buf{ bufL :: Int
bufL = Int
off Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 }
                    Int -> [ByteString] -> IO ByteString
mkBigPS Int
new_len (ByteString
xsByteString -> [ByteString] -> [ByteString]
forall 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
xsByteString -> [ByteString] -> [ByteString]
forall 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 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
w = Int -> IO Int
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 Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> Word8
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Char -> Int
ord Char
'\n')
                then Int -> IO Int
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
rInt -> Int -> Int
forall 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 -> (Ptr Word8 -> IO ()) -> IO ByteString
create Int
len ((Ptr Word8 -> IO ()) -> IO ByteString)
-> (Ptr Word8 -> IO ()) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p ->
   ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withRawBuffer ForeignPtr Word8
buf ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
pbuf -> Ptr Word8 -> Ptr Word8 -> Int -> IO ()
forall a. Ptr a -> Ptr a -> Int -> IO ()
copyBytes Ptr Word8
p (Ptr Word8
pbuf Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
start) Int
len
 where
   len :: Int
len = Int
end Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
start

mkBigPS :: Int -> [ByteString] -> IO ByteString
mkBigPS :: Int -> [ByteString] -> IO ByteString
mkBigPS Int
_ [ByteString
ps] = ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
ps
mkBigPS Int
_ [ByteString]
pss = ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$! [ByteString] -> ByteString
concat ([ByteString] -> [ByteString]
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
_ (PS ForeignPtr Word8
_  Int
_ Int
0) = () -> IO ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
hPut Handle
h (PS ForeignPtr Word8
ps Int
s Int
l) = ForeignPtr Word8 -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
ps ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p-> Handle -> Ptr Any -> Int -> IO ()
forall a. Handle -> Ptr a -> Int -> IO ()
hPutBuf Handle
h (Ptr Word8
p Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) 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@(PS ForeignPtr Word8
ps Int
s Int
l) = do
  Int
bytesWritten <- ForeignPtr Word8 -> (Ptr Word8 -> IO Int) -> IO Int
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
ps ((Ptr Word8 -> IO Int) -> IO Int)
-> (Ptr Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p-> Handle -> Ptr Any -> Int -> IO Int
forall a. Handle -> Ptr a -> Int -> IO Int
hPutBufNonBlocking Handle
h (Ptr Word8
p Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) Int
l
  ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
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 a handle, appending a newline byte
hPutStrLn :: Handle -> ByteString -> IO ()
hPutStrLn :: Handle -> ByteString -> IO ()
hPutStrLn Handle
h ByteString
ps
    | ByteString -> Int
length ByteString
ps Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
1024 = Handle -> ByteString -> IO ()
hPut Handle
h (ByteString
ps ByteString -> Word8 -> ByteString
`snoc` Word8
0x0a)
    | Bool
otherwise        = Handle -> ByteString -> IO ()
hPut Handle
h ByteString
ps IO () -> IO () -> IO ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Handle -> ByteString -> IO ()
hPut Handle
h (Word8 -> ByteString
singleton (Word8
0x0a)) -- don't copy

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

-- | Write a ByteString to stdout, appending a newline byte
putStrLn :: ByteString -> IO ()
putStrLn :: ByteString -> IO ()
putStrLn = Handle -> ByteString -> IO ()
hPutStrLn Handle
stdout

{-# DEPRECATED hPutStrLn
    "Use Data.ByteString.Char8.hPutStrLn instead. (Functions that rely on ASCII encodings belong in Data.ByteString.Char8)"
  #-}
{-# DEPRECATED putStrLn
    "Use Data.ByteString.Char8.putStrLn instead. (Functions that rely on ASCII encodings belong in Data.ByteString.Char8)"
  #-}

------------------------------------------------------------------------
-- 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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>  Int
0    = Int -> (Ptr Word8 -> IO Int) -> IO ByteString
createAndTrim Int
i ((Ptr Word8 -> IO Int) -> IO ByteString)
-> (Ptr Word8 -> IO Int) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Handle -> Ptr Word8 -> Int -> IO Int
forall a. Handle -> Ptr a -> Int -> IO Int
hGetBuf Handle
h Ptr Word8
p Int
i
    | Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0    = ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
empty
    | Bool
otherwise = Handle -> String -> Int -> IO ByteString
forall a. Handle -> String -> Int -> IO a
illegalBufferSize Handle
h String
"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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>  Int
0    = Int -> (Ptr Word8 -> IO Int) -> IO ByteString
createAndTrim Int
i ((Ptr Word8 -> IO Int) -> IO ByteString)
-> (Ptr Word8 -> IO Int) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Handle -> Ptr Word8 -> Int -> IO Int
forall a. Handle -> Ptr a -> Int -> IO Int
hGetBufNonBlocking Handle
h Ptr Word8
p Int
i
    | Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0    = ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
empty
    | Bool
otherwise = Handle -> String -> Int -> IO ByteString
forall a. Handle -> String -> Int -> IO a
illegalBufferSize Handle
h String
"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
#if MIN_VERSION_base(4,3,0)
    | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>  Int
0    = Int -> (Ptr Word8 -> IO Int) -> IO ByteString
createAndTrim Int
i ((Ptr Word8 -> IO Int) -> IO ByteString)
-> (Ptr Word8 -> IO Int) -> IO ByteString
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p -> Handle -> Ptr Word8 -> Int -> IO Int
forall a. Handle -> Ptr a -> Int -> IO Int
hGetBufSome Handle
hh Ptr Word8
p Int
i
#else
    | i >  0    = let
                   loop = do
                     s <- hGetNonBlocking hh i
                     if not (null s)
                        then return s
                        else do eof <- hIsEOF hh
                                if eof then return s
                                       else hWaitForInput hh (-1) >> loop
                                         -- for this to work correctly, the
                                         -- Handle should be in binary mode
                                         -- (see GHC ticket #3808)
                  in loop
#endif
    | Int
i Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0    = ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return ByteString
empty
    | Bool
otherwise = Handle -> String -> Int -> IO ByteString
forall a. Handle -> String -> Int -> IO a
illegalBufferSize Handle
hh String
"hGetSome" Int
i

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


-- | Read 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
            IO ByteString -> IO () -> IO ByteString
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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
900
      then ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$! ByteString -> ByteString
copy ByteString
bs
      else ByteString -> IO ByteString
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        <- Int -> IO (ForeignPtr Word8)
forall a. Int -> IO (ForeignPtr a)
mallocByteString Int
sz
      Int
readcount <- ForeignPtr Word8 -> (Ptr Word8 -> IO Int) -> IO Int
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
unsafeWithForeignPtr ForeignPtr Word8
fp ((Ptr Word8 -> IO Int) -> IO Int)
-> (Ptr Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
buf -> Handle -> Ptr Word8 -> Int -> IO Int
forall a. Handle -> Ptr a -> Int -> IO Int
hGetBuf Handle
hnd Ptr Word8
buf Int
sz
      let chunk :: ByteString
chunk = ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
fp Int
0 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 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
sz Bool -> Bool -> Bool
&& Int
sz Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
        then ByteString -> IO ByteString
forall (m :: * -> *) a. Monad m => a -> m a
return (ByteString -> IO ByteString) -> ByteString -> IO ByteString
forall a b. (a -> b) -> a -> b
$! [ByteString] -> ByteString
concat ([ByteString] -> [ByteString]
forall a. [a] -> [a]
P.reverse (ByteString
chunk ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: [ByteString]
chunks))
        else [ByteString] -> Int -> Int -> IO ByteString
readChunks (ByteString
chunk ByteString -> [ByteString] -> [ByteString]
forall a. a -> [a] -> [a]
: [ByteString]
chunks) Int
sz' ((Int
szInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
sz') Int -> Int -> Int
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 (ByteString -> IO ())
-> (ByteString -> ByteString) -> ByteString -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
transformer (ByteString -> IO ()) -> IO ByteString -> IO ()
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< IO ByteString
getContents

-- | Read an entire file strictly into a 'ByteString'.
--
readFile :: FilePath -> IO ByteString
readFile :: String -> IO ByteString
readFile String
f =
    String -> IOMode -> (Handle -> IO ByteString) -> IO ByteString
forall r. String -> IOMode -> (Handle -> IO r) -> IO r
withBinaryFile String
f IOMode
ReadMode ((Handle -> IO ByteString) -> IO ByteString)
-> (Handle -> IO ByteString) -> IO ByteString
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 <- IO Integer -> (IOError -> IO Integer) -> IO Integer
forall e a. Exception e => IO a -> (e -> IO a) -> IO a
catch (Handle -> IO Integer
hFileSize Handle
h) IOError -> IO Integer
useZeroIfNotRegularFile
      let readsz :: Int
readsz = (Integer -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Integer
filesz Int -> Int -> Int
forall a. Ord a => a -> a -> a
`max` Int
0) Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
      Handle -> Int -> Int -> IO ByteString
hGetContentsSizeHint Handle
h Int
readsz (Int
readsz Int -> Int -> Int
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 :: IOError -> IO Integer
useZeroIfNotRegularFile IOError
_ = Integer -> IO Integer
forall (m :: * -> *) a. Monad m => a -> m a
return Integer
0

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

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

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

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

-- | 'findIndexOrEnd' is a variant of findIndex, that returns the length
-- of the string if no element is found, rather than Nothing.
findIndexOrEnd :: (Word8 -> Bool) -> ByteString -> Int
findIndexOrEnd :: (Word8 -> Bool) -> ByteString -> Int
findIndexOrEnd Word8 -> Bool
k (PS ForeignPtr Word8
x Int
s Int
l) =
    IO Int -> Int
forall a. IO a -> a
accursedUnutterablePerformIO (IO Int -> Int) -> IO Int -> Int
forall a b. (a -> b) -> a -> b
$
      ForeignPtr Word8 -> (Ptr Word8 -> IO Int) -> IO Int
forall a b. ForeignPtr a -> (Ptr a -> IO b) -> IO b
withForeignPtr ForeignPtr Word8
x ((Ptr Word8 -> IO Int) -> IO Int)
-> (Ptr Word8 -> IO Int) -> IO Int
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
f ->
        Ptr Word8 -> Int -> IO Int
go (Ptr Word8
f Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
s) Int
0
  where
    go :: Ptr Word8 -> Int -> IO Int
go !Ptr Word8
ptr !Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l    = Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
l
               | Bool
otherwise = do Word8
w <- Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
ptr
                                if Word8 -> Bool
k Word8
w
                                  then Int -> IO Int
forall (m :: * -> *) a. Monad m => a -> m a
return Int
n
                                  else Ptr Word8 -> Int -> IO Int
go (Ptr Word8
ptr Ptr Word8 -> Int -> Ptr Word8
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1) (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1)
{-# INLINE findIndexOrEnd #-}

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

moduleError :: String -> String -> a
moduleError :: String -> String -> a
moduleError String
fun String
msg = String -> a
forall a. (?callStack::CallStack) => String -> a
error (String -> String -> String
moduleErrorMsg String
fun String
msg)
{-# NOINLINE moduleError #-}

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

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

-- 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@(PS ForeignPtr Word8
x Int
s Int
l)
  | ByteString -> Bool
null ByteString
ps = Int
0
  | Word8 -> Bool
f (ByteString -> Word8
unsafeLast ByteString
ps) = Int
l
  | Bool
otherwise = (Word8 -> Bool) -> ByteString -> Int
findFromEndUntil Word8 -> Bool
f (ForeignPtr Word8 -> Int -> Int -> ByteString
PS ForeignPtr Word8
x Int
s (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1))