1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 08:54:07 +03:00

Add Eq1 instances to exception types

This commit is contained in:
joshvera 2018-03-23 11:48:56 -04:00
parent 68ca81ad97
commit 173781c501
4 changed files with 22 additions and 13 deletions

View File

@ -1,17 +1,18 @@
{-# LANGUAGE MultiParamTypeClasses, Rank2Types, TypeFamilies, TypeOperators, UndecidableInstances, GADTs, StandaloneDeriving #-}
{-# LANGUAGE GADTs, MultiParamTypeClasses, Rank2Types, StandaloneDeriving, TypeFamilies, TypeOperators,
UndecidableInstances #-}
module Control.Abstract.Value where
import Control.Abstract.Addressable
import Control.Abstract.Analysis
import Control.Abstract.Addressable
import Control.Abstract.Analysis
import qualified Data.Abstract.Environment as Env
import Data.Abstract.FreeVariables
import Data.Abstract.Number as Number
import Data.Abstract.Type as Type
import Data.Abstract.Value as Value
import Data.Scientific (Scientific)
import Data.Abstract.FreeVariables
import Data.Abstract.Number as Number
import Data.Abstract.Type as Type
import Data.Abstract.Value as Value
import Data.Scientific (Scientific)
import qualified Data.Set as Set
import Prelude hiding (fail)
import Prologue
import Prelude hiding (fail)
import Prologue
-- | 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
@ -142,6 +143,11 @@ data ValueExc v where
ValueExc :: Prelude.String -> ValueExc Value
StringExc :: Prelude.String -> ValueExc ByteString
instance Eq1 ValueExc where
liftEq _ (ValueExc a) (ValueExc b) = a == b
liftEq _ (StringExc a) (StringExc b) = a == b
liftEq _ _ _ = False
deriving instance Show (ValueExc v)
instance Show1 ValueExc where
liftShowsPrec _ _ = showsPrec

View File

@ -24,6 +24,9 @@ import Prologue
data Unspecialized a b where
Unspecialized :: { getUnspecialized :: Prelude.String } -> Unspecialized value value
instance Eq1 (Unspecialized a) where
liftEq _ (Unspecialized a) (Unspecialized b) = a == b
deriving instance Eq (Unspecialized a b)
deriving instance Show (Unspecialized a b)
instance Show1 (Unspecialized a) where

View File

@ -36,11 +36,11 @@ spec = parallel $ do
it "subclasses" $ do
res <- evaluate' "subclass.py"
join (fst res) `shouldBe` Right (injValue (String "\"bar\""))
fst res `shouldBe` Right (Right (Right (injValue (String "\"bar\""))))
it "handles multiple inheritance left-to-right" $ do
res <- evaluate' "multiple_inheritance.py"
join (fst res) `shouldBe` Right (injValue (String "\"foo!\""))
fst res `shouldBe` Right (Right (Right (injValue (String "\"foo!\""))))
where
addr = Address . Precise

View File

@ -28,7 +28,7 @@ spec = parallel $ do
it "subclass" $ do
res <- evaluate' "subclass.rb"
join (fst res) `shouldBe` Right (injValue (String "\"<bar>\""))
fst res `shouldBe` Right (Right (Right (injValue (String "\"<bar>\""))))
where
addr = Address . Precise