Skip to content

Commit

Permalink
Add a lazy bytestring enumerator to Data.Enumerator
Browse files Browse the repository at this point in the history
  • Loading branch information
Gregory Collins committed Oct 23, 2009
1 parent 652c232 commit e2fa164
Showing 1 changed file with 16 additions and 1 deletion.
17 changes: 16 additions & 1 deletion Data/Enumerator.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,12 @@
{-# LANGUAGE Rank2Types #-}

module Data.Enumerator
( -- Enumerators
( EnumeratorM,
IterateeM,

-- Enumerators
bytesEnum,
lazyBytesEnum,
chunkEnum,
partialSocketEnum,
socketEnum,
Expand All @@ -13,6 +17,7 @@ module Data.Enumerator

import Control.Monad (liftM)
import qualified Data.ByteString as S
import qualified Data.ByteString.Lazy as L
import qualified Data.ByteString.Char8 as C (unpack)
import Data.Word (Word8)
import Network.Socket (Socket)
Expand All @@ -38,6 +43,16 @@ bytesEnum bs f seed =
Right seed'' -> bytesEnum (S.drop blockSize bs) f seed''


-- | Enumerates a lazy 'ByteString'.
lazyBytesEnum :: Monad m => L.ByteString -> EnumeratorM m
lazyBytesEnum bs f seed = go (L.toChunks bs) f seed
where
go [] _ sd = return sd
go (x:xs) g sd = do
sd' <- bytesEnum x g sd
go xs g sd'


nl :: Word8
nl = 10

Expand Down

0 comments on commit e2fa164

Please sign in to comment.