module Control.Foldl.ByteString (
fold
, head
, last
, null
, length
, any
, all
, maximum
, minimum
, elem
, notElem
, find
, index
, elemIndex
, findIndex
, count
, module Control.Foldl
, module Data.ByteString
, module Data.Word
) where
import Control.Foldl (Fold)
import Control.Foldl.Internal (Maybe'(..), lazy, strict, Either'(..), hush)
import qualified Control.Foldl as L
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy.Internal as Lazy
import qualified Data.ByteString.Unsafe as BU
import Data.Word (Word8)
import Prelude hiding (
head, last, null, length, any, all, maximum, minimum, elem, notElem )
fold :: Fold ByteString a -> Lazy.ByteString -> a
fold (L.Fold step begin done) as = done (Lazy.foldlChunks step begin as)
head :: Fold ByteString (Maybe Word8)
head = L.Fold step Nothing' lazy
where
step mw8 bs =
if B.null bs
then mw8
else case mw8 of
Just' _ -> mw8
Nothing' -> Just' (BU.unsafeHead bs)
last :: Fold ByteString (Maybe Word8)
last = L.Fold step Nothing' lazy
where
step mw8 bs =
if B.null bs
then mw8
else Just' (B.last bs)
null :: Fold ByteString Bool
null = L.Fold step True id
where
step isNull bs = isNull && B.null bs
length :: Num n => Fold ByteString n
length = L.Fold (\n bs -> n + fromIntegral (B.length bs)) 0 id
all :: (Word8 -> Bool) -> Fold ByteString Bool
all predicate = L.Fold (\b bs -> b && B.all predicate bs) True id
any :: (Word8 -> Bool) -> Fold ByteString Bool
any predicate = L.Fold (\b bs -> b || B.any predicate bs) False id
maximum :: Fold ByteString (Maybe Word8)
maximum = L.Fold step Nothing' lazy
where
step mw8 bs =
if B.null bs
then mw8
else Just' (case mw8 of
Nothing' -> B.maximum bs
Just' w8 -> max w8 (B.maximum bs) )
minimum :: Fold ByteString (Maybe Word8)
minimum = L.Fold step Nothing' lazy
where
step mw8 bs =
if B.null bs
then mw8
else Just' (case mw8 of
Nothing' -> B.minimum bs
Just' w8 -> min w8 (B.minimum bs) )
elem :: Word8 -> Fold ByteString Bool
elem w8 = any (w8 ==)
notElem :: Word8 -> Fold ByteString Bool
notElem w8 = all (w8 /=)
find :: (Word8 -> Bool) -> Fold ByteString (Maybe Word8)
find predicate = L.Fold step Nothing' lazy
where
step mw8 bs = case mw8 of
Nothing' -> strict (B.find predicate bs)
Just' _ -> mw8
index :: Integral n => n -> Fold ByteString (Maybe Word8)
index i = L.Fold step (Left' (fromIntegral i)) hush
where
step x bs = case x of
Left' remainder ->
let len = B.length bs
in if remainder < len
then Right' (BU.unsafeIndex bs remainder)
else Left' (remainder len)
_ -> x
elemIndex :: Num n => Word8 -> Fold ByteString (Maybe n)
elemIndex w8 = findIndex (w8 ==)
findIndex :: Num n => (Word8 -> Bool) -> Fold ByteString (Maybe n)
findIndex predicate = L.Fold step (Left' 0) hush
where
step x bs = case x of
Left' m -> case B.findIndex predicate bs of
Nothing -> Left' (m + fromIntegral (B.length bs))
Just n -> Right' (m + fromIntegral n)
_ -> x
count :: Num n => Word8 -> Fold ByteString n
count w8 = L.Fold step 0 id
where
step n bs = n + fromIntegral (B.count w8 bs)