{-# LANGUAGE OverloadedStrings #-} module Boilerplate.ConfigParserTests where import qualified Data.Text as T import Test.HUnit (assertEqual) import qualified Data.Map.Strict as M import Data.Either.Extra (mapLeft) import Boilerplate.ConfigParser import Boilerplate.Types import Data.Text (Text) import Test.Tasty.Hspec import Text.Parsec (parse) shouldParseTo :: HasCallStack => Text -> Config -> Expectation shouldParseTo input expected = do let parseConfig = mapLeft show . parse configParser "test" parseConfig' = mapLeft show . parse configCommentParser "test" shouldParse p i = assertEqual (T.unpack i) (p i) (Right expected) parseConfig `shouldParse` input parseConfig' `shouldParse` ("{- BOILERPLATE " <> input <> " -}") parseConfig' `shouldParse` ("-- BOILERPLATE " <> input) spec_config :: Spec spec_config = do it "should parse a simple config" $ do "Foo FromJSON" `shouldParseTo` Config "Foo" ["FromJSON"] [] it "should parse the start and end" $ do "START" `shouldParseTo` ConfigStart "END" `shouldParseTo` ConfigEnd it "should parse multiple rules" $ do "Foo FromJSON, ToJSON" `shouldParseTo` Config "Foo" ["FromJSON", "ToJSON"] [] it "should parse fqn rule" $ do "Foo Data.Aeson.FromJSON, ToJSON" `shouldParseTo` Config "Foo" ["Data.Aeson.FromJSON", "ToJSON"] [] it "should parse a custom symbol option" $ do "Foo FromJSON foo=bar" `shouldParseTo` Config "Foo" ["FromJSON"] [("foo", Global "bar")] it "should parse multiple options" $ do "Foo FromJSON foo=bar baz=gaz" `shouldParseTo` Config "Foo" ["FromJSON"] [("foo", Global "bar"), ("baz", Global "gaz")] it "should parse a custom string option" $ do "Foo FromJSON foo = \"bar baz\"" `shouldParseTo` Config "Foo" ["FromJSON"] [("foo", Global "bar baz")] it "should parse a custom array option" $ do "Foo FromJSON foo = [bar, baz]" `shouldParseTo` Config "Foo" ["FromJSON"] [("foo", Indexed ["bar", "baz"])] it "should parse a custom object of strings object" $ do "Foo FromJSON foo={ bar: foo, baz : faa }" `shouldParseTo` Config "Foo" ["FromJSON"] [("foo", Named $ M.fromList [("bar", "foo"), ("baz", "faa")])] it "should parse a custom object of array object" $ do "Foo FromJSON foo={ bar: [f, o, o], baz : [f,a,a] }" `shouldParseTo` Config "Foo" ["FromJSON"] [("foo", NamedIndexed $ M.fromList [("bar", ["f", "o", "o"]), ("baz", ["f", "a", "a"])])] it "should parse the README example" $ do "Coord FromJSON, ToJSON\n field = [x, y]" `shouldParseTo` Config "Coord" ["FromJSON", "ToJSON"] [("field", Indexed ["x", "y"])]