mirror of
https://github.com/github/semantic.git
synced 2024-12-24 23:42:31 +03:00
Add valueRef tests back
This commit is contained in:
parent
60ad7e7263
commit
a2026e8ada
@ -196,11 +196,11 @@ lookupDeclaration declaration scope g = do
|
||||
index <- Seq.findIndexR (((Declaration declaration) ==) . fst) dataSeq
|
||||
(, Position index) <$> Seq.lookup index dataSeq
|
||||
|
||||
declarationNames :: Ord address => [EdgeLabel] -> Scope address -> ScopeGraph address -> [Declaration]
|
||||
declarationNames :: Ord address => [EdgeLabel] -> Scope address -> ScopeGraph address -> Set Declaration
|
||||
declarationNames edgeLabels scope scopeGraph = localDeclarations <> edgeNames
|
||||
where addresses = join (Map.elems $ Map.restrictKeys (edges scope) (Set.fromList edgeLabels))
|
||||
edgeNames = addresses >>= toList . flip lookupScope scopeGraph >>= flip (declarationNames edgeLabels) scopeGraph
|
||||
localDeclarations = toList . fmap fst $ declarations scope
|
||||
edgeNames = flip foldMap addresses $ \address -> maybe mempty (flip (declarationNames edgeLabels) scopeGraph) (lookupScope address scopeGraph)
|
||||
localDeclarations = Set.fromList . toList . fmap fst $ declarations scope
|
||||
|
||||
|
||||
putDeclarationScopeAtPosition :: Ord scopeAddress => scopeAddress -> Position -> Maybe scopeAddress -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
|
||||
|
@ -20,7 +20,7 @@ spec config = parallel $ do
|
||||
it "evaluates require_relative" $ do
|
||||
(scopeGraph, (heap, res)) <- evaluate ["main.rb", "foo.rb"]
|
||||
case ModuleTable.lookup "main.rb" <$> res of
|
||||
Right (Just (Module _ (scopeAndFrame, _) :| [])) -> do
|
||||
Right (Just (Module _ (scopeAndFrame, valueRef) :| [])) -> do
|
||||
valueRef `shouldBe` Rval (Value.Integer (Number.Integer 1))
|
||||
() <$ SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
|
||||
other -> expectationFailure (show other)
|
||||
@ -28,7 +28,7 @@ spec config = parallel $ do
|
||||
it "evaluates load" $ do
|
||||
(scopeGraph, (heap, res)) <- evaluate ["load.rb", "foo.rb"]
|
||||
case ModuleTable.lookup "load.rb" <$> res of
|
||||
Right (Just (Module _ (scopeAndFrame, _) :| [])) -> do
|
||||
Right (Just (Module _ (scopeAndFrame, valueRef) :| [])) -> do
|
||||
valueRef `shouldBe` Rval (Value.Integer (Number.Integer 1))
|
||||
() <$ SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
|
||||
other -> expectationFailure (show other)
|
||||
@ -44,8 +44,7 @@ spec config = parallel $ do
|
||||
valueRef `shouldBe` Rval (String "\"<bar>\"")
|
||||
() <$ SpecHelpers.lookupDeclaration "Bar" scopeAndFrame heap scopeGraph `shouldBe` Just ()
|
||||
() <$ SpecHelpers.lookupDeclaration "Foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
|
||||
|
||||
-- (lookupDeclaration "Bar" heap >>= deNamespace heap) `shouldBe` Just ("Bar", ["baz", "inspect", "foo"])
|
||||
SpecHelpers.lookupMembers "Bar" Superclass scopeAndFrame heap scopeGraph `shouldBe` Just ["baz", "foo", "inspect"]
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "evaluates modules" $ do
|
||||
|
@ -39,8 +39,8 @@ spec config = parallel $ do
|
||||
-- Env.names env `shouldBe` [ "b", "z" ]
|
||||
() <$ SpecHelpers.lookupDeclaration "b" scopeAndFrame heap scopeGraph `shouldBe` Just ()
|
||||
() <$ SpecHelpers.lookupDeclaration "z" scopeAndFrame heap scopeGraph `shouldBe` Just ()
|
||||
lookupMembers "b" Import scopeAndFrame heap scopeGraph `shouldBe` Just [ "foo", "baz" ]
|
||||
lookupMembers "z" Import scopeAndFrame heap scopeGraph `shouldBe` Just [ "foo", "baz" ]
|
||||
lookupMembers "b" Import scopeAndFrame heap scopeGraph `shouldBe` Just [ "baz", "foo" ]
|
||||
lookupMembers "z" Import scopeAndFrame heap scopeGraph `shouldBe` Just [ "baz", "foo" ]
|
||||
-- (Heap.lookupDeclaration "b" heap >>= deNamespace heap) `shouldBe` Just ("b", [ "baz", "foo" ])
|
||||
-- (Heap.lookupDeclaration "z" heap >>= deNamespace heap) `shouldBe` Just ("z", [ "baz", "foo" ])
|
||||
() <$ SpecHelpers.lookupDeclaration "baz" scopeAndFrame heap scopeGraph `shouldBe` Nothing
|
||||
|
@ -179,7 +179,7 @@ frameNames :: [ EdgeLabel ]
|
||||
frameNames edge heap scopeGraph frame = do
|
||||
scopeAddress <- Heap.scopeLookup frame heap
|
||||
scope <- ScopeGraph.lookupScope scopeAddress scopeGraph
|
||||
pure (unDeclaration <$> ScopeGraph.declarationNames edge scope scopeGraph)
|
||||
pure (unDeclaration <$> toList (ScopeGraph.declarationNames edge scope scopeGraph))
|
||||
|
||||
lookupMembers :: Name -> EdgeLabel -> (Precise, Precise) -> Heap Precise Precise (Value term Precise) -> ScopeGraph Precise -> Maybe [ Name ]
|
||||
lookupMembers name edgeLabel scopeAndFrame heap scopeGraph =
|
||||
|
Loading…
Reference in New Issue
Block a user