2018-03-14 02:19:26 +03:00
|
|
|
module Analysis.Ruby.Spec (spec) where
|
|
|
|
|
2018-05-10 16:08:12 +03:00
|
|
|
import Data.Abstract.Environment as Env
|
2018-04-22 17:47:59 +03:00
|
|
|
import Data.Abstract.Evaluatable
|
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
|
2018-07-03 21:22:26 +03:00
|
|
|
import Data.Abstract.Value.Concrete as Value
|
2018-05-28 16:55:01 +03:00
|
|
|
import Data.AST
|
2018-03-28 19:58:12 +03:00
|
|
|
import Control.Monad.Effect (SomeExc(..))
|
|
|
|
import Data.List.NonEmpty (NonEmpty(..))
|
2018-05-07 23:56:40 +03:00
|
|
|
import Data.Sum
|
2018-04-21 17:22:09 +03:00
|
|
|
import qualified Language.Ruby.Assignment as Ruby
|
2018-04-24 02:47:13 +03:00
|
|
|
import qualified Data.Language as Language
|
2018-03-14 02:19:26 +03:00
|
|
|
|
|
|
|
import SpecHelpers
|
|
|
|
|
|
|
|
|
2018-07-10 21:09:22 +03:00
|
|
|
spec :: TaskConfig -> Spec
|
|
|
|
spec config = parallel $ do
|
2018-03-26 21:09:22 +03:00
|
|
|
describe "Ruby" $ do
|
2018-06-26 00:28:35 +03:00
|
|
|
it "evaluates require_relative" $ do
|
2018-06-26 22:14:28 +03:00
|
|
|
(_, (heap, res)) <- evaluate ["main.rb", "foo.rb"]
|
2018-06-26 00:28:35 +03:00
|
|
|
case ModuleTable.lookup "main.rb" <$> res of
|
2018-06-26 22:14:28 +03:00
|
|
|
Right (Just (Module _ (env, addr) :| [])) -> do
|
2018-06-26 00:28:35 +03:00
|
|
|
heapLookupAll addr heap `shouldBe` Just [Value.Integer (Number.Integer 1)]
|
|
|
|
Env.names env `shouldContain` [ "foo" ]
|
|
|
|
other -> expectationFailure (show other)
|
|
|
|
|
|
|
|
it "evaluates load" $ do
|
2018-06-26 22:14:28 +03:00
|
|
|
(_, (heap, res)) <- evaluate ["load.rb", "foo.rb"]
|
2018-06-26 00:28:35 +03:00
|
|
|
case ModuleTable.lookup "load.rb" <$> res of
|
2018-06-26 22:14:28 +03:00
|
|
|
Right (Just (Module _ (env, addr) :| [])) -> do
|
2018-06-26 00:28:35 +03:00
|
|
|
heapLookupAll addr heap `shouldBe` Just [Value.Integer (Number.Integer 1)]
|
|
|
|
Env.names env `shouldContain` [ "foo" ]
|
|
|
|
other -> expectationFailure (show other)
|
|
|
|
|
|
|
|
it "evaluates load with wrapper" $ do
|
2018-06-26 22:14:28 +03:00
|
|
|
(_, (_, res)) <- evaluate ["load-wrap.rb", "foo.rb"]
|
2018-06-26 00:28:35 +03:00
|
|
|
res `shouldBe` Left (SomeExc (inject @(EnvironmentError Precise) (FreeVariable "foo")))
|
|
|
|
|
|
|
|
it "evaluates subclass" $ do
|
2018-06-26 22:14:28 +03:00
|
|
|
(_, (heap, res)) <- evaluate ["subclass.rb"]
|
2018-06-26 00:28:35 +03:00
|
|
|
case ModuleTable.lookup "subclass.rb" <$> res of
|
2018-06-26 22:14:28 +03:00
|
|
|
Right (Just (Module _ (env, addr) :| [])) -> do
|
2018-06-26 00:28:35 +03:00
|
|
|
heapLookupAll addr heap `shouldBe` Just [String "\"<bar>\""]
|
|
|
|
Env.names env `shouldContain` [ "Bar", "Foo" ]
|
|
|
|
|
2018-07-19 10:03:17 +03:00
|
|
|
(derefQName heap ("Bar" :| []) env >>= deNamespace heap) `shouldBe` Just ("Bar", ["baz", "foo", "inspect"])
|
2018-06-26 00:28:35 +03:00
|
|
|
other -> expectationFailure (show other)
|
|
|
|
|
|
|
|
it "evaluates modules" $ do
|
2018-06-26 22:14:28 +03:00
|
|
|
(_, (heap, res)) <- evaluate ["modules.rb"]
|
2018-06-26 00:28:35 +03:00
|
|
|
case ModuleTable.lookup "modules.rb" <$> res of
|
2018-06-26 22:14:28 +03:00
|
|
|
Right (Just (Module _ (env, addr) :| [])) -> do
|
2018-06-26 00:28:35 +03:00
|
|
|
heapLookupAll addr heap `shouldBe` Just [String "\"<hello>\""]
|
|
|
|
Env.names env `shouldContain` [ "Bar" ]
|
|
|
|
other -> expectationFailure (show other)
|
|
|
|
|
|
|
|
it "handles break correctly" $ do
|
2018-06-26 22:14:28 +03:00
|
|
|
(_, (heap, res)) <- evaluate ["break.rb"]
|
2018-06-26 00:28:35 +03:00
|
|
|
case ModuleTable.lookup "break.rb" <$> res of
|
2018-06-26 22:14:28 +03:00
|
|
|
Right (Just (Module _ (env, addr) :| [])) -> heapLookupAll addr heap `shouldBe` Just [Value.Integer (Number.Integer 3)]
|
2018-06-26 00:28:35 +03:00
|
|
|
other -> expectationFailure (show other)
|
|
|
|
|
|
|
|
it "handles next correctly" $ do
|
2018-06-26 22:14:28 +03:00
|
|
|
(_, (heap, res)) <- evaluate ["next.rb"]
|
2018-06-26 00:28:35 +03:00
|
|
|
case ModuleTable.lookup "next.rb" <$> res of
|
2018-06-26 22:14:28 +03:00
|
|
|
Right (Just (Module _ (env, addr) :| [])) -> heapLookupAll addr heap `shouldBe` Just [Value.Integer (Number.Integer 8)]
|
2018-06-26 00:28:35 +03:00
|
|
|
other -> expectationFailure (show other)
|
|
|
|
|
|
|
|
it "calls functions with arguments" $ do
|
2018-06-26 22:14:28 +03:00
|
|
|
(_, (heap, res)) <- evaluate ["call.rb"]
|
2018-06-26 00:28:35 +03:00
|
|
|
case ModuleTable.lookup "call.rb" <$> res of
|
2018-06-26 22:14:28 +03:00
|
|
|
Right (Just (Module _ (env, addr) :| [])) -> heapLookupAll addr heap `shouldBe` Just [Value.Integer (Number.Integer 579)]
|
2018-06-26 00:28:35 +03:00
|
|
|
other -> expectationFailure (show other)
|
|
|
|
|
|
|
|
it "evaluates early return statements" $ do
|
2018-06-26 22:14:28 +03:00
|
|
|
(_, (heap, res)) <- evaluate ["early-return.rb"]
|
2018-06-26 00:28:35 +03:00
|
|
|
case ModuleTable.lookup "early-return.rb" <$> res of
|
2018-06-26 22:14:28 +03:00
|
|
|
Right (Just (Module _ (env, addr) :| [])) -> heapLookupAll addr heap `shouldBe` Just [Value.Integer (Number.Integer 123)]
|
2018-06-26 00:28:35 +03:00
|
|
|
other -> expectationFailure (show other)
|
|
|
|
|
|
|
|
it "has prelude" $ do
|
2018-06-26 22:14:28 +03:00
|
|
|
(_, (heap, res)) <- evaluate ["preluded.rb"]
|
2018-06-26 00:28:35 +03:00
|
|
|
case ModuleTable.lookup "preluded.rb" <$> res of
|
2018-06-26 22:14:28 +03:00
|
|
|
Right (Just (Module _ (env, addr) :| [])) -> heapLookupAll addr heap `shouldBe` Just [String "\"<foo>\""]
|
2018-06-26 00:28:35 +03:00
|
|
|
other -> expectationFailure (show other)
|
|
|
|
|
|
|
|
it "evaluates __LINE__" $ do
|
2018-06-26 22:14:28 +03:00
|
|
|
(_, (heap, res)) <- evaluate ["line.rb"]
|
2018-06-26 00:28:35 +03:00
|
|
|
case ModuleTable.lookup "line.rb" <$> res of
|
2018-06-26 22:14:28 +03:00
|
|
|
Right (Just (Module _ (env, addr) :| [])) -> heapLookupAll addr heap `shouldBe` Just [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-06-26 22:14:28 +03:00
|
|
|
(traces, (heap, res)) <- evaluate ["puts.rb"]
|
2018-06-26 00:28:35 +03:00
|
|
|
case ModuleTable.lookup "puts.rb" <$> res of
|
2018-06-26 22:14:28 +03:00
|
|
|
Right (Just (Module _ (env, addr) :| [])) -> do
|
2018-06-26 00:28:35 +03:00
|
|
|
heapLookupAll addr heap `shouldBe` Just [Unit]
|
|
|
|
traces `shouldContain` [ "\"hello\"" ]
|
|
|
|
other -> expectationFailure (show other)
|
2018-05-10 18:03:42 +03:00
|
|
|
|
2018-03-14 02:19:26 +03:00
|
|
|
where
|
2018-05-28 15:54:33 +03:00
|
|
|
ns n = Just . Latest . Last . Just . Namespace n
|
2018-03-14 02:19:26 +03:00
|
|
|
fixtures = "test/fixtures/ruby/analysis/"
|
2018-06-22 22:45:42 +03:00
|
|
|
evaluate = evalRubyProject . map (fixtures <>)
|
2018-07-10 21:09:22 +03:00
|
|
|
evalRubyProject = testEvaluating <=< evaluateProject' config (Proxy :: Proxy 'Language.Ruby) rubyParser Language.Ruby
|