1
1
mirror of https://github.com/github/semantic.git synced 2024-11-23 08:27:56 +03:00

Add a ToScopeGraph interface in semantic-python

This commit is contained in:
joshvera 2020-01-08 12:29:17 -05:00
parent 1eabf451e0
commit 4ba5989776
6 changed files with 35 additions and 13 deletions

View File

@ -41,6 +41,8 @@ package semantic-ruby
package semantic-tags
ghc-options: -Werror
package semantic-scope-graph
package semantic-ast
ghc-options: -Werror

View File

@ -27,6 +27,7 @@ common haskell
, semantic-core ^>= 0.0
, semantic-source ^>= 0.0
, semantic-tags ^>= 0.0
, semantic-scope-graph ^>= 0.0
, text ^>= 1.2.3
, tree-sitter ^>= 0.7.2
, tree-sitter-python ^>= 0.8
@ -53,6 +54,7 @@ library
Language.Python
Language.Python.Core
Language.Python.Failure
Language.Python.ScopeGraph
Language.Python.Tags
hs-source-dirs: src

View File

@ -5,7 +5,9 @@ module Language.Python
) where
import qualified Language.Python.Tags as PyTags
import qualified Language.Python.ScopeGraph as PyScopeGraph
import qualified Tags.Tagging.Precise as Tags
import qualified Data.ScopeGraph as ScopeGraph
import qualified TreeSitter.Python (tree_sitter_python)
import qualified TreeSitter.Python.AST as Py
import qualified TreeSitter.Unmarshal as TS
@ -17,3 +19,7 @@ instance TS.Unmarshal Term where
instance Tags.ToTags Term where
tags src = Tags.runTagging src . PyTags.tags . getTerm
instance ScopeGraph.ToScopeGraph Term where
scopeGraph src = ScopeGraph.runScopeGraph src . PyScopeGraph.scopeGraph . getTerm

View File

@ -0,0 +1,11 @@
module Language.Python.ScopeGraph (ToScopeGraph(..)) where
import Control.Effect.Reader
import Control.Effect.Writer
import Source.Loc
-- import Source.Range
import Source.Source as Source
import Data.ScopeGraph (ScopeGraph, Info)
class ToScopeGraph t where
scopeGraph :: ( Has (Reader Source) sig m, Has (Writer (ScopeGraph Info)) sig m) => t Loc -> m ()

View File

@ -1,6 +1,6 @@
{-# LANGUAGE DuplicateRecordFields #-}
module Data.ScopeGraph () where
module Data.ScopeGraph (ToScopeGraph(..), ScopeGraph, Info, runScopeGraph) where
import Algebra.Graph.Labelled (Graph, (-<), (>-))
import qualified Algebra.Graph.Labelled as G
@ -44,18 +44,18 @@ type SGM =
class ToScopeGraph t where
scopeGraph :: Source -> t Loc -> SGM (ScopeGraph Info)
instance ToScopeGraph Py.Identifier where
scopeGraph _ (Py.Identifier _ t) = ScopeGraph . G.vertex . Node (Ref t) <$> liftIO newUnique
-- instance ToScopeGraph Py.Identifier where
-- scopeGraph _ (Py.Identifier _ t) = ScopeGraph . G.vertex . Node (Ref t) <$> liftIO newUnique
instance ToScopeGraph Py.Module where
scopeGraph src Py.Module { Py.extraChildren = stmts } = do
parent <- ask
self <- ScopeGraph . G.vertex . Node Scope <$> liftIO newUnique
foldr (\item acc -> do {
x <- acc;
y <- scopeGraph src item;
pure (x --> y);
}) (pure (parent --> self)) stmts
-- instance ToScopeGraph Py.Module where
-- scopeGraph src Py.Module { Py.extraChildren = stmts } = do
-- parent <- ask
-- self <- ScopeGraph . G.vertex . Node Scope <$> liftIO newUnique
-- foldr (\item acc -> do {
-- x <- acc;
-- y <- scopeGraph src item;
-- pure (x --> y);
-- }) (pure (parent --> self)) stmts
runScopeGraph :: ToScopeGraph t => Source -> t Loc -> IO (ScopeGraph Info)
runScopeGraph src item = do

View File

@ -290,9 +290,10 @@ library
, semantic-json ^>= 0
, semantic-python ^>= 0
, semantic-ruby ^>= 0
, semantic-scope-graph ^>= 0
, semantic-tags ^>= 0
, semantic-tsx ^>= 0
, semantic-typescript ^>= 0
, semantic-tags ^>= 0
, semigroupoids ^>= 5.3.2
, split ^>= 0.2.3.3
, stm-chans ^>= 3.0.0.4