Skip to content

Commit 1f34489

Browse files
authored
Merge pull request #26 from haskell-works/bytestring-support
Add bytestring support
2 parents 163b0ad + 0c59ef3 commit 1f34489

File tree

2 files changed

+41
-0
lines changed

2 files changed

+41
-0
lines changed
Lines changed: 29 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,29 @@
1+
{-# LANGUAGE ScopedTypeVariables #-}
2+
3+
module HaskellWorks.Data.Streams.ByteString
4+
( streamChunks
5+
, stream
6+
) where
7+
8+
import Data.Word
9+
import HaskellWorks.Data.Streams.Size
10+
import HaskellWorks.Data.Streams.Stream (Step (..), Stream (..))
11+
import Prelude hiding (foldl, map, sum, zipWith)
12+
13+
import qualified Data.ByteString as BS
14+
15+
streamChunks :: [BS.ByteString] -> Stream Word8
16+
streamChunks ass = Stream step (ass, 0) Unknown
17+
where step (bss, i) = case bss of
18+
cs:css -> if i < BS.length cs
19+
then Yield (BS.index cs i) (bss, i + 1)
20+
else Skip (css, 0)
21+
[] -> Done
22+
{-# INLINE [1] streamChunks #-}
23+
24+
stream :: BS.ByteString -> Stream Word8
25+
stream bs = Stream step (bs, 0) Unknown
26+
where step (cs, i) = if i < BS.length cs
27+
then Yield (BS.index cs i) (cs, i + 1)
28+
else Done
29+
{-# INLINE [1] stream #-}
Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,12 @@
1+
module HaskellWorks.Data.Streams.ByteString.Lazy
2+
( stream
3+
) where
4+
5+
import Data.Word
6+
import HaskellWorks.Data.Streams.Stream (Stream (..))
7+
8+
import qualified Data.ByteString.Lazy as LBS
9+
import qualified HaskellWorks.Data.Streams.ByteString as BS
10+
11+
stream :: LBS.ByteString -> Stream Word8
12+
stream = BS.streamChunks . LBS.toChunks

0 commit comments

Comments
 (0)