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

Merge pull request #2057 from github/call-graph-tests

Add test cases for graphs.
This commit is contained in:
Patrick Thomson 2018-07-16 13:29:28 -04:00 committed by GitHub
commit 3a56dc17e0
7 changed files with 73 additions and 0 deletions

View File

@ -289,6 +289,7 @@ test-suite test
, Diffing.Algorithm.RWS.Spec
, Diffing.Algorithm.SES.Spec
, Diffing.Interpreter.Spec
, Graphing.Calls.Spec
, Integration.Spec
, Matching.Go.Spec
, Numeric.Spec
@ -301,6 +302,7 @@ test-suite test
, SpecHelpers
, Test.Hspec.LeanCheck
build-depends: aeson
, algebraic-graphs
, array
, async
, base

View File

@ -0,0 +1,47 @@
{-# LANGUAGE PackageImports #-}
module Graphing.Calls.Spec ( spec ) where
import Prelude hiding (readFile)
import Prologue
import SpecHelpers hiding (readFile)
import Algebra.Graph
import Data.List (uncons)
import "semantic" Data.Graph (Graph (..), topologicalSort)
import Data.Graph.Vertex
import qualified Data.Language as Language
import Semantic.Config (defaultOptions)
import Semantic.Graph
import Semantic.IO
callGraphPythonProject paths = runTaskWithOptions defaultOptions $ do
let proxy = Proxy @'Language.Python
let lang = Language.Python
blobs <- catMaybes <$> traverse readFile (flip File lang <$> paths)
package <- parsePackage pythonParser (Project (takeDirectory (maybe "/" fst (uncons paths))) blobs lang [])
modules <- topologicalSort <$> runImportGraph proxy package
runCallGraph proxy False modules package
spec :: Spec
spec = describe "call graphing" $ do
let needs r n = unGraph r `shouldSatisfy` hasVertex (Variable n)
it "should work for a simple example" $ do
res <- callGraphPythonProject ["test/fixtures/python/graphing/simple/simple.py"]
res `needs` "magnus"
it "should evaluate both sides of an if-statement" $ do
res <- callGraphPythonProject ["test/fixtures/python/graphing/conditional/conditional.py"]
res `needs` "merle"
res `needs` "taako"
it "should continue even when a type error is encountered" $ do
res <- callGraphPythonProject ["test/fixtures/python/graphing/typeerror/typeerror.py"]
res `needs` "lup"
it "should continue when an unbound variable is encountered" $ do
res <- callGraphPythonProject ["test/fixtures/python/graphing/unbound/unbound.py"]
res `needs` "lucretia"

View File

@ -16,6 +16,7 @@ import qualified Data.Term.Spec
import qualified Diffing.Algorithm.RWS.Spec
import qualified Diffing.Algorithm.SES.Spec
import qualified Diffing.Interpreter.Spec
import qualified Graphing.Calls.Spec
import qualified Integration.Spec
import qualified Matching.Go.Spec
import qualified Numeric.Spec
@ -52,6 +53,7 @@ main = do
describe "Diffing.Algorithm.RWS" Diffing.Algorithm.RWS.Spec.spec
describe "Diffing.Algorithm.SES" Diffing.Algorithm.SES.Spec.spec
describe "Diffing.Interpreter" Diffing.Interpreter.Spec.spec
describe "Graphing.Calls" Graphing.Calls.Spec.spec
describe "Matching" Matching.Go.Spec.spec
describe "Numeric" Numeric.Spec.spec
describe "Rendering.TOC" Rendering.TOC.Spec.spec

View File

@ -0,0 +1,8 @@
cond = True
if cond:
def merle(): pass
merle()
else:
def taako(): pass
taako()

View File

@ -0,0 +1,4 @@
def magnus():
return "string"
magnus()

View File

@ -0,0 +1,5 @@
var = 1 + "thing"
def lup(): pass
lup()

View File

@ -0,0 +1,5 @@
var = thing + 1
def lucretia(): pass
lucretia()