\section{Binary} :f Data/Enumerator/Binary.hs |Data.Enumerator.Binary module header| module Data.Enumerator.Binary ( |Data.Enumerator.Binary exports| ) where import Prelude hiding (head, drop, takeWhile) import Data.Enumerator hiding (head, drop) import qualified Data.ByteString as B |Data.Enumerator.Binary imports| : \subsection{IO} {\tt enumHandle} and {\tt enumFile} are rough analogues of {\tt hGetContents} and {\tt readFile} from the standard library, except they operate only in binary mode. Any exceptions thrown while reading or writing data are caught and reported using {\tt throwError}, so errors can be handled in pure iteratees. :d Data.Enumerator.Binary imports import Data.Enumerator.Util (tryStep) import qualified Control.Exception as Exc import Control.Monad.IO.Class (MonadIO) import qualified System.IO as IO import System.IO.Error (isEOFError) : :f Data/Enumerator/Binary.hs |apidoc Data.Enumerator.Binary.enumHandle| enumHandle :: MonadIO m => Integer -- ^ Buffer size -> IO.Handle -> Enumerator B.ByteString m b enumHandle bufferSize h = loop where loop (Continue k) = withBytes $ \bytes -> if B.null bytes then continue k else k (Chunks [bytes]) >>== loop loop step = returnI step intSize = fromInteger bufferSize withBytes = tryStep $ do hasInput <- Exc.catch (IO.hWaitForInput h (-1)) (\err -> if isEOFError err then return False else Exc.throwIO err) if hasInput then B.hGetNonBlocking h intSize else return B.empty : :f Data/Enumerator/Binary.hs |apidoc Data.Enumerator.Binary.enumFile| enumFile :: FilePath -> Enumerator B.ByteString IO b enumFile path = enum where withHandle = tryStep (IO.openBinaryFile path IO.ReadMode) enum step = withHandle $ \h -> do Iteratee $ Exc.finally (runIteratee (enumHandle 4096 h step)) (IO.hClose h) : :f Data/Enumerator/Binary.hs |apidoc Data.Enumerator.Binary.iterHandle| iterHandle :: MonadIO m => IO.Handle -> Iteratee B.ByteString m () iterHandle h = continue step where step EOF = yield () EOF step (Chunks []) = continue step step (Chunks bytes) = let put = mapM_ (B.hPut h) bytes in tryStep put (\_ -> continue step) : :d Data.Enumerator.Binary exports -- * Binary IO enumHandle , enumFile , iterHandle : \subsection{List analogues} :d Data.Enumerator.Binary imports import Data.Word (Word8) import qualified Data.ByteString.Lazy as BL : :f Data/Enumerator/Binary.hs toChunks :: BL.ByteString -> Stream B.ByteString toChunks = Chunks . BL.toChunks : :f Data/Enumerator/Binary.hs |apidoc Data.Enumerator.Binary.head| head :: Monad m => Iteratee B.ByteString m (Maybe Word8) head = continue loop where loop (Chunks xs) = case BL.uncons (BL.fromChunks xs) of Just (char, extra) -> yield (Just char) (toChunks extra) Nothing -> head loop EOF = yield Nothing EOF : :f Data/Enumerator/Binary.hs |apidoc Data.Enumerator.Binary.drop| drop :: Monad m => Integer -> Iteratee B.ByteString m () drop n | n <= 0 = return () drop n = continue (loop n) where loop n' (Chunks xs) = iter where lazy = BL.fromChunks xs len = toInteger (BL.length lazy) iter = if len < n' then drop (n' - len) else yield () (toChunks (BL.drop (fromInteger n') lazy)) loop _ EOF = yield () EOF : :f Data/Enumerator/Binary.hs |apidoc Data.Enumerator.Binary.dropWhile| dropWhile :: Monad m => (Word8 -> Bool) -> Iteratee B.ByteString m () dropWhile p = continue loop where loop (Chunks xs) = iter where lazy = BL.dropWhile p (BL.fromChunks xs) iter = if BL.null lazy then continue loop else yield () (toChunks lazy) loop EOF = yield () EOF : :f Data/Enumerator/Binary.hs |apidoc Data.Enumerator.Binary.take| take :: Monad m => Integer -> Iteratee B.ByteString m BL.ByteString take n | n <= 0 = return BL.empty take n = continue (loop id n) where loop acc n' (Chunks xs) = iter where lazy = BL.fromChunks xs len = toInteger (BL.length lazy) iter = if len < n' then continue (loop (acc . (BL.append lazy)) (n' - len)) else let (xs', extra) = BL.splitAt (fromInteger n') lazy in yield (acc xs') (toChunks extra) loop acc _ EOF = yield (acc BL.empty) EOF : :f Data/Enumerator/Binary.hs |apidoc Data.Enumerator.Binary.takeWhile| takeWhile :: Monad m => (Word8 -> Bool) -> Iteratee B.ByteString m BL.ByteString takeWhile p = continue (loop id) where loop acc (Chunks []) = continue (loop acc) loop acc (Chunks xs) = iter where lazy = BL.fromChunks xs (xs', extra) = BL.span p lazy iter = if BL.null extra then continue (loop (acc . (BL.append lazy))) else yield (acc xs') (toChunks extra) loop acc EOF = yield (acc BL.empty) EOF : :f Data/Enumerator/Binary.hs |apidoc Data.Enumerator.Binary.consume| consume :: Monad m => Iteratee B.ByteString m BL.ByteString consume = continue (loop id) where loop acc (Chunks []) = continue (loop acc) loop acc (Chunks xs) = iter where lazy = BL.fromChunks xs iter = continue (loop (acc . (BL.append lazy))) loop acc EOF = yield (acc BL.empty) EOF : :f Data/Enumerator/Binary.hs |apidoc Data.Enumerator.Binary.require| require :: Monad m => Integer -> Iteratee B.ByteString m () require n | n <= 0 = return () require n = continue (loop id n) where loop acc n' (Chunks xs) = iter where lazy = BL.fromChunks xs len = toInteger (BL.length lazy) iter = if len < n' then continue (loop (acc . (BL.append lazy)) (n' - len)) else yield () (toChunks (acc lazy)) loop _ _ EOF = throwError (Exc.ErrorCall "require: Unexpected EOF") : Same caveats as {\tt Data.Enumerator.List.isolate} :f Data/Enumerator/Binary.hs |apidoc Data.Enumerator.Binary.isolate| isolate :: Monad m => Integer -> Enumeratee B.ByteString B.ByteString m b isolate n step | n <= 0 = return step isolate n (Continue k) = continue loop where loop (Chunks []) = continue loop loop (Chunks xs) = iter where lazy = BL.fromChunks xs len = toInteger (BL.length lazy) iter = if len <= n then k (Chunks xs) >>== isolate (n - len) else let (s1, s2) = BL.splitAt (fromInteger n) lazy in k (toChunks s1) >>== (\step -> yield step (toChunks s2)) loop EOF = k EOF >>== (\step -> yield step EOF) isolate n step = drop n >> return step : :d Data.Enumerator.Binary exports -- * List analogues , Data.Enumerator.Binary.head , Data.Enumerator.Binary.drop , Data.Enumerator.Binary.dropWhile , Data.Enumerator.Binary.take , Data.Enumerator.Binary.takeWhile , Data.Enumerator.Binary.consume , require , isolate :