mirror of
https://github.com/github/semantic.git
synced 2024-12-27 17:05:33 +03:00
Move over Function and Reference properties.
This commit is contained in:
parent
4bfbd5407e
commit
1672c57768
@ -39,6 +39,8 @@ import GHC.TypeLits
|
||||
import Language.Python.Patterns
|
||||
import ScopeGraph.Convert (Result (..), complete, todo)
|
||||
import qualified ScopeGraph.Properties.Declaration as Props
|
||||
import qualified ScopeGraph.Properties.Function as Props
|
||||
import qualified ScopeGraph.Properties.Reference as Props
|
||||
import Source.Loc
|
||||
import Source.Span (span_)
|
||||
import qualified TreeSitter.Python.AST as Py
|
||||
@ -191,9 +193,9 @@ instance ToScopeGraph Py.FunctionDefinition where
|
||||
, parameters = Py.Parameters _ann2 parameters
|
||||
, body
|
||||
} = do
|
||||
(_, associatedScope) <- declareFunction (Just $ Name.name name) FunProperties
|
||||
{ kind = ScopeGraph.Function
|
||||
, spanInfo = ann^.span_
|
||||
(_, associatedScope) <- declareFunction (Just $ Name.name name) Props.Function
|
||||
{ Props.kind = ScopeGraph.Function
|
||||
, Props.span = ann^.span_
|
||||
}
|
||||
withScope associatedScope $ do
|
||||
let declProps = Props.Declaration
|
||||
@ -220,7 +222,7 @@ instance ToScopeGraph Py.GeneratorExpression where scopeGraph = todo
|
||||
|
||||
instance ToScopeGraph Py.Identifier where
|
||||
scopeGraph (Py.Identifier _ name) = do
|
||||
reference name name RefProperties
|
||||
reference name name Props.Reference
|
||||
complete
|
||||
|
||||
instance ToScopeGraph Py.IfStatement where
|
||||
|
@ -18,6 +18,8 @@ import qualified Language.Python ()
|
||||
import qualified Language.Python as Py (Term)
|
||||
import ScopeGraph.Convert
|
||||
import qualified ScopeGraph.Properties.Declaration as Props
|
||||
import qualified ScopeGraph.Properties.Function as Props
|
||||
import qualified ScopeGraph.Properties.Reference as Props
|
||||
import Source.Loc
|
||||
import qualified Source.Source as Source
|
||||
import Source.Span
|
||||
@ -78,7 +80,7 @@ assertSimpleAssignment = do
|
||||
expectedReference :: (Has Sketch sig m) => m Result
|
||||
expectedReference = do
|
||||
declare "x" (Props.Declaration ScopeGraph.Assignment ScopeGraph.Default Nothing (Span (Pos 0 0) (Pos 0 5)))
|
||||
reference "x" "x" RefProperties
|
||||
reference "x" "x" Props.Reference
|
||||
pure Complete
|
||||
|
||||
assertSimpleReference :: HUnit.Assertion
|
||||
@ -91,18 +93,18 @@ assertSimpleReference = do
|
||||
|
||||
expectedLexicalScope :: (Has Sketch sig m) => m Result
|
||||
expectedLexicalScope = do
|
||||
_ <- declareFunction (Just $ Name.name "foo") (FunProperties ScopeGraph.Function (Span (Pos 0 0) (Pos 1 24)))
|
||||
reference "foo" "foo" RefProperties {}
|
||||
_ <- declareFunction (Just $ Name.name "foo") (Props.Function ScopeGraph.Function (Span (Pos 0 0) (Pos 1 24)))
|
||||
reference "foo" "foo" Props.Reference {}
|
||||
pure Complete
|
||||
|
||||
expectedFunctionArg :: (Has Sketch sig m) => m Result
|
||||
expectedFunctionArg = do
|
||||
(_, associatedScope) <- declareFunction (Just $ Name.name "foo") (FunProperties ScopeGraph.Function (Span (Pos 0 0) (Pos 1 12)))
|
||||
(_, associatedScope) <- declareFunction (Just $ Name.name "foo") (Props.Function ScopeGraph.Function (Span (Pos 0 0) (Pos 1 12)))
|
||||
withScope associatedScope $ do
|
||||
declare "x" (Props.Declaration ScopeGraph.Identifier ScopeGraph.Default Nothing lowerBound)
|
||||
reference "x" "x" RefProperties
|
||||
reference "x" "x" Props.Reference
|
||||
pure ()
|
||||
reference "foo" "foo" RefProperties
|
||||
reference "foo" "foo" Props.Reference
|
||||
pure Complete
|
||||
|
||||
assertLexicalScope :: HUnit.Assertion
|
||||
|
@ -24,6 +24,8 @@ library
|
||||
Control.Effect.Sketch
|
||||
ScopeGraph.Convert
|
||||
ScopeGraph.Properties.Declaration
|
||||
ScopeGraph.Properties.Function
|
||||
ScopeGraph.Properties.Reference
|
||||
Data.Hole
|
||||
Data.Module
|
||||
Data.ScopeGraph
|
||||
|
@ -14,8 +14,6 @@
|
||||
module Control.Effect.Sketch
|
||||
( Sketch
|
||||
, SketchEff (..)
|
||||
, RefProperties (..)
|
||||
, FunProperties (..)
|
||||
, declare
|
||||
-- Scope Manipulation
|
||||
, currentScope
|
||||
@ -32,26 +30,14 @@ import qualified Analysis.Name as Name
|
||||
import Control.Algebra
|
||||
import Control.Effect.Fresh
|
||||
import Control.Effect.Reader
|
||||
import Control.Lens ((^.))
|
||||
import Data.Generics.Product (field)
|
||||
import Data.Map.Strict (Map)
|
||||
import qualified Data.Map.Strict as Map
|
||||
import qualified Data.ScopeGraph as ScopeGraph
|
||||
import Data.Text (Text)
|
||||
import GHC.Generics (Generic, Generic1)
|
||||
import GHC.Records
|
||||
import qualified ScopeGraph.Properties.Declaration as Props
|
||||
import Source.Span
|
||||
|
||||
|
||||
data RefProperties = RefProperties
|
||||
|
||||
data FunProperties = FunProperties
|
||||
{ kind :: ScopeGraph.Kind
|
||||
, spanInfo :: Span
|
||||
} deriving Generic
|
||||
|
||||
instance HasSpan FunProperties where span_ = field @"spanInfo"
|
||||
import qualified ScopeGraph.Properties.Function as Props
|
||||
import qualified ScopeGraph.Properties.Reference as Props
|
||||
|
||||
type Sketch
|
||||
= SketchEff
|
||||
@ -60,7 +46,7 @@ type Sketch
|
||||
|
||||
data SketchEff m k =
|
||||
Declare Name Props.Declaration (() -> m k)
|
||||
| Reference Text Text RefProperties (() -> m k)
|
||||
| Reference Text Text Props.Reference (() -> m k)
|
||||
| NewScope (Map ScopeGraph.EdgeLabel [Name]) (Name -> m k)
|
||||
deriving (Generic, Generic1, HFunctor, Effect)
|
||||
|
||||
@ -71,22 +57,22 @@ declare :: forall sig m . (Has Sketch sig m) => Name -> Props.Declaration -> m (
|
||||
declare n props = send (Declare n props pure)
|
||||
|
||||
-- | Establish a reference to a prior declaration.
|
||||
reference :: forall sig m . (Has Sketch sig m) => Text -> Text -> RefProperties -> m ()
|
||||
reference :: forall sig m . (Has Sketch sig m) => Text -> Text -> Props.Reference -> m ()
|
||||
reference n decl props = send (Reference n decl props pure)
|
||||
|
||||
newScope :: forall sig m . (Has Sketch sig m) => Map ScopeGraph.EdgeLabel [Name] -> m Name
|
||||
newScope edges = send (NewScope edges pure)
|
||||
|
||||
declareFunction :: forall sig m . (Has Sketch sig m) => Maybe Name -> FunProperties -> m (Name, Name)
|
||||
declareFunction name props = do
|
||||
declareFunction :: forall sig m . (Has Sketch sig m) => Maybe Name -> Props.Function -> m (Name, Name)
|
||||
declareFunction name (Props.Function kind span) = do
|
||||
currentScope' <- currentScope
|
||||
let lexicalEdges = Map.singleton ScopeGraph.Lexical [ currentScope' ]
|
||||
associatedScope <- newScope lexicalEdges
|
||||
name' <- declareMaybeName name Props.Declaration
|
||||
{ Props.relation = ScopeGraph.Default
|
||||
, Props.kind = (getField @"kind" @FunProperties props)
|
||||
, Props.kind = kind
|
||||
, Props.associatedScope = Just associatedScope
|
||||
, Props.span = props^.span_
|
||||
, Props.span = span
|
||||
}
|
||||
pure (name', associatedScope)
|
||||
|
||||
|
22
semantic-scope-graph/src/ScopeGraph/Properties/Function.hs
Normal file
22
semantic-scope-graph/src/ScopeGraph/Properties/Function.hs
Normal file
@ -0,0 +1,22 @@
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
{-# LANGUAGE DeriveGeneric #-}
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
|
||||
-- | The 'Function' record type is used by the 'Control.Effect.Sketch' module to keep
|
||||
-- track of the parameters that need to be passed when establishing a new declaration.
|
||||
-- That is to say, it is a record type primarily used for its selector names.
|
||||
module ScopeGraph.Properties.Function
|
||||
( Function (..)
|
||||
) where
|
||||
|
||||
import Data.Generics.Product (field)
|
||||
import qualified Data.ScopeGraph as ScopeGraph (Kind)
|
||||
import GHC.Generics (Generic)
|
||||
import Source.Span
|
||||
|
||||
data Function = Function
|
||||
{ kind :: ScopeGraph.Kind
|
||||
, span :: Span
|
||||
} deriving Generic
|
||||
|
||||
instance HasSpan Function where span_ = field @"span"
|
@ -0,0 +1,9 @@
|
||||
-- | The 'Declaration' record type is used by the 'Control.Effect.Sketch' module to keep
|
||||
-- track of the parameters that need to be passed when establishing a new reference.
|
||||
-- It is currently unused, but will possess more fields in the future as scope graph
|
||||
-- functionality is enhanced.
|
||||
module ScopeGraph.Properties.Reference
|
||||
( Reference (..)
|
||||
) where
|
||||
|
||||
data Reference = Reference
|
Loading…
Reference in New Issue
Block a user