2019-10-23 18:58:02 +03:00
|
|
|
{-# LANGUAGE GADTs, PackageImports #-}
|
2018-07-16 18:07:40 +03:00
|
|
|
|
|
|
|
module Graphing.Calls.Spec ( spec ) where
|
|
|
|
|
|
|
|
import Prelude hiding (readFile)
|
2019-10-02 23:53:16 +03:00
|
|
|
import SpecHelpers
|
2018-07-16 18:07:40 +03:00
|
|
|
|
|
|
|
import Algebra.Graph
|
|
|
|
|
2019-10-23 21:52:34 +03:00
|
|
|
import Control.Effect.Parse
|
2018-07-16 18:12:17 +03:00
|
|
|
import "semantic" Data.Graph (Graph (..), topologicalSort)
|
2018-09-07 02:29:59 +03:00
|
|
|
import Data.Graph.ControlFlowVertex
|
2018-07-16 18:07:40 +03:00
|
|
|
import qualified Data.Language as Language
|
2019-10-23 18:58:02 +03:00
|
|
|
import Data.Maybe (fromJust)
|
2018-07-16 18:12:17 +03:00
|
|
|
import Semantic.Graph
|
2019-09-20 19:26:49 +03:00
|
|
|
import qualified System.Path as Path
|
2018-07-16 18:07:40 +03:00
|
|
|
|
2019-09-20 19:26:49 +03:00
|
|
|
callGraphPythonProject :: Path.RelFile -> IO (Semantic.Graph.Graph ControlFlowVertex)
|
|
|
|
callGraphPythonProject path = runTaskOrDie $ do
|
2018-07-16 18:07:40 +03:00
|
|
|
let proxy = Proxy @'Language.Python
|
2019-10-23 18:58:02 +03:00
|
|
|
lang = Language.Python
|
2019-10-23 19:17:10 +03:00
|
|
|
SomeParser parser <- pure . fromJust $! parserForLanguage analysisParsers Language.Python
|
2019-10-12 02:24:53 +03:00
|
|
|
blob <- readBlobFromFile' (fileForTypedPath path)
|
2019-10-23 18:58:02 +03:00
|
|
|
package <- fmap snd <$> parsePackage parser (Project (Path.toString (Path.takeDirectory path)) [blob] lang [])
|
2018-07-24 21:06:14 +03:00
|
|
|
modules <- topologicalSort <$> runImportGraphToModules proxy package
|
2018-07-16 18:07:40 +03:00
|
|
|
runCallGraph proxy False modules package
|
|
|
|
|
|
|
|
spec :: Spec
|
|
|
|
spec = describe "call graphing" $ do
|
|
|
|
|
2018-07-18 17:53:46 +03:00
|
|
|
let needs r v = unGraph r `shouldSatisfy` hasVertex v
|
2018-07-16 20:13:05 +03:00
|
|
|
|
2018-07-16 18:07:40 +03:00
|
|
|
it "should work for a simple example" $ do
|
2019-09-20 19:26:49 +03:00
|
|
|
res <- callGraphPythonProject (Path.relFile "test/fixtures/python/graphing/simple/simple.py")
|
2018-07-18 17:53:46 +03:00
|
|
|
res `needs` Variable "magnus" "simple.py" (Span (Pos 4 1) (Pos 4 7))
|
2018-07-16 18:12:17 +03:00
|
|
|
|
|
|
|
it "should evaluate both sides of an if-statement" $ do
|
2019-09-20 19:26:49 +03:00
|
|
|
res <- callGraphPythonProject (Path.relFile "test/fixtures/python/graphing/conditional/conditional.py")
|
2018-07-18 17:53:46 +03:00
|
|
|
res `needs` Variable "merle" "conditional.py" (Span (Pos 5 5) (Pos 5 10))
|
|
|
|
res `needs` Variable "taako" "conditional.py" (Span (Pos 8 5) (Pos 8 10))
|
2018-07-16 18:36:17 +03:00
|
|
|
|
|
|
|
it "should continue even when a type error is encountered" $ do
|
2019-09-20 19:26:49 +03:00
|
|
|
res <- callGraphPythonProject (Path.relFile "test/fixtures/python/graphing/typeerror/typeerror.py")
|
2018-07-18 17:53:46 +03:00
|
|
|
res `needs` Variable "lup" "typeerror.py" (Span (Pos 5 1) (Pos 5 4))
|
2018-07-16 18:36:17 +03:00
|
|
|
|
|
|
|
it "should continue when an unbound variable is encountered" $ do
|
2019-09-20 19:26:49 +03:00
|
|
|
res <- callGraphPythonProject (Path.relFile "test/fixtures/python/graphing/unbound/unbound.py")
|
2018-07-18 17:53:46 +03:00
|
|
|
res `needs` Variable "lucretia" "unbound.py" (Span (Pos 5 1) (Pos 5 9))
|