1
1
mirror of https://github.com/github/semantic.git synced 2024-12-20 05:11:44 +03:00
semantic/test/Analysis/Ruby/Spec.hs

63 lines
2.1 KiB
Haskell
Raw Normal View History

2018-03-16 23:58:15 +03:00
{-# LANGUAGE OverloadedLists #-}
2018-03-14 02:19:26 +03:00
module Analysis.Ruby.Spec (spec) where
2018-03-28 19:58:12 +03:00
import Data.Abstract.Evaluatable (EvalError(..))
2018-03-14 02:19:26 +03:00
import Data.Abstract.Value
2018-03-28 19:58:12 +03:00
import Control.Monad.Effect (SomeExc(..))
import Data.List.NonEmpty (NonEmpty(..))
2018-03-14 02:19:26 +03:00
import Data.Map
import Data.Map.Monoidal as Map
2018-03-14 02:19:26 +03:00
import SpecHelpers
spec :: Spec
spec = parallel $ do
describe "Ruby" $ do
it "evaluates require_relative" $ do
env <- environment . snd <$> evaluate "main.rb"
env `shouldBe` [ ("Object", addr 0)
, ("foo", addr 3) ]
2018-03-14 02:19:26 +03:00
2018-03-28 01:18:38 +03:00
it "evaluates load" $ do
env <- environment . snd <$> evaluate "load.rb"
env `shouldBe` [ ("Object", addr 0)
, ("foo", addr 3) ]
2018-03-16 01:09:07 +03:00
2018-03-28 01:18:38 +03:00
it "evaluates load with wrapper" $ do
2018-03-23 20:11:29 +03:00
res <- evaluate "load-wrap.rb"
fst res `shouldBe` Right (Right (Right (Right (Left (SomeExc (FreeVariableError ("foo")))))))
environment (snd res) `shouldBe` [ ("Object", addr 0) ]
2018-03-16 01:09:07 +03:00
2018-03-28 01:18:38 +03:00
it "evaluates subclass" $ do
res <- evaluate "subclass.rb"
fst res `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"<bar>\""))))))
environment (snd res) `shouldBe` [ ("Bar", addr 6)
, ("Foo", addr 3)
, ("Object", addr 0) ]
heapLookup (Address (Precise 6)) (heap (snd res))
`shouldBe` ns "Bar" [ ("baz", addr 8)
, ("foo", addr 5)
, ("inspect", addr 7) ]
2018-03-22 19:31:53 +03:00
2018-03-26 22:50:06 +03:00
it "evaluates modules" $ do
2018-03-26 22:53:58 +03:00
res <- evaluate "modules.rb"
fst res `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"<hello>\""))))))
environment (snd res) `shouldBe` [ ("Object", addr 0)
, ("Bar", addr 3) ]
2018-03-26 22:50:06 +03:00
2018-03-22 20:02:39 +03:00
it "has prelude" $ do
res <- fst <$> evaluate "preluded.rb"
2018-03-28 19:58:12 +03:00
res `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"<foo>\""))))))
2018-03-22 19:31:53 +03:00
2018-03-14 02:19:26 +03:00
where
ns n = Just . Latest . Just . injValue . Namespace n
2018-03-14 02:19:26 +03:00
addr = Address . Precise
fixtures = "test/fixtures/ruby/analysis/"
evaluate entry = evaluateFilesWithPrelude rubyParser
2018-03-14 02:19:26 +03:00
[ fixtures <> entry
, fixtures <> "foo.rb"
]