Skip to content

Commit

Permalink
Fix #102 for foldr
Browse files Browse the repository at this point in the history
This fixes a defect in the Foldable implementation for foldr, which -
according to the documentation - should skip records which failed to
convert.
  • Loading branch information
Roman Joost authored and hvr committed Nov 7, 2015
1 parent 48e8370 commit 6c9127e
Show file tree
Hide file tree
Showing 2 changed files with 18 additions and 0 deletions.
1 change: 1 addition & 0 deletions Data/Csv/Streaming.hs
Expand Up @@ -106,6 +106,7 @@ foldrRecords :: (a -> b -> b) -> b -> Records a -> b
foldrRecords f = go
where
go z (Cons (Right x) rs) = f x (go z rs)
go z (Cons (Left _) rs) = go z rs
go z _ = z
{-# INLINE foldrRecords #-}

Expand Down
17 changes: 17 additions & 0 deletions tests/UnitTests.hs
Expand Up @@ -13,6 +13,7 @@ import Data.Int
import qualified Data.Text as T
import qualified Data.Text.Lazy as LT
import qualified Data.Vector as V
import qualified Data.Foldable as F
import Data.Word
import Test.HUnit
import Test.Framework as TF
Expand Down Expand Up @@ -361,6 +362,21 @@ customOptionsTests =
[ testProperty "customDelim" customDelim
]

------------------------------------------------------------------------
-- Instance tests

instanceTests :: [TF.Test]
instanceTests =
[
testGroup "Records instances"
[ testCase "foldr Foldable" (expected @=? F.foldr (:) [] input)
]
]
where
input = S.Cons (Left "empty") (
S.Cons (Right ("a" :: String)) (S.Nil Nothing BL8.empty))
expected = ["a" :: String]

------------------------------------------------------------------------
-- Test harness

Expand All @@ -369,6 +385,7 @@ allTests = [ testGroup "positional" positionalTests
, testGroup "named" nameBasedTests
, testGroup "conversion" conversionTests
, testGroup "custom-options" customOptionsTests
, testGroup "instances" instanceTests
]

main :: IO ()
Expand Down

0 comments on commit 6c9127e

Please sign in to comment.