1
1
mirror of https://github.com/github/semantic.git synced 2024-12-25 16:02:43 +03:00

Use the EvaluatingState fields directly.

This commit is contained in:
Rob Rix 2018-03-27 15:23:26 -04:00
parent 7a10eabfd7
commit b8d714af28
6 changed files with 29 additions and 36 deletions

View File

@ -2,9 +2,6 @@
module Analysis.Go.Spec (spec) where module Analysis.Go.Spec (spec) where
import Data.Abstract.Value import Data.Abstract.Value
import Data.Map
import Data.Either
import SpecHelpers import SpecHelpers
@ -12,7 +9,7 @@ spec :: Spec
spec = parallel $ do spec = parallel $ do
describe "evalutes Go" $ do describe "evalutes Go" $ do
it "imports and wildcard imports" $ do it "imports and wildcard imports" $ do
env <- findEnv <$> evaluate "main.go" env <- environment . snd <$> evaluate "main.go"
env `shouldBe` [ (qualifiedName ["foo", "New"], addr 0) env `shouldBe` [ (qualifiedName ["foo", "New"], addr 0)
, (qualifiedName ["Rab"], addr 1) , (qualifiedName ["Rab"], addr 1)
, (qualifiedName ["Bar"], addr 2) , (qualifiedName ["Bar"], addr 2)
@ -20,7 +17,7 @@ spec = parallel $ do
] ]
it "imports with aliases (and side effects only)" $ do it "imports with aliases (and side effects only)" $ do
env <- findEnv <$> evaluate "main1.go" env <- environment . snd <$> evaluate "main1.go"
env `shouldBe` [ (qualifiedName ["f", "New"], addr 0) env `shouldBe` [ (qualifiedName ["f", "New"], addr 0)
, (qualifiedName ["main"], addr 3) -- addr 3 is due to side effects of , (qualifiedName ["main"], addr 3) -- addr 3 is due to side effects of
-- eval'ing `import _ "./bar"` which -- eval'ing `import _ "./bar"` which

View File

@ -2,9 +2,6 @@
module Analysis.PHP.Spec (spec) where module Analysis.PHP.Spec (spec) where
import Data.Abstract.Value import Data.Abstract.Value
import Data.Map
import Data.Map.Monoidal as Map
import SpecHelpers import SpecHelpers
@ -12,27 +9,26 @@ spec :: Spec
spec = parallel $ do spec = parallel $ do
describe "PHP" $ do describe "PHP" $ do
it "evaluates include and require" $ do it "evaluates include and require" $ do
env <- findEnv <$> evaluate "main.php" env <- environment . snd <$> evaluate "main.php"
env `shouldBe` [ (name "foo", addr 0) env `shouldBe` [ (name "foo", addr 0)
, (name "bar", addr 1) ] , (name "bar", addr 1) ]
it "evaluates include_once and require_once" $ do it "evaluates include_once and require_once" $ do
env <- findEnv <$> evaluate "main_once.php" env <- environment . snd <$> evaluate "main_once.php"
env `shouldBe` [ (name "foo", addr 0) env `shouldBe` [ (name "foo", addr 0)
, (name "bar", addr 1) ] , (name "bar", addr 1) ]
it "evaluates namespaces" $ do it "evaluates namespaces" $ do
res <- evaluate "namespaces.php" res <- snd <$> evaluate "namespaces.php"
findEnv res `shouldBe` [ (name "NS1", addr 0) environment res `shouldBe` [ (name "NS1", addr 0)
, (name "Foo", addr 6) ] , (name "Foo", addr 6) ]
let heap = findHeap res heapLookup (Address (Precise 0)) (heap res) `shouldBe` ns "NS1" [ (name "Sub1", addr 1)
Map.lookup (Precise 0) heap `shouldBe` ns "NS1" [ (name "Sub1", addr 1)
, (name "b", addr 4) , (name "b", addr 4)
, (name "c", addr 5) , (name "c", addr 5)
] ]
Map.lookup (Precise 1) heap `shouldBe` ns "Sub1" [ (name "Sub2", addr 2) ] heapLookup (Address (Precise 1)) (heap res) `shouldBe` ns "Sub1" [ (name "Sub2", addr 2) ]
Map.lookup (Precise 2) heap `shouldBe` ns "Sub2" [ (name "f", addr 3) ] heapLookup (Address (Precise 2)) (heap res) `shouldBe` ns "Sub2" [ (name "f", addr 3) ]
where where
ns n = Just . Latest . Just . injValue . Namespace (name n) ns n = Just . Latest . Just . injValue . Namespace (name n)

View File

@ -11,29 +11,29 @@ spec :: Spec
spec = parallel $ do spec = parallel $ do
describe "evalutes Python" $ do describe "evalutes Python" $ do
it "imports" $ do it "imports" $ do
env <- findEnv <$> evaluate "main.py" env <- environment . snd <$> evaluate "main.py"
env `shouldBe` [ (qualifiedName ["a", "foo"], addr 0) env `shouldBe` [ (qualifiedName ["a", "foo"], addr 0)
, (qualifiedName ["b", "c", "baz"], addr 1) , (qualifiedName ["b", "c", "baz"], addr 1)
] ]
it "imports with aliases" $ do it "imports with aliases" $ do
env <- findEnv <$> evaluate "main1.py" env <- environment . snd <$> evaluate "main1.py"
env `shouldBe` [ (qualifiedName ["b", "foo"], addr 0) env `shouldBe` [ (qualifiedName ["b", "foo"], addr 0)
, (qualifiedName ["e", "baz"], addr 1) , (qualifiedName ["e", "baz"], addr 1)
] ]
it "imports using 'from' syntax" $ do it "imports using 'from' syntax" $ do
env <- findEnv <$> evaluate "main2.py" env <- environment . snd <$> evaluate "main2.py"
env `shouldBe` [ (qualifiedName ["foo"], addr 0) env `shouldBe` [ (qualifiedName ["foo"], addr 0)
, (qualifiedName ["bar"], addr 1) , (qualifiedName ["bar"], addr 1)
] ]
it "subclasses" $ do it "subclasses" $ do
v <- findValue <$> evaluate "subclass.py" v <- fst <$> evaluate "subclass.py"
v `shouldBe` Right (Right (Right (injValue (String "\"bar\"")))) v `shouldBe` Right (Right (Right (injValue (String "\"bar\""))))
it "handles multiple inheritance left-to-right" $ do it "handles multiple inheritance left-to-right" $ do
v <- findValue <$> evaluate "multiple_inheritance.py" v <- fst <$> evaluate "multiple_inheritance.py"
v `shouldBe` Right (Right (Right (injValue (String "\"foo!\"")))) v `shouldBe` Right (Right (Right (injValue (String "\"foo!\""))))
where where

View File

@ -12,28 +12,28 @@ spec :: Spec
spec = parallel $ do spec = parallel $ do
describe "evalutes Ruby" $ do describe "evalutes Ruby" $ do
it "require_relative" $ do it "require_relative" $ do
env <- findEnv <$> evaluate "main.rb" env <- environment . snd <$> evaluate "main.rb"
let expectedEnv = [ (qualifiedName ["Object"], addr 0) let expectedEnv = [ (qualifiedName ["Object"], addr 0)
, (qualifiedName ["foo"], addr 3)] , (qualifiedName ["foo"], addr 3)]
env `shouldBe` expectedEnv env `shouldBe` expectedEnv
it "load" $ do it "load" $ do
env <- findEnv <$> evaluate "load.rb" env <- environment . snd <$> evaluate "load.rb"
let expectedEnv = [ (qualifiedName ["Object"], addr 0) let expectedEnv = [ (qualifiedName ["Object"], addr 0)
, (qualifiedName ["foo"], addr 3) ] , (qualifiedName ["foo"], addr 3) ]
env `shouldBe` expectedEnv env `shouldBe` expectedEnv
it "load wrap" $ do it "load wrap" $ do
res <- evaluate "load-wrap.rb" res <- evaluate "load-wrap.rb"
findValue res `shouldBe` Left "free variable: \"foo\"" fst res `shouldBe` Left "free variable: \"foo\""
findEnv res `shouldBe` [(qualifiedName ["Object"], addr 0)] environment (snd res) `shouldBe` [(qualifiedName ["Object"], addr 0)]
it "subclass" $ do it "subclass" $ do
res <- findValue <$> evaluate "subclass.rb" res <- fst <$> evaluate "subclass.rb"
res `shouldBe` Right (Right (Right (injValue (String "\"<bar>\"")))) res `shouldBe` Right (Right (Right (injValue (String "\"<bar>\""))))
it "has prelude" $ do it "has prelude" $ do
res <- findValue <$> evaluate "preluded.rb" res <- fst <$> evaluate "preluded.rb"
res `shouldBe` Right (Right (Right (injValue (String "\"<foo>\"")))) res `shouldBe` Right (Right (Right (injValue (String "\"<foo>\""))))
where where

View File

@ -11,11 +11,11 @@ spec :: Spec
spec = parallel $ do spec = parallel $ do
describe "evalutes TypeScript" $ do describe "evalutes TypeScript" $ do
it "imports with aliased symbols" $ do it "imports with aliased symbols" $ do
env <- findEnv <$> evaluate "main.ts" env <- environment . snd <$> evaluate "main.ts"
env `shouldBe` [ (qualifiedName ["bar"], addr 0) ] env `shouldBe` [ (qualifiedName ["bar"], addr 0) ]
it "imports with qualified names" $ do it "imports with qualified names" $ do
env <- findEnv <$> evaluate "main1.ts" env <- environment . snd <$> evaluate "main1.ts"
env `shouldBe` [ (qualifiedName ["b", "baz"], addr 0) env `shouldBe` [ (qualifiedName ["b", "baz"], addr 0)
, (qualifiedName ["b", "foo"], addr 2) , (qualifiedName ["b", "foo"], addr 2)
, (qualifiedName ["z", "baz"], addr 0) , (qualifiedName ["z", "baz"], addr 0)
@ -23,11 +23,11 @@ spec = parallel $ do
] ]
it "side effect only imports" $ do it "side effect only imports" $ do
env <- findEnv <$> evaluate "main2.ts" env <- environment . snd <$> evaluate "main2.ts"
env `shouldBe` mempty env `shouldBe` mempty
it "fails exporting symbols not defined in the module" $ do it "fails exporting symbols not defined in the module" $ do
v <- findValue <$> evaluate "bad-export.ts" v <- fst <$> evaluate "bad-export.ts"
v `shouldBe` Left "module \"foo\" does not export \"pip\"" v `shouldBe` Left "module \"foo\" does not export \"pip\""
where where

View File

@ -9,7 +9,7 @@ module SpecHelpers (
, Verbatim(..) , Verbatim(..)
, ) where , ) where
import Analysis.Abstract.Evaluating as X (findValue, findEnv, findHeap) import Analysis.Abstract.Evaluating as X (EvaluatingState(..))
import Data.Abstract.Address as X import Data.Abstract.Address as X
import Data.Abstract.FreeVariables as X hiding (dropExtension) import Data.Abstract.FreeVariables as X hiding (dropExtension)
import Data.Abstract.Heap as X import Data.Abstract.Heap as X