csv-sip/test/Data/CSV/SipSpec.hs

353 lines
8.3 KiB
Haskell

{-
csv-sip
Copyright (C) Jonathan Lamothe <jonathan@jlamothe.net>
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation, either version 3 of the License, or (at
your option) any later version.
This program is distributed in the hope that it will be useful, but
WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
General Public License for more details.
You should have received a copy of the GNU General Public License
along with this program. If not, see <https://www.gnu.org/licenses/>.
-}
{-# LANGUAGE OverloadedStrings #-}
module Data.CSV.SipSpec (spec) where
import Conduit (runConduit, (.|))
import qualified Data.ByteString as BS
import Data.Char (ord)
import Data.Conduit.List (consume, sourceList)
import qualified Data.Map as M
import Test.Hspec (Spec, context, describe, it, shouldBe)
import Data.CSV.Sip
spec :: Spec
spec = describe "Data.CSV.Sip" $ do
encodeCSVSpec
encodeRawCSVSpec
encodeRowsSpec
encodeRawRowsSpec
labelFieldsSpec
decodeRowsSpec
decodeRawRowsSpec
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
(sourceList input .| encodeRows .| 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"
]
encodeRawRowsSpec :: Spec
encodeRawRowsSpec = describe "encodeRawRows" $ do
result <- BS.concat <$> runConduit
(sourceList input .| encodeRawRows .| consume)
it ("should be " ++ 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"
]
labelFieldsSpec :: Spec
labelFieldsSpec = describe "labelFields" $ mapM_
( \(label, input, expected) -> context label $ do
result <- runConduit $ sourceList input .| labelFields .| consume
let
expLen = length expected
resLen = length result
it ("should have " ++ show expLen ++ " rows") $
resLen `shouldBe` expLen
mapM_
( \(n, result', expected') -> context ("row " ++ show n) $
it ("should be " ++ show expected') $
result' `shouldBe` expected'
) $ zip3 [(0::Int)..] result expected
)
-- label, input, expected
[ ( "empty", [], [] )
, ( "no body", [headers], [] )
, ( "with body", withBodyIn, withBodyRes )
, ( "mixed cols", mixedColsIn, mixedColsRes )
]
where
headers = ["foo", "bar", "baz"] :: [String]
withBodyIn = headers :
[ ["a", "b", "c"]
, ["d", "e", "f"]
] :: [[String]]
mixedColsIn =
[ ["foo", "bar"]
, ["a"]
, ["b", "c"]
, ["d", "e", "f"]
] :: [[String]]
withBodyRes = map M.fromList
[ [("foo", "a"), ("bar", "b"), ("baz", "c")]
, [("foo", "d"), ("bar", "e"), ("baz", "f")]
] :: [M.Map String String]
mixedColsRes = map M.fromList
[ [("foo", "a")]
, [("foo", "b"), ("bar", "c")]
, [("foo", "d"), ("bar", "e")]
] :: [M.Map String String]
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
it ("should have " ++ show expLen ++ " rows") $
resLen `shouldBe` expLen
mapM_
( \(n, expected', result') -> context ("row " ++ show n) $
it ("should be " ++ show expected') $
result' `shouldBe` expected'
) $ zip3 [(0::Int)..] expected result
)
-- label, input, expected
[ ( "valid", validIn, validRes )
, ( "invalid", invalidIn, invalidRes )
, ( "empty", [], [] )
]
where
validIn = ["foo,bar\r\n", "baz,quux\r\n"]
invalidIn = ["\"a"]
validRes = [["foo", "bar"], ["baz", "quux"]]
invalidRes = [[""]]
decodeRawRowsSpec :: Spec
decodeRawRowsSpec = describe "decodeRawRows" $ mapM_
( \(label, input, expected) -> context label $ do
result <- runConduit $ sourceList input .| decodeRawRows .| consume
let
expLen = length expected
resLen = length result
it ("should have " ++ show expLen ++ " rows") $
resLen `shouldBe` expLen
mapM_
( \(n, expected', result') -> context ("row " ++ show n) $
it ("should be " ++ show result') $
result' `shouldBe` expected'
) $ zip3 [(0::Int)..] expected result
)
-- label, input, expected
[ ( "unquoted", unquotedIn, normalRes )
, ( "quoted", quotedIn, normalRes )
, ( "mixed", mixedIn, normalRes )
, ( "CR only", crOnlyIn, normalRes )
, ( "LF only", lfOnlyIn, normalRes )
, ( "has quote", quoteIn, quoteRes )
, ( "has CR", crIn, crRes )
, ( "has LF", lfIn, lfRes )
, ( "has CRLF", crlfIn, crlfRes )
, ( "odd chunk", oddChunkIn, normalRes )
, ( "no newline", noNewlineIn, normalRes )
, ( "malformed", malformedIn, malformedRes )
, ( "blank end", blankEndIn, blankEndRes )
]
where
unquotedIn =
[ "foo,bar\r\n"
, "baz,quux\r\n"
]
quotedIn =
[ "\"foo\",\"bar\"\r\n"
, "\"baz\",\"quux\"\r\n"
]
mixedIn =
[ "\"foo\",bar\r\n"
, "baz,\"quux\"\r\n"
]
crOnlyIn =
[ "foo,bar\r"
, "baz,quux\r"
]
lfOnlyIn =
[ "foo,bar\n"
, "baz,quux\n"
]
quoteIn =
[ "\"a\"\"b\",bar\r\n"
, "baz,quux\r\n"
]
crIn =
[ "\"a\rb\",bar\r\n"
, "baz,quux\r\n"
]
lfIn =
[ "\"a\nb\",bar\r\n"
, "baz,quux\r\n"
]
crlfIn =
[ "\"a\r\nb\",bar\r\n"
, "baz,quux\r\n"
]
oddChunkIn =
[ "foo,"
, "bar\r\nbaz,"
, "quux\r\n"
]
noNewlineIn =
[ "foo,bar\r\n"
, "baz,quux"
]
malformedIn =
[ "a\"b,bar\r\n"
, "baz,quux\r\n"
]
blankEndIn =
[ "foo,bar,\r\n"
, "baz,quux\r\n"
]
normalRes =
[ ["foo", "bar"]
, ["baz", "quux"]
]
quoteRes =
[ ["a\"b", "bar"]
, ["baz", "quux"]
]
crRes =
[ ["a\rb", "bar"]
, ["baz", "quux"]
]
lfRes =
[ ["a\nb", "bar"]
, ["baz", "quux"]
]
crlfRes =
[ ["a\r\nb", "bar"]
, ["baz", "quux"]
]
malformedRes =
[ ["", "bar"]
, ["baz", "quux"]
]
blankEndRes =
[ ["foo", "bar", ""]
, ["baz", "quux"]
]
decodeUTF8Spec :: Spec
decodeUTF8Spec = describe "decodeUTF8" $ mapM_
( \(label, input, expected) -> context label $
it ("should be " ++ show expected) $
decodeUTF8 input `shouldBe` expected
)
-- label, input, expected
[ ( "plain ASCII", "hello", Just "hello" )
, ( "valid UTF8", "\xc3\xa9", Just "é" )
, ( "invalid UTF8", "\xff", Nothing )
, ( "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