2018-03-10 02:01:29 +03:00
|
|
|
{-# LANGUAGE TypeApplications #-}
|
2018-03-10 02:16:07 +03:00
|
|
|
module Analysis.Python.Spec where
|
2018-03-10 02:01:29 +03:00
|
|
|
|
2018-03-10 03:24:23 +03:00
|
|
|
import Data.Abstract.Address
|
|
|
|
import Data.Abstract.Environment
|
|
|
|
import Data.Abstract.FreeVariables
|
|
|
|
import Data.Abstract.Value as Value
|
2018-03-10 02:01:29 +03:00
|
|
|
import Data.AST
|
2018-03-10 03:24:23 +03:00
|
|
|
import Data.Map as Map
|
2018-03-10 02:01:29 +03:00
|
|
|
import Data.Record
|
2018-03-10 03:24:23 +03:00
|
|
|
import Data.Semigroup
|
2018-03-10 02:01:29 +03:00
|
|
|
import Data.Term
|
|
|
|
import Data.Union
|
|
|
|
import Parsing.Parser
|
|
|
|
|
|
|
|
import SpecHelpers
|
|
|
|
import Test.Hspec (Spec, describe, it, xit, parallel, pendingWith)
|
|
|
|
import Test.Hspec.Expectations.Pretty
|
2018-03-10 03:24:23 +03:00
|
|
|
import qualified Language.Python.Assignment as Python
|
2018-03-10 02:01:29 +03:00
|
|
|
|
|
|
|
|
2018-03-10 03:24:23 +03:00
|
|
|
type PythonValue = Value Precise (Term (Union Python.Syntax) (Record Location))
|
|
|
|
|
2018-03-10 02:01:29 +03:00
|
|
|
spec :: Spec
|
|
|
|
spec = parallel $ do
|
2018-03-10 02:55:04 +03:00
|
|
|
describe "evalutes Python" $ do
|
2018-03-10 02:16:07 +03:00
|
|
|
it "imports" $ do
|
|
|
|
res <- evaluate "main.py"
|
2018-03-10 02:01:29 +03:00
|
|
|
let expectedEnv = Environment $ fromList
|
|
|
|
[ (qualifiedName ["a", "foo"], addr 0)
|
|
|
|
, (qualifiedName ["b", "c", "baz"], addr 1)
|
|
|
|
]
|
2018-03-12 19:25:04 +03:00
|
|
|
assertEnvironment res expectedEnv
|
2018-03-10 02:01:29 +03:00
|
|
|
|
2018-03-10 02:16:07 +03:00
|
|
|
it "imports with aliases" $ do
|
|
|
|
res <- evaluate "main1.py"
|
|
|
|
let expectedEnv = Environment $ fromList
|
|
|
|
[ (qualifiedName ["b", "foo"], addr 0)
|
|
|
|
, (qualifiedName ["e", "baz"], addr 1)
|
|
|
|
]
|
2018-03-12 19:25:04 +03:00
|
|
|
assertEnvironment res expectedEnv
|
2018-03-10 02:16:07 +03:00
|
|
|
|
|
|
|
it "imports using 'from' syntax" $ do
|
|
|
|
res <- evaluate "main2.py"
|
|
|
|
let expectedEnv = Environment $ fromList
|
|
|
|
[ (qualifiedName ["foo"], addr 0)
|
|
|
|
, (qualifiedName ["bar"], addr 1)
|
|
|
|
]
|
2018-03-12 19:25:04 +03:00
|
|
|
assertEnvironment res expectedEnv
|
2018-03-10 02:16:07 +03:00
|
|
|
|
2018-03-10 02:01:29 +03:00
|
|
|
where
|
2018-03-12 19:25:04 +03:00
|
|
|
assertEnvironment result expectedEnv = case result of
|
|
|
|
Left e -> expectationFailure ("Evaluating expected to succeed, but failed with: " <> e)
|
2018-03-13 02:13:21 +03:00
|
|
|
Right res -> let Just (Interface _ env) = prjValue @(Interface Precise) res in env `shouldBe` expectedEnv
|
2018-03-12 19:25:04 +03:00
|
|
|
|
2018-03-10 02:01:29 +03:00
|
|
|
addr = Address . Precise
|
2018-03-10 03:24:23 +03:00
|
|
|
fixtures = "test/fixtures/python/analysis/"
|
|
|
|
evaluate entry = fst . fst . fst . fst <$>
|
|
|
|
evaluateFiles @PythonValue pythonParser
|
|
|
|
[ fixtures <> entry
|
|
|
|
, fixtures <> "a.py"
|
|
|
|
, fixtures <> "b/c.py"
|
2018-03-10 02:16:07 +03:00
|
|
|
]
|