implemented encodeCSV and encodeRawCSV
This commit is contained in:
parent
3df133147f
commit
5c74085ada
|
@ -33,6 +33,8 @@ module Data.CSV.Sip (
|
|||
slurpRawLabelledCSV,
|
||||
-- * Conduits
|
||||
-- ** Encoding
|
||||
encodeCSV,
|
||||
encodeRawCSV,
|
||||
encodeRows,
|
||||
encodeRawRows,
|
||||
-- ** Decoding
|
||||
|
@ -57,7 +59,7 @@ import Control.Monad (unless)
|
|||
import Control.Monad.Trans.Class (lift)
|
||||
import Control.Monad.Trans.State (StateT, evalStateT, get, gets, modify)
|
||||
import qualified Data.ByteString as BS
|
||||
import Data.Conduit.List (consume)
|
||||
import Data.Conduit.List (consume, sourceList)
|
||||
import qualified Data.Map as M
|
||||
import Data.Maybe (fromMaybe)
|
||||
import qualified Data.Text as T
|
||||
|
@ -98,6 +100,22 @@ slurpRawLabelledCSV
|
|||
slurpRawLabelledCSV file = runConduit $
|
||||
sourceFile file .| decodeRawRows .| labelFields .|consume
|
||||
|
||||
-- | encode an entire CSV file
|
||||
encodeCSV
|
||||
:: Monad m
|
||||
=> [[T.Text]]
|
||||
-- ^ the data being encoded, organized into rows and fields
|
||||
-> ConduitT () BS.ByteString m ()
|
||||
encodeCSV csv = sourceList csv .| encodeRows
|
||||
|
||||
-- | encode an entire CSV file
|
||||
encodeRawCSV
|
||||
:: Monad m
|
||||
=> [[BS.ByteString]]
|
||||
-- ^ the data being encoded, organized into rows and fields
|
||||
-> ConduitT () BS.ByteString m ()
|
||||
encodeRawCSV csv = sourceList csv .| encodeRawRows
|
||||
|
||||
-- | encode a CSV stream row by row, each element in the list read
|
||||
-- represents a field, with the entire list representing a row
|
||||
encodeRows :: Monad m => ConduitT [T.Text] BS.ByteString m ()
|
||||
|
|
|
@ -33,6 +33,8 @@ import Data.CSV.Sip
|
|||
|
||||
spec :: Spec
|
||||
spec = describe "Data.CSV.Sip" $ do
|
||||
encodeCSVSpec
|
||||
encodeRawCSVSpec
|
||||
encodeRowsSpec
|
||||
encodeRawRowsSpec
|
||||
labelFieldsSpec
|
||||
|
@ -41,6 +43,42 @@ spec = describe "Data.CSV.Sip" $ do
|
|||
decodeUTF8Spec
|
||||
toBytesSpec
|
||||
|
||||
encodeCSVSpec :: Spec
|
||||
encodeCSVSpec = describe "encodeCSV" $ do
|
||||
result <- BS.concat <$> runConduit
|
||||
(encodeCSV input .| consume)
|
||||
it ("shouldBe " ++ show expected) $
|
||||
result `shouldBe` expected
|
||||
where
|
||||
|
||||
input =
|
||||
[ [ "foo", "a\"b" ]
|
||||
, [ "a\rb", "a\nb" ]
|
||||
]
|
||||
|
||||
expected = BS.concat
|
||||
[ "\"foo\",\"a\"\"b\"\r\n"
|
||||
, "\"a\rb\",\"a\nb\"\r\n"
|
||||
]
|
||||
|
||||
encodeRawCSVSpec :: Spec
|
||||
encodeRawCSVSpec = describe "encodeRawCSV" $ do
|
||||
result <- BS.concat <$> runConduit
|
||||
(encodeRawCSV input .| consume)
|
||||
it ("shouldBe " ++ show expected) $
|
||||
result `shouldBe` expected
|
||||
where
|
||||
|
||||
input =
|
||||
[ [ "foo", "a\"b" ]
|
||||
, [ "a\rb", "a\nb" ]
|
||||
]
|
||||
|
||||
expected = BS.concat
|
||||
[ "\"foo\",\"a\"\"b\"\r\n"
|
||||
, "\"a\rb\",\"a\nb\"\r\n"
|
||||
]
|
||||
|
||||
encodeRowsSpec :: Spec
|
||||
encodeRowsSpec = describe "encodeRows" $ do
|
||||
result <- BS.concat <$> runConduit
|
||||
|
|
Loading…
Reference in New Issue
Block a user