\section{Lists} :f Data/Enumerator/List.hs |Data.Enumerator.List module header| module Data.Enumerator.List ( |Data.Enumerator.List exports| ) where import Data.Enumerator hiding (consume, head, peek, drop, dropWhile) import Control.Exception (ErrorCall(..)) import Prelude hiding (head, drop, dropWhile, take, takeWhile) import qualified Data.List as L : :f Data/Enumerator/List.hs |apidoc Data.Enumerator.List.head| 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 : :f Data/Enumerator/List.hs |apidoc Data.Enumerator.List.drop| 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 : :f Data/Enumerator/List.hs |apidoc Data.Enumerator.List.dropWhile| 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 : :f Data/Enumerator/List.hs |apidoc Data.Enumerator.List.take| 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 : :f Data/Enumerator/List.hs |apidoc Data.Enumerator.List.takeWhile| 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 : :# NOTE: peeking properly is currently impossible with the current design of :# 'Stream'. Once it's updated to support EOF with "final data", peek can be :# re-enabled :# :# :d Data/Enumerator/List.hs :# |apidoc Data.Enumerator.List.peek| :# peek :: Monad m => Integer -> Iteratee a m [a] :# peek n | n <= 0 = return [] :# peek 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' = L.genericTake n' xs :# in yield (acc xs') (Chunks (acc xs)) :# loop acc _ EOF = yield (acc []) EOF :# : :# :# :d Data/Enumerator/List.hs (disabled) :# |apidoc Data.Enumerator.List.peekWhile| :# peekWhile :: Monad m => (a -> Bool) -> Iteratee a m [a] :# peekWhile 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', _) -> yield (acc xs') (Chunks (acc xs)) :# loop acc EOF = yield (acc []) EOF :# : :f Data/Enumerator/List.hs |apidoc Data.Enumerator.List.consume| 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 : :f Data/Enumerator/List.hs |apidoc Data.Enumerator.List.require| 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") : Note: {\tt isolate} has some odd behavior regarding extra input in the inner iteratee. Depending on how large the chunks are, extra input might be returned in the {\tt Step}, or dropped. This doesn't matter if {\tt joinI} is used, but might if a user is poking around inside the {\tt Step}. Eventually, enumeratees will be modified to avoid exposing its internal iteratee state. :f Data/Enumerator/List.hs |apidoc Data.Enumerator.List.isolate| 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) >>== (\step -> yield step (Chunks s2)) loop EOF = k EOF >>== (\step -> yield step EOF) isolate n step = drop n >> return step : :d Data.Enumerator.List exports head , drop , dropWhile , take , takeWhile , consume , require , isolate :