mirror of
https://github.com/github/semantic.git
synced 2024-11-23 16:37:50 +03:00
commit
f6c7c5e870
2
.github/workflows/haskell.yml
vendored
2
.github/workflows/haskell.yml
vendored
@ -37,7 +37,7 @@ jobs:
|
||||
name: Cache ~/.cabal/store
|
||||
with:
|
||||
path: ~/.cabal/store
|
||||
key: ${{ runner.os }}-${{ matrix.ghc }}-v8-cabal-store
|
||||
key: ${{ runner.os }}-${{ matrix.ghc }}-v9-cabal-store
|
||||
|
||||
- uses: actions/cache@v1
|
||||
name: Cache dist-newstyle
|
||||
|
@ -24,7 +24,7 @@ module Language.Python.ScopeGraph
|
||||
import qualified Analysis.Name as Name
|
||||
import AST.Element
|
||||
import Control.Effect.Fresh
|
||||
import Control.Effect.Sketch
|
||||
import Control.Effect.ScopeGraph
|
||||
import Control.Lens (set, (^.))
|
||||
import Data.Foldable
|
||||
import Data.Maybe
|
||||
@ -49,7 +49,7 @@ import Source.Span (span_)
|
||||
-- every single Python AST type.
|
||||
class (forall a . Show a => Show (t a)) => ToScopeGraph t where
|
||||
scopeGraph ::
|
||||
( Has Sketch sig m
|
||||
( Has ScopeGraph sig m
|
||||
, Monoid (m Result)
|
||||
)
|
||||
=> t Loc
|
||||
@ -61,7 +61,7 @@ instance (ToScopeGraph l, ToScopeGraph r) => ToScopeGraph (l :+: r) where
|
||||
|
||||
onField ::
|
||||
forall (field :: Symbol) syn sig m r .
|
||||
( Has Sketch sig m
|
||||
( Has ScopeGraph sig m
|
||||
, HasField field (r Loc) (syn Loc)
|
||||
, ToScopeGraph syn
|
||||
, Monoid (m Result)
|
||||
@ -75,7 +75,7 @@ onField
|
||||
onChildren ::
|
||||
( Traversable t
|
||||
, ToScopeGraph syn
|
||||
, Has Sketch sig m
|
||||
, Has ScopeGraph sig m
|
||||
, HasField "extraChildren" (r Loc) (t (syn Loc))
|
||||
, Monoid (m Result)
|
||||
)
|
||||
@ -86,7 +86,7 @@ onChildren
|
||||
. traverse scopeGraph
|
||||
. getField @"extraChildren"
|
||||
|
||||
scopeGraphModule :: Has Sketch sig m => Py.Module Loc -> m Result
|
||||
scopeGraphModule :: Has ScopeGraph sig m => Py.Module Loc -> m Result
|
||||
scopeGraphModule = getAp . scopeGraph
|
||||
|
||||
instance ToScopeGraph Py.AssertStatement where scopeGraph = onChildren
|
||||
@ -231,7 +231,13 @@ instance ToScopeGraph Py.Integer where scopeGraph = mempty
|
||||
|
||||
instance ToScopeGraph Py.ImportStatement where scopeGraph = todo
|
||||
|
||||
instance ToScopeGraph Py.ImportFromStatement where scopeGraph = todo
|
||||
instance ToScopeGraph Py.ImportFromStatement where
|
||||
scopeGraph (Py.ImportFromStatement _ [] (L1 (Py.DottedName _ names)) (Just (Py.WildcardImport _ _))) = do
|
||||
let toName (Py.Identifier _ name) = Name.name name
|
||||
complete <* insertEdge ScopeGraph.Import (toName <$> names)
|
||||
scopeGraph term = todo (show term)
|
||||
|
||||
|
||||
|
||||
instance ToScopeGraph Py.Lambda where scopeGraph = todo
|
||||
|
||||
|
@ -7,15 +7,19 @@ module Main (main) where
|
||||
|
||||
import Analysis.Name (Name)
|
||||
import qualified Analysis.Name as Name
|
||||
import qualified AST.Unmarshal as TS
|
||||
import Control.Algebra
|
||||
import Control.Carrier.Lift
|
||||
import Control.Carrier.Sketch.Fresh
|
||||
import Control.Carrier.Sketch.ScopeGraph
|
||||
import Control.Effect.ScopeGraph
|
||||
import Control.Monad
|
||||
import qualified Data.ByteString as ByteString
|
||||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
import qualified Data.ScopeGraph as ScopeGraph
|
||||
import Data.Semilattice.Lower
|
||||
import qualified Language.Python ()
|
||||
import qualified Language.Python as Py (Term)
|
||||
import qualified Language.Python.Grammar as TSP
|
||||
import ScopeGraph.Convert
|
||||
import qualified ScopeGraph.Properties.Declaration as Props
|
||||
import qualified ScopeGraph.Properties.Function as Props
|
||||
@ -29,8 +33,6 @@ import qualified System.Path as Path
|
||||
import qualified System.Path.Directory as Path
|
||||
import qualified Test.Tasty as Tasty
|
||||
import qualified Test.Tasty.HUnit as HUnit
|
||||
import qualified Language.Python.Grammar as TSP
|
||||
import qualified AST.Unmarshal as TS
|
||||
|
||||
{-
|
||||
|
||||
@ -56,7 +58,7 @@ The graph should be
|
||||
runScopeGraph :: ToScopeGraph t => Path.AbsRelFile -> Source.Source -> t Loc -> (ScopeGraph.ScopeGraph Name, Result)
|
||||
runScopeGraph p _src item = run . runSketch (Just p) $ scopeGraph item
|
||||
|
||||
sampleGraphThing :: (Has Sketch sig m) => m Result
|
||||
sampleGraphThing :: (Has ScopeGraph sig m) => m Result
|
||||
sampleGraphThing = do
|
||||
declare "hello" (Props.Declaration ScopeGraph.Assignment ScopeGraph.Default Nothing (Span (Pos 2 0) (Pos 2 10)))
|
||||
declare "goodbye" (Props.Declaration ScopeGraph.Assignment ScopeGraph.Default Nothing (Span (Pos 3 0) (Pos 3 12)))
|
||||
@ -77,7 +79,7 @@ assertSimpleAssignment = do
|
||||
(expecto, Complete) <- runM $ runSketch Nothing sampleGraphThing
|
||||
HUnit.assertEqual "Should work for simple case" expecto result
|
||||
|
||||
expectedReference :: (Has Sketch sig m) => m Result
|
||||
expectedReference :: (Has ScopeGraph 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" Props.Reference
|
||||
@ -91,13 +93,13 @@ assertSimpleReference = do
|
||||
|
||||
HUnit.assertEqual "Should work for simple case" expecto result
|
||||
|
||||
expectedLexicalScope :: (Has Sketch sig m) => m Result
|
||||
expectedLexicalScope :: (Has ScopeGraph sig m) => m Result
|
||||
expectedLexicalScope = do
|
||||
_ <- 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 :: (Has ScopeGraph sig m) => m Result
|
||||
expectedFunctionArg = do
|
||||
(_, associatedScope) <- declareFunction (Just $ Name.name "foo") (Props.Function ScopeGraph.Function (Span (Pos 0 0) (Pos 1 12)))
|
||||
withScope associatedScope $ do
|
||||
@ -107,6 +109,11 @@ expectedFunctionArg = do
|
||||
reference "foo" "foo" Props.Reference
|
||||
pure Complete
|
||||
|
||||
expectedImportHole :: (Has ScopeGraph sig m) => m Result
|
||||
expectedImportHole = do
|
||||
insertEdge ScopeGraph.Import (NonEmpty.fromList ["cheese", "ints"])
|
||||
pure Complete
|
||||
|
||||
assertLexicalScope :: HUnit.Assertion
|
||||
assertLexicalScope = do
|
||||
let path = "semantic-python/test/fixtures/5-02-simple-function.py"
|
||||
@ -123,6 +130,14 @@ assertFunctionArg = do
|
||||
(expecto, Complete) -> HUnit.assertEqual "Should work for simple case" expecto graph
|
||||
(_, Todo msg) -> HUnit.assertFailure ("Failed to complete:" <> show msg)
|
||||
|
||||
assertImportHole :: HUnit.Assertion
|
||||
assertImportHole = do
|
||||
let path = "semantic-python/test/fixtures/cheese/6-01-imports.py"
|
||||
(graph, _) <- graphFile path
|
||||
case run (runSketch Nothing expectedImportHole) of
|
||||
(expecto, Complete) -> HUnit.assertEqual "Should work for simple case" expecto graph
|
||||
(_, Todo msg) -> HUnit.assertFailure ("Failed to complete:" <> show msg)
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
-- make sure we're in the root directory so the paths resolve properly
|
||||
@ -141,5 +156,8 @@ main = do
|
||||
Tasty.testGroup "lexical scopes" [
|
||||
HUnit.testCase "simple function scope" assertLexicalScope
|
||||
, HUnit.testCase "simple function argument" assertFunctionArg
|
||||
],
|
||||
Tasty.testGroup "imports" [
|
||||
HUnit.testCase "simple function argument" assertImportHole
|
||||
]
|
||||
]
|
||||
|
1
semantic-python/test/fixtures/cheese/6-01-imports.py
vendored
Normal file
1
semantic-python/test/fixtures/cheese/6-01-imports.py
vendored
Normal file
@ -0,0 +1 @@
|
||||
from cheese.ints import *
|
5
semantic-python/test/fixtures/cheese/ints.py
vendored
Normal file
5
semantic-python/test/fixtures/cheese/ints.py
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
def one():
|
||||
return 1
|
||||
|
||||
def two():
|
||||
return 2
|
@ -20,8 +20,8 @@ tested-with: GHC == 8.6.5
|
||||
|
||||
library
|
||||
exposed-modules:
|
||||
Control.Carrier.Sketch.Fresh
|
||||
Control.Effect.Sketch
|
||||
Control.Carrier.Sketch.ScopeGraph
|
||||
Control.Effect.ScopeGraph
|
||||
ScopeGraph.Convert
|
||||
ScopeGraph.Properties.Declaration
|
||||
ScopeGraph.Properties.Function
|
||||
|
@ -13,10 +13,10 @@
|
||||
|
||||
-- | This carrier interprets the Sketch effect, keeping track of
|
||||
-- the current scope and in-progress graph internally.
|
||||
module Control.Carrier.Sketch.Fresh
|
||||
module Control.Carrier.Sketch.ScopeGraph
|
||||
( SketchC (..)
|
||||
, runSketch
|
||||
, module Control.Effect.Sketch
|
||||
, module Control.Effect.ScopeGraph
|
||||
) where
|
||||
|
||||
import Analysis.Name (Name)
|
||||
@ -25,9 +25,10 @@ import Control.Algebra
|
||||
import Control.Carrier.Fresh.Strict
|
||||
import Control.Carrier.Reader
|
||||
import Control.Carrier.State.Strict
|
||||
import Control.Effect.Sketch
|
||||
import Control.Effect.ScopeGraph (ScopeGraphEff (..))
|
||||
import Control.Monad.IO.Class
|
||||
import Data.Bifunctor
|
||||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
import Data.Module
|
||||
import Data.ScopeGraph (ScopeGraph)
|
||||
import qualified Data.ScopeGraph as ScopeGraph
|
||||
@ -56,7 +57,7 @@ instance Lower Sketchbook where
|
||||
newtype SketchC address m a = SketchC (StateC Sketchbook (FreshC m) a)
|
||||
deriving (Applicative, Functor, Monad, MonadIO)
|
||||
|
||||
instance (Effect sig, Algebra sig m) => Algebra (SketchEff :+: Reader Name :+: Fresh :+: sig) (SketchC Name m) where
|
||||
instance (Effect sig, Algebra sig m) => Algebra (ScopeGraphEff :+: Reader Name :+: Fresh :+: sig) (SketchC Name m) where
|
||||
alg (L (Declare n props k)) = do
|
||||
Sketchbook old current <- SketchC (get @Sketchbook)
|
||||
let Props.Declaration kind relation associatedScope span = props
|
||||
@ -92,6 +93,12 @@ instance (Effect sig, Algebra sig m) => Algebra (SketchEff :+: Reader Name :+: F
|
||||
let new = ScopeGraph.newScope name edges old
|
||||
SketchC (put (Sketchbook new current))
|
||||
k name
|
||||
alg (L (InsertEdge label address k)) = do
|
||||
Sketchbook old current <- SketchC get
|
||||
let new = ScopeGraph.addImportEdge label (NonEmpty.toList address) current old
|
||||
SketchC (put (Sketchbook new current))
|
||||
k ()
|
||||
|
||||
alg (R (L a)) = case a of
|
||||
Ask k -> SketchC (gets sCurrentScope) >>= k
|
||||
Local fn go k -> do
|
@ -8,15 +8,16 @@
|
||||
{-# LANGUAGE TypeApplications #-}
|
||||
{-# LANGUAGE TypeOperators #-}
|
||||
|
||||
-- | The Sketch effect is used to build up a scope graph over
|
||||
-- | The ScopeGraph effect is used to build up a scope graph over
|
||||
-- the lifetime of a monadic computation. The name is meant to evoke
|
||||
-- physically sketching the hierarchical outline of a graph.
|
||||
module Control.Effect.Sketch
|
||||
( Sketch
|
||||
, SketchEff (..)
|
||||
module Control.Effect.ScopeGraph
|
||||
( ScopeGraph
|
||||
, ScopeGraphEff (..)
|
||||
, declare
|
||||
-- Scope Manipulation
|
||||
, currentScope
|
||||
, insertEdge
|
||||
, newScope
|
||||
, withScope
|
||||
, declareFunction
|
||||
@ -35,35 +36,42 @@ import qualified Data.Map.Strict as Map
|
||||
import qualified Data.ScopeGraph as ScopeGraph
|
||||
import Data.Text (Text)
|
||||
import GHC.Generics (Generic, Generic1)
|
||||
import Data.List.NonEmpty
|
||||
|
||||
import qualified ScopeGraph.Properties.Declaration as Props
|
||||
import qualified ScopeGraph.Properties.Function as Props
|
||||
import qualified ScopeGraph.Properties.Reference as Props
|
||||
|
||||
type Sketch
|
||||
= SketchEff
|
||||
type ScopeGraph
|
||||
= ScopeGraphEff
|
||||
:+: Fresh
|
||||
:+: Reader Name
|
||||
|
||||
data SketchEff m k =
|
||||
data ScopeGraphEff m k =
|
||||
Declare Name Props.Declaration (() -> m k)
|
||||
| Reference Text Text Props.Reference (() -> m k)
|
||||
| NewScope (Map ScopeGraph.EdgeLabel [Name]) (Name -> m k)
|
||||
| InsertEdge ScopeGraph.EdgeLabel (NonEmpty Name) (() -> m k)
|
||||
deriving (Generic, Generic1, HFunctor, Effect)
|
||||
|
||||
currentScope :: Has (Reader Name) sig m => m Name
|
||||
currentScope = ask
|
||||
|
||||
declare :: forall sig m . (Has Sketch sig m) => Name -> Props.Declaration -> m ()
|
||||
declare :: forall sig m . (Has ScopeGraph 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 -> Props.Reference -> m ()
|
||||
reference :: forall sig m . (Has ScopeGraph 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 :: forall sig m . Has ScopeGraph sig m => Map ScopeGraph.EdgeLabel [Name] -> m Name
|
||||
newScope edges = send (NewScope edges pure)
|
||||
|
||||
declareFunction :: forall sig m . (Has Sketch sig m) => Maybe Name -> Props.Function -> m (Name, Name)
|
||||
-- | Takes an edge label and a list of names and inserts an import edge to a hole.
|
||||
insertEdge :: Has ScopeGraph sig m => ScopeGraph.EdgeLabel -> NonEmpty Name -> m ()
|
||||
insertEdge label targets = send (InsertEdge label targets pure)
|
||||
|
||||
declareFunction :: forall sig m . (Has ScopeGraph 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' ]
|
||||
@ -76,7 +84,7 @@ declareFunction name (Props.Function kind span) = do
|
||||
}
|
||||
pure (name', associatedScope)
|
||||
|
||||
declareMaybeName :: Has Sketch sig m
|
||||
declareMaybeName :: Has ScopeGraph sig m
|
||||
=> Maybe Name
|
||||
-> Props.Declaration
|
||||
-> m Name
|
||||
@ -87,9 +95,8 @@ declareMaybeName maybeName props = do
|
||||
name <- Name.gensym
|
||||
name <$ declare name (props { Props.relation = ScopeGraph.Gensym })
|
||||
|
||||
withScope :: Has Sketch sig m
|
||||
withScope :: Has ScopeGraph sig m
|
||||
=> Name
|
||||
-> m a
|
||||
-> m a
|
||||
withScope scope = local (const scope)
|
||||
|
@ -23,6 +23,7 @@ module Data.ScopeGraph
|
||||
, insertImportReference
|
||||
, newScope
|
||||
, newPreludeScope
|
||||
, addImportEdge
|
||||
, insertScope
|
||||
, insertEdge
|
||||
, Path(..)
|
||||
@ -57,6 +58,8 @@ import Data.Bifunctor
|
||||
import Data.Foldable
|
||||
import Data.Hashable
|
||||
import Data.Hole
|
||||
import Data.List.NonEmpty (NonEmpty)
|
||||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
import Data.Map.Strict (Map)
|
||||
import qualified Data.Map.Strict as Map
|
||||
import Data.Maybe
|
||||
@ -342,7 +345,8 @@ putDeclarationScopeAtPosition scope position assocScope g@(ScopeGraph graph) = f
|
||||
let seq = Seq.adjust' (\Info{..} -> Info { infoAssociatedScope = assocScope, .. }) (unPosition position) dataSeq
|
||||
pure $ ScopeGraph (Map.adjust (\s -> s { declarations = seq }) scope graph)
|
||||
|
||||
lookupReference :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Path scopeAddress)
|
||||
-- | Lookup a reference by traversing the paths of a given scope and return a Maybe (Path address)
|
||||
lookupReference :: Ord address => Name -> address -> ScopeGraph address -> Maybe (Path address)
|
||||
lookupReference name scope g = fmap snd . Map.lookup (Reference name) =<< pathsOfScope scope g
|
||||
|
||||
insertEdge :: Ord scopeAddress => EdgeLabel -> scopeAddress -> scopeAddress -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
|
||||
@ -352,6 +356,34 @@ insertEdge label target currentAddress g@(ScopeGraph graph) = fromMaybe g $ do
|
||||
let newScope = currentScope' { edges = Map.insert label (target : scopes) (edges currentScope') }
|
||||
pure (ScopeGraph (Map.insert currentAddress newScope graph))
|
||||
|
||||
insertEdges :: Ord scopeAddress => NonEmpty EdgeLabel -> scopeAddress -> scopeAddress -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
|
||||
insertEdges labels target currentAddress g =
|
||||
foldr (\label graph -> insertEdge label target currentAddress graph) g labels
|
||||
|
||||
-- | Add an import edge of the form 'a -> Import -> b -> Import -> c' or creates intermediate void scopes of the form
|
||||
-- 'a -> Void -> b -> Import -> c' if the given scopes cannot be found.
|
||||
addImportEdge :: Ord scopeAddress => EdgeLabel -> [scopeAddress] -> scopeAddress -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
|
||||
addImportEdge edge importEdge currentAddress g = do
|
||||
case importEdge of
|
||||
[] -> g
|
||||
(name:[]) -> maybe
|
||||
(addImportHole edge name currentAddress g)
|
||||
(const (insertEdge edge name currentAddress g))
|
||||
(lookupScope name g)
|
||||
(name:names) -> let
|
||||
scopeGraph' = maybe
|
||||
(addImportHole edge name currentAddress g)
|
||||
(const (insertEdge edge name currentAddress g))
|
||||
(lookupScope name g)
|
||||
in
|
||||
addImportEdge edge names name scopeGraph'
|
||||
|
||||
addImportHole :: Ord scopeAddress => EdgeLabel -> scopeAddress -> scopeAddress -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
|
||||
addImportHole edge name currentAddress g = let
|
||||
scopeGraph' = newScope name mempty g
|
||||
in
|
||||
insertEdges (NonEmpty.fromList [Void, edge]) name currentAddress scopeGraph'
|
||||
|
||||
|
||||
-- | Update the 'Scope' containing a 'Declaration' with an associated scope address.
|
||||
-- Returns an unmodified 'ScopeGraph' if the 'Declaration' cannot be found with the given scope address.
|
||||
@ -428,5 +460,5 @@ formatDeclaration = formatName . unDeclaration
|
||||
|
||||
-- | The type of edge from a scope to its parent scopes.
|
||||
-- Either a lexical edge or an import edge in the case of non-lexical edges.
|
||||
data EdgeLabel = Lexical | Import | Export | Superclass
|
||||
data EdgeLabel = Lexical | Import | Export | Superclass | Void
|
||||
deriving (Bounded, Enum, Eq, Ord, Show)
|
||||
|
@ -13,14 +13,14 @@ module ScopeGraph.Convert
|
||||
, complete
|
||||
) where
|
||||
|
||||
import Control.Effect.Sketch
|
||||
import Control.Effect.ScopeGraph
|
||||
import Data.List.NonEmpty
|
||||
import Data.Typeable
|
||||
import Source.Loc
|
||||
|
||||
class Typeable t => ToScopeGraph t where
|
||||
scopeGraph ::
|
||||
( Has Sketch sig m
|
||||
( Has ScopeGraph sig m
|
||||
)
|
||||
=> t Loc
|
||||
-> m Result
|
||||
|
@ -34,7 +34,7 @@ import Data.List.NonEmpty (NonEmpty, nonEmpty)
|
||||
import qualified Data.Map as Map
|
||||
|
||||
import Control.Abstract hiding
|
||||
(Array (..), Boolean (..), Function (..), Hash (..), Numeric (..), Object (..), String (..), Unit (..), While (..))
|
||||
(Array (..), Boolean (..), Function (..), Hash (..), Numeric (..), Object (..), String (..), Unit (..), While (..), Void)
|
||||
import qualified Control.Abstract as Abstract
|
||||
import Data.Abstract.BaseError
|
||||
import Data.Abstract.Evaluatable
|
||||
|
@ -14,7 +14,7 @@ module Data.Syntax.Expression (module Data.Syntax.Expression) where
|
||||
import Prelude hiding (null)
|
||||
|
||||
import Analysis.Name as Name
|
||||
import Control.Abstract hiding (Bitwise (..), Call)
|
||||
import Control.Abstract hiding (Bitwise (..), Call, Void)
|
||||
import Control.Applicative
|
||||
import Control.Monad
|
||||
import Data.Abstract.Evaluatable as Abstract
|
||||
|
Loading…
Reference in New Issue
Block a user