mirror of
https://github.com/github/semantic.git
synced 2024-11-27 12:57:49 +03:00
Fix tests.
This commit is contained in:
parent
d6b619fa09
commit
c67a72e531
@ -1,4 +1,7 @@
|
||||
{-# LANGUAGE DataKinds, ImplicitParams, OverloadedStrings, TypeApplications #-}
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE ImplicitParams #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# OPTIONS_GHC -O0 #-}
|
||||
module Analysis.Ruby.Spec (spec) where
|
||||
|
||||
@ -36,7 +39,7 @@ spec = do
|
||||
|
||||
it "evaluates load with wrapper" $ do
|
||||
(_, (_, res)) <- evaluate ["load-wrap.rb", "foo.rb"]
|
||||
res `shouldBe` Left (SomeError (inject @(BaseError (ScopeError Precise)) (BaseError (ModuleInfo "load-wrap.rb" Language.Ruby mempty) (Span (Pos 3 1) (Pos 3 7)) (LookupPathError (Declaration "foo")))))
|
||||
res `shouldBe` Left (SomeError (inject @(BaseError (ScopeError Precise)) (BaseError (ModuleInfo "load-wrap.rb" "Ruby" mempty) (Span (Pos 3 1) (Pos 3 7)) (LookupPathError (Declaration "foo")))))
|
||||
|
||||
it "evaluates subclass" $ do
|
||||
(scopeGraph, (heap, res)) <- evaluate ["subclass.rb"]
|
||||
@ -59,37 +62,37 @@ spec = do
|
||||
(_, (_, res)) <- evaluate ["break.rb"]
|
||||
case ModuleTable.lookup "break.rb" <$> res of
|
||||
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 3)
|
||||
other -> expectationFailure (show other)
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "handles next correctly" $ do
|
||||
(_, (_, res)) <- evaluate ["next.rb"]
|
||||
case ModuleTable.lookup "next.rb" <$> res of
|
||||
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 8)
|
||||
other -> expectationFailure (show other)
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "calls functions with arguments" $ do
|
||||
(_, (_, res)) <- evaluate ["call.rb"]
|
||||
case ModuleTable.lookup "call.rb" <$> res of
|
||||
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 579)
|
||||
other -> expectationFailure (show other)
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "evaluates early return statements" $ do
|
||||
(_, (_, res)) <- evaluate ["early-return.rb"]
|
||||
case ModuleTable.lookup "early-return.rb" <$> res of
|
||||
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 123)
|
||||
other -> expectationFailure (show other)
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "has prelude" $ do
|
||||
(_, (_, res)) <- evaluate ["preluded.rb"]
|
||||
case ModuleTable.lookup "preluded.rb" <$> res of
|
||||
Right (Just (Module _ (_, value))) -> value `shouldBe` String "\"<foo>\""
|
||||
other -> expectationFailure (show other)
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "evaluates __LINE__" $ do
|
||||
(_, (_, res)) <- evaluate ["line.rb"]
|
||||
case ModuleTable.lookup "line.rb" <$> res of
|
||||
Right (Just (Module _ (_, value))) -> value `shouldBe` Value.Integer (Number.Integer 4)
|
||||
other -> expectationFailure (show other)
|
||||
other -> expectationFailure (show other)
|
||||
|
||||
it "resolves builtins used in the prelude" $ do
|
||||
(scopeGraph, (heap, res)) <- evaluate ["puts.rb"]
|
||||
|
@ -1,21 +1,24 @@
|
||||
{-# LANGUAGE DataKinds, ImplicitParams, OverloadedStrings, TypeApplications #-}
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE ImplicitParams #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# OPTIONS_GHC -O0 #-}
|
||||
|
||||
module Analysis.TypeScript.Spec (spec) where
|
||||
|
||||
import Control.Abstract.ScopeGraph hiding (AccessControl(..))
|
||||
import Control.Abstract.ScopeGraph hiding (AccessControl (..))
|
||||
import Control.Carrier.Resumable.Either (SomeError (..))
|
||||
import Data.Syntax.Statement (StatementBlock(..))
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph (AccessControl(..))
|
||||
import Data.Abstract.Evaluatable
|
||||
import qualified Data.Abstract.Heap as Heap
|
||||
import qualified Data.Abstract.ModuleTable as ModuleTable
|
||||
import Data.Abstract.Number as Number
|
||||
import Data.Abstract.Package (PackageInfo (..))
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph (AccessControl (..))
|
||||
import Data.Abstract.Value.Concrete as Concrete
|
||||
import qualified Data.Language as Language
|
||||
import Data.Scientific (scientific)
|
||||
import Data.Sum
|
||||
import Data.Syntax.Statement (StatementBlock (..))
|
||||
import Data.Text (pack)
|
||||
import qualified Language.TypeScript.Term as TypeScript
|
||||
import Source.Loc
|
||||
@ -81,7 +84,7 @@ spec = do
|
||||
|
||||
it "fails exporting symbols not defined in the module" $ do
|
||||
(_, (_, res)) <- evaluate ["bad-export.ts", "pip.ts", "a.ts", "foo.ts"]
|
||||
res `shouldBe` Left (SomeError (inject @(BaseError (ScopeError Precise)) (BaseError (ModuleInfo "bad-export.ts" Language.TypeScript mempty) (Span (Pos 2 1) (Pos 2 28)) ImportReferenceError)))
|
||||
res `shouldBe` Left (SomeError (inject @(BaseError (ScopeError Precise)) (BaseError (ModuleInfo "bad-export.ts" "TypeScript" mempty) (Span (Pos 2 1) (Pos 2 28)) ImportReferenceError)))
|
||||
|
||||
it "evaluates early return statements" $ do
|
||||
(scopeGraph, (heap, res)) <- evaluate ["early-return.ts"]
|
||||
@ -165,17 +168,17 @@ spec = do
|
||||
|
||||
it "member access of private field definition throws AccessControlError" $ do
|
||||
(_, (_, res)) <- evaluate ["access_control/adder.ts", "access_control/private_field_definition.ts"]
|
||||
let expected = Left (SomeError (inject @TypeScriptEvalError (BaseError (ModuleInfo "private_field_definition.ts" Language.TypeScript mempty) (Span (Pos 4 1) (Pos 4 6)) (AccessControlError ("foo", ScopeGraph.Public) ("y", ScopeGraph.Private) (Concrete.Float (Decimal 2.0))))))
|
||||
let expected = Left (SomeError (inject @TypeScriptEvalError (BaseError (ModuleInfo "private_field_definition.ts" "TypeScript" mempty) (Span (Pos 4 1) (Pos 4 6)) (AccessControlError ("foo", ScopeGraph.Public) ("y", ScopeGraph.Private) (Concrete.Float (Decimal 2.0))))))
|
||||
res `shouldBe` expected
|
||||
|
||||
it "member access of private static field definition throws AccessControlError" $ do
|
||||
(_, (_, res)) <- evaluate ["access_control/adder.ts", "access_control/private_static_field_definition.ts"]
|
||||
let expected = Left (SomeError (inject @TypeScriptEvalError (BaseError (ModuleInfo "private_static_field_definition.ts" Language.TypeScript mempty) (Span (Pos 3 1) (Pos 3 8)) (AccessControlError ("Adder", ScopeGraph.Public) ("z", ScopeGraph.Private) Unit))))
|
||||
let expected = Left (SomeError (inject @TypeScriptEvalError (BaseError (ModuleInfo "private_static_field_definition.ts" "TypeScript" mempty) (Span (Pos 3 1) (Pos 3 8)) (AccessControlError ("Adder", ScopeGraph.Public) ("z", ScopeGraph.Private) Unit))))
|
||||
res `shouldBe` expected
|
||||
|
||||
it "member access of private methods throws AccessControlError" $ do
|
||||
(_, (_, res)) <- evaluate ["access_control/adder.ts", "access_control/private_method.ts"]
|
||||
let expected = Left (SomeError (inject @TypeScriptEvalError (BaseError (ModuleInfo "private_method.ts" Language.TypeScript mempty) (Span (Pos 4 1) (Pos 4 16)) (AccessControlError ("foo", ScopeGraph.Public) ("private_add", ScopeGraph.Private) (Closure (PackageInfo "access_control" mempty) (ModuleInfo "adder.ts" Language.TypeScript mempty) (Just "private_add") Nothing [] (Right (TypeScript.Term (In (Loc (Range 146 148) (Span (Pos 7 27) (Pos 7 29))) (inject (StatementBlock []))))) (Precise 20) (Precise 18))))))
|
||||
let expected = Left (SomeError (inject @TypeScriptEvalError (BaseError (ModuleInfo "private_method.ts" "TypeScript" mempty) (Span (Pos 4 1) (Pos 4 16)) (AccessControlError ("foo", ScopeGraph.Public) ("private_add", ScopeGraph.Private) (Closure (PackageInfo "access_control" mempty) (ModuleInfo "adder.ts" "TypeScript" mempty) (Just "private_add") Nothing [] (Right (TypeScript.Term (In (Loc (Range 146 148) (Span (Pos 7 27) (Pos 7 29))) (inject (StatementBlock []))))) (Precise 20) (Precise 18))))))
|
||||
res `shouldBe` expected
|
||||
|
||||
where
|
||||
|
@ -1,4 +1,7 @@
|
||||
{-# LANGUAGE DataKinds, OverloadedStrings, TypeApplications, TypeOperators #-}
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
{-# OPTIONS_GHC -fno-warn-missing-signatures #-}
|
||||
module Control.Abstract.Evaluator.Spec
|
||||
( spec
|
||||
@ -6,9 +9,9 @@ module Control.Abstract.Evaluator.Spec
|
||||
|
||||
import Control.Abstract as Abstract
|
||||
import qualified Control.Abstract.Heap as Heap
|
||||
import Control.Carrier.Lift
|
||||
import Control.Carrier.Error.Either
|
||||
import Control.Carrier.Fresh.Strict
|
||||
import Control.Carrier.Lift
|
||||
import Control.Carrier.Resumable.Either
|
||||
import Control.Carrier.State.Strict
|
||||
import Control.Carrier.Trace.Ignoring
|
||||
@ -20,7 +23,6 @@ import qualified Data.Abstract.Number as Number
|
||||
import Data.Abstract.Package
|
||||
import qualified Data.Abstract.ScopeGraph as ScopeGraph
|
||||
import Data.Abstract.Value.Concrete as Value
|
||||
import qualified Data.Language as Language
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Data.Sum
|
||||
import SpecHelpers hiding (reassociate)
|
||||
@ -55,7 +57,7 @@ evaluate
|
||||
. fmap snd
|
||||
. runFresh 0
|
||||
. runReader (PackageInfo (SpecHelpers.name "test") mempty)
|
||||
. runReader (ModuleInfo "test/Control/Abstract/Evaluator/Spec.hs" Language.Haskell mempty)
|
||||
. runReader (ModuleInfo "test/Control/Abstract/Evaluator/Spec.hs" "Haskell" mempty)
|
||||
. evalState (lowerBound @Span)
|
||||
. runReader (lowerBound @Span)
|
||||
. runEvaluator
|
||||
|
Loading…
Reference in New Issue
Block a user