forked from OSS/graphql
		
	Replace tasty and HUnit with Hspec
This commit is contained in:
		
							
								
								
									
										99
									
								
								tests/Language/GraphQL/LexerSpec.hs
									
									
									
									
									
										Normal file
									
								
							
							
						
						
									
										99
									
								
								tests/Language/GraphQL/LexerSpec.hs
									
									
									
									
									
										Normal file
									
								
							| @@ -0,0 +1,99 @@ | ||||
| {-# LANGUAGE ExplicitForAll #-} | ||||
| {-# LANGUAGE OverloadedStrings #-} | ||||
| {-# LANGUAGE QuasiQuotes #-} | ||||
| module Language.GraphQL.LexerSpec | ||||
|     ( spec | ||||
|     ) where | ||||
|  | ||||
| import Language.GraphQL.Lexer | ||||
| import qualified Data.Text as T | ||||
| import Data.Void (Void) | ||||
| import Test.Hspec ( Spec | ||||
|                   , context | ||||
|                   , describe | ||||
|                   , it | ||||
|                   , shouldBe | ||||
|                   ) | ||||
| import Text.Megaparsec ( ParseErrorBundle | ||||
|                        , parse | ||||
|                        ) | ||||
| import Text.RawString.QQ (r) | ||||
|  | ||||
| spec :: Spec | ||||
| spec = describe "Lexer" $ do | ||||
|     context "Reference tests" $ do | ||||
|         it "lexes strings" $ do | ||||
|             runParser string [r|"simple"|] `shouldBe` Right "simple" | ||||
|             runParser string [r|" white space "|] `shouldBe` Right " white space " | ||||
|             runParser string [r|"quote \""|] `shouldBe` Right [r|quote "|] | ||||
|             runParser string [r|"escaped \n"|] `shouldBe` Right "escaped \n" | ||||
|             runParser string [r|"slashes \\ \/"|] `shouldBe` Right [r|slashes \ /|] | ||||
|             runParser string [r|"unicode \u1234\u5678\u90AB\uCDEF"|] | ||||
|                 `shouldBe` Right "unicode ሴ噸邫췯" | ||||
|  | ||||
|         it "lexes block string" $ do | ||||
|             runParser blockString [r|"""simple"""|] `shouldBe` Right "simple" | ||||
|             runParser blockString [r|""" white space """|] | ||||
|                 `shouldBe` Right " white space " | ||||
|             runParser blockString [r|"""contains " quote"""|] | ||||
|                 `shouldBe` Right [r|contains " quote|] | ||||
|             runParser blockString [r|"""contains \""" triplequote"""|] | ||||
|                 `shouldBe` Right [r|contains """ triplequote|] | ||||
|             runParser blockString "\"\"\"multi\nline\"\"\"" `shouldBe` Right "multi\nline" | ||||
|             runParser blockString "\"\"\"multi\rline\r\nnormalized\"\"\"" | ||||
|                 `shouldBe` Right "multi\nline\nnormalized" | ||||
|             runParser blockString "\"\"\"multi\rline\r\nnormalized\"\"\"" | ||||
|                 `shouldBe` Right "multi\nline\nnormalized" | ||||
|             runParser blockString [r|"""unescaped \n\r\b\t\f\u1234"""|] | ||||
|                 `shouldBe` Right [r|unescaped \n\r\b\t\f\u1234|] | ||||
|             runParser blockString [r|"""slashes \\ \/"""|] | ||||
|                 `shouldBe` Right [r|slashes \\ \/|] | ||||
|             runParser blockString [r|""" | ||||
|  | ||||
|                 spans | ||||
|                   multiple | ||||
|                     lines | ||||
|  | ||||
|                 """|] `shouldBe` Right "spans\n  multiple\n    lines" | ||||
|  | ||||
|         it "lexes numbers" $ do | ||||
|             runParser integer "4" `shouldBe` Right (4 :: Int) | ||||
|             runParser float "4.123" `shouldBe` Right 4.123 | ||||
|             runParser integer "-4" `shouldBe` Right (-4 :: Int) | ||||
|             runParser integer "9" `shouldBe` Right (9 :: Int) | ||||
|             runParser integer "0" `shouldBe` Right (0 :: Int) | ||||
|             runParser float "-4.123" `shouldBe` Right (-4.123) | ||||
|             runParser float "0.123" `shouldBe` Right 0.123 | ||||
|             runParser float "123e4" `shouldBe` Right 123e4 | ||||
|             runParser float "123E4" `shouldBe` Right 123E4 | ||||
|             runParser float "123e-4" `shouldBe` Right 123e-4 | ||||
|             runParser float "123e+4" `shouldBe` Right 123e+4 | ||||
|             runParser float "-1.123e4" `shouldBe` Right (-1.123e4) | ||||
|             runParser float "-1.123E4" `shouldBe` Right (-1.123E4) | ||||
|             runParser float "-1.123e-4" `shouldBe` Right (-1.123e-4) | ||||
|             runParser float "-1.123e+4" `shouldBe` Right (-1.123e+4) | ||||
|             runParser float "-1.123e4567" `shouldBe` Right (-1.123e4567) | ||||
|  | ||||
|         it "lexes punctuation" $ do | ||||
|             runParser bang "!" `shouldBe` Right '!' | ||||
|             runParser dollar "$" `shouldBe` Right '$' | ||||
|             runBetween parens "()" `shouldBe` Right () | ||||
|             runParser spread "..." `shouldBe` Right "..." | ||||
|             runParser colon ":" `shouldBe` Right ":" | ||||
|             runParser equals "=" `shouldBe` Right "=" | ||||
|             runParser at "@" `shouldBe` Right '@' | ||||
|             runBetween brackets "[]" `shouldBe` Right () | ||||
|             runBetween braces "{}" `shouldBe` Right () | ||||
|             runParser pipe "|" `shouldBe` Right "|" | ||||
|  | ||||
|     context "Implementation tests" $ do | ||||
|         it "lexes empty block strings" $ | ||||
|             runParser blockString [r|""""""|] `shouldBe` Right "" | ||||
|         it "lexes ampersand" $ | ||||
|             runParser amp "&" `shouldBe` Right "&" | ||||
|  | ||||
| runParser :: forall a. Parser a -> T.Text -> Either (ParseErrorBundle T.Text Void) a | ||||
| runParser = flip parse "" | ||||
|  | ||||
| runBetween :: (Parser () -> Parser ()) -> T.Text -> Either (ParseErrorBundle T.Text Void) () | ||||
| runBetween parser = parse (parser $ pure ()) "" | ||||
| @@ -1,102 +0,0 @@ | ||||
| {-# LANGUAGE ExplicitForAll #-} | ||||
| {-# LANGUAGE OverloadedStrings #-} | ||||
| {-# LANGUAGE QuasiQuotes #-} | ||||
| module Language.GraphQL.LexerTest | ||||
|     ( implementation | ||||
|     , reference | ||||
|     ) where | ||||
|  | ||||
| import Language.GraphQL.Lexer | ||||
| import qualified Data.Text as T | ||||
| import Data.Void (Void) | ||||
| import Test.Tasty ( TestTree | ||||
|                   , testGroup | ||||
|                   ) | ||||
| import Test.Tasty.HUnit ( testCase | ||||
|                         , (@?=) | ||||
|                         ) | ||||
| import Text.Megaparsec ( ParseErrorBundle | ||||
|                        , parse | ||||
|                        ) | ||||
| import Text.RawString.QQ (r) | ||||
|  | ||||
| reference :: TestTree | ||||
| reference = testGroup "Lexer" | ||||
|     [ testCase "lexes strings" $ do | ||||
|         runParser string [r|"simple"|] @?= Right "simple" | ||||
|         runParser string [r|" white space "|] @?= Right " white space " | ||||
|         runParser string [r|"quote \""|] @?= Right [r|quote "|] | ||||
|         runParser string [r|"escaped \n"|] @?= Right "escaped \n" | ||||
|         runParser string [r|"slashes \\ \/"|] @?= Right [r|slashes \ /|] | ||||
|         runParser string [r|"unicode \u1234\u5678\u90AB\uCDEF"|] | ||||
|             @?= Right "unicode ሴ噸邫췯" | ||||
|  | ||||
|     , testCase "lexes block string" $ do | ||||
|         runParser blockString [r|"""simple"""|] @?= Right "simple" | ||||
|         runParser blockString [r|""" white space """|] | ||||
|             @?= Right " white space " | ||||
|         runParser blockString [r|"""contains " quote"""|] | ||||
|             @?= Right [r|contains " quote|] | ||||
|         runParser blockString [r|"""contains \""" triplequote"""|] | ||||
|             @?= Right [r|contains """ triplequote|] | ||||
|         runParser blockString "\"\"\"multi\nline\"\"\"" @?= Right "multi\nline" | ||||
|         runParser blockString "\"\"\"multi\rline\r\nnormalized\"\"\"" | ||||
|             @?= Right "multi\nline\nnormalized" | ||||
|         runParser blockString "\"\"\"multi\rline\r\nnormalized\"\"\"" | ||||
|             @?= Right "multi\nline\nnormalized" | ||||
|         runParser blockString [r|"""unescaped \n\r\b\t\f\u1234"""|] | ||||
|             @?= Right [r|unescaped \n\r\b\t\f\u1234|] | ||||
|         runParser blockString [r|"""slashes \\ \/"""|] | ||||
|             @?= Right [r|slashes \\ \/|] | ||||
|         runParser blockString [r|""" | ||||
|  | ||||
|             spans | ||||
|               multiple | ||||
|                 lines | ||||
|  | ||||
|             """|] @?= Right "spans\n  multiple\n    lines" | ||||
|  | ||||
|     , testCase "lexes numbers" $ do | ||||
|         runParser integer "4" @?= Right (4 :: Int) | ||||
|         runParser float "4.123" @?= Right 4.123 | ||||
|         runParser integer "-4" @?= Right (-4 :: Int) | ||||
|         runParser integer "9" @?= Right (9 :: Int) | ||||
|         runParser integer "0" @?= Right (0 :: Int) | ||||
|         runParser float "-4.123" @?= Right (-4.123) | ||||
|         runParser float "0.123" @?= Right 0.123 | ||||
|         runParser float "123e4" @?= Right 123e4 | ||||
|         runParser float "123E4" @?= Right 123E4 | ||||
|         runParser float "123e-4" @?= Right 123e-4 | ||||
|         runParser float "123e+4" @?= Right 123e+4 | ||||
|         runParser float "-1.123e4" @?= Right (-1.123e4) | ||||
|         runParser float "-1.123E4" @?= Right (-1.123E4) | ||||
|         runParser float "-1.123e-4" @?= Right (-1.123e-4) | ||||
|         runParser float "-1.123e+4" @?= Right (-1.123e+4) | ||||
|         runParser float "-1.123e4567" @?= Right (-1.123e4567) | ||||
|  | ||||
|     , testCase "lexes punctuation" $ do | ||||
|         runParser bang "!" @?= Right '!' | ||||
|         runParser dollar "$" @?= Right '$' | ||||
|         runBetween parens "()" @?= Right () | ||||
|         runParser spread "..." @?= Right "..." | ||||
|         runParser colon ":" @?= Right ":" | ||||
|         runParser equals "=" @?= Right "=" | ||||
|         runParser at "@" @?= Right '@' | ||||
|         runBetween brackets "[]" @?= Right () | ||||
|         runBetween braces "{}" @?= Right () | ||||
|         runParser pipe "|" @?= Right "|" | ||||
|     ] | ||||
|  | ||||
| implementation :: TestTree | ||||
| implementation = testGroup "Lexer" | ||||
|     [ testCase "lexes empty block strings" $ | ||||
|         runParser blockString [r|""""""|] @?= Right "" | ||||
|     , testCase "lexes ampersand" $ | ||||
|         runParser amp "&" @?= Right "&" | ||||
|     ] | ||||
|  | ||||
| runParser :: forall a. Parser a -> T.Text -> Either (ParseErrorBundle T.Text Void) a | ||||
| runParser = flip parse "" | ||||
|  | ||||
| runBetween :: (Parser () -> Parser ()) -> T.Text -> Either (ParseErrorBundle T.Text Void) () | ||||
| runBetween parser = parse (parser $ pure ()) "" | ||||
		Reference in New Issue
	
	Block a user