{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MagicHash #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE UnliftedFFITypes #-}
{-# LANGUAGE PackageImports #-}

module Data.ByteString.Short
  (
  -- * Types
  ShortByteString,

  -- * Introducing and eliminating 'ShortByteString's
  empty,
  singleton,
  pack,
  unpack,
  fromShort,
  toShort,

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

  -- * Transforming ShortByteStrings
  map,
  reverse,
  intercalate,

  -- * Reducing 'ShortByteString's (folds)
  foldl,
  foldl',
  foldl1,
  foldl1',

  foldr,
  foldr',
  foldr1,
  foldr1',

  -- ** Special folds
  all,
  any,
  concat,

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

  -- * Substrings

  -- ** Breaking strings
  take,
  takeEnd,
  takeWhileEnd,
  takeWhile,
  drop,
  dropEnd,
  dropWhile,
  dropWhileEnd,
  breakEnd,
  break,
  span,
  spanEnd,
  splitAt,
  split,
  splitWith,
  stripSuffix,
  stripPrefix,

  -- * Predicates
  isInfixOf,
  isPrefixOf,
  isSuffixOf,

  -- ** Search for arbitrary substrings
  breakSubstring,

  -- * Searching ShortByteStrings

  -- ** Searching by equality
  elem,

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

  -- * Indexing ShortByteStrings
  index,
  indexMaybe,
  (!?),
  elemIndex,
  elemIndices,
  count,
  findIndex,
  findIndices,

  -- * Low level conversions
  -- ** Packing 'CString's and pointers
  packCString,
  packCStringLen,

  -- ** Using ShortByteStrings as 'CString's
  useAsCString,
  useAsCStringLen,
  )
where

import Prelude hiding
    ( all
    , any
    , break
    , concat
    , drop
    , dropWhile
    , elem
    , filter
    , foldl
    , foldl1
    , foldr
    , foldr1
    , head
    , init
    , last
    , length
    , map
    , reverse
    , null
    , replicate
    , span
    , splitAt
    , tail
    , take
    , takeWhile
    )

import "bytestring" Data.ByteString.Short.Internal
import Data.ByteString.Short.Internal
import Data.Word8

import qualified "bytestring" Data.ByteString.Short as BS
import qualified "bytestring" Data.ByteString.Short.Internal as BS


import Data.ByteString.Internal
    ( memcmp )
import Foreign.Marshal.Alloc
  ( mallocBytes, free )
import GHC.List (errorEmptyList)
import Data.Bifunctor
    ( first, bimap )
import qualified Data.List as List
import qualified Data.Foldable as Foldable
import Foreign.Ptr

import GHC.Exts
import GHC.IO
import GHC.ST
    ( ST (ST) )
import GHC.Word
import Data.Bits
    ( FiniteBits (finiteBitSize), shiftL, (.&.), (.|.) )


-- $setup
-- >>> :set -XPackageImports
-- >>> import "shortbytestring" Data.ByteString.Short

-- -----------------------------------------------------------------------------
-- Introducing and eliminating 'ShortByteString's

-- | /O(1)/ Convert a 'Word8' into a 'ShortByteString'
singleton :: Word8 -> ShortByteString
singleton :: Word8 -> ShortByteString
singleton = \Word8
w -> Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
1 (\MBA s
mba -> MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba Int
0 Word8
w)
{-# INLINE [1] singleton #-}


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

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

-- | /O(n)/ Append a byte to the end of a 'ShortByteString'
-- 
-- Note: copies the entire byte array
snoc :: ShortByteString -> Word8 -> ShortByteString
snoc :: ShortByteString -> Word8 -> ShortByteString
snoc = \ShortByteString
sbs Word8
c -> let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
                     nl :: Int
nl = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
  in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> do
      BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
0 Int
l
      MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba Int
l Word8
c
{-# INLINE snoc #-}

-- | /O(n)/ 'cons' is analogous to (:) for lists.
--
-- Note: copies the entire byte array
cons :: Word8 -> ShortByteString -> ShortByteString
cons :: Word8 -> ShortByteString -> ShortByteString
cons Word8
c = \ShortByteString
sbs -> let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
                     nl :: Int
nl = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
  in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> do
      MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba Int
0 Word8
c
      BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
1 Int
l
{-# INLINE cons #-}

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

-- | /O(1)/ Extract the last element of a ShortByteString, which must be finite and non-empty.
-- An exception will be thrown in the case of an empty ShortByteString.
last :: ShortByteString -> Word8
last :: ShortByteString -> Word8
last = \ShortByteString
sbs -> case ShortByteString -> Bool
BS.null ShortByteString
sbs of
  Bool
True -> [Char] -> Word8
forall a. HasCallStack => [Char] -> a
error [Char]
"empty ShortByteString"
  Bool
False -> BA -> Int -> Word8
indexWord8Array (ShortByteString -> BA
asBA ShortByteString
sbs) (ShortByteString -> Int
BS.length ShortByteString
sbs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
{-# INLINE last #-}

-- | /O(n)/ Extract the elements after the head of a ShortByteString, which must be non-empty.
-- An exception will be thrown in the case of an empty ShortByteString.
--
-- Note: copies the entire byte array
tail :: ShortByteString -> ShortByteString
tail :: ShortByteString -> ShortByteString
tail = \ShortByteString
sbs -> 
  let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
      nl :: Int
nl = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
  in case ShortByteString -> Bool
BS.null ShortByteString
sbs of
      Bool
True -> [Char] -> ShortByteString
forall a. HasCallStack => [Char] -> a
error [Char]
"empty ShortByteString"
      Bool
False -> Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
1 MBA s
mba Int
0 Int
nl
{-# INLINE tail #-}

-- | /O(1)/ Extract the first element of a ShortByteString, which must be non-empty.
-- An exception will be thrown in the case of an empty ShortByteString.
head :: ShortByteString -> Word8
head :: ShortByteString -> Word8
head = \ShortByteString
sbs -> case ShortByteString -> Bool
BS.null ShortByteString
sbs of
  Bool
True -> [Char] -> Word8
forall a. HasCallStack => [Char] -> a
error [Char]
"empty ShortByteString"
  Bool
False -> BA -> Int -> Word8
indexWord8Array (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0
{-# INLINE head #-}

-- | /O(n)/ Return all the elements of a 'ShortByteString' except the last one.
-- An exception will be thrown in the case of an empty ShortByteString.
--
-- Note: copies the entire byte array
init :: ShortByteString -> ShortByteString
init :: ShortByteString -> ShortByteString
init = \ShortByteString
sbs ->
  let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
      nl :: Int
nl = Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1
  in case ShortByteString -> Bool
BS.null ShortByteString
sbs of
      Bool
True -> [Char] -> ShortByteString
forall a. HasCallStack => [Char] -> a
error [Char]
"empty ShortByteString"
      Bool
False -> Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
0 Int
nl
{-# INLINE init #-}


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

-- | /O(n)/ 'map' @f xs@ is the ShortByteString obtained by applying @f@ to each
-- element of @xs@.
map :: (Word8 -> Word8) -> ShortByteString -> ShortByteString
map :: (Word8 -> Word8) -> ShortByteString -> ShortByteString
map Word8 -> Word8
f = \ShortByteString
sbs ->
    let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
        ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
    in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
l (\MBA s
mba -> BA -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> MBA s -> Int -> Int -> ST s ()
go BA
ba MBA s
mba Int
0 Int
l)
  where
    go :: BA -> MBA s -> Int -> Int -> ST s ()
    go :: BA -> MBA s -> Int -> Int -> ST s ()
go !BA
ba !MBA s
mba !Int
i !Int
l
      | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l = () -> ST s ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
      | Bool
otherwise = do
          let w :: Word8
w = BA -> Int -> Word8
indexWord8Array BA
ba Int
i
          MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba Int
i (Word8 -> Word8
f Word8
w)
          BA -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> MBA s -> Int -> Int -> ST s ()
go BA
ba MBA s
mba (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
l


-- | /O(n)/ 'reverse' @xs@ efficiently returns the elements of @xs@ in reverse order.
reverse :: ShortByteString -> ShortByteString
reverse :: ShortByteString -> ShortByteString
reverse = \ShortByteString
sbs ->
    let l :: Int
l = ShortByteString -> Int
length ShortByteString
sbs
        ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
    in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
l (\MBA s
mba -> BA -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> MBA s -> Int -> Int -> ST s ()
go BA
ba MBA s
mba Int
0 Int
l)
  where
    go :: BA -> MBA s -> Int -> Int -> ST s ()
    go :: BA -> MBA s -> Int -> Int -> ST s ()
go !BA
ba !MBA s
mba !Int
i !Int
l
      | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l = () -> ST s ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
      | Bool
otherwise = do
          let w :: Word8
w = BA -> Int -> Word8
indexWord8Array BA
ba Int
i
          MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba (Int
l Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
i) Word8
w
          BA -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> MBA s -> Int -> Int -> ST s ()
go BA
ba MBA s
mba (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Int
l


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


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

-- | 'foldl', applied to a binary operator, a starting value (typically
-- the left-identity of the operator), and a ShortByteString, reduces the
-- ShortByteString using the binary operator, from left to right.
--
foldl :: (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl :: (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl a -> Word8 -> a
f a
v = (a -> Word8 -> a) -> a -> [Word8] -> a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl a -> Word8 -> a
f a
v ([Word8] -> a)
-> (ShortByteString -> [Word8]) -> ShortByteString -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
unpack
{-# INLINE foldl #-}

-- | 'foldl'' is like 'foldl', but strict in the accumulator.
--
foldl' :: (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl' :: (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl' a -> Word8 -> a
f a
v = (a -> Word8 -> a) -> a -> [Word8] -> a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' a -> Word8 -> a
f a
v ([Word8] -> a)
-> (ShortByteString -> [Word8]) -> ShortByteString -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
unpack
{-# INLINE foldl' #-}

-- | 'foldr', applied to a binary operator, a starting value
-- (typically the right-identity of the operator), and a ShortByteString,
-- reduces the ShortByteString using the binary operator, from right to left.
foldr :: (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr :: (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr Word8 -> a -> a
f a
v = (Word8 -> a -> a) -> a -> [Word8] -> a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
List.foldr Word8 -> a -> a
f a
v ([Word8] -> a)
-> (ShortByteString -> [Word8]) -> ShortByteString -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
unpack
{-# INLINE foldr #-}

-- | 'foldr'' is like 'foldr', but strict in the accumulator.
foldr' :: (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr' :: (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr' Word8 -> a -> a
k a
v = (Word8 -> a -> a) -> a -> [Word8] -> a
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Foldable.foldr' Word8 -> a -> a
k a
v ([Word8] -> a)
-> (ShortByteString -> [Word8]) -> ShortByteString -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
unpack
{-# INLINE foldr' #-}

-- | 'foldl1' is a variant of 'foldl' that has no starting value
-- argument, and thus must be applied to non-empty 'ShortByteString's.
-- An exception will be thrown in the case of an empty ShortByteString.
foldl1 :: (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldl1 :: (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldl1 Word8 -> Word8 -> Word8
k = (Word8 -> Word8 -> Word8) -> [Word8] -> Word8
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
List.foldl1 Word8 -> Word8 -> Word8
k ([Word8] -> Word8)
-> (ShortByteString -> [Word8]) -> ShortByteString -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
unpack
{-# INLINE foldl1 #-}

-- | 'foldl1'' is like 'foldl1', but strict in the accumulator.
-- An exception will be thrown in the case of an empty ShortByteString.
foldl1' :: (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldl1' :: (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldl1' Word8 -> Word8 -> Word8
k = (Word8 -> Word8 -> Word8) -> [Word8] -> Word8
forall a. (a -> a -> a) -> [a] -> a
List.foldl1' Word8 -> Word8 -> Word8
k ([Word8] -> Word8)
-> (ShortByteString -> [Word8]) -> ShortByteString -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
unpack

-- | 'foldr1' is a variant of 'foldr' that has no starting value argument,
-- and thus must be applied to non-empty 'ShortByteString's
-- An exception will be thrown in the case of an empty ShortByteString.
foldr1 :: (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldr1 :: (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldr1 Word8 -> Word8 -> Word8
k = (Word8 -> Word8 -> Word8) -> [Word8] -> Word8
forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
List.foldr1 Word8 -> Word8 -> Word8
k ([Word8] -> Word8)
-> (ShortByteString -> [Word8]) -> ShortByteString -> Word8
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
unpack
{-# INLINE foldr1 #-}

-- | 'foldr1'' is a variant of 'foldr1', but is strict in the
-- accumulator.
foldr1' :: (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldr1' :: (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldr1' Word8 -> Word8 -> Word8
k = \ShortByteString
sbs -> if ShortByteString -> Bool
null ShortByteString
sbs then [Char] -> Word8
forall a. [Char] -> a
errorEmptyList [Char]
"foldr1'" else (Word8 -> Word8 -> Word8) -> Word8 -> ShortByteString -> Word8
forall a. (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr' Word8 -> Word8 -> Word8
k (ShortByteString -> Word8
last ShortByteString
sbs) (ShortByteString -> ShortByteString
init ShortByteString
sbs)
{-# INLINE foldr1' #-}



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

-- | /O(n)/ Applied to a predicate and a 'ShortByteString', 'all' determines
-- if all elements of the 'ShortByteString' satisfy the predicate.
all :: (Word8 -> Bool) -> ShortByteString -> Bool
all :: (Word8 -> Bool) -> ShortByteString -> Bool
all Word8 -> Bool
k = \ShortByteString
sbs ->
  let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
      ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
      w :: Int -> Word8
w = BA -> Int -> Word8
indexWord8Array BA
ba
      go :: Int -> Bool
go !Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l    = Bool
True
            | Bool
otherwise = Word8 -> Bool
k (Int -> Word8
w Int
n) Bool -> Bool -> Bool
&& Int -> Bool
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
  in Int -> Bool
go Int
0


-- | /O(n)/ Applied to a predicate and a ByteString, 'any' determines if
-- any element of the 'ByteString' satisfies the predicate.
any :: (Word8 -> Bool) -> ShortByteString -> Bool
any :: (Word8 -> Bool) -> ShortByteString -> Bool
any Word8 -> Bool
k = \ShortByteString
sbs ->
  let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
      ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
      w :: Int -> Word8
w = BA -> Int -> Word8
indexWord8Array BA
ba
      go :: Int -> Bool
go !Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l    = Bool
False
            | Bool
otherwise = Word8 -> Bool
k (Int -> Word8
w Int
n) Bool -> Bool -> Bool
|| Int -> Bool
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
  in Int -> Bool
go Int
0
{-# INLINE [1] any #-}


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


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

-- | /O(n)/ 'take' @n@, applied to a ShortByteString @xs@, returns the prefix
-- of @xs@ of length @n@, or @xs@ itself if @n > 'length' xs@.
--
-- Note: copies the entire byte array
take :: Int -> ShortByteString -> ShortByteString
take :: Int -> ShortByteString -> ShortByteString
take = \Int
n -> \ShortByteString
sbs ->
  let len :: Int
len = Int -> Int -> Int
forall a. Ord a => a -> a -> a
min (ShortByteString -> Int
BS.length ShortByteString
sbs) (Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 Int
n)
  in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
len ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
0 Int
len
{-# INLINE take #-}

-- | Similar to 'P.takeWhile',
-- returns the longest (possibly empty) prefix of elements
-- satisfying the predicate.
takeWhile :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
takeWhile :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
takeWhile Word8 -> Bool
f ShortByteString
ps = Int -> ShortByteString -> ShortByteString
take ((Word8 -> Bool) -> ShortByteString -> Int
findIndexOrLength (Bool -> Bool
not (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
f) ShortByteString
ps) ShortByteString
ps
{-# INLINE [1] takeWhile #-}

-- | /O(1)/ @'takeEnd' n xs@ is equivalent to @'drop' ('length' xs - n) xs@.
-- Takes @n@ elements from end of bytestring.
--
-- >>> takeEnd 3 "abcdefg"
-- "efg"
-- >>> takeEnd 0 "abcdefg"
-- ""
-- >>> takeEnd 4 "abc"
-- "abc"
takeEnd :: Int -> ShortByteString -> ShortByteString
takeEnd :: Int -> ShortByteString -> ShortByteString
takeEnd Int
n ShortByteString
sbs
    | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= ShortByteString -> Int
length ShortByteString
sbs  = ShortByteString
sbs
    | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0           = ShortByteString
empty
    | Bool
otherwise        = Int -> ShortByteString -> ShortByteString
drop (ShortByteString -> Int
length ShortByteString
sbs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n) ShortByteString
sbs
{-# INLINE takeEnd #-}

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

-- | /O(n)/ 'drop' @n@ @xs@ returns the suffix of @xs@ after the first n elements, or @[]@ if @n > 'length' xs@.
--
-- Note: copies the entire byte array
drop  :: Int -> ShortByteString -> ShortByteString
drop :: Int -> ShortByteString -> ShortByteString
drop = \Int
n -> \ShortByteString
sbs ->
  let len :: Int
len = ShortByteString -> Int
BS.length ShortByteString
sbs
      newLen :: Int
newLen = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 (Int
len Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
0 Int
n)
  in if | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0    -> ShortByteString
sbs
        | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
len  -> ShortByteString
empty
        | Bool
otherwise -> Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
newLen ((forall s. MBA s -> ST s ()) -> ShortByteString)
-> (forall s. MBA s -> ST s ()) -> ShortByteString
forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> BA -> Int -> MBA s -> Int -> Int -> ST s ()
forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
n MBA s
mba Int
0 Int
newLen
{-# INLINE drop #-}

-- | /O(1)/ @'dropEnd' n xs@ is equivalent to @'take' ('length' xs - n) xs@.
-- Drops @n@ elements from end of bytestring.
--
-- >>> dropEnd 3 "abcdefg"
-- "abcd"
-- >>> dropEnd 0 "abcdefg"
-- "abcdefg"
-- >>> dropEnd 4 "abc"
-- ""
dropEnd :: Int -> ShortByteString -> ShortByteString
dropEnd :: Int -> ShortByteString -> ShortByteString
dropEnd Int
n ShortByteString
sbs
    | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0           = ShortByteString
sbs
    | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= ShortByteString -> Int
length ShortByteString
sbs  = ShortByteString
empty
    | Bool
otherwise        = Int -> ShortByteString -> ShortByteString
take (ShortByteString -> Int
length ShortByteString
sbs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
n) ShortByteString
sbs

{-# INLINE dropEnd #-}
-- | Similar to 'P.dropWhile',
-- drops the longest (possibly empty) prefix of elements
-- satisfying the predicate and returns the remainder.
--
-- Note: copies the entire byte array
dropWhile :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
dropWhile :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
dropWhile Word8 -> Bool
f = \ShortByteString
ps -> Int -> ShortByteString -> ShortByteString
drop ((Word8 -> Bool) -> ShortByteString -> Int
findIndexOrLength (Bool -> Bool
not (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
f) ShortByteString
ps) ShortByteString
ps

-- | Similar to 'P.dropWhileEnd',
-- drops the longest (possibly empty) suffix of elements
-- satisfying the predicate and returns the remainder.
--
-- @'dropWhileEnd' p@ is equivalent to @'reverse' . 'dropWhile' p . 'reverse'@.
--
-- @since 0.10.12.0
dropWhileEnd :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
dropWhileEnd :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
dropWhileEnd Word8 -> Bool
f = \ShortByteString
ps -> Int -> ShortByteString -> ShortByteString
take ((Word8 -> Bool) -> ShortByteString -> Int
findFromEndUntil (Bool -> Bool
not (Bool -> Bool) -> (Word8 -> Bool) -> Word8 -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Bool
f) ShortByteString
ps) ShortByteString
ps
{-# INLINE dropWhileEnd #-}

-- | Returns the longest (possibly empty) suffix of elements which __do not__
-- satisfy the predicate and the remainder of the string.
--
-- 'breakEnd' @p@ is equivalent to @'spanEnd' (not . p)@ and to @('takeWhileEnd' (not . p) &&& 'dropWhileEnd' (not . p))@.
breakEnd :: (Word8 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
breakEnd :: (Word8 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
breakEnd Word8 -> Bool
p = \ShortByteString
sbs -> Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt ((Word8 -> Bool) -> ShortByteString -> Int
findFromEndUntil Word8 -> Bool
p ShortByteString
sbs) ShortByteString
sbs
{-# INLINE breakEnd #-}

-- | Similar to 'P.break',
-- returns the longest (possibly empty) prefix of elements which __do not__
-- satisfy the predicate and the remainder of the string.
--
-- 'break' @p@ is equivalent to @'span' (not . p)@ and to @('takeWhile' (not . p) &&& 'dropWhile' (not . p))@.
break :: (Word8 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
break :: (Word8 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
break = \Word8 -> Bool
p -> \ShortByteString
ps -> case (Word8 -> Bool) -> ShortByteString -> Int
findIndexOrLength Word8 -> Bool
p ShortByteString
ps of Int
n -> (Int -> ShortByteString -> ShortByteString
take Int
n ShortByteString
ps, Int -> ShortByteString -> ShortByteString
drop Int
n ShortByteString
ps)
{-# INLINE [1] break #-}

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

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

-- | /O(n)/ 'splitAt' @n xs@ is equivalent to @('take' n xs, 'drop' n xs)@.
--
-- Note: copies the substrings
splitAt :: Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt :: Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt Int
n = \ShortByteString
xs -> if
  | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0 -> (ShortByteString
forall a. Monoid a => a
mempty, ShortByteString
xs)
  | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= ShortByteString -> Int
BS.length ShortByteString
xs -> (ShortByteString
xs, ShortByteString
forall a. Monoid a => a
mempty)
  | Bool
otherwise -> (Int -> ShortByteString -> ShortByteString
take Int
n ShortByteString
xs, Int -> ShortByteString -> ShortByteString
drop Int
n ShortByteString
xs)

-- | /O(n)/ Break a 'ShortByteString' into pieces separated by the byte
-- argument, consuming the delimiter. I.e.
--
-- > split 10  "a\nb\nd\ne" == ["a","b","d","e"]   -- fromEnum '\n' == 10
-- > split 97  "aXaXaXa"    == ["","X","X","X",""] -- fromEnum 'a' == 97
-- > split 120 "x"          == ["",""]             -- fromEnum 'x' == 120
-- > split undefined ""     == []                  -- and not [""]
--
-- and
--
-- > intercalate [c] . split c == id
-- > split == splitWith . (==)
--
-- Note: copies the substrings
split :: Word8 -> ShortByteString -> [ShortByteString]
split :: Word8 -> ShortByteString -> [ShortByteString]
split Word8
w = (Word8 -> Bool) -> ShortByteString -> [ShortByteString]
splitWith (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
== Word8
w)


-- | /O(n)/ Splits a 'ShortByteString' into components delimited by
-- separators, where the predicate returns True for a separator element.
-- The resulting components do not contain the separators.  Two adjacent
-- separators result in an empty component in the output.  eg.
--
-- > splitWith (==97) "aabbaca" == ["","","bb","c",""] -- fromEnum 'a' == 97
-- > splitWith undefined ""     == []                  -- and not [""]
--
splitWith :: (Word8 -> Bool) -> ShortByteString -> [ShortByteString]
splitWith :: (Word8 -> Bool) -> ShortByteString -> [ShortByteString]
splitWith Word8 -> Bool
p = \ShortByteString
sbs -> if
  | ShortByteString -> Bool
BS.null ShortByteString
sbs -> []
  | Bool
otherwise -> ShortByteString -> [ShortByteString]
go ShortByteString
sbs
  where
    go :: ShortByteString -> [ShortByteString]
go ShortByteString
sbs'
      | ShortByteString -> Bool
BS.null ShortByteString
sbs' = [ShortByteString
forall a. Monoid a => a
mempty]
      | Bool
otherwise =
          case (Word8 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
break Word8 -> Bool
p ShortByteString
sbs' of
            (ShortByteString
a, ShortByteString
b)
              | ShortByteString -> Bool
BS.null ShortByteString
b -> [ShortByteString
a]
              | Bool
otherwise -> ShortByteString
a ShortByteString -> [ShortByteString] -> [ShortByteString]
forall a. a -> [a] -> [a]
: ShortByteString -> [ShortByteString]
go (ShortByteString -> ShortByteString
tail ShortByteString
b)


-- | /O(n)/ The 'stripSuffix' function takes two ShortByteStrings and returns 'Just'
-- the remainder of the second iff the first is its suffix, and otherwise
-- 'Nothing'.
stripSuffix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
stripSuffix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
stripSuffix ShortByteString
sbs1 ShortByteString
sbs2 = do
  let l1 :: Int
l1 = ShortByteString -> Int
BS.length ShortByteString
sbs1
      l2 :: Int
l2 = ShortByteString -> Int
BS.length ShortByteString
sbs2
  if | Int
l1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0   -> ShortByteString -> Maybe ShortByteString
forall a. a -> Maybe a
Just ShortByteString
sbs2
     | Int
l2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
l1   -> Maybe ShortByteString
forall a. Maybe a
Nothing
     | Bool
otherwise -> IO (Maybe ShortByteString) -> Maybe ShortByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO (Maybe ShortByteString) -> Maybe ShortByteString)
-> IO (Maybe ShortByteString) -> Maybe ShortByteString
forall a b. (a -> b) -> a -> b
$ do
         Ptr Word8
p1 <- Int -> IO (Ptr Word8)
forall a. Int -> IO (Ptr a)
mallocBytes Int
l1
         Ptr Any
p2 <- Int -> IO (Ptr Any)
forall a. Int -> IO (Ptr a)
mallocBytes Int
l2
         ShortByteString -> Int -> Ptr Word8 -> Int -> IO ()
forall a. ShortByteString -> Int -> Ptr a -> Int -> IO ()
BS.copyToPtr ShortByteString
sbs1 Int
0 Ptr Word8
p1 Int
l1
         ShortByteString -> Int -> Ptr Any -> Int -> IO ()
forall a. ShortByteString -> Int -> Ptr a -> Int -> IO ()
BS.copyToPtr ShortByteString
sbs2 Int
0 Ptr Any
p2 Int
l2
         CInt
i <- Ptr Word8 -> Ptr Word8 -> Int -> IO CInt
memcmp Ptr Word8
p1 (Ptr Any
p2 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)
         if CInt
i CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
0
          then do
            ShortByteString
sbs <- Ptr Any -> Int -> IO ShortByteString
forall a. Ptr a -> Int -> IO ShortByteString
createFromPtr Ptr Any
p2 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
l1))
            Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Word8
p1
            Ptr Any -> IO ()
forall a. Ptr a -> IO ()
free Ptr Any
p2
            Maybe ShortByteString -> IO (Maybe ShortByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ShortByteString -> IO (Maybe ShortByteString))
-> Maybe ShortByteString -> IO (Maybe ShortByteString)
forall a b. (a -> b) -> a -> b
$! ShortByteString -> Maybe ShortByteString
forall a. a -> Maybe a
Just ShortByteString
sbs
          else do
            Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Word8
p1
            Ptr Any -> IO ()
forall a. Ptr a -> IO ()
free Ptr Any
p2
            Maybe ShortByteString -> IO (Maybe ShortByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ShortByteString
forall a. Maybe a
Nothing

-- | /O(n)/ The 'stripPrefix' function takes two ShortByteStrings and returns 'Just'
-- the remainder of the second iff the first is its prefix, and otherwise
-- 'Nothing'.
stripPrefix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
stripPrefix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
stripPrefix ShortByteString
sbs1 ShortByteString
sbs2 = do
  let l1 :: Int
l1 = ShortByteString -> Int
BS.length ShortByteString
sbs1
      l2 :: Int
l2 = ShortByteString -> Int
BS.length ShortByteString
sbs2
  if | Int
l1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0   -> ShortByteString -> Maybe ShortByteString
forall a. a -> Maybe a
Just ShortByteString
sbs2
     | Int
l2 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
l1   -> Maybe ShortByteString
forall a. Maybe a
Nothing
     | Bool
otherwise -> IO (Maybe ShortByteString) -> Maybe ShortByteString
forall a. IO a -> a
unsafeDupablePerformIO (IO (Maybe ShortByteString) -> Maybe ShortByteString)
-> IO (Maybe ShortByteString) -> Maybe ShortByteString
forall a b. (a -> b) -> a -> b
$ do
         Ptr Word8
p1 <- Int -> IO (Ptr Word8)
forall a. Int -> IO (Ptr a)
mallocBytes Int
l1
         Ptr Word8
p2 <- Int -> IO (Ptr Word8)
forall a. Int -> IO (Ptr a)
mallocBytes Int
l2
         ShortByteString -> Int -> Ptr Word8 -> Int -> IO ()
forall a. ShortByteString -> Int -> Ptr a -> Int -> IO ()
BS.copyToPtr ShortByteString
sbs1 Int
0 Ptr Word8
p1 Int
l1
         ShortByteString -> Int -> Ptr Word8 -> Int -> IO ()
forall a. ShortByteString -> Int -> Ptr a -> Int -> IO ()
BS.copyToPtr ShortByteString
sbs2 Int
0 Ptr Word8
p2 Int
l2
         CInt
i <- Ptr Word8 -> Ptr Word8 -> Int -> IO CInt
memcmp Ptr Word8
p1 Ptr Word8
p2 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l1)
         if CInt
i CInt -> CInt -> Bool
forall a. Eq a => a -> a -> Bool
== CInt
0
          then do
            ShortByteString
sbs <- Ptr Any -> Int -> IO ShortByteString
forall a. Ptr a -> Int -> IO ShortByteString
createFromPtr (Ptr Word8
p2 Ptr Word8 -> Int -> Ptr Any
forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
l1) (Int
l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
l1)
            Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Word8
p1
            Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Word8
p2
            Maybe ShortByteString -> IO (Maybe ShortByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return (Maybe ShortByteString -> IO (Maybe ShortByteString))
-> Maybe ShortByteString -> IO (Maybe ShortByteString)
forall a b. (a -> b) -> a -> b
$! ShortByteString -> Maybe ShortByteString
forall a. a -> Maybe a
Just ShortByteString
sbs
          else do
            Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Word8
p1
            Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Word8
p2
            Maybe ShortByteString -> IO (Maybe ShortByteString)
forall (m :: * -> *) a. Monad m => a -> m a
return Maybe ShortByteString
forall a. Maybe a
Nothing


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


-- | /O(n)/ 'replicate' @n x@ is a ByteString of length @n@ with @x@
-- the value of every element. The following holds:
--
-- > replicate w c = unfoldr w (\u -> Just (u,u)) c
--
-- This implementation uses @memset(3)@
replicate :: Int -> Word8 -> ShortByteString
replicate :: Int -> Word8 -> ShortByteString
replicate Int
w Word8
c
    | Int
w Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
0    = ShortByteString
empty
    | Bool
otherwise = Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
w (\MBA s
mba -> MBA s -> Int -> ST s ()
forall s. MBA s -> Int -> ST s ()
go MBA s
mba Int
0)
  where
    go :: MBA s -> Int -> ST s ()
go MBA s
mba Int
ix
      | Int
ix Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
ix Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
w = () -> ST s ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
      | Bool
otherwise = MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba Int
ix Word8
c ST s () -> ST s () -> ST s ()
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MBA s -> Int -> ST s ()
go MBA s
mba (Int
ix Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
{-# INLINE replicate #-}

-- | /O(n)/, where /n/ is the length of the result.  The 'unfoldr'
-- function is analogous to the List \'unfoldr\'.  'unfoldr' builds a
-- ShortByteString from a seed value.  The function takes the element and
-- returns 'Nothing' if it is done producing the ShortByteString 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.
--
-- This function is not efficient/safe. It will build a list of @[Word8]@
-- and run the generator until it returns `Nothing`, otherwise recurse infinitely,
-- then finally create a 'ShortByteString'.
--
-- 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 -> ShortByteString
unfoldr :: (a -> Maybe (Word8, a)) -> a -> ShortByteString
unfoldr a -> Maybe (Word8, a)
f a
x0 = [Word8] -> ShortByteString
packBytesRev ([Word8] -> ShortByteString) -> [Word8] -> ShortByteString
forall a b. (a -> b) -> a -> b
$ a -> [Word8] -> [Word8]
go a
x0 [Word8]
forall a. Monoid a => a
mempty
 where
   go :: a -> [Word8] -> [Word8]
go a
x [Word8]
words' = case a -> Maybe (Word8, a)
f a
x of
                    Maybe (Word8, a)
Nothing -> [Word8]
words'
                    Just (Word8
w, a
x') -> a -> [Word8] -> [Word8]
go a
x' (Word8
wWord8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
:[Word8]
words')
{-# INLINE unfoldr #-}

-- | /O(n)/ Like 'unfoldr', 'unfoldrN' builds a ShortByteString 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.
--
-- This function is not efficient. It will build a full list of @[Word8]@
-- before creating a 'ShortByteString'.
--
-- The following equation relates 'unfoldrN' and 'unfoldr':
--
-- > fst (unfoldrN n f s) == take n (unfoldr f s)
--
unfoldrN :: Int -> (a -> Maybe (Word8, a)) -> a -> (ShortByteString, Maybe a)
unfoldrN :: Int -> (a -> Maybe (Word8, a)) -> a -> (ShortByteString, Maybe a)
unfoldrN Int
i a -> Maybe (Word8, a)
f a
x0 = ([Word8] -> ShortByteString)
-> ([Word8], Maybe a) -> (ShortByteString, Maybe a)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first [Word8] -> ShortByteString
packBytesRev (([Word8], Maybe a) -> (ShortByteString, Maybe a))
-> ([Word8], Maybe a) -> (ShortByteString, Maybe a)
forall a b. (a -> b) -> a -> b
$ Int -> a -> [Word8] -> ([Word8], Maybe a)
forall t. (Ord t, Num t) => t -> a -> [Word8] -> ([Word8], Maybe a)
go (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) a
x0 [Word8]
forall a. Monoid a => a
mempty
 where
   go :: t -> a -> [Word8] -> ([Word8], Maybe a)
go t
i' a
x [Word8]
words'
    | t
i' t -> t -> Bool
forall a. Ord a => a -> a -> Bool
< t
0     = ([Word8]
words', 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 -> ([Word8]
words', Maybe a
forall a. Maybe a
Nothing)
                    Just (Word8
w, a
x') -> t -> a -> [Word8] -> ([Word8], Maybe a)
go (t
i' t -> t -> t
forall a. Num a => a -> a -> a
- t
1) a
x' (Word8
wWord8 -> [Word8] -> [Word8]
forall a. a -> [a] -> [a]
:[Word8]
words')
{-# INLINE unfoldrN #-}


-- --------------------------------------------------------------------
-- Predicates

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

-- |/O(n)/ The 'isPrefixOf' function takes two ShortByteStrings and returns 'True'
isPrefixOf :: ShortByteString -> ShortByteString -> Bool
isPrefixOf :: ShortByteString -> ShortByteString -> Bool
isPrefixOf ShortByteString
sbs1 ShortByteString
sbs2 = do
  let l1 :: Int
l1 = ShortByteString -> Int
BS.length ShortByteString
sbs1
      l2 :: Int
l2 = ShortByteString -> Int
BS.length ShortByteString
sbs2
  if | 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
unsafeDupablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ do
         Ptr Word8
p1 <- Int -> IO (Ptr Word8)
forall a. Int -> IO (Ptr a)
mallocBytes Int
l1
         Ptr Word8
p2 <- Int -> IO (Ptr Word8)
forall a. Int -> IO (Ptr a)
mallocBytes Int
l2
         ShortByteString -> Int -> Ptr Word8 -> Int -> IO ()
forall a. ShortByteString -> Int -> Ptr a -> Int -> IO ()
BS.copyToPtr ShortByteString
sbs1 Int
0 Ptr Word8
p1 Int
l1
         ShortByteString -> Int -> Ptr Word8 -> Int -> IO ()
forall a. ShortByteString -> Int -> Ptr a -> Int -> IO ()
BS.copyToPtr ShortByteString
sbs2 Int
0 Ptr Word8
p2 Int
l2
         CInt
i <- Ptr Word8 -> Ptr Word8 -> Int -> IO CInt
memcmp Ptr Word8
p1 Ptr Word8
p2 (Int -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
l1)
         Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Word8
p1
         Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Word8
p2
         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 'isSuffixOf' function takes two ShortByteStrings and returns 'True'
-- iff the first is a suffix of the second.
--
-- The following holds:
--
-- > isSuffixOf x y == reverse x `isPrefixOf` reverse y
isSuffixOf :: ShortByteString -> ShortByteString -> Bool
isSuffixOf :: ShortByteString -> ShortByteString -> Bool
isSuffixOf ShortByteString
sbs1 ShortByteString
sbs2 = do
  let l1 :: Int
l1 = ShortByteString -> Int
BS.length ShortByteString
sbs1
      l2 :: Int
l2 = ShortByteString -> Int
BS.length ShortByteString
sbs2
  if | 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
unsafeDupablePerformIO (IO Bool -> Bool) -> IO Bool -> Bool
forall a b. (a -> b) -> a -> b
$ do
         Ptr Word8
p1 <- Int -> IO (Ptr Word8)
forall a. Int -> IO (Ptr a)
mallocBytes Int
l1
         Ptr Any
p2 <- Int -> IO (Ptr Any)
forall a. Int -> IO (Ptr a)
mallocBytes Int
l2
         ShortByteString -> Int -> Ptr Word8 -> Int -> IO ()
forall a. ShortByteString -> Int -> Ptr a -> Int -> IO ()
BS.copyToPtr ShortByteString
sbs1 Int
0 Ptr Word8
p1 Int
l1
         ShortByteString -> Int -> Ptr Any -> Int -> IO ()
forall a. ShortByteString -> Int -> Ptr a -> Int -> IO ()
BS.copyToPtr ShortByteString
sbs2 Int
0 Ptr Any
p2 Int
l2
         CInt
i <- Ptr Word8 -> Ptr Word8 -> Int -> IO CInt
memcmp Ptr Word8
p1 (Ptr Any
p2 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)
         Ptr Word8 -> IO ()
forall a. Ptr a -> IO ()
free Ptr Word8
p1
         Ptr Any -> IO ()
forall a. Ptr a -> IO ()
free Ptr Any
p2
         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

-- | Break a string on a substring, returning a pair of the part of the
-- string prior to the match, and the rest of the string.
--
-- The following relationships hold:
--
-- > break (== c) l == breakSubstring (singleton c) l
--
-- For example, to tokenise a string, dropping delimiters:
--
-- > tokenise x y = h : if null t then [] else tokenise x (drop (length x) t)
-- >     where (h,t) = breakSubstring x y
--
-- To skip to the first 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 :: ShortByteString -- ^ String to search for
               -> ShortByteString -- ^ String to search in
               -> (ShortByteString, ShortByteString) -- ^ Head and tail of string broken at substring
breakSubstring :: ShortByteString
-> ShortByteString -> (ShortByteString, ShortByteString)
breakSubstring ShortByteString
pat =
  case Int
lp of
    Int
0 -> (ShortByteString
forall a. Monoid a => a
mempty,)
    Int
1 -> Word8 -> ShortByteString -> (ShortByteString, ShortByteString)
breakByte (ShortByteString -> Word8
head ShortByteString
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 ShortByteString -> (ShortByteString, ShortByteString)
shift
             else ShortByteString -> (ShortByteString, ShortByteString)
karpRabin
  where
    lp :: Int
lp = ShortByteString -> Int
BS.length ShortByteString
pat
    karpRabin :: ShortByteString -> (ShortByteString, ShortByteString)
    karpRabin :: ShortByteString -> (ShortByteString, ShortByteString)
karpRabin ShortByteString
src
        | ShortByteString -> Int
BS.length ShortByteString
src Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
lp = (ShortByteString
src,ShortByteString
forall a. Monoid a => a
mempty)
        | Bool
otherwise = Word32 -> Int -> (ShortByteString, ShortByteString)
search (ShortByteString -> Word32
rollingHash (ShortByteString -> Word32) -> ShortByteString -> Word32
forall a b. (a -> b) -> a -> b
$ Int -> ShortByteString -> ShortByteString
take Int
lp ShortByteString
src) Int
lp
      where
        k :: Word32
k           = Word32
2891336453 :: Word32
        rollingHash :: ShortByteString -> Word32
rollingHash = (Word32 -> Word8 -> Word32) -> Word32 -> ShortByteString -> Word32
forall a. (a -> Word8 -> a) -> a -> ShortByteString -> 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          = ShortByteString -> Word32
rollingHash ShortByteString
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
. ShortByteString -> Int -> Word8
BS.unsafeIndex ShortByteString
src
        search :: Word32 -> Int -> (ShortByteString, ShortByteString)
search !Word32
hs !Int
i
            | Word32
hp Word32 -> Word32 -> Bool
forall a. Eq a => a -> a -> Bool
== Word32
hs Bool -> Bool -> Bool
&& ShortByteString
pat ShortByteString -> ShortByteString -> Bool
forall a. Eq a => a -> a -> Bool
== Int -> ShortByteString -> ShortByteString
take Int
lp ShortByteString
b = (ShortByteString, ShortByteString)
u
            | ShortByteString -> Int
BS.length ShortByteString
src Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i           = (ShortByteString
src, ShortByteString
forall a. Monoid a => a
mempty) -- not found
            | Bool
otherwise                    = Word32 -> Int -> (ShortByteString, ShortByteString)
search Word32
hs' (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
          where
            u :: (ShortByteString, ShortByteString)
u@(ShortByteString
_, ShortByteString
b) = Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) ShortByteString
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 :: ShortByteString -> (ShortByteString, ShortByteString)
    shift :: ShortByteString -> (ShortByteString, ShortByteString)
shift !ShortByteString
src
        | ShortByteString -> Int
BS.length ShortByteString
src Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
lp = (ShortByteString
src, ShortByteString
forall a. Monoid a => a
mempty)
        | Bool
otherwise       = Word -> Int -> (ShortByteString, ShortByteString)
search (ShortByteString -> Word
intoWord (ShortByteString -> Word) -> ShortByteString -> Word
forall a b. (a -> b) -> a -> b
$ Int -> ShortByteString -> ShortByteString
take Int
lp ShortByteString
src) Int
lp
      where
        intoWord :: ShortByteString -> Word
        intoWord :: ShortByteString -> Word
intoWord = (Word -> Word8 -> Word) -> Word -> ShortByteString -> Word
forall a. (a -> Word8 -> a) -> a -> ShortByteString -> 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   = ShortByteString -> Word
intoWord ShortByteString
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 -> (ShortByteString, ShortByteString)
search !Word
w !Int
i
            | Word
w Word -> Word -> Bool
forall a. Eq a => a -> a -> Bool
== Word
wp            = Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
lp) ShortByteString
src
            | ShortByteString -> Int
BS.length ShortByteString
src Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
<= Int
i = (ShortByteString
src, ShortByteString
forall a. Monoid a => a
mempty)
            | Bool
otherwise       = Word -> Int -> (ShortByteString, ShortByteString)
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 (ShortByteString -> Int -> Word8
BS.unsafeIndex ShortByteString
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 #-}


-- --------------------------------------------------------------------
-- Searching ShortByteString

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

-- | /O(n)/ 'filter', applied to a predicate and a ByteString,
-- returns a ByteString containing those characters that satisfy the
-- predicate.
filter :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
filter :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
filter Word8 -> Bool
k = \ShortByteString
sbs -> if
    | ShortByteString -> Bool
null ShortByteString
sbs  -> ShortByteString
sbs
    | Bool
otherwise -> [Word8] -> ShortByteString
pack ([Word8] -> ShortByteString)
-> (ShortByteString -> [Word8])
-> ShortByteString
-> ShortByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Bool) -> [Word8] -> [Word8]
forall a. (a -> Bool) -> [a] -> [a]
List.filter Word8 -> Bool
k ([Word8] -> [Word8])
-> (ShortByteString -> [Word8]) -> ShortByteString -> [Word8]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
unpack (ShortByteString -> ShortByteString)
-> ShortByteString -> ShortByteString
forall a b. (a -> b) -> a -> b
$ ShortByteString
sbs
{-# INLINE filter #-}

-- | /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) -> ShortByteString -> Maybe Word8
find :: (Word8 -> Bool) -> ShortByteString -> Maybe Word8
find Word8 -> Bool
f = \ShortByteString
p -> case (Word8 -> Bool) -> ShortByteString -> Maybe Int
findIndex Word8 -> Bool
f ShortByteString
p of
                    Just Int
n -> Word8 -> Maybe Word8
forall a. a -> Maybe a
Just (ShortByteString
p ShortByteString -> Int -> Word8
`index` 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) -> ShortByteString -> (ShortByteString, ShortByteString)
partition :: (Word8 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
partition Word8 -> Bool
f = \ShortByteString
s -> if
    | ShortByteString -> Bool
null ShortByteString
s    -> (ShortByteString
s, ShortByteString
s)
    | Bool
otherwise -> ([Word8] -> ShortByteString)
-> ([Word8] -> ShortByteString)
-> ([Word8], [Word8])
-> (ShortByteString, ShortByteString)
forall (p :: * -> * -> *) a b c d.
Bifunctor p =>
(a -> b) -> (c -> d) -> p a c -> p b d
bimap [Word8] -> ShortByteString
pack [Word8] -> ShortByteString
pack (([Word8], [Word8]) -> (ShortByteString, ShortByteString))
-> (ShortByteString -> ([Word8], [Word8]))
-> ShortByteString
-> (ShortByteString, ShortByteString)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word8 -> Bool) -> [Word8] -> ([Word8], [Word8])
forall a. (a -> Bool) -> [a] -> ([a], [a])
List.partition Word8 -> Bool
f ([Word8] -> ([Word8], [Word8]))
-> (ShortByteString -> [Word8])
-> ShortByteString
-> ([Word8], [Word8])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word8]
unpack (ShortByteString -> (ShortByteString, ShortByteString))
-> ShortByteString -> (ShortByteString, ShortByteString)
forall a b. (a -> b) -> a -> b
$ ShortByteString
s


#if !MIN_VERSION_bytestring(0,11,0)
-- | /O(1)/ 'ShortByteString' index, starting from 0, that returns 'Just' if:
--
-- > 0 <= n < length bs
--
-- @since 0.11.0.0
indexMaybe :: ShortByteString -> Int -> Maybe Word8
indexMaybe :: ShortByteString -> Int -> Maybe Word8
indexMaybe ShortByteString
sbs Int
i
  | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< ShortByteString -> Int
length ShortByteString
sbs = Word8 -> Maybe Word8
forall a. a -> Maybe a
Just (Word8 -> Maybe Word8) -> Word8 -> Maybe Word8
forall a b. (a -> b) -> a -> b
$! BA -> Int -> Word8
indexWord8Array (ShortByteString -> BA
asBA ShortByteString
sbs) Int
i
  | Bool
otherwise                = Maybe Word8
forall a. Maybe a
Nothing
{-# INLINE indexMaybe #-}

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


-- --------------------------------------------------------------------
-- Indexing ShortByteString

-- | /O(n)/ The 'elemIndex' function returns the index of the first
-- element in the given 'ShortByteString' which is equal to the query
-- element, or 'Nothing' if there is no such element.
elemIndex :: Word8 -> ShortByteString -> Maybe Int
elemIndex :: Word8 -> ShortByteString -> Maybe Int
elemIndex Word8
k = (Word8 -> Bool) -> ShortByteString -> Maybe Int
findIndex (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
==Word8
k)
{-# INLINE elemIndex #-}

-- | /O(n)/ The 'elemIndices' function extends 'elemIndex', by returning
-- the indices of all elements equal to the query element, in ascending order.
elemIndices :: Word8 -> ShortByteString -> [Int]
elemIndices :: Word8 -> ShortByteString -> [Int]
elemIndices Word8
k = (Word8 -> Bool) -> ShortByteString -> [Int]
findIndices (Word8 -> Word8 -> Bool
forall a. Eq a => a -> a -> Bool
==Word8
k)

-- | count returns the number of times its argument appears in the ShortByteString
count :: Word8 -> ShortByteString -> Int
count :: Word8 -> ShortByteString -> Int
count Word8
w = [Int] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
List.length ([Int] -> Int)
-> (ShortByteString -> [Int]) -> ShortByteString -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> ShortByteString -> [Int]
elemIndices Word8
w

-- | /O(n)/ The 'findIndex' function takes a predicate and a 'ShortByteString' and
-- returns the index of the first element in the ByteString
-- satisfying the predicate.
findIndex :: (Word8 -> Bool) -> ShortByteString -> Maybe Int
findIndex :: (Word8 -> Bool) -> ShortByteString -> Maybe Int
findIndex Word8 -> Bool
k = \ShortByteString
sbs ->
  let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
      ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
      w :: Int -> Word8
w = BA -> Int -> Word8
indexWord8Array BA
ba
      go :: Int -> Maybe Int
go !Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l    = Maybe Int
forall a. Maybe a
Nothing
            | Word8 -> Bool
k (Int -> Word8
w Int
n)   = Int -> Maybe Int
forall a. a -> Maybe a
Just Int
n
            | Bool
otherwise = Int -> Maybe Int
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
  in Int -> Maybe Int
go Int
0
{-# INLINE findIndex #-}


-- | /O(n)/ The 'findIndices' function extends 'findIndex', by returning the
-- indices of all elements satisfying the predicate, in ascending order.
findIndices :: (Word8 -> Bool) -> ShortByteString -> [Int]
findIndices :: (Word8 -> Bool) -> ShortByteString -> [Int]
findIndices Word8 -> Bool
k = \ShortByteString
sbs ->
  let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
      ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
      w :: Int -> Word8
w = BA -> Int -> Word8
indexWord8Array BA
ba
      go :: Int -> [Int]
go !Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l    = []
            | Word8 -> Bool
k (Int -> Word8
w Int
n)   = Int
n Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
: Int -> [Int]
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
            | Bool
otherwise = Int -> [Int]
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
  in Int -> [Int]
go Int
0
{-# INLINE [1] findIndices #-}


-- --------------------------------------------------------------------
-- Internal

-- Find from the end of the string using predicate
findFromEndUntil :: (Word8 -> Bool) -> ShortByteString -> Int
findFromEndUntil :: (Word8 -> Bool) -> ShortByteString -> Int
findFromEndUntil Word8 -> Bool
k ShortByteString
sbs = Int -> Int
go (ShortByteString -> Int
BS.length ShortByteString
sbs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
  where
    ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
    w :: Int -> Word8
w = BA -> Int -> Word8
indexWord8Array BA
ba
    go :: Int -> Int
go !Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
0     = Int
0
          | Word8 -> Bool
k (Int -> Word8
w Int
n)   = Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
          | Bool
otherwise = Int -> Int
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1)
{-# INLINE findFromEndUntil #-}

findIndexOrLength :: (Word8 -> Bool) -> ShortByteString -> Int
findIndexOrLength :: (Word8 -> Bool) -> ShortByteString -> Int
findIndexOrLength Word8 -> Bool
k ShortByteString
sbs = Int -> Int
go Int
0
  where
    l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
    ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
    w :: Int -> Word8
w = BA -> Int -> Word8
indexWord8Array BA
ba
    go :: Int -> Int
go !Int
n | Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
l    = Int
l
          | Word8 -> Bool
k (Int -> Word8
w Int
n)   = Int
n
          | Bool
otherwise = Int -> Int
go (Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1)
{-# INLINE findIndexOrLength #-}


packBytesRev :: [Word8] -> ShortByteString
packBytesRev :: [Word8] -> ShortByteString
packBytesRev [Word8]
cs = Int -> [Word8] -> ShortByteString
packLenBytesRev ([Word8] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
List.length [Word8]
cs) [Word8]
cs

packLenBytesRev :: Int -> [Word8] -> ShortByteString
packLenBytesRev :: Int -> [Word8] -> ShortByteString
packLenBytesRev Int
len [Word8]
ws0 =
    Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
len (\MBA s
mba -> MBA s -> Int -> [Word8] -> ST s ()
forall s. MBA s -> Int -> [Word8] -> ST s ()
go MBA s
mba Int
len [Word8]
ws0)
  where
    go :: MBA s -> Int -> [Word8] -> ST s ()
    go :: MBA s -> Int -> [Word8] -> ST s ()
go !MBA s
_   !Int
_ []     = () -> ST s ()
forall (m :: * -> *) a. Monad m => a -> m a
return ()
    go !MBA s
mba !Int
i (Word8
w:[Word8]
ws) = do
      MBA s -> Int -> Word8 -> ST s ()
forall s. MBA s -> Int -> Word8 -> ST s ()
writeWord8Array MBA s
mba (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) Word8
w
      MBA s -> Int -> [Word8] -> ST s ()
forall s. MBA s -> Int -> [Word8] -> ST s ()
go MBA s
mba (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [Word8]
ws


breakByte :: Word8 -> ShortByteString -> (ShortByteString, ShortByteString)
breakByte :: Word8 -> ShortByteString -> (ShortByteString, ShortByteString)
breakByte Word8
c ShortByteString
p = case Word8 -> ShortByteString -> Maybe Int
elemIndex Word8
c ShortByteString
p of
    Maybe Int
Nothing -> (ShortByteString
p, ShortByteString
forall a. Monoid a => a
mempty)
    Just Int
n  -> (Int -> ShortByteString -> ShortByteString
take Int
n ShortByteString
p, Int -> ShortByteString -> ShortByteString
drop Int
n ShortByteString
p)
{-# INLINE breakByte #-}

indexWord8Array :: BA -> Int -> Word8
indexWord8Array :: BA -> Int -> Word8
indexWord8Array (BA# ByteArray#
ba#) (I# Int#
i#) = Word# -> Word8
W8# (ByteArray# -> Int# -> Word#
indexWord8Array# ByteArray#
ba# Int#
i#)

writeWord8Array :: MBA s -> Int -> Word8 -> ST s ()
writeWord8Array :: MBA s -> Int -> Word8 -> ST s ()
writeWord8Array (MBA# MutableByteArray# s
mba#) (I# Int#
i#) (W8# Word#
w#) =
  STRep s () -> ST s ()
forall s a. STRep s a -> ST s a
ST (STRep s () -> ST s ()) -> STRep s () -> ST s ()
forall a b. (a -> b) -> a -> b
$ \State# s
s -> case MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
forall d.
MutableByteArray# d -> Int# -> Word# -> State# d -> State# d
writeWord8Array# MutableByteArray# s
mba# Int#
i# Word#
w# State# s
s of
               State# s
s' -> (# State# s
s', () #)