1
1
mirror of https://github.com/github/semantic.git synced 2024-11-25 11:04:00 +03:00
semantic/semantic-core/test/Spec.hs

119 lines
4.0 KiB
Haskell
Raw Normal View History

2019-06-16 14:00:47 +03:00
{-# LANGUAGE OverloadedStrings #-}
2019-06-04 18:26:42 +03:00
module Main (main) where
import Data.String
import qualified Text.Trifecta as Trifecta
import Hedgehog hiding (Var)
import Test.Tasty
import Test.Tasty.Hedgehog
import Test.Tasty.HUnit
import Data.File
import qualified Generators as Gen
import qualified Analysis.Eval as Eval
import Data.Core
import Data.Core.Pretty
import Data.Core.Parser as Parse
import Data.Name
2019-07-17 19:44:34 +03:00
import Data.Term
2019-06-04 18:26:42 +03:00
-- * Helpers
2019-07-17 19:55:05 +03:00
true, false :: Term Core User
true = bool True
false = bool False
2019-06-04 18:26:42 +03:00
parseEither :: Trifecta.Parser a -> String -> Either String a
parseEither p = Trifecta.foldResult (Left . show . Trifecta._errDoc) Right . Trifecta.parseString (p <* Trifecta.eof) mempty
-- * Parser roundtripping properties. Note that parsing and prettyprinting is generally
-- not a roundtrip, because the parser inserts 'Ann' nodes itself.
2019-07-17 19:55:05 +03:00
prop_roundtrips :: Gen (Term Core User) -> Property
2019-06-04 18:26:42 +03:00
prop_roundtrips gen = property $ do
input <- forAll gen
tripping input showCore (parseEither (Parse.core <* Trifecta.eof))
parserProps :: TestTree
parserProps = testGroup "Parsing: roundtripping"
[ testProperty "literals" $ prop_roundtrips Gen.literal
, testProperty "if/then/else" . prop_roundtrips . Gen.ifthenelse $ Gen.variable
, testProperty "lambda" . prop_roundtrips $ Gen.lambda Gen.literal
, testProperty "function application" . prop_roundtrips $ Gen.apply Gen.variable
]
-- * Parser specs
2019-07-17 19:55:05 +03:00
parsesInto :: String -> Term Core User -> Assertion
2019-06-04 18:26:42 +03:00
parsesInto str res = case parseEither Parse.core str of
Right x -> x @?= res
Left m -> assertFailure m
assert_booleans_parse :: Assertion
assert_booleans_parse = do
parseEither Parse.core "#true" @?= Right true
parseEither Parse.core "#false" @?= Right false
2019-07-17 19:55:05 +03:00
a, f, g, h :: Term Core User
(a, f, g, h) = (pure "a", pure "f", pure "g", pure "h")
2019-06-04 18:26:42 +03:00
assert_ifthen_parse :: Assertion
2019-07-17 19:55:05 +03:00
assert_ifthen_parse = "if #true then #true else #false" `parsesInto` (if' true true false)
2019-06-04 18:26:42 +03:00
assert_application_parse :: Assertion
2019-07-17 19:55:05 +03:00
assert_application_parse = "f g" `parsesInto` (f $$ g)
2019-06-04 18:26:42 +03:00
assert_application_left_associative :: Assertion
2019-07-17 19:55:05 +03:00
assert_application_left_associative = "f g h" `parsesInto` (f $$ g $$ h)
2019-06-04 18:26:42 +03:00
assert_push_left_associative :: Assertion
2019-07-22 21:27:03 +03:00
assert_push_left_associative = "f.g.h" `parsesInto` (f ... "g" ... "h")
2019-06-04 18:26:42 +03:00
assert_ascii_lambda_parse :: Assertion
2019-07-17 19:55:05 +03:00
assert_ascii_lambda_parse = "\\a -> a" `parsesInto` lam (named' "a") a
2019-06-04 18:26:42 +03:00
assert_unicode_lambda_parse :: Assertion
2019-07-17 19:55:05 +03:00
assert_unicode_lambda_parse = "λa → a" `parsesInto` lam (named' "a") a
2019-06-04 18:26:42 +03:00
assert_quoted_name_parse :: Assertion
2019-07-17 19:55:05 +03:00
assert_quoted_name_parse = "#{(NilClass)}" `parsesInto` pure "(NilClass)"
2019-06-04 18:26:42 +03:00
parserSpecs :: TestTree
parserSpecs = testGroup "Parsing: simple specs"
[ testCase "true/false" assert_booleans_parse
, testCase "if/then/else" assert_ifthen_parse
, testCase "function application" assert_application_parse
, testCase "application is left-associative" assert_application_left_associative
, testCase "dotted push is left-associative" assert_push_left_associative
, testCase "lambda with ASCII syntax" assert_ascii_lambda_parse
, testCase "lambda with unicode syntax" assert_unicode_lambda_parse
, testCase "quoted names" assert_quoted_name_parse
]
2019-07-17 19:55:05 +03:00
assert_roundtrips :: File (Term Core User) -> Assertion
assert_roundtrips (File _ core) = case parseEither Parse.core (showCore core) of
Right v -> v @?= stripAnnotations core
Left e -> assertFailure e
2019-06-04 18:26:42 +03:00
parserExamples :: TestTree
parserExamples = testGroup "Parsing: Eval.hs examples"
[ testCase "prog1" (assert_roundtrips Eval.prog1)
, testCase "prog2" (assert_roundtrips Eval.prog2)
, testCase "prog3" (assert_roundtrips Eval.prog3)
, testCase "prog4" (assert_roundtrips Eval.prog4)
, testCase "prog6.1" (assert_roundtrips (head Eval.prog6))
, testCase "prog6.2" (assert_roundtrips (last Eval.prog6))
, testCase "ruby" (assert_roundtrips Eval.ruby)
]
tests :: TestTree
tests = testGroup "semantic-core"
[ parserSpecs
, parserExamples
, parserProps
]
main :: IO ()
main = defaultMain tests