1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 17:04:47 +03:00

Merge branch 'module-resolution' into default-extensions

This commit is contained in:
joshvera 2018-03-23 10:31:07 -04:00
commit 9b2524cc81
17 changed files with 86 additions and 33 deletions

View File

@ -121,8 +121,7 @@ deriving instance Member NonDet effects => MonadNonDet (Evaluating term value ef
-- | Effects necessary for evaluating (whether concrete or abstract). -- | Effects necessary for evaluating (whether concrete or abstract).
type EvaluatingEffects term value type EvaluatingEffects term value
= '[ = '[ Resumable Prelude.String value
Resumable Prelude.String value
, Fail -- Failure with an error message , Fail -- Failure with an error message
, State (EnvironmentFor value) -- Environments (both local and global) , State (EnvironmentFor value) -- Environments (both local and global)
, State (HeapFor value) -- The heap , State (HeapFor value) -- The heap

View File

@ -88,7 +88,7 @@ class (Monad m, Show value) => MonadValue value m where
-- | Build a class value from a name and environment. -- | Build a class value from a name and environment.
klass :: Name -- ^ The new class's identifier klass :: Name -- ^ The new class's identifier
-> Maybe value -- ^ An optional superclass. -> [value] -- ^ A list of superclasses
-> EnvironmentFor value -- ^ The environment to capture -> EnvironmentFor value -- ^ The environment to capture
-> m value -> m value
@ -155,10 +155,10 @@ instance ( Monad m
multiple = pure . injValue . Value.Tuple multiple = pure . injValue . Value.Tuple
array = pure . injValue . Value.Array array = pure . injValue . Value.Array
klass n Nothing env = pure . injValue $ Class n env klass n [] env = pure . injValue $ Class n env
klass n (Just super) env klass n supers env = do
| Just (Class _ superEnv) <- prjValue super = pure . injValue $ Class n (Env.push superEnv <> env) product <- mconcat <$> traverse objectEnvironment supers
| otherwise = fail ("Attempted to inherit from a non-class object: " <> show super) pure . injValue $ Class n (Env.push product <> env)
objectEnvironment o objectEnvironment o

View File

@ -151,7 +151,7 @@ instance Evaluatable Class where
(v, addr) <- letrec name $ do (v, addr) <- letrec name $ do
void $ subtermValue classBody void $ subtermValue classBody
classEnv <- Env.head <$> getEnv classEnv <- Env.head <$> getEnv
klass name (listToMaybe supers) classEnv klass name supers classEnv
v <$ modifyEnv (Env.insert name addr) v <$ modifyEnv (Env.insert name addr)
data Module a = Module { moduleIdentifier :: !a, moduleScope :: ![a] } data Module a = Module { moduleIdentifier :: !a, moduleScope :: ![a] }

View File

@ -340,12 +340,9 @@ yield = makeTerm <$> symbol Yield <*> (Statement.Yield <$> children (term ( expr
-- Identifiers and qualified identifiers (e.g. `a.b.c`) from things like DottedName and Attribute -- Identifiers and qualified identifiers (e.g. `a.b.c`) from things like DottedName and Attribute
identifier :: Assignment identifier :: Assignment
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> (name <$> source)) identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> (name <$> source))
<|> makeQualifiedIdentifier <$> symbol Attribute <*> children (attribute <|> identifierPair)
<|> makeQualifiedIdentifier <$> symbol DottedName <*> children (some identifier') <|> makeQualifiedIdentifier <$> symbol DottedName <*> children (some identifier')
<|> symbol DottedName *> children identifier <|> symbol DottedName *> children identifier
where where
attribute = (\a b -> a <> [b]) <$> (symbol Attribute *> children (attribute <|> identifierPair)) <*> identifier'
identifierPair = (\a b -> [a, b]) <$> identifier' <*> identifier'
identifier' = (symbol Identifier <|> symbol Identifier') *> source identifier' = (symbol Identifier <|> symbol Identifier') *> source
makeQualifiedIdentifier loc xs = makeTerm loc (Syntax.Identifier (qualifiedName xs)) makeQualifiedIdentifier loc xs = makeTerm loc (Syntax.Identifier (qualifiedName xs))

View File

@ -34,10 +34,19 @@ spec = parallel $ do
] ]
env `shouldBe` expectedEnv env `shouldBe` expectedEnv
it "subclasses" $ do
res <- evaluate' "subclass.py"
join (fst res) `shouldBe` Right (injValue (String "\"bar\""))
it "handles multiple inheritance left-to-right" $ do
res <- evaluate' "multiple_inheritance.py"
join (fst res) `shouldBe` Right (injValue (String "\"foo!\""))
where where
addr = Address . Precise addr = Address . Precise
fixtures = "test/fixtures/python/analysis/" fixtures = "test/fixtures/python/analysis/"
evaluate entry = snd . fst . fst . fst . fst <$> evaluate entry = snd <$> evaluate' entry
evaluate' entry = fst . fst . fst . fst <$>
evaluateFiles pythonParser evaluateFiles pythonParser
[ fixtures <> entry [ fixtures <> entry
, fixtures <> "a.py" , fixtures <> "a.py"

View File

@ -28,7 +28,7 @@ spec = parallel $ do
it "subclass" $ do it "subclass" $ do
res <- evaluate' "subclass.rb" res <- evaluate' "subclass.rb"
fst res `shouldBe` Right (injValue (String "\"<bar>\"")) join (fst res) `shouldBe` Right (injValue (String "\"<bar>\""))
where where
addr = Address . Precise addr = Address . Precise

View File

@ -34,6 +34,7 @@ import Data.Functor.Both as X (Both, runBothWith, both)
import Data.Maybe as X import Data.Maybe as X
import Data.Monoid as X (Monoid(..), First(..), Last(..)) import Data.Monoid as X (Monoid(..), First(..), Last(..))
import Data.Semigroup as X (Semigroup(..)) import Data.Semigroup as X (Semigroup(..))
import Control.Monad as X
import Test.Hspec as X (Spec, SpecWith, context, describe, it, xit, parallel, pendingWith, around, runIO) import Test.Hspec as X (Spec, SpecWith, context, describe, it, xit, parallel, pendingWith, around, runIO)
import Test.Hspec.Expectations.Pretty as X import Test.Hspec.Expectations.Pretty as X

View File

@ -0,0 +1,12 @@
class Foo:
def dang(self):
return "foo!"
class Bar:
def dang(self):
return "bar!"
class Baz(Foo, Bar): pass
Baz.dang()

View File

@ -0,0 +1,9 @@
class Foo():
def dang():
return "foo"
class Bar():
def dang():
return "bar"
Bar.dang()

View File

@ -14,6 +14,8 @@
{+(Identifier)+} {+(Identifier)+}
(Empty)) (Empty))
{+(Call {+(Call
{+(MemberAccess
{+(Identifier)+} {+(Identifier)+}
{+(Identifier)+})+}
{+(Integer)+} {+(Integer)+}
{+(Empty)+})+}) {+(Empty)+})+})

View File

@ -14,6 +14,8 @@
{+(Identifier)+} {+(Identifier)+}
(Empty)) (Empty))
{-(Call {-(Call
{-(MemberAccess
{-(Identifier)-} {-(Identifier)-}
{-(Identifier)-})-}
{-(Integer)-} {-(Integer)-}
{-(Empty)-})-}) {-(Empty)-})-})

View File

@ -12,6 +12,8 @@
(Identifier) (Identifier)
(Empty)) (Empty))
(Call (Call
(MemberAccess
(Identifier) (Identifier)
(Identifier))
(Integer) (Integer)
(Empty))) (Empty)))

View File

@ -269,8 +269,10 @@
22 22
] ]
}, },
"symbol": "os.getcwd", "symbol": "getcwd",
"targets": [] "targets": [
"os"
]
}, },
{ {
"span": { "span": {
@ -283,8 +285,10 @@
31 31
] ]
}, },
"symbol": "np.array", "symbol": "array",
"targets": [] "targets": [
"np"
]
}, },
{ {
"span": { "span": {
@ -297,8 +301,10 @@
20 20
] ]
}, },
"symbol": "x.sum", "symbol": "sum",
"targets": [] "targets": [
"x"
]
}, },
{ {
"span": { "span": {
@ -311,8 +317,10 @@
19 19
] ]
}, },
"symbol": "x.sum", "symbol": "sum",
"targets": [] "targets": [
"x"
]
}, },
{ {
"span": { "span": {

View File

@ -25,7 +25,9 @@
{+(Let {+(Let
{+(Empty)+} {+(Empty)+}
{+(Call {+(Call
{+(MemberAccess
{+(Identifier)+} {+(Identifier)+}
{+(Identifier)+})+}
{+(Identifier)+} {+(Identifier)+}
{+(TextElement)+} {+(TextElement)+}
{+(Identifier)+} {+(Identifier)+}
@ -34,7 +36,9 @@
{+(Let {+(Let
{+(Empty)+} {+(Empty)+}
{+(Call {+(Call
{+(MemberAccess
{+(Identifier)+} {+(Identifier)+}
{+(Identifier)+})+}
{+(Identifier)+} {+(Identifier)+}
{+(TextElement)+} {+(TextElement)+}
{+(Identifier)+} {+(Identifier)+}

View File

@ -25,7 +25,9 @@
{-(Let {-(Let
{-(Empty)-} {-(Empty)-}
{-(Call {-(Call
{-(MemberAccess
{-(Identifier)-} {-(Identifier)-}
{-(Identifier)-})-}
{-(Identifier)-} {-(Identifier)-}
{-(TextElement)-} {-(TextElement)-}
{-(Identifier)-} {-(Identifier)-}
@ -34,7 +36,9 @@
{-(Let {-(Let
{-(Empty)-} {-(Empty)-}
{-(Call {-(Call
{-(MemberAccess
{-(Identifier)-} {-(Identifier)-}
{-(Identifier)-})-}
{-(Identifier)-} {-(Identifier)-}
{-(TextElement)-} {-(TextElement)-}
{-(Identifier)-} {-(Identifier)-}

View File

@ -12,7 +12,9 @@
(Let (Let
(Empty) (Empty)
(Call (Call
(MemberAccess
(Identifier) (Identifier)
(Identifier))
(Identifier) (Identifier)
(TextElement) (TextElement)
(Identifier) (Identifier)
@ -21,7 +23,9 @@
(Let (Let
(Empty) (Empty)
(Call (Call
(MemberAccess
(Identifier) (Identifier)
(Identifier))
(Identifier) (Identifier)
(TextElement) (TextElement)
(Identifier) (Identifier)