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

67 lines
1.9 KiB
Haskell
Raw Normal View History

2020-01-10 23:14:05 +03:00
{-# LANGUAGE AllowAmbiguousTypes #-}
2020-01-10 20:22:13 +03:00
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module Main (main) where
2020-01-10 23:14:05 +03:00
import Control.Algebra
import Control.Carrier.Sketch.Fresh
2020-01-10 20:22:13 +03:00
import Control.Monad
import Convert.ToScopeGraph
import qualified Data.ByteString as ByteString
import qualified Data.ScopeGraph as ScopeGraph
import qualified Language.Python ()
2020-01-10 20:22:13 +03:00
import Source.Loc
import qualified Source.Source as Source
import System.Exit (die)
import qualified System.Path as Path
import qualified TreeSitter.Python as TSP
2020-01-10 20:22:13 +03:00
import qualified TreeSitter.Python.AST as Py
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"
-}
2020-01-13 22:39:53 +03:00
runScopeGraph :: ToScopeGraph t => Path.AbsRelFile -> Source.Source -> t Loc -> ScopeGraph.ScopeGraph ScopeGraph.Info
runScopeGraph p _src item = run . runSketch @ScopeGraph.Info (Just p) $ scopeGraph item
2020-01-13 22:39:53 +03:00
sampleGraphThing :: (Has (Sketch ScopeGraph.Info) sig m) => m (ScopeGraph.ScopeGraph ScopeGraph.Info)
2020-01-10 23:14:05 +03:00
sampleGraphThing = do
2020-01-13 22:39:53 +03:00
void $ declare @ScopeGraph.Info "hello" DeclProperties
2020-01-11 01:46:37 +03:00
declare @ScopeGraph.Info "goodbye" DeclProperties
2020-01-10 23:14:05 +03:00
2020-01-10 20:22:13 +03:00
assertEqual :: (Show a, Eq a) => a -> a -> IO ()
assertEqual a b = unless (a == b) (die (show a <> "\ndoes not equal\n" <> show b))
main :: IO ()
main = do
let path = "semantic-python/test/fixtures/1-04-toplevel-assignment.py"
file <- ByteString.readFile path
tree <- TS.parseByteString @Py.Module @Loc TSP.tree_sitter_python file
pyModule <- either die pure tree
2020-01-13 22:39:53 +03:00
let expecto = run $ runSketch @ScopeGraph.Info Nothing sampleGraphThing
let result = runScopeGraph (Path.absRel path) (Source.fromUTF8 file) pyModule
2020-01-10 20:22:13 +03:00
print result
assertEqual expecto result