mirror of
https://github.com/github/semantic.git
synced 2024-11-28 01:47:01 +03:00
Add Eq1 error instances and fix tests
This commit is contained in:
parent
9043193e13
commit
af0793a7ad
@ -26,7 +26,7 @@ import Data.Abstract.Number as Number
|
||||
import Data.Scientific (Scientific)
|
||||
import Data.Semigroup.Reducer hiding (unit)
|
||||
import Prelude
|
||||
import Prologue
|
||||
import Prologue hiding (TypeError)
|
||||
|
||||
-- | This datum is passed into liftComparison to handle the fact that Ruby and PHP
|
||||
-- have built-in generalized-comparison ("spaceship") operators. If you want to
|
||||
|
@ -49,6 +49,8 @@ deriving instance Eq (LoadError term a b)
|
||||
deriving instance Show (LoadError term a b)
|
||||
instance Show1 (LoadError term value) where
|
||||
liftShowsPrec _ _ = showsPrec
|
||||
instance Eq1 (LoadError term a) where
|
||||
liftEq _ (LoadError a) (LoadError b) = a == b
|
||||
|
||||
data EvalError value resume where
|
||||
FreeVariableError :: Name -> EvalError value value
|
||||
@ -57,6 +59,8 @@ deriving instance Eq (EvalError a b)
|
||||
deriving instance Show (EvalError a b)
|
||||
instance Show1 (EvalError value) where
|
||||
liftShowsPrec _ _ = showsPrec
|
||||
instance Eq1 (EvalError term) where
|
||||
liftEq _ (FreeVariableError a) (FreeVariableError b) = a == b
|
||||
|
||||
throwLoadError :: MonadEvaluatable term value m => LoadError term value resume -> m resume
|
||||
throwLoadError = throwException
|
||||
|
@ -30,11 +30,11 @@ spec = parallel $ do
|
||||
|
||||
it "subclasses" $ do
|
||||
v <- findValue <$> evaluate "subclass.py"
|
||||
v `shouldBe` Right (Right (Right (injValue (String "\"bar\""))))
|
||||
v `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"bar\""))))))
|
||||
|
||||
it "handles multiple inheritance left-to-right" $ do
|
||||
v <- findValue <$> evaluate "multiple_inheritance.py"
|
||||
v `shouldBe` Right (Right (Right (injValue (String "\"foo!\""))))
|
||||
v `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"foo!\""))))))
|
||||
|
||||
where
|
||||
addr = Address . Precise
|
||||
|
@ -2,7 +2,10 @@
|
||||
|
||||
module Analysis.Ruby.Spec (spec) where
|
||||
|
||||
import Data.Abstract.Evaluatable (EvalError(..))
|
||||
import Data.Abstract.Value
|
||||
import Control.Monad.Effect (SomeExc(..))
|
||||
import Data.List.NonEmpty (NonEmpty(..))
|
||||
import Data.Map
|
||||
import Data.Map.Monoidal as Map
|
||||
|
||||
@ -24,12 +27,12 @@ spec = parallel $ do
|
||||
|
||||
it "evaluates load with wrapper" $ do
|
||||
res <- evaluate "load-wrap.rb"
|
||||
findValue res `shouldBe` Left "free variable: \"foo\""
|
||||
findValue res `shouldBe` Right (Right (Right (Right (Left (SomeExc (FreeVariableError ("foo" :| [])))))))
|
||||
findEnv res `shouldBe` [ (name "Object", addr 0) ]
|
||||
|
||||
it "evaluates subclass" $ do
|
||||
res <- evaluate "subclass.rb"
|
||||
findValue res `shouldBe` Right (Right (Right (injValue (String "\"<bar>\""))))
|
||||
findValue res `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"<bar>\""))))))
|
||||
findEnv res `shouldBe` [ (name "Bar", addr 6)
|
||||
, (name "Foo", addr 3)
|
||||
, (name "Object", addr 0) ]
|
||||
@ -41,13 +44,13 @@ spec = parallel $ do
|
||||
|
||||
it "evaluates modules" $ do
|
||||
res <- evaluate "modules.rb"
|
||||
findValue res `shouldBe` Right (Right (Right (injValue (String "\"<hello>\""))))
|
||||
findValue res `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"<hello>\""))))))
|
||||
findEnv res `shouldBe` [ (name "Object", addr 0)
|
||||
, (name "Bar", addr 3) ]
|
||||
|
||||
it "has prelude" $ do
|
||||
res <- findValue <$> evaluate "preluded.rb"
|
||||
res `shouldBe` Right (Right (Right (injValue (String "\"<foo>\""))))
|
||||
res `shouldBe` Right (Right (Right (Right (Right (injValue (String "\"<foo>\""))))))
|
||||
|
||||
where
|
||||
ns n = Just . Latest . Just . injValue . Namespace (name n)
|
||||
|
Loading…
Reference in New Issue
Block a user