mirror of
https://github.com/github/semantic.git
synced 2024-12-20 21:31:48 +03:00
Merge branch 'new-expressions' of https://github.com/github/semantic into new-expressions
This commit is contained in:
commit
9be3403d21
@ -172,7 +172,7 @@ defineSelf :: ( AbstractValue term address value m
|
|||||||
)
|
)
|
||||||
=> Evaluator term address value m ()
|
=> Evaluator term address value m ()
|
||||||
defineSelf = do
|
defineSelf = do
|
||||||
let self = Declaration $ X.name "__self"
|
let self = Declaration X.__semantic_self
|
||||||
-- TODO: Should `self` be given a special Relation?
|
-- TODO: Should `self` be given a special Relation?
|
||||||
declare self Default emptySpan Nothing
|
declare self Default emptySpan Nothing
|
||||||
slot <- lookupDeclaration self
|
slot <- lookupDeclaration self
|
||||||
|
@ -6,6 +6,7 @@ module Data.Abstract.Name
|
|||||||
, name
|
, name
|
||||||
, nameI
|
, nameI
|
||||||
, formatName
|
, formatName
|
||||||
|
, __semantic_self
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Effect
|
import Control.Effect
|
||||||
@ -70,3 +71,6 @@ instance Hashable Name where
|
|||||||
instance ToJSON Name where
|
instance ToJSON Name where
|
||||||
toJSON = toJSON . formatName
|
toJSON = toJSON . formatName
|
||||||
toEncoding = toEncoding . formatName
|
toEncoding = toEncoding . formatName
|
||||||
|
|
||||||
|
__semantic_self :: Name
|
||||||
|
__semantic_self = name "__self"
|
||||||
|
@ -94,7 +94,7 @@ instance ( FreeVariables term
|
|||||||
Abstract.BuiltIn associatedScope builtIn k -> runEvaluator $ do
|
Abstract.BuiltIn associatedScope builtIn k -> runEvaluator $ do
|
||||||
val <- closure Nothing [] (Left builtIn) associatedScope
|
val <- closure Nothing [] (Left builtIn) associatedScope
|
||||||
Evaluator $ runFunctionC (k val) eval
|
Evaluator $ runFunctionC (k val) eval
|
||||||
Abstract.Bind obj@(Object frame) (Closure packageInfo moduleInfo name _ names body scope parentFrame) k ->
|
Abstract.Bind obj (Closure packageInfo moduleInfo name _ names body scope parentFrame) k ->
|
||||||
runFunctionC (k (Closure packageInfo moduleInfo name (Just obj) names body scope parentFrame)) eval
|
runFunctionC (k (Closure packageInfo moduleInfo name (Just obj) names body scope parentFrame)) eval
|
||||||
Abstract.Bind _ value k -> runFunctionC (k value) eval
|
Abstract.Bind _ value k -> runFunctionC (k value) eval
|
||||||
Abstract.Call op params k -> runEvaluator $ do
|
Abstract.Call op params k -> runEvaluator $ do
|
||||||
@ -111,7 +111,7 @@ instance ( FreeVariables term
|
|||||||
withScopeAndFrame frameAddress $ do
|
withScopeAndFrame frameAddress $ do
|
||||||
case maybeThis of
|
case maybeThis of
|
||||||
Just object -> do
|
Just object -> do
|
||||||
slot <- lookupDeclaration (Declaration $ name "__self")
|
slot <- lookupDeclaration (Declaration __semantic_self)
|
||||||
assign slot object
|
assign slot object
|
||||||
Nothing -> pure ()
|
Nothing -> pure ()
|
||||||
for_ (zip names params) $ \(name, param) -> do
|
for_ (zip names params) $ \(name, param) -> do
|
||||||
|
@ -13,7 +13,7 @@ import Prologue
|
|||||||
import Proto3.Suite.Class
|
import Proto3.Suite.Class
|
||||||
import Reprinting.Tokenize hiding (Superclass)
|
import Reprinting.Tokenize hiding (Superclass)
|
||||||
import Data.Span (emptySpan)
|
import Data.Span (emptySpan)
|
||||||
import Data.Abstract.Name as Name
|
import Data.Abstract.Name (__semantic_self)
|
||||||
|
|
||||||
data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a }
|
data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a }
|
||||||
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1, Named1, Message1, NFData1)
|
deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, ToJSONFields1, Named1, Message1, NFData1)
|
||||||
@ -91,9 +91,8 @@ instance Evaluatable Method where
|
|||||||
associatedScope <- declareFunction name span
|
associatedScope <- declareFunction name span
|
||||||
|
|
||||||
params <- withScope associatedScope $ do
|
params <- withScope associatedScope $ do
|
||||||
let self = Name.name "__self"
|
|
||||||
-- TODO: Should we give `self` a special Relation?
|
-- TODO: Should we give `self` a special Relation?
|
||||||
declare (Declaration self) Default emptySpan Nothing
|
declare (Declaration __semantic_self) Default emptySpan Nothing
|
||||||
for methodParameters $ \paramNode -> do
|
for methodParameters $ \paramNode -> do
|
||||||
param <- maybeM (throwEvalError $ NoNameError paramNode) (declaredName paramNode)
|
param <- maybeM (throwEvalError $ NoNameError paramNode) (declaredName paramNode)
|
||||||
param <$ declare (Declaration param) Default span Nothing
|
param <$ declare (Declaration param) Default span Nothing
|
||||||
|
@ -701,6 +701,5 @@ instance Ord1 This where liftCompare = genericLiftCompare
|
|||||||
instance Show1 This where liftShowsPrec = genericLiftShowsPrec
|
instance Show1 This where liftShowsPrec = genericLiftShowsPrec
|
||||||
instance Evaluatable This where
|
instance Evaluatable This where
|
||||||
eval _ _ This = do
|
eval _ _ This = do
|
||||||
let name = Name.name "__self"
|
reference (Reference __semantic_self) (Declaration __semantic_self)
|
||||||
reference (Reference name) (Declaration name)
|
deref =<< lookupDeclaration (Declaration __semantic_self)
|
||||||
deref =<< lookupDeclaration (Declaration name)
|
|
||||||
|
@ -76,7 +76,7 @@ instance Evaluatable Send where
|
|||||||
Nothing ->
|
Nothing ->
|
||||||
pure (Name.name "call")
|
pure (Name.name "call")
|
||||||
|
|
||||||
let self = lookupDeclaration (Declaration $ Name.name "__self") >>= deref
|
let self = lookupDeclaration (Declaration __semantic_self) >>= deref
|
||||||
lhsValue <- maybe self eval sendReceiver
|
lhsValue <- maybe self eval sendReceiver
|
||||||
lhsFrame <- Abstract.scopedEnvironment lhsValue
|
lhsFrame <- Abstract.scopedEnvironment lhsValue
|
||||||
|
|
||||||
|
@ -101,7 +101,7 @@ spec config = parallel $ do
|
|||||||
(_, (_, res)) <- evaluate ["void.ts"]
|
(_, (_, res)) <- evaluate ["void.ts"]
|
||||||
case ModuleTable.lookup "void.ts" <$> res of
|
case ModuleTable.lookup "void.ts" <$> res of
|
||||||
Right (Just (Module _ (_, value))) -> value `shouldBe` Null
|
Right (Just (Module _ (_, value))) -> value `shouldBe` Null
|
||||||
other -> expectationFailure (show other)
|
other -> expectationFailure (show other)
|
||||||
|
|
||||||
it "evaluates delete" $ do
|
it "evaluates delete" $ do
|
||||||
(scopeGraph, (heap, res)) <- evaluate ["delete.ts"]
|
(scopeGraph, (heap, res)) <- evaluate ["delete.ts"]
|
||||||
@ -124,39 +124,44 @@ spec config = parallel $ do
|
|||||||
it "evaluates BOr statements" $ do
|
it "evaluates BOr statements" $ do
|
||||||
(_, (_, res)) <- evaluate ["bor.ts"]
|
(_, (_, res)) <- evaluate ["bor.ts"]
|
||||||
case ModuleTable.lookup "bor.ts" <$> res of
|
case ModuleTable.lookup "bor.ts" <$> res of
|
||||||
Right (Just (Module _ (_, value))) ->
|
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 3)
|
||||||
value `shouldBe` Value.Integer (Number.Integer 3)
|
other -> expectationFailure (show other)
|
||||||
other -> expectationFailure (show other)
|
|
||||||
|
|
||||||
it "evaluates BAnd statements" $ do
|
it "evaluates BAnd statements" $ do
|
||||||
(_, (_, res)) <- evaluate ["band.ts"]
|
(_, (_, res)) <- evaluate ["band.ts"]
|
||||||
case ModuleTable.lookup "band.ts" <$> res of
|
case ModuleTable.lookup "band.ts" <$> res of
|
||||||
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 0)
|
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 0)
|
||||||
other -> expectationFailure (show other)
|
other -> expectationFailure (show other)
|
||||||
|
|
||||||
it "evaluates BXOr statements" $ do
|
it "evaluates BXOr statements" $ do
|
||||||
(_, (_, res)) <- evaluate ["bxor.ts"]
|
(_, (_, res)) <- evaluate ["bxor.ts"]
|
||||||
case ModuleTable.lookup "bxor.ts" <$> res of
|
case ModuleTable.lookup "bxor.ts" <$> res of
|
||||||
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 3)
|
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 3)
|
||||||
other -> expectationFailure (show other)
|
other -> expectationFailure (show other)
|
||||||
|
|
||||||
it "evaluates LShift statements" $ do
|
it "evaluates LShift statements" $ do
|
||||||
(_, (_, res)) <- evaluate ["lshift.ts"]
|
(_, (_, res)) <- evaluate ["lshift.ts"]
|
||||||
case ModuleTable.lookup "lshift.ts" <$> res of
|
case ModuleTable.lookup "lshift.ts" <$> res of
|
||||||
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 4)
|
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 4)
|
||||||
other -> expectationFailure (show other)
|
other -> expectationFailure (show other)
|
||||||
|
|
||||||
it "evaluates RShift statements" $ do
|
it "evaluates RShift statements" $ do
|
||||||
(_, (_, res)) <- evaluate ["rshift.ts"]
|
(_, (_, res)) <- evaluate ["rshift.ts"]
|
||||||
case ModuleTable.lookup "rshift.ts" <$> res of
|
case ModuleTable.lookup "rshift.ts" <$> res of
|
||||||
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 0)
|
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 0)
|
||||||
other -> expectationFailure (show other)
|
other -> expectationFailure (show other)
|
||||||
|
|
||||||
it "evaluates Complement statements" $ do
|
it "evaluates Complement statements" $ do
|
||||||
(_, (_, res)) <- evaluate ["complement.ts"]
|
(_, (_, res)) <- evaluate ["complement.ts"]
|
||||||
case ModuleTable.lookup "complement.ts" <$> res of
|
case ModuleTable.lookup "complement.ts" <$> res of
|
||||||
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer (-2))
|
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer (-2))
|
||||||
other -> expectationFailure (show other)
|
other -> expectationFailure (show other)
|
||||||
|
|
||||||
|
it "uniquely tracks public fields for instances" $ do
|
||||||
|
(scopeGraph, (heap, res)) <- evaluate ["class1.ts", "class2.ts"]
|
||||||
|
case ModuleTable.lookup "class1.ts" <$> res of
|
||||||
|
Right (Just (Module _ (_, value))) -> value `shouldBe` (float 9.0)
|
||||||
|
other -> expectationFailure (show other)
|
||||||
|
|
||||||
|
|
||||||
where
|
where
|
||||||
|
@ -35,9 +35,9 @@ spec = parallel $ do
|
|||||||
let lexicalEdges = Map.singleton Lexical [ currentScope' ]
|
let lexicalEdges = Map.singleton Lexical [ currentScope' ]
|
||||||
x = SpecHelpers.name "x"
|
x = SpecHelpers.name "x"
|
||||||
associatedScope <- newScope lexicalEdges
|
associatedScope <- newScope lexicalEdges
|
||||||
declare (ScopeGraph.Declaration "identity") emptySpan (Just associatedScope)
|
declare (ScopeGraph.Declaration "identity") Default emptySpan (Just associatedScope)
|
||||||
withScope associatedScope $ do
|
withScope associatedScope $ do
|
||||||
declare (Declaration x) emptySpan Nothing
|
declare (Declaration x) Default emptySpan Nothing
|
||||||
identity <- function "identity" [ x ]
|
identity <- function "identity" [ x ]
|
||||||
(SpecEff (Heap.lookupDeclaration (ScopeGraph.Declaration (SpecHelpers.name "x")) >>= deref)) associatedScope
|
(SpecEff (Heap.lookupDeclaration (ScopeGraph.Declaration (SpecHelpers.name "x")) >>= deref)) associatedScope
|
||||||
val <- pure (integer 123)
|
val <- pure (integer 123)
|
||||||
|
Loading…
Reference in New Issue
Block a user