#if defined(i386_HOST_ARCH) || defined(x86_64_HOST_ARCH) \
    || ((defined(arm_HOST_ARCH) || defined(aarch64_HOST_ARCH)) \
        && defined(__ARM_FEATURE_UNALIGNED)) \
    || defined(powerpc_HOST_ARCH) || defined(powerpc64_HOST_ARCH) \
    || defined(powerpc64le_HOST_ARCH)
#define SAFE_UNALIGNED 1
#endif
module Data.ByteString.Short.Internal (
    
    ShortByteString(..),
    
    empty,
    singleton,
    pack,
    unpack,
    fromShort,
    toShort,
    
    snoc,
    cons,
    append,
    last,
    tail,
    uncons,
    head,
    init,
    unsnoc,
    null,
    length,
    
    map,
    reverse,
    intercalate,
    
    foldl,
    foldl',
    foldl1,
    foldl1',
    foldr,
    foldr',
    foldr1,
    foldr1',
    
    all,
    any,
    concat,
    
    replicate,
    unfoldr,
    unfoldrN,
    
    
    take,
    takeEnd,
    takeWhileEnd,
    takeWhile,
    drop,
    dropEnd,
    dropWhile,
    dropWhileEnd,
    breakEnd,
    break,
    span,
    spanEnd,
    splitAt,
    split,
    splitWith,
    stripSuffix,
    stripPrefix,
    
    isInfixOf,
    isPrefixOf,
    isSuffixOf,
    
    breakSubstring,
    
    
    elem,
    
    find,
    filter,
    partition,
    
    index,
    indexMaybe,
    (!?),
    elemIndex,
    elemIndices,
    count,
    findIndex,
    findIndices,
    
    createFromPtr,
    copyToPtr,
    
    isValidUtf8,
    
    
    packCString,
    packCStringLen,
    
    useAsCString,
    useAsCStringLen,
  ) where
import Data.ByteString.Internal
  ( ByteString(..)
  , accursedUnutterablePerformIO
  , checkedAdd
  )
import Data.Bits
  ( FiniteBits (finiteBitSize)
  , shiftL
#if MIN_VERSION_base(4,12,0) && defined(SAFE_UNALIGNED)
  , shiftR
#endif
  , (.&.)
  , (.|.)
  )
import Data.Data
  ( Data(..)
  , mkNoRepType
  )
import Data.Monoid
  ( Monoid(..) )
import Data.Semigroup
  ( Semigroup((<>)) )
import Data.String
  ( IsString(..) )
import Data.Typeable
  ( Typeable )
import Control.Applicative
  ( pure )
import Control.DeepSeq
  ( NFData(..) )
import Control.Exception
  ( assert )
import Control.Monad
  ( (>>) )
import Foreign.C.String
  ( CString
  , CStringLen
  )
import Foreign.C.Types
  ( CSize(..)
  , CInt(..)
  , CPtrdiff(..)
  )
import Foreign.ForeignPtr
  ( touchForeignPtr )
import Foreign.ForeignPtr.Unsafe
  ( unsafeForeignPtrToPtr )
import Foreign.Marshal.Alloc
  ( allocaBytes )
import Foreign.Storable
  ( pokeByteOff )
import GHC.Exts
  ( Int(I#), Int#, Ptr(Ptr), Addr#, Char(C#)
  , State#, RealWorld
  , ByteArray#, MutableByteArray#
  , newByteArray#
  , newPinnedByteArray#
  , byteArrayContents#
  , unsafeCoerce#
  , copyMutableByteArray#
#if MIN_VERSION_base(4,10,0)
  , isByteArrayPinned#
  , isTrue#
#endif
#if MIN_VERSION_base(4,11,0)
  , compareByteArrays#
#endif
  , sizeofByteArray#
  , indexWord8Array#, indexCharArray#
  , writeWord8Array#
  , unsafeFreezeByteArray#
#if MIN_VERSION_base(4,12,0) && defined(SAFE_UNALIGNED)
  ,writeWord64Array#
  ,indexWord8ArrayAsWord64#
#endif
  , setByteArray#
  , sizeofByteArray#
  , indexWord8Array#, indexCharArray#
  , writeWord8Array#
  , unsafeFreezeByteArray#
  , touch# )
import GHC.IO
import GHC.ForeignPtr
  ( ForeignPtr(ForeignPtr)
  , ForeignPtrContents(PlainPtr)
  )
import GHC.ST
  ( ST(ST)
  , runST
  )
import GHC.Stack.Types
  ( HasCallStack )
import GHC.Word
import Prelude
  ( Eq(..), Ord(..), Ordering(..), Read(..), Show(..)
  , ($), ($!), error, (++), (.), (||)
  , String, userError
  , Bool(..), (&&), otherwise
  , (+), (), fromIntegral
  , (*)
  , (^)
  , (<$>)
  , return
  , Maybe(..)
  , not
  , snd
  )
import qualified Data.ByteString.Internal as BS
import qualified Data.Foldable as Foldable
import qualified Data.List as List
import qualified GHC.Exts
import qualified Language.Haskell.TH.Lib as TH
import qualified Language.Haskell.TH.Syntax as TH
data ShortByteString = SBS ByteArray#
    deriving Typeable
instance TH.Lift ShortByteString where
#if MIN_VERSION_template_haskell(2,16,0)
  lift sbs = [| unsafePackLenLiteral |]
    `TH.appE` TH.litE (TH.integerL (fromIntegral len))
    `TH.appE` TH.litE (TH.BytesPrimL $ TH.Bytes ptr 0 (fromIntegral len))
    where
      BS ptr len = fromShort sbs
#else
  lift sbs = [| unsafePackLenLiteral |]
    `TH.appE` TH.litE (TH.integerL (fromIntegral len))
    `TH.appE` TH.litE (TH.StringPrimL $ BS.unpackBytes bs)
    where
      bs@(BS _ len) = fromShort sbs
#endif
#if MIN_VERSION_template_haskell(2,17,0)
  liftTyped = TH.unsafeCodeCoerce . TH.lift
#elif MIN_VERSION_template_haskell(2,16,0)
  liftTyped = TH.unsafeTExpCoerce . TH.lift
#endif
instance Eq ShortByteString where
    (==)    = equateBytes
instance Ord ShortByteString where
    compare = compareBytes
instance Semigroup ShortByteString where
    (<>)    = append
instance Monoid ShortByteString where
    mempty  = empty
    mappend = (<>)
    mconcat = concat
instance NFData ShortByteString where
    rnf SBS{} = ()
instance Show ShortByteString where
    showsPrec p ps r = showsPrec p (unpackChars ps) r
instance Read ShortByteString where
    readsPrec p str = [ (packChars x, y) | (x, y) <- readsPrec p str ]
instance GHC.Exts.IsList ShortByteString where
  type Item ShortByteString = Word8
  fromList = packBytes
  toList   = unpackBytes
instance IsString ShortByteString where
    fromString = packChars
instance Data ShortByteString where
  gfoldl f z txt = z packBytes `f` unpackBytes txt
  toConstr _     = error "Data.ByteString.Short.ShortByteString.toConstr"
  gunfold _ _    = error "Data.ByteString.Short.ShortByteString.gunfold"
  dataTypeOf _   = mkNoRepType "Data.ByteString.Short.ShortByteString"
empty :: ShortByteString
empty = create 0 (\_ -> return ())
length :: ShortByteString -> Int
length (SBS barr#) = I# (sizeofByteArray# barr#)
null :: ShortByteString -> Bool
null sbs = length sbs == 0
index :: HasCallStack => ShortByteString -> Int -> Word8
index sbs i
  | i >= 0 && i < length sbs = unsafeIndex sbs i
  | otherwise                = indexError sbs i
indexMaybe :: ShortByteString -> Int -> Maybe Word8
indexMaybe sbs i
  | i >= 0 && i < length sbs = Just $! unsafeIndex sbs i
  | otherwise                = Nothing
(!?) :: ShortByteString -> Int -> Maybe Word8
(!?) = indexMaybe
unsafeIndex :: ShortByteString -> Int -> Word8
unsafeIndex sbs = indexWord8Array (asBA sbs)
indexError :: HasCallStack => ShortByteString -> Int -> a
indexError sbs i =
  moduleError "index" $ "error in array index: " ++ show i
                        ++ " not in range [0.." ++ show (length sbs) ++ "]"
unsafePackLenLiteral :: Int -> Addr# -> ShortByteString
unsafePackLenLiteral len addr# =
    accursedUnutterablePerformIO $ createFromPtr (Ptr addr#) len
asBA :: ShortByteString -> BA
asBA (SBS ba#) = BA# ba#
create :: Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create len fill =
    runST $ do
      mba <- newByteArray len
      fill mba
      BA# ba# <- unsafeFreezeByteArray mba
      return (SBS ba#)
createAndTrim :: Int -> (forall s. MBA s -> ST s (Int, a)) -> (ShortByteString, a)
createAndTrim l fill =
    runST $ do
      mba <- newByteArray l
      (l', res) <- fill mba
      if assert (l' <= l) $ l' >= l
          then do
            BA# ba# <- unsafeFreezeByteArray mba
            return (SBS ba#, res)
          else do
            mba2 <- newByteArray l'
            copyMutableByteArray mba 0 mba2 0 l'
            BA# ba# <- unsafeFreezeByteArray mba2
            return (SBS ba#, res)
createAndTrim' :: Int -> (forall s. MBA s -> ST s Int) -> ShortByteString
createAndTrim' l fill =
    runST $ do
      mba <- newByteArray l
      l' <- fill mba
      if assert (l' <= l) $ l' >= l
          then do
            BA# ba# <- unsafeFreezeByteArray mba
            return (SBS ba#)
          else do
            mba2 <- newByteArray l'
            copyMutableByteArray mba 0 mba2 0 l'
            BA# ba# <- unsafeFreezeByteArray mba2
            return (SBS ba#)
createAndTrim'' :: Int -> (forall s. MBA s -> MBA s -> ST s (Int, Int)) -> (ShortByteString, ShortByteString)
createAndTrim'' l fill =
    runST $ do
      mba1 <- newByteArray l
      mba2 <- newByteArray l
      (l1, l2) <- fill mba1 mba2
      sbs1 <- freeze' l1 mba1
      sbs2 <- freeze' l2 mba2
      pure (sbs1, sbs2)
  where
    freeze' :: Int -> MBA s -> ST s ShortByteString
    freeze' l' mba =
      if assert (l' <= l) $ l' >= l
          then do
            BA# ba# <- unsafeFreezeByteArray mba
            return (SBS ba#)
          else do
            mba2 <- newByteArray l'
            copyMutableByteArray mba 0 mba2 0 l'
            BA# ba# <- unsafeFreezeByteArray mba2
            return (SBS ba#)
isPinned :: ByteArray# -> Bool
#if MIN_VERSION_base(4,10,0)
isPinned ba# = isTrue# (isByteArrayPinned# ba#)
#else
isPinned _ = False
#endif
toShort :: ByteString -> ShortByteString
toShort !bs = unsafeDupablePerformIO (toShortIO bs)
toShortIO :: ByteString -> IO ShortByteString
toShortIO (BS fptr len) = do
    mba <- stToIO (newByteArray len)
    let ptr = unsafeForeignPtrToPtr fptr
    stToIO (copyAddrToByteArray ptr mba 0 len)
    touchForeignPtr fptr
    BA# ba# <- stToIO (unsafeFreezeByteArray mba)
    return (SBS ba#)
fromShort :: ShortByteString -> ByteString
fromShort (SBS b#)
  | isPinned b# = BS fp len
  where
    addr# = byteArrayContents# b#
    fp = ForeignPtr addr# (PlainPtr (unsafeCoerce# b#))
    len = I# (sizeofByteArray# b#)
fromShort !sbs = unsafeDupablePerformIO (fromShortIO sbs)
fromShortIO :: ShortByteString -> IO ByteString
fromShortIO sbs = do
    let len = length sbs
    mba@(MBA# mba#) <- stToIO (newPinnedByteArray len)
    stToIO (copyByteArray (asBA sbs) 0 mba 0 len)
    let fp = ForeignPtr (byteArrayContents# (unsafeCoerce# mba#))
                        (PlainPtr mba#)
    return (BS fp len)
singleton :: Word8 -> ShortByteString
singleton = \w -> create 1 (\mba -> writeWord8Array mba 0 w)
pack :: [Word8] -> ShortByteString
pack = packBytes
unpack :: ShortByteString -> [Word8]
unpack = unpackBytes
packChars :: [Char] -> ShortByteString
packChars = \cs -> packLenBytes (List.length cs) (List.map BS.c2w cs)
packBytes :: [Word8] -> ShortByteString
packBytes = \ws -> packLenBytes (List.length ws) ws
packLenBytes :: Int -> [Word8] -> ShortByteString
packLenBytes len ws0 =
    create len (\mba -> go mba 0 ws0)
  where
    go :: MBA s -> Int -> [Word8] -> ST s ()
    go !_   !_ []     = return ()
    go !mba !i (w:ws) = do
      writeWord8Array mba i w
      go mba (i+1) ws
unpackChars :: ShortByteString -> [Char]
unpackChars sbs = unpackAppendCharsLazy sbs []
unpackBytes :: ShortByteString -> [Word8]
unpackBytes sbs = unpackAppendBytesLazy sbs []
unpackAppendCharsLazy :: ShortByteString -> [Char] -> [Char]
unpackAppendCharsLazy sbs = go 0 (length sbs)
  where
    sz = 100
    go off len cs
      | len <= sz = unpackAppendCharsStrict sbs off len cs
      | otherwise = unpackAppendCharsStrict sbs off sz  remainder
                      where remainder = go (off+sz) (lensz) cs
unpackAppendBytesLazy :: ShortByteString -> [Word8] -> [Word8]
unpackAppendBytesLazy sbs = go 0 (length sbs)
  where
    sz = 100
    go off len ws
      | len <= sz = unpackAppendBytesStrict sbs off len ws
      | otherwise = unpackAppendBytesStrict sbs off sz  remainder
                      where remainder = go (off+sz) (lensz) ws
unpackAppendCharsStrict :: ShortByteString -> Int -> Int -> [Char] -> [Char]
unpackAppendCharsStrict !sbs off len = go (off1) (off1 + len)
  where
    go !sentinal !i !acc
      | i == sentinal = acc
      | otherwise     = let !c = indexCharArray (asBA sbs) i
                        in go sentinal (i1) (c:acc)
unpackAppendBytesStrict :: ShortByteString -> Int -> Int -> [Word8] -> [Word8]
unpackAppendBytesStrict !sbs off len = go (off1) (off1 + len)
  where
    go !sentinal !i !acc
      | i == sentinal = acc
      | otherwise     = let !w = indexWord8Array (asBA sbs) i
                         in go sentinal (i1) (w:acc)
equateBytes :: ShortByteString -> ShortByteString -> Bool
equateBytes sbs1 sbs2 =
    let !len1 = length sbs1
        !len2 = length sbs2
     in len1 == len2
     && 0 == compareByteArrays (asBA sbs1) (asBA sbs2) len1
compareBytes :: ShortByteString -> ShortByteString -> Ordering
compareBytes sbs1 sbs2 =
    let !len1 = length sbs1
        !len2 = length sbs2
        !len  = min len1 len2
     in case compareByteArrays (asBA sbs1) (asBA sbs2) len of
          i | i    < 0    -> LT
            | i    > 0    -> GT
            | len2 > len1 -> LT
            | len2 < len1 -> GT
            | otherwise   -> EQ
append :: ShortByteString -> ShortByteString -> ShortByteString
append src1 src2 =
  let !len1 = length src1
      !len2 = length src2
   in create (len1 + len2) $ \dst -> do
        copyByteArray (asBA src1) 0 dst 0    len1
        copyByteArray (asBA src2) 0 dst len1 len2
concat :: [ShortByteString] -> ShortByteString
concat = \sbss ->
    create (totalLen 0 sbss) (\dst -> copy dst 0 sbss)
  where
    totalLen !acc []          = acc
    totalLen !acc (sbs: sbss) = totalLen (acc + length sbs) sbss
    copy :: MBA s -> Int -> [ShortByteString] -> ST s ()
    copy !_   !_   []                           = return ()
    copy !dst !off (src : sbss) = do
      let !len = length src
      copyByteArray (asBA src) 0 dst off len
      copy dst (off + len) sbss
infixr 5 `cons` 
infixl 5 `snoc`
snoc :: ShortByteString -> Word8 -> ShortByteString
snoc = \sbs c -> let l  = length sbs
                     nl = l + 1
  in create nl $ \mba -> do
      copyByteArray (asBA sbs) 0 mba 0 l
      writeWord8Array mba l c
cons :: Word8 -> ShortByteString -> ShortByteString
cons c = \sbs -> let l  = length sbs
                     nl = l + 1
  in create nl $ \mba -> do
      writeWord8Array mba 0 c
      copyByteArray (asBA sbs) 0 mba 1 l
last :: HasCallStack => ShortByteString -> Word8
last = \sbs -> case null sbs of
  True -> errorEmptySBS "last"
  False -> indexWord8Array (asBA sbs) (length sbs  1)
tail :: HasCallStack => ShortByteString -> ShortByteString
tail = \sbs ->
  let l  = length sbs
      nl = l  1
  in case null sbs of
      True -> errorEmptySBS "tail"
      False -> create nl $ \mba -> copyByteArray (asBA sbs) 1 mba 0 nl
uncons :: ShortByteString -> Maybe (Word8, ShortByteString)
uncons = \sbs ->
  let l  = length sbs
      nl = l  1
  in if | l <= 0 -> Nothing
        | otherwise -> let h = indexWord8Array (asBA sbs) 0
                           t = create nl $ \mba -> copyByteArray (asBA sbs) 1 mba 0 nl
                       in Just (h, t)
head :: HasCallStack => ShortByteString -> Word8
head = \sbs -> case null sbs of
  True -> errorEmptySBS "head"
  False -> indexWord8Array (asBA sbs) 0
init :: HasCallStack => ShortByteString -> ShortByteString
init = \sbs ->
  let l  = length sbs
      nl = l  1
  in case null sbs of
      True -> errorEmptySBS "init"
      False -> create nl $ \mba -> copyByteArray (asBA sbs) 0 mba 0 nl
unsnoc :: ShortByteString -> Maybe (ShortByteString, Word8)
unsnoc = \sbs ->
  let l  = length sbs
      nl = l  1
  in if | l <= 0 -> Nothing
        | otherwise -> let l' = indexWord8Array (asBA sbs) (l  1)
                           i  = create nl $ \mba -> copyByteArray (asBA sbs) 0 mba 0 nl
                       in Just (i, l')
map :: (Word8 -> Word8) -> ShortByteString -> ShortByteString
map f = \sbs ->
    let l  = length sbs
        ba = asBA sbs
    in create l (\mba -> go ba mba 0 l)
  where
    go :: BA -> MBA s -> Int -> Int -> ST s ()
    go !ba !mba !i !l
      | i >= l = return ()
      | otherwise = do
          let w = indexWord8Array ba i
          writeWord8Array mba i (f w)
          go ba mba (i+1) l
reverse :: ShortByteString -> ShortByteString
reverse = \sbs ->
    let l  = length sbs
        ba = asBA sbs
#if MIN_VERSION_base(4,12,0) && defined(SAFE_UNALIGNED)
    in create l (\mba -> go ba mba l)
  where
    go :: forall s. BA -> MBA s -> Int -> ST s ()
    go !ba !mba !l = do
      
      let q = l `shiftR` 3
          r = l .&. 7
      i' <- goWord8Chunk 0 r
      goWord64Chunk i' 0 q
     where
      goWord64Chunk :: Int -> Int -> Int -> ST s ()
      goWord64Chunk !off !i' !cl = loop i'
       where
        loop :: Int -> ST s ()
        loop !i
          | i >= cl = return ()
          | otherwise = do
              let w = indexWord8ArrayAsWord64 ba (off + (i * 8))
              writeWord64Array mba (cl  1  i) (byteSwap64 w)
              loop (i+1)
      goWord8Chunk :: Int -> Int -> ST s Int
      goWord8Chunk !i' !cl = loop i'
       where
        loop :: Int -> ST s Int
        loop !i
          | i >= cl = return i
          | otherwise = do
              let w = indexWord8Array ba i
              writeWord8Array mba (l  1  i) w
              loop (i+1)
#else
    in create l (\mba -> go ba mba 0 l)
   where
    go :: BA -> MBA s -> Int -> Int -> ST s ()
    go !ba !mba !i !l
      | i >= l = return ()
      | otherwise = do
          let w = indexWord8Array ba i
          writeWord8Array mba (l  1  i) w
          go ba mba (i+1) l
#endif
intercalate :: ShortByteString -> [ShortByteString] -> ShortByteString
intercalate sep = \case
                    []      -> empty
                    [x]     -> x 
                    (sbs:t) -> let !totalLen = List.foldl' (\acc chunk -> acc +! length sep +! length chunk) (length sbs) t
                               in create totalLen (\mba ->
                                      let !l = length sbs
                                      in copyByteArray (asBA sbs) 0 mba 0 l >> go mba l t)
 where
  ba  = asBA sep
  lba = length sep
  go :: MBA s -> Int -> [ShortByteString] -> ST s ()
  go _ _ [] = pure ()
  go mba !off (chunk:chunks) = do
    let lc = length chunk
    copyByteArray ba 0 mba off lba
    copyByteArray (asBA chunk) 0 mba (off + lba) lc
    go mba (off + lc + lba) chunks
  (+!) = checkedAdd "Short.intercalate"
foldl :: (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl f v = List.foldl f v . unpack
foldl' :: (a -> Word8 -> a) -> a -> ShortByteString -> a
foldl' f v = List.foldl' f v . unpack
foldr :: (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr f v = List.foldr f v . unpack
foldr' :: (Word8 -> a -> a) -> a -> ShortByteString -> a
foldr' k v = Foldable.foldr' k v . unpack
foldl1 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldl1 k = List.foldl1 k . unpack
foldl1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldl1' k = List.foldl1' k . unpack
foldr1 :: HasCallStack => (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldr1 k = List.foldr1 k . unpack
foldr1' :: HasCallStack => (Word8 -> Word8 -> Word8) -> ShortByteString -> Word8
foldr1' k = \sbs -> if null sbs then errorEmptySBS "foldr1'" else foldr' k (last sbs) (init sbs)
all :: (Word8 -> Bool) -> ShortByteString -> Bool
all k = \sbs ->
  let l  = length sbs
      ba = asBA sbs
      w  = indexWord8Array ba
      go !n | n >= l    = True
            | otherwise = k (w n) && go (n + 1)
  in go 0
any :: (Word8 -> Bool) -> ShortByteString -> Bool
any k = \sbs ->
  let l  = length sbs
      ba = asBA sbs
      w  = indexWord8Array ba
      go !n | n >= l    = False
            | otherwise = k (w n) || go (n + 1)
  in go 0
take :: Int -> ShortByteString -> ShortByteString
take = \n -> \sbs -> let sl = length sbs
                     in if | n >= sl   -> sbs
                           | n <= 0    -> empty
                           | otherwise ->
                               create n $ \mba -> copyByteArray (asBA sbs) 0 mba 0 n
takeWhile :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
takeWhile f = \sbs -> take (findIndexOrLength (not . f) sbs) sbs
takeEnd :: Int -> ShortByteString -> ShortByteString
takeEnd n = \sbs -> let sl = length sbs
                    in if | n >= sl   -> sbs
                          | n <= 0    -> empty
                          | otherwise -> create n $ \mba -> copyByteArray (asBA sbs) (max 0 (sl  n)) mba 0 n
takeWhileEnd :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
takeWhileEnd f = \sbs -> drop (findFromEndUntil (not . f) sbs) sbs
drop :: Int -> ShortByteString -> ShortByteString
drop = \n -> \sbs ->
  let len = length sbs
  in if | n <= 0    -> sbs
        | n >= len  -> empty
        | otherwise ->
            let newLen = len  n
            in create newLen $ \mba -> copyByteArray (asBA sbs) n mba 0 newLen
dropEnd :: Int -> ShortByteString -> ShortByteString
dropEnd n = \sbs -> let sl = length sbs
                        nl = sl  n
                    in if | n >= sl   -> empty
                          | n <= 0    -> sbs
                          | otherwise -> create nl $ \mba -> copyByteArray (asBA sbs) 0 mba 0 nl
dropWhile :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
dropWhile f = \sbs -> drop (findIndexOrLength (not . f) sbs) sbs
dropWhileEnd :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
dropWhileEnd f = \sbs -> take (findFromEndUntil (not . f) sbs) sbs
breakEnd :: (Word8 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
breakEnd p = \sbs -> splitAt (findFromEndUntil p sbs) sbs
break :: (Word8 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
break = \p -> \sbs -> case findIndexOrLength p sbs of n -> (take n sbs, drop n sbs)
span :: (Word8 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
span p = break (not . p)
spanEnd :: (Word8 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
spanEnd p = \sbs -> splitAt (findFromEndUntil (not . p) sbs) sbs
splitAt :: Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt n = \sbs -> if
  | n <= 0 -> (empty, sbs)
  | otherwise ->
      let slen = length sbs
      in if | n >= length sbs -> (sbs, empty)
            | otherwise ->
                let llen = min slen (max 0 n)
                    rlen = max 0 (slen  max 0 n)
                    lsbs = create llen $ \mba -> copyByteArray (asBA sbs) 0 mba 0 llen
                    rsbs = create rlen $ \mba -> copyByteArray (asBA sbs) n mba 0 rlen
                in (lsbs, rsbs)
split :: Word8 -> ShortByteString -> [ShortByteString]
split w = splitWith (== w)
splitWith :: (Word8 -> Bool) -> ShortByteString -> [ShortByteString]
splitWith p = \sbs -> if
  | null sbs  -> []
  | otherwise -> go sbs
  where
    go sbs'
      | null sbs' = [empty]
      | otherwise =
          case break p sbs' of
            (a, b)
              | null b    -> [a]
              | otherwise -> a : go (tail b)
stripSuffix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
stripSuffix sbs1 = \sbs2 -> do
  let l1 = length sbs1
      l2 = length sbs2
  if | isSuffixOf sbs1 sbs2 ->
         if null sbs1
         then Just sbs2
         else Just $! create (l2  l1) $ \dst -> do
                copyByteArray (asBA sbs2) 0 dst 0 (l2  l1)
     | otherwise -> Nothing
stripPrefix :: ShortByteString -> ShortByteString -> Maybe ShortByteString
stripPrefix sbs1 = \sbs2 -> do
  let l1 = length sbs1
      l2 = length sbs2
  if | isPrefixOf sbs1 sbs2 ->
         if null sbs1
         then Just sbs2
         else Just $! create (l2  l1) $ \dst -> do
                copyByteArray (asBA sbs2) l1 dst 0 (l2  l1)
     | otherwise -> Nothing
replicate :: Int -> Word8 -> ShortByteString
replicate w c
    | w <= 0    = empty
    | otherwise = create w (\mba -> setByteArray mba 0 w (fromIntegral c))
unfoldr :: (a -> Maybe (Word8, a)) -> a -> ShortByteString
unfoldr f = \x0 -> packBytesRev $ go x0 []
 where
   go x words' = case f x of
                    Nothing      -> words'
                    Just (w, x') -> go x' (w:words')
unfoldrN :: forall a. Int -> (a -> Maybe (Word8, a)) -> a -> (ShortByteString, Maybe a)
unfoldrN i f = \x0 ->
  if | i < 0     -> (empty, Just x0)
     | otherwise -> createAndTrim i $ \mba -> go mba x0 0
  where
    go :: forall s. MBA s -> a -> Int -> ST s (Int, Maybe a)
    go !mba !x !n = go' x n
      where
        go' :: a -> Int -> ST s (Int, Maybe a)
        go' !x' !n'
          | n' == i   = return (n', Just x')
          | otherwise = case f x' of
                          Nothing       -> return (n', Nothing)
                          Just (w, x'') -> do
                                             writeWord8Array mba n' w
                                             go' x'' (n'+1)
isInfixOf :: ShortByteString -> ShortByteString -> Bool
isInfixOf sbs = \s -> null sbs || not (null $ snd $ (GHC.Exts.inline breakSubstring) sbs s)
isPrefixOf :: ShortByteString -> ShortByteString -> Bool
isPrefixOf sbs1 = \sbs2 -> do
  let l1 = length sbs1
      l2 = length sbs2
  if | l1 == 0   -> True
     | l2 < l1   -> False
     | otherwise ->
         let i = compareByteArraysOff (asBA sbs1) 0 (asBA sbs2) 0 l1
         in i == 0
isSuffixOf :: ShortByteString -> ShortByteString -> Bool
isSuffixOf sbs1 = \sbs2 -> do
  let l1 = length sbs1
      l2 = length sbs2
  if | l1 == 0   -> True
     | l2 < l1   -> False
     | otherwise ->
         let i = compareByteArraysOff (asBA sbs1) 0 (asBA sbs2) (l2  l1) l1
         in i == 0
breakSubstring :: ShortByteString 
               -> ShortByteString 
               -> (ShortByteString, ShortByteString) 
breakSubstring pat =
  case lp of
    0 -> (empty,)
    1 -> breakByte (head pat)
    _ -> if lp * 8 <= finiteBitSize (0 :: Word)
             then shift
             else karpRabin
  where
    lp = length pat
    karpRabin :: ShortByteString -> (ShortByteString, ShortByteString)
    karpRabin src
        | length src < lp = (src,empty)
        | otherwise       = search (rollingHash $ take lp src) lp
      where
        k           = 2891336453 :: Word32
        rollingHash = foldl' (\h b -> h * k + fromIntegral b) 0
        hp          = rollingHash pat
        m           = k ^ lp
        get = fromIntegral . unsafeIndex src
        search !hs !i
            | hp == hs && pat == take lp b = u
            | length src <= i              = (src, empty) 
            | otherwise                    = search hs' (i + 1)
          where
            u@(_, b) = splitAt (i  lp) src
            hs' = hs * k +
                  get i 
                  m * get (i  lp)
    
    shift :: ShortByteString -> (ShortByteString, ShortByteString)
    shift !src
        | length src < lp = (src, empty)
        | otherwise       = search (intoWord $ take lp src) lp
      where
        intoWord :: ShortByteString -> Word
        intoWord = foldl' (\w b -> (w `shiftL` 8) .|. fromIntegral b) 0
        wp    = intoWord pat
        mask' = (1 `shiftL` (8 * lp))  1
        search !w !i
            | w == wp         = splitAt (i  lp) src
            | length src <= i = (src, empty)
            | otherwise       = search w' (i + 1)
          where
            b  = fromIntegral (unsafeIndex src i)
            w' = mask' .&. ((w `shiftL` 8) .|. b)
    
elem :: Word8 -> ShortByteString -> Bool
elem c = \sbs -> case elemIndex c sbs of Nothing -> False ; _ -> True
filter :: (Word8 -> Bool) -> ShortByteString -> ShortByteString
filter k = \sbs -> let l = length sbs
                   in if | l <= 0    -> sbs
                         | otherwise -> createAndTrim' l $ \mba -> go mba (asBA sbs) l
  where
    go :: forall s. MBA s 
       -> BA              
       -> Int             
       -> ST s Int
    go !mba ba !l = go' 0 0
      where
        go' :: Int 
            -> Int 
            -> ST s Int
        go' !br !bw
          | br >= l   = return bw
          | otherwise = do
              let w = indexWord8Array ba br
              if k w
              then do
                writeWord8Array mba bw w
                go' (br+1) (bw+1)
              else
                go' (br+1) bw
find :: (Word8 -> Bool) -> ShortByteString -> Maybe Word8
find f = \sbs -> case findIndex f sbs of
                    Just n -> Just (sbs `index` n)
                    _      -> Nothing
partition :: (Word8 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
partition k = \sbs -> let l = length sbs
                   in if | l <= 0    -> (sbs, sbs)
                         | otherwise -> createAndTrim'' l $ \mba1 mba2 -> go mba1 mba2 (asBA sbs) l
  where
    go :: forall s.
          MBA s           
       -> MBA s           
       -> BA              
       -> Int             
       -> ST s (Int, Int) 
    go !mba1 !mba2 ba !l = go' 0 0
      where
        go' :: Int 
            -> Int 
            -> ST s (Int, Int) 
        go' !br !bw1
          | br >= l   = return (bw1, br  bw1)
          | otherwise = do
              let w = indexWord8Array ba br
              if k w
              then do
                writeWord8Array mba1 bw1 w
                go' (br+1) (bw1+1)
              else do
                writeWord8Array mba2 (br  bw1) w
                go' (br+1) bw1
elemIndex :: Word8 -> ShortByteString -> Maybe Int
elemIndex c = \sbs@(SBS ba#) -> do
    let l = length sbs
    accursedUnutterablePerformIO $ do
      !s <- c_elem_index ba# c (fromIntegral l)
      return $! if s < 0 then Nothing else Just (fromIntegral s)
elemIndices :: Word8 -> ShortByteString -> [Int]
elemIndices k = findIndices (==k)
count :: Word8 -> ShortByteString -> Int
count w = \sbs@(SBS ba#) -> accursedUnutterablePerformIO $
    fromIntegral <$> c_count ba# (fromIntegral $ length sbs) w
findIndex :: (Word8 -> Bool) -> ShortByteString -> Maybe Int
findIndex k = \sbs ->
  let l  = length sbs
      ba = asBA sbs
      w  = indexWord8Array ba
      go !n | n >= l    = Nothing
            | k (w n)   = Just n
            | otherwise = go (n + 1)
  in go 0
findIndices :: (Word8 -> Bool) -> ShortByteString -> [Int]
findIndices k = \sbs ->
  let l  = length sbs
      ba = asBA sbs
      w  = indexWord8Array ba
      go !n | n >= l    = []
            | k (w n)   = n : go (n + 1)
            | otherwise = go (n + 1)
  in go 0
copyToPtr :: ShortByteString  
          -> Int              
          -> Ptr a            
          -> Int              
          -> IO ()
copyToPtr src off dst len =
    stToIO $
      copyByteArrayToAddr (asBA src) off dst len
createFromPtr :: Ptr a   
              -> Int     
              -> IO ShortByteString
createFromPtr !ptr len =
    stToIO $ do
      mba <- newByteArray len
      copyAddrToByteArray ptr mba 0 len
      BA# ba# <- unsafeFreezeByteArray mba
      return (SBS ba#)
data BA    = BA# ByteArray#
data MBA s = MBA# (MutableByteArray# s)
indexCharArray :: BA -> Int -> Char
indexCharArray (BA# ba#) (I# i#) = C# (indexCharArray# ba# i#)
indexWord8Array :: BA -> Int -> Word8
indexWord8Array (BA# ba#) (I# i#) = W8# (indexWord8Array# ba# i#)
#if MIN_VERSION_base(4,12,0) && defined(SAFE_UNALIGNED)
indexWord8ArrayAsWord64 :: BA -> Int -> Word64
indexWord8ArrayAsWord64 (BA# ba#) (I# i#) = W64# (indexWord8ArrayAsWord64# ba# i#)
#endif
newByteArray :: Int -> ST s (MBA s)
newByteArray (I# len#) =
    ST $ \s -> case newByteArray# len# s of
                 (# s, mba# #) -> (# s, MBA# mba# #)
newPinnedByteArray :: Int -> ST s (MBA s)
newPinnedByteArray (I# len#) =
    ST $ \s -> case newPinnedByteArray# len# s of
                 (# s, mba# #) -> (# s, MBA# mba# #)
unsafeFreezeByteArray :: MBA s -> ST s BA
unsafeFreezeByteArray (MBA# mba#) =
    ST $ \s -> case unsafeFreezeByteArray# mba# s of
                 (# s, ba# #) -> (# s, BA# ba# #)
writeWord8Array :: MBA s -> Int -> Word8 -> ST s ()
writeWord8Array (MBA# mba#) (I# i#) (W8# w#) =
  ST $ \s -> case writeWord8Array# mba# i# w# s of
               s -> (# s, () #)
#if MIN_VERSION_base(4,12,0) && defined(SAFE_UNALIGNED)
writeWord64Array :: MBA s -> Int -> Word64 -> ST s ()
writeWord64Array (MBA# mba#) (I# i#) (W64# w#) =
  ST $ \s -> case writeWord64Array# mba# i# w# s of
               s -> (# s, () #)
#endif
copyAddrToByteArray :: Ptr a -> MBA RealWorld -> Int -> Int -> ST RealWorld ()
copyAddrToByteArray (Ptr src#) (MBA# dst#) (I# dst_off#) (I# len#) =
    ST $ \s -> case copyAddrToByteArray# src# dst# dst_off# len# s of
                 s -> (# s, () #)
copyByteArrayToAddr :: BA -> Int -> Ptr a -> Int -> ST RealWorld ()
copyByteArrayToAddr (BA# src#) (I# src_off#) (Ptr dst#) (I# len#) =
    ST $ \s -> case copyByteArrayToAddr# src# src_off# dst# len# s of
                 s -> (# s, () #)
copyByteArray :: BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (BA# src#) (I# src_off#) (MBA# dst#) (I# dst_off#) (I# len#) =
    ST $ \s -> case copyByteArray# src# src_off# dst# dst_off# len# s of
                 s -> (# s, () #)
setByteArray :: MBA s -> Int -> Int -> Int -> ST s ()
setByteArray (MBA# dst#) (I# off#) (I# len#) (I# c#) =
    ST $ \s -> case setByteArray# dst# off# len# c# s of
                 s -> (# s, () #)
copyMutableByteArray :: MBA s -> Int -> MBA s -> Int -> Int -> ST s ()
copyMutableByteArray (MBA# src#) (I# src_off#) (MBA# dst#) (I# dst_off#) (I# len#) =
    ST $ \s -> case copyMutableByteArray# src# src_off# dst# dst_off# len# s of
                 s -> (# s, () #)
compareByteArrays :: BA -> BA -> Int -> Int
compareByteArrays ba1 ba2 = compareByteArraysOff ba1 0 ba2 0
compareByteArraysOff :: BA  
                     -> Int 
                     -> BA  
                     -> Int 
                     -> Int 
                     -> Int 
#if MIN_VERSION_base(4,11,0)
compareByteArraysOff (BA# ba1#) (I# ba1off#) (BA# ba2#) (I# ba2off#) (I# len#) =
  I# (compareByteArrays#  ba1# ba1off# ba2# ba2off# len#)
#else
compareByteArraysOff (BA# ba1#) ba1off (BA# ba2#) ba2off len =
  assert (ba1off + len <= (I# (sizeofByteArray# ba1#)))
  $ assert (ba2off + len <= (I# (sizeofByteArray# ba2#)))
  $ fromIntegral $ accursedUnutterablePerformIO $
    c_memcmp_ByteArray ba1#
                       ba1off
                       ba2#
                       ba2off
                       (fromIntegral len)
foreign import ccall unsafe "static sbs_memcmp_off"
  c_memcmp_ByteArray :: ByteArray# -> Int -> ByteArray# -> Int -> CSize -> IO CInt
#endif
foreign import ccall unsafe "static sbs_elem_index"
    c_elem_index :: ByteArray# -> Word8 -> CSize -> IO CPtrdiff
foreign import ccall unsafe "static fpstring.h fps_count" c_count
    :: ByteArray# -> CSize -> Word8 -> IO CSize
copyAddrToByteArray# :: Addr#
                     -> MutableByteArray# RealWorld -> Int#
                     -> Int#
                     -> State# RealWorld -> State# RealWorld
copyByteArrayToAddr# :: ByteArray# -> Int#
                     -> Addr#
                     -> Int#
                     -> State# RealWorld -> State# RealWorld
copyByteArray#       :: ByteArray# -> Int#
                     -> MutableByteArray# s -> Int#
                     -> Int#
                     -> State# s -> State# s
copyAddrToByteArray# = GHC.Exts.copyAddrToByteArray#
copyByteArrayToAddr# = GHC.Exts.copyByteArrayToAddr#
copyByteArray# = GHC.Exts.copyByteArray#
packCString :: CString -> IO ShortByteString
packCString cstr = do
  len <- BS.c_strlen cstr
  packCStringLen (cstr, fromIntegral len)
packCStringLen :: CStringLen -> IO ShortByteString
packCStringLen (cstr, len) | len >= 0 = createFromPtr cstr len
packCStringLen (_, len) =
  moduleErrorIO "packCStringLen" ("negative length: " ++ show len)
useAsCString :: ShortByteString -> (CString -> IO a) -> IO a
useAsCString sbs action =
  allocaBytes (l+1) $ \buf -> do
      copyToPtr sbs 0 buf (fromIntegral l)
      pokeByteOff buf l (0::Word8)
      action buf
  where l = length sbs
useAsCStringLen :: ShortByteString -> (CStringLen -> IO a) -> IO a
useAsCStringLen sbs action =
  allocaBytes l $ \buf -> do
      copyToPtr sbs 0 buf (fromIntegral l)
      action (buf, l)
  where l = length sbs
isValidUtf8 :: ShortByteString -> Bool
isValidUtf8 sbs@(SBS ba#) = accursedUnutterablePerformIO $ do
  let n = length sbs
  
  
  
  
  
  
  i <- if n < 1000000 || not (isPinned ba#)
     then cIsValidUtf8 ba# (fromIntegral n)
     else cIsValidUtf8Safe ba# (fromIntegral n)
  IO (\s -> (# touch# ba# s, () #))
  return $ i /= 0
foreign import ccall unsafe "bytestring_is_valid_utf8" cIsValidUtf8
  :: ByteArray# -> CSize -> IO CInt
foreign import ccall safe "bytestring_is_valid_utf8" cIsValidUtf8Safe
  :: ByteArray# -> CSize -> IO CInt
moduleErrorIO :: HasCallStack => String -> String -> IO a
moduleErrorIO fun msg = throwIO . userError $ moduleErrorMsg fun msg
moduleErrorMsg :: String -> String -> String
moduleErrorMsg fun msg = "Data.ByteString.Short." ++ fun ++ ':':' ':msg
findFromEndUntil :: (Word8 -> Bool) -> ShortByteString -> Int
findFromEndUntil k sbs = go (length sbs  1)
  where
    ba = asBA sbs
    go !n | n < 0                    = 0
          | k (indexWord8Array ba n) = n + 1
          | otherwise                = go (n  1)
findIndexOrLength :: (Word8 -> Bool) -> ShortByteString -> Int
findIndexOrLength k sbs = go 0
  where
    l = length sbs
    ba = asBA sbs
    go !n | n >= l                   = l
          | k (indexWord8Array ba n) = n
          | otherwise                = go (n + 1)
packBytesRev :: [Word8] -> ShortByteString
packBytesRev cs = packLenBytesRev (List.length cs) cs
packLenBytesRev :: Int -> [Word8] -> ShortByteString
packLenBytesRev len ws0 =
    create len (\mba -> go mba len ws0)
  where
    go :: MBA s -> Int -> [Word8] -> ST s ()
    go !_   !_ []     = return ()
    go !mba !i (w:ws) = do
      writeWord8Array mba (i  1) w
      go mba (i  1) ws
breakByte :: Word8 -> ShortByteString -> (ShortByteString, ShortByteString)
breakByte c sbs = case elemIndex c sbs of
    Nothing -> (sbs, empty)
    Just n  -> (take n sbs, drop n sbs)
errorEmptySBS :: HasCallStack => String -> a
errorEmptySBS fun = moduleError fun "empty ShortByteString"
moduleError :: HasCallStack => String -> String -> a
moduleError fun msg = error (moduleErrorMsg fun msg)