implemented toBytes

This commit is contained in:
Jonathan Lamothe 2022-04-19 20:12:12 -04:00
parent 67e85f0a78
commit 63b97649a6
2 changed files with 18 additions and 3 deletions

View File

@ -23,7 +23,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
-} -}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE LambdaCase, OverloadedStrings #-}
module Data.CSV.Slurp ( module Data.CSV.Slurp (
decodeRows, decodeRows,
@ -32,7 +32,7 @@ module Data.CSV.Slurp (
toBytes, toBytes,
) where ) where
import Conduit (ConduitT, mapC, (.|)) import Conduit (ConduitT, await, mapC, yield, (.|))
import Control.Monad.Trans.State (StateT, evalStateT) import Control.Monad.Trans.State (StateT, evalStateT)
import qualified Data.ByteString as BS import qualified Data.ByteString as BS
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
@ -56,7 +56,12 @@ decodeUTF8 bs = case decodeUtf8' bs of
-- | convert a stream to ByteStrings to a string of bytes -- | convert a stream to ByteStrings to a string of bytes
toBytes :: Monad m => ConduitT BS.ByteString Word8 m () 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 data DecodeState = DecodeState
{ isQuoted :: Bool { isQuoted :: Bool

View File

@ -23,6 +23,7 @@ along with this program. If not, see <https://www.gnu.org/licenses/>.
module Data.CSV.SlurpSpec (spec) where module Data.CSV.SlurpSpec (spec) where
import Conduit (runConduit, (.|)) import Conduit (runConduit, (.|))
import Data.Char (ord)
import Data.Conduit.List (consume, sourceList) import Data.Conduit.List (consume, sourceList)
import Test.Hspec (Spec, context, describe, it, shouldBe, xit) import Test.Hspec (Spec, context, describe, it, shouldBe, xit)
@ -33,6 +34,7 @@ spec = describe "Data.CSV.Slurp" $ do
decodeRowsSpec decodeRowsSpec
decodeRawRowsSpec decodeRawRowsSpec
decodeUTF8Spec decodeUTF8Spec
toBytesSpec
decodeRowsSpec :: Spec decodeRowsSpec :: Spec
decodeRowsSpec = describe "decodeRows" $ mapM_ decodeRowsSpec = describe "decodeRows" $ mapM_
@ -199,4 +201,12 @@ decodeUTF8Spec = describe "decodeUTF8" $ mapM_
, ( "blank", "", Just "" ) , ( "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 --jl