{-# LANGUAGE BangPatterns #-}{-# LANGUAGE CPP #-}{-# LANGUAGE MultiWayIf #-}{-# LANGUAGE RankNTypes #-}{-# LANGUAGE MagicHash #-}{-# LANGUAGE ViewPatterns #-}{-# LANGUAGE ScopedTypeVariables #-}{-# LANGUAGE TupleSections #-}{-# OPTIONS_GHC -fno-warn-name-shadowing -fexpose-all-unfoldings #-}-- |-- Module : System.OsString.Data.ByteString.Short.Word16-- Copyright : © 2022 Julian Ospald-- License : MIT---- Maintainer : Julian Ospald <hasufell@posteo.de>-- Stability : experimental-- Portability : portable---- ShortByteStrings encoded as UTF16-LE, suitable for windows FFI calls.---- Word16s are *always* in BE encoding (both input and output), so e.g. 'pack'-- takes a list of BE encoded @[Word16]@ and produces a UTF16-LE encoded ShortByteString.---- Likewise, 'unpack' takes a UTF16-LE encoded ShortByteString and produces a list of BE encoded @[Word16]@.---- Indices and lengths are always in respect to Word16, not Word8.---- All functions will error out if the input string is not a valid UTF16 stream (uneven number of bytes).-- So use this module with caution.moduleSystem.OsString.Data.ByteString.Short.Word16(-- * The @ShortByteString@ type and representationShortByteString(..),-- * Introducing and eliminating 'ShortByteString'sempty,singleton ,pack ,unpack ,fromShort,toShort,-- * Basic interfacesnoc ,cons ,append,last ,tail ,uncons ,uncons2 ,head ,init ,unsnoc ,null,length,numWord16 ,-- * Transforming ShortByteStringsmap ,reverse ,intercalate,-- * Reducing 'ShortByteString's (folds)foldl ,foldl' ,foldl1 ,foldl1' ,foldr ,foldr' ,foldr1 ,foldr1' ,-- ** Special foldsall ,any ,concat,-- ** Generating and unfolding ByteStringsreplicate ,unfoldr ,unfoldrN ,-- * Substrings-- ** Breaking stringstake ,takeEnd ,takeWhileEnd ,takeWhile ,drop ,dropEnd ,dropWhile ,dropWhileEnd ,breakEnd ,break ,span ,spanEnd ,splitAt ,split ,splitWith ,stripSuffix,stripPrefix,-- * PredicatesisInfixOf ,isPrefixOf,isSuffixOf,-- ** Search for arbitrary substringsbreakSubstring ,-- * Searching ShortByteStrings-- ** Searching by equalityelem ,-- ** Searching with a predicatefind ,filter ,partition ,-- * Indexing ShortByteStringsindex ,indexMaybe ,(!?) ,elemIndex ,elemIndices ,count ,findIndex ,findIndices ,-- ** Encoding validation-- isValidUtf8,-- * Low level conversions-- ** Packing 'CString's and pointerspackCWString ,packCWStringLen ,newCWString ,-- ** Using ShortByteStrings as 'CString'suseAsCWString ,useAsCWStringLen )whereimportSystem.OsString.Data.ByteString.Short (append,intercalate,concat,stripSuffix,stripPrefix,isPrefixOf,isSuffixOf,length,empty,null,ShortByteString(..),fromShort,toShort)importSystem.OsString.Data.ByteString.Short.Internal importData.Bits(shiftR)importData.WordimportPreludehiding(Foldable(..),all,any,reverse,break,concat,drop,dropWhile,filter,head,init,last,map,replicate,span,splitAt,tail,take,takeWhile)importqualifiedData.FoldableasFoldableimportGHC.ST(ST)importGHC.Stack(HasCallStack)importGHC.Exts(inline)importqualifiedData.ByteString.Short.InternalasBSimportqualifiedData.ListasList-- ------------------------------------------------------------------------------- Introducing and eliminating 'ShortByteString's-- | /O(1)/ Convert a 'Word16' into a 'ShortByteString'singleton ::Word16->ShortByteStringsingleton :: Word16 -> ShortByteString singleton =\Word16 w ->Int -> (forall s. MBA s -> ST s ()) -> ShortByteString create Int 2(\MBA s mba ->MBA s -> Int -> Word16 -> ST s () forall s. MBA s -> Int -> Word16 -> ST s () writeWord16Array MBA s mba Int 0Word16 w )-- | /O(n)/. Convert a list into a 'ShortByteString'pack ::[Word16]->ShortByteStringpack :: [Word16] -> ShortByteString pack =[Word16] -> ShortByteString packWord16 -- | /O(n)/. Convert a 'ShortByteString' into a list.unpack ::ShortByteString->[Word16]unpack :: ShortByteString -> [Word16] unpack =ShortByteString -> [Word16] unpackWord16 (ShortByteString -> [Word16]) -> (ShortByteString -> ShortByteString) -> ShortByteString -> [Word16] forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven -- ----------------------------------------------------------------------- Basic interface-- | This is like 'length', but the number of 'Word16', not 'Word8'.numWord16 ::ShortByteString->IntnumWord16 :: ShortByteString -> Int numWord16 =(Int -> Int -> Int forall a. Bits a => a -> Int -> a `shiftR`Int 1)(Int -> Int) -> (ShortByteString -> Int) -> ShortByteString -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> Int BS.length(ShortByteString -> Int) -> (ShortByteString -> ShortByteString) -> ShortByteString -> Int forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven infixr5`cons` --same as list (:)infixl5`snoc` -- | /O(n)/ Append a Word16 to the end of a 'ShortByteString'-- -- Note: copies the entire byte arraysnoc ::ShortByteString->Word16->ShortByteStringsnoc :: ShortByteString -> Word16 -> ShortByteString snoc =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )Word16 c ->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString sbs nl :: Int nl =Int l Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2inInt -> (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 ->doBA -> Int -> MBA s -> Int -> Int -> ST s () forall s. BA -> Int -> MBA s -> Int -> Int -> ST s () copyByteArray (ShortByteString -> BA asBA ShortByteString sbs )Int 0MBA s mba Int 0Int l MBA s -> Int -> Word16 -> ST s () forall s. MBA s -> Int -> Word16 -> ST s () writeWord16Array MBA s mba Int l Word16 c -- | /O(n)/ 'cons' is analogous to (:) for lists.---- Note: copies the entire byte arraycons ::Word16->ShortByteString->ShortByteStringcons :: Word16 -> ShortByteString -> ShortByteString cons Word16 c =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString sbs nl :: Int nl =Int l Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2inInt -> (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 ->doMBA s -> Int -> Word16 -> ST s () forall s. MBA s -> Int -> Word16 -> ST s () writeWord16Array MBA s mba Int 0Word16 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 0MBA s mba Int 2Int l -- | /O(1)/ Extract the last element of a ShortByteString, which must be finite and at least one Word16.-- An exception will be thrown in the case of an empty ShortByteString.last ::HasCallStack=>ShortByteString->Word16last :: HasCallStack => ShortByteString -> Word16 last =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->caseShortByteString -> Bool nullShortByteString sbs ofBool True->String -> Word16 forall a. HasCallStack => String -> a errorEmptySBS String "last"Bool False->BA -> Int -> Word16 indexWord16Array (ShortByteString -> BA asBA ShortByteString sbs )(ShortByteString -> Int BS.lengthShortByteString sbs Int -> Int -> Int forall a. Num a => a -> a -> a -Int 2)-- | /O(n)/ Extract the elements after the head of a ShortByteString, which must at least one Word16.-- An exception will be thrown in the case of an empty ShortByteString.---- Note: copies the entire byte arraytail ::HasCallStack=>ShortByteString->ShortByteStringtail :: HasCallStack => ShortByteString -> ShortByteString tail =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString sbs nl :: Int nl =Int l Int -> Int -> Int forall a. Num a => a -> a -> a -Int 2inif|Int l Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <=Int 0->String -> ShortByteString forall a. HasCallStack => String -> a errorEmptySBS String "tail"|Bool otherwise->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 2MBA s mba Int 0Int nl -- | /O(n)/ Extract the head and tail of a ByteString, returning Nothing-- if it is empty.uncons ::ShortByteString->Maybe(Word16,ShortByteString)uncons :: ShortByteString -> Maybe (Word16, ShortByteString) uncons =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString sbs nl :: Int nl =Int l Int -> Int -> Int forall a. Num a => a -> a -> a -Int 2inif|Int l Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <=Int 0->Maybe (Word16, ShortByteString) forall a. Maybe a Nothing|Bool otherwise->leth :: Word16 h =BA -> Int -> Word16 indexWord16Array (ShortByteString -> BA asBA ShortByteString sbs )Int 0t :: ShortByteString t =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 2MBA s mba Int 0Int nl in(Word16, ShortByteString) -> Maybe (Word16, ShortByteString) forall a. a -> Maybe a Just(Word16 h ,ShortByteString t )-- | /O(n)/ Extract first two elements and the rest of a ByteString,-- returning Nothing if it is shorter than two elements.uncons2 ::ShortByteString->Maybe(Word16,Word16,ShortByteString)uncons2 :: ShortByteString -> Maybe (Word16, Word16, ShortByteString) uncons2 =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString sbs nl :: Int nl =Int l Int -> Int -> Int forall a. Num a => a -> a -> a -Int 4inif|Int l Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <=Int 2->Maybe (Word16, Word16, ShortByteString) forall a. Maybe a Nothing|Bool otherwise->leth :: Word16 h =BA -> Int -> Word16 indexWord16Array (ShortByteString -> BA asBA ShortByteString sbs )Int 0h' :: Word16 h' =BA -> Int -> Word16 indexWord16Array (ShortByteString -> BA asBA ShortByteString sbs )Int 2t :: ShortByteString t =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 4MBA s mba Int 0Int nl in(Word16, Word16, ShortByteString) -> Maybe (Word16, Word16, ShortByteString) forall a. a -> Maybe a Just(Word16 h ,Word16 h' ,ShortByteString t )-- | /O(1)/ Extract the first element of a ShortByteString, which must be at least one Word16.-- An exception will be thrown in the case of an empty ShortByteString.head ::HasCallStack=>ShortByteString->Word16head :: HasCallStack => ShortByteString -> Word16 head =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->caseShortByteString -> Bool nullShortByteString sbs ofBool True->String -> Word16 forall a. HasCallStack => String -> a errorEmptySBS String "last"Bool False->BA -> Int -> Word16 indexWord16Array (ShortByteString -> BA asBA ShortByteString sbs )Int 0-- | /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 arrayinit ::HasCallStack=>ShortByteString->ShortByteStringinit :: HasCallStack => ShortByteString -> ShortByteString init =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString sbs nl :: Int nl =Int l Int -> Int -> Int forall a. Num a => a -> a -> a -Int 2inif|Int l Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <=Int 0->String -> ShortByteString forall a. HasCallStack => String -> a errorEmptySBS String "tail"|Bool otherwise->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 0MBA s mba Int 0Int nl -- | /O(n)/ Extract the 'init' and 'last' of a ByteString, returning Nothing-- if it is empty.unsnoc ::ShortByteString->Maybe(ShortByteString,Word16)unsnoc :: ShortByteString -> Maybe (ShortByteString, Word16) unsnoc =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString sbs nl :: Int nl =Int l Int -> Int -> Int forall a. Num a => a -> a -> a -Int 2inif|Int l Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <=Int 0->Maybe (ShortByteString, Word16) forall a. Maybe a Nothing|Bool otherwise->letl' :: Word16 l' =BA -> Int -> Word16 indexWord16Array (ShortByteString -> BA asBA ShortByteString sbs )(Int l Int -> Int -> Int forall a. Num a => a -> a -> a -Int 2)i :: ShortByteString i =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 0MBA s mba Int 0Int nl in(ShortByteString, Word16) -> Maybe (ShortByteString, Word16) forall a. a -> Maybe a Just(ShortByteString i ,Word16 l' )-- ----------------------------------------------------------------------- Transformations-- | /O(n)/ 'map' @f xs@ is the ShortByteString obtained by applying @f@ to each-- element of @xs@.map ::(Word16->Word16)->ShortByteString->ShortByteStringmap :: (Word16 -> Word16) -> ShortByteString -> ShortByteString map Word16 -> Word16 f =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString sbs ba :: BA ba =ShortByteString -> BA asBA ShortByteString sbs inInt -> (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 0Int l )wherego ::BA ->MBA s ->Int->Int->STs ()go :: forall s. 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 a. a -> ST s a forall (m :: * -> *) a. Monad m => a -> m a return()|Bool otherwise=doletw :: Word16 w =BA -> Int -> Word16 indexWord16Array BA ba Int i MBA s -> Int -> Word16 -> ST s () forall s. MBA s -> Int -> Word16 -> ST s () writeWord16Array MBA s mba Int i (Word16 -> Word16 f Word16 w )BA -> MBA s -> Int -> Int -> ST s () forall s. BA -> MBA s -> Int -> Int -> ST s () go BA ba MBA s mba (Int i Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)Int l -- TODO: implement more efficiently-- | /O(n)/ 'reverse' @xs@ efficiently returns the elements of @xs@ in reverse order.reverse ::ShortByteString->ShortByteStringreverse :: ShortByteString -> ShortByteString reverse =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString sbs ba :: BA ba =ShortByteString -> BA asBA ShortByteString sbs inInt -> (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 0Int l )wherego ::BA ->MBA s ->Int->Int->STs ()go :: forall s. 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 a. a -> ST s a forall (m :: * -> *) a. Monad m => a -> m a return()|Bool otherwise=doletw :: Word16 w =BA -> Int -> Word16 indexWord16Array BA ba Int i MBA s -> Int -> Word16 -> ST s () forall s. MBA s -> Int -> Word16 -> ST s () writeWord16Array MBA s mba (Int l Int -> Int -> Int forall a. Num a => a -> a -> a -Int 2Int -> Int -> Int forall a. Num a => a -> a -> a -Int i )Word16 w BA -> MBA s -> Int -> Int -> ST s () forall s. BA -> MBA s -> Int -> Int -> ST s () go BA ba MBA s mba (Int i Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)Int l -- ----------------------------------------------------------------------- Special folds-- | /O(n)/ Applied to a predicate and a 'ShortByteString', 'all' determines-- if all elements of the 'ShortByteString' satisfy the predicate.all ::(Word16->Bool)->ShortByteString->Boolall :: (Word16 -> Bool) -> ShortByteString -> Bool all Word16 -> Bool k =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString 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 Int -> Int -> Bool 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 Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)inInt -> 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 ::(Word16->Bool)->ShortByteString->Boolany :: (Word16 -> Bool) -> ShortByteString -> Bool any Word16 -> Bool k =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString 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 Int -> Int -> Bool 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 Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)inInt -> Bool go Int 0-- ----------------------------------------------------------------------- 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)) creplicate ::Int->Word16->ShortByteStringreplicate :: Int -> Word16 -> ShortByteString replicate Int w Word16 c |Int w Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <=Int 0=ShortByteString empty-- can't use setByteArray here, because we write UTF-16LE|Bool otherwise=Int -> (forall s. MBA s -> ST s ()) -> ShortByteString create (Int w Int -> Int -> Int forall a. Num a => a -> a -> a *Int 2)(MBA s -> Int -> ST s () forall {s}. MBA s -> Int -> ST s () `go` Int 0)wherego :: MBA s -> Int -> ST s () go MBA s mba Int ix |Int ix Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <Int 0Bool -> Bool -> Bool ||Int ix Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >=Int w Int -> Int -> Int forall a. Num a => a -> a -> a *Int 2=() -> ST s () forall a. a -> ST s a forall (f :: * -> *) a. Applicative f => a -> f a pure()|Bool otherwise=MBA s -> Int -> Word16 -> ST s () forall s. MBA s -> Int -> Word16 -> ST s () writeWord16Array MBA s mba Int ix Word16 c ST s () -> ST s () -> ST s () forall a b. ST s a -> ST s b -> ST s b 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 2)-- | /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 @[Word16]@-- 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(Word16,a ))->a ->ShortByteStringunfoldr :: forall a. (a -> Maybe (Word16, a)) -> a -> ShortByteString unfoldr a -> Maybe (Word16, a) f a x0 =[Word16] -> ShortByteString packWord16Rev ([Word16] -> ShortByteString) -> [Word16] -> ShortByteString forall a b. (a -> b) -> a -> b $a -> [Word16] -> [Word16] go a x0 [Word16] forall a. Monoid a => a memptywherego :: a -> [Word16] -> [Word16] go a x [Word16] words' =casea -> Maybe (Word16, a) f a x ofMaybe (Word16, a) Nothing->[Word16] words' Just(Word16 w ,a x' )->a -> [Word16] -> [Word16] go a x' (Word16 w Word16 -> [Word16] -> [Word16] forall a. a -> [a] -> [a] :[Word16] words' )-- | /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.---- The following equation relates 'unfoldrN' and 'unfoldr':---- > fst (unfoldrN n f s) == take n (unfoldr f s)--unfoldrN ::foralla .Int-- ^ number of 'Word16'->(a ->Maybe(Word16,a ))->a ->(ShortByteString,Maybea )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 Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <Int 0->(ShortByteString empty,a -> Maybe a forall a. a -> Maybe a Justa x0 )|Bool otherwise->Int -> (forall {s}. MBA s -> ST s (Int, Maybe a)) -> (ShortByteString, Maybe a) forall a. Int -> (forall s. MBA s -> ST s (Int, a)) -> (ShortByteString, a) createAndTrim (Int i Int -> Int -> Int forall a. Num a => a -> a -> a *Int 2)((forall {s}. MBA s -> ST s (Int, Maybe a)) -> (ShortByteString, Maybe a)) -> (forall {s}. MBA s -> ST s (Int, Maybe a)) -> (ShortByteString, Maybe a) forall a b. (a -> b) -> a -> b $\MBA s mba ->MBA s -> a -> Int -> ST s (Int, Maybe a) forall s. MBA s -> a -> Int -> ST s (Int, Maybe a) go MBA s mba a x0 Int 0wherego ::foralls .MBA s ->a ->Int->STs (Int,Maybea )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 wherego' ::a ->Int->STs (Int,Maybea )go' :: a -> Int -> ST s (Int, Maybe a) go' !a x' !Int n' |Int n' Int -> Int -> Bool forall a. Eq a => a -> a -> Bool ==Int i Int -> Int -> Int forall a. Num a => a -> a -> a *Int 2=(Int, Maybe a) -> ST s (Int, Maybe a) forall a. a -> ST s a forall (m :: * -> *) a. Monad m => a -> m a return(Int n' ,a -> Maybe a forall a. a -> Maybe a Justa x' )|Bool otherwise=casea -> Maybe (Word16, a) f a x' ofMaybe (Word16, a) Nothing->(Int, Maybe a) -> ST s (Int, Maybe a) forall a. a -> ST s a forall (m :: * -> *) a. Monad m => a -> m a return(Int n' ,Maybe a forall a. Maybe a Nothing)Just(Word16 w ,a x'' )->doMBA s -> Int -> Word16 -> ST s () 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' Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)-- ---------------------------------------------------------------------- Predicates-- ----------------------------------------------------------------------- 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 arraytake ::Int-- ^ number of Word16->ShortByteString->ShortByteStringtake :: Int -> ShortByteString -> ShortByteString take =\Int n (ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letsl :: Int sl =ShortByteString -> Int numWord16 ShortByteString sbs len8 :: Int len8 =Int n Int -> Int -> Int forall a. Num a => a -> a -> a *Int 2inif|Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >=Int sl ->ShortByteString sbs |Int n 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 len8 ((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 0MBA s mba Int 0Int len8 -- | /O(1)/ @'takeEnd' n xs@ is equivalent to @'drop' ('length' xs - n) xs@.-- Takes @n@ elements from end of bytestring.---- >>> takeEnd 3 "a\NULb\NULc\NULd\NULe\NULf\NULg\NUL"-- "e\NULf\NULg\NUL"-- >>> takeEnd 0 "a\NULb\NULc\NULd\NULe\NULf\NULg\NUL"-- ""-- >>> takeEnd 4 "a\NULb\NULc\NUL"-- "a\NULb\NULc\NUL"takeEnd ::Int-- ^ number of 'Word16'->ShortByteString->ShortByteStringtakeEnd :: Int -> ShortByteString -> ShortByteString takeEnd Int n =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letsl :: Int sl =ShortByteString -> Int BS.lengthShortByteString sbs n2 :: Int n2 =Int n Int -> Int -> Int forall a. Num a => a -> a -> a *Int 2inif|Int n2 Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >=Int sl ->ShortByteString sbs |Int n2 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 n2 ((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 -> Int -> Int forall a. Ord a => a -> a -> a maxInt 0(Int sl Int -> Int -> Int forall a. Num a => a -> a -> a -Int n2 ))MBA s mba Int 0Int n2 -- | Similar to 'P.takeWhile',-- returns the longest (possibly empty) prefix of elements-- satisfying the predicate.takeWhile ::(Word16->Bool)->ShortByteString->ShortByteStringtakeWhile :: (Word16 -> Bool) -> ShortByteString -> ShortByteString takeWhile Word16 -> Bool f ShortByteString ps =Int -> ShortByteString -> ShortByteString take ((Word16 -> Bool) -> ShortByteString -> Int findIndexOrLength (Bool -> Bool not(Bool -> Bool) -> (Word16 -> Bool) -> Word16 -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c .Word16 -> Bool f )ShortByteString ps )ShortByteString ps -- | Returns the longest (possibly empty) suffix of elements-- satisfying the predicate.---- @'takeWhileEnd' p@ is equivalent to @'reverse' . 'takeWhile' p . 'reverse'@.takeWhileEnd ::(Word16->Bool)->ShortByteString->ShortByteStringtakeWhileEnd :: (Word16 -> Bool) -> ShortByteString -> ShortByteString takeWhileEnd Word16 -> Bool f ShortByteString ps =Int -> ShortByteString -> ShortByteString drop ((Word16 -> Bool) -> ShortByteString -> Int findFromEndUntil (Bool -> Bool not(Bool -> Bool) -> (Word16 -> Bool) -> Word16 -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c .Word16 -> Bool f )ShortByteString ps )ShortByteString ps -- | /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 arraydrop ::Int-- ^ number of 'Word16'->ShortByteString->ShortByteStringdrop :: Int -> ShortByteString -> ShortByteString drop =\Int n' (ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letlen :: Int len =ShortByteString -> Int BS.lengthShortByteString sbs n :: Int n =Int n' Int -> Int -> Int forall a. Num a => a -> a -> a *Int 2inif|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->letnewLen :: Int newLen =Int len Int -> Int -> Int forall a. Num a => a -> a -> a -Int n inInt -> (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 0Int newLen -- | /O(1)/ @'dropEnd' n xs@ is equivalent to @'take' ('length' xs - n) xs@.-- Drops @n@ elements from end of bytestring.---- >>> dropEnd 3 "a\NULb\NULc\NULd\NULe\NULf\NULg\NUL"-- "a\NULb\NULc\NULd\NUL"-- >>> dropEnd 0 "a\NULb\NULc\NULd\NULe\NULf\NULg\NUL"-- "a\NULb\NULc\NULd\NULe\NULf\NULg\NUL"-- >>> dropEnd 4 "a\NULb\NULc\NUL"-- ""dropEnd ::Int-- ^ number of 'Word16'->ShortByteString->ShortByteStringdropEnd :: Int -> ShortByteString -> ShortByteString dropEnd Int n' =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letsl :: Int sl =ShortByteString -> Int BS.lengthShortByteString sbs nl :: Int nl =Int sl Int -> Int -> Int forall a. Num a => a -> a -> a -Int n n :: Int n =Int n' Int -> Int -> Int forall a. Num a => a -> a -> a *Int 2inif|Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >=Int sl ->ShortByteString empty|Int n Int -> Int -> Bool 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 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 0MBA s mba Int 0Int nl -- | Similar to 'P.dropWhile',-- drops the longest (possibly empty) prefix of elements-- satisfying the predicate and returns the remainder.---- Note: copies the entire byte arraydropWhile ::(Word16->Bool)->ShortByteString->ShortByteStringdropWhile :: (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(Bool -> Bool) -> (Word16 -> Bool) -> Word16 -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c .Word16 -> 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.0dropWhileEnd ::(Word16->Bool)->ShortByteString->ShortByteStringdropWhileEnd :: (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(Bool -> Bool) -> (Word16 -> Bool) -> Word16 -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c .Word16 -> Bool f )ShortByteString ps )ShortByteString ps -- | 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 ::(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 -- | 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 ::(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 ofInt n ->Int -> ShortByteString -> (ShortByteString, ShortByteString) splitAt Int n ShortByteString ps -- | 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 ::(Word16->Bool)->ShortByteString->(ShortByteString,ShortByteString){- HLINT ignore "Use span" -}span :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString) span Word16 -> Bool p =(Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString) break (Bool -> Bool not(Bool -> Bool) -> (Word16 -> Bool) -> Word16 -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c .Word16 -> Bool p )(ShortByteString -> (ShortByteString, ShortByteString)) -> (ShortByteString -> ShortByteString) -> ShortByteString -> (ShortByteString, ShortByteString) forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven -- | 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 ::(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 not(Bool -> Bool) -> (Word16 -> Bool) -> Word16 -> Bool forall b c a. (b -> c) -> (a -> b) -> a -> c .Word16 -> Bool p )ShortByteString ps )ShortByteString ps -- | /O(n)/ 'splitAt' @n xs@ is equivalent to @('take' n xs, 'drop' n xs)@.---- Note: copies the substringssplitAt ::Int-- ^ number of Word16->ShortByteString->(ShortByteString,ShortByteString)splitAt :: Int -> ShortByteString -> (ShortByteString, ShortByteString) splitAt Int n' =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->if|Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <=Int 0->(ShortByteString empty,ShortByteString sbs )|Bool otherwise->letslen :: Int slen =ShortByteString -> Int BS.lengthShortByteString sbs inif|Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >=ShortByteString -> Int BS.lengthShortByteString sbs ->(ShortByteString sbs ,ShortByteString empty)|Bool otherwise->letllen :: Int llen =Int -> Int -> Int forall a. Ord a => a -> a -> a minInt slen (Int -> Int -> Int forall a. Ord a => a -> a -> a maxInt 0Int n )rlen :: Int rlen =Int -> Int -> Int forall a. Ord a => a -> a -> a maxInt 0(Int slen Int -> Int -> Int forall a. Num a => a -> a -> a -Int -> Int -> Int forall a. Ord a => a -> a -> a maxInt 0Int n )lsbs :: ShortByteString lsbs =Int -> (forall s. MBA s -> ST s ()) -> ShortByteString create Int llen ((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 0MBA s mba Int 0Int llen rsbs :: ShortByteString rsbs =Int -> (forall s. MBA s -> ST s ()) -> ShortByteString create Int rlen ((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 0Int rlen in(ShortByteString lsbs ,ShortByteString rsbs )wheren :: Int n =Int n' Int -> Int -> Int forall a. Num a => a -> a -> a *Int 2-- | /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 substringssplit ::Word16->ShortByteString->[ShortByteString]split :: Word16 -> ShortByteString -> [ShortByteString] split Word16 w =(Word16 -> Bool) -> ShortByteString -> [ShortByteString] splitWith (Word16 -> Word16 -> Bool forall a. Eq a => a -> a -> Bool ==Word16 w )(ShortByteString -> [ShortByteString]) -> (ShortByteString -> ShortByteString) -> ShortByteString -> [ShortByteString] forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven -- | /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 ::(Word16->Bool)->ShortByteString->[ShortByteString]splitWith :: (Word16 -> Bool) -> ShortByteString -> [ShortByteString] splitWith Word16 -> Bool p =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->if|ShortByteString -> Bool BS.nullShortByteString sbs ->[]|Bool otherwise->ShortByteString -> [ShortByteString] go ShortByteString sbs wherego :: ShortByteString -> [ShortByteString] go ShortByteString sbs' |ShortByteString -> Bool BS.nullShortByteString sbs' =[ShortByteString 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.nullShortByteString b ->[ShortByteString a ]|Bool otherwise->ShortByteString a ShortByteString -> [ShortByteString] -> [ShortByteString] forall a. a -> [a] -> [a] :ShortByteString -> [ShortByteString] go (HasCallStack => ShortByteString -> ShortByteString ShortByteString -> ShortByteString tail ShortByteString b )-- | Check whether one string is a substring of another.isInfixOf ::ShortByteString->ShortByteString->BoolisInfixOf :: ShortByteString -> ShortByteString -> Bool isInfixOf ShortByteString sbs =\ShortByteString s ->ShortByteString -> Bool nullShortByteString sbs Bool -> Bool -> Bool ||Bool -> Bool not(ShortByteString -> Bool 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)) -> ShortByteString -> ShortByteString -> (ShortByteString, ShortByteString) forall a. a -> a GHC.Exts.inlineShortByteString -> ShortByteString -> (ShortByteString, ShortByteString) breakSubstring ShortByteString sbs ShortByteString s )-- algorithm: https://github.com/haskell/filepath/issues/195#issuecomment-1605633713breakSubstring ::ShortByteString-- ^ String to search for->ShortByteString-- ^ String to search in->(ShortByteString,ShortByteString)-- ^ Head and tail of string broken at substringbreakSubstring :: ShortByteString -> ShortByteString -> (ShortByteString, ShortByteString) breakSubstring bPat :: ShortByteString bPat @(ShortByteString -> BA asBA ->BA pat )bInp :: ShortByteString bInp @(ShortByteString -> BA asBA ->BA inp )=Int -> (ShortByteString, ShortByteString) go Int 0wherelpat :: Int lpat =ShortByteString -> Int BS.lengthShortByteString bPat linp :: Int linp =ShortByteString -> Int BS.lengthShortByteString bInp go :: Int -> (ShortByteString, ShortByteString) go Int ix |letix' :: Int ix' =Int ix Int -> Int -> Int forall a. Num a => a -> a -> a *Int 2,Int linp Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >=Int ix' Int -> Int -> Int forall a. Num a => a -> a -> a +Int lpat =if|BA -> Int -> BA -> Int -> Int -> Int compareByteArraysOff BA pat Int 0BA inp Int ix' Int lpat Int -> Int -> Bool forall a. Eq a => a -> a -> Bool ==Int 0->Int -> ShortByteString -> (ShortByteString, ShortByteString) splitAt Int ix ShortByteString bInp |Bool otherwise->Int -> (ShortByteString, ShortByteString) go (Int ix Int -> Int -> Int forall a. Num a => a -> a -> a +Int 1)|Bool otherwise=(ShortByteString bInp ,ShortByteString forall a. Monoid a => a mempty)-- ----------------------------------------------------------------------- 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 ->Word16->a )->a ->ShortByteString->a foldl :: forall a. (a -> Word16 -> a) -> a -> ShortByteString -> a foldl a -> Word16 -> a f a v =(a -> Word16 -> a) -> a -> [Word16] -> a forall b a. (b -> a -> b) -> b -> [a] -> b forall (t :: * -> *) b a. Foldable t => (b -> a -> b) -> b -> t a -> b List.foldla -> Word16 -> a f a v ([Word16] -> a) -> (ShortByteString -> [Word16]) -> ShortByteString -> a forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> [Word16] unpack (ShortByteString -> [Word16]) -> (ShortByteString -> ShortByteString) -> ShortByteString -> [Word16] forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven -- | 'foldl'' is like 'foldl', but strict in the accumulator.--foldl' ::(a ->Word16->a )->a ->ShortByteString->a foldl' :: forall a. (a -> Word16 -> a) -> a -> ShortByteString -> a foldl' a -> Word16 -> a f a v =(a -> Word16 -> a) -> a -> [Word16] -> a forall b a. (b -> a -> b) -> b -> [a] -> b forall (t :: * -> *) b a. Foldable t => (b -> a -> b) -> b -> t a -> b List.foldl'a -> Word16 -> a f a v ([Word16] -> a) -> (ShortByteString -> [Word16]) -> ShortByteString -> a forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> [Word16] unpack (ShortByteString -> [Word16]) -> (ShortByteString -> ShortByteString) -> ShortByteString -> [Word16] forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven -- | '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 ::(Word16->a ->a )->a ->ShortByteString->a foldr :: forall a. (Word16 -> a -> a) -> a -> ShortByteString -> a foldr Word16 -> a -> a f a v =(Word16 -> a -> a) -> a -> [Word16] -> a forall a b. (a -> b -> b) -> b -> [a] -> b forall (t :: * -> *) a b. Foldable t => (a -> b -> b) -> b -> t a -> b List.foldrWord16 -> a -> a f a v ([Word16] -> a) -> (ShortByteString -> [Word16]) -> ShortByteString -> a forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> [Word16] unpack (ShortByteString -> [Word16]) -> (ShortByteString -> ShortByteString) -> ShortByteString -> [Word16] forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven -- | 'foldr'' is like 'foldr', but strict in the accumulator.foldr' ::(Word16->a ->a )->a ->ShortByteString->a foldr' :: forall a. (Word16 -> a -> a) -> a -> ShortByteString -> a foldr' Word16 -> a -> a k a v =(Word16 -> a -> a) -> a -> [Word16] -> a forall a b. (a -> b -> b) -> b -> [a] -> b forall (t :: * -> *) a b. Foldable t => (a -> b -> b) -> b -> t a -> b Foldable.foldr'Word16 -> a -> a k a v ([Word16] -> a) -> (ShortByteString -> [Word16]) -> ShortByteString -> a forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> [Word16] unpack (ShortByteString -> [Word16]) -> (ShortByteString -> ShortByteString) -> ShortByteString -> [Word16] forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven -- | '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 ::HasCallStack=>(Word16->Word16->Word16)->ShortByteString->Word16foldl1 :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16 foldl1 Word16 -> Word16 -> Word16 k =(Word16 -> Word16 -> Word16) -> [Word16] -> Word16 forall a. (a -> a -> a) -> [a] -> a forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a List.foldl1Word16 -> Word16 -> Word16 k ([Word16] -> Word16) -> (ShortByteString -> [Word16]) -> ShortByteString -> Word16 forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> [Word16] unpack (ShortByteString -> [Word16]) -> (ShortByteString -> ShortByteString) -> ShortByteString -> [Word16] forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven -- | 'foldl1'' is like 'foldl1', but strict in the accumulator.-- An exception will be thrown in the case of an empty ShortByteString.foldl1' ::HasCallStack=>(Word16->Word16->Word16)->ShortByteString->Word16foldl1' :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16 foldl1' Word16 -> Word16 -> Word16 k =(Word16 -> Word16 -> Word16) -> [Word16] -> Word16 forall a. HasCallStack => (a -> a -> a) -> [a] -> a List.foldl1'Word16 -> Word16 -> Word16 k ([Word16] -> Word16) -> (ShortByteString -> [Word16]) -> ShortByteString -> Word16 forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> [Word16] unpack (ShortByteString -> [Word16]) -> (ShortByteString -> ShortByteString) -> ShortByteString -> [Word16] forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven -- | '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 ::HasCallStack=>(Word16->Word16->Word16)->ShortByteString->Word16foldr1 :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16 foldr1 Word16 -> Word16 -> Word16 k =(Word16 -> Word16 -> Word16) -> [Word16] -> Word16 forall a. (a -> a -> a) -> [a] -> a forall (t :: * -> *) a. Foldable t => (a -> a -> a) -> t a -> a List.foldr1Word16 -> Word16 -> Word16 k ([Word16] -> Word16) -> (ShortByteString -> [Word16]) -> ShortByteString -> Word16 forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> [Word16] unpack (ShortByteString -> [Word16]) -> (ShortByteString -> ShortByteString) -> ShortByteString -> [Word16] forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven -- | 'foldr1'' is a variant of 'foldr1', but is strict in the-- accumulator.foldr1' ::HasCallStack=>(Word16->Word16->Word16)->ShortByteString->Word16foldr1' :: HasCallStack => (Word16 -> Word16 -> Word16) -> ShortByteString -> Word16 foldr1' Word16 -> Word16 -> Word16 k =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->ifShortByteString -> Bool nullShortByteString sbs thenString -> Word16 forall a. HasCallStack => String -> a errorEmptySBS String "foldr1'"else(Word16 -> Word16 -> Word16) -> Word16 -> ShortByteString -> Word16 forall a. (Word16 -> a -> a) -> a -> ShortByteString -> a foldr' Word16 -> Word16 -> Word16 k (HasCallStack => ShortByteString -> Word16 ShortByteString -> Word16 last ShortByteString sbs )(HasCallStack => ShortByteString -> ShortByteString ShortByteString -> ShortByteString init ShortByteString sbs )-- ---------------------------------------------------------------------- Searching ShortByteString-- | /O(1)/ 'ShortByteString' index (subscript) operator, starting from 0.index ::HasCallStack=>ShortByteString->Int-- ^ number of 'Word16'->Word16index :: HasCallStack => ShortByteString -> Int -> Word16 index =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )Int i ->if|Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >=Int 0Bool -> Bool -> Bool &&Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <ShortByteString -> Int numWord16 ShortByteString sbs ->ShortByteString -> Int -> Word16 unsafeIndex ShortByteString sbs Int i |Bool otherwise->ShortByteString -> Int -> Word16 forall a. HasCallStack => ShortByteString -> Int -> a indexError ShortByteString sbs Int i -- | /O(1)/ 'ShortByteString' index, starting from 0, that returns 'Just' if:---- > 0 <= n < length bs---- @since 0.11.0.0indexMaybe ::ShortByteString->Int-- ^ number of 'Word16'->MaybeWord16indexMaybe :: ShortByteString -> Int -> Maybe Word16 indexMaybe =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )Int i ->if|Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >=Int 0Bool -> Bool -> Bool &&Int i Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <ShortByteString -> Int numWord16 ShortByteString sbs ->Word16 -> Maybe Word16 forall a. a -> Maybe a Just(Word16 -> Maybe Word16) -> Word16 -> Maybe Word16 forall a b. (a -> b) -> a -> b $!ShortByteString -> Int -> Word16 unsafeIndex ShortByteString sbs Int i |Bool otherwise->Maybe Word16 forall a. Maybe a Nothing{-# INLINEindexMaybe #-}unsafeIndex ::ShortByteString->Int-- ^ number of 'Word16'->Word16unsafeIndex :: ShortByteString -> Int -> Word16 unsafeIndex ShortByteString sbs Int i =BA -> Int -> Word16 indexWord16Array (ShortByteString -> BA asBA ShortByteString sbs )(Int i Int -> Int -> Int 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 =String -> String -> a forall a. HasCallStack => String -> String -> a moduleError String "index"(String -> a) -> String -> a forall a b. (a -> b) -> a -> b $String "error in array index: "String -> String -> String forall a. [a] -> [a] -> [a] ++Int -> String forall a. Show a => a -> String showInt i String -> String -> String forall a. [a] -> [a] -> [a] ++String " not in range [0.."String -> String -> String forall a. [a] -> [a] -> [a] ++Int -> String forall a. Show a => a -> String show(ShortByteString -> Int numWord16 ShortByteString sbs )String -> String -> String forall a. [a] -> [a] -> [a] ++String "]"-- | /O(1)/ 'ShortByteString' index, starting from 0, that returns 'Just' if:---- > 0 <= n < length bs---- @since 0.11.0.0(!?) ::ShortByteString->Int-- ^ number of 'Word16'->MaybeWord16!? :: ShortByteString -> Int -> Maybe Word16 (!?) =ShortByteString -> Int -> Maybe Word16 indexMaybe {-# INLINE(!?)#-}-- | /O(n)/ 'elem' is the 'ShortByteString' membership predicate.elem ::Word16->ShortByteString->Boolelem :: Word16 -> ShortByteString -> Bool elem Word16 c =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->caseWord16 -> ShortByteString -> Maybe Int elemIndex Word16 c ShortByteString sbs ofMaybe 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 ::(Word16->Bool)->ShortByteString->ShortByteStringfilter :: (Word16 -> Bool) -> ShortByteString -> ShortByteString filter Word16 -> Bool k =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString sbs inif|Int l Int -> Int -> Bool 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 s. MBA s -> ST s Int) -> ShortByteString) -> (forall s. MBA s -> ST s Int) -> ShortByteString forall a b. (a -> b) -> a -> b $\MBA s mba ->MBA s -> BA -> Int -> ST s Int forall s. MBA s -> BA -> Int -> ST s Int go MBA s mba (ShortByteString -> BA asBA ShortByteString sbs )Int l wherego ::foralls .MBA s -- mutable output bytestring->BA -- input bytestring->Int-- length of input bytestring->STs Intgo :: forall s. MBA s -> BA -> Int -> ST s Int go !MBA s mba BA ba !Int l =Int -> Int -> ST s Int go' Int 0Int 0wherego' ::Int-- bytes read->Int-- bytes written->STs Intgo' :: Int -> Int -> ST s Int go' !Int br !Int bw |Int br Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >=Int l =Int -> ST s Int forall a. a -> ST s a forall (m :: * -> *) a. Monad m => a -> m a returnInt bw |Bool otherwise=doletw :: Word16 w =BA -> Int -> Word16 indexWord16Array BA ba Int br ifWord16 -> Bool k Word16 w thendoMBA s -> Int -> Word16 -> ST s () forall s. MBA s -> Int -> Word16 -> ST s () writeWord16Array MBA s mba Int bw Word16 w Int -> Int -> ST s Int go' (Int br Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)(Int bw Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)elseInt -> Int -> ST s Int go' (Int br Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)Int bw -- | /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 ::(Word16->Bool)->ShortByteString->MaybeWord16find :: (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 ofJustInt n ->Word16 -> Maybe Word16 forall a. a -> Maybe a Just(ShortByteString sbs HasCallStack => ShortByteString -> Int -> Word16 ShortByteString -> Int -> Word16 `index` Int n )Maybe Int _->Maybe Word16 forall a. Maybe a Nothing-- | /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 ::(Word16->Bool)->ShortByteString->(ShortByteString,ShortByteString)partition :: (Word16 -> Bool) -> ShortByteString -> (ShortByteString, ShortByteString) partition Word16 -> Bool k =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString sbs inif|Int l Int -> Int -> Bool 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 s. MBA s -> MBA s -> ST s (Int, Int)) -> (ShortByteString, ShortByteString)) -> (forall s. MBA s -> MBA s -> ST s (Int, Int)) -> (ShortByteString, ShortByteString) forall a b. (a -> b) -> a -> b $\MBA s mba1 MBA s mba2 ->MBA s -> MBA s -> BA -> Int -> ST s (Int, Int) 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 wherego ::foralls .MBA s -- mutable output bytestring1->MBA s -- mutable output bytestring2->BA -- input bytestring->Int-- length of input bytestring->STs (Int,Int)-- (length mba1, length mba2)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 0Int 0wherego' ::Int-- bytes read->Int-- bytes written to bytestring 1->STs (Int,Int)-- (length mba1, length mba2)go' :: Int -> Int -> ST s (Int, Int) go' !Int br !Int bw1 |Int br Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >=Int l =(Int, Int) -> ST s (Int, Int) forall a. a -> ST s a forall (m :: * -> *) a. Monad m => a -> m a return(Int bw1 ,Int br Int -> Int -> Int forall a. Num a => a -> a -> a -Int bw1 )|Bool otherwise=doletw :: Word16 w =BA -> Int -> Word16 indexWord16Array BA ba Int br ifWord16 -> Bool k Word16 w thendoMBA s -> Int -> Word16 -> ST s () forall s. MBA s -> Int -> Word16 -> ST s () writeWord16Array MBA s mba1 Int bw1 Word16 w Int -> Int -> ST s (Int, Int) go' (Int br Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)(Int bw1 Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)elsedoMBA s -> Int -> Word16 -> ST s () forall s. MBA s -> Int -> Word16 -> ST s () writeWord16Array MBA s mba2 (Int br Int -> Int -> Int forall a. Num a => a -> a -> a -Int bw1 )Word16 w Int -> Int -> ST s (Int, Int) go' (Int br Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)Int bw1 -- ---------------------------------------------------------------------- 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 ::Word16->ShortByteString->MaybeInt-- ^ number of 'Word16'{- HLINT ignore "Use elemIndex" -}elemIndex :: Word16 -> ShortByteString -> Maybe Int elemIndex Word16 k =(Word16 -> Bool) -> ShortByteString -> Maybe Int findIndex (Word16 -> Word16 -> Bool forall a. Eq a => a -> a -> Bool ==Word16 k )(ShortByteString -> Maybe Int) -> (ShortByteString -> ShortByteString) -> ShortByteString -> Maybe Int forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven -- | /O(n)/ The 'elemIndices' function extends 'elemIndex', by returning-- the indices of all elements equal to the query element, in ascending order.elemIndices ::Word16->ShortByteString->[Int]{- HLINT ignore "Use elemIndices" -}elemIndices :: Word16 -> ShortByteString -> [Int] elemIndices Word16 k =(Word16 -> Bool) -> ShortByteString -> [Int] findIndices (Word16 -> Word16 -> Bool forall a. Eq a => a -> a -> Bool ==Word16 k )(ShortByteString -> [Int]) -> (ShortByteString -> ShortByteString) -> ShortByteString -> [Int] forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven -- | count returns the number of times its argument appears in the ShortByteStringcount ::Word16->ShortByteString->Intcount :: Word16 -> ShortByteString -> Int count Word16 w =[Int] -> Int forall a. [a] -> 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 .Word16 -> ShortByteString -> [Int] elemIndices Word16 w (ShortByteString -> [Int]) -> (ShortByteString -> ShortByteString) -> ShortByteString -> [Int] forall b c a. (b -> c) -> (a -> b) -> a -> c .ShortByteString -> ShortByteString assertEven -- | /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 ::(Word16->Bool)->ShortByteString->MaybeIntfindIndex :: (Word16 -> Bool) -> ShortByteString -> Maybe Int findIndex Word16 -> Bool k =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString 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 Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >=Int l =Maybe Int forall a. Maybe a Nothing|Word16 -> Bool k (Int -> Word16 w Int n )=Int -> Maybe Int forall a. a -> Maybe a Just(Int n Int -> Int -> Int forall a. Bits a => a -> Int -> a `shiftR`Int 1)|Bool otherwise=Int -> Maybe Int go (Int n Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)inInt -> Maybe Int go Int 0-- | /O(n)/ The 'findIndices' function extends 'findIndex', by returning the-- indices of all elements satisfying the predicate, in ascending order.findIndices ::(Word16->Bool)->ShortByteString->[Int]findIndices :: (Word16 -> Bool) -> ShortByteString -> [Int] findIndices Word16 -> Bool k =\(ShortByteString -> ShortByteString assertEven ->ShortByteString sbs )->letl :: Int l =ShortByteString -> Int BS.lengthShortByteString 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 Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >=Int l =[]|Word16 -> Bool k (Int -> Word16 w Int n )=(Int n Int -> Int -> Int forall a. Bits a => a -> Int -> a `shiftR`Int 1)Int -> [Int] -> [Int] forall a. a -> [a] -> [a] :Int -> [Int] go (Int n Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)|Bool otherwise=Int -> [Int] go (Int n Int -> Int -> Int forall a. Num a => a -> a -> a +Int 2)inInt -> [Int] go Int 0