From 63b97649a668987d0d86a69841b2213bf98c9641 Mon Sep 17 00:00:00 2001 From: Jonathan Lamothe Date: Tue, 19 Apr 2022 20:12:12 -0400 Subject: [PATCH] implemented toBytes --- src/Data/CSV/Slurp.hs | 11 ++++++++--- test/Data/CSV/SlurpSpec.hs | 10 ++++++++++ 2 files changed, 18 insertions(+), 3 deletions(-) diff --git a/src/Data/CSV/Slurp.hs b/src/Data/CSV/Slurp.hs index cd272f6..6d1a168 100644 --- a/src/Data/CSV/Slurp.hs +++ b/src/Data/CSV/Slurp.hs @@ -23,7 +23,7 @@ along with this program. If not, see . -} -{-# LANGUAGE OverloadedStrings #-} +{-# LANGUAGE LambdaCase, OverloadedStrings #-} module Data.CSV.Slurp ( decodeRows, @@ -32,7 +32,7 @@ module Data.CSV.Slurp ( toBytes, ) where -import Conduit (ConduitT, mapC, (.|)) +import Conduit (ConduitT, await, mapC, yield, (.|)) import Control.Monad.Trans.State (StateT, evalStateT) import qualified Data.ByteString as BS import Data.Maybe (fromMaybe) @@ -56,7 +56,12 @@ decodeUTF8 bs = case decodeUtf8' bs of -- | convert a stream to ByteStrings to a string of bytes toBytes :: Monad m => ConduitT BS.ByteString Word8 m () -toBytes = return () +toBytes = await >>= \case + Just bs -> do + let bytes = BS.unpack bs + mapM_ yield bytes + toBytes + Nothing -> return () data DecodeState = DecodeState { isQuoted :: Bool diff --git a/test/Data/CSV/SlurpSpec.hs b/test/Data/CSV/SlurpSpec.hs index d36d7da..53089e8 100644 --- a/test/Data/CSV/SlurpSpec.hs +++ b/test/Data/CSV/SlurpSpec.hs @@ -23,6 +23,7 @@ along with this program. If not, see . module Data.CSV.SlurpSpec (spec) where import Conduit (runConduit, (.|)) +import Data.Char (ord) import Data.Conduit.List (consume, sourceList) import Test.Hspec (Spec, context, describe, it, shouldBe, xit) @@ -33,6 +34,7 @@ spec = describe "Data.CSV.Slurp" $ do decodeRowsSpec decodeRawRowsSpec decodeUTF8Spec + toBytesSpec decodeRowsSpec :: Spec decodeRowsSpec = describe "decodeRows" $ mapM_ @@ -199,4 +201,12 @@ decodeUTF8Spec = describe "decodeUTF8" $ mapM_ , ( "blank", "", Just "" ) ] +toBytesSpec :: Spec +toBytesSpec = describe "toBytes" $ let + input = ["ab", "cd"] + expected = map (fromIntegral . ord) "abcd" + in it ("should be " ++ show expected) $ do + result <- runConduit $ sourceList input .| toBytes .| consume + result `shouldBe` expected + --jl