module Lazy.Scope.Scoped where import Data.ByteString.Lazy qualified as L import Data.ByteString.Lazy.Char8 qualified as L8 import Lazy.Scope.Type import Relude hiding (Handle) unScope :: (NFData a, Monad m) => Scoped s a -> LazyT s m a unScope :: forall {k} a (m :: * -> *) (s :: k). (NFData a, Monad m) => Scoped s a -> LazyT s m a unScope (Scoped !a a) = case a -> () forall a. NFData a => a -> () rnf a a of () -> a -> LazyT s m a forall a. a -> LazyT s m a forall (f :: * -> *) a. Applicative f => a -> f a pure a a bs2Scoped :: (LByteString -> a) -> Bs s -> Scoped s a bs2Scoped :: forall {k} a (s :: k). (LByteString -> a) -> Bs s -> Scoped s a bs2Scoped LByteString -> a f = (LByteString -> a) -> Scoped s LByteString -> Scoped s a forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> a f scoped2Bs :: (a -> LByteString) -> Scoped s a -> Bs s scoped2Bs :: forall {k} a (s :: k). (a -> LByteString) -> Scoped s a -> Bs s scoped2Bs a -> LByteString f = (a -> LByteString) -> Scoped s a -> Scoped s LByteString forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap a -> LByteString f toBs :: LByteString -> Bs s toBs :: forall {k} (s :: k). LByteString -> Bs s toBs = LByteString -> Scoped s LByteString forall {k} (s :: k) a. a -> Scoped s a Scoped {-# INLINE toBs #-} condM :: [(Scoped s Bool, m a)] -> m a -> m a condM :: forall {k} {k} (s :: k) (m :: k -> *) (a :: k). [(Scoped s Bool, m a)] -> m a -> m a condM [] m a o = m a o condM ((Scoped Bool True, m a a):[(Scoped s Bool, m a)] _) m a _ = m a a condM ((Scoped Bool False, m a _):[(Scoped s Bool, m a)] t) m a o = [(Scoped s Bool, m a)] -> m a -> m a forall {k} {k} (s :: k) (m :: k -> *) (a :: k). [(Scoped s Bool, m a)] -> m a -> m a condM [(Scoped s Bool, m a)] t m a o empty :: Bs s empty :: forall {k} (s :: k). Bs s empty = LByteString -> Scoped s LByteString forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure LByteString L.empty singleton :: W8 s -> Bs s singleton :: forall {k} (s :: k). W8 s -> Bs s singleton = LByteString -> Scoped s LByteString forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure (LByteString -> Scoped s LByteString) -> (W8 s -> LByteString) -> W8 s -> Scoped s LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Word8 -> LByteString L.singleton (Word8 -> LByteString) -> (W8 s -> Word8) -> W8 s -> LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . W8 s -> Word8 forall {k} (s :: k) a. Scoped s a -> a unScoped pack :: [W8 s] -> Bs s pack :: forall {k} (s :: k). [W8 s] -> Bs s pack = LByteString -> Scoped s LByteString forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure (LByteString -> Scoped s LByteString) -> ([W8 s] -> LByteString) -> [W8 s] -> Scoped s LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . [Word8] -> LByteString L.pack ([Word8] -> LByteString) -> ([W8 s] -> [Word8]) -> [W8 s] -> LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . (W8 s -> Word8) -> [W8 s] -> [Word8] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap W8 s -> Word8 forall {k} (s :: k) a. Scoped s a -> a unScoped cons :: W8 s -> Bs s -> Bs s cons :: forall {k} (s :: k). W8 s -> Bs s -> Bs s cons = (Word8 -> LByteString -> LByteString) -> Scoped s Word8 -> Scoped s LByteString -> Scoped s LByteString forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 Word8 -> LByteString -> LByteString L.cons snoc :: Bs s -> W8 s -> Bs s snoc :: forall {k} (s :: k). Bs s -> W8 s -> Bs s snoc = (LByteString -> Word8 -> LByteString) -> Scoped s LByteString -> Scoped s Word8 -> Scoped s LByteString forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 LByteString -> Word8 -> LByteString L.snoc uncons :: Bs s -> Scoped s (Maybe (Word8, LByteString)) uncons :: forall {k} (s :: k). Bs s -> Scoped s (Maybe (Word8, LByteString)) uncons = (LByteString -> Maybe (Word8, LByteString)) -> Scoped s LByteString -> Scoped s (Maybe (Word8, LByteString)) forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> Maybe (Word8, LByteString) L.uncons unsnoc :: Bs s -> Scoped s (Maybe (LByteString, Word8)) unsnoc :: forall {k} (s :: k). Bs s -> Scoped s (Maybe (LByteString, Word8)) unsnoc = (LByteString -> Maybe (LByteString, Word8)) -> Scoped s LByteString -> Scoped s (Maybe (LByteString, Word8)) forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> Maybe (LByteString, Word8) L.unsnoc null :: Bs s -> B s null :: forall {k} (s :: k). Bs s -> B s null = (LByteString -> Bool) -> Scoped s LByteString -> Scoped s Bool forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> Bool L.null reverse :: Bs s -> Bs s reverse :: forall {k} (s :: k). Bs s -> Bs s reverse = (LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> LByteString L.reverse intersperse :: W8 s -> Bs s -> Bs s intersperse :: forall {k} (s :: k). W8 s -> Bs s -> Bs s intersperse = (Word8 -> LByteString -> LByteString) -> Scoped s Word8 -> Scoped s LByteString -> Scoped s LByteString forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 Word8 -> LByteString -> LByteString L.intersperse intercalate :: Bs s -> [Bs s] -> Bs s intercalate :: forall {k} (s :: k). Bs s -> [Bs s] -> Bs s intercalate (Scoped LByteString bs) = LByteString -> Scoped s LByteString forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure (LByteString -> Scoped s LByteString) -> ([Scoped s LByteString] -> LByteString) -> [Scoped s LByteString] -> Scoped s LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . LByteString -> [LByteString] -> LByteString L.intercalate LByteString bs ([LByteString] -> LByteString) -> ([Scoped s LByteString] -> [LByteString]) -> [Scoped s LByteString] -> LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . (Scoped s LByteString -> LByteString) -> [Scoped s LByteString] -> [LByteString] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Scoped s LByteString -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped transpose :: [Bs s] -> [Bs s] transpose :: forall {k} (s :: k). [Bs s] -> [Bs s] transpose = (LByteString -> Bs s) -> [LByteString] -> [Bs s] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> Bs s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure ([LByteString] -> [Bs s]) -> ([Bs s] -> [LByteString]) -> [Bs s] -> [Bs s] forall b c a. (b -> c) -> (a -> b) -> a -> c . [LByteString] -> [LByteString] L.transpose ([LByteString] -> [LByteString]) -> ([Bs s] -> [LByteString]) -> [Bs s] -> [LByteString] forall b c a. (b -> c) -> (a -> b) -> a -> c . (Bs s -> LByteString) -> [Bs s] -> [LByteString] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Bs s -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped foldl' :: (Scoped s a -> Word8 -> Scoped s a) -> Scoped s a -> Bs s -> Scoped s a foldl' :: forall {k} (s :: k) a. (Scoped s a -> Word8 -> Scoped s a) -> Scoped s a -> Bs s -> Scoped s a foldl' Scoped s a -> Word8 -> Scoped s a f (Scoped a b) = (LByteString -> a) -> Scoped s LByteString -> Scoped s a forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((a -> Word8 -> a) -> a -> LByteString -> a forall a. (a -> Word8 -> a) -> a -> LByteString -> a L.foldl' (\a a Word8 i -> Scoped s a -> a forall {k} (s :: k) a. Scoped s a -> a unScoped (Scoped s a -> a) -> Scoped s a -> a forall a b. (a -> b) -> a -> b $ Scoped s a -> Word8 -> Scoped s a f (a -> Scoped s a forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure a a) Word8 i) a b) foldr' :: (Word8 -> Scoped s a -> Scoped s a) -> Scoped s a -> Bs s -> Scoped s a foldr' :: forall {k} (s :: k) a. (Word8 -> Scoped s a -> Scoped s a) -> Scoped s a -> Bs s -> Scoped s a foldr' Word8 -> Scoped s a -> Scoped s a f (Scoped a b) = (LByteString -> a) -> Scoped s LByteString -> Scoped s a forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> a -> a) -> a -> LByteString -> a forall a. (Word8 -> a -> a) -> a -> LByteString -> a L.foldr' (\Word8 i a a -> Scoped s a -> a forall {k} (s :: k) a. Scoped s a -> a unScoped (Scoped s a -> a) -> Scoped s a -> a forall a b. (a -> b) -> a -> b $ Word8 -> Scoped s a -> Scoped s a f Word8 i (a -> Scoped s a forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure a a)) a b) concat :: [Bs s] -> Bs s concat :: forall {k} (s :: k). [Bs s] -> Bs s concat = LByteString -> Scoped s LByteString forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure (LByteString -> Scoped s LByteString) -> ([Scoped s LByteString] -> LByteString) -> [Scoped s LByteString] -> Scoped s LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . [LByteString] -> LByteString L.concat ([LByteString] -> LByteString) -> ([Scoped s LByteString] -> [LByteString]) -> [Scoped s LByteString] -> LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . (Scoped s LByteString -> LByteString) -> [Scoped s LByteString] -> [LByteString] forall a b. (a -> b) -> [a] -> [b] forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Scoped s LByteString -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped concatMap :: (Word8 -> LByteString) -> Bs s -> Bs s concatMap :: forall {k} (s :: k). (Word8 -> LByteString) -> Bs s -> Bs s concatMap Word8 -> LByteString f = (LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> LByteString) -> LByteString -> LByteString L.concatMap Word8 -> LByteString f) any :: (Word8 -> Bool) -> Bs s -> B s any :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> B s any Word8 -> Bool p = (LByteString -> Bool) -> Scoped s LByteString -> Scoped s Bool forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> Bool) -> LByteString -> Bool L.any Word8 -> Bool p) all :: (Word8 -> Bool) -> Bs s -> B s all :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> B s all Word8 -> Bool p = (LByteString -> Bool) -> Scoped s LByteString -> Scoped s Bool forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> Bool) -> LByteString -> Bool L.all Word8 -> Bool p) maximum :: HasCallStack => Bs s -> W8 s maximum :: forall {k} (s :: k). HasCallStack => Bs s -> W8 s maximum = (LByteString -> Word8) -> Scoped s LByteString -> Scoped s Word8 forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap HasCallStack => LByteString -> Word8 LByteString -> Word8 L.maximum minimum :: HasCallStack => Bs s -> W8 s minimum :: forall {k} (s :: k). HasCallStack => Bs s -> W8 s minimum = (LByteString -> Word8) -> Scoped s LByteString -> Scoped s Word8 forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap HasCallStack => LByteString -> Word8 LByteString -> Word8 L.minimum compareLength :: Bs s -> I64 s -> Scoped s Ordering compareLength :: forall {k} (s :: k). Bs s -> I64 s -> Scoped s Ordering compareLength = (LByteString -> Int64 -> Ordering) -> Scoped s LByteString -> Scoped s Int64 -> Scoped s Ordering forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 LByteString -> Int64 -> Ordering L.compareLength scanl :: (W8 s -> W8 s -> W8 s) -> W8 s -> Bs s -> Bs s scanl :: forall {k} (s :: k). (W8 s -> W8 s -> W8 s) -> W8 s -> Bs s -> Bs s scanl W8 s -> W8 s -> W8 s f W8 s i = (LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> Word8 -> Word8) -> Word8 -> LByteString -> LByteString L.scanl (\Word8 a Word8 e -> W8 s -> Word8 forall {k} (s :: k) a. Scoped s a -> a unScoped (W8 s -> Word8) -> W8 s -> Word8 forall a b. (a -> b) -> a -> b $ W8 s -> W8 s -> W8 s f (Word8 -> W8 s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure Word8 a) (Word8 -> W8 s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure Word8 e)) (Word8 -> LByteString -> LByteString) -> Word8 -> LByteString -> LByteString forall a b. (a -> b) -> a -> b $ W8 s -> Word8 forall {k} (s :: k) a. Scoped s a -> a unScoped W8 s i) scanl1 :: (W8 s -> W8 s -> W8 s) -> Bs s -> Bs s scanl1 :: forall {k} (s :: k). (W8 s -> W8 s -> W8 s) -> Bs s -> Bs s scanl1 W8 s -> W8 s -> W8 s f = (LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> Word8 -> Word8) -> LByteString -> LByteString L.scanl1 (\Word8 a Word8 e -> W8 s -> Word8 forall {k} (s :: k) a. Scoped s a -> a unScoped (W8 s -> Word8) -> W8 s -> Word8 forall a b. (a -> b) -> a -> b $ W8 s -> W8 s -> W8 s f (Word8 -> W8 s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure Word8 a) (Word8 -> W8 s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure Word8 e))) scanr :: (W8 s -> W8 s -> W8 s) -> W8 s -> Bs s -> Bs s scanr :: forall {k} (s :: k). (W8 s -> W8 s -> W8 s) -> W8 s -> Bs s -> Bs s scanr W8 s -> W8 s -> W8 s f W8 s i = (LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> Word8 -> Word8) -> Word8 -> LByteString -> LByteString L.scanr (\Word8 a Word8 e -> W8 s -> Word8 forall {k} (s :: k) a. Scoped s a -> a unScoped (W8 s -> Word8) -> W8 s -> Word8 forall a b. (a -> b) -> a -> b $ W8 s -> W8 s -> W8 s f (Word8 -> W8 s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure Word8 a) (Word8 -> W8 s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure Word8 e)) (Word8 -> LByteString -> LByteString) -> Word8 -> LByteString -> LByteString forall a b. (a -> b) -> a -> b $ W8 s -> Word8 forall {k} (s :: k) a. Scoped s a -> a unScoped W8 s i) scanr1 :: (W8 s -> W8 s -> W8 s) -> Bs s -> Bs s scanr1 :: forall {k} (s :: k). (W8 s -> W8 s -> W8 s) -> Bs s -> Bs s scanr1 W8 s -> W8 s -> W8 s f = (LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> Word8 -> Word8) -> LByteString -> LByteString L.scanr1 (\Word8 a Word8 e -> W8 s -> Word8 forall {k} (s :: k) a. Scoped s a -> a unScoped (W8 s -> Word8) -> W8 s -> Word8 forall a b. (a -> b) -> a -> b $ W8 s -> W8 s -> W8 s f (Word8 -> W8 s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure Word8 a) (Word8 -> W8 s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure Word8 e))) mapAccumL :: (acc -> W8 s -> (acc, W8 s)) -> acc -> Bs s -> (acc, Bs s) mapAccumL :: forall {k} acc (s :: k). (acc -> W8 s -> (acc, W8 s)) -> acc -> Bs s -> (acc, Bs s) mapAccumL acc -> W8 s -> (acc, W8 s) f acc a (Scoped LByteString lbs) = case (acc -> Word8 -> (acc, Word8)) -> acc -> LByteString -> (acc, LByteString) forall acc. (acc -> Word8 -> (acc, Word8)) -> acc -> LByteString -> (acc, LByteString) L.mapAccumL (\acc acc (Word8 b :: Word8) -> (W8 s -> Word8) -> (acc, W8 s) -> (acc, Word8) forall a b c. (a -> b) -> (c, a) -> (c, b) mapSnd W8 s -> Word8 forall {k} (s :: k) a. Scoped s a -> a unScoped ((acc, W8 s) -> (acc, Word8)) -> (acc, W8 s) -> (acc, Word8) forall a b. (a -> b) -> a -> b $ acc -> W8 s -> (acc, W8 s) f acc acc (Word8 -> W8 s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure Word8 b)) acc a LByteString lbs of (acc acc, LByteString lbs') -> (acc acc, LByteString -> Scoped s LByteString forall {k} (s :: k). LByteString -> Bs s toBs LByteString lbs') mapAccumR :: (acc -> W8 s -> (acc, W8 s)) -> acc -> Bs s -> (acc, Bs s) mapAccumR :: forall {k} acc (s :: k). (acc -> W8 s -> (acc, W8 s)) -> acc -> Bs s -> (acc, Bs s) mapAccumR acc -> W8 s -> (acc, W8 s) f acc a (Scoped LByteString lbs) = case (acc -> Word8 -> (acc, Word8)) -> acc -> LByteString -> (acc, LByteString) forall acc. (acc -> Word8 -> (acc, Word8)) -> acc -> LByteString -> (acc, LByteString) L.mapAccumR (\acc acc Word8 b -> (W8 s -> Word8) -> (acc, W8 s) -> (acc, Word8) forall a b c. (a -> b) -> (c, a) -> (c, b) mapSnd W8 s -> Word8 forall {k} (s :: k) a. Scoped s a -> a unScoped ((acc, W8 s) -> (acc, Word8)) -> (acc, W8 s) -> (acc, Word8) forall a b. (a -> b) -> a -> b $ acc -> W8 s -> (acc, W8 s) f acc acc (Word8 -> W8 s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure Word8 b)) acc a LByteString lbs of (acc acc, LByteString lbs') -> (acc acc, LByteString -> Scoped s LByteString forall {k} (s :: k). LByteString -> Bs s toBs LByteString lbs') repeat :: W8 s -> Bs s repeat :: forall {k} (s :: k). W8 s -> Bs s repeat = (Word8 -> LByteString) -> Scoped s Word8 -> Scoped s LByteString forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap Word8 -> LByteString L.repeat replicate :: I64 s -> W8 s -> Bs s replicate :: forall {k} (s :: k). I64 s -> W8 s -> Bs s replicate = (Int64 -> Word8 -> LByteString) -> Scoped s Int64 -> Scoped s Word8 -> Scoped s LByteString forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 Int64 -> Word8 -> LByteString L.replicate cycle :: HasCallStack => Bs s -> Bs s cycle :: forall {k} (s :: k). HasCallStack => Bs s -> Bs s cycle = (LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap HasCallStack => LByteString -> LByteString LByteString -> LByteString L.cycle iterate :: (W8 s -> W8 s) -> W8 s -> Bs s iterate :: forall {k} (s :: k). (W8 s -> W8 s) -> W8 s -> Bs s iterate W8 s -> W8 s f (Scoped Word8 i) = LByteString -> Bs s forall {k} (s :: k). LByteString -> Bs s toBs (LByteString -> Bs s) -> LByteString -> Bs s forall a b. (a -> b) -> a -> b $ (Word8 -> Word8) -> Word8 -> LByteString L.iterate (W8 s -> Word8 forall {k} (s :: k) a. Scoped s a -> a unScoped (W8 s -> Word8) -> (Word8 -> W8 s) -> Word8 -> Word8 forall b c a. (b -> c) -> (a -> b) -> a -> c . W8 s -> W8 s f (W8 s -> W8 s) -> (Word8 -> W8 s) -> Word8 -> W8 s forall b c a. (b -> c) -> (a -> b) -> a -> c . Word8 -> W8 s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure) Word8 i unfoldr :: (a -> Maybe (W8 s, a)) -> a -> Bs s unfoldr :: forall {k} a (s :: k). (a -> Maybe (W8 s, a)) -> a -> Bs s unfoldr a -> Maybe (W8 s, a) f = LByteString -> Bs s forall {k} (s :: k). LByteString -> Bs s toBs (LByteString -> Bs s) -> (a -> LByteString) -> a -> Bs s forall b c a. (b -> c) -> (a -> b) -> a -> c . (a -> Maybe (Word8, a)) -> a -> LByteString forall a. (a -> Maybe (Word8, a)) -> a -> LByteString L.unfoldr (\a a -> ((W8 s, a) -> (Word8, a)) -> Maybe (W8 s, a) -> Maybe (Word8, a) forall a b. (a -> b) -> Maybe a -> Maybe b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((W8 s -> Word8) -> (W8 s, a) -> (Word8, a) forall a b c. (a -> b) -> (a, c) -> (b, c) mapFst W8 s -> Word8 forall {k} (s :: k) a. Scoped s a -> a unScoped) (Maybe (W8 s, a) -> Maybe (Word8, a)) -> Maybe (W8 s, a) -> Maybe (Word8, a) forall a b. (a -> b) -> a -> b $ a -> Maybe (W8 s, a) f a a) isPrefixOf :: Bs s -> Bs s -> B s isPrefixOf :: forall {k} (s :: k). Bs s -> Bs s -> B s isPrefixOf = (LByteString -> LByteString -> Bool) -> Scoped s LByteString -> Scoped s LByteString -> Scoped s Bool forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 LByteString -> LByteString -> Bool L.isPrefixOf isSuffixOf :: Bs s -> Bs s -> B s isSuffixOf :: forall {k} (s :: k). Bs s -> Bs s -> B s isSuffixOf = (LByteString -> LByteString -> Bool) -> Scoped s LByteString -> Scoped s LByteString -> Scoped s Bool forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 LByteString -> LByteString -> Bool L.isSuffixOf elem :: W8 s -> Bs s -> B s elem :: forall {k} (s :: k). W8 s -> Bs s -> B s elem = (Word8 -> LByteString -> Bool) -> Scoped s Word8 -> Scoped s LByteString -> Scoped s Bool forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 Word8 -> LByteString -> Bool L.elem notElem :: W8 s -> Bs s -> B s notElem :: forall {k} (s :: k). W8 s -> Bs s -> B s notElem = (Word8 -> LByteString -> Bool) -> Scoped s Word8 -> Scoped s LByteString -> Scoped s Bool forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 Word8 -> LByteString -> Bool L.notElem find :: (Word8 -> Bool) -> Bs s -> Scoped s (Maybe Word8) find :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Scoped s (Maybe Word8) find Word8 -> Bool f = (LByteString -> Maybe Word8) -> Scoped s LByteString -> Scoped s (Maybe Word8) forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> Bool) -> LByteString -> Maybe Word8 L.find Word8 -> Bool f) filter :: (Word8 -> Bool) -> Bs s -> Bs s filter :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Bs s filter Word8 -> Bool f = (LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> Bool) -> LByteString -> LByteString L.filter Word8 -> Bool f) partition :: (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) partition :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) partition Word8 -> Bool f = (LByteString -> Bs s) -> (LByteString, LByteString) -> (Bs s, Bs s) forall a b. (a -> b) -> (a, a) -> (b, b) both LByteString -> Bs s forall {k} (s :: k). LByteString -> Bs s toBs ((LByteString, LByteString) -> (Bs s, Bs s)) -> (Bs s -> (LByteString, LByteString)) -> Bs s -> (Bs s, Bs s) forall b c a. (b -> c) -> (a -> b) -> a -> c . (Word8 -> Bool) -> LByteString -> (LByteString, LByteString) L.partition Word8 -> Bool f (LByteString -> (LByteString, LByteString)) -> (Bs s -> LByteString) -> Bs s -> (LByteString, LByteString) forall b c a. (b -> c) -> (a -> b) -> a -> c . Bs s -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped index :: HasCallStack => Bs s -> I64 s -> W8 s index :: forall {k} (s :: k). HasCallStack => Bs s -> I64 s -> W8 s index = (LByteString -> Int64 -> Word8) -> Scoped s LByteString -> Scoped s Int64 -> Scoped s Word8 forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 HasCallStack => LByteString -> Int64 -> Word8 LByteString -> Int64 -> Word8 L.index indexMaybe :: Bs s -> I64 s -> Scoped s (Maybe Word8) indexMaybe :: forall {k} (s :: k). Bs s -> I64 s -> Scoped s (Maybe Word8) indexMaybe = (LByteString -> Int64 -> Maybe Word8) -> Scoped s LByteString -> Scoped s Int64 -> Scoped s (Maybe Word8) forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 LByteString -> Int64 -> Maybe Word8 L.indexMaybe (!?) :: Bs s -> I64 s -> Scoped s (Maybe Word8) !? :: forall {k} (s :: k). Bs s -> I64 s -> Scoped s (Maybe Word8) (!?)= (LByteString -> Int64 -> Maybe Word8) -> Scoped s LByteString -> Scoped s Int64 -> Scoped s (Maybe Word8) forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 LByteString -> Int64 -> Maybe Word8 (L.!?) elemIndex :: W8 s -> Bs s -> Scoped s (Maybe Int64) elemIndex :: forall {k} (s :: k). W8 s -> Bs s -> Scoped s (Maybe Int64) elemIndex = (Word8 -> LByteString -> Maybe Int64) -> Scoped s Word8 -> Scoped s LByteString -> Scoped s (Maybe Int64) forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 Word8 -> LByteString -> Maybe Int64 L.elemIndex elemIndexEnd :: W8 s -> Bs s -> Scoped s (Maybe Int64) elemIndexEnd :: forall {k} (s :: k). W8 s -> Bs s -> Scoped s (Maybe Int64) elemIndexEnd = (Word8 -> LByteString -> Maybe Int64) -> Scoped s Word8 -> Scoped s LByteString -> Scoped s (Maybe Int64) forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 Word8 -> LByteString -> Maybe Int64 L.elemIndexEnd elemIndices :: W8 s -> Bs s -> Scoped s [Int64] elemIndices :: forall {k} (s :: k). W8 s -> Bs s -> Scoped s [Int64] elemIndices = (Word8 -> LByteString -> [Int64]) -> Scoped s Word8 -> Scoped s LByteString -> Scoped s [Int64] forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 Word8 -> LByteString -> [Int64] L.elemIndices findIndex :: (Word8 -> Bool) -> Bs s -> Scoped s (Maybe Int64) findIndex :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Scoped s (Maybe Int64) findIndex Word8 -> Bool p = (LByteString -> Maybe Int64) -> Scoped s LByteString -> Scoped s (Maybe Int64) forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> Bool) -> LByteString -> Maybe Int64 L.findIndex Word8 -> Bool p) findIndexEnd :: (Word8 -> Bool) -> Bs s -> Scoped s (Maybe Int64) findIndexEnd :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Scoped s (Maybe Int64) findIndexEnd Word8 -> Bool p = (LByteString -> Maybe Int64) -> Scoped s LByteString -> Scoped s (Maybe Int64) forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> Bool) -> LByteString -> Maybe Int64 L.findIndexEnd Word8 -> Bool p) findIndices :: (Word8 -> Bool) -> Bs s -> Scoped s [Int64] findIndices :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Scoped s [Int64] findIndices Word8 -> Bool p = (LByteString -> [Int64]) -> Scoped s LByteString -> Scoped s [Int64] forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> Bool) -> LByteString -> [Int64] L.findIndices Word8 -> Bool p) count :: W8 s -> Bs s -> I64 s count :: forall {k} (s :: k). W8 s -> Bs s -> I64 s count = (Word8 -> LByteString -> Int64) -> Scoped s Word8 -> Scoped s LByteString -> Scoped s Int64 forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 Word8 -> LByteString -> Int64 L.count zip :: Bs s -> Bs s -> Scoped s [(Word8, Word8)] zip :: forall {k} (s :: k). Bs s -> Bs s -> Scoped s [(Word8, Word8)] zip = (LByteString -> LByteString -> [(Word8, Word8)]) -> Scoped s LByteString -> Scoped s LByteString -> Scoped s [(Word8, Word8)] forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 LByteString -> LByteString -> [(Word8, Word8)] L.zip zipWith :: (Word8 -> Word8 -> a) -> Bs s -> Bs s -> Scoped s [a] zipWith :: forall {k} a (s :: k). (Word8 -> Word8 -> a) -> Bs s -> Bs s -> Scoped s [a] zipWith Word8 -> Word8 -> a f = (LByteString -> LByteString -> [a]) -> Scoped s LByteString -> Scoped s LByteString -> Scoped s [a] forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 ((Word8 -> Word8 -> a) -> LByteString -> LByteString -> [a] forall a. (Word8 -> Word8 -> a) -> LByteString -> LByteString -> [a] L.zipWith Word8 -> Word8 -> a f) packZipWith :: (Word8 -> Word8 -> Word8) -> Bs s -> Bs s -> Bs s packZipWith :: forall {k} (s :: k). (Word8 -> Word8 -> Word8) -> Bs s -> Bs s -> Bs s packZipWith Word8 -> Word8 -> Word8 f = (LByteString -> LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString -> Scoped s LByteString forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 ((Word8 -> Word8 -> Word8) -> LByteString -> LByteString -> LByteString L.packZipWith Word8 -> Word8 -> Word8 f) unzip :: Scoped s [(Word8, Word8)] -> (Bs s, Bs s) unzip :: forall {k} (s :: k). Scoped s [(Word8, Word8)] -> (Bs s, Bs s) unzip = (LByteString -> Bs s) -> (LByteString, LByteString) -> (Bs s, Bs s) forall a b. (a -> b) -> (a, a) -> (b, b) both LByteString -> Bs s forall {k} (s :: k). LByteString -> Bs s toBs ((LByteString, LByteString) -> (Bs s, Bs s)) -> (Scoped s [(Word8, Word8)] -> (LByteString, LByteString)) -> Scoped s [(Word8, Word8)] -> (Bs s, Bs s) forall b c a. (b -> c) -> (a -> b) -> a -> c . [(Word8, Word8)] -> (LByteString, LByteString) L.unzip ([(Word8, Word8)] -> (LByteString, LByteString)) -> (Scoped s [(Word8, Word8)] -> [(Word8, Word8)]) -> Scoped s [(Word8, Word8)] -> (LByteString, LByteString) forall b c a. (b -> c) -> (a -> b) -> a -> c . Scoped s [(Word8, Word8)] -> [(Word8, Word8)] forall {k} (s :: k) a. Scoped s a -> a unScoped copy :: Bs s -> Bs s copy :: forall {k} (s :: k). Bs s -> Bs s copy = (LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> LByteString L.copy take :: Int64 -> Bs s -> Bs s take :: forall {k} (s :: k). Int64 -> Bs s -> Bs s take Int64 n = LByteString -> Scoped s LByteString forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure (LByteString -> Scoped s LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Int64 -> LByteString -> LByteString L.take Int64 n (LByteString -> LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Scoped s LByteString -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped {-# INLINE take #-} length :: Bs s -> I64 s length :: forall {k} (s :: k). Bs s -> I64 s length = (LByteString -> Int64) -> Scoped s LByteString -> Scoped s Int64 forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> Int64 L.length {-# INLINE length #-} drop :: I64 s -> Bs s -> Bs s drop :: forall {k} (s :: k). I64 s -> Bs s -> Bs s drop (Scoped Int64 n) = LByteString -> Scoped s LByteString forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure (LByteString -> Scoped s LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Int64 -> LByteString -> LByteString L.drop Int64 n (LByteString -> LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Scoped s LByteString -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped {-# INLINE drop #-} dropEnd :: I64 s -> Bs s -> Bs s dropEnd :: forall {k} (s :: k). I64 s -> Bs s -> Bs s dropEnd (Scoped Int64 n) = LByteString -> Scoped s LByteString forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure (LByteString -> Scoped s LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Int64 -> LByteString -> LByteString L.dropEnd Int64 n (LByteString -> LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Scoped s LByteString -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped {-# INLINE dropEnd #-} dropWhile :: (Word8 -> Bool) -> Bs s -> Bs s dropWhile :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Bs s dropWhile Word8 -> Bool p = LByteString -> Scoped s LByteString forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure (LByteString -> Scoped s LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . (Word8 -> Bool) -> LByteString -> LByteString L.dropWhile Word8 -> Bool p (LByteString -> LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Scoped s LByteString -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped {-# INLINE dropWhile #-} dropWhileEnd :: (Word8 -> Bool) -> Bs s -> Bs s dropWhileEnd :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Bs s dropWhileEnd Word8 -> Bool p = LByteString -> Scoped s LByteString forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure (LByteString -> Scoped s LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . (Word8 -> Bool) -> LByteString -> LByteString L.dropWhileEnd Word8 -> Bool p (LByteString -> LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Scoped s LByteString -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped {-# INLINE dropWhileEnd #-} takeWhile :: (Word8 -> Bool) -> Bs s -> Bs s takeWhile :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Bs s takeWhile Word8 -> Bool p = LByteString -> Scoped s LByteString forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure (LByteString -> Scoped s LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . (Word8 -> Bool) -> LByteString -> LByteString L.takeWhile Word8 -> Bool p (LByteString -> LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Scoped s LByteString -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped {-# INLINE takeWhile #-} takeWhileEnd :: (Word8 -> Bool) -> Bs s -> Bs s takeWhileEnd :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Bs s takeWhileEnd Word8 -> Bool p = LByteString -> Scoped s LByteString forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure (LByteString -> Scoped s LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . (Word8 -> Bool) -> LByteString -> LByteString L.takeWhileEnd Word8 -> Bool p (LByteString -> LByteString) -> (Scoped s LByteString -> LByteString) -> Scoped s LByteString -> LByteString forall b c a. (b -> c) -> (a -> b) -> a -> c . Scoped s LByteString -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped {-# INLINE takeWhileEnd #-} span :: (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) span :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) span Word8 -> Bool p = (LByteString -> Bs s) -> (LByteString, LByteString) -> (Bs s, Bs s) forall a b. (a -> b) -> (a, a) -> (b, b) both LByteString -> Bs s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure ((LByteString, LByteString) -> (Bs s, Bs s)) -> (Bs s -> (LByteString, LByteString)) -> Bs s -> (Bs s, Bs s) forall b c a. (b -> c) -> (a -> b) -> a -> c . (Word8 -> Bool) -> LByteString -> (LByteString, LByteString) L.span Word8 -> Bool p (LByteString -> (LByteString, LByteString)) -> (Bs s -> LByteString) -> Bs s -> (LByteString, LByteString) forall b c a. (b -> c) -> (a -> b) -> a -> c . Bs s -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped spanEnd :: (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) spanEnd :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) spanEnd Word8 -> Bool p = (LByteString -> Bs s) -> (LByteString, LByteString) -> (Bs s, Bs s) forall a b. (a -> b) -> (a, a) -> (b, b) both LByteString -> Bs s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure ((LByteString, LByteString) -> (Bs s, Bs s)) -> (Bs s -> (LByteString, LByteString)) -> Bs s -> (Bs s, Bs s) forall b c a. (b -> c) -> (a -> b) -> a -> c . (Word8 -> Bool) -> LByteString -> (LByteString, LByteString) L.spanEnd Word8 -> Bool p (LByteString -> (LByteString, LByteString)) -> (Bs s -> LByteString) -> Bs s -> (LByteString, LByteString) forall b c a. (b -> c) -> (a -> b) -> a -> c . Bs s -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped break :: (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) break :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) break Word8 -> Bool p = (LByteString -> Bs s) -> (LByteString, LByteString) -> (Bs s, Bs s) forall a b. (a -> b) -> (a, a) -> (b, b) both LByteString -> Bs s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure ((LByteString, LByteString) -> (Bs s, Bs s)) -> (Bs s -> (LByteString, LByteString)) -> Bs s -> (Bs s, Bs s) forall b c a. (b -> c) -> (a -> b) -> a -> c . (Word8 -> Bool) -> LByteString -> (LByteString, LByteString) L.break Word8 -> Bool p (LByteString -> (LByteString, LByteString)) -> (Bs s -> LByteString) -> Bs s -> (LByteString, LByteString) forall b c a. (b -> c) -> (a -> b) -> a -> c . Bs s -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped breakEnd :: (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) breakEnd :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> (Bs s, Bs s) breakEnd Word8 -> Bool p = (LByteString -> Bs s) -> (LByteString, LByteString) -> (Bs s, Bs s) forall a b. (a -> b) -> (a, a) -> (b, b) both LByteString -> Bs s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure ((LByteString, LByteString) -> (Bs s, Bs s)) -> (Bs s -> (LByteString, LByteString)) -> Bs s -> (Bs s, Bs s) forall b c a. (b -> c) -> (a -> b) -> a -> c . (Word8 -> Bool) -> LByteString -> (LByteString, LByteString) L.breakEnd Word8 -> Bool p (LByteString -> (LByteString, LByteString)) -> (Bs s -> LByteString) -> Bs s -> (LByteString, LByteString) forall b c a. (b -> c) -> (a -> b) -> a -> c . Bs s -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped splitAt :: I64 s -> Bs s -> (Bs s, Bs s) splitAt :: forall {k} (s :: k). I64 s -> Bs s -> (Bs s, Bs s) splitAt (Scoped Int64 n) = (LByteString -> Bs s) -> (LByteString, LByteString) -> (Bs s, Bs s) forall a b. (a -> b) -> (a, a) -> (b, b) both LByteString -> Bs s forall a. a -> Scoped s a forall (f :: * -> *) a. Applicative f => a -> f a pure ((LByteString, LByteString) -> (Bs s, Bs s)) -> (Bs s -> (LByteString, LByteString)) -> Bs s -> (Bs s, Bs s) forall b c a. (b -> c) -> (a -> b) -> a -> c . Int64 -> LByteString -> (LByteString, LByteString) L.splitAt Int64 n (LByteString -> (LByteString, LByteString)) -> (Bs s -> LByteString) -> Bs s -> (LByteString, LByteString) forall b c a. (b -> c) -> (a -> b) -> a -> c . Bs s -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped mapLbs :: (LByteString -> LByteString) -> Bs s -> Bs s mapLbs :: forall {k} (s :: k). (LByteString -> LByteString) -> Bs s -> Bs s mapLbs LByteString -> LByteString f = (LByteString -> LByteString) -> Scoped s LByteString -> Scoped s LByteString forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> LByteString f unpack8 :: Monad m => Bs s -> LazyT s m String unpack8 :: forall {k} (m :: * -> *) (s :: k). Monad m => Bs s -> LazyT s m String unpack8 = String -> LazyT s m String forall a. a -> LazyT s m a forall (f :: * -> *) a. Applicative f => a -> f a pure (String -> LazyT s m String) -> (Bs s -> String) -> Bs s -> LazyT s m String forall b c a. (b -> c) -> (a -> b) -> a -> c . LByteString -> String L8.unpack (LByteString -> String) -> (Bs s -> LByteString) -> Bs s -> String forall b c a. (b -> c) -> (a -> b) -> a -> c . Bs s -> LByteString forall {k} (s :: k) a. Scoped s a -> a unScoped toLbs :: Monad m => Bs s -> LazyT s m LByteString toLbs :: forall {k} (m :: * -> *) (s :: k). Monad m => Bs s -> LazyT s m LByteString toLbs (Scoped LByteString a) = case LByteString -> () forall a. NFData a => a -> () rnf LByteString a of () -> LByteString -> LazyT s m LByteString forall a. a -> LazyT s m a forall (f :: * -> *) a. Applicative f => a -> f a pure LByteString a group :: Bs s -> Scoped s [LByteString] group :: forall {k} (s :: k). Bs s -> Scoped s [LByteString] group = (LByteString -> [LByteString]) -> Scoped s LByteString -> Scoped s [LByteString] forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> [LByteString] L.group groupBy :: (Word8 -> Word8 -> Bool) -> Bs s -> Scoped s [LByteString] groupBy :: forall {k} (s :: k). (Word8 -> Word8 -> Bool) -> Bs s -> Scoped s [LByteString] groupBy Word8 -> Word8 -> Bool p = (LByteString -> [LByteString]) -> Scoped s LByteString -> Scoped s [LByteString] forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> Word8 -> Bool) -> LByteString -> [LByteString] L.groupBy Word8 -> Word8 -> Bool p) inits :: Bs s -> Scoped s [LByteString] inits :: forall {k} (s :: k). Bs s -> Scoped s [LByteString] inits = (LByteString -> [LByteString]) -> Scoped s LByteString -> Scoped s [LByteString] forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> [LByteString] L.inits tails :: Bs s -> Scoped s [LByteString] tails :: forall {k} (s :: k). Bs s -> Scoped s [LByteString] tails = (LByteString -> [LByteString]) -> Scoped s LByteString -> Scoped s [LByteString] forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> [LByteString] L.tails initsNE :: Bs s -> Scoped s (NonEmpty LByteString) initsNE :: forall {k} (s :: k). Bs s -> Scoped s (NonEmpty LByteString) initsNE = (LByteString -> NonEmpty LByteString) -> Scoped s LByteString -> Scoped s (NonEmpty LByteString) forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> NonEmpty LByteString L.initsNE tailsNE :: Bs s -> Scoped s (NonEmpty LByteString) tailsNE :: forall {k} (s :: k). Bs s -> Scoped s (NonEmpty LByteString) tailsNE = (LByteString -> NonEmpty LByteString) -> Scoped s LByteString -> Scoped s (NonEmpty LByteString) forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap LByteString -> NonEmpty LByteString L.tailsNE stripPrefix :: Bs s -> Bs s -> Scoped s (Maybe LByteString) stripPrefix :: forall {k} (s :: k). Bs s -> Bs s -> Scoped s (Maybe LByteString) stripPrefix = (LByteString -> LByteString -> Maybe LByteString) -> Scoped s LByteString -> Scoped s LByteString -> Scoped s (Maybe LByteString) forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 LByteString -> LByteString -> Maybe LByteString L.stripPrefix stripSuffix :: Bs s -> Bs s -> Scoped s (Maybe LByteString) stripSuffix :: forall {k} (s :: k). Bs s -> Bs s -> Scoped s (Maybe LByteString) stripSuffix = (LByteString -> LByteString -> Maybe LByteString) -> Scoped s LByteString -> Scoped s LByteString -> Scoped s (Maybe LByteString) forall a b c. (a -> b -> c) -> Scoped s a -> Scoped s b -> Scoped s c forall (f :: * -> *) a b c. Applicative f => (a -> b -> c) -> f a -> f b -> f c liftA2 LByteString -> LByteString -> Maybe LByteString L.stripSuffix splitWith :: (Word8 -> Bool) -> Bs s -> Scoped s [LByteString] splitWith :: forall {k} (s :: k). (Word8 -> Bool) -> Bs s -> Scoped s [LByteString] splitWith Word8 -> Bool p = (LByteString -> [LByteString]) -> Scoped s LByteString -> Scoped s [LByteString] forall a b. (a -> b) -> Scoped s a -> Scoped s b forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b fmap ((Word8 -> Bool) -> LByteString -> [LByteString] L.splitWith Word8 -> Bool p)