1
1
mirror of https://github.com/github/semantic.git synced 2024-12-18 12:21:57 +03:00
semantic/semantic-python/test-graphing/GraphTest.hs

104 lines
3.1 KiB
Haskell
Raw Normal View History

2020-01-10 23:14:05 +03:00
{-# LANGUAGE AllowAmbiguousTypes #-}
2020-01-14 23:36:07 +03:00
{-# LANGUAGE OverloadedStrings #-}
2020-01-10 20:22:13 +03:00
{-# LANGUAGE ScopedTypeVariables #-}
2020-01-14 23:36:07 +03:00
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
module Main (main) where
2020-01-10 23:14:05 +03:00
import Control.Algebra
import Control.Carrier.Sketch.Fresh
import Control.Monad
import qualified Data.ByteString as ByteString
import Data.Name (Name)
import qualified Data.ScopeGraph as ScopeGraph
import qualified Language.Python ()
2020-01-15 23:00:01 +03:00
import qualified Language.Python as Py (Term)
import ScopeGraph.Convert
2020-01-10 20:22:13 +03:00
import Source.Loc
import qualified Source.Source as Source
import System.Exit (die)
import System.Path ((</>))
import qualified System.Path as Path
import qualified System.Path.Directory as Path
2020-01-14 22:53:10 +03:00
import qualified Test.Tasty as Tasty
import qualified Test.Tasty.HUnit as HUnit
import qualified TreeSitter.Python as TSP
import qualified TreeSitter.Unmarshal as TS
2020-01-10 20:22:13 +03:00
{-
The Python code here is
hello = ()
goodbye = ()
The graph should be
🏁
|
1----"hello"
|
|
|
|
2----"goodbye"
-}
runScopeGraph :: ToScopeGraph t => Path.AbsRelFile -> Source.Source -> t Loc -> (ScopeGraph.ScopeGraph Name, Result)
2020-01-14 22:44:08 +03:00
runScopeGraph p _src item = run . runSketch (Just p) $ scopeGraph item
sampleGraphThing :: (Has (Sketch Name) sig m) => m Result
2020-01-10 23:14:05 +03:00
sampleGraphThing = do
declare @Name "hello" DeclProperties
declare @Name "goodbye" DeclProperties
pure Complete
2020-01-10 23:14:05 +03:00
2020-01-15 19:19:38 +03:00
graphFile :: FilePath -> IO (ScopeGraph.ScopeGraph Name, Result)
graphFile fp = do
file <- ByteString.readFile fp
2020-01-15 23:00:01 +03:00
tree <- TS.parseByteString @Py.Term @Loc TSP.tree_sitter_python file
2020-01-15 19:19:38 +03:00
pyModule <- either die pure tree
pure $ runScopeGraph (Path.absRel fp) (Source.fromUTF8 file) pyModule
2020-01-14 22:53:10 +03:00
assertSimpleAssignment :: HUnit.Assertion
assertSimpleAssignment = do
let path = "semantic-python/test/fixtures/1-04-toplevel-assignment.py"
2020-01-15 19:19:38 +03:00
(result, Complete) <- graphFile path
2020-01-14 22:44:08 +03:00
let (expecto, Complete) = run $ runSketch Nothing sampleGraphThing
2020-01-14 22:53:10 +03:00
HUnit.assertEqual "Should work for simple case" expecto result
2020-01-10 20:22:13 +03:00
2020-01-15 02:08:10 +03:00
expectedReference :: (Has (Sketch Name) sig m) => m Result
expectedReference = do
declare @Name "x" DeclProperties
reference @Name "x" "x" RefProperties
pure Complete
assertSimpleReference :: HUnit.Assertion
assertSimpleReference = do
let path = "semantic-python/test/fixtures/5-01-simple-reference.py"
2020-01-15 19:19:38 +03:00
(result, Complete) <- graphFile path
2020-01-15 02:08:10 +03:00
let (expecto, Complete) = run $ runSketch Nothing expectedReference
2020-01-15 19:19:38 +03:00
2020-01-15 02:08:10 +03:00
HUnit.assertEqual "Should work for simple case" expecto result
2020-01-14 22:53:10 +03:00
main :: IO ()
main = do
-- make sure we're in the root directory so the paths resolve properly
cwd <- Path.getCurrentDirectory
when (Path.takeDirName cwd == Just (Path.relDir "semantic-python"))
(Path.setCurrentDirectory (cwd </> Path.relDir ".."))
Tasty.defaultMain $
Tasty.testGroup "Tests" [
Tasty.testGroup "declare" [
HUnit.testCase "toplevel assignment" assertSimpleAssignment
],
Tasty.testGroup "reference" [
HUnit.testCase "simple reference" assertSimpleReference
]
2020-01-15 01:28:56 +03:00
]