1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 08:54:07 +03:00

Get the tests compiling.

This commit is contained in:
Rob Rix 2018-06-22 13:52:21 -04:00
parent 2a99657e5e
commit 33c04b15c3
8 changed files with 56 additions and 56 deletions

View File

@ -11,13 +11,13 @@ spec :: Spec
spec = parallel $ do
describe "evaluates Go" $ do
it "imports and wildcard imports" $ do
((Right [(_, env)], state), _) <- evaluate "main.go"
(_, (state, Right [(env, _)])) <- evaluate "main.go"
Env.names env `shouldBe` [ "Bar", "Rab", "foo", "main" ]
(derefQName (heap state) ("foo" :| []) env >>= deNamespace) `shouldBe` Just ("foo", ["New"])
it "imports with aliases (and side effects only)" $ do
((Right [(_, env)], state), _) <- evaluate "main1.go"
(_, (state, Right [(env, _)])) <- evaluate "main1.go"
Env.names env `shouldBe` [ "f", "main" ]
(derefQName (heap state) ("f" :| []) env >>= deNamespace) `shouldBe` Just ("f", ["New"])

View File

@ -12,17 +12,17 @@ spec :: Spec
spec = parallel $ do
describe "PHP" $ do
it "evaluates include and require" $ do
((Right [(res, env)], state), _) <- evaluate "main.php"
(_, (_, Right [(env, res)])) <- evaluate "main.php"
res `shouldBe` unit
Env.names env `shouldBe` [ "bar", "foo" ]
it "evaluates include_once and require_once" $ do
((Right [(res, env)], state), _) <- evaluate "main_once.php"
(_, (_, Right [(env, res)])) <- evaluate "main_once.php"
res `shouldBe` unit
Env.names env `shouldBe` [ "bar", "foo" ]
it "evaluates namespaces" $ do
((Right [(_, env)], state), _) <- evaluate "namespaces.php"
(_, (state, Right [(env, _)])) <- evaluate "namespaces.php"
Env.names env `shouldBe` [ "Foo", "NS1" ]
(derefQName (heap state) ("NS1" :| []) env >>= deNamespace) `shouldBe` Just ("NS1", ["Sub1", "b", "c"])

View File

@ -14,7 +14,7 @@ spec :: Spec
spec = parallel $ do
describe "evaluates Python" $ do
it "imports" $ do
((Right [(_, env)], state), _) <- evaluate "main.py"
(_, (state, Right [(env, _)])) <- evaluate "main.py"
Env.names env `shouldContain` [ "a", "b" ]
(derefQName (heap state) ("a" :| []) env >>= deNamespace) `shouldBe` Just ("a", ["foo"])
@ -22,25 +22,25 @@ spec = parallel $ do
(derefQName (heap state) ("b" :| ["c"]) env >>= deNamespace) `shouldBe` Just ("c", ["baz"])
it "imports with aliases" $ do
((Right [(_, env)], _), _) <- evaluate "main1.py"
(_, (_, Right [(env, _)])) <- evaluate "main1.py"
Env.names env `shouldContain` [ "b", "e" ]
it "imports using 'from' syntax" $ do
((Right [(_, env)], _), _) <- evaluate "main2.py"
(_, (_, Right [(env, _)])) <- evaluate "main2.py"
Env.names env `shouldContain` [ "bar", "foo" ]
it "imports with relative syntax" $ do
((Right [(_, env)], state), _) <- evaluate "main3.py"
(_, (state, Right [(env, _)])) <- evaluate "main3.py"
Env.names env `shouldContain` [ "utils" ]
(derefQName (heap state) ("utils" :| []) env >>= deNamespace) `shouldBe` Just ("utils", ["to_s"])
it "subclasses" $ do
((res, _), _) <- evaluate "subclass.py"
fmap fst <$> res `shouldBe` Right [String "\"bar\""]
(_, (_, res)) <- evaluate "subclass.py"
fmap snd <$> res `shouldBe` Right [String "\"bar\""]
it "handles multiple inheritance left-to-right" $ do
((res, _), _) <- evaluate "multiple_inheritance.py"
fmap fst <$> res `shouldBe` Right [String "\"foo!\""]
(_, (_, res)) <- evaluate "multiple_inheritance.py"
fmap snd <$> res `shouldBe` Right [String "\"foo!\""]
where
ns n = Just . Latest . Last . Just . Namespace n

View File

@ -20,57 +20,57 @@ spec :: Spec
spec = parallel $ do
describe "Ruby" $ do
it "evaluates require_relative" $ do
((Right [(res, env)], state), _) <- evaluate "main.rb"
(_, (_, Right [(env, res)])) <- evaluate "main.rb"
res `shouldBe` Value.Integer (Number.Integer 1)
Env.names env `shouldContain` ["foo"]
it "evaluates load" $ do
((Right [(_, env)], _), _) <- evaluate "load.rb"
(_, (_, Right [(env, _)])) <- evaluate "load.rb"
Env.names env `shouldContain` ["foo"]
it "evaluates load with wrapper" $ do
((res, state), _) <- evaluate "load-wrap.rb"
(_, (_, res)) <- evaluate "load-wrap.rb"
res `shouldBe` Left (SomeExc (inject @(EnvironmentError Precise) (FreeVariable "foo")))
it "evaluates subclass" $ do
((Right [(res, env)], state), _) <- evaluate "subclass.rb"
(_, (state, Right [(env, res)])) <- evaluate "subclass.rb"
res `shouldBe` String "\"<bar>\""
Env.names env `shouldContain` [ "Bar", "Foo" ]
(derefQName (heap state) ("Bar" :| []) env >>= deNamespace) `shouldBe` Just ("Bar", ["baz", "foo", "inspect"])
it "evaluates modules" $ do
((Right [(res, env)], state), _) <- evaluate "modules.rb"
(_, (state, Right [(env, res)])) <- evaluate "modules.rb"
res `shouldBe` String "\"<hello>\""
Env.names env `shouldContain` [ "Bar" ]
it "handles break correctly" $ do
((res, _), _) <- evaluate "break.rb"
fmap fst <$> res `shouldBe` Right [Value.Integer (Number.Integer 3)]
(_, (_, res)) <- evaluate "break.rb"
fmap snd <$> res `shouldBe` Right [Value.Integer (Number.Integer 3)]
it "handles break correctly" $ do
((res, _), _) <- evaluate "next.rb"
fmap fst <$> res `shouldBe` Right [Value.Integer (Number.Integer 8)]
(_, (_, res)) <- evaluate "next.rb"
fmap snd <$> res `shouldBe` Right [Value.Integer (Number.Integer 8)]
it "calls functions with arguments" $ do
((res, _), _) <- evaluate "call.rb"
fmap fst <$> res `shouldBe` Right [Value.Integer (Number.Integer 579)]
(_, (_, res)) <- evaluate "call.rb"
fmap snd <$> res `shouldBe` Right [Value.Integer (Number.Integer 579)]
it "evaluates early return statements" $ do
((res, _), _) <- evaluate "early-return.rb"
fmap fst <$> res `shouldBe` Right [Value.Integer (Number.Integer 123)]
(_, (_, res)) <- evaluate "early-return.rb"
fmap snd <$> res `shouldBe` Right [Value.Integer (Number.Integer 123)]
it "has prelude" $ do
((res, _), _) <- evaluate "preluded.rb"
fmap fst <$> res `shouldBe` Right [String "\"<foo>\""]
(_, (_, res)) <- evaluate "preluded.rb"
fmap snd <$> res `shouldBe` Right [String "\"<foo>\""]
it "evaluates __LINE__" $ do
((res, _), _) <- evaluate "line.rb"
fmap fst <$> res `shouldBe` Right [Value.Integer (Number.Integer 4)]
(_, (_, res)) <- evaluate "line.rb"
fmap snd <$> res `shouldBe` Right [Value.Integer (Number.Integer 4)]
it "resolves builtins used in the prelude" $ do
((res, _), traces) <- evaluate "puts.rb"
fmap fst <$> res `shouldBe` Right [Unit]
(traces, (_, res)) <- evaluate "puts.rb"
fmap snd <$> res `shouldBe` Right [Unit]
traces `shouldContain` [ "\"hello\"" ]
where

View File

@ -15,27 +15,27 @@ spec :: Spec
spec = parallel $ do
describe "evaluates TypeScript" $ do
it "imports with aliased symbols" $ do
((Right [(_, env)], _), _) <- evaluate "main.ts"
(_, (_, Right [(env, _)])) <- evaluate "main.ts"
Env.names env `shouldBe` [ "bar", "quz" ]
it "imports with qualified names" $ do
((Right [(_, env)], state), _) <- evaluate "main1.ts"
(_, (state, Right [(env, _)])) <- evaluate "main1.ts"
Env.names env `shouldBe` [ "b", "z" ]
(derefQName (heap state) ("b" :| []) env >>= deNamespace) `shouldBe` Just ("b", [ "baz", "foo" ])
(derefQName (heap state) ("z" :| []) env >>= deNamespace) `shouldBe` Just ("z", [ "baz", "foo" ])
it "side effect only imports" $ do
((res, _), _) <- evaluate "main2.ts"
fmap snd <$> res `shouldBe` Right [lowerBound]
(_, (_, res)) <- evaluate "main2.ts"
fmap fst <$> res `shouldBe` Right [lowerBound]
it "fails exporting symbols not defined in the module" $ do
((res, _), _) <- evaluate "bad-export.ts"
(_, (_, res)) <- evaluate "bad-export.ts"
res `shouldBe` Left (SomeExc (inject @EvalError (ExportError "foo.ts" (name "pip"))))
it "evaluates early return statements" $ do
((res, _), _) <- evaluate "early-return.ts"
fmap fst <$> res `shouldBe` Right [Value.Float (Number.Decimal 123.0)]
(_, (_, res)) <- evaluate "early-return.ts"
fmap snd <$> res `shouldBe` Right [Value.Float (Number.Decimal 123.0)]
where
fixtures = "test/fixtures/typescript/analysis/"

View File

@ -19,18 +19,18 @@ import SpecHelpers hiding (reassociate)
spec :: Spec
spec = parallel $ do
it "constructs integers" $ do
(expected, _) <- evaluate (box (integer 123))
(_, expected) <- evaluate (box (integer 123))
expected `shouldBe` Right (Value.Integer (Number.Integer 123))
it "calls functions" $ do
(expected, _) <- evaluate $ do
(_, expected) <- evaluate $ do
identity <- closure [name "x"] lowerBound (variable (name "x"))
call identity [box (integer 123)]
expected `shouldBe` Right (Value.Integer (Number.Integer 123))
evaluate
= runM
. evaluating @Precise @Val
. evaluating @_ @Precise @Val
. runReader (PackageInfo (name "test") Nothing mempty)
. runReader (ModuleInfo "test/Control/Abstract/Evaluator/Spec.hs")
. fmap reassociate
@ -38,7 +38,7 @@ evaluate
. runEnvironmentError
. runAddressError
. runAllocator
. (>>= deref . fst)
. (>>= deref . snd)
. runEnv lowerBound
. runReturn
. runLoopControl
@ -59,7 +59,7 @@ newtype SpecEff a = SpecEff
, Reader PackageInfo
, Fresh
, State (Heap Precise Latest Val)
, State (ModuleTable (Maybe (Precise, Environment Precise)))
, IO
, State (ModuleTable (Maybe (Environment Precise, Precise)))
, Lift IO
] a
}

View File

@ -242,10 +242,10 @@ diffWithParser :: ( HasField fields Data.Span.Span
, Diffable syntax
, HasDeclaration syntax
, Hashable1 syntax
, Member (Distribute WrappedTask) effs
, Member Distribute effs
, Member Task effs
)
=> Parser (Term syntax (Record fields))
-> BlobPair
-> Eff effs (Diff syntax (Record (Maybe Declaration ': fields)) (Record (Maybe Declaration ': fields)))
diffWithParser parser blobs = distributeFor blobs (\ blob -> WrapTask $ parse parser blob >>= decorate (declarationAlgebra blob)) >>= SpecHelpers.diff . runJoin
diffWithParser parser blobs = distributeFor blobs (\ blob -> parse parser blob >>= decorate (declarationAlgebra blob)) >>= SpecHelpers.diff . runJoin

View File

@ -91,11 +91,13 @@ testEvaluating :: TermEvaluator term Precise
, Resumable (LoadError Precise Val)
, Fresh
, State (Heap Precise Latest Val)
, State (ModuleTable (Maybe (Precise, Environment Precise)))
, State (ModuleTable (Maybe (Environment Precise, Precise)))
, Trace
]
[(Precise, Environment Precise)]
-> ((Either
[(Environment Precise, Precise)]
-> ( [String]
, ( EvaluatingState Precise Val
, Either
(SomeExc
(Data.Sum.Sum
'[ ValueError Precise TestEff
@ -106,9 +108,7 @@ testEvaluating :: TermEvaluator term Precise
, Unspecialized Val
, LoadError Precise Val
]))
[(Value Precise TestEff, Environment Precise)],
EvaluatingState Precise Val),
[String])
[(Environment Precise, Value Precise TestEff)]))
testEvaluating
= run
. runReturningTrace
@ -143,14 +143,14 @@ newtype TestEff a = TestEff
, Resumable (LoadError Precise Val)
, Fresh
, State (Heap Precise Latest Val)
, State (ModuleTable (Maybe (Precise, Environment Precise)))
, State (ModuleTable (Maybe (Environment Precise, Precise)))
, Trace
] a
}
deref1 (ptr, env) = runAllocator $ do
deref1 (env, ptr) = runAllocator $ do
val <- deref ptr
pure (val, env)
pure (env, val)
deNamespace :: Value Precise term -> Maybe (Name, [Name])
deNamespace (Namespace name scope) = Just (name, Env.names scope)