File: Test.hs

package info (click to toggle)
haskell-csv-conduit 0.7.3.0-1
  • links: PTS, VCS
  • area: main
  • in suites: bookworm
  • size: 156 kB
  • sloc: haskell: 1,307; makefile: 3
file content (116 lines) | stat: -rw-r--r-- 3,322 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}

module Main where

import qualified Conduit as C
import Control.Exception
import qualified Data.ByteString.Char8 as B
import Data.CSV.Conduit
import Data.CSV.Conduit.Conversion
import qualified Data.Map as Map
import qualified Data.Map.Ordered as OMap
import Data.Monoid as M
import Data.Text
import qualified Data.Vector as V
import System.Directory
import Test.Framework (Test, defaultMain, testGroup)
import Test.Framework.Providers.HUnit
import Test.HUnit (assertFailure, (@=?), (@?=))

main :: IO ()
main = defaultMain tests

tests :: [Test]
tests =
  [ testGroup "Basic Ops" baseTests,
    testGroup "decodeCSV" decodeCSVTests
  ]

baseTests :: [Test]
baseTests =
  [ testCase "mapping with id works" test_identityMap,
    testCase "simple parsing works" test_simpleParse,
    testCase "OrderedMap" test_orderedMap
  ]

decodeCSVTests :: [Test]
decodeCSVTests =
  [ testCase "parses a CSV" $ do
      let efoos = decodeCSV defCSVSettings ("Foo\nfoo" :: B.ByteString)
      case efoos :: Either SomeException (V.Vector (Named Foo)) of
        Left e -> assertFailure (show e)
        Right foos -> V.fromList [Named Foo] @=? foos,
    testCase "eats parse errors, evidently" $ do
      let efoos = decodeCSV defCSVSettings ("Foo\nbad" :: B.ByteString)
      case efoos :: Either SomeException (V.Vector (Named Foo)) of
        Left e -> assertFailure (show e)
        Right foos -> M.mempty @=? foos
  ]

data Foo = Foo deriving (Show, Eq)

instance FromNamedRecord Foo where
  parseNamedRecord nr = do
    s <- nr .: "Foo"
    case s of
      "foo" -> pure Foo
      _ -> fail ("Expected \"foo\" but got " <> B.unpack s)

instance ToNamedRecord Foo where
  toNamedRecord Foo = namedRecord ["Foo" .= ("foo" :: B.ByteString)]

test_identityMap :: IO ()
test_identityMap = do
  _ <- runResourceT $ mapCSVFile csvSettings f testFile2 outFile
  f1 <- readFile testFile2
  f2 <- readFile outFile
  f1 @=? f2
  removeFile outFile
  where
    outFile = "test/testOut.csv"
    f :: Row Text -> [Row Text]
    f = return

test_simpleParse :: IO ()
test_simpleParse = do
  (d :: V.Vector (MapRow B.ByteString)) <- readCSVFile csvSettings testFile1
  V.mapM_ assertRow d
  where
    assertRow r = v3 @=? (v1 + v2)
      where
        v1 = readBS $ r Map.! "Col2"
        v2 = readBS $ r Map.! "Col3"
        v3 = readBS $ r Map.! "Sum"

test_orderedMap :: IO ()
test_orderedMap = do
  unorderedRes <-
    C.runConduit $
      C.yieldMany [unorderedRow]
        C..| writeHeaders defCSVSettings
        C..| C.foldC
  unorderedRes @?= ("\"a\",\"b\"\n\"aval\",\"bval\"\n" :: B.ByteString)
  orderedRes <-
    C.runConduit $
      C.yieldMany [orderedRow]
        C..| writeHeadersOrdered defCSVSettings
        C..| C.foldC
  orderedRes @?= ("\"b\",\"a\"\n\"bval\",\"aval\"\n" :: B.ByteString)
  where
    orderedRow :: OrderedMapRow Text
    orderedRow = OMap.fromList pairs
    unorderedRow :: MapRow Text
    unorderedRow = Map.fromList pairs
    pairs = [("b", "bval"), ("a", "aval")]

csvSettings :: CSVSettings
csvSettings = defCSVSettings {csvQuoteChar = Just '`'}

testFile1, testFile2 :: FilePath
testFile1 = "test/test.csv"
testFile2 = "test/test.csv"

readBS :: B.ByteString -> Int
readBS = read . B.unpack