mirror of
https://github.com/github/semantic.git
synced 2024-12-24 23:42:31 +03:00
Deref slots in evalRubyProject
Co-Authored-By: Rob Rix <rob.rix@github.com>
This commit is contained in:
parent
1914a94500
commit
73ae9f85a1
@ -109,7 +109,7 @@ evaluateProject' (TaskConfig config logger statter) proxy parser paths = either
|
||||
(runModuleTable
|
||||
(runModules (ModuleTable.modulePaths (packageModules package))
|
||||
(raiseHandler (runReader (packageInfo package))
|
||||
(raiseHandler (runState (lowerBound @Span))
|
||||
(raiseHandler (evalState (lowerBound @Span))
|
||||
(raiseHandler (runReader (lowerBound @Span))
|
||||
(evaluate proxy id (evalTerm withTermSpans) modules)))))))
|
||||
|
||||
@ -122,7 +122,7 @@ evaluatePythonProjects proxy parser lang path = runTaskWithOptions debugOptions
|
||||
(runModuleTable
|
||||
(runModules (ModuleTable.modulePaths (packageModules package))
|
||||
(raiseHandler (runReader (packageInfo package))
|
||||
(raiseHandler (runState (lowerBound @Span))
|
||||
(raiseHandler (evalState (lowerBound @Span))
|
||||
(raiseHandler (runReader (lowerBound @Span))
|
||||
(evaluate proxy id (evalTerm withTermSpans) modules)))))))
|
||||
|
||||
@ -133,7 +133,7 @@ evaluateProjectWithCaching proxy parser path = runTaskWithOptions debugOptions $
|
||||
modules <- topologicalSort <$> runImportGraphToModules proxy package
|
||||
pure (id @(Evaluator _ Monovariant _ _ _)
|
||||
(raiseHandler (runReader (packageInfo package))
|
||||
(raiseHandler (runState (lowerBound @Span))
|
||||
(raiseHandler (evalState (lowerBound @Span))
|
||||
(raiseHandler (runReader (lowerBound @Span))
|
||||
(runModuleTable
|
||||
(runModules (ModuleTable.modulePaths (packageModules package))
|
||||
|
@ -1,15 +1,15 @@
|
||||
{-# LANGUAGE TupleSections #-}
|
||||
module Analysis.Ruby.Spec (spec) where
|
||||
|
||||
import Control.Abstract (Declaration (..), ScopeError (..), runDeref, value)
|
||||
import Control.Effect.Resumable (SomeError (..))
|
||||
import Data.Abstract.Evaluatable
|
||||
import qualified Data.Abstract.ModuleTable as ModuleTable
|
||||
import Data.Abstract.Number as Number
|
||||
import Data.Abstract.Value.Concrete as Value
|
||||
import Control.Effect.Resumable (SomeError(..))
|
||||
import Data.List.NonEmpty (NonEmpty(..))
|
||||
import Data.Sum
|
||||
import Data.Abstract.Number as Number
|
||||
import Data.Abstract.Value.Concrete as Value
|
||||
import qualified Data.Language as Language
|
||||
import Data.Abstract.Evaluatable
|
||||
import Control.Abstract (ScopeError(..), Declaration(..), value)
|
||||
import Data.List.NonEmpty (NonEmpty (..))
|
||||
import Data.Sum
|
||||
|
||||
import SpecHelpers
|
||||
|
||||
@ -57,37 +57,37 @@ spec config = parallel $ do
|
||||
(_, (_, res)) <- evaluate ["break.rb"]
|
||||
case ModuleTable.lookup "break.rb" <$> res of
|
||||
Right (Just (Module _ (_, valueRef) :| [])) -> valueRef `shouldBe` Rval (Value.Integer (Number.Integer 3))
|
||||
other -> expectationFailure (show other)
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "handles next correctly" $ do
|
||||
(_, (_, res)) <- evaluate ["next.rb"]
|
||||
case ModuleTable.lookup "next.rb" <$> res of
|
||||
Right (Just (Module _ (_, valueRef) :| [])) -> valueRef `shouldBe` Rval (Value.Integer (Number.Integer 8))
|
||||
other -> expectationFailure (show other)
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "calls functions with arguments" $ do
|
||||
(_, (_, res)) <- evaluate ["call.rb"]
|
||||
case ModuleTable.lookup "call.rb" <$> res of
|
||||
Right (Just (Module _ (_, valueRef) :| [])) -> valueRef `shouldBe` Rval (Value.Integer (Number.Integer 579))
|
||||
other -> expectationFailure (show other)
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "evaluates early return statements" $ do
|
||||
(_, (_, res)) <- evaluate ["early-return.rb"]
|
||||
case ModuleTable.lookup "early-return.rb" <$> res of
|
||||
Right (Just (Module _ (_, valueRef) :| [])) -> valueRef `shouldBe` Rval (Value.Integer (Number.Integer 123))
|
||||
other -> expectationFailure (show other)
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "has prelude" $ do
|
||||
(_, (_, res)) <- evaluate ["preluded.rb"]
|
||||
case ModuleTable.lookup "preluded.rb" <$> res of
|
||||
Right (Just (Module _ (_, valueRef) :| [])) -> valueRef `shouldBe` Rval (String "\"<foo>\"")
|
||||
other -> expectationFailure (show other)
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "evaluates __LINE__" $ do
|
||||
(_, (_, res)) <- evaluate ["line.rb"]
|
||||
case ModuleTable.lookup "line.rb" <$> res of
|
||||
Right (Just (Module _ (_, valueRef) :| [])) -> valueRef `shouldBe` Rval (Value.Integer (Number.Integer 4))
|
||||
other -> expectationFailure (show other)
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "resolves builtins used in the prelude" $ do
|
||||
(scopeGraph, (heap, res)) <- evaluate ["puts.rb"]
|
||||
@ -100,4 +100,11 @@ spec config = parallel $ do
|
||||
where
|
||||
fixtures = "test/fixtures/ruby/analysis/"
|
||||
evaluate = evalRubyProject . map (fixtures <>)
|
||||
evalRubyProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Ruby) rubyParser
|
||||
evalRubyProject files = testEvaluating =<< do
|
||||
action <- evaluateProject' config (Proxy :: Proxy 'Language.Ruby) rubyParser files
|
||||
pure $ do
|
||||
moduleTable <- action
|
||||
for moduleTable (traverse (\ (Module info (scopeAndFrame, valueRef)) -> do
|
||||
|
||||
valueRef' <- raiseHandler (runReader info . runReader emptySpan) (runDeref (value valueRef >>= rvalBox))
|
||||
pure (Module info (scopeAndFrame, valueRef'))))
|
||||
|
@ -26,6 +26,7 @@ import qualified Data.Abstract.Heap as Heap
|
||||
import Control.Arrow ((&&&))
|
||||
import Control.Effect.Trace as X (runTraceByIgnoring, runTraceByReturning)
|
||||
import Control.Monad ((>=>))
|
||||
import Data.Traversable as X (for)
|
||||
import Data.Abstract.Address.Precise as X
|
||||
import Data.Abstract.Evaluatable hiding (lookupDeclaration)
|
||||
import Data.Abstract.FreeVariables as X
|
||||
@ -136,7 +137,7 @@ type TestEvaluatingErrors term
|
||||
, BaseError (UnspecializedError (Val term))
|
||||
, BaseError (LoadError Precise (Val term))
|
||||
]
|
||||
testEvaluating :: Evaluator term Precise (Val term) (TestEvaluatingC term) (Span, a)
|
||||
testEvaluating :: Evaluator term Precise (Val term) (TestEvaluatingC term) a
|
||||
-> IO
|
||||
(ScopeGraph Precise,
|
||||
(Heap Precise Precise (Value term Precise),
|
||||
@ -157,7 +158,6 @@ testEvaluating
|
||||
. runResolutionError
|
||||
. runValueError
|
||||
. runAddressError
|
||||
. fmap snd
|
||||
|
||||
type Val term = Value term Precise
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user