1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 00:42:33 +03:00

Merge branch 'master' into markdone

This commit is contained in:
Josh Vera 2020-02-13 14:32:29 -05:00 committed by GitHub
commit c7c6df0828
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
724 changed files with 19858 additions and 11322 deletions

View File

@ -6,6 +6,7 @@
module Evaluation (benchmarks) where
import Analysis.Project
import Control.Carrier.Parse.Simple
import Data.Abstract.Evaluatable
import Data.Bifunctor
@ -13,7 +14,6 @@ import Data.Blob.IO (readBlobFromPath)
import qualified Data.Duration as Duration
import Data.Graph.Algebraic (topologicalSort)
import qualified Data.Language as Language
import Data.Project
import Data.Proxy
import Gauge.Main
import Parsing.Parser

View File

@ -9,7 +9,7 @@ import Control.Carrier.Reader
import Control.Exception (throwIO)
import Control.Monad
import Data.Foldable
import Data.Language (LanguageMode (..), PerLanguageModes (..))
import Data.Language (PerLanguageModes (..), aLaCarteLanguageModes, preciseLanguageModes)
import Gauge
import System.FilePath.Glob
import qualified System.Path as Path
@ -68,28 +68,6 @@ parseSymbolsFilePath ::
-> m ParseTreeSymbolResponse
parseSymbolsFilePath languageModes path = readBlob (File.fromPath path) >>= runReader languageModes . parseSymbols . pure @[]
aLaCarteLanguageModes :: PerLanguageModes
aLaCarteLanguageModes = PerLanguageModes
{ pythonMode = ALaCarte
, rubyMode = ALaCarte
, goMode = ALaCarte
, typescriptMode = ALaCarte
, tsxMode = ALaCarte
, javascriptMode = ALaCarte
, jsxMode = ALaCarte
}
preciseLanguageModes :: PerLanguageModes
preciseLanguageModes = PerLanguageModes
{ pythonMode = Precise
, rubyMode = Precise
, goMode = Precise
, typescriptMode = Precise
, tsxMode = Precise
, javascriptMode = Precise
, jsxMode = Precise
}
testOptions :: Config.Options
testOptions = defaultOptions
{ optionsFailOnWarning = flag FailOnWarning True

View File

@ -40,6 +40,7 @@ library
import: common
hs-source-dirs: src
exposed-modules:
Analysis.Blob
Analysis.Carrier.Env.Monovariant
Analysis.Carrier.Env.Precise
Analysis.Carrier.Heap.Monovariant
@ -54,6 +55,7 @@ library
Analysis.ImportGraph
Analysis.Intro
Analysis.Name
Analysis.Project
Analysis.Typecheck
Control.Carrier.Fail.WithLoc
build-depends:

View File

@ -0,0 +1,45 @@
{-# LANGUAGE OverloadedStrings #-}
module Analysis.Blob
( Blob (..)
, fromSource
, blobLanguage
, blobPath
, nullBlob
) where
import Analysis.File
import Data.Aeson
import Source.Language as Language
import Source.Source as Source
import qualified System.Path as Path
import qualified System.Path.PartClass as Path.PartClass
-- | The source, path information, and language of a file read from disk.
data Blob = Blob
{ blobSource :: Source -- ^ The UTF-8 encoded source text of the blob.
, blobFile :: File Language -- ^ Path/language information for this blob.
} deriving (Show, Eq)
instance FromJSON Blob where
parseJSON = withObject "Blob" $ \b -> do
src <- b .: "content"
Right pth <- fmap Path.parse (b .: "path")
lang <- b .: "language"
let lang' = if knownLanguage lang then lang else Language.forPath pth
pure (fromSource (pth :: Path.AbsRelFile) lang' src)
-- | Create a Blob from a provided path, language, and UTF-8 source.
-- The resulting Blob's span is taken from the 'totalSpan' of the source.
fromSource :: Path.PartClass.AbsRel ar => Path.File ar -> Language -> Source -> Blob
fromSource filepath language source
= Blob source (Analysis.File.File (Path.toAbsRel filepath) (totalSpan source) language)
blobLanguage :: Blob -> Language
blobLanguage = Analysis.File.fileBody . blobFile
blobPath :: Blob -> FilePath
blobPath = Path.toString . Analysis.File.filePath . blobFile
nullBlob :: Blob -> Bool
nullBlob = Source.null . blobSource

View File

@ -0,0 +1,33 @@
module Analysis.Project
( Project (..)
, projectExtensions
, projectName
, projectFiles
) where
import Prelude hiding (readFile)
import Analysis.Blob
import Analysis.File
import Data.Text (Text)
import qualified Data.Text as T
import Source.Language
import System.FilePath.Posix
-- | A 'Project' contains all the information that semantic needs
-- to execute an analysis, diffing, or graphing pass.
data Project = Project
{ projectRootDir :: FilePath
, projectBlobs :: [Blob]
, projectLanguage :: Language
, projectExcludeDirs :: [FilePath]
} deriving (Eq, Show)
projectName :: Project -> Text
projectName = T.pack . dropExtensions . takeFileName . projectRootDir
projectExtensions :: Project -> [String]
projectExtensions = extensionsForLanguage . projectLanguage
projectFiles :: Project -> [File Language]
projectFiles = fmap blobFile . projectBlobs

View File

@ -4,14 +4,14 @@ module Language.Python
, Language.Python.Grammar.tree_sitter_python
) where
import qualified AST.Unmarshal as TS
import Data.Proxy
import qualified Language.Python.AST as Py
import qualified Language.Python.Grammar (tree_sitter_python)
import Language.Python.ScopeGraph
import qualified Language.Python.Tags as PyTags
import ScopeGraph.Convert
import Scope.Graph.Convert
import qualified Tags.Tagging.Precise as Tags
import qualified Language.Python.Grammar (tree_sitter_python)
import qualified AST.Unmarshal as TS
newtype Term a = Term { getTerm :: Py.Module a }

View File

@ -23,10 +23,13 @@ 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 qualified Control.Effect.ScopeGraph.Properties.Declaration as Props
import qualified Control.Effect.ScopeGraph.Properties.Function as Props
import qualified Control.Effect.ScopeGraph.Properties.Reference as Props
import Control.Lens (set, (^.))
import Data.Foldable
import Data.List.NonEmpty (NonEmpty (..))
import Data.Maybe
import Data.Monoid
import qualified Data.ScopeGraph as ScopeGraph
@ -36,12 +39,9 @@ import GHC.Records
import GHC.TypeLits
import qualified Language.Python.AST as Py
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 Scope.Graph.Convert (Result (..), complete, todo)
import Source.Loc (Loc)
import Source.Span (Span, span_)
-- This typeclass is internal-only, though it shares the same interface
-- as the one defined in semantic-scope-graph. The somewhat-unconventional
@ -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
( ScopeGraphEff 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
( ScopeGraphEff 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
, ScopeGraphEff 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 :: ScopeGraphEff sig m => Py.Module Loc -> m Result
scopeGraphModule = getAp . scopeGraph
instance ToScopeGraph Py.AssertStatement where scopeGraph = onChildren
@ -215,8 +215,9 @@ instance ToScopeGraph Py.FutureImportStatement where scopeGraph = todo
instance ToScopeGraph Py.GeneratorExpression where scopeGraph = todo
instance ToScopeGraph Py.Identifier where
scopeGraph (Py.Identifier _ name) = do
reference name name Props.Reference
scopeGraph (Py.Identifier ann name) = do
let refProps = Props.Reference ScopeGraph.Identifier ScopeGraph.Default (ann^.span_ :: Span)
newReference (Name.name name) refProps
complete
instance ToScopeGraph Py.IfStatement where
@ -229,9 +230,33 @@ instance ToScopeGraph Py.GlobalStatement where scopeGraph = todo
instance ToScopeGraph Py.Integer where scopeGraph = mempty
instance ToScopeGraph Py.ImportStatement where scopeGraph = todo
instance ToScopeGraph Py.ImportStatement where
scopeGraph (Py.ImportStatement _ ((R1 (Py.DottedName _ names@((Py.Identifier ann name) :| _))) :| [])) = do
let toName (Py.Identifier _ name) = Name.name name
newEdge ScopeGraph.Import (toName <$> names)
let referenceProps = Props.Reference ScopeGraph.Identifier ScopeGraph.Default (ann^.span_ :: Span)
newReference (Name.name name) referenceProps
let pairs = zip (toList names) (tail $ toList names)
for_ pairs $ \pair -> do
case pair of
(scopeIdentifier, referenceIdentifier@(Py.Identifier ann2 _)) -> do
withScope (toName scopeIdentifier) $ do
let referenceProps = Props.Reference ScopeGraph.Identifier ScopeGraph.Default (ann2^.span_ :: Span)
newReference (toName referenceIdentifier) referenceProps
complete
scopeGraph term = todo (show term)
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 <* newEdge ScopeGraph.Import (toName <$> names)
scopeGraph impossibleTerm@(Py.ImportFromStatement _ [] (L1 (Py.DottedName _ _)) Nothing) =
todo impossibleTerm
scopeGraph term = todo term
instance ToScopeGraph Py.ImportFromStatement where scopeGraph = todo
instance ToScopeGraph Py.Lambda where scopeGraph = todo

View File

@ -7,19 +7,22 @@ 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 qualified Control.Effect.ScopeGraph.Properties.Declaration as Props
import qualified Control.Effect.ScopeGraph.Properties.Function as Props
import qualified Control.Effect.ScopeGraph.Properties.Reference as Props
import Control.Monad
import qualified Data.ByteString as ByteString
import qualified Data.List.NonEmpty as NonEmpty
import Data.Module (ModuleInfo (..))
import qualified Data.ScopeGraph as ScopeGraph
import Data.Semilattice.Lower
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 qualified Language.Python.Grammar as TSP
import Scope.Graph.Convert
import Source.Loc
import qualified Source.Source as Source
import Source.Span
@ -29,8 +32,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
{-
@ -54,9 +55,11 @@ 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
runScopeGraph p _src item = run . runSketch info $ scopeGraph item
where
info = ModuleInfo (Path.toString p) "Python" mempty
sampleGraphThing :: (Has Sketch sig m) => m Result
sampleGraphThing :: ScopeGraphEff 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)))
@ -74,52 +77,95 @@ assertSimpleAssignment :: HUnit.Assertion
assertSimpleAssignment = do
let path = "semantic-python/test/fixtures/1-04-toplevel-assignment.py"
(result, Complete) <- graphFile path
(expecto, Complete) <- runM $ runSketch Nothing sampleGraphThing
(expecto, Complete) <- runM $ runSketch (ModuleInfo path "Python" mempty) sampleGraphThing
HUnit.assertEqual "Should work for simple case" expecto result
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" Props.Reference
pure Complete
assertSimpleReference :: HUnit.Assertion
assertSimpleReference = do
let path = "semantic-python/test/fixtures/5-01-simple-reference.py"
(result, Complete) <- graphFile path
(expecto, Complete) <- runM $ runSketch Nothing expectedReference
(expecto, Complete) <- runM $ runSketch (ModuleInfo path "Python" mempty) expectedReference
HUnit.assertEqual "Should work for simple case" expecto result
expectedLexicalScope :: (Has Sketch 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 {}
expectedReference :: ScopeGraphEff sig m => m Result
expectedReference = do
declare "x" (Props.Declaration ScopeGraph.Assignment ScopeGraph.Default Nothing (Span (Pos 0 0) (Pos 0 5)))
let refProperties = Props.Reference ScopeGraph.Identifier ScopeGraph.Default (Span (Pos 1 0) (Pos 1 1))
newReference "x" refProperties
pure Complete
expectedFunctionArg :: (Has Sketch 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
declare "x" (Props.Declaration ScopeGraph.Identifier ScopeGraph.Default Nothing lowerBound)
reference "x" "x" Props.Reference
pure ()
reference "foo" "foo" Props.Reference
expectedQualifiedImport :: ScopeGraphEff sig m => m Result
expectedQualifiedImport = do
newEdge ScopeGraph.Import (NonEmpty.fromList ["cheese", "ints"])
let refProperties = Props.Reference ScopeGraph.Identifier ScopeGraph.Default (Span (Pos 0 7) (Pos 0 13))
newReference (Name.name "cheese") refProperties
withScope "cheese" $ do
let refProperties = Props.Reference ScopeGraph.Identifier ScopeGraph.Default (Span (Pos 0 14) (Pos 0 18))
newReference (Name.name "ints") refProperties
pure Complete
expectedImportHole :: ScopeGraphEff sig m => m Result
expectedImportHole = do
newEdge ScopeGraph.Import (NonEmpty.fromList ["cheese", "ints"])
pure Complete
assertLexicalScope :: HUnit.Assertion
assertLexicalScope = do
let path = "semantic-python/test/fixtures/5-02-simple-function.py"
let info = ModuleInfo path "Python" mempty
(graph, _) <- graphFile path
case run (runSketch Nothing expectedLexicalScope) of
case run (runSketch info expectedLexicalScope) of
(expecto, Complete) -> HUnit.assertEqual "Should work for simple case" expecto graph
(_, Todo msg) -> HUnit.assertFailure ("Failed to complete:" <> show msg)
expectedLexicalScope :: ScopeGraphEff sig m => m Result
expectedLexicalScope = do
_ <- declareFunction (Just $ Name.name "foo") (Props.Function ScopeGraph.Function (Span (Pos 0 0) (Pos 1 24)))
let refProperties = Props.Reference ScopeGraph.Identifier ScopeGraph.Default (Span (Pos 3 0) (Pos 3 3))
newReference "foo" refProperties
pure Complete
assertFunctionArg :: HUnit.Assertion
assertFunctionArg = do
let path = "semantic-python/test/fixtures/5-03-function-argument.py"
(graph, _) <- graphFile path
case run (runSketch Nothing expectedFunctionArg) of
let info = ModuleInfo path "Python" mempty
case run (runSketch info expectedFunctionArg) of
(expecto, Complete) -> HUnit.assertEqual "Should work for simple case" expecto graph
(_, Todo msg) -> HUnit.assertFailure ("Failed to complete:" <> show msg)
expectedFunctionArg :: ScopeGraphEff 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
declare "x" (Props.Declaration ScopeGraph.Parameter ScopeGraph.Default Nothing (Span (Pos 0 8) (Pos 0 9)))
let refProperties = Props.Reference ScopeGraph.Identifier ScopeGraph.Default (Span (Pos 1 11) (Pos 1 12))
newReference "x" refProperties
pure ()
let refProperties = Props.Reference ScopeGraph.Identifier ScopeGraph.Default (Span (Pos 3 0) (Pos 3 3))
newReference "foo" refProperties
pure Complete
assertImportHole :: HUnit.Assertion
assertImportHole = do
let path = "semantic-python/test/fixtures/cheese/6-01-imports.py"
(graph, _) <- graphFile path
let info = ModuleInfo path "Python" mempty
case run (runSketch info expectedImportHole) of
(expecto, Complete) -> HUnit.assertEqual "Should work for simple case" expecto graph
(_, Todo msg) -> HUnit.assertFailure ("Failed to complete:" <> show msg)
assertQualifiedImport :: HUnit.Assertion
assertQualifiedImport = do
let path = "semantic-python/test/fixtures/cheese/6-01-qualified-imports.py"
(graph, _) <- graphFile path
let info = ModuleInfo path "Python" mempty
case run (runSketch info expectedQualifiedImport) of
(expecto, Complete) -> HUnit.assertEqual "Should work for simple case" expecto graph
(_, Todo msg) -> HUnit.assertFailure ("Failed to complete:" <> show msg)
@ -141,5 +187,9 @@ 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
, HUnit.testCase "qualified imports" assertQualifiedImport
]
]

View File

@ -0,0 +1 @@
from cheese.ints import *

View File

@ -0,0 +1 @@
import cheese.ints

View File

@ -0,0 +1,5 @@
def one():
return 1
def two():
return 2

View File

@ -20,12 +20,18 @@ tested-with: GHC == 8.6.5
library
exposed-modules:
Control.Carrier.Sketch.Fresh
Control.Effect.Sketch
ScopeGraph.Convert
ScopeGraph.Properties.Declaration
ScopeGraph.Properties.Function
ScopeGraph.Properties.Reference
Control.Carrier.Sketch.ScopeGraph
Control.Effect.ScopeGraph
Control.Effect.ScopeGraph.Properties.Declaration
Control.Effect.ScopeGraph.Properties.Function
Control.Effect.ScopeGraph.Properties.Reference
Scope.Graph.AdjacencyList
Scope.Graph.Convert
Scope.Info
Scope.Path
Scope.Reference
Scope.Scope
Scope.Types
Data.Hole
Data.Module
Data.ScopeGraph

View File

@ -1,117 +0,0 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
-- | This carrier interprets the Sketch effect, keeping track of
-- the current scope and in-progress graph internally.
module Control.Carrier.Sketch.Fresh
( SketchC (..)
, runSketch
, module Control.Effect.Sketch
) where
import Analysis.Name (Name)
import qualified Analysis.Name as Name
import Control.Algebra
import Control.Carrier.Fresh.Strict
import Control.Carrier.Reader
import Control.Carrier.State.Strict
import Control.Effect.Sketch
import Control.Monad.IO.Class
import Data.Bifunctor
import Data.Module
import Data.ScopeGraph (ScopeGraph)
import qualified Data.ScopeGraph as ScopeGraph
import Data.Semilattice.Lower
import qualified ScopeGraph.Properties.Declaration as Props
import Source.Span
import qualified System.Path as Path
-- | The state type used to keep track of the in-progress graph and
-- positional/contextual information. The name "sketchbook" is meant
-- to invoke an in-progress, concealed work, as well as the
-- "sketching" of a graph.
data Sketchbook = Sketchbook
{ sGraph :: ScopeGraph Name
, sCurrentScope :: Name
} deriving (Eq, Show)
instance Lower Sketchbook where
lowerBound =
let
initialGraph = ScopeGraph.insertScope n lowerBound lowerBound
n = Name.nameI 0
in
Sketchbook initialGraph n
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
alg (L (Declare n props k)) = do
Sketchbook old current <- SketchC (get @Sketchbook)
let Props.Declaration kind relation associatedScope span = props
let (new, _pos) =
ScopeGraph.declare
(ScopeGraph.Declaration n)
(lowerBound @ModuleInfo)
relation
ScopeGraph.Public
span
kind
associatedScope
current
old
SketchC (put (Sketchbook new current))
k ()
alg (L (Reference n decl _props k)) = do
Sketchbook old current <- SketchC (get @Sketchbook)
let new =
ScopeGraph.reference
(ScopeGraph.Reference (Name.name n))
(lowerBound @ModuleInfo)
(lowerBound @Span)
ScopeGraph.Identifier
(ScopeGraph.Declaration (Name.name decl))
current
old
SketchC (put (Sketchbook new current))
k ()
alg (L (NewScope edges k)) = do
Sketchbook old current <- SketchC get
name <- SketchC Name.gensym
let new = ScopeGraph.newScope name edges old
SketchC (put (Sketchbook new current))
k name
alg (R (L a)) = case a of
Ask k -> SketchC (gets sCurrentScope) >>= k
Local fn go k -> do
initial@(Sketchbook s oldScope) <- SketchC get
let newScope = fn oldScope
SketchC (put (Sketchbook s newScope))
result <- go
SketchC (put initial)
k result
alg (R (R (L a))) = send (handleCoercible a)
alg (R (R (R a))) = send (handleCoercible a)
runSketch ::
(Functor m)
=> Maybe Path.AbsRelFile
-> SketchC Name m a
-> m (ScopeGraph Name, a)
runSketch _rootpath (SketchC go)
= evalFresh 1
. fmap (first sGraph)
. runState lowerBound
$ go

View File

@ -0,0 +1,55 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# OPTIONS_GHC -fprint-expanded-synonyms #-}
-- | This carrier interprets the Sketch effect, keeping track of
-- the current scope and in-progress graph internally.
module Control.Carrier.Sketch.ScopeGraph
( SketchC
, runSketch
, module Control.Effect.ScopeGraph
) where
import Analysis.Name (Name)
import qualified Analysis.Name as Name
import Control.Carrier.Fresh.Strict
import Control.Carrier.Reader
import Control.Carrier.State.Strict
import Control.Effect.ScopeGraph
import Data.Module (ModuleInfo)
import qualified Data.ScopeGraph as ScopeGraph
import Data.Semilattice.Lower
type SketchC addr m
= StateC (ScopeGraph Name)
( StateC Name
( ReaderC Name
( ReaderC ModuleInfo
( FreshC m
))))
runSketch ::
(Functor m)
=> ModuleInfo
-> SketchC Name m a
-> m (ScopeGraph Name, a)
runSketch info go
= evalFresh 0
. runReader @ModuleInfo info
. runReader @Name rootname
. evalState @Name rootname
. runState @(ScopeGraph Name) initialGraph
$ go
where
rootname = Name.nameI 0
initialGraph = ScopeGraph.insertScope rootname lowerBound lowerBound

View File

@ -0,0 +1,185 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
-- | 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.ScopeGraph
( ScopeGraph
, ScopeGraphEff
, declare
-- Scope Manipulation
, currentScope
, newEdge
, newReference
, newScope
, withScope
, declareFunction
, declareMaybeName
, reference
, Has
) where
import Analysis.Name (Name)
import qualified Analysis.Name as Name
import Control.Algebra
import Control.Effect.Fresh
import Control.Effect.Reader
import Control.Lens
import Data.List.NonEmpty
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import qualified Data.Module as Module
import qualified Data.ScopeGraph as ScopeGraph
import Data.Semilattice.Lower
import Data.Text (Text)
import GHC.Records
import qualified Scope.Reference as Reference
import Source.Span
import Scope.Graph.AdjacencyList (ScopeGraph)
import qualified Scope.Graph.AdjacencyList as AdjacencyList
import qualified Control.Effect.ScopeGraph.Properties.Declaration as Props
import qualified Control.Effect.ScopeGraph.Properties.Function as Props
import qualified Control.Effect.ScopeGraph.Properties.Reference as Props
import qualified Control.Effect.ScopeGraph.Properties.Reference as Props.Reference
import Control.Effect.State
-- | Extract the 'Just' of a 'Maybe' in an 'Applicative' context or, given 'Nothing', run the provided action.
maybeM :: Applicative f => f a -> Maybe a -> f a
maybeM f = maybe f pure
{-# INLINE maybeM #-}
type ScopeGraphEff sig m
= ( Has (State (ScopeGraph Name)) sig m
, Has (State Name) sig m
, Has (Reader Name) sig m
, Has (Reader Module.ModuleInfo) sig m
, Has Fresh sig m
)
graphInProgress :: ScopeGraphEff sig m => m (ScopeGraph Name)
graphInProgress = get
currentScope :: ScopeGraphEff sig m => m Name
currentScope = ask
withScope :: ScopeGraphEff sig m
=> Name
-> m a
-> m a
withScope scope = local (const scope)
declare :: ScopeGraphEff sig m => Name -> Props.Declaration -> m ()
declare n props = do
current <- currentScope
old <- graphInProgress
info <- ask
let Props.Declaration kind relation associatedScope span = props
let (new, _pos) =
ScopeGraph.declare
(ScopeGraph.Declaration n)
info
relation
ScopeGraph.Public
span
kind
associatedScope
current
old
put new
-- | Establish a reference to a prior declaration.
reference :: forall sig m . ScopeGraphEff sig m => Text -> Text -> Props.Reference -> m ()
reference n decl props = do
current <- currentScope
old <- graphInProgress
info <- ask
let new =
ScopeGraph.reference
(ScopeGraph.Reference (Name.name n))
info
(Props.Reference.span props)
(Props.Reference.kind props)
(ScopeGraph.Declaration (Name.name decl))
current
old
put new
newScope :: forall sig m . ScopeGraphEff sig m => Map ScopeGraph.EdgeLabel [Name] -> m Name
newScope edges = do
old <- graphInProgress
name <- Name.gensym
let new = ScopeGraph.newScope name edges old
name <$ put new
-- | Takes an edge label and a list of names and inserts an import edge to a hole.
newEdge :: ScopeGraphEff sig m => ScopeGraph.EdgeLabel -> NonEmpty Name -> m ()
newEdge label address = do
current <- currentScope
old <- graphInProgress
let new = ScopeGraph.addImportEdge label (toList address) current old
put new
lookupScope :: ScopeGraphEff sig m => Name -> m (ScopeGraph.Scope Name)
lookupScope address = maybeM undefined . ScopeGraph.lookupScope address =<< get
-- | Inserts a reference.
newReference :: ScopeGraphEff sig m => Name -> Props.Reference -> m ()
newReference name props = do
currentAddress <- currentScope
scope <- lookupScope currentAddress
let refProps = Reference.ReferenceInfo (props^.span_) (Props.Reference.kind props) lowerBound
insertRef' :: ScopeGraph.Path Name -> ScopeGraph.ScopeGraph Name -> ScopeGraph.ScopeGraph Name
insertRef' path scopeGraph = let
scope' = (ScopeGraph.insertReference (Reference.Reference name) lowerBound (Props.Reference.span props) (getField @"kind" props) path) scope
in
(ScopeGraph.insertScope currentAddress scope' scopeGraph)
scopeGraph <- get @(ScopeGraph.ScopeGraph Name)
case AdjacencyList.findPath (const Nothing) (ScopeGraph.Declaration name) currentAddress scopeGraph of
-- If a path to a declaration is found, insert a reference into the current scope.
Just path -> modify (insertRef' path)
-- If no path is found, insert a reference with a hole into the current scope.
Nothing ->
modify (ScopeGraph.insertScope
currentAddress
(ScopeGraph.newReference
(Reference.Reference name)
refProps
scope))
declareFunction :: forall sig m . ScopeGraphEff 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 = kind
, Props.associatedScope = Just associatedScope
, Props.span = span
}
pure (name', associatedScope)
declareMaybeName :: ScopeGraphEff sig m
=> Maybe Name
-> Props.Declaration
-> m Name
declareMaybeName maybeName props = do
case maybeName of
Just name -> name <$ declare name props
_ -> do
name <- Name.gensym
name <$ declare name (props { Props.relation = ScopeGraph.Gensym })

View File

@ -5,7 +5,7 @@
-- | 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 declaration.
-- That is to say, it is a record type primarily used for its selector names.
module ScopeGraph.Properties.Declaration
module Control.Effect.ScopeGraph.Properties.Declaration
( Declaration (..)
) where

View File

@ -5,7 +5,7 @@
-- | 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
module Control.Effect.ScopeGraph.Properties.Function
( Function (..)
) where

View File

@ -0,0 +1,27 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}
-- | 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 Control.Effect.ScopeGraph.Properties.Reference
( Reference (..)
) where
import Control.Lens
import Data.ScopeGraph as ScopeGraph (Kind, Relation)
import GHC.Generics (Generic)
import Prelude hiding (span)
import Source.Span
data Reference = Reference
{ kind :: ScopeGraph.Kind
, relation :: ScopeGraph.Relation
, span :: Span
} deriving (Generic, Show)
instance HasSpan Reference where
span_ = lens span (\r s -> r { span = s })
{-# INLINE span_ #-}

View File

@ -1,95 +0,0 @@
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
-- | The Sketch 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 (..)
, declare
-- Scope Manipulation
, currentScope
, newScope
, withScope
, declareFunction
, declareMaybeName
, reference
, Has
) where
import Analysis.Name (Name)
import qualified Analysis.Name as Name
import Control.Algebra
import Control.Effect.Fresh
import Control.Effect.Reader
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 qualified ScopeGraph.Properties.Declaration as Props
import qualified ScopeGraph.Properties.Function as Props
import qualified ScopeGraph.Properties.Reference as Props
type Sketch
= SketchEff
:+: Fresh
:+: Reader Name
data SketchEff m k =
Declare Name Props.Declaration (() -> m k)
| Reference Text Text Props.Reference (() -> m k)
| NewScope (Map ScopeGraph.EdgeLabel [Name]) (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 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 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 -> 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 = kind
, Props.associatedScope = Just associatedScope
, Props.span = span
}
pure (name', associatedScope)
declareMaybeName :: Has Sketch sig m
=> Maybe Name
-> Props.Declaration
-> m Name
declareMaybeName maybeName props = do
case maybeName of
Just name -> name <$ declare name props
_ -> do
name <- Name.gensym
name <$ declare name (props { Props.relation = ScopeGraph.Gensym })
withScope :: Has Sketch sig m
=> Name
-> m a
-> m a
withScope scope = local (const scope)

View File

@ -1,432 +1,13 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
module Data.ScopeGraph
( Slot(..)
, Info(..)
, associatedScope
, lookupDeclaration
, declarationByName
, declarationsByAccessControl
, declarationsByRelation
, Declaration(..) -- TODO don't export these constructors
, declare
, formatDeclaration
, EdgeLabel(..)
, insertDeclarationScope
, insertDeclarationSpan
, insertImportReference
, newScope
, newPreludeScope
, insertScope
, insertEdge
, Path(..)
, pathDeclaration
, pathOfRef
, pathPosition
, Position(..)
, reference
, Reference(..) -- TODO don't export these constructors
, ReferenceInfo(..)
, Relation(..)
, ScopeGraph(..)
, Kind(..)
, lookupScope
, lookupScopePath
, Scope(..)
, scopeOfRef
, pathDeclarationScope
, putDeclarationScopeAtPosition
, declarationNames
, AccessControl(..)
( module Scope.Info
, module Scope.Path
, module Scope.Scope
, module Scope.Types
, module Scope.Graph.AdjacencyList
) where
import Prelude hiding (lookup)
import Analysis.Name
import Control.Applicative
import Control.Lens.Lens
import Control.Monad
import Data.Aeson
import Data.Bifunctor
import Data.Foldable
import Data.Hashable
import Data.Hole
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as Map
import Data.Maybe
import Data.Module
import Data.Monoid
import Data.Semilattice.Lower
import Data.Sequence (Seq)
import qualified Data.Sequence as Seq
import Data.Set (Set)
import qualified Data.Set as Set
import Data.Text (Text)
import GHC.Generics
import Source.Span
-- A slot is a location in the heap where a value is stored.
data Slot address = Slot { frameAddress :: address, position :: Position }
deriving (Eq, Show, Ord)
data AccessControl = Public
| Protected
| Private
deriving (Bounded, Enum, Eq, Generic, Hashable, ToJSON, Show)
-- | The Ord AccessControl instance represents an order specification of AccessControls.
-- AccessControls that are less than or equal to another AccessControl implies access.
-- It is helpful to consider `Public <= Private` as saying "Can a Public syntax term access a Private syntax term?"
-- In this way, Public AccessControl is the top of the order specification, and Private AccessControl is the bottom.
instance Ord AccessControl where
-- | Private AccessControl represents the least overlap or accessibility with other AccessControls.
-- When asking if the AccessControl "on the left" is less than the AccessControl "on the right", Private AccessControl on the left always implies access to the thing on the right.
(<=) Private _ = True
(<=) _ Private = False
-- | Protected AccessControl is in between Private and Public in the order specification.
-- Protected AccessControl "on the left" has access to Protected or Public AccessControls "on the right".
(<=) Protected Public = True
(<=) Protected Protected = True
-- | Public AccessControl "on the left" has access only to Public AccessControl "on the right".
(<=) Public Public = True
(<=) Public _ = False
data Relation = Default | Instance | Prelude | Gensym
deriving (Bounded, Enum, Eq, Show, Ord)
instance Lower Relation where
lowerBound = Default
data Info scopeAddress = Info
{ infoDeclaration :: Declaration
, infoModule :: ModuleInfo
, infoRelation :: Relation
, infoAccessControl :: AccessControl
, infoSpan :: Span
, infoKind :: Kind
, infoAssociatedScope :: Maybe scopeAddress
} deriving (Eq, Show, Ord)
instance HasSpan (Info scopeAddress) where
span_ = lens infoSpan (\i s -> i { infoSpan = s })
{-# INLINE span_ #-}
instance Lower (Info scopeAddress) where
lowerBound = Info lowerBound lowerBound lowerBound Public lowerBound lowerBound Nothing
data ReferenceInfo = ReferenceInfo
{ refSpan :: Span
, refKind :: Kind
, refModule :: ModuleInfo
} deriving (Eq, Show, Ord)
instance HasSpan ReferenceInfo where
span_ = lens refSpan (\r s -> r { refSpan = s })
{-# INLINE span_ #-}
data Kind = AbstractClass
| Assignment
| Call
| Class
| DefaultExport
| Function
| Identifier
| Let
| MemberAccess
| Method
| Module
| New
| Parameter
| PublicField
| QualifiedAliasedImport
| QualifiedExport
| QualifiedImport
| RequiredParameter
| This
| TypeAlias
| TypeIdentifier
| Unknown
| UnqualifiedImport
| VariableDeclaration
deriving (Bounded, Enum, Eq, Show, Ord)
instance Lower Kind where
lowerBound = Unknown
data Domain
= Standard
| Preluded
deriving (Eq, Show, Ord)
-- Offsets and frame addresses in the heap should be addresses?
data Scope address = Scope
{ edges :: Map EdgeLabel [address]
, references :: Map Reference ([ReferenceInfo], Path address)
, declarations :: Seq (Info address)
, domain :: Domain
} deriving (Eq, Show, Ord)
instance Lower (Scope scopeAddress) where
lowerBound = Scope mempty mempty mempty Standard
instance AbstractHole (Scope scopeAddress) where
hole = lowerBound
instance AbstractHole address => AbstractHole (Slot address) where
hole = Slot hole (Position 0)
instance AbstractHole (Info address) where
hole = lowerBound
newtype Position = Position { unPosition :: Int }
deriving (Eq, Show, Ord)
newtype ScopeGraph scope = ScopeGraph { unScopeGraph :: Map scope (Scope scope) }
deriving (Eq, Ord, Show)
instance Ord scope => Lower (ScopeGraph scope) where
lowerBound = ScopeGraph mempty
data Path scope
= Hole
-- | Construct a direct path to a declaration.
| DPath Declaration Position
-- | Construct an edge from a scope to another declaration path.
| EPath EdgeLabel scope (Path scope)
deriving (Eq, Functor, Ord, Show)
instance AbstractHole (Path scope) where
hole = Hole
-- Returns the declaration of a path.
pathDeclaration :: Path scope -> Declaration
pathDeclaration (DPath d _) = d
pathDeclaration (EPath _ _ p) = pathDeclaration p
pathDeclaration Hole = undefined
-- TODO: Store the current scope closer _in_ the DPath?
pathDeclarationScope :: scope -> Path scope -> Maybe scope
pathDeclarationScope _ (EPath _ scope (DPath _ _)) = Just scope
pathDeclarationScope currentScope (EPath _ _ p) = pathDeclarationScope currentScope p
pathDeclarationScope currentScope (DPath _ _) = Just currentScope
pathDeclarationScope _ Hole = Nothing
-- TODO: Possibly return in Maybe since we can have Hole paths
pathPosition :: Path scope -> Position
pathPosition Hole = Position 0
pathPosition (DPath _ p) = p
pathPosition (EPath _ _ p) = pathPosition p
-- Returns the reference paths of a scope in a scope graph.
pathsOfScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Map Reference ([ReferenceInfo], Path scope))
pathsOfScope scope = fmap references . Map.lookup scope . unScopeGraph
-- Returns the declaration data of a scope in a scope graph.
ddataOfScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Seq (Info scope))
ddataOfScope scope = fmap declarations . Map.lookup scope . unScopeGraph
-- Returns the edges of a scope in a scope graph.
linksOfScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Map EdgeLabel [scope])
linksOfScope scope = fmap edges . Map.lookup scope . unScopeGraph
declarationsByAccessControl :: Ord scope => scope -> AccessControl -> ScopeGraph scope -> [ Info scope ]
declarationsByAccessControl scope accessControl g = fromMaybe mempty $ do
dataSeq <- ddataOfScope scope g
pure . toList $ Seq.filter (\Info{..} -> accessControl <= infoAccessControl) dataSeq
declarationsByRelation :: Ord scope => scope -> Relation -> ScopeGraph scope -> [ Info scope ]
declarationsByRelation scope relation g = fromMaybe mempty $ do
dataSeq <- ddataOfScope scope g
pure . toList $ Seq.filter (\Info{..} -> infoRelation == relation) dataSeq
declarationByName :: Ord scope => scope -> Declaration -> ScopeGraph scope -> Maybe (Info scope)
declarationByName scope name g = do
dataSeq <- ddataOfScope scope g
find (\Info{..} -> infoDeclaration == name) dataSeq
-- Lookup a scope in the scope graph.
lookupScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Scope scope)
lookupScope scope = Map.lookup scope . unScopeGraph
-- Declare a declaration with a span and an associated scope in the scope graph.
-- TODO: Return the whole value in Maybe or Either.
declare :: Ord scope
=> Declaration
-> ModuleInfo
-> Relation
-> AccessControl
-> Span
-> Kind
-> Maybe scope
-> scope
-> ScopeGraph scope
-> (ScopeGraph scope, Maybe Position)
declare decl moduleInfo rel accessControl declSpan kind assocScope currentScope g = fromMaybe (g, Nothing) $ do
scope <- lookupScope currentScope g
dataSeq <- ddataOfScope currentScope g
case Seq.findIndexR (\Info{..} -> decl == infoDeclaration && declSpan == infoSpan && rel == infoRelation) dataSeq of
Just index -> pure (g, Just (Position index))
Nothing -> do
let newScope = scope { declarations = declarations scope Seq.|> Info decl moduleInfo rel accessControl declSpan kind assocScope }
pure (insertScope currentScope newScope g, Just (Position (length (declarations newScope))))
-- | Add a reference to a declaration in the scope graph.
-- Returns the original scope graph if the declaration could not be found.
reference :: Ord scope => Reference -> ModuleInfo -> Span -> Kind -> Declaration -> scope -> ScopeGraph scope -> ScopeGraph scope
reference ref moduleInfo span kind decl currentAddress g = fromMaybe g $ do
-- Start from the current address
currentScope' <- lookupScope currentAddress g
-- Build a path up to the declaration
flip (insertScope currentAddress) g . flip (insertReference ref moduleInfo span kind) currentScope' <$> findPath (const Nothing) decl currentAddress g
-- | Insert a reference into the given scope by constructing a resolution path to the declaration within the given scope graph.
insertImportReference :: Ord address => Reference -> ModuleInfo -> Span -> Kind -> Declaration -> address -> ScopeGraph address -> Scope address -> Maybe (Scope address)
insertImportReference ref moduleInfo span kind decl currentAddress g scope = flip (insertReference ref moduleInfo span kind) scope . EPath Import currentAddress <$> findPath (const Nothing) decl currentAddress g
lookupScopePath :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Path scopeAddress)
lookupScopePath declaration currentAddress g = findPath (flip (lookupReference declaration) g) (Declaration declaration) currentAddress g
findPath :: Ord scopeAddress => (scopeAddress -> Maybe (Path scopeAddress)) -> Declaration -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Path scopeAddress)
findPath extra decl currentAddress g = snd <$> getFirst (foldGraph combine currentAddress g)
where combine address path = fmap (address, )
$ First (pathToDeclaration decl address g)
<> First (extra address)
<> (uncurry (EPath Superclass) <$> path Superclass)
<> (uncurry (EPath Import) <$> path Import)
<> (uncurry (EPath Export) <$> path Export)
<> (uncurry (EPath Lexical) <$> path Lexical)
foldGraph :: (Ord scopeAddress, Monoid a) => (scopeAddress -> (EdgeLabel -> a) -> a) -> scopeAddress -> ScopeGraph scopeAddress -> a
foldGraph combine address graph = go lowerBound address
where go visited address
| address `Set.notMember` visited
, Just edges <- linksOfScope address graph = combine address (recur edges)
| otherwise = mempty
where visited' = Set.insert address visited
recur edges edge = maybe mempty (foldMap (go visited')) (Map.lookup edge edges)
pathToDeclaration :: Ord scopeAddress => Declaration -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Path scopeAddress)
pathToDeclaration decl address g = DPath decl . snd <$> lookupDeclaration (unDeclaration decl) address g
insertReference :: Reference -> ModuleInfo -> Span -> Kind -> Path scopeAddress -> Scope scopeAddress -> Scope scopeAddress
insertReference ref moduleInfo span kind path scope = scope { references = Map.alter (\case
Nothing -> pure ([ ReferenceInfo span kind moduleInfo ], path)
Just (refInfos, path) -> pure (ReferenceInfo span kind moduleInfo : refInfos, path)) ref (references scope) }
lookupDeclaration :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Info scopeAddress, Position)
lookupDeclaration name scope g = do
dataSeq <- ddataOfScope scope g
index <- Seq.findIndexR (\Info{..} -> Declaration name == infoDeclaration) dataSeq
(, Position index) <$> Seq.lookup index dataSeq
declarationNames :: Ord address => [EdgeLabel] -> Scope address -> ScopeGraph address -> Set Declaration
declarationNames edgeLabels scope scopeGraph = localDeclarations <> edgeNames
where addresses = join (Map.elems $ Map.restrictKeys (edges scope) (Set.fromList edgeLabels))
edgeNames = flip foldMap addresses $ \address -> maybe mempty (flip (declarationNames edgeLabels) scopeGraph) (lookupScope address scopeGraph)
localDeclarations = Set.fromList . toList . fmap infoDeclaration $ declarations scope
putDeclarationScopeAtPosition :: Ord scopeAddress => scopeAddress -> Position -> Maybe scopeAddress -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
putDeclarationScopeAtPosition scope position assocScope g@(ScopeGraph graph) = fromMaybe g $ do
dataSeq <- ddataOfScope scope g
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)
lookupReference name scope g = fmap snd . Map.lookup (Reference name) =<< pathsOfScope scope g
insertEdge :: Ord scopeAddress => EdgeLabel -> scopeAddress -> scopeAddress -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
insertEdge label target currentAddress g@(ScopeGraph graph) = fromMaybe g $ do
currentScope' <- lookupScope currentAddress g
scopes <- maybe (Just mempty) pure (Map.lookup label (edges currentScope'))
let newScope = currentScope' { edges = Map.insert label (target : scopes) (edges currentScope') }
pure (ScopeGraph (Map.insert currentAddress newScope graph))
-- | 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.
insertDeclarationScope :: Ord scopeAddress => Declaration -> scopeAddress -> scopeAddress -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
insertDeclarationScope Declaration{..} associatedScopeAddress scopeAddress g = fromMaybe g $ do
declScopeAddress <- pathDeclarationScope scopeAddress =<< lookupScopePath unDeclaration scopeAddress g
scope <- lookupScope declScopeAddress g
(declInfo, position) <- second unPosition <$> lookupDeclaration unDeclaration declScopeAddress g
pure $ insertScope declScopeAddress (scope { declarations = Seq.update position (declInfo { infoAssociatedScope = Just associatedScopeAddress }) (declarations scope) }) g
-- | Insert a declaration span into the declaration in the scope graph.
insertDeclarationSpan :: Ord scopeAddress => Declaration -> Span -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
insertDeclarationSpan decl@Declaration{..} span g = fromMaybe g $ do
declScopeAddress <- scopeOfDeclaration decl g
(declInfo, position) <- second unPosition <$> lookupDeclaration unDeclaration declScopeAddress g
scope <- lookupScope declScopeAddress g
pure $ insertScope declScopeAddress (scope { declarations = Seq.update position (declInfo { infoSpan = span }) (declarations scope) }) g
-- | Insert a new scope with the given address and edges into the scope graph.
newScope :: Ord address => address -> Map EdgeLabel [address] -> ScopeGraph address -> ScopeGraph address
newScope address edges = insertScope address (Scope edges mempty mempty Standard)
-- | Insert a new scope with the given address and edges into the scope graph.
newPreludeScope :: Ord address => address -> Map EdgeLabel [address] -> ScopeGraph address -> ScopeGraph address
newPreludeScope address edges = insertScope address (Scope edges mempty mempty Preluded)
insertScope :: Ord address => address -> Scope address -> ScopeGraph address -> ScopeGraph address
insertScope address scope = ScopeGraph . Map.insert address scope . unScopeGraph
-- | Returns the scope of a reference in the scope graph.
scopeOfRef :: Ord scope => Reference -> ScopeGraph scope -> Maybe scope
scopeOfRef ref g@(ScopeGraph graph) = go (Map.keys graph)
where
go (s : scopes') = fromMaybe (go scopes') $ do
pathMap <- pathsOfScope s g
_ <- Map.lookup ref pathMap
pure (Just s)
go [] = Nothing
-- | Returns the path of a reference in the scope graph.
pathOfRef :: (Ord scope) => Reference -> ScopeGraph scope -> Maybe (Path scope)
pathOfRef ref graph = do
scope <- scopeOfRef ref graph
pathsMap <- pathsOfScope scope graph
snd <$> Map.lookup ref pathsMap
-- Returns the scope the declaration was declared in.
scopeOfDeclaration :: Ord scope => Declaration -> ScopeGraph scope -> Maybe scope
scopeOfDeclaration Declaration{..} g@(ScopeGraph graph) = go (Map.keys graph)
where
go = foldr (\ scope -> (scope <$ lookupDeclaration unDeclaration scope g <|>)) Nothing
-- | Returns the scope associated with a declaration (the child scope if any exists).
associatedScope :: Ord scope => Declaration -> ScopeGraph scope -> Maybe scope
associatedScope Declaration{..} g@(ScopeGraph graph) = go (Map.keys graph)
where
go = foldr lookupAssociatedScope Nothing
lookupAssociatedScope scope = ((lookupDeclaration unDeclaration scope g >>= infoAssociatedScope . fst) <|>)
newtype Reference = Reference { unReference :: Name }
deriving (Eq, Ord, Show)
instance Lower Reference where
lowerBound = Reference $ name ""
newtype Declaration = Declaration { unDeclaration :: Name }
deriving (Eq, Ord, Show)
instance Lower Declaration where
lowerBound = Declaration $ name ""
formatDeclaration :: Declaration -> Text
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
deriving (Bounded, Enum, Eq, Ord, Show)
import Scope.Graph.AdjacencyList
import Scope.Info
import Scope.Path
import Scope.Scope
import Scope.Types

View File

@ -0,0 +1,257 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TupleSections #-}
module Scope.Graph.AdjacencyList
( module Scope.Graph.AdjacencyList
) where
import Analysis.Name
import Control.Applicative
import Control.Monad
import Data.Bifunctor
import Data.Foldable
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
import Data.Module
import Data.Monoid
import Data.Semilattice.Lower
import Data.Sequence (Seq)
import qualified Data.Sequence as Seq
import Data.Set (Set)
import qualified Data.Set as Set
import Scope.Info
import Scope.Path
import Scope.Reference
import Scope.Scope
import Scope.Types
import Source.Span
newtype CurrentScope address = CurrentScope { unCurrentScope :: address }
newtype ScopeGraph scope = ScopeGraph { unScopeGraph :: Map scope (Scope scope) }
deriving (Eq, Ord, Show)
instance Ord scope => Lower (ScopeGraph scope) where
lowerBound = ScopeGraph mempty
-- Returns the reference paths of a scope in a scope graph.
pathsOfScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Map Reference ([ReferenceInfo], Path scope))
pathsOfScope scope = fmap references . Map.lookup scope . unScopeGraph
-- Returns the declaration data of a scope in a scope graph.
ddataOfScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Seq (Info scope))
ddataOfScope scope = fmap declarations . Map.lookup scope . unScopeGraph
-- Returns the edges of a scope in a scope graph.
linksOfScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Map EdgeLabel [scope])
linksOfScope scope = fmap edges . Map.lookup scope . unScopeGraph
declarationsByAccessControl :: Ord scope => scope -> AccessControl -> ScopeGraph scope -> [ Info scope ]
declarationsByAccessControl scope accessControl g = fromMaybe mempty $ do
dataSeq <- ddataOfScope scope g
pure . toList $ Seq.filter (\Info{..} -> accessControl <= infoAccessControl) dataSeq
declarationsByRelation :: Ord scope => scope -> Relation -> ScopeGraph scope -> [ Info scope ]
declarationsByRelation scope relation g = fromMaybe mempty $ do
dataSeq <- ddataOfScope scope g
pure . toList $ Seq.filter (\Info{..} -> infoRelation == relation) dataSeq
declarationByName :: Ord scope => scope -> Declaration -> ScopeGraph scope -> Maybe (Info scope)
declarationByName scope name g = do
dataSeq <- ddataOfScope scope g
find (\Info{..} -> infoDeclaration == name) dataSeq
-- Lookup a scope in the scope graph.
lookupScope :: Ord scope => scope -> ScopeGraph scope -> Maybe (Scope scope)
lookupScope scope = Map.lookup scope . unScopeGraph
-- Declare a declaration with a span and an associated scope in the scope graph.
-- TODO: Return the whole value in Maybe or Either.
declare :: Ord scope
=> Declaration
-> ModuleInfo
-> Relation
-> AccessControl
-> Span
-> Kind
-> Maybe scope
-> scope
-> ScopeGraph scope
-> (ScopeGraph scope, Maybe Position)
declare decl moduleInfo rel accessControl declSpan kind assocScope currentScope g = fromMaybe (g, Nothing) $ do
scope <- lookupScope currentScope g
dataSeq <- ddataOfScope currentScope g
case Seq.findIndexR (\Info{..} -> decl == infoDeclaration && declSpan == infoSpan && rel == infoRelation) dataSeq of
Just index -> pure (g, Just (Position index))
Nothing -> do
let newScope = scope { declarations = declarations scope Seq.|> Info decl moduleInfo rel accessControl declSpan kind assocScope }
pure (insertScope currentScope newScope g, Just (Position (length (declarations newScope))))
-- | Add a reference to a declaration in the scope graph.
-- Returns the original scope graph if the declaration could not be found.
reference :: Ord scope => Reference -> ModuleInfo -> Span -> Kind -> Declaration -> scope -> ScopeGraph scope -> ScopeGraph scope
reference ref moduleInfo span kind decl currentAddress g = fromMaybe g $ do
-- Start from the current address
currentScope' <- lookupScope currentAddress g
-- Build a path up to the declaration
flip (insertScope currentAddress) g . flip (insertReference ref moduleInfo span kind) currentScope' <$> findPath (const Nothing) decl currentAddress g
-- | Insert a reference into the given scope by constructing a resolution path to the declaration within the given scope graph.
insertImportReference :: Ord address => Reference -> ModuleInfo -> Span -> Kind -> Declaration -> address -> ScopeGraph address -> Scope address -> Maybe (Scope address)
insertImportReference ref moduleInfo span kind decl currentAddress g scope = flip (insertReference ref moduleInfo span kind) scope . EPath Import currentAddress <$> findPath (const Nothing) decl currentAddress g
lookupScopePath :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Path scopeAddress)
lookupScopePath declaration currentAddress g = findPath (flip (lookupReference declaration) g) (Declaration declaration) currentAddress g
findPath :: Ord scopeAddress => (scopeAddress -> Maybe (Path scopeAddress)) -> Declaration -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Path scopeAddress)
findPath extra decl currentAddress g = snd <$> getFirst (foldGraph combine currentAddress g)
where combine address path = fmap (address, )
$ First (pathToDeclaration decl address g)
<> First (extra address)
<> (uncurry (EPath Superclass) <$> path Superclass)
<> (uncurry (EPath Import) <$> path Import)
<> (uncurry (EPath Export) <$> path Export)
<> (uncurry (EPath Lexical) <$> path Lexical)
foldGraph :: (Ord scopeAddress, Monoid a) => (scopeAddress -> (EdgeLabel -> a) -> a) -> scopeAddress -> ScopeGraph scopeAddress -> a
foldGraph combine address graph = go lowerBound address
where go visited address
| address `Set.notMember` visited
, Just edges <- linksOfScope address graph = combine address (recur edges)
| otherwise = mempty
where visited' = Set.insert address visited
recur edges edge = maybe mempty (foldMap (go visited')) (Map.lookup edge edges)
pathToDeclaration :: Ord scopeAddress => Declaration -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Path scopeAddress)
pathToDeclaration decl address g = DPath decl . snd <$> lookupDeclaration (unDeclaration decl) address g
insertReference :: Reference -> ModuleInfo -> Span -> Kind -> Path scopeAddress -> Scope scopeAddress -> Scope scopeAddress
insertReference ref moduleInfo span kind path scope = scope { references = Map.alter (\case
Nothing -> pure ([ ReferenceInfo span kind moduleInfo ], path)
Just (refInfos, path) -> pure (ReferenceInfo span kind moduleInfo : refInfos, path)) ref (references scope) }
-- | Adds a reference and a Hole path to the given scope.
newReference :: Reference -> ReferenceInfo -> Scope scopeAddress -> Scope scopeAddress
newReference ref info scope = scope { references = Map.alter (\case
Nothing -> pure ([ info ], Hole)
Just (refInfos, path) -> pure (info : refInfos, path)) ref (references scope) }
lookupDeclaration :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Info scopeAddress, Position)
lookupDeclaration name scope g = do
dataSeq <- ddataOfScope scope g
index <- Seq.findIndexR (\Info{..} -> Declaration name == infoDeclaration) dataSeq
(, Position index) <$> Seq.lookup index dataSeq
declarationNames :: Ord address => [EdgeLabel] -> Scope address -> ScopeGraph address -> Set Declaration
declarationNames edgeLabels scope scopeGraph = localDeclarations <> edgeNames
where addresses = join (Map.elems $ Map.restrictKeys (edges scope) (Set.fromList edgeLabels))
edgeNames = flip foldMap addresses $ \address -> maybe mempty (flip (declarationNames edgeLabels) scopeGraph) (lookupScope address scopeGraph)
localDeclarations = Set.fromList . toList . fmap infoDeclaration $ declarations scope
putDeclarationScopeAtPosition :: Ord scopeAddress => scopeAddress -> Position -> Maybe scopeAddress -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
putDeclarationScopeAtPosition scope position assocScope g@(ScopeGraph graph) = fromMaybe g $ do
dataSeq <- ddataOfScope scope g
let seq = Seq.adjust' (\Info{..} -> Info { infoAssociatedScope = assocScope, .. }) (unPosition position) dataSeq
pure $ ScopeGraph (Map.adjust (\s -> s { declarations = seq }) scope graph)
-- | 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
insertEdge label target currentAddress g@(ScopeGraph graph) = fromMaybe g $ do
currentScope' <- lookupScope currentAddress g
scopes <- maybe (Just mempty) pure (Map.lookup label (edges currentScope'))
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.
insertDeclarationScope :: Ord scopeAddress => Declaration -> scopeAddress -> scopeAddress -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
insertDeclarationScope Declaration{..} associatedScopeAddress scopeAddress g = fromMaybe g $ do
declScopeAddress <- pathDeclarationScope scopeAddress =<< lookupScopePath unDeclaration scopeAddress g
scope <- lookupScope declScopeAddress g
(declInfo, position) <- second unPosition <$> lookupDeclaration unDeclaration declScopeAddress g
pure $ insertScope declScopeAddress (scope { declarations = Seq.update position (declInfo { infoAssociatedScope = Just associatedScopeAddress }) (declarations scope) }) g
-- | Insert a declaration span into the declaration in the scope graph.
insertDeclarationSpan :: Ord scopeAddress => Declaration -> Span -> ScopeGraph scopeAddress -> ScopeGraph scopeAddress
insertDeclarationSpan decl@Declaration{..} span g = fromMaybe g $ do
declScopeAddress <- scopeOfDeclaration decl g
(declInfo, position) <- second unPosition <$> lookupDeclaration unDeclaration declScopeAddress g
scope <- lookupScope declScopeAddress g
pure $ insertScope declScopeAddress (scope { declarations = Seq.update position (declInfo { infoSpan = span }) (declarations scope) }) g
-- | Insert a new scope with the given address and edges into the scope graph.
newScope :: Ord address => address -> Map EdgeLabel [address] -> ScopeGraph address -> ScopeGraph address
newScope address edges = insertScope address (Scope edges mempty mempty Standard)
-- | Insert a new scope with the given address and edges into the scope graph.
newPreludeScope :: Ord address => address -> Map EdgeLabel [address] -> ScopeGraph address -> ScopeGraph address
newPreludeScope address edges = insertScope address (Scope edges mempty mempty Preluded)
insertScope :: Ord address => address -> Scope address -> ScopeGraph address -> ScopeGraph address
insertScope address scope = ScopeGraph . Map.insert address scope . unScopeGraph
-- | Returns the scope of a reference in the scope graph.
scopeOfRef :: Ord scope => Reference -> ScopeGraph scope -> Maybe scope
scopeOfRef ref g@(ScopeGraph graph) = go (Map.keys graph)
where
go (s : scopes') = fromMaybe (go scopes') $ do
pathMap <- pathsOfScope s g
_ <- Map.lookup ref pathMap
pure (Just s)
go [] = Nothing
-- | Returns the path of a reference in the scope graph.
pathOfRef :: (Ord scope) => Reference -> ScopeGraph scope -> Maybe (Path scope)
pathOfRef ref graph = do
scope <- scopeOfRef ref graph
pathsMap <- pathsOfScope scope graph
snd <$> Map.lookup ref pathsMap
-- Returns the scope the declaration was declared in.
scopeOfDeclaration :: Ord scope => Declaration -> ScopeGraph scope -> Maybe scope
scopeOfDeclaration Declaration{..} g@(ScopeGraph graph) = go (Map.keys graph)
where
go = foldr (\ scope -> (scope <$ lookupDeclaration unDeclaration scope g <|>)) Nothing
-- | Returns the scope associated with a declaration (the child scope if any exists).
associatedScope :: Ord scope => Declaration -> ScopeGraph scope -> Maybe scope
associatedScope Declaration{..} g@(ScopeGraph graph) = go (Map.keys graph)
where
go = foldr lookupAssociatedScope Nothing
lookupAssociatedScope scope = ((lookupDeclaration unDeclaration scope g >>= infoAssociatedScope . fst) <|>)

View File

@ -6,21 +6,21 @@
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
module ScopeGraph.Convert
module Scope.Graph.Convert
( ToScopeGraph (..)
, Result (..)
, todo
, 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
( ScopeGraphEff sig m
)
=> t Loc
-> m Result

View File

@ -0,0 +1,61 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
module Scope.Info
( Info (..)
, Declaration (..)
, formatDeclaration
, Relation (..)
, Kind (..)
, AccessControl (..)
) where
import Analysis.Name
import Data.Generics.Product (field)
import Data.Hole
import Data.Module
import Data.Semilattice.Lower
import Data.Text (Text)
import GHC.Generics (Generic)
import Scope.Types
import Source.Span
data Info scopeAddress = Info
{ infoDeclaration :: Declaration
, infoModule :: ModuleInfo
, infoRelation :: Relation
, infoAccessControl :: AccessControl
, infoSpan :: Span
, infoKind :: Kind
, infoAssociatedScope :: Maybe scopeAddress
} deriving (Eq, Show, Ord, Generic)
instance HasSpan (Info scopeAddress) where
span_ = field @"infoSpan"
{-# INLINE span_ #-}
instance Lower (Info scopeAddress) where
lowerBound = Info lowerBound lowerBound lowerBound Public lowerBound lowerBound Nothing
instance AbstractHole (Info address) where
hole = lowerBound
newtype Declaration = Declaration { unDeclaration :: Name }
deriving (Eq, Ord, Show)
instance Lower Declaration where
lowerBound = Declaration $ name ""
formatDeclaration :: Declaration -> Text
formatDeclaration = formatName . unDeclaration
data Relation = Default | Instance | Prelude | Gensym
deriving (Bounded, Enum, Eq, Show, Ord)
instance Lower Relation where
lowerBound = Default

View File

@ -0,0 +1,41 @@
{-# LANGUAGE DeriveFunctor #-}
module Scope.Path
( Path (..)
, pathDeclaration
, pathDeclarationScope
, pathPosition
) where
import Data.Hole
import Scope.Info
import Scope.Types
data Path scope
= Hole
-- | Construct a direct path to a declaration.
| DPath Declaration Position
-- | Construct an edge from a scope to another declaration path.
| EPath EdgeLabel scope (Path scope)
deriving (Eq, Functor, Ord, Show)
instance AbstractHole (Path scope) where
hole = Hole
-- Returns the declaration of a path.
pathDeclaration :: Path scope -> Declaration
pathDeclaration (DPath d _) = d
pathDeclaration (EPath _ _ p) = pathDeclaration p
pathDeclaration Hole = undefined
-- TODO: Store the current scope closer _in_ the DPath?
pathDeclarationScope :: scope -> Path scope -> Maybe scope
pathDeclarationScope _ (EPath _ scope (DPath _ _)) = Just scope
pathDeclarationScope currentScope (EPath _ _ p) = pathDeclarationScope currentScope p
pathDeclarationScope currentScope (DPath _ _) = Just currentScope
pathDeclarationScope _ Hole = Nothing
-- TODO: Possibly return in Maybe since we can have Hole paths
pathPosition :: Path scope -> Position
pathPosition Hole = Position 0
pathPosition (DPath _ p) = p
pathPosition (EPath _ _ p) = pathPosition p

View File

@ -0,0 +1,28 @@
{-# LANGUAGE OverloadedStrings #-}
module Scope.Reference
( ReferenceInfo (..)
, Reference (..)
) where
import Analysis.Name
import Control.Lens (lens)
import Data.Module
import Data.Semilattice.Lower
import Scope.Types
import Source.Span
data ReferenceInfo = ReferenceInfo
{ refSpan :: Span
, refKind :: Kind
, refModule :: ModuleInfo
} deriving (Eq, Show, Ord)
instance HasSpan ReferenceInfo where
span_ = lens refSpan (\r s -> r { refSpan = s })
{-# INLINE span_ #-}
newtype Reference = Reference { unReference :: Name }
deriving (Eq, Ord, Show)
instance Lower Reference where
lowerBound = Reference $ name ""

View File

@ -0,0 +1,30 @@
{-# LANGUAGE OverloadedStrings #-}
module Scope.Scope
( Scope (..)
, Reference (..)
, ReferenceInfo (..)
, Domain (..)
) where
import Data.Hole
import Data.Map.Strict (Map)
import Data.Semilattice.Lower
import Data.Sequence (Seq)
import Scope.Info
import Scope.Path
import Scope.Reference
import Scope.Types
-- Offsets and frame addresses in the heap should be addresses?
data Scope address = Scope
{ edges :: Map EdgeLabel [address]
, references :: Map Reference ([ReferenceInfo], Path address)
, declarations :: Seq (Info address)
, domain :: Domain
} deriving (Eq, Show, Ord)
instance Lower (Scope scopeAddress) where
lowerBound = Scope mempty mempty mempty Standard
instance AbstractHole (Scope scopeAddress) where
hole = lowerBound

View File

@ -0,0 +1,94 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
module Scope.Types
( Slot (..)
, EdgeLabel (..)
, Position (..)
, Domain (..)
, Kind (..)
, AccessControl (..)
) where
import Data.Aeson (ToJSON)
import Data.Hashable
import Data.Hole
import Data.Semilattice.Lower
import GHC.Generics (Generic)
-- A slot is a location in the heap where a value is stored.
data Slot address = Slot { frameAddress :: address, position :: Position }
deriving (Eq, Show, Ord)
instance AbstractHole address => AbstractHole (Slot address) where
hole = Slot hole (Position 0)
-- | 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 | Void
deriving (Bounded, Enum, Eq, Ord, Show)
newtype Position = Position { unPosition :: Int }
deriving (Eq, Show, Ord)
data Domain
= Standard
| Preluded
deriving (Eq, Show, Ord)
data Kind = AbstractClass
| Assignment
| Call
| Class
| DefaultExport
| Function
| Identifier
| Let
| MemberAccess
| Method
| Module
| New
| Parameter
| PublicField
| QualifiedAliasedImport
| QualifiedExport
| QualifiedImport
| RequiredParameter
| This
| TypeAlias
| TypeIdentifier
| Unknown
| UnqualifiedImport
| VariableDeclaration
deriving (Bounded, Enum, Eq, Show, Ord)
instance Lower Kind where
lowerBound = Unknown
data AccessControl = Public
| Protected
| Private
deriving (Bounded, Enum, Eq, Generic, Hashable, ToJSON, Show)
-- | The Ord AccessControl instance represents an order specification of AccessControls.
-- AccessControls that are less than or equal to another AccessControl implies access.
-- It is helpful to consider `Public <= Private` as saying "Can a Public syntax term access a Private syntax term?"
-- In this way, Public AccessControl is the top of the order specification, and Private AccessControl is the bottom.
instance Ord AccessControl where
-- | Private AccessControl represents the least overlap or accessibility with other AccessControls.
-- When asking if the AccessControl "on the left" is less than the AccessControl "on the right", Private AccessControl on the left always implies access to the thing on the right.
(<=) Private _ = True
(<=) _ Private = False
-- | Protected AccessControl is in between Private and Public in the order specification.
-- Protected AccessControl "on the left" has access to Protected or Public AccessControls "on the right".
(<=) Protected Public = True
(<=) Protected Protected = True
-- | Public AccessControl "on the left" has access only to Public AccessControl "on the right".
(<=) Public Public = True
(<=) Public _ = False

View File

@ -1,9 +0,0 @@
-- | 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

View File

@ -160,7 +160,6 @@ library
, Data.Language
, Data.Map.Monoidal
, Data.Maybe.Exts
, Data.Project
, Data.Quieterm
, Data.Semigroup.App
, Data.Scientific.Exts

View File

@ -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

View File

@ -5,15 +5,12 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
-- | Semantic-specific functionality for blob handling.
module Data.Blob
( Blob(..)
, Blobs(..)
, blobLanguage
( Blobs(..)
, NoLanguageForBlob (..)
, blobPath
, decodeBlobs
, nullBlob
, fromSource
, moduleForBlob
, noLanguageForBlob
, BlobPair
@ -23,10 +20,11 @@ module Data.Blob
, languageTagForBlobPair
, pathForBlobPair
, pathKeyForBlobPair
, module Analysis.Blob
) where
import Analysis.File (File (..))
import Analysis.Blob
import Control.Effect.Error
import Control.Exception
import Data.Aeson
@ -39,44 +37,12 @@ import Data.Maybe.Exts
import Data.Module
import GHC.Generics (Generic)
import Source.Language as Language
import Source.Source (Source, totalSpan)
import qualified Source.Source as Source
import qualified System.FilePath as FP
import qualified System.Path as Path
import qualified System.Path.PartClass as Path.PartClass
-- | The source, path information, and language of a file read from disk.
data Blob = Blob
{ blobSource :: Source -- ^ The UTF-8 encoded source text of the blob.
, blobFile :: File Language -- ^ Path/language information for this blob.
} deriving (Show, Eq)
blobLanguage :: Blob -> Language
blobLanguage = Analysis.File.fileBody . blobFile
blobPath :: Blob -> FilePath
blobPath = Path.toString . Analysis.File.filePath . blobFile
newtype Blobs a = Blobs { blobs :: [a] }
deriving (Generic, FromJSON)
instance FromJSON Blob where
parseJSON = withObject "Blob" $ \b -> do
src <- b .: "content"
Right pth <- fmap Path.parse (b .: "path")
lang <- b .: "language"
let lang' = if knownLanguage lang then lang else Language.forPath pth
pure (fromSource (pth :: Path.AbsRelFile) lang' src)
nullBlob :: Blob -> Bool
nullBlob Blob{..} = Source.null blobSource
-- | Create a Blob from a provided path, language, and UTF-8 source.
-- The resulting Blob's span is taken from the 'totalSpan' of the source.
fromSource :: Path.PartClass.AbsRel ar => Path.File ar -> Language -> Source -> Blob
fromSource filepath language source
= Blob source (Analysis.File.File (Path.toAbsRel filepath) (totalSpan source) language)
decodeBlobs :: BL.ByteString -> Either String [Blob]
decodeBlobs = fmap blobs <$> eitherDecode

View File

@ -7,19 +7,49 @@ module Data.Blob.IO
, readBlobFromPath
, readBlobsFromDir
, readFilePair
, readProjectFromPaths
) where
import Analysis.Blob
import Analysis.File as File
import Analysis.Project
import qualified Control.Concurrent.Async as Async
import Control.Monad.IO.Class
import Data.Blob
import qualified Data.ByteString as B
import Data.Language
import Data.Maybe.Exts
import Data.Semilattice.Lower
import Semantic.IO
import qualified Source.Source as Source
import qualified System.Path as Path
-- | Deprecated: this has very weird semantics.
readProjectFromPaths :: MonadIO m
=> Maybe Path.AbsRelDir -- ^ An optional root directory for the project
-> Path.AbsRelFileDir -- ^ A file or directory to parse. Passing a file path loads all files in that file's parent directory.
-> Language
-> [Path.AbsRelDir] -- ^ Directories to exclude.
-> m Project
readProjectFromPaths maybeRoot path lang excludeDirs = do
let rootDir :: Path.AbsRelDir
rootDir = case maybeRoot >>= Path.fromAbsRel of
-- If we were provided a root directory, use that.
Just root -> root
Nothing -> case Path.fileFromFileDir path of
-- If we weren't and the path is a file, drop its file name.
Just fp -> Path.takeDirectory fp
-- Otherwise, load from the path.
Nothing -> Path.dirFromFileDir path
paths <- liftIO $ findFilesInDir rootDir exts excludeDirs
blobs <- liftIO $ traverse (readBlobFromFile' . toFile) paths
pure $ Project (Path.toString rootDir) blobs lang (fmap Path.toString excludeDirs)
where
toFile path = File path lowerBound lang
exts = extensionsForLanguage lang
-- | Read a utf8-encoded file to a 'Blob'.
readBlobFromFile :: MonadIO m => File Language -> m (Maybe Blob)
readBlobFromFile (File (Path.toString -> "/dev/null") _ _) = pure Nothing

View File

@ -3,6 +3,8 @@ module Data.Language
, LanguageMode(..)
, PerLanguageModes(..)
, defaultLanguageModes
, preciseLanguageModes
, aLaCarteLanguageModes
, codeNavLanguages
, supportedExts
) where
@ -36,7 +38,10 @@ data PerLanguageModes = PerLanguageModes
deriving (Eq, Ord, Show)
defaultLanguageModes :: PerLanguageModes
defaultLanguageModes = PerLanguageModes
defaultLanguageModes = preciseLanguageModes
aLaCarteLanguageModes :: PerLanguageModes
aLaCarteLanguageModes = PerLanguageModes
{ pythonMode = ALaCarte
, rubyMode = ALaCarte
, goMode = ALaCarte
@ -46,6 +51,17 @@ defaultLanguageModes = PerLanguageModes
, jsxMode = ALaCarte
}
preciseLanguageModes :: PerLanguageModes
preciseLanguageModes = PerLanguageModes
{ pythonMode = Precise
, rubyMode = Precise
, goMode = Precise
, typescriptMode = Precise
, tsxMode = Precise
, javascriptMode = Precise
, jsxMode = Precise
}
data LanguageMode
= ALaCarte
| Precise

View File

@ -1,63 +0,0 @@
module Data.Project
( Project (..)
, projectExtensions
, projectName
, projectFiles
, readProjectFromPaths
) where
import Prelude hiding (readFile)
import Analysis.File
import Control.Monad.IO.Class
import Data.Blob
import Data.Blob.IO
import Data.Language
import Data.Semilattice.Lower
import Data.Text (Text)
import qualified Data.Text as T
import Semantic.IO
import System.FilePath.Posix
import qualified System.Path as Path
-- | A 'Project' contains all the information that semantic needs
-- to execute an analysis, diffing, or graphing pass.
data Project = Project
{ projectRootDir :: FilePath
, projectBlobs :: [Blob]
, projectLanguage :: Language
, projectExcludeDirs :: [FilePath]
} deriving (Eq, Show)
projectName :: Project -> Text
projectName = T.pack . dropExtensions . takeFileName . projectRootDir
projectExtensions :: Project -> [String]
projectExtensions = extensionsForLanguage . projectLanguage
projectFiles :: Project -> [File Language]
projectFiles = fmap blobFile . projectBlobs
readProjectFromPaths :: MonadIO m
=> Maybe Path.AbsRelDir -- ^ An optional root directory for the project
-> Path.AbsRelFileDir -- ^ A file or directory to parse. Passing a file path loads all files in that file's parent directory.
-> Language
-> [Path.AbsRelDir] -- ^ Directories to exclude.
-> m Project
readProjectFromPaths maybeRoot path lang excludeDirs = do
let rootDir :: Path.AbsRelDir
rootDir = case maybeRoot >>= Path.fromAbsRel of
-- If we were provided a root directory, use that.
Just root -> root
Nothing -> case Path.fileFromFileDir path of
-- If we weren't and the path is a file, drop its file name.
Just fp -> Path.takeDirectory fp
-- Otherwise, load from the path.
Nothing -> Path.dirFromFileDir path
paths <- liftIO $ findFilesInDir rootDir exts excludeDirs
blobs <- liftIO $ traverse (readBlobFromFile' . toFile) paths
pure $ Project (Path.toString rootDir) blobs lang (fmap Path.toString excludeDirs)
where
toFile path = File path lowerBound lang
exts = extensionsForLanguage lang

View File

@ -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

View File

@ -3,6 +3,7 @@
module Semantic.CLI (main) where
import qualified Analysis.File as File
import Analysis.Project
import qualified Control.Carrier.Parse.Measured as Parse
import Control.Carrier.Reader
import Control.Exception
@ -15,7 +16,6 @@ import Data.Handle
import qualified Data.Language as Language
import Data.List (intercalate)
import Data.Maybe.Exts
import Data.Project
import Options.Applicative hiding (style)
import Semantic.Api hiding (File)
import Semantic.Config
@ -91,7 +91,6 @@ diffCommand :: Mod CommandFields (Parse.ParseC Task.TaskC Builder)
diffCommand = command "diff" (info diffArgumentsParser (progDesc "Compute changes between paths"))
where
diffArgumentsParser = do
languageModes <- languageModes
renderer <- flag (parseDiffBuilder DiffSExpression) (parseDiffBuilder DiffSExpression) (long "sexpression" <> help "Output s-expression diff tree (default)")
<|> flag' (parseDiffBuilder DiffJSONTree) (long "json" <> help "Output JSON diff trees")
<|> flag' (parseDiffBuilder DiffJSONGraph) (long "json-graph" <> help "Output JSON diff trees")
@ -99,7 +98,7 @@ diffCommand = command "diff" (info diffArgumentsParser (progDesc "Compute change
<|> flag' (parseDiffBuilder DiffDotGraph) (long "dot" <> help "Output the diff as a DOT graph")
<|> flag' (parseDiffBuilder DiffShow) (long "show" <> help "Output using the Show instance (debug only, format subject to change without notice)")
filesOrStdin <- Right <$> some ((,) <$> argument filePathReader (metavar "FILE_A") <*> argument filePathReader (metavar "FILE_B")) <|> pure (Left stdin)
pure $ Task.readBlobPairs filesOrStdin >>= runReader languageModes . renderer
pure $ Task.readBlobPairs filesOrStdin >>= runReader Language.aLaCarteLanguageModes . renderer
parseCommand :: Mod CommandFields (Parse.ParseC Task.TaskC Builder)
parseCommand = command "parse" (info parseArgumentsParser (progDesc "Generate parse trees for path(s)"))
@ -184,7 +183,7 @@ languageModes = Language.PerLanguageModes
= option auto ( long (shortName <> "-mode")
<> help ("The AST representation to use for " <> fullName <> " sources")
<> metavar "ALaCarte|Precise"
<> value Language.ALaCarte
<> value Language.Precise
<> showDefault)
filePathReader :: ReadM (File.File Language.Language)

View File

@ -44,6 +44,7 @@ import Analysis.Abstract.Caching.FlowInsensitive
import Analysis.Abstract.Collecting
import Analysis.Abstract.Graph as Graph
import Analysis.File
import Analysis.Project
import Control.Abstract hiding (String)
import Control.Abstract.PythonPackage as PythonPackage
import Control.Carrier.Fresh.Strict
@ -73,7 +74,6 @@ import Data.Language as Language
import Data.List (find, isPrefixOf)
import Data.Map (Map)
import qualified Data.Map as Map
import Data.Project
import Data.Proxy
import Data.Text (pack, unpack)
import Language.Haskell.HsColour

View File

@ -20,6 +20,7 @@ module Semantic.Resolution
) where
import Analysis.File as File
import Analysis.Project
import Control.Algebra
import Control.Monad.IO.Class
import Data.Aeson
@ -30,7 +31,6 @@ import Data.Language
import qualified Data.Map as Map
import Data.Map.Strict (Map)
import Data.Maybe.Exts
import Data.Project
import Data.Text (Text)
import GHC.Generics (Generic1)
import Semantic.Task.Files

View File

@ -28,6 +28,7 @@ module Semantic.Task.Files
) where
import Analysis.File
import Analysis.Project
import Control.Algebra
import Control.Effect.Error
import Control.Exception
@ -37,7 +38,6 @@ import Data.Blob.IO
import qualified Data.ByteString.Builder as B
import Data.Handle
import Data.Language
import Data.Project
import Prelude hiding (readFile)
import Semantic.IO
import qualified System.IO as IO hiding (withBinaryFile)

View File

@ -18,6 +18,7 @@ module Semantic.Util
import Prelude hiding (readFile)
import Analysis.File
import Analysis.Project
import Control.Abstract
import Control.Carrier.Fresh.Strict
import Control.Carrier.Lift
@ -40,7 +41,6 @@ import Data.Graph.Algebraic (topologicalSort)
import qualified Data.Language as Language
import Data.List (uncons)
import Data.Maybe
import Data.Project
import Data.Semilattice.Lower
import Data.Sum
import Parsing.Parser

View File

@ -78,5 +78,5 @@ instance ToSExpression t => GToSExpression (Rec1 t) where
instance (Foldable f, GToSExpression g) => GToSExpression (f :.: g) where
gtoSExpression (Comp1 fs) n
| null fs = [nl n <> pad n <> "[]"]
| otherwise = nl n <> pad n <> "[" : foldMap gtoSExpression fs (n + 1) <> ["]"]
| null fs = mempty
| otherwise = foldMap gtoSExpression fs n

View File

@ -18,7 +18,7 @@ import Control.Monad
import Data.Blob
import Data.Foldable
import Data.Int
import Data.Language (LanguageMode (..), PerLanguageModes (..))
import Data.Language (LanguageMode (..), PerLanguageModes (..), aLaCarteLanguageModes, preciseLanguageModes)
import Data.List
import qualified Data.Text as Text
import Data.Traversable
@ -259,28 +259,6 @@ okALaCarteSymbol _ _ = True
filterALaCarteSymbols :: String -> [Text.Text] -> [Text.Text]
filterALaCarteSymbols lang = filter (okALaCarteSymbol lang)
aLaCarteLanguageModes :: PerLanguageModes
aLaCarteLanguageModes = PerLanguageModes
{ pythonMode = ALaCarte
, rubyMode = ALaCarte
, goMode = ALaCarte
, typescriptMode = ALaCarte
, tsxMode = ALaCarte
, javascriptMode = ALaCarte
, jsxMode = ALaCarte
}
preciseLanguageModes :: PerLanguageModes
preciseLanguageModes = PerLanguageModes
{ pythonMode = Precise
, rubyMode = Precise
, goMode = Precise
, typescriptMode = Precise
, tsxMode = Precise
, javascriptMode = Precise
, jsxMode = Precise
}
testOptions :: Config.Options
testOptions = defaultOptions
{ optionsFailOnWarning = flag FailOnWarning True

View File

@ -30,6 +30,8 @@ import qualified System.Path as Path
import SpecHelpers
don't :: Applicative m => m a -> m ()
don't = const (pure ())
spec :: Spec
spec = do
@ -140,20 +142,19 @@ spec = do
describe "diff with diffSummaryBuilder" $ do
it "produces JSON output" $ do
blobs <- blobsForPaths (Path.relFile "ruby/toc/methods.A.rb") (Path.relFile "ruby/toc/methods.B.rb")
output <- runTaskOrDie (runReader defaultLanguageModes (diffSummaryBuilder Format.JSON [blobs]))
output <- runTaskOrDie (runReader aLaCarteLanguageModes (diffSummaryBuilder Format.JSON [blobs]))
runBuilder output `shouldBe` ("{\"files\":[{\"path\":\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.B.rb\",\"language\":\"Ruby\",\"changes\":[{\"category\":\"Method\",\"term\":\"self.foo\",\"span\":{\"start\":{\"line\":1,\"column\":1},\"end\":{\"line\":2,\"column\":4}},\"changeType\":\"ADDED\"},{\"category\":\"Method\",\"term\":\"bar\",\"span\":{\"start\":{\"line\":4,\"column\":1},\"end\":{\"line\":6,\"column\":4}},\"changeType\":\"MODIFIED\"},{\"category\":\"Method\",\"term\":\"baz\",\"span\":{\"start\":{\"line\":4,\"column\":1},\"end\":{\"line\":5,\"column\":4}},\"changeType\":\"REMOVED\"}]}]}\n" :: ByteString)
it "produces JSON output if there are parse errors" $ do
it "[DISABLED] produces JSON output if there are parse errors" . don't $ do
blobs <- blobsForPaths (Path.relFile "ruby/toc/methods.A.rb") (Path.relFile "ruby/toc/methods.X.rb")
output <- runTaskOrDie (runReader defaultLanguageModes (diffSummaryBuilder Format.JSON [blobs]))
runBuilder output `shouldBe` ("{\"files\":[{\"path\":\"test/fixtures/ruby/toc/methods.A.rb -> test/fixtures/ruby/toc/methods.X.rb\",\"language\":\"Ruby\",\"changes\":[{\"category\":\"Method\",\"term\":\"bar\",\"span\":{\"start\":{\"line\":1,\"column\":1},\"end\":{\"line\":2,\"column\":4}},\"changeType\":\"REMOVED\"},{\"category\":\"Method\",\"term\":\"baz\",\"span\":{\"start\":{\"line\":4,\"column\":1},\"end\":{\"line\":5,\"column\":4}},\"changeType\":\"REMOVED\"}],\"errors\":[{\"error\":\"expected end of input nodes, but got ParseError\",\"span\":{\"start\":{\"line\":1,\"column\":1},\"end\":{\"line\":3,\"column\":1}}}]}]}\n" :: ByteString)
it "ignores anonymous functions" $ do
blobs <- blobsForPaths (Path.relFile "ruby/toc/lambda.A.rb") (Path.relFile "ruby/toc/lambda.B.rb")
output <- runTaskOrDie (runReader defaultLanguageModes (diffSummaryBuilder Format.JSON [blobs]))
output <- runTaskOrDie (runReader aLaCarteLanguageModes (diffSummaryBuilder Format.JSON [blobs]))
runBuilder output `shouldBe` ("{\"files\":[{\"path\":\"test/fixtures/ruby/toc/lambda.A.rb -> test/fixtures/ruby/toc/lambda.B.rb\",\"language\":\"Ruby\"}]}\n" :: ByteString)
type Diff' = Diff ListableSyntax (Maybe Declaration) (Maybe Declaration)
type Term' = Term ListableSyntax (Maybe Declaration)
@ -219,4 +220,4 @@ summarize
:: (Has (Error SomeException) sig m, Has Parse sig m, Has Telemetry sig m, MonadIO m)
=> BlobPair
-> m [Either ErrorSummary TOCSummary]
summarize = parsePairWith (summarizeTermParsers defaultLanguageModes) summarizeTerms
summarize = parsePairWith (summarizeTermParsers aLaCarteLanguageModes) summarizeTerms

View File

@ -71,8 +71,8 @@ diffFixtures :: [(String, [BlobPair] -> ParseC TaskC Builder, [(File Language, F
diffFixtures =
[ ("json diff", parseDiffBuilder DiffJSONTree, pathMode, prefix </> Path.file "diff-tree.json")
, ("s-expression diff", parseDiffBuilder DiffSExpression, pathMode, Path.relFile "test/fixtures/ruby/corpus/method-declaration.diffA-B.txt")
, ("toc summaries diff", runReader defaultLanguageModes . diffSummaryBuilder Serializing.Format.JSON, pathMode, prefix </> Path.file "diff-tree.toc.json")
, ("protobuf diff", runReader defaultLanguageModes . diffSummaryBuilder Serializing.Format.Proto, pathMode, prefix </> Path.file "diff-tree.toc.protobuf.bin")
, ("toc summaries diff", runReader aLaCarteLanguageModes . diffSummaryBuilder Serializing.Format.JSON, pathMode, prefix </> Path.file "diff-tree.toc.json")
, ("protobuf diff", runReader aLaCarteLanguageModes . diffSummaryBuilder Serializing.Format.Proto, pathMode, prefix </> Path.file "diff-tree.toc.protobuf.bin")
]
where pathMode = [(File (Path.absRel "test/fixtures/ruby/corpus/method-declaration.A.rb") lowerBound Ruby, File (Path.absRel "test/fixtures/ruby/corpus/method-declaration.B.rb") lowerBound Ruby)]
prefix = Path.relDir "test/fixtures/cli"

View File

@ -31,4 +31,4 @@ spec = do
it "renders with the specified renderer" $ do
output <- fmap runBuilder . runTaskOrDie . runReader defaultLanguageModes $ parseTermBuilder TermSExpression [methodsBlob]
output `shouldBe` "(Statements\n (Method\n (Empty)\n (Identifier)\n (Statements)))\n"
output `shouldBe` "(Program \n (Statement \n (Arg \n (Primary \n (Method \n (MethodName \n (Identifier \"foo\")))))))\n"

View File

@ -26,6 +26,7 @@ module SpecHelpers
import qualified Analysis.File as File
import Analysis.Name as X
import Analysis.Project as X
import Control.Abstract
import Control.Carrier.Fresh.Strict
import Control.Carrier.Lift
@ -56,7 +57,6 @@ import Data.Language as X hiding (Precise)
import Data.List.NonEmpty as X (NonEmpty (..))
import Data.Maybe as X
import Data.Monoid as X (First (..), Last (..), Monoid (..))
import Data.Project as X
import Data.Proxy as X
import Data.Semigroup as X (Semigroup (..))
import Data.Semilattice.Lower as X

View File

@ -12,27 +12,27 @@ import Tags.Tagging as Tags
spec :: Spec
spec = do
describe "go" $ do
it "produces tags for functions with docs" $
it "produces tags for functions with docs (TODO)" $
parseTestFile [Function] (Path.relFile "test/fixtures/go/tags/simple_functions.go") `shouldReturn`
[ Tag "TestFromBits" Function (Loc (Range 51 92) (Span (Pos 6 1) (Pos 8 2))) "func TestFromBits(t *testing.T) {" (Just "// TestFromBits ...")
, Tag "Hi" Function (Loc (Range 94 107) (Span (Pos 10 1) (Pos 11 2))) "func Hi()" Nothing ]
[ Tag "TestFromBits" Function (Loc (Range 51 92) (Span (Pos 6 1) (Pos 8 2))) "func TestFromBits(t *testing.T) {" Nothing
, Tag "Hi" Function (Loc (Range 94 107) (Span (Pos 10 1) (Pos 11 2))) "func Hi() {" Nothing ]
it "produces tags for methods" $
parseTestFile [Method] (Path.relFile "test/fixtures/go/tags/method.go") `shouldReturn`
[ Tag "CheckAuth" Method (Loc (Range 19 118) (Span (Pos 3 1) (Pos 3 100))) "func (c *apiClient) CheckAuth(req *http.Request, user, repo string) (*authenticatedActor, error)" Nothing]
[ Tag "CheckAuth" Method (Loc (Range 19 118) (Span (Pos 3 1) (Pos 3 100))) "func (c *apiClient) CheckAuth(req *http.Request, user, repo string) (*authenticatedActor, error) {}" Nothing]
it "produces tags for calls" $
parseTestFile [Call] (Path.relFile "test/fixtures/go/tags/simple_functions.go") `shouldReturn`
[ Tag "Hi" Call (Loc (Range 86 90) (Span (Pos 7 2) (Pos 7 6))) "Hi()" Nothing]
describe "javascript and typescript" $ do
it "produces tags for functions with docs" $
it "produces tags for functions with docs (TODO)" $
parseTestFile [Function] (Path.relFile "test/fixtures/javascript/tags/simple_function_with_docs.js") `shouldReturn`
[ Tag "myFunction" Function (Loc (Range 22 59) (Span (Pos 2 1) (Pos 4 2))) "function myFunction()" (Just "// This is myFunction") ]
[ Tag "myFunction" Function (Loc (Range 22 59) (Span (Pos 2 1) (Pos 4 2))) "function myFunction() {" Nothing ]
it "produces tags for classes" $
parseTestFile [Class] (Path.relFile "test/fixtures/typescript/tags/class.ts") `shouldReturn`
[ Tag "FooBar" Class (Loc (Range 0 15) (Span (Pos 1 1) (Pos 1 16))) "class FooBar" Nothing ]
[ Tag "FooBar" Class (Loc (Range 0 15) (Span (Pos 1 1) (Pos 1 16))) "class FooBar {}" Nothing ]
it "produces tags for modules" $
parseTestFile [Tags.Module] (Path.relFile "test/fixtures/typescript/tags/module.ts") `shouldReturn`
@ -72,19 +72,19 @@ spec = do
, Tag "a" Call (Loc (Range 22 23) (Span (Pos 3 3) (Pos 3 4))) "a" Nothing
]
it "produces tags for methods with docs" $
it "produces tags for methods with docs (TODO)" $
parseTestFile [Method] (Path.relFile "test/fixtures/ruby/tags/simple_method_with_docs.rb") `shouldReturn`
[ Tag "foo" Method (Loc (Range 14 25) (Span (Pos 2 1) (Pos 3 4))) "def foo" (Just "# Public: foo") ]
[ Tag "foo" Method (Loc (Range 14 25) (Span (Pos 2 1) (Pos 3 4))) "def foo" Nothing ]
it "correctly tags files containing multibyte UTF-8 characters" $
it "correctly tags files containing multibyte UTF-8 characters (TODO)" $
parseTestFile [Method] (Path.relFile "test/fixtures/ruby/tags/unicode_identifiers.rb") `shouldReturn`
[ Tag "日本語" Method (Loc (Range 16 43) (Span (Pos 2 1) (Pos 4 4))) "def 日本語" (Just "# coding: utf-8")]
[ Tag "日本語" Method (Loc (Range 16 43) (Span (Pos 2 1) (Pos 4 4))) "def 日本語" Nothing]
it "produces tags for methods and classes with docs" $
it "produces tags for methods and classes with docs (TODO)" $
parseTestFile [Class, Method, Tags.Module] (Path.relFile "test/fixtures/ruby/tags/class_module.rb") `shouldReturn`
[ Tag "Foo" Tags.Module (Loc (Range 14 118) (Span (Pos 2 1 ) (Pos 12 4))) "module Foo" (Just "# Public: Foo")
, Tag "Bar" Class (Loc (Range 44 114) (Span (Pos 5 3 ) (Pos 11 6))) "class Bar" (Just "# Public: Bar")
, Tag "baz" Method (Loc (Range 77 108) (Span (Pos 8 5 ) (Pos 10 8))) "def baz(a)" (Just "# Public: baz")
[ Tag "Foo" Tags.Module (Loc (Range 14 118) (Span (Pos 2 1 ) (Pos 12 4))) "module Foo" Nothing
, Tag "Bar" Class (Loc (Range 44 114) (Span (Pos 5 3 ) (Pos 11 6))) "class Bar" Nothing
, Tag "baz" Method (Loc (Range 77 108) (Span (Pos 8 5 ) (Pos 10 8))) "def baz(a)" Nothing
, Tag "C" Class (Loc (Range 120 188) (Span (Pos 14 1) (Pos 20 4))) "class A::B::C" Nothing
, Tag "foo" Method (Loc (Range 136 163) (Span (Pos 15 3) (Pos 17 6))) "def foo" Nothing
, Tag "foo" Method (Loc (Range 166 184) (Span (Pos 18 3) (Pos 19 6))) "def self.foo" Nothing

View File

@ -1,32 +1,63 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Statements
(Type
(Identifier)
(Array
(Plus
(Integer)
(Integer))
(Identifier))))
(Statements
(Type
(Identifier)
(Array
(Integer)
(Array
(Integer)
(Identifier)))))
(Statements
(Type
(Identifier)
(Array
(Integer)
(Array
(Integer)
(Array
(Integer)
(Identifier)))))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "a")
(Type
(SimpleType
(ArrayType
(Expression
(BinaryExpression
(Token)
(Expression
(IntLiteral "2"))
(Expression
(IntLiteral "2"))))
(Type
(SimpleType
(TypeIdentifier "x")))))))))
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "b")
(Type
(SimpleType
(ArrayType
(Expression
(IntLiteral "3"))
(Type
(SimpleType
(ArrayType
(Expression
(IntLiteral "5"))
(Type
(SimpleType
(TypeIdentifier "int"))))))))))))
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "c")
(Type
(SimpleType
(ArrayType
(Expression
(IntLiteral "2"))
(Type
(SimpleType
(ArrayType
(Expression
(IntLiteral "2"))
(Type
(SimpleType
(ArrayType
(Expression
(IntLiteral "2"))
(Type
(SimpleType
(TypeIdentifier "float64"))))))))))))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,32 +1,63 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Statements
(Type
(Identifier)
(Array
(Plus
(Integer)
(Integer))
(Identifier))))
(Statements
(Type
(Identifier)
(Array
(Integer)
(Array
(Integer)
(Identifier)))))
(Statements
(Type
(Identifier)
(Array
(Integer)
(Array
(Integer)
(Array
(Integer)
(Identifier)))))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "a")
(Type
(SimpleType
(ArrayType
(Expression
(BinaryExpression
(Token)
(Expression
(IntLiteral "1"))
(Expression
(IntLiteral "1"))))
(Type
(SimpleType
(TypeIdentifier "y")))))))))
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "d")
(Type
(SimpleType
(ArrayType
(Expression
(IntLiteral "6"))
(Type
(SimpleType
(ArrayType
(Expression
(IntLiteral "9"))
(Type
(SimpleType
(TypeIdentifier "int"))))))))))))
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "e")
(Type
(SimpleType
(ArrayType
(Expression
(IntLiteral "1"))
(Type
(SimpleType
(ArrayType
(Expression
(IntLiteral "2"))
(Type
(SimpleType
(ArrayType
(Expression
(IntLiteral "3"))
(Type
(SimpleType
(TypeIdentifier "float64"))))))))))))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,14 +1,28 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Assignment
(Identifier)
(Composite
(Array
(Identifier))
(Statements
(Integer)
(Integer)
(Integer))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(CompositeLiteral
(LiteralValue
(Element
(Expression
(IntLiteral "1")))
(Element
(Expression
(IntLiteral "2")))
(Element
(Expression
(IntLiteral "3"))))
(ImplicitLengthArrayType
(Type
(SimpleType
(TypeIdentifier "int")))))))
(Identifier "a1")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,14 +1,28 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Assignment
(Identifier)
(Composite
(Array
(Identifier))
(Statements
(Integer)
(Integer)
(Integer))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(CompositeLiteral
(LiteralValue
(Element
(Expression
(IntLiteral "4")))
(Element
(Expression
(IntLiteral "5")))
(Element
(Expression
(IntLiteral "6"))))
(ImplicitLengthArrayType
(Type
(SimpleType
(TypeIdentifier "int")))))))
(Identifier "a1")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,62 +1,133 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Assignment
(Identifier)
(Integer))
(AugmentedAssignment
(Plus
(Statements
(Identifier)
(Identifier))
(Statements
(Integer)
(Integer))))
(AugmentedAssignment
(Times
(Identifier)
(Integer)))
(AugmentedAssignment
(Plus
(Identifier)
(Integer)))
(AugmentedAssignment
(LShift
(Identifier)
(Integer)))
(AugmentedAssignment
(RShift
(Identifier)
(Integer)))
(AugmentedAssignment
(DividedBy
(Identifier)
(Integer)))
(AugmentedAssignment
(BXOr
(Identifier)
(Integer)))
(AugmentedAssignment
(Modulo
(Identifier)
(Integer)))
(AugmentedAssignment
(Not
(BAnd
(Identifier)
(Integer))))
(Assignment
(Identifier)
(Statements
(Pointer
(Identifier))
(Reference
(Composite
(Identifier)
(Statements
(KeyValue
(Identifier)
(Integer))))))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "a")))
(ExpressionList
(Expression
(IntLiteral "1"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "b"))
(Expression
(Identifier "c")))
(ExpressionList
(Expression
(IntLiteral "2"))
(Expression
(IntLiteral "3"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "d")))
(ExpressionList
(Expression
(IntLiteral "3"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "e")))
(ExpressionList
(Expression
(IntLiteral "1"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "f")))
(ExpressionList
(Expression
(IntLiteral "1"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "g")))
(ExpressionList
(Expression
(IntLiteral "2"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "h")))
(ExpressionList
(Expression
(IntLiteral "2"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "i")))
(ExpressionList
(Expression
(IntLiteral "2"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "j")))
(ExpressionList
(Expression
(IntLiteral "2"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "k")))
(ExpressionList
(Expression
(IntLiteral "2"))))))
(Statement
(VarDeclaration
(VarSpec
(ExpressionList
(Expression
(UnaryExpression
(Token)
(Expression
(CompositeLiteral
(LiteralValue
(KeyedElement
(FieldIdentifier "y")
(Expression
(IntLiteral "1000"))))
(TypeIdentifier "Point3D"))))))
(Identifier "pointer")
(Type
(SimpleType
(PointerType
(Type
(SimpleType
(TypeIdentifier "Point3D"))))))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,62 +1,133 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Assignment
(Identifier)
(Integer))
(AugmentedAssignment
(Plus
(Statements
(Identifier)
(Identifier))
(Statements
(Integer)
(Integer))))
(AugmentedAssignment
(Times
(Identifier)
(Integer)))
(AugmentedAssignment
(Plus
(Identifier)
(Integer)))
(AugmentedAssignment
(LShift
(Identifier)
(Integer)))
(AugmentedAssignment
(RShift
(Identifier)
(Integer)))
(AugmentedAssignment
(DividedBy
(Identifier)
(Integer)))
(AugmentedAssignment
(BXOr
(Identifier)
(Integer)))
(AugmentedAssignment
(Modulo
(Identifier)
(Integer)))
(AugmentedAssignment
(Not
(BAnd
(Identifier)
(Integer))))
(Assignment
(Identifier)
(Statements
(Pointer
(Identifier))
(Reference
(Composite
(Identifier)
(Statements
(KeyValue
(Identifier)
(Integer))))))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "l")))
(ExpressionList
(Expression
(IntLiteral "1"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "m"))
(Expression
(Identifier "n")))
(ExpressionList
(Expression
(IntLiteral "2"))
(Expression
(IntLiteral "3"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "o")))
(ExpressionList
(Expression
(IntLiteral "3"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "p")))
(ExpressionList
(Expression
(IntLiteral "1"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "q")))
(ExpressionList
(Expression
(IntLiteral "1"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "s")))
(ExpressionList
(Expression
(IntLiteral "2"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "t")))
(ExpressionList
(Expression
(IntLiteral "2"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "u")))
(ExpressionList
(Expression
(IntLiteral "2"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "v")))
(ExpressionList
(Expression
(IntLiteral "2"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "w")))
(ExpressionList
(Expression
(IntLiteral "2"))))))
(Statement
(VarDeclaration
(VarSpec
(ExpressionList
(Expression
(UnaryExpression
(Token)
(Expression
(CompositeLiteral
(LiteralValue
(KeyedElement
(FieldIdentifier "x")
(Expression
(IntLiteral "1000"))))
(TypeIdentifier "Point2D"))))))
(Identifier "pointer")
(Type
(SimpleType
(PointerType
(Type
(SimpleType
(TypeIdentifier "Point2D"))))))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,70 +1,178 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Context
(Comment)
(Or
(Identifier)
(Context
(Comment)
(Identifier))))
(Context
(Comment)
(And
(Identifier)
(Identifier)))
(Equal
(Identifier)
(Identifier))
(Not
(Equal
(Identifier)
(Identifier)))
(LessThan
(Identifier)
(Identifier))
(LessThanEqual
(Identifier)
(Identifier))
(GreaterThan
(Identifier)
(Identifier))
(GreaterThanEqual
(Identifier)
(Identifier))
(Plus
(Identifier)
(Identifier))
(Minus
(Identifier)
(Identifier))
(BOr
(Identifier)
(Identifier))
(BXOr
(Identifier)
(Identifier))
(Times
(Identifier)
(Identifier))
(DividedBy
(Identifier)
(Identifier))
(Modulo
(Identifier)
(Identifier))
(LShift
(Identifier)
(Identifier))
(RShift
(Identifier)
(Identifier))
(BAnd
(Identifier)
(Identifier))
(BAnd
(Identifier)
(Identifier)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "a"))
(Expression
(Identifier "b"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "c"))
(Expression
(Identifier "d"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "e"))
(Expression
(Identifier "f"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "g"))
(Expression
(Identifier "h"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "i"))
(Expression
(Identifier "j"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "k"))
(Expression
(Identifier "l"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "m"))
(Expression
(Identifier "n"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "o"))
(Expression
(Identifier "p"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "q"))
(Expression
(Identifier "r"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "s"))
(Expression
(Identifier "t"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "u"))
(Expression
(Identifier "v"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "x"))
(Expression
(Identifier "y"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "z"))
(Expression
(Identifier "aa"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "bb"))
(Expression
(Identifier "cc"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "dd"))
(Expression
(Identifier "ee"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "ff"))
(Expression
(Identifier "gg"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "hh"))
(Expression
(Identifier "ii"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "jj"))
(Expression
(Identifier "kk"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "ll"))
(Expression
(Identifier "mm")))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,70 +1,178 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Context
(Comment)
(Or
(Identifier)
(Context
(Comment)
(Identifier))))
(Context
(Comment)
(And
(Identifier)
(Identifier)))
(Equal
(Identifier)
(Identifier))
(Not
(Equal
(Identifier)
(Identifier)))
(LessThan
(Identifier)
(Identifier))
(LessThanEqual
(Identifier)
(Identifier))
(GreaterThan
(Identifier)
(Identifier))
(GreaterThanEqual
(Identifier)
(Identifier))
(Plus
(Identifier)
(Identifier))
(Minus
(Identifier)
(Identifier))
(BOr
(Identifier)
(Identifier))
(BXOr
(Identifier)
(Identifier))
(Times
(Identifier)
(Identifier))
(DividedBy
(Identifier)
(Identifier))
(Modulo
(Identifier)
(Identifier))
(LShift
(Identifier)
(Identifier))
(RShift
(Identifier)
(Identifier))
(BAnd
(Identifier)
(Identifier))
(BAnd
(Identifier)
(Identifier)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "b"))
(Expression
(Identifier "c"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "d"))
(Expression
(Identifier "c"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "f"))
(Expression
(Identifier "e"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "h"))
(Expression
(Identifier "g"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "j"))
(Expression
(Identifier "i"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "l"))
(Expression
(Identifier "k"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "n"))
(Expression
(Identifier "m"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "p"))
(Expression
(Identifier "o"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "r"))
(Expression
(Identifier "q"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "t"))
(Expression
(Identifier "s"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "v"))
(Expression
(Identifier "u"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "y"))
(Expression
(Identifier "x"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "aa"))
(Expression
(Identifier "z"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "cc"))
(Expression
(Identifier "bb"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "ee"))
(Expression
(Identifier "dd"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "gg"))
(Expression
(Identifier "ff"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "ii"))
(Expression
(Identifier "hh"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "kk"))
(Expression
(Identifier "jj"))))))
(Statement
(SimpleStatement
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "mm"))
(Expression
(Identifier "ll")))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,30 +1,49 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Call
(Identifier)
(Statements
(Identifier)
(Variadic
(Identifier)))
(Empty))
(Call
(Identifier)
(Statements
(Identifier)
(Identifier))
(Empty))
(Call
(Identifier)
(Statements
(Identifier)
(Variadic
(Identifier)))
(Empty))
(Call
(Identifier)
(Statements)
(Empty)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "x"))
(ArgumentList
(Expression
(Identifier "b"))
(VariadicArgument
(Expression
(Identifier "c"))))))))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "y"))
(ArgumentList
(Expression
(Identifier "b"))
(Expression
(Identifier "c")))))))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "z"))
(ArgumentList
(Expression
(Identifier "b"))
(VariadicArgument
(Expression
(Identifier "c"))))))))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,26 +1,42 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Call
(Identifier)
(Statements
(Identifier)
(Variadic
(Identifier)))
(Empty))
(Call
(Identifier)
(Statements
(Identifier)
(Identifier))
(Empty))
(Call
(Identifier)
(Statements
(Identifier)
(Variadic
(Identifier)))
(Empty)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList
(Expression
(Identifier "b"))
(VariadicArgument
(Expression
(Identifier "c"))))))))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "b"))
(ArgumentList
(Expression
(Identifier "b"))
(Expression
(Identifier "c")))))))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "c"))
(ArgumentList
(Expression
(Identifier "b"))
(VariadicArgument
(Expression
(Identifier "c")))))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,8 +1,9 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Match
(Empty)
(Statements))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ExpressionSwitchStatement)))
(Identifier "main")
(ParameterList)))

View File

@ -1,43 +1,56 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Match
(Statements)
(Pattern
(Statements
(Identifier)
(Call
(Identifier)
(Statements)
(Empty)))
(Statements)))
(Match
(Statements
(Identifier))
(Pattern
(Statements
(Statements
(Integer)
(Integer))
(Call
(Identifier)
(Statements)
(Empty))
(Call
(Identifier)
(Statements)
(Empty))
(Pattern
(Identifier)
(Empty)))
(DefaultPattern
(Statements
(Call
(Identifier)
(Statements)
(Empty))
(Break
(Empty)))))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ExpressionSwitchStatement
(ExpressionCase
(ExpressionList
(Expression
(Identifier "foo")))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "f1"))
(ArgumentList))))))))
(Statement
(ExpressionSwitchStatement
(Expression
(Identifier "e"))
(ExpressionCase
(ExpressionList
(Expression
(IntLiteral "1"))
(Expression
(IntLiteral "2")))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList)))))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "b"))
(ArgumentList)))))
(Statement
(FallthroughStatement "fallthrough")))
(DefaultCase
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "c"))
(ArgumentList)))))
(Statement
(BreakStatement))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,34 +1,67 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Type
(Identifier)
(BidirectionalChannel
(ReceiveChannel
(Identifier))))
(Type
(Identifier)
(SendChannel
(SendChannel
(Constructor
(Empty)
(Statements)))))
(Type
(Identifier)
(SendChannel
(ReceiveChannel
(Identifier))))
(Type
(Identifier)
(ReceiveChannel
(ReceiveChannel
(Identifier))))
(Type
(Identifier)
(BidirectionalChannel
(Parenthesized
(ReceiveChannel
(Identifier))))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "c1")
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "int"))))))))))
(TypeSpec
(TypeIdentifier "c2")
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(StructType
(FieldDeclarationList)))))))))))
(TypeSpec
(TypeIdentifier "c3")
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "int"))))))))))
(TypeSpec
(TypeIdentifier "c4")
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "int"))))))))))
(TypeSpec
(TypeIdentifier "c5")
(Type
(SimpleType
(ChannelType
(Type
(ParenthesizedType
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "int")))))))))))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,34 +1,67 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Type
(Identifier)
(BidirectionalChannel
(ReceiveChannel
(Identifier))))
(Type
(Identifier)
(SendChannel
(SendChannel
(Constructor
(Empty)
(Statements)))))
(Type
(Identifier)
(SendChannel
(ReceiveChannel
(Identifier))))
(Type
(Identifier)
(ReceiveChannel
(ReceiveChannel
(Identifier))))
(Type
(Identifier)
(BidirectionalChannel
(Parenthesized
(ReceiveChannel
(Identifier))))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "c2")
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "string"))))))))))
(TypeSpec
(TypeIdentifier "c3")
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(StructType
(FieldDeclarationList)))))))))))
(TypeSpec
(TypeIdentifier "c4")
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "string"))))))))))
(TypeSpec
(TypeIdentifier "c4")
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "string"))))))))))
(TypeSpec
(TypeIdentifier "c5")
(Type
(SimpleType
(ChannelType
(Type
(ParenthesizedType
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "string")))))))))))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,8 +1,7 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Context
(Comment)
(Empty))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block)
(Identifier "main")
(ParameterList)))

View File

@ -1,8 +1,7 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Context
(Comment)
(Empty))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block)
(Identifier "main")
(ParameterList)))

View File

@ -1,11 +1,17 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Assignment
(Annotation
(Statements
(Identifier))
(Identifier))
(Integer))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(IntLiteral "0")))
(Identifier "zero")
(Type
(SimpleType
(TypeIdentifier "int")))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,14 +1,21 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Assignment
(Annotation
(Statements
(Identifier)
(Identifier))
(Identifier))
(Statements
(Integer)
(Integer)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(IntLiteral "1"))
(Expression
(IntLiteral "2")))
(Identifier "one")
(Token)
(Identifier "two")
(Type
(SimpleType
(TypeIdentifier "uiint64")))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,8 +1,14 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Assignment
(Identifier)
(Integer))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(IntLiteral "0")))
(Identifier "zero")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,12 +1,18 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Assignment
(Statements
(Identifier)
(Identifier))
(Statements
(Integer)
(Integer)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(IntLiteral "1"))
(Expression
(IntLiteral "2")))
(Identifier "one")
(Token)
(Identifier "two")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,15 +1,18 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Assignment
(Identifier)
(Identifier))
(Assignment
(Identifier)
(Statements))
(Assignment
(Identifier)
(Statements)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(Identifier "iota")))
(Identifier "zero"))
(ConstSpec
(Identifier "one"))
(ConstSpec
(Identifier "two")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,15 +1,18 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Assignment
(Identifier)
(Identifier))
(Assignment
(Identifier)
(Statements))
(Assignment
(Identifier)
(Statements)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(Identifier "iota")))
(Identifier "a"))
(ConstSpec
(Identifier "b"))
(ConstSpec
(Identifier "c")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,34 +1,75 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Call
(Identifier)
(SendChannel
(Identifier))
(Empty))
(Call
(Identifier)
(Statements
(SendChannel
(Identifier))
(Minus
(Identifier)
(Identifier)))
(Empty))
(Call
(Identifier)
(Statements
(SendChannel
(Identifier))
(Integer)
(Integer))
(Empty))
(Call
(Identifier)
(Map
(Identifier)
(Identifier))
(Empty)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "make"))
(ArgumentList
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "int")))))))))))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "make"))
(ArgumentList
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "int"))))))
(Expression
(ParenthesizedExpression
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "new"))
(Expression
(Identifier "old")))))))))))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "make"))
(ArgumentList
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "int"))))))
(Expression
(IntLiteral "5"))
(Expression
(IntLiteral "10")))))))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "new"))
(ArgumentList
(Type
(SimpleType
(MapType
(Type
(SimpleType
(TypeIdentifier "string")))
(Type
(SimpleType
(TypeIdentifier "string"))))))))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,34 +1,75 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Call
(Identifier)
(SendChannel
(Identifier))
(Empty))
(Call
(Identifier)
(Statements
(SendChannel
(Identifier))
(Minus
(Identifier)
(Identifier)))
(Empty))
(Call
(Identifier)
(Statements
(SendChannel
(Identifier))
(Integer)
(Integer))
(Empty))
(Call
(Identifier)
(Map
(Identifier)
(Identifier))
(Empty)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "make"))
(ArgumentList
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "string")))))))))))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "make"))
(ArgumentList
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "string"))))))
(Expression
(ParenthesizedExpression
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "new"))
(Expression
(Identifier "old")))))))))))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "make"))
(ArgumentList
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "string"))))))
(Expression
(IntLiteral "7"))
(Expression
(IntLiteral "11")))))))
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "new"))
(ArgumentList
(Type
(SimpleType
(MapType
(Type
(SimpleType
(TypeIdentifier "int")))
(Type
(SimpleType
(TypeIdentifier "int"))))))))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,21 +1,57 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Assignment
(Identifier)
(Float))
(Assignment
(Identifier)
(Float))
(Assignment
(Identifier)
(Float))
(Assignment
(Identifier)
(Float))
(Assignment
(Identifier)
(Float)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "f1")))
(ExpressionList
(Expression
(FloatLiteral "1.5"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "f2")))
(ExpressionList
(Expression
(FloatLiteral "1.5e100"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "f3")))
(ExpressionList
(Expression
(FloatLiteral "1.5e+50"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "f4")))
(ExpressionList
(Expression
(FloatLiteral "1.5e-5"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "f5")))
(ExpressionList
(Expression
(FloatLiteral ".5e-50")))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,21 +1,57 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Assignment
(Identifier)
(Float))
(Assignment
(Identifier)
(Float))
(Assignment
(Identifier)
(Float))
(Assignment
(Identifier)
(Float))
(Assignment
(Identifier)
(Float)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "f1")))
(ExpressionList
(Expression
(FloatLiteral "2.6"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "f2")))
(ExpressionList
(Expression
(FloatLiteral "2.6e211"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "f3")))
(ExpressionList
(Expression
(FloatLiteral "2.6e+60"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "f4")))
(ExpressionList
(Expression
(FloatLiteral "2.6e-7"))))))
(Statement
(SimpleStatement
(AssignmentStatement
(Token)
(ExpressionList
(Expression
(Identifier "f5")))
(ExpressionList
(Expression
(FloatLiteral ".6e-60")))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,104 +1,178 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(For
(Empty)
(Empty)
(Empty)
(Statements
(Call
(Identifier)
(Statements)
(Empty))
(Goto
(Identifier))))
(For
(Assignment
(Identifier)
(Integer))
(LessThan
(Identifier)
(Integer))
(PostIncrement
(Identifier))
(Statements
(Call
(Identifier)
(Statements)
(Empty))
(Break
(Identifier))))
(For
(LessThan
(Identifier)
(Integer))
(PostIncrement
(Identifier))
(Empty)
(Statements
(Call
(Identifier)
(Statements)
(Empty))
(Continue
(Identifier))))
(For
(Empty)
(Empty)
(Empty)
(Statements
(Call
(Identifier)
(Statements)
(Empty))
(Continue
(Empty))))
(ForEach
(Identifier)
(Identifier)
(Statements
(Call
(Identifier)
(Identifier)
(Empty))
(Break
(Empty))))
(ForEach
(Statements
(Identifier)
(Identifier))
(Identifier)
(Call
(Identifier)
(Statements
(Identifier)
(Identifier))
(Empty)))
(ForEach
(Statements
(Identifier)
(Identifier))
(Identifier)
(Call
(Identifier)
(Statements
(Identifier)
(Identifier))
(Empty)))
(For
(Empty)
(LessThan
(Integer)
(Integer))
(Empty)
(Call
(Identifier)
(Statements)
(Empty)))
(ForEach
(Empty)
(Identifier)
(Statements)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList)))))
(Statement
(GotoStatement
(LabelName "loop"))))))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList)))))
(Statement
(BreakStatement
(LabelName "loop"))))
(ForClause
(SimpleStatement
(ShortVarDeclaration
(ExpressionList
(Expression
(Identifier "i")))
(ExpressionList
(Expression
(IntLiteral "0")))))
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "i"))
(Expression
(IntLiteral "5"))))
(SimpleStatement
(IncStatement
(Expression
(Identifier "i")))))))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList)))))
(Statement
(ContinueStatement
(LabelName "loop2"))))
(ForClause
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "i"))
(Expression
(IntLiteral "10"))))
(SimpleStatement
(IncStatement
(Expression
(Identifier "i")))))))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList)))))
(Statement
(ContinueStatement)))
(ForClause)))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList
(Expression
(Identifier "x")))))))
(Statement
(BreakStatement)))
(RangeClause
(ExpressionList
(Expression
(Identifier "x")))
(Expression
(Identifier "y")))))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "g"))
(ArgumentList
(Expression
(Identifier "i"))
(Expression
(Identifier "s"))))))))
(RangeClause
(ExpressionList
(Expression
(Identifier "i"))
(Expression
(Identifier "s")))
(Expression
(Identifier "a")))))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "h"))
(ArgumentList
(Expression
(Identifier "key"))
(Expression
(Identifier "val"))))))))
(RangeClause
(ExpressionList
(Expression
(Identifier "key"))
(Expression
(Identifier "val")))
(Expression
(Identifier "m")))))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "i"))
(ArgumentList))))))
(Expression
(BinaryExpression
(Token)
(Expression
(IntLiteral "1"))
(Expression
(IntLiteral "2"))))))
(Statement
(ForStatement
(Block)
(RangeClause
(Expression
(Identifier "ch"))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,99 +1,159 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(For
(Empty)
(Empty)
(Empty)
(Statements
(Call
(Identifier)
(Statements)
(Empty))
(Goto
(Identifier))))
(ForEach
(Identifier)
(Identifier)
(Statements
(Call
(Identifier)
(Statements)
(Empty))
(Break
(Identifier))))
(For
(Empty)
(Empty)
(Empty)
(Statements
(Call
(Identifier)
(Statements)
(Empty))
(Continue
(Identifier))))
(For
(LessThan
(Identifier)
(Integer))
(PostIncrement
(Identifier))
(Empty)
(Statements
(Call
(Identifier)
(Statements)
(Empty))
(Continue
(Empty))))
(For
(Empty)
(Empty)
(Empty)
(Statements
(Call
(Identifier)
(Identifier)
(Empty))
(Break
(Empty))))
(ForEach
(Statements
(Identifier)
(Identifier))
(Identifier)
(Call
(Identifier)
(Statements
(Identifier)
(Identifier))
(Empty)))
(ForEach
(Statements
(Identifier)
(Identifier))
(Identifier)
(Call
(Identifier)
(Statements
(Identifier)
(Identifier))
(Empty)))
(For
(Empty)
(LessThan
(Integer)
(Integer))
(Empty)
(Call
(Identifier)
(Statements)
(Empty)))
(ForEach
(Empty)
(Identifier)
(Statements)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList)))))
(Statement
(GotoStatement
(LabelName "loop"))))
(ForClause)))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList)))))
(Statement
(BreakStatement
(LabelName "loop"))))
(RangeClause
(ExpressionList
(Expression
(Identifier "x")))
(Expression
(Identifier "y")))))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList)))))
(Statement
(ContinueStatement
(LabelName "loop2"))))
(ForClause)))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList)))))
(Statement
(ContinueStatement)))
(ForClause
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "i"))
(Expression
(IntLiteral "10"))))
(SimpleStatement
(IncStatement
(Expression
(Identifier "i")))))))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList
(Expression
(Identifier "x")))))))
(Statement
(BreakStatement)))))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "g"))
(ArgumentList
(Expression
(Identifier "i"))
(Expression
(Identifier "s"))))))))
(RangeClause
(ExpressionList
(Expression
(Identifier "s"))
(Expression
(Identifier "i")))
(Expression
(Identifier "b")))))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "h"))
(ArgumentList
(Expression
(Identifier "k"))
(Expression
(Identifier "v"))))))))
(RangeClause
(ExpressionList
(Expression
(Identifier "k"))
(Expression
(Identifier "v")))
(Expression
(Identifier "m")))))
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "j"))
(ArgumentList))))))
(Expression
(BinaryExpression
(Token)
(Expression
(IntLiteral "2"))
(Expression
(IntLiteral "1"))))))
(Statement
(ForStatement
(Block)
(RangeClause
(Expression
(Identifier "b"))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,53 +1,76 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements))
(Function
(Identifier)
(Statements))
(Function
(Identifier)
(Identifier)
(Statements
(Identifier)
(Identifier))
(Statements
(Identifier)
(Identifier)
(Identifier)
(Identifier))
(Statements))
(Function
(Statements
(Statements
(Identifier))
(Statements
(Identifier)))
(Identifier)
(Statements))
(Function
(Statements
(Statements
(Identifier)
(Identifier))
(Statements
(Identifier)
(Identifier)))
(Identifier)
(Statements))
(Function
(Identifier)
(Identifier)
(Empty))
(Function
(Context
(Comment)
(Empty))
(Identifier)
(Statements
(Identifier)
(Pointer
(Identifier)))
(Statements)))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block)
(Identifier "main")
(ParameterList))
(FunctionDeclaration
(Block)
(Identifier "f1")
(ParameterList))
(FunctionDeclaration
(Block)
(SimpleType
(TypeIdentifier "int"))
(Identifier "f2")
(ParameterList
(ParameterDeclaration
(Identifier "a")
(Type
(SimpleType
(TypeIdentifier "int"))))
(ParameterDeclaration
(Identifier "b")
(Token)
(Identifier "c")
(Token)
(Identifier "d")
(Type
(SimpleType
(TypeIdentifier "string"))))))
(FunctionDeclaration
(Block)
(ParameterList
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "int"))))
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "error")))))
(Identifier "f2")
(ParameterList))
(FunctionDeclaration
(Block)
(ParameterList
(ParameterDeclaration
(Identifier "result")
(Type
(SimpleType
(TypeIdentifier "int"))))
(ParameterDeclaration
(Identifier "err")
(Type
(SimpleType
(TypeIdentifier "error")))))
(Identifier "f2")
(ParameterList))
(FunctionDeclaration
(SimpleType
(TypeIdentifier "bool"))
(Identifier "lockedOSThread")
(ParameterList))
(FunctionDeclaration
(Block)
(Identifier "getcontext")
(ParameterList
(ParameterDeclaration
(Identifier "c")
(Type
(SimpleType
(PointerType
(Type
(SimpleType
(TypeIdentifier "u"))))))))))

View File

@ -1,58 +1,83 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements))
(Function
(Identifier)
(Statements))
(Function
(Identifier)
(Identifier)
(Statements
(Identifier)
(Identifier))
(Statements
(Identifier)
(Identifier)
(Identifier)
(Identifier))
(Statements))
(Function
(Statements
(Statements
(Identifier))
(Statements
(Identifier)))
(Identifier)
(Statements))
(Function
(Statements
(Statements
(Identifier)
(Identifier))
(Statements
(Identifier)
(Identifier)))
(Identifier)
(Statements))
(Function
(Statements)
(Identifier)
(NoOp
(Empty)))
(Function
(Identifier)
(Identifier)
(Empty))
(Function
(Context
(Comment)
(Empty))
(Identifier)
(Statements
(Identifier)
(Pointer
(Identifier)))
(Statements)))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block)
(Identifier "main")
(ParameterList))
(FunctionDeclaration
(Block)
(Identifier "fa")
(ParameterList))
(FunctionDeclaration
(Block)
(SimpleType
(TypeIdentifier "int"))
(Identifier "fb")
(ParameterList
(ParameterDeclaration
(Identifier "a")
(Type
(SimpleType
(TypeIdentifier "int"))))
(ParameterDeclaration
(Identifier "b")
(Token)
(Identifier "c")
(Token)
(Identifier "d")
(Type
(SimpleType
(TypeIdentifier "string"))))))
(FunctionDeclaration
(Block)
(ParameterList
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "int"))))
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "error")))))
(Identifier "fc")
(ParameterList))
(FunctionDeclaration
(Block)
(ParameterList
(ParameterDeclaration
(Identifier "result")
(Type
(SimpleType
(TypeIdentifier "int"))))
(ParameterDeclaration
(Identifier "err")
(Type
(SimpleType
(TypeIdentifier "error")))))
(Identifier "fd")
(ParameterList))
(FunctionDeclaration
(Block
(Statement
(EmptyStatement ";")))
(ParameterList)
(Identifier "fe")
(ParameterList))
(FunctionDeclaration
(SimpleType
(TypeIdentifier "int"))
(Identifier "lockOSThread")
(ParameterList))
(FunctionDeclaration
(Block)
(Identifier "setcontext")
(ParameterList
(ParameterDeclaration
(Identifier "c")
(Type
(SimpleType
(PointerType
(Type
(SimpleType
(TypeIdentifier "u"))))))))))

View File

@ -1,21 +1,37 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Assignment
(Identifier)
(Function
(Statements
(Statements
(Identifier))
(Statements
(Identifier)))
(Empty)
(Statements
(Identifier)
(Identifier))
(Return
(Statements
(Integer)
(Integer)))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(FuncLiteral
(Block
(Statement
(ReturnStatement
(ExpressionList
(Expression
(IntLiteral "1"))
(Expression
(IntLiteral "2"))))))
(ParameterList
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "int"))))
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "int")))))
(ParameterList
(ParameterDeclaration
(Identifier "s")
(Type
(SimpleType
(TypeIdentifier "string"))))))))
(Identifier "s1")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,21 +1,37 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Assignment
(Identifier)
(Function
(Statements
(Statements
(Identifier))
(Statements
(Identifier)))
(Empty)
(Statements
(Identifier)
(Identifier))
(Return
(Statements
(Integer)
(Integer)))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(FuncLiteral
(Block
(Statement
(ReturnStatement
(ExpressionList
(Expression
(IntLiteral "1"))
(Expression
(IntLiteral "2"))))))
(ParameterList
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "string"))))
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "string")))))
(ParameterList
(ParameterDeclaration
(Identifier "b")
(Type
(SimpleType
(TypeIdentifier "int"))))))))
(Identifier "s1")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,24 +1,44 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Type
(Identifier)
(Function
(Statements
(Identifier))
(Identifier)))
(Type
(Identifier)
(Function
(Statements
(Identifier))
(Statements
(Identifier))
(Statements
(Statements
(Identifier))
(Statements
(Identifier))))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "a")
(Type
(SimpleType
(FunctionType
(SimpleType
(TypeIdentifier "int"))
(ParameterList
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "int")))))))))
(TypeSpec
(TypeIdentifier "b")
(Type
(SimpleType
(FunctionType
(ParameterList
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "bool"))))
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "error")))))
(ParameterList
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "int"))))
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "string"))))))))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,25 +1,47 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Type
(Identifier)
(Function
(Statements
(Identifier))
(Identifier)))
(Type
(Identifier)
(Function
(Statements
(Identifier))
(Statements
(Identifier))
(Statements
(Statements
(BidirectionalChannel
(Identifier)))
(Statements
(Identifier))))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "x")
(Type
(SimpleType
(FunctionType
(SimpleType
(TypeIdentifier "string"))
(ParameterList
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "string")))))))))
(TypeSpec
(TypeIdentifier "y")
(Type
(SimpleType
(FunctionType
(ParameterList
(ParameterDeclaration
(Type
(SimpleType
(ChannelType
(Type
(SimpleType
(TypeIdentifier "x")))))))
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "error")))))
(ParameterList
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "string"))))
(ParameterDeclaration
(Type
(SimpleType
(TypeIdentifier "int"))))))))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,20 +1,27 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Defer
(Call
(MemberAccess
(Identifier)
(Identifier))
(Statements)
(Empty)))
(Go
(Call
(MemberAccess
(Identifier)
(Identifier))
(Statements)
(Empty))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(DeferStatement
(Expression
(CallExpression
(Expression
(SelectorExpression
(FieldIdentifier "y")
(Expression
(Identifier "x"))))
(ArgumentList)))))
(Statement
(GoStatement
(Expression
(CallExpression
(Expression
(SelectorExpression
(FieldIdentifier "y")
(Expression
(Identifier "x"))))
(ArgumentList))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,20 +1,27 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Defer
(Call
(MemberAccess
(Identifier)
(Identifier))
(Statements)
(Empty)))
(Go
(Call
(MemberAccess
(Identifier)
(Identifier))
(Statements)
(Empty))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(DeferStatement
(Expression
(CallExpression
(Expression
(SelectorExpression
(FieldIdentifier "b")
(Expression
(Identifier "a"))))
(ArgumentList)))))
(Statement
(GoStatement
(Expression
(CallExpression
(Expression
(SelectorExpression
(FieldIdentifier "d")
(Expression
(Identifier "c"))))
(ArgumentList))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,13 +1,17 @@
(Statements
(Package
(Identifier))
(Statements
(QualifiedImport
(Identifier))
(Import
(TextElement))
(QualifiedImport
(Identifier)))
(Function
(Identifier)
(Statements)))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(ImportDeclaration
(ImportSpecList
(ImportSpec
(InterpretedStringLiteral))
(ImportSpec
(InterpretedStringLiteral)
(Dot "."))
(ImportSpec
(InterpretedStringLiteral)
(PackageIdentifier "alias"))))
(FunctionDeclaration
(Block)
(Identifier "main")
(ParameterList)))

View File

@ -1,13 +1,17 @@
(Statements
(Package
(Identifier))
(Statements
(QualifiedImport
(Identifier))
(Import
(TextElement))
(QualifiedImport
(Identifier)))
(Function
(Identifier)
(Statements)))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(ImportDeclaration
(ImportSpecList
(ImportSpec
(InterpretedStringLiteral))
(ImportSpec
(InterpretedStringLiteral)
(Dot "."))
(ImportSpec
(InterpretedStringLiteral)
(PackageIdentifier "alias"))))
(FunctionDeclaration
(Block)
(Identifier "main")
(ParameterList)))

View File

@ -1,12 +1,19 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Assignment
(Identifier)
(Integer))
(Assignment
(Identifier)
(Integer)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(VarDeclaration
(VarSpec
(ExpressionList
(Expression
(IntLiteral "0")))
(Identifier "zero"))
(VarSpec
(ExpressionList
(Expression
(IntLiteral "1")))
(Identifier "one")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,12 +1,19 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Assignment
(Identifier)
(Integer))
(Assignment
(Identifier)
(Integer)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(VarDeclaration
(VarSpec
(ExpressionList
(Expression
(IntLiteral "0")))
(Identifier "a"))
(VarSpec
(ExpressionList
(Expression
(IntLiteral "1")))
(Identifier "b")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,79 +1,123 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(If
(Statements
(Call
(Identifier)
(Statements)
(Empty)))
(Call
(Identifier)
(Statements)
(Empty))
(Empty))
(If
(Statements
(Assignment
(Identifier)
(Call
(Identifier)
(Statements)
(Empty)))
(Identifier))
(Call
(Identifier)
(Statements)
(Empty))
(Empty))
(If
(Statements
(Call
(Identifier)
(Statements)
(Empty)))
(Call
(Identifier)
(Statements)
(Empty))
(Call
(Identifier)
(Statements)
(Empty)))
(If
(Statements
(Assignment
(Identifier)
(Integer))
(LessThan
(Identifier)
(Integer)))
(Call
(Identifier)
(Statements)
(Empty))
(If
(Statements
(LessThan
(Identifier)
(Integer)))
(Call
(Identifier)
(Statements)
(Empty))
(Context
(Comment)
(If
(Statements
(Call
(Identifier)
(Statements)
(Empty)))
(Call
(Identifier)
(Statements)
(Empty))
(Empty))))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(IfStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "b"))
(ArgumentList))))))
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList)))))
(Statement
(IfStatement
(SimpleStatement
(ShortVarDeclaration
(ExpressionList
(Expression
(Identifier "a")))
(ExpressionList
(Expression
(CallExpression
(Expression
(Identifier "b"))
(ArgumentList))))))
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "d"))
(ArgumentList))))))
(Expression
(Identifier "c"))))
(Statement
(IfStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "c"))
(ArgumentList))))))
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "b"))
(ArgumentList))))))
(Expression
(CallExpression
(Expression
(Identifier "a"))
(ArgumentList)))))
(Statement
(IfStatement
(IfStatement
(IfStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "g"))
(ArgumentList))))))
(Expression
(CallExpression
(Expression
(Identifier "f"))
(ArgumentList))))
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "e"))
(ArgumentList))))))
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "num"))
(Expression
(IntLiteral "10")))))
(SimpleStatement
(ShortVarDeclaration
(ExpressionList
(Expression
(Identifier "num")))
(ExpressionList
(Expression
(IntLiteral "9")))))
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "d"))
(ArgumentList))))))
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "num"))
(Expression
(IntLiteral "0")))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,72 +1,117 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(If
(Statements
(Call
(Identifier)
(Statements)
(Empty)))
(Call
(Identifier)
(Statements)
(Empty))
(Empty))
(If
(Statements
(Assignment
(Identifier)
(Call
(Identifier)
(Statements)
(Empty)))
(Identifier))
(Call
(Identifier)
(Statements)
(Empty))
(Empty))
(If
(Statements
(Call
(Identifier)
(Statements)
(Empty)))
(Call
(Identifier)
(Statements)
(Empty))
(Call
(Identifier)
(Statements)
(Empty)))
(If
(Statements
(Assignment
(Identifier)
(Integer))
(LessThan
(Identifier)
(Integer)))
(Call
(Identifier)
(Statements)
(Empty))
(Context
(Comment)
(If
(Statements
(LessThan
(Identifier)
(Integer)))
(Call
(Identifier)
(Statements)
(Empty))
(Call
(Identifier)
(Statements)
(Empty))))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(IfStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "b"))
(ArgumentList))))))
(Expression
(CallExpression
(Expression
(Identifier "x"))
(ArgumentList)))))
(Statement
(IfStatement
(SimpleStatement
(ShortVarDeclaration
(ExpressionList
(Expression
(Identifier "y")))
(ExpressionList
(Expression
(CallExpression
(Expression
(Identifier "b"))
(ArgumentList))))))
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "d"))
(ArgumentList))))))
(Expression
(Identifier "c"))))
(Statement
(IfStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "c"))
(ArgumentList))))))
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "b"))
(ArgumentList))))))
(Expression
(CallExpression
(Expression
(Identifier "z"))
(ArgumentList)))))
(Statement
(IfStatement
(IfStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "h"))
(ArgumentList))))))
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "g"))
(ArgumentList))))))
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "num"))
(Expression
(IntLiteral "100")))))
(SimpleStatement
(ShortVarDeclaration
(ExpressionList
(Expression
(Identifier "num")))
(ExpressionList
(Expression
(IntLiteral "10")))))
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "f"))
(ArgumentList))))))
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "num"))
(Expression
(IntLiteral "0")))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,12 +1,19 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Assignment
(Identifier)
(Complex))
(Assignment
(Identifier)
(Complex)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(ImaginaryLiteral "01i")))
(Identifier "a"))
(ConstSpec
(ExpressionList
(Expression
(ImaginaryLiteral "1.e+100i")))
(Identifier "b")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,12 +1,19 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Assignment
(Identifier)
(Complex))
(Assignment
(Identifier)
(Complex)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(ImaginaryLiteral "02i")))
(Identifier "a"))
(ConstSpec
(ExpressionList
(Expression
(ImaginaryLiteral "1.e+103i")))
(Identifier "b")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,12 +1,11 @@
(Statements
(Package
(Identifier))
(Statements
(Comment)
(Comment)
(QualifiedImport
(Identifier))
(Comment))
(Function
(Identifier)
(Statements)))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(ImportDeclaration
(ImportSpecList
(ImportSpec
(InterpretedStringLiteral))))
(FunctionDeclaration
(Block)
(Identifier "main")
(ParameterList)))

View File

@ -1,12 +1,11 @@
(Statements
(Package
(Identifier))
(Statements
(Comment)
(Comment)
(QualifiedImport
(Identifier))
(Comment))
(Function
(Identifier)
(Statements)))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(ImportDeclaration
(ImportSpecList
(ImportSpec
(InterpretedStringLiteral))))
(FunctionDeclaration
(Block)
(Identifier "main")
(ParameterList)))

View File

@ -1,10 +1,17 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(PostIncrement
(Identifier))
(PostDecrement
(Identifier)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(SimpleStatement
(IncStatement
(Expression
(Identifier "i")))))
(Statement
(SimpleStatement
(DecStatement
(Expression
(Identifier "j"))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,10 +1,17 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(PostIncrement
(Identifier))
(PostIncrement
(Identifier)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(SimpleStatement
(IncStatement
(Expression
(Identifier "foo")))))
(Statement
(SimpleStatement
(IncStatement
(Expression
(Identifier "x"))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,15 +1,24 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Assignment
(Identifier)
(Integer))
(Assignment
(Identifier)
(Integer))
(Assignment
(Identifier)
(Integer)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(IntLiteral "1")))
(Identifier "a"))
(ConstSpec
(ExpressionList
(Expression
(IntLiteral "2")))
(Identifier "b"))
(ConstSpec
(ExpressionList
(Expression
(IntLiteral "3")))
(Identifier "c")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,15 +1,24 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Assignment
(Identifier)
(Integer))
(Assignment
(Identifier)
(Integer))
(Assignment
(Identifier)
(Integer)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(ConstDeclaration
(ConstSpec
(ExpressionList
(Expression
(IntLiteral "4")))
(Identifier "a"))
(ConstSpec
(ExpressionList
(Expression
(IntLiteral "5")))
(Identifier "b"))
(ConstSpec
(ExpressionList
(Expression
(IntLiteral "6")))
(Identifier "c")))))
(Identifier "main")
(ParameterList)))

View File

@ -1,42 +1,59 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Statements
(Type
(Identifier)
(Interface
(Statements))))
(Statements
(Type
(Identifier)
(Interface
(MemberAccess
(Identifier)
(Identifier)))))
(Statements
(Type
(Identifier)
(Interface
(Statements
(Identifier)
(MemberAccess
(Identifier)
(Identifier))
(MethodSignature
(Identifier)
(Identifier)
(Statements
(Identifier)
(Identifier)))))))
(Context
(Comment)
(Statements
(Type
(Identifier)
(Interface
(MethodSignature
(Empty)
(Identifier)))))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "i1")
(Type
(SimpleType
(InterfaceType
(MethodSpecList)))))))
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "i2")
(Type
(SimpleType
(InterfaceType
(MethodSpecList
(QualifiedType
(TypeIdentifier "Reader")
(PackageIdentifier "io")))))))))
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "i3")
(Type
(SimpleType
(InterfaceType
(MethodSpecList
(TypeIdentifier "i1")
(QualifiedType
(TypeIdentifier "Reader")
(PackageIdentifier "io"))
(MethodSpec
(SimpleType
(TypeIdentifier "error"))
(FieldIdentifier "SomeMethod")
(ParameterList
(ParameterDeclaration
(Identifier "s")
(Type
(SimpleType
(TypeIdentifier "string")))))))))))))
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "OptionA")
(Type
(SimpleType
(InterfaceType
(MethodSpecList
(MethodSpec
(FieldIdentifier "public")
(ParameterList))))))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,42 +1,59 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Statements
(Type
(Identifier)
(Interface
(Statements))))
(Statements
(Type
(Identifier)
(Interface
(MemberAccess
(Identifier)
(Identifier)))))
(Statements
(Type
(Identifier)
(Interface
(Statements
(Identifier)
(MemberAccess
(Identifier)
(Identifier))
(MethodSignature
(Identifier)
(Identifier)
(Statements
(Identifier)
(Identifier)))))))
(Context
(Comment)
(Statements
(Type
(Identifier)
(Interface
(MethodSignature
(Empty)
(Identifier)))))))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "j1")
(Type
(SimpleType
(InterfaceType
(MethodSpecList)))))))
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "j2")
(Type
(SimpleType
(InterfaceType
(MethodSpecList
(QualifiedType
(TypeIdentifier "Reader")
(PackageIdentifier "io")))))))))
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "j3")
(Type
(SimpleType
(InterfaceType
(MethodSpecList
(TypeIdentifier "i1")
(QualifiedType
(TypeIdentifier "Reader")
(PackageIdentifier "io"))
(MethodSpec
(SimpleType
(TypeIdentifier "error"))
(FieldIdentifier "SomeMethod")
(ParameterList
(ParameterDeclaration
(Identifier "s")
(Type
(SimpleType
(TypeIdentifier "string")))))))))))))
(Statement
(TypeDeclaration
(TypeSpec
(TypeIdentifier "OptionB")
(Type
(SimpleType
(InterfaceType
(MethodSpecList
(MethodSpec
(FieldIdentifier "private")
(ParameterList))))))))))
(Identifier "main")
(ParameterList)))

View File

@ -1,38 +1,57 @@
(Statements
(Package
(Identifier))
(Function
(Identifier)
(Statements
(Label
(Identifier)
(NoOp
(Empty)))
(Context
(Comment)
(Label
(Identifier)
(Context
(Comment)
(For
(Assignment
(Identifier)
(Integer))
(LessThan
(Identifier)
(Integer))
(PostIncrement
(Identifier))
(Statements
(Call
(Identifier)
(Identifier)
(Empty))
(Break
(Identifier))
(Context
(Comment)
(Empty)))))))
(Label
(Identifier)
(Empty)))))
(SourceFile
(PackageClause
(PackageIdentifier "main"))
(FunctionDeclaration
(Block
(Statement
(LabeledStatement
(LabelName "L")
(Statement
(EmptyStatement ";"))))
(Statement
(LabeledStatement
(LabelName "L1")
(Statement
(Block
(Statement
(ForStatement
(Block
(Statement
(SimpleStatement
(Expression
(CallExpression
(Expression
(Identifier "println"))
(ArgumentList
(Expression
(Identifier "i")))))))
(Statement
(BreakStatement
(LabelName "L1"))))
(ForClause
(SimpleStatement
(ShortVarDeclaration
(ExpressionList
(Expression
(Identifier "i")))
(ExpressionList
(Expression
(IntLiteral "0")))))
(Expression
(BinaryExpression
(Token)
(Expression
(Identifier "i"))
(Expression
(IntLiteral "10"))))
(SimpleStatement
(IncStatement
(Expression
(Identifier "i")))))))))))
(Statement
(Block
(Statement
(LabeledStatement
(LabelName "insert"))))))
(Identifier "main")
(ParameterList)))

Some files were not shown because too many files have changed in this diff Show More