1
1
mirror of https://github.com/github/semantic.git synced 2024-12-19 12:51:52 +03:00
semantic/test/Analysis/Ruby/Spec.hs

106 lines
5.1 KiB
Haskell
Raw Normal View History

2018-03-14 02:19:26 +03:00
module Analysis.Ruby.Spec (spec) where
2018-06-26 00:28:35 +03:00
import qualified Data.Abstract.ModuleTable as ModuleTable
2018-04-19 10:09:30 +03:00
import Data.Abstract.Number as Number
import Data.Abstract.Value.Concrete as Value
2018-10-24 17:11:27 +03:00
import Control.Effect.Resumable (SomeError(..))
2018-03-28 19:58:12 +03:00
import Data.List.NonEmpty (NonEmpty(..))
2018-05-07 23:56:40 +03:00
import Data.Sum
2018-04-24 02:47:13 +03:00
import qualified Data.Language as Language
import Data.Abstract.Evaluatable
2018-11-09 02:22:35 +03:00
import Control.Abstract (ScopeError(..), Declaration(..))
2018-03-14 02:19:26 +03:00
import SpecHelpers
spec :: TaskConfig -> Spec
spec config = parallel $ do
describe "Ruby" $ do
2018-06-26 00:28:35 +03:00
it "evaluates require_relative" $ do
(scopeGraph, (heap, res)) <- evaluate ["main.rb", "foo.rb"]
2018-06-26 00:28:35 +03:00
case ModuleTable.lookup "main.rb" <$> res of
Right (Just (Module _ (scopeAndFrame, valueRef) :| [])) -> do
2018-11-09 02:22:35 +03:00
valueRef `shouldBe` Rval (Value.Integer (Number.Integer 1))
2018-11-29 04:38:52 +03:00
const () <$> SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
2018-06-26 00:28:35 +03:00
other -> expectationFailure (show other)
it "evaluates load" $ do
2018-11-29 03:59:05 +03:00
(scopeGraph, (heap, res)) <- evaluate ["load.rb", "foo.rb"]
2018-06-26 00:28:35 +03:00
case ModuleTable.lookup "load.rb" <$> res of
2018-11-29 03:59:05 +03:00
Right (Just (Module _ (scopeAndFrame, valueRef) :| [])) -> do
2018-11-09 02:22:35 +03:00
valueRef `shouldBe` Rval (Value.Integer (Number.Integer 1))
2018-11-29 03:59:05 +03:00
const () <$> SpecHelpers.lookupDeclaration "foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
2018-06-26 00:28:35 +03:00
other -> expectationFailure (show other)
it "evaluates load with wrapper" $ do
2018-11-29 03:59:05 +03:00
(_, (_, res)) <- evaluate ["load-wrap.rb", "foo.rb"]
2018-11-09 02:22:35 +03:00
res `shouldBe` Left (SomeError (inject @(BaseError (ScopeError Precise)) (BaseError (ModuleInfo "load-wrap.rb") emptySpan (ScopeError (Declaration "foo") emptySpan))))
2018-06-26 00:28:35 +03:00
it "evaluates subclass" $ do
2018-11-29 03:59:05 +03:00
(scopeGraph, (heap, res)) <- evaluate ["subclass.rb"]
2018-06-26 00:28:35 +03:00
case ModuleTable.lookup "subclass.rb" <$> res of
2018-11-29 03:59:05 +03:00
Right (Just (Module _ (scopeAndFrame, valueRef) :| [])) -> do
2018-11-09 02:22:35 +03:00
valueRef `shouldBe` Rval (String "\"<bar>\"")
2018-11-29 03:59:05 +03:00
const () <$> SpecHelpers.lookupDeclaration "Bar" scopeAndFrame heap scopeGraph `shouldBe` Just ()
const () <$> SpecHelpers.lookupDeclaration "Foo" scopeAndFrame heap scopeGraph `shouldBe` Just ()
2018-06-26 00:28:35 +03:00
2018-11-09 02:22:35 +03:00
-- (lookupDeclaration "Bar" heap >>= deNamespace heap) `shouldBe` Just ("Bar", ["baz", "inspect", "foo"])
2018-06-26 00:28:35 +03:00
other -> expectationFailure (show other)
it "evaluates modules" $ do
2018-11-29 03:59:05 +03:00
(scopeGraph, (heap, res)) <- evaluate ["modules.rb"]
2018-06-26 00:28:35 +03:00
case ModuleTable.lookup "modules.rb" <$> res of
2018-11-29 03:59:05 +03:00
Right (Just (Module _ (scopeAndFrame, valueRef) :| [])) -> do
2018-11-09 02:22:35 +03:00
valueRef `shouldBe` Rval (String "\"<hello>\"")
2018-11-29 03:59:05 +03:00
const () <$> SpecHelpers.lookupDeclaration "Bar" scopeAndFrame heap scopeGraph `shouldBe` Just ()
2018-06-26 00:28:35 +03:00
other -> expectationFailure (show other)
it "handles break correctly" $ do
2018-11-29 03:59:05 +03:00
(_, (_, res)) <- evaluate ["break.rb"]
2018-06-26 00:28:35 +03:00
case ModuleTable.lookup "break.rb" <$> res of
2018-11-29 03:59:05 +03:00
Right (Just (Module _ (_, valueRef) :| [])) -> valueRef `shouldBe` Rval (Value.Integer (Number.Integer 3))
2018-06-26 00:28:35 +03:00
other -> expectationFailure (show other)
it "handles next correctly" $ do
2018-11-29 03:59:05 +03:00
(_, (_, res)) <- evaluate ["next.rb"]
2018-06-26 00:28:35 +03:00
case ModuleTable.lookup "next.rb" <$> res of
2018-11-29 03:59:05 +03:00
Right (Just (Module _ (_, valueRef) :| [])) -> valueRef `shouldBe` Rval (Value.Integer (Number.Integer 8))
2018-06-26 00:28:35 +03:00
other -> expectationFailure (show other)
it "calls functions with arguments" $ do
2018-11-29 03:59:05 +03:00
(_, (_, res)) <- evaluate ["call.rb"]
2018-06-26 00:28:35 +03:00
case ModuleTable.lookup "call.rb" <$> res of
2018-11-29 03:59:05 +03:00
Right (Just (Module _ (_, valueRef) :| [])) -> valueRef `shouldBe` Rval (Value.Integer (Number.Integer 579))
2018-06-26 00:28:35 +03:00
other -> expectationFailure (show other)
it "evaluates early return statements" $ do
2018-11-29 03:59:05 +03:00
(_, (_, res)) <- evaluate ["early-return.rb"]
2018-06-26 00:28:35 +03:00
case ModuleTable.lookup "early-return.rb" <$> res of
2018-11-29 03:59:05 +03:00
Right (Just (Module _ (_, valueRef) :| [])) -> valueRef `shouldBe` Rval (Value.Integer (Number.Integer 123))
2018-06-26 00:28:35 +03:00
other -> expectationFailure (show other)
it "has prelude" $ do
2018-11-29 03:59:05 +03:00
(_, (_, res)) <- evaluate ["preluded.rb"]
2018-06-26 00:28:35 +03:00
case ModuleTable.lookup "preluded.rb" <$> res of
2018-11-29 03:59:05 +03:00
Right (Just (Module _ (_, valueRef) :| [])) -> valueRef `shouldBe` Rval (String "\"<foo>\"")
2018-06-26 00:28:35 +03:00
other -> expectationFailure (show other)
it "evaluates __LINE__" $ do
2018-11-29 03:59:05 +03:00
(_, (_, res)) <- evaluate ["line.rb"]
2018-06-26 00:28:35 +03:00
case ModuleTable.lookup "line.rb" <$> res of
2018-11-29 03:59:05 +03:00
Right (Just (Module _ (_, valueRef) :| [])) -> valueRef `shouldBe` Rval (Value.Integer (Number.Integer 4))
2018-06-26 00:28:35 +03:00
other -> expectationFailure (show other)
it "resolves builtins used in the prelude" $ do
2018-11-29 03:59:05 +03:00
(scopeGraph, (heap, res)) <- evaluate ["puts.rb"]
2018-06-26 00:28:35 +03:00
case ModuleTable.lookup "puts.rb" <$> res of
2018-11-29 03:59:05 +03:00
Right (Just (Module _ (scopeAndFrame, valueRef) :| [])) -> do
2018-11-09 02:22:35 +03:00
valueRef `shouldBe` Rval Unit
2018-11-29 03:59:05 +03:00
const () <$> SpecHelpers.lookupDeclaration "puts" scopeAndFrame heap scopeGraph `shouldBe` Just ()
2018-06-26 00:28:35 +03:00
other -> expectationFailure (show other)
2018-05-10 18:03:42 +03:00
2018-03-14 02:19:26 +03:00
where
fixtures = "test/fixtures/ruby/analysis/"
evaluate = evalRubyProject . map (fixtures <>)
2018-08-02 17:24:55 +03:00
evalRubyProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Ruby) rubyParser