module Data.Enumerator.List
(
fold
, foldM
, Data.Enumerator.List.map
, Data.Enumerator.List.mapM
, Data.Enumerator.List.mapM_
, Data.Enumerator.List.concatMap
, concatMapM
, mapAccum
, mapAccumM
, concatMapAccum
, concatMapAccumM
, Data.Enumerator.List.iterate
, iterateM
, Data.Enumerator.List.repeat
, repeatM
, Data.Enumerator.List.replicate
, replicateM
, generateM
, unfold
, unfoldM
, drop
, Data.Enumerator.List.dropWhile
, Data.Enumerator.List.filter
, filterM
, unique
, head
, head_
, Data.Enumerator.List.take
, takeWhile
, consume
, zip
, zip3
, zip4
, zip5
, zip6
, zip7
, zipWith
, zipWith3
, zipWith4
, zipWith5
, zipWith6
, zipWith7
, require
, isolate
, isolateWhile
, splitWhen
) where
import Prelude hiding (head, drop, sequence, takeWhile, zip, zip3, zipWith, zipWith3)
import Control.Exception (ErrorCall(..))
import qualified Control.Monad as CM
import Control.Monad.Trans.Class (lift)
import qualified Data.List as L
import Data.Monoid (mappend)
import qualified Data.Set
import Data.Enumerator (sequence, throwError)
import Data.Enumerator.Internal
fold :: Monad m => (b -> a -> b) -> b
-> Iteratee a m b
fold step = continue . loop where
f = L.foldl' step
loop acc stream = case stream of
Chunks [] -> continue (loop acc)
Chunks xs -> continue (loop $! f acc xs)
EOF -> yield acc EOF
foldM :: Monad m => (b -> a -> m b) -> b
-> Iteratee a m b
foldM step = continue . loop where
f = CM.foldM step
loop acc stream = acc `seq` case stream of
Chunks [] -> continue (loop acc)
Chunks xs -> lift (f acc xs) >>= continue . loop
EOF -> yield acc EOF
unfold :: Monad m => (s -> Maybe (a, s)) -> s -> Enumerator a m b
unfold f = checkContinue1 $ \loop s k -> case f s of
Nothing -> continue k
Just (a, s') -> k (Chunks [a]) >>== loop s'
unfoldM :: Monad m => (s -> m (Maybe (a, s))) -> s -> Enumerator a m b
unfoldM f = checkContinue1 $ \loop s k -> do
fs <- lift (f s)
case fs of
Nothing -> continue k
Just (a, s') -> k (Chunks [a]) >>== loop s'
concatMapM :: Monad m => (ao -> m [ai])
-> Enumeratee ao ai m b
concatMapM f = checkDone (continue . step) where
step k EOF = yield (Continue k) EOF
step k (Chunks xs) = loop k xs
loop k [] = continue (step k)
loop k (x:xs) = do
fx <- lift (f x)
k (Chunks fx) >>==
checkDoneEx (Chunks xs) (`loop` xs)
concatMap :: Monad m => (ao -> [ai])
-> Enumeratee ao ai m b
concatMap f = concatMapM (return . f)
map :: Monad m => (ao -> ai)
-> Enumeratee ao ai m b
map f = Data.Enumerator.List.concatMap (\x -> [f x])
mapM :: Monad m => (ao -> m ai)
-> Enumeratee ao ai m b
mapM f = concatMapM (\x -> Prelude.mapM f [x])
mapM_ :: Monad m => (a -> m b) -> Iteratee a m ()
mapM_ f = foldM (\_ x -> f x >> return ()) ()
concatMapAccum :: Monad m => (s -> ao -> (s, [ai])) -> s -> Enumeratee ao ai m b
concatMapAccum f s0 = checkDone (continue . step s0) where
step _ k EOF = yield (Continue k) EOF
step s k (Chunks xs) = loop s k xs
loop s k [] = continue (step s k)
loop s k (x:xs) = case f s x of
(s', ai) -> k (Chunks ai) >>==
checkDoneEx (Chunks xs) (\k' -> loop s' k' xs)
concatMapAccumM :: Monad m => (s -> ao -> m (s, [ai])) -> s -> Enumeratee ao ai m b
concatMapAccumM f s0 = checkDone (continue . step s0) where
step _ k EOF = yield (Continue k) EOF
step s k (Chunks xs) = loop s k xs
loop s k [] = continue (step s k)
loop s k (x:xs) = do
(s', ai) <- lift (f s x)
k (Chunks ai) >>==
checkDoneEx (Chunks xs) (\k' -> loop s' k' xs)
mapAccum :: Monad m => (s -> ao -> (s, ai)) -> s -> Enumeratee ao ai m b
mapAccum f = concatMapAccum (\s ao -> case f s ao of (s', ai) -> (s', [ai]))
mapAccumM :: Monad m => (s -> ao -> m (s, ai)) -> s -> Enumeratee ao ai m b
mapAccumM f = concatMapAccumM (\s ao -> do
(s', ai) <- f s ao
return (s', [ai]))
iterate :: Monad m => (a -> a) -> a -> Enumerator a m b
iterate f = checkContinue1 $ \loop s k -> k (Chunks [s]) >>== loop (f s)
iterateM :: Monad m => (a -> m a) -> a
-> Enumerator a m b
iterateM f base = worker (return base) where
worker = checkContinue1 $ \loop m_a k -> do
a <- lift m_a
k (Chunks [a]) >>== loop (f a)
repeat :: Monad m => a -> Enumerator a m b
repeat a = checkContinue0 $ \loop k -> k (Chunks [a]) >>== loop
repeatM :: Monad m => m a -> Enumerator a m b
repeatM m_a step = do
a <- lift m_a
iterateM (const m_a) a step
replicateM :: Monad m => Integer -> m a
-> Enumerator a m b
replicateM maxCount getNext = loop maxCount where
loop 0 step = returnI step
loop n (Continue k) = do
next <- lift getNext
k (Chunks [next]) >>== loop (n 1)
loop _ step = returnI step
replicate :: Monad m => Integer -> a
-> Enumerator a m b
replicate maxCount a = replicateM maxCount (return a)
generateM :: Monad m => m (Maybe a)
-> Enumerator a m b
generateM getNext = checkContinue0 $ \loop k -> do
next <- lift getNext
case next of
Nothing -> continue k
Just x -> k (Chunks [x]) >>== loop
filter :: Monad m => (a -> Bool)
-> Enumeratee a a m b
filter p = Data.Enumerator.List.concatMap (\x -> [x | p x])
filterM :: Monad m => (a -> m Bool)
-> Enumeratee a a m b
filterM p = concatMapM (\x -> CM.filterM p [x])
take :: Monad m => Integer -> Iteratee a m [a]
take n | n <= 0 = return []
take n = continue (loop id n) where
len = L.genericLength
loop acc n' (Chunks xs)
| len xs < n' = continue (loop (acc . (xs ++)) (n' len xs))
| otherwise = let
(xs', extra) = L.genericSplitAt n' xs
in yield (acc xs') (Chunks extra)
loop acc _ EOF = yield (acc []) EOF
takeWhile :: Monad m => (a -> Bool) -> Iteratee a m [a]
takeWhile p = continue (loop id) where
loop acc (Chunks []) = continue (loop acc)
loop acc (Chunks xs) = case Prelude.span p xs of
(_, []) -> continue (loop (acc . (xs ++)))
(xs', extra) -> yield (acc xs') (Chunks extra)
loop acc EOF = yield (acc []) EOF
consume :: Monad m => Iteratee a m [a]
consume = continue (loop id) where
loop acc (Chunks []) = continue (loop acc)
loop acc (Chunks xs) = continue (loop (acc . (xs ++)))
loop acc EOF = yield (acc []) EOF
zip :: Monad m
=> Iteratee a m b1
-> Iteratee a m b2
-> Iteratee a m (b1, b2)
zip i1 i2 = continue step where
step (Chunks []) = continue step
step stream@(Chunks _) = do
let enumStream s = case s of
Continue k -> k stream
Yield b extra -> yield b (mappend extra stream)
Error err -> throwError err
s1 <- lift (runIteratee (enumStream ==<< i1))
s2 <- lift (runIteratee (enumStream ==<< i2))
case (s1, s2) of
(Continue k1, Continue k2) -> zip (continue k1) (continue k2)
(Yield b1 _, Continue k2) -> zip (yield b1 (Chunks [])) (continue k2)
(Continue k1, Yield b2 _) -> zip (continue k1) (yield b2 (Chunks []))
(Yield b1 ex1, Yield b2 ex2) -> yield (b1, b2) (shorter ex1 ex2)
(Error err, _) -> throwError err
(_, Error err) -> throwError err
step EOF = do
b1 <- enumEOF =<< lift (runIteratee i1)
b2 <- enumEOF =<< lift (runIteratee i2)
return (b1, b2)
shorter c1@(Chunks xs) c2@(Chunks ys) = if length xs < length ys
then c1
else c2
shorter _ _ = EOF
zip3 :: Monad m
=> Iteratee a m b1
-> Iteratee a m b2
-> Iteratee a m b3
-> Iteratee a m (b1, b2, b3)
zip3 i1 i2 i3 = do
(b1, (b2, b3)) <- zip i1 (zip i2 i3)
return (b1, b2, b3)
zip4 :: Monad m
=> Iteratee a m b1
-> Iteratee a m b2
-> Iteratee a m b3
-> Iteratee a m b4
-> Iteratee a m (b1, b2, b3, b4)
zip4 i1 i2 i3 i4 = do
(b1, (b2, b3, b4)) <- zip i1 (zip3 i2 i3 i4)
return (b1, b2, b3, b4)
zip5 :: Monad m
=> Iteratee a m b1
-> Iteratee a m b2
-> Iteratee a m b3
-> Iteratee a m b4
-> Iteratee a m b5
-> Iteratee a m (b1, b2, b3, b4, b5)
zip5 i1 i2 i3 i4 i5 = do
(b1, (b2, b3, b4, b5)) <- zip i1 (zip4 i2 i3 i4 i5)
return (b1, b2, b3, b4, b5)
zip6 :: Monad m
=> Iteratee a m b1
-> Iteratee a m b2
-> Iteratee a m b3
-> Iteratee a m b4
-> Iteratee a m b5
-> Iteratee a m b6
-> Iteratee a m (b1, b2, b3, b4, b5, b6)
zip6 i1 i2 i3 i4 i5 i6 = do
(b1, (b2, b3, b4, b5, b6)) <- zip i1 (zip5 i2 i3 i4 i5 i6)
return (b1, b2, b3, b4, b5, b6)
zip7 :: Monad m
=> Iteratee a m b1
-> Iteratee a m b2
-> Iteratee a m b3
-> Iteratee a m b4
-> Iteratee a m b5
-> Iteratee a m b6
-> Iteratee a m b7
-> Iteratee a m (b1, b2, b3, b4, b5, b6, b7)
zip7 i1 i2 i3 i4 i5 i6 i7 = do
(b1, (b2, b3, b4, b5, b6, b7)) <- zip i1 (zip6 i2 i3 i4 i5 i6 i7)
return (b1, b2, b3, b4, b5, b6, b7)
zipWith :: Monad m
=> (b1 -> b2 -> c)
-> Iteratee a m b1
-> Iteratee a m b2
-> Iteratee a m c
zipWith f i1 i2 = do
(b1, b2) <- zip i1 i2
return (f b1 b2)
zipWith3 :: Monad m
=> (b1 -> b2 -> b3 -> c)
-> Iteratee a m b1
-> Iteratee a m b2
-> Iteratee a m b3
-> Iteratee a m c
zipWith3 f i1 i2 i3 = do
(b1, b2, b3) <- zip3 i1 i2 i3
return (f b1 b2 b3)
zipWith4 :: Monad m
=> (b1 -> b2 -> b3 -> b4 -> c)
-> Iteratee a m b1
-> Iteratee a m b2
-> Iteratee a m b3
-> Iteratee a m b4
-> Iteratee a m c
zipWith4 f i1 i2 i3 i4 = do
(b1, b2, b3, b4) <- zip4 i1 i2 i3 i4
return (f b1 b2 b3 b4)
zipWith5 :: Monad m
=> (b1 -> b2 -> b3 -> b4 -> b5 -> c)
-> Iteratee a m b1
-> Iteratee a m b2
-> Iteratee a m b3
-> Iteratee a m b4
-> Iteratee a m b5
-> Iteratee a m c
zipWith5 f i1 i2 i3 i4 i5 = do
(b1, b2, b3, b4, b5) <- zip5 i1 i2 i3 i4 i5
return (f b1 b2 b3 b4 b5)
zipWith6 :: Monad m
=> (b1 -> b2 -> b3 -> b4 -> b5 -> b6 -> c)
-> Iteratee a m b1
-> Iteratee a m b2
-> Iteratee a m b3
-> Iteratee a m b4
-> Iteratee a m b5
-> Iteratee a m b6
-> Iteratee a m c
zipWith6 f i1 i2 i3 i4 i5 i6 = do
(b1, b2, b3, b4, b5, b6) <- zip6 i1 i2 i3 i4 i5 i6
return (f b1 b2 b3 b4 b5 b6)
zipWith7 :: Monad m
=> (b1 -> b2 -> b3 -> b4 -> b5 -> b6 -> b7 -> c)
-> Iteratee a m b1
-> Iteratee a m b2
-> Iteratee a m b3
-> Iteratee a m b4
-> Iteratee a m b5
-> Iteratee a m b6
-> Iteratee a m b7
-> Iteratee a m c
zipWith7 f i1 i2 i3 i4 i5 i6 i7 = do
(b1, b2, b3, b4, b5, b6, b7) <- zip7 i1 i2 i3 i4 i5 i6 i7
return (f b1 b2 b3 b4 b5 b6 b7)
head :: Monad m => Iteratee a m (Maybe a)
head = continue loop where
loop (Chunks []) = head
loop (Chunks (x:xs)) = yield (Just x) (Chunks xs)
loop EOF = yield Nothing EOF
head_ :: Monad m => Iteratee a m a
head_ = head >>= \x -> case x of
Just x' -> return x'
Nothing -> throwError (ErrorCall "head_: stream has ended")
drop :: Monad m => Integer -> Iteratee a m ()
drop n | n <= 0 = return ()
drop n = continue (loop n) where
loop n' (Chunks xs) = iter where
len = L.genericLength xs
iter = if len < n'
then drop (n' len)
else yield () (Chunks (L.genericDrop n' xs))
loop _ EOF = yield () EOF
dropWhile :: Monad m => (a -> Bool) -> Iteratee a m ()
dropWhile p = continue loop where
loop (Chunks xs) = case L.dropWhile p xs of
[] -> continue loop
xs' -> yield () (Chunks xs')
loop EOF = yield () EOF
require :: Monad m => Integer -> Iteratee a m ()
require n | n <= 0 = return ()
require n = continue (loop id n) where
len = L.genericLength
loop acc n' (Chunks xs)
| len xs < n' = continue (loop (acc . (xs ++)) (n' len xs))
| otherwise = yield () (Chunks (acc xs))
loop _ _ EOF = throwError (ErrorCall "require: Unexpected EOF")
isolate :: Monad m => Integer -> Enumeratee a a m b
isolate n step | n <= 0 = return step
isolate n (Continue k) = continue loop where
len = L.genericLength
loop (Chunks []) = continue loop
loop (Chunks xs)
| len xs <= n = k (Chunks xs) >>== isolate (n len xs)
| otherwise = let
(s1, s2) = L.genericSplitAt n xs
in k (Chunks s1) >>== (`yield` Chunks s2)
loop EOF = k EOF >>== (`yield` EOF)
isolate n step = drop n >> return step
isolateWhile :: Monad m => (a -> Bool) -> Enumeratee a a m b
isolateWhile p (Continue k) = continue loop where
loop (Chunks []) = continue loop
loop (Chunks xs) = case Prelude.span p xs of
(_, []) -> k (Chunks xs) >>== isolateWhile p
(s1, s2) -> k (Chunks s1) >>== (`yield` Chunks s2)
loop EOF = k EOF >>== (`yield` EOF)
isolateWhile p step = Data.Enumerator.List.dropWhile p >> return step
splitWhen :: Monad m => (a -> Bool) -> Enumeratee a [a] m b
splitWhen p = sequence $ do
as <- takeWhile (not . p)
drop 1
return as
unique :: (Ord a, Monad m) => Enumeratee a a m b
unique = concatMapAccum step Data.Set.empty where
step s x = if Data.Set.member x s
then (s, [])
else (Data.Set.insert x s, [x])