Skip to content

Commit

Permalink
Merge pull request #296 from tomsmalley/master
Browse files Browse the repository at this point in the history
Add function Data.Conduit.List.chunksOf (issue #295)
  • Loading branch information
snoyberg committed Feb 8, 2017
2 parents be80321 + 942fd2c commit e2894d3
Show file tree
Hide file tree
Showing 4 changed files with 34 additions and 1 deletion.
4 changes: 4 additions & 0 deletions conduit/ChangeLog.md
@@ -1,3 +1,7 @@
## 1.2.9

* `chunksOf` [#296](https://github.com/snoyberg/conduit/pull/296)

## 1.2.8

* Implement
Expand Down
21 changes: 21 additions & 0 deletions conduit/Data/Conduit/List.hs
Expand Up @@ -50,6 +50,7 @@ module Data.Conduit.List
, scanl
, scan
, mapAccum
, chunksOf
, groupBy
, groupOn1
, isolate
Expand Down Expand Up @@ -80,6 +81,7 @@ import Prelude
, Enum, Eq
, maybe
, (<=)
, (>)
)
import Data.Monoid (Monoid, mempty, mappend)
import qualified Data.Foldable as F
Expand Down Expand Up @@ -631,6 +633,25 @@ consumeC =
{-# INLINE consumeC #-}
STREAMING0(consume, consumeC, consumeS)

-- | Group a stream into chunks of a given size. The last chunk may contain
-- fewer than n elements.
--
-- Subject to fusion
--
-- Since 1.2.9
chunksOf :: Monad m => Int -> Conduit a m [a]
chunksOf n =
start
where
start = await >>= maybe (return ()) (\x -> loop n (x:))

loop !count rest =
await >>= maybe (yield (rest [])) go
where
go y
| count > 1 = loop (count - 1) (rest . (y:))
| otherwise = yield (rest []) >> loop n (y:)

-- | Grouping input according to an equality function.
--
-- Subject to fusion
Expand Down
3 changes: 2 additions & 1 deletion conduit/conduit.cabal
@@ -1,5 +1,5 @@
Name: conduit
Version: 1.2.8
Version: 1.2.9
Synopsis: Streaming data processing library.
description:
`conduit` is a solution to the streaming data problem, allowing for production,
Expand Down Expand Up @@ -64,6 +64,7 @@ test-suite test
, containers
, exceptions >= 0.6
, safe
, split >= 0.2.0.0
if !impl(ghc>=7.9)
build-depends: void
ghc-options: -Wall
Expand Down
7 changes: 7 additions & 0 deletions conduit/test/main.hs
Expand Up @@ -16,6 +16,7 @@ import Control.Exception (throw)
import Control.Monad.Trans.Resource as C (runResourceT)
import Data.Maybe (fromMaybe,catMaybes,fromJust)
import qualified Data.List as DL
import qualified Data.List.Split as DLS (chunksOf)
import Control.Monad.ST (runST)
import Data.Monoid
import qualified Data.IORef as I
Expand Down Expand Up @@ -235,6 +236,12 @@ main = hspec $ do
C.=$ CL.fold (+) 0
x `shouldBe` 2 * sum [1..10 :: Int]

prop "chunksOf" $ equivToList
(DLS.chunksOf 5 :: [Int]->[[Int]]) (CL.chunksOf 5)

prop "chunksOf (negative)" $ equivToList
(map (:[]) :: [Int]->[[Int]]) (CL.chunksOf (-5))

it "groupBy" $ do
let input = [1::Int, 1, 2, 3, 3, 3, 4, 5, 5]
x <- runResourceT $ CL.sourceList input
Expand Down

0 comments on commit e2894d3

Please sign in to comment.