{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE MultiWayIf #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# OPTIONS_GHC -fno-warn-name-shadowing -fexpose-all-unfoldings #-}
module System.OsPath.Data.ByteString.Short.Word16 (
    
    ShortByteString(..),
    
    empty,
    singleton,
    pack,
    unpack,
    fromShort,
    toShort,
    
    snoc,
    cons,
    append,
    last,
    tail,
    uncons,
    head,
    init,
    unsnoc,
    null,
    length,
    numWord16,
    
    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,
    
    
    
    
    packCWString,
    packCWStringLen,
    newCWString,
   
    
    useAsCWString,
    useAsCWStringLen
  )
where
import System.OsPath.Data.ByteString.Short ( append, intercalate, concat, stripSuffix, stripPrefix, isInfixOf, isPrefixOf, isSuffixOf, breakSubstring, length, empty, null, ShortByteString(..), fromShort, toShort )
import System.OsPath.Data.ByteString.Short.Internal
import Data.Bits
    ( shiftR )
import Data.Word
import Prelude hiding
    ( all
    , any
    , reverse
    , break
    , concat
    , drop
    , dropWhile
    , elem
    , filter
    , foldl
    , foldl1
    , foldr
    , foldr1
    , head
    , init
    , last
    , length
    , map
    , null
    , replicate
    , span
    , splitAt
    , tail
    , take
    , takeWhile
    )
import qualified Data.Foldable as Foldable
import GHC.ST ( ST )
import GHC.Stack ( HasCallStack )
import qualified Data.ByteString.Short.Internal as BS
import qualified Data.List as List
singleton :: Word16 -> ShortByteString
singleton :: Word16 -> ShortByteString
singleton = \Word16
w -> Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
2 (\MBA s
mba -> forall s. MBA s -> Int -> Word16 -> ST s ()
writeWord16Array MBA s
mba Int
0 Word16
w)
pack :: [Word16] -> ShortByteString
pack :: [Word16] -> ShortByteString
pack = [Word16] -> ShortByteString
packWord16
unpack :: ShortByteString -> [Word16]
unpack :: ShortByteString -> [Word16]
unpack = ShortByteString -> [Word16]
unpackWord16 forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
numWord16 :: ShortByteString -> Int
numWord16 :: ShortByteString -> Int
numWord16 = (forall a. Bits a => a -> Int -> a
`shiftR` Int
1) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> Int
BS.length forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
infixr 5 `cons` 
infixl 5 `snoc`
snoc :: ShortByteString -> Word16 -> ShortByteString
snoc :: ShortByteString -> Word16 -> ShortByteString
snoc = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) Word16
c -> let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
                                     nl :: Int
nl = Int
l forall a. Num a => a -> a -> a
+ Int
2
  in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> do
      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
      forall s. MBA s -> Int -> Word16 -> ST s ()
writeWord16Array MBA s
mba Int
l Word16
c
cons :: Word16 -> ShortByteString -> ShortByteString
cons :: Word16 -> ShortByteString -> ShortByteString
cons Word16
c = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) -> let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
                                     nl :: Int
nl = Int
l forall a. Num a => a -> a -> a
+ Int
2
  in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> do
      forall s. MBA s -> Int -> Word16 -> ST s ()
writeWord16Array MBA s
mba Int
0 Word16
c
      forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
2 Int
l
last :: HasCallStack => ShortByteString -> Word16
last :: HasCallStack => ShortByteString -> Word16
last = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) -> case ShortByteString -> Bool
null ShortByteString
sbs of
  Bool
True -> forall a. HasCallStack => String -> a
errorEmptySBS String
"last"
  Bool
False -> BA -> Int -> Word16
indexWord16Array (ShortByteString -> BA
asBA ShortByteString
sbs) (ShortByteString -> Int
BS.length ShortByteString
sbs forall a. Num a => a -> a -> a
- Int
2)
tail :: HasCallStack => ShortByteString -> ShortByteString
tail :: HasCallStack => ShortByteString -> ShortByteString
tail = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) -> 
  let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
      nl :: Int
nl = Int
l forall a. Num a => a -> a -> a
- Int
2
  in if
      | Int
l forall a. Ord a => a -> a -> Bool
<= Int
0 -> forall a. HasCallStack => String -> a
errorEmptySBS String
"tail"
      | Bool
otherwise -> Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
2 MBA s
mba Int
0 Int
nl
uncons :: ShortByteString -> Maybe (Word16, ShortByteString)
uncons :: ShortByteString -> Maybe (Word16, ShortByteString)
uncons = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
  let l :: Int
l  = ShortByteString -> Int
BS.length ShortByteString
sbs
      nl :: Int
nl = Int
l forall a. Num a => a -> a -> a
- Int
2
  in if | Int
l forall a. Ord a => a -> a -> Bool
<= Int
0 -> forall a. Maybe a
Nothing
        | Bool
otherwise -> let h :: Word16
h = BA -> Int -> Word16
indexWord16Array (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0
                           t :: ShortByteString
t = Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
2 MBA s
mba Int
0 Int
nl
                       in forall a. a -> Maybe a
Just (Word16
h, ShortByteString
t)
head :: HasCallStack => ShortByteString -> Word16
head :: HasCallStack => ShortByteString -> Word16
head = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) -> case ShortByteString -> Bool
null ShortByteString
sbs of
  Bool
True -> forall a. HasCallStack => String -> a
errorEmptySBS String
"last"
  Bool
False -> BA -> Int -> Word16
indexWord16Array (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0
init :: HasCallStack => ShortByteString -> ShortByteString
init :: HasCallStack => ShortByteString -> ShortByteString
init = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
  let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
      nl :: Int
nl = Int
l forall a. Num a => a -> a -> a
- Int
2
  in if
      | Int
l forall a. Ord a => a -> a -> Bool
<= Int
0 -> forall a. HasCallStack => String -> a
errorEmptySBS String
"tail"
      | Bool
otherwise   -> Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> 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
unsnoc :: ShortByteString -> Maybe (ShortByteString, Word16)
unsnoc :: ShortByteString -> Maybe (ShortByteString, Word16)
unsnoc = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
  let l :: Int
l  = ShortByteString -> Int
BS.length ShortByteString
sbs
      nl :: Int
nl = Int
l forall a. Num a => a -> a -> a
- Int
2
  in if | Int
l forall a. Ord a => a -> a -> Bool
<= Int
0 -> forall a. Maybe a
Nothing
        | Bool
otherwise -> let l' :: Word16
l' = BA -> Int -> Word16
indexWord16Array (ShortByteString -> BA
asBA ShortByteString
sbs) (Int
l forall a. Num a => a -> a -> a
- Int
2)
                           i :: ShortByteString
i  = Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> 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
                       in forall a. a -> Maybe a
Just (ShortByteString
i, Word16
l')
map :: (Word16 -> Word16) -> ShortByteString -> ShortByteString
map :: (Word16 -> Word16) -> ShortByteString -> ShortByteString
map Word16 -> Word16
f = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
    let l :: Int
l = ShortByteString -> Int
BS.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 -> 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 :: forall s. BA -> MBA s -> Int -> Int -> ST s ()
go !BA
ba !MBA s
mba !Int
i !Int
l
      | Int
i forall a. Ord a => a -> a -> Bool
>= Int
l = forall (m :: * -> *) a. Monad m => a -> m a
return ()
      | Bool
otherwise = do
          let w :: Word16
w = BA -> Int -> Word16
indexWord16Array BA
ba Int
i
          forall s. MBA s -> Int -> Word16 -> ST s ()
writeWord16Array MBA s
mba Int
i (Word16 -> Word16
f Word16
w)
          forall s. BA -> MBA s -> Int -> Int -> ST s ()
go BA
ba MBA s
mba (Int
iforall a. Num a => a -> a -> a
+Int
2) Int
l
reverse :: ShortByteString -> ShortByteString
reverse :: ShortByteString -> ShortByteString
reverse = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
    let l :: Int
l = ShortByteString -> Int
BS.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 -> 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 :: forall s. BA -> MBA s -> Int -> Int -> ST s ()
go !BA
ba !MBA s
mba !Int
i !Int
l
      | Int
i forall a. Ord a => a -> a -> Bool
>= Int
l = forall (m :: * -> *) a. Monad m => a -> m a
return ()
      | Bool
otherwise = do
          let w :: Word16
w = BA -> Int -> Word16
indexWord16Array BA
ba Int
i
          forall s. MBA s -> Int -> Word16 -> ST s ()
writeWord16Array MBA s
mba (Int
l forall a. Num a => a -> a -> a
- Int
2 forall a. Num a => a -> a -> a
- Int
i) Word16
w
          forall s. BA -> MBA s -> Int -> Int -> ST s ()
go BA
ba MBA s
mba (Int
iforall a. Num a => a -> a -> a
+Int
2) Int
l
all :: (Word16 -> Bool) -> ShortByteString -> Bool
all :: (Word16 -> Bool) -> ShortByteString -> Bool
all Word16 -> Bool
k = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) -> 
  let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
      ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
      w :: Int -> Word16
w = BA -> Int -> Word16
indexWord16Array BA
ba
      go :: Int -> Bool
go !Int
n | Int
n forall a. Ord a => a -> a -> Bool
>= Int
l = Bool
True
            | Bool
otherwise = Word16 -> Bool
k (Int -> Word16
w Int
n) Bool -> Bool -> Bool
&& Int -> Bool
go (Int
n forall a. Num a => a -> a -> a
+ Int
2)
  in Int -> Bool
go Int
0
any :: (Word16 -> Bool) -> ShortByteString -> Bool
any :: (Word16 -> Bool) -> ShortByteString -> Bool
any Word16 -> Bool
k = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
  let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
      ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
      w :: Int -> Word16
w = BA -> Int -> Word16
indexWord16Array BA
ba
      go :: Int -> Bool
go !Int
n | Int
n forall a. Ord a => a -> a -> Bool
>= Int
l = Bool
False
            | Bool
otherwise = Word16 -> Bool
k (Int -> Word16
w Int
n) Bool -> Bool -> Bool
|| Int -> Bool
go (Int
n forall a. Num a => a -> a -> a
+ Int
2)
  in Int -> Bool
go Int
0
replicate :: Int -> Word16 -> ShortByteString
replicate :: Int -> Word16 -> ShortByteString
replicate Int
w Word16
c
    | Int
w forall a. Ord a => a -> a -> Bool
<= Int
0    = ShortByteString
empty
    
    | Bool
otherwise = Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create (Int
w forall a. Num a => a -> a -> a
* Int
2) (forall {s}. MBA s -> Int -> ST s ()
`go` Int
0)
  where
    go :: MBA s -> Int -> ST s ()
go MBA s
mba Int
ix
      | Int
ix forall a. Ord a => a -> a -> Bool
< Int
0 Bool -> Bool -> Bool
|| Int
ix forall a. Ord a => a -> a -> Bool
>= Int
w forall a. Num a => a -> a -> a
* Int
2 = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
      | Bool
otherwise = forall s. MBA s -> Int -> Word16 -> ST s ()
writeWord16Array MBA s
mba Int
ix Word16
c forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> MBA s -> Int -> ST s ()
go MBA s
mba (Int
ix forall a. Num a => a -> a -> a
+ Int
2)
unfoldr :: (a -> Maybe (Word16, a)) -> a -> ShortByteString
unfoldr :: forall a. (a -> Maybe (Word16, a)) -> a -> ShortByteString
unfoldr a -> Maybe (Word16, a)
f a
x0 = [Word16] -> ShortByteString
packWord16Rev forall a b. (a -> b) -> a -> b
$ a -> [Word16] -> [Word16]
go a
x0 forall a. Monoid a => a
mempty
 where
   go :: a -> [Word16] -> [Word16]
go a
x [Word16]
words' = case a -> Maybe (Word16, a)
f a
x of
                    Maybe (Word16, a)
Nothing -> [Word16]
words'
                    Just (Word16
w, a
x') -> a -> [Word16] -> [Word16]
go a
x' (Word16
wforall a. a -> [a] -> [a]
:[Word16]
words')
unfoldrN :: forall a.
            Int  
         -> (a -> Maybe (Word16, a))
         -> a
         -> (ShortByteString, Maybe a)
unfoldrN :: forall a.
Int -> (a -> Maybe (Word16, a)) -> a -> (ShortByteString, Maybe a)
unfoldrN Int
i a -> Maybe (Word16, a)
f = \a
x0 ->
  if | Int
i forall a. Ord a => a -> a -> Bool
< Int
0     -> (ShortByteString
empty, forall a. a -> Maybe a
Just a
x0)
     | Bool
otherwise -> forall a.
Int -> (forall s. MBA s -> ST s (Int, a)) -> (ShortByteString, a)
createAndTrim (Int
i forall a. Num a => a -> a -> a
* Int
2) forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> forall s. MBA s -> a -> Int -> ST s (Int, Maybe a)
go MBA s
mba a
x0 Int
0
  where
    go :: forall s. MBA s -> a -> Int -> ST s (Int, Maybe a)
    go :: forall s. MBA s -> a -> Int -> ST s (Int, Maybe a)
go !MBA s
mba !a
x !Int
n = a -> Int -> ST s (Int, Maybe a)
go' a
x Int
n
      where
        go' :: a -> Int -> ST s (Int, Maybe a)
        go' :: a -> Int -> ST s (Int, Maybe a)
go' !a
x' !Int
n'
          | Int
n' forall a. Eq a => a -> a -> Bool
== Int
i forall a. Num a => a -> a -> a
* Int
2 = forall (m :: * -> *) a. Monad m => a -> m a
return (Int
n', forall a. a -> Maybe a
Just a
x')
          | Bool
otherwise   = case a -> Maybe (Word16, a)
f a
x' of
                          Maybe (Word16, a)
Nothing       -> forall (m :: * -> *) a. Monad m => a -> m a
return (Int
n', forall a. Maybe a
Nothing)
                          Just (Word16
w, a
x'') -> do
                                             forall s. MBA s -> Int -> Word16 -> ST s ()
writeWord16Array MBA s
mba Int
n' Word16
w
                                             a -> Int -> ST s (Int, Maybe a)
go' a
x'' (Int
n'forall a. Num a => a -> a -> a
+Int
2)
take :: Int  
     -> ShortByteString
     -> ShortByteString
take :: Int -> ShortByteString -> ShortByteString
take = \Int
n (ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
                     let sl :: Int
sl   = ShortByteString -> Int
numWord16 ShortByteString
sbs
                         len8 :: Int
len8 = Int
n forall a. Num a => a -> a -> a
* Int
2
                     in if | Int
n forall a. Ord a => a -> a -> Bool
>= Int
sl   -> ShortByteString
sbs
                           | Int
n forall a. Ord a => a -> a -> Bool
<= Int
0    -> ShortByteString
empty
                           | Bool
otherwise ->
                               Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
len8 forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
0 Int
len8
takeEnd :: Int  
        -> ShortByteString
        -> ShortByteString
takeEnd :: Int -> ShortByteString -> ShortByteString
takeEnd Int
n = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
                    let sl :: Int
sl = ShortByteString -> Int
BS.length ShortByteString
sbs
                        n2 :: Int
n2 = Int
n forall a. Num a => a -> a -> a
* Int
2
                    in if | Int
n2 forall a. Ord a => a -> a -> Bool
>= Int
sl  -> ShortByteString
sbs
                          | Int
n2 forall a. Ord a => a -> a -> Bool
<= Int
0   -> ShortByteString
empty
                          | Bool
otherwise -> Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
n2 forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) (forall a. Ord a => a -> a -> a
max Int
0 (Int
sl forall a. Num a => a -> a -> a
- Int
n2)) MBA s
mba Int
0 Int
n2
takeWhile :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
takeWhile :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
takeWhile Word16 -> Bool
f ShortByteString
ps = Int -> ShortByteString -> ShortByteString
take ((Word16 -> Bool) -> ShortByteString -> Int
findIndexOrLength (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Bool
f) ShortByteString
ps) ShortByteString
ps
takeWhileEnd :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
takeWhileEnd :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
takeWhileEnd Word16 -> Bool
f ShortByteString
ps = Int -> ShortByteString -> ShortByteString
drop ((Word16 -> Bool) -> ShortByteString -> Int
findFromEndUntil (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Bool
f) ShortByteString
ps) ShortByteString
ps
drop  :: Int  
      -> ShortByteString
      -> ShortByteString
drop :: Int -> ShortByteString -> ShortByteString
drop = \Int
n' (ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
  let len :: Int
len = ShortByteString -> Int
BS.length ShortByteString
sbs
      n :: Int
n   = Int
n' forall a. Num a => a -> a -> a
* Int
2
  in if | Int
n forall a. Ord a => a -> a -> Bool
<= Int
0    -> ShortByteString
sbs
        | Int
n forall a. Ord a => a -> a -> Bool
>= Int
len  -> ShortByteString
empty
        | Bool
otherwise ->
            let newLen :: Int
newLen = Int
len forall a. Num a => a -> a -> a
- Int
n
            in Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
newLen forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> 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
dropEnd :: Int  
        -> ShortByteString
        -> ShortByteString
dropEnd :: Int -> ShortByteString -> ShortByteString
dropEnd Int
n' = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
                    let sl :: Int
sl = ShortByteString -> Int
BS.length ShortByteString
sbs
                        nl :: Int
nl = Int
sl forall a. Num a => a -> a -> a
- Int
n
                        n :: Int
n  = Int
n' forall a. Num a => a -> a -> a
* Int
2
                    in if | Int
n forall a. Ord a => a -> a -> Bool
>= Int
sl   -> ShortByteString
empty
                          | Int
n forall a. Ord a => a -> a -> Bool
<= Int
0    -> ShortByteString
sbs
                          | Bool
otherwise -> Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
nl forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> 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
dropWhile :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
dropWhile :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
dropWhile Word16 -> Bool
f = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
ps) -> Int -> ShortByteString -> ShortByteString
drop ((Word16 -> Bool) -> ShortByteString -> Int
findIndexOrLength (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Bool
f) ShortByteString
ps) ShortByteString
ps
dropWhileEnd :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
dropWhileEnd :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
dropWhileEnd Word16 -> Bool
f = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
ps) -> Int -> ShortByteString -> ShortByteString
take ((Word16 -> Bool) -> ShortByteString -> Int
findFromEndUntil (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Bool
f) ShortByteString
ps) ShortByteString
ps
breakEnd :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
breakEnd :: (Word16 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
breakEnd Word16 -> Bool
p = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) -> Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt ((Word16 -> Bool) -> ShortByteString -> Int
findFromEndUntil Word16 -> Bool
p ShortByteString
sbs) ShortByteString
sbs
break :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
break :: (Word16 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
break = \Word16 -> Bool
p (ShortByteString -> ShortByteString
assertEven -> ShortByteString
ps) -> case (Word16 -> Bool) -> ShortByteString -> Int
findIndexOrLength Word16 -> Bool
p ShortByteString
ps of Int
n -> Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt Int
n ShortByteString
ps
span :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
span :: (Word16 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
span Word16 -> Bool
p = (Word16 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
break (Bool -> Bool
not forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Bool
p) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
spanEnd :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
spanEnd :: (Word16 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
spanEnd  Word16 -> Bool
p = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
ps) -> Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt ((Word16 -> Bool) -> ShortByteString -> Int
findFromEndUntil (Bool -> Bool
notforall b c a. (b -> c) -> (a -> b) -> a -> c
.Word16 -> Bool
p) ShortByteString
ps) ShortByteString
ps
splitAt :: Int 
        -> ShortByteString
        -> (ShortByteString, ShortByteString)
splitAt :: Int -> ShortByteString -> (ShortByteString, ShortByteString)
splitAt Int
n' = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) -> if
  | Int
n forall a. Ord a => a -> a -> Bool
<= Int
0 -> (ShortByteString
empty, ShortByteString
sbs)
  | Bool
otherwise ->
      let slen :: Int
slen = ShortByteString -> Int
BS.length ShortByteString
sbs
      in if | Int
n forall a. Ord a => a -> a -> Bool
>= ShortByteString -> Int
BS.length ShortByteString
sbs -> (ShortByteString
sbs, ShortByteString
empty)
            | Bool
otherwise ->
                let llen :: Int
llen = forall a. Ord a => a -> a -> a
min Int
slen (forall a. Ord a => a -> a -> a
max Int
0 Int
n)
                    rlen :: Int
rlen = forall a. Ord a => a -> a -> a
max Int
0 (Int
slen forall a. Num a => a -> a -> a
- forall a. Ord a => a -> a -> a
max Int
0 Int
n)
                    lsbs :: ShortByteString
lsbs = Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
llen forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
0 MBA s
mba Int
0 Int
llen
                    rsbs :: ShortByteString
rsbs = Int -> (forall s. MBA s -> ST s ()) -> ShortByteString
create Int
rlen forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> forall s. BA -> Int -> MBA s -> Int -> Int -> ST s ()
copyByteArray (ShortByteString -> BA
asBA ShortByteString
sbs) Int
n MBA s
mba Int
0 Int
rlen
                in (ShortByteString
lsbs, ShortByteString
rsbs)
 where
  n :: Int
n = Int
n' forall a. Num a => a -> a -> a
* Int
2
split :: Word16 -> ShortByteString -> [ShortByteString]
split :: Word16 -> ShortByteString -> [ShortByteString]
split Word16
w = (Word16 -> Bool) -> ShortByteString -> [ShortByteString]
splitWith (forall a. Eq a => a -> a -> Bool
== Word16
w) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
splitWith :: (Word16 -> Bool) -> ShortByteString -> [ShortByteString]
splitWith :: (Word16 -> Bool) -> ShortByteString -> [ShortByteString]
splitWith Word16 -> Bool
p = \(ShortByteString -> ShortByteString
assertEven -> 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' = [forall a. Monoid a => a
mempty]
      | Bool
otherwise =
          case (Word16 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
break Word16 -> Bool
p ShortByteString
sbs' of
            (ShortByteString
a, ShortByteString
b)
              | ShortByteString -> Bool
BS.null ShortByteString
b -> [ShortByteString
a]
              | Bool
otherwise -> ShortByteString
a forall a. a -> [a] -> [a]
: ShortByteString -> [ShortByteString]
go (HasCallStack => ShortByteString -> ShortByteString
tail ShortByteString
b)
foldl :: (a -> Word16 -> a) -> a -> ShortByteString -> a
foldl :: forall a. (a -> Word16 -> a) -> a -> ShortByteString -> a
foldl a -> Word16 -> a
f a
v = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl a -> Word16 -> a
f a
v forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word16]
unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
foldl' :: (a -> Word16 -> a) -> a -> ShortByteString -> a
foldl' :: forall a. (a -> Word16 -> a) -> a -> ShortByteString -> a
foldl' a -> Word16 -> a
f a
v = forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
List.foldl' a -> Word16 -> a
f a
v forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word16]
unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
foldr :: (Word16 -> a -> a) -> a -> ShortByteString -> a
foldr :: forall a. (Word16 -> a -> a) -> a -> ShortByteString -> a
foldr Word16 -> a -> a
f a
v = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
List.foldr Word16 -> a -> a
f a
v forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word16]
unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
foldr' :: (Word16 -> a -> a) -> a -> ShortByteString -> a
foldr' :: forall a. (Word16 -> a -> a) -> a -> ShortByteString -> a
foldr' Word16 -> a -> a
k a
v = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
Foldable.foldr' Word16 -> a -> a
k a
v forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word16]
unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
foldl1 :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16
foldl1 :: HasCallStack =>
(Word16 -> Word16 -> Word16) -> ShortByteString -> Word16
foldl1 Word16 -> Word16 -> Word16
k = forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
List.foldl1 Word16 -> Word16 -> Word16
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word16]
unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
foldl1' :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16
foldl1' :: HasCallStack =>
(Word16 -> Word16 -> Word16) -> ShortByteString -> Word16
foldl1' Word16 -> Word16 -> Word16
k = forall a. (a -> a -> a) -> [a] -> a
List.foldl1' Word16 -> Word16 -> Word16
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word16]
unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
foldr1 :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16
foldr1 :: HasCallStack =>
(Word16 -> Word16 -> Word16) -> ShortByteString -> Word16
foldr1 Word16 -> Word16 -> Word16
k = forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a
List.foldr1 Word16 -> Word16 -> Word16
k forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> [Word16]
unpack forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
foldr1' :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16
foldr1' :: HasCallStack =>
(Word16 -> Word16 -> Word16) -> ShortByteString -> Word16
foldr1' Word16 -> Word16 -> Word16
k = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) -> if ShortByteString -> Bool
null ShortByteString
sbs then forall a. HasCallStack => String -> a
errorEmptySBS String
"foldr1'" else forall a. (Word16 -> a -> a) -> a -> ShortByteString -> a
foldr' Word16 -> Word16 -> Word16
k (HasCallStack => ShortByteString -> Word16
last ShortByteString
sbs) (HasCallStack => ShortByteString -> ShortByteString
init ShortByteString
sbs)
index :: HasCallStack
      => ShortByteString
      -> Int  
      -> Word16
index :: HasCallStack => ShortByteString -> Int -> Word16
index = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) Int
i -> if
  | Int
i forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
i forall a. Ord a => a -> a -> Bool
< ShortByteString -> Int
numWord16 ShortByteString
sbs -> ShortByteString -> Int -> Word16
unsafeIndex ShortByteString
sbs Int
i
  | Bool
otherwise                   -> forall a. HasCallStack => ShortByteString -> Int -> a
indexError ShortByteString
sbs Int
i
indexMaybe :: ShortByteString
           -> Int  
           -> Maybe Word16
indexMaybe :: ShortByteString -> Int -> Maybe Word16
indexMaybe = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) Int
i -> if
  | Int
i forall a. Ord a => a -> a -> Bool
>= Int
0 Bool -> Bool -> Bool
&& Int
i forall a. Ord a => a -> a -> Bool
< ShortByteString -> Int
numWord16 ShortByteString
sbs -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$! ShortByteString -> Int -> Word16
unsafeIndex ShortByteString
sbs Int
i
  | Bool
otherwise                   -> forall a. Maybe a
Nothing
{-# INLINE indexMaybe #-}
unsafeIndex :: ShortByteString
            -> Int  
            -> Word16
unsafeIndex :: ShortByteString -> Int -> Word16
unsafeIndex ShortByteString
sbs Int
i = BA -> Int -> Word16
indexWord16Array (ShortByteString -> BA
asBA ShortByteString
sbs) (Int
i forall a. Num a => a -> a -> a
* Int
2)
indexError :: HasCallStack => ShortByteString -> Int -> a
indexError :: forall a. HasCallStack => ShortByteString -> Int -> a
indexError ShortByteString
sbs Int
i =
  forall a. HasCallStack => String -> String -> a
moduleError String
"index" forall a b. (a -> b) -> a -> b
$ String
"error in array index: " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
i
                        forall a. [a] -> [a] -> [a]
++ String
" not in range [0.." forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show (ShortByteString -> Int
numWord16 ShortByteString
sbs) forall a. [a] -> [a] -> [a]
++ String
"]"
(!?) :: ShortByteString
     -> Int  
     -> Maybe Word16
!? :: ShortByteString -> Int -> Maybe Word16
(!?) = ShortByteString -> Int -> Maybe Word16
indexMaybe
{-# INLINE (!?) #-}
elem :: Word16 -> ShortByteString -> Bool
elem :: Word16 -> ShortByteString -> Bool
elem Word16
c = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) -> case Word16 -> ShortByteString -> Maybe Int
elemIndex Word16
c ShortByteString
sbs of Maybe Int
Nothing -> Bool
False ; Maybe Int
_ -> Bool
True
filter :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
filter :: (Word16 -> Bool) -> ShortByteString -> ShortByteString
filter Word16 -> Bool
k = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
                   let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
                   in if | Int
l forall a. Ord a => a -> a -> Bool
<= Int
0    -> ShortByteString
sbs
                         | Bool
otherwise -> Int -> (forall s. MBA s -> ST s Int) -> ShortByteString
createAndTrim' Int
l forall a b. (a -> b) -> a -> b
$ \MBA s
mba -> forall s. MBA s -> BA -> Int -> ST s Int
go MBA s
mba (ShortByteString -> BA
asBA ShortByteString
sbs) Int
l
  where
    go :: forall s. MBA s 
       -> BA              
       -> Int             
       -> ST s Int
    go :: forall s. MBA s -> BA -> Int -> ST s Int
go !MBA s
mba BA
ba !Int
l = Int -> Int -> ST s Int
go' Int
0 Int
0
      where
        go' :: Int 
            -> Int 
            -> ST s Int
        go' :: Int -> Int -> ST s Int
go' !Int
br !Int
bw
          | Int
br forall a. Ord a => a -> a -> Bool
>= Int
l   = forall (m :: * -> *) a. Monad m => a -> m a
return Int
bw
          | Bool
otherwise = do
              let w :: Word16
w = BA -> Int -> Word16
indexWord16Array BA
ba Int
br
              if Word16 -> Bool
k Word16
w
              then do
                forall s. MBA s -> Int -> Word16 -> ST s ()
writeWord16Array MBA s
mba Int
bw Word16
w
                Int -> Int -> ST s Int
go' (Int
brforall a. Num a => a -> a -> a
+Int
2) (Int
bwforall a. Num a => a -> a -> a
+Int
2)
              else
                Int -> Int -> ST s Int
go' (Int
brforall a. Num a => a -> a -> a
+Int
2) Int
bw
find :: (Word16 -> Bool) -> ShortByteString -> Maybe Word16
find :: (Word16 -> Bool) -> ShortByteString -> Maybe Word16
find Word16 -> Bool
f = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) -> case (Word16 -> Bool) -> ShortByteString -> Maybe Int
findIndex Word16 -> Bool
f ShortByteString
sbs of
                    Just Int
n -> forall a. a -> Maybe a
Just (ShortByteString
sbs HasCallStack => ShortByteString -> Int -> Word16
`index` Int
n)
                    Maybe Int
_      -> forall a. Maybe a
Nothing
partition :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString)
partition :: (Word16 -> Bool)
-> ShortByteString -> (ShortByteString, ShortByteString)
partition Word16 -> Bool
k = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
                   let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
                   in if | Int
l forall a. Ord a => a -> a -> Bool
<= Int
0    -> (ShortByteString
sbs, ShortByteString
sbs)
                         | Bool
otherwise -> Int
-> (forall s. MBA s -> MBA s -> ST s (Int, Int))
-> (ShortByteString, ShortByteString)
createAndTrim'' Int
l forall a b. (a -> b) -> a -> b
$ \MBA s
mba1 MBA s
mba2 -> forall s. MBA s -> MBA s -> BA -> Int -> ST s (Int, Int)
go MBA s
mba1 MBA s
mba2 (ShortByteString -> BA
asBA ShortByteString
sbs) Int
l
  where
    go :: forall s.
          MBA s           
       -> MBA s           
       -> BA              
       -> Int             
       -> ST s (Int, Int) 
    go :: forall s. MBA s -> MBA s -> BA -> Int -> ST s (Int, Int)
go !MBA s
mba1 !MBA s
mba2 BA
ba !Int
l = Int -> Int -> ST s (Int, Int)
go' Int
0 Int
0
      where
        go' :: Int 
            -> Int 
            -> ST s (Int, Int) 
        go' :: Int -> Int -> ST s (Int, Int)
go' !Int
br !Int
bw1
          | Int
br forall a. Ord a => a -> a -> Bool
>= Int
l   = forall (m :: * -> *) a. Monad m => a -> m a
return (Int
bw1, Int
br forall a. Num a => a -> a -> a
- Int
bw1)
          | Bool
otherwise = do
              let w :: Word16
w = BA -> Int -> Word16
indexWord16Array BA
ba Int
br
              if Word16 -> Bool
k Word16
w
              then do
                forall s. MBA s -> Int -> Word16 -> ST s ()
writeWord16Array MBA s
mba1 Int
bw1 Word16
w
                Int -> Int -> ST s (Int, Int)
go' (Int
brforall a. Num a => a -> a -> a
+Int
2) (Int
bw1forall a. Num a => a -> a -> a
+Int
2)
              else do
                forall s. MBA s -> Int -> Word16 -> ST s ()
writeWord16Array MBA s
mba2 (Int
br forall a. Num a => a -> a -> a
- Int
bw1) Word16
w
                Int -> Int -> ST s (Int, Int)
go' (Int
brforall a. Num a => a -> a -> a
+Int
2) Int
bw1
elemIndex :: Word16
          -> ShortByteString
          -> Maybe Int  
elemIndex :: Word16 -> ShortByteString -> Maybe Int
elemIndex Word16
k = (Word16 -> Bool) -> ShortByteString -> Maybe Int
findIndex (forall a. Eq a => a -> a -> Bool
==Word16
k) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
elemIndices :: Word16 -> ShortByteString -> [Int]
elemIndices :: Word16 -> ShortByteString -> [Int]
elemIndices Word16
k = (Word16 -> Bool) -> ShortByteString -> [Int]
findIndices (forall a. Eq a => a -> a -> Bool
==Word16
k) forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
count :: Word16 -> ShortByteString -> Int
count :: Word16 -> ShortByteString -> Int
count Word16
w = forall (t :: * -> *) a. Foldable t => t a -> Int
List.length forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> ShortByteString -> [Int]
elemIndices Word16
w forall b c a. (b -> c) -> (a -> b) -> a -> c
. ShortByteString -> ShortByteString
assertEven
findIndex :: (Word16 -> Bool) -> ShortByteString -> Maybe Int
findIndex :: (Word16 -> Bool) -> ShortByteString -> Maybe Int
findIndex Word16 -> Bool
k = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
  let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
      ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
      w :: Int -> Word16
w = BA -> Int -> Word16
indexWord16Array BA
ba
      go :: Int -> Maybe Int
go !Int
n | Int
n forall a. Ord a => a -> a -> Bool
>= Int
l    = forall a. Maybe a
Nothing
            | Word16 -> Bool
k (Int -> Word16
w Int
n)   = forall a. a -> Maybe a
Just (Int
n forall a. Bits a => a -> Int -> a
`shiftR` Int
1)
            | Bool
otherwise = Int -> Maybe Int
go (Int
n forall a. Num a => a -> a -> a
+ Int
2)
  in Int -> Maybe Int
go Int
0
findIndices :: (Word16 -> Bool) -> ShortByteString -> [Int]
findIndices :: (Word16 -> Bool) -> ShortByteString -> [Int]
findIndices Word16 -> Bool
k = \(ShortByteString -> ShortByteString
assertEven -> ShortByteString
sbs) ->
  let l :: Int
l = ShortByteString -> Int
BS.length ShortByteString
sbs
      ba :: BA
ba = ShortByteString -> BA
asBA ShortByteString
sbs
      w :: Int -> Word16
w = BA -> Int -> Word16
indexWord16Array BA
ba
      go :: Int -> [Int]
go !Int
n | Int
n forall a. Ord a => a -> a -> Bool
>= Int
l    = []
            | Word16 -> Bool
k (Int -> Word16
w Int
n)   = (Int
n forall a. Bits a => a -> Int -> a
`shiftR` Int
1) forall a. a -> [a] -> [a]
: Int -> [Int]
go (Int
n forall a. Num a => a -> a -> a
+ Int
2)
            | Bool
otherwise = Int -> [Int]
go (Int
n forall a. Num a => a -> a -> a
+ Int
2)
  in Int -> [Int]
go Int
0