module Lentil.ExportSpec where import Test.Hspec import Lentil.Types import Lentil.Export is :: [Issue] is = [Issue "./file" 1 "da" [Tag "a", Tag "c"], Issue "file" 2 "db" [Tag "e:f"]] csv :: String csv = "\"Filepath\",\"Row\",\"Description\",\"Tags\"\n\ \\"file\",\"1\",\"da\",\"a c\"\n\ \\"file\",\"2\",\"db\",\"e:f\"" cmp :: String cmp = unlines $ ["file:1:", " da [a] [c]", "", "file:2:", " db [e:f]"] main :: IO () main = hspec spec spec :: Spec spec = do describe "tags2String" $ do it "converts tags to plain string, intercalated by ' '" $ tags2String [Tag "a", Tag "b"] `shouldBe` "a b" describe "tags2StringPretty" $ do it "converts tags to string, with open/close delimiters" $ tags2StringPretty [Tag "a", Tag "b"] `shouldBe` "[a] [b]" describe "issues2CSV" $ do it "exports issues to CSV" $ issues2CSV is `shouldBe` csv describe "issues2Compiler" $ do it "exports issues to compiler-like output format" $ issues2Compiler is `shouldBe` cmp