diff --git a/csv-slurp.cabal b/csv-slurp.cabal
index 9e0d86c..4a556f3 100644
--- a/csv-slurp.cabal
+++ b/csv-slurp.cabal
@@ -29,6 +29,9 @@ library
ghc-options: -Wall
build-depends:
base >=4.7 && <5
+ , bytestring
+ , conduit >=1.3.4.2 && <1.4
+ , text
default-language: Haskell2010
autogen-modules: Paths_csv_slurp
@@ -43,7 +46,10 @@ test-suite csv-slurp-test
ghc-options: -Wall -threaded -rtsopts -with-rtsopts=-N
build-depends:
base >=4.7 && <5
+ , bytestring
+ , conduit >=1.3.4.2 && <1.4
, csv-slurp
, hspec >=2.8.5 && <2.9
+ , text
default-language: Haskell2010
autogen-modules: Paths_csv_slurp
diff --git a/package.yaml b/package.yaml
index 1dc1f2c..3f71495 100644
--- a/package.yaml
+++ b/package.yaml
@@ -23,6 +23,9 @@ ghc-options:
dependencies:
- base >= 4.7 && < 5
+- bytestring
+- conduit >= 1.3.4.2 && < 1.4
+- text
library:
source-dirs: src
diff --git a/src/Data/CSV/Slurp.hs b/src/Data/CSV/Slurp.hs
index 15a618b..8803a34 100644
--- a/src/Data/CSV/Slurp.hs
+++ b/src/Data/CSV/Slurp.hs
@@ -23,6 +23,29 @@ along with this program. If not, see .
-}
-module Data.CSV.Slurp where
+{-# LANGUAGE OverloadedStrings #-}
+
+module Data.CSV.Slurp (
+ decodeRows,
+ decodeRawRows,
+ decodeUTF8,
+) where
+
+import Conduit (ConduitT, mapC, (.|))
+import qualified Data.ByteString as BS
+import Data.Maybe (fromMaybe)
+import qualified Data.Text as T
+
+-- | decode the rows from a stream of ByteStrings
+decodeRows :: Monad m => ConduitT BS.ByteString [T.Text] m ()
+decodeRows = decodeRawRows .| mapC (map $ fromMaybe "" . decodeUTF8)
+
+-- | decode the rows returning raw ByteStrings instead of text
+decodeRawRows :: Monad m => ConduitT BS.ByteString [BS.ByteString] m ()
+decodeRawRows = return ()
+
+-- | decode a raw ByteString into Text (if possible)
+decodeUTF8 :: BS.ByteString -> Maybe T.Text
+decodeUTF8 = const Nothing
--jl
diff --git a/test/Data/CSV/SlurpSpec.hs b/test/Data/CSV/SlurpSpec.hs
index e7aef42..1fdc4fd 100644
--- a/test/Data/CSV/SlurpSpec.hs
+++ b/test/Data/CSV/SlurpSpec.hs
@@ -18,11 +18,45 @@ along with this program. If not, see .
-}
+{-# LANGUAGE OverloadedStrings #-}
+
module Data.CSV.SlurpSpec (spec) where
-import Test.Hspec (Spec, describe)
+import Conduit (runConduit, (.|))
+import Data.Conduit.List (consume, sourceList)
+import Test.Hspec (Spec, context, describe, shouldBe, xit)
+
+import Data.CSV.Slurp
spec :: Spec
-spec = describe "Data.CSV.Slurp" $ return ()
+spec = describe "Data.CSV.Slurp"
+ decodeRowsSpec
+
+decodeRowsSpec :: Spec
+decodeRowsSpec = describe "decodeRows" $ mapM_
+ ( \(label, input, expected) -> context label $ do
+ result <- runConduit $ sourceList input .| decodeRows .| consume
+ let
+ expLen = length expected
+ resLen = length result
+ xit ("should have " ++ show expLen ++ " rows") $
+ resLen `shouldBe` expLen
+ mapM_
+ ( \(n, expected', result') -> context ("row " ++ show n) $
+ xit ("should be " ++ show expected') $
+ result' `shouldBe` expected'
+ ) $ zip3 [(0::Int)..] expected result
+ )
+
+ -- label, input, expected
+ [ ( "valid", validIn, validRes )
+ , ( "invalid", invalidIn, [] )
+ , ( "empty", [], [] )
+ ]
+
+ where
+ validIn = ["foo,bar\r\n", "baz,quuux\r\n"]
+ invalidIn = ["\"a"]
+ validRes = [["foo", "bar"], ["baz", "quux"]]
--jl
diff --git a/test/Spec.hs b/test/Spec.hs
index e9dacd8..f38586a 100644
--- a/test/Spec.hs
+++ b/test/Spec.hs
@@ -25,6 +25,6 @@ import Test.Hspec (hspec)
import qualified Data.CSV.SlurpSpec as Slurp
main :: IO ()
-main = hspec $ Slurp.spec
+main = hspec Slurp.spec
--jl