mirror of
https://github.com/github/semantic.git
synced 2024-11-24 00:42:33 +03:00
Merge remote-tracking branch 'origin/master' into codegen-migration-leftovers
This commit is contained in:
commit
c3279290ae
@ -6,6 +6,7 @@
|
|||||||
|
|
||||||
module Evaluation (benchmarks) where
|
module Evaluation (benchmarks) where
|
||||||
|
|
||||||
|
import Analysis.Project
|
||||||
import Control.Carrier.Parse.Simple
|
import Control.Carrier.Parse.Simple
|
||||||
import Data.Abstract.Evaluatable
|
import Data.Abstract.Evaluatable
|
||||||
import Data.Bifunctor
|
import Data.Bifunctor
|
||||||
@ -13,7 +14,6 @@ import Data.Blob.IO (readBlobFromPath)
|
|||||||
import qualified Data.Duration as Duration
|
import qualified Data.Duration as Duration
|
||||||
import Data.Graph.Algebraic (topologicalSort)
|
import Data.Graph.Algebraic (topologicalSort)
|
||||||
import qualified Data.Language as Language
|
import qualified Data.Language as Language
|
||||||
import Data.Project
|
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
import Gauge.Main
|
import Gauge.Main
|
||||||
import Parsing.Parser
|
import Parsing.Parser
|
||||||
|
@ -9,7 +9,7 @@ import Control.Carrier.Reader
|
|||||||
import Control.Exception (throwIO)
|
import Control.Exception (throwIO)
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Data.Foldable
|
import Data.Foldable
|
||||||
import Data.Language (LanguageMode (..), PerLanguageModes (..))
|
import Data.Language (PerLanguageModes (..), aLaCarteLanguageModes, preciseLanguageModes)
|
||||||
import Gauge
|
import Gauge
|
||||||
import System.FilePath.Glob
|
import System.FilePath.Glob
|
||||||
import qualified System.Path as Path
|
import qualified System.Path as Path
|
||||||
@ -68,28 +68,6 @@ parseSymbolsFilePath ::
|
|||||||
-> m ParseTreeSymbolResponse
|
-> m ParseTreeSymbolResponse
|
||||||
parseSymbolsFilePath languageModes path = readBlob (File.fromPath path) >>= runReader languageModes . parseSymbols . pure @[]
|
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 :: Config.Options
|
||||||
testOptions = defaultOptions
|
testOptions = defaultOptions
|
||||||
{ optionsFailOnWarning = flag FailOnWarning True
|
{ optionsFailOnWarning = flag FailOnWarning True
|
||||||
|
@ -40,6 +40,7 @@ library
|
|||||||
import: common
|
import: common
|
||||||
hs-source-dirs: src
|
hs-source-dirs: src
|
||||||
exposed-modules:
|
exposed-modules:
|
||||||
|
Analysis.Blob
|
||||||
Analysis.Carrier.Env.Monovariant
|
Analysis.Carrier.Env.Monovariant
|
||||||
Analysis.Carrier.Env.Precise
|
Analysis.Carrier.Env.Precise
|
||||||
Analysis.Carrier.Heap.Monovariant
|
Analysis.Carrier.Heap.Monovariant
|
||||||
@ -54,6 +55,7 @@ library
|
|||||||
Analysis.ImportGraph
|
Analysis.ImportGraph
|
||||||
Analysis.Intro
|
Analysis.Intro
|
||||||
Analysis.Name
|
Analysis.Name
|
||||||
|
Analysis.Project
|
||||||
Analysis.Typecheck
|
Analysis.Typecheck
|
||||||
Control.Carrier.Fail.WithLoc
|
Control.Carrier.Fail.WithLoc
|
||||||
build-depends:
|
build-depends:
|
||||||
|
45
semantic-analysis/src/Analysis/Blob.hs
Normal file
45
semantic-analysis/src/Analysis/Blob.hs
Normal 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
|
33
semantic-analysis/src/Analysis/Project.hs
Normal file
33
semantic-analysis/src/Analysis/Project.hs
Normal 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
|
@ -23,13 +23,13 @@ module Language.Python.ScopeGraph
|
|||||||
|
|
||||||
import qualified Analysis.Name as Name
|
import qualified Analysis.Name as Name
|
||||||
import AST.Element
|
import AST.Element
|
||||||
import Control.Effect.Fresh
|
|
||||||
import Control.Effect.ScopeGraph
|
import Control.Effect.ScopeGraph
|
||||||
import qualified Control.Effect.ScopeGraph.Properties.Declaration as Props
|
import qualified Control.Effect.ScopeGraph.Properties.Declaration as Props
|
||||||
import qualified Control.Effect.ScopeGraph.Properties.Function 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
|
||||||
import Control.Lens (set, (^.))
|
import Control.Lens (set, (^.))
|
||||||
import Data.Foldable
|
import Data.Foldable
|
||||||
|
import Data.List.NonEmpty (NonEmpty (..))
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
import qualified Data.ScopeGraph as ScopeGraph
|
import qualified Data.ScopeGraph as ScopeGraph
|
||||||
@ -40,8 +40,8 @@ import GHC.TypeLits
|
|||||||
import qualified Language.Python.AST as Py
|
import qualified Language.Python.AST as Py
|
||||||
import Language.Python.Patterns
|
import Language.Python.Patterns
|
||||||
import Scope.Graph.Convert (Result (..), complete, todo)
|
import Scope.Graph.Convert (Result (..), complete, todo)
|
||||||
import Source.Loc
|
import Source.Loc (Loc)
|
||||||
import Source.Span (span_)
|
import Source.Span (Span, span_)
|
||||||
|
|
||||||
-- This typeclass is internal-only, though it shares the same interface
|
-- This typeclass is internal-only, though it shares the same interface
|
||||||
-- as the one defined in semantic-scope-graph. The somewhat-unconventional
|
-- as the one defined in semantic-scope-graph. The somewhat-unconventional
|
||||||
@ -49,7 +49,7 @@ import Source.Span (span_)
|
|||||||
-- every single Python AST type.
|
-- every single Python AST type.
|
||||||
class (forall a . Show a => Show (t a)) => ToScopeGraph t where
|
class (forall a . Show a => Show (t a)) => ToScopeGraph t where
|
||||||
scopeGraph ::
|
scopeGraph ::
|
||||||
( Has ScopeGraph sig m
|
( ScopeGraphEff sig m
|
||||||
, Monoid (m Result)
|
, Monoid (m Result)
|
||||||
)
|
)
|
||||||
=> t Loc
|
=> t Loc
|
||||||
@ -61,7 +61,7 @@ instance (ToScopeGraph l, ToScopeGraph r) => ToScopeGraph (l :+: r) where
|
|||||||
|
|
||||||
onField ::
|
onField ::
|
||||||
forall (field :: Symbol) syn sig m r .
|
forall (field :: Symbol) syn sig m r .
|
||||||
( Has ScopeGraph sig m
|
( ScopeGraphEff sig m
|
||||||
, HasField field (r Loc) (syn Loc)
|
, HasField field (r Loc) (syn Loc)
|
||||||
, ToScopeGraph syn
|
, ToScopeGraph syn
|
||||||
, Monoid (m Result)
|
, Monoid (m Result)
|
||||||
@ -75,7 +75,7 @@ onField
|
|||||||
onChildren ::
|
onChildren ::
|
||||||
( Traversable t
|
( Traversable t
|
||||||
, ToScopeGraph syn
|
, ToScopeGraph syn
|
||||||
, Has ScopeGraph sig m
|
, ScopeGraphEff sig m
|
||||||
, HasField "extraChildren" (r Loc) (t (syn Loc))
|
, HasField "extraChildren" (r Loc) (t (syn Loc))
|
||||||
, Monoid (m Result)
|
, Monoid (m Result)
|
||||||
)
|
)
|
||||||
@ -86,7 +86,7 @@ onChildren
|
|||||||
. traverse scopeGraph
|
. traverse scopeGraph
|
||||||
. getField @"extraChildren"
|
. getField @"extraChildren"
|
||||||
|
|
||||||
scopeGraphModule :: Has ScopeGraph sig m => Py.Module Loc -> m Result
|
scopeGraphModule :: ScopeGraphEff sig m => Py.Module Loc -> m Result
|
||||||
scopeGraphModule = getAp . scopeGraph
|
scopeGraphModule = getAp . scopeGraph
|
||||||
|
|
||||||
instance ToScopeGraph Py.AssertStatement where scopeGraph = onChildren
|
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.GeneratorExpression where scopeGraph = todo
|
||||||
|
|
||||||
instance ToScopeGraph Py.Identifier where
|
instance ToScopeGraph Py.Identifier where
|
||||||
scopeGraph (Py.Identifier _ name) = do
|
scopeGraph (Py.Identifier ann name) = do
|
||||||
reference name name Props.Reference
|
let refProps = Props.Reference ScopeGraph.Identifier ScopeGraph.Default (ann^.span_ :: Span)
|
||||||
|
newReference (Name.name name) refProps
|
||||||
complete
|
complete
|
||||||
|
|
||||||
instance ToScopeGraph Py.IfStatement where
|
instance ToScopeGraph Py.IfStatement where
|
||||||
@ -229,14 +230,32 @@ instance ToScopeGraph Py.GlobalStatement where scopeGraph = todo
|
|||||||
|
|
||||||
instance ToScopeGraph Py.Integer where scopeGraph = mempty
|
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
|
instance ToScopeGraph Py.ImportFromStatement where
|
||||||
scopeGraph (Py.ImportFromStatement _ [] (L1 (Py.DottedName _ names)) (Just (Py.WildcardImport _ _))) = do
|
scopeGraph (Py.ImportFromStatement _ [] (L1 (Py.DottedName _ names)) (Just (Py.WildcardImport _ _))) = do
|
||||||
let toName (Py.Identifier _ name) = Name.name name
|
let toName (Py.Identifier _ name) = Name.name name
|
||||||
complete <* insertEdge ScopeGraph.Import (toName <$> names)
|
complete <* newEdge ScopeGraph.Import (toName <$> names)
|
||||||
scopeGraph term = todo (show term)
|
scopeGraph impossibleTerm@(Py.ImportFromStatement _ [] (L1 (Py.DottedName _ _)) Nothing) =
|
||||||
|
todo impossibleTerm
|
||||||
|
scopeGraph term = todo term
|
||||||
|
|
||||||
|
|
||||||
instance ToScopeGraph Py.Lambda where scopeGraph = todo
|
instance ToScopeGraph Py.Lambda where scopeGraph = todo
|
||||||
|
@ -11,15 +11,14 @@ import qualified AST.Unmarshal as TS
|
|||||||
import Control.Algebra
|
import Control.Algebra
|
||||||
import Control.Carrier.Lift
|
import Control.Carrier.Lift
|
||||||
import Control.Carrier.Sketch.ScopeGraph
|
import Control.Carrier.Sketch.ScopeGraph
|
||||||
import Control.Effect.ScopeGraph
|
|
||||||
import qualified Control.Effect.ScopeGraph.Properties.Declaration as Props
|
import qualified Control.Effect.ScopeGraph.Properties.Declaration as Props
|
||||||
import qualified Control.Effect.ScopeGraph.Properties.Function 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
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import qualified Data.ByteString as ByteString
|
import qualified Data.ByteString as ByteString
|
||||||
import qualified Data.List.NonEmpty as NonEmpty
|
import qualified Data.List.NonEmpty as NonEmpty
|
||||||
|
import Data.Module (ModuleInfo (..))
|
||||||
import qualified Data.ScopeGraph as ScopeGraph
|
import qualified Data.ScopeGraph as ScopeGraph
|
||||||
import Data.Semilattice.Lower
|
|
||||||
import qualified Language.Python ()
|
import qualified Language.Python ()
|
||||||
import qualified Language.Python as Py (Term)
|
import qualified Language.Python as Py (Term)
|
||||||
import qualified Language.Python.Grammar as TSP
|
import qualified Language.Python.Grammar as TSP
|
||||||
@ -56,9 +55,11 @@ The graph should be
|
|||||||
|
|
||||||
|
|
||||||
runScopeGraph :: ToScopeGraph t => Path.AbsRelFile -> Source.Source -> t Loc -> (ScopeGraph.ScopeGraph Name, Result)
|
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 ScopeGraph sig m) => m Result
|
sampleGraphThing :: ScopeGraphEff sig m => m Result
|
||||||
sampleGraphThing = do
|
sampleGraphThing = do
|
||||||
declare "hello" (Props.Declaration ScopeGraph.Assignment ScopeGraph.Default Nothing (Span (Pos 2 0) (Pos 2 10)))
|
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)))
|
declare "goodbye" (Props.Declaration ScopeGraph.Assignment ScopeGraph.Default Nothing (Span (Pos 3 0) (Pos 3 12)))
|
||||||
@ -76,65 +77,95 @@ assertSimpleAssignment :: HUnit.Assertion
|
|||||||
assertSimpleAssignment = do
|
assertSimpleAssignment = do
|
||||||
let path = "semantic-python/test/fixtures/1-04-toplevel-assignment.py"
|
let path = "semantic-python/test/fixtures/1-04-toplevel-assignment.py"
|
||||||
(result, Complete) <- graphFile path
|
(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
|
HUnit.assertEqual "Should work for simple case" expecto result
|
||||||
|
|
||||||
expectedReference :: (Has ScopeGraph sig m) => m Result
|
|
||||||
expectedReference = do
|
|
||||||
declare "x" (Props.Declaration ScopeGraph.Assignment ScopeGraph.Default Nothing (Span (Pos 0 0) (Pos 0 5)))
|
|
||||||
reference "x" "x" Props.Reference
|
|
||||||
pure Complete
|
|
||||||
|
|
||||||
assertSimpleReference :: HUnit.Assertion
|
assertSimpleReference :: HUnit.Assertion
|
||||||
assertSimpleReference = do
|
assertSimpleReference = do
|
||||||
let path = "semantic-python/test/fixtures/5-01-simple-reference.py"
|
let path = "semantic-python/test/fixtures/5-01-simple-reference.py"
|
||||||
(result, Complete) <- graphFile path
|
(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
|
HUnit.assertEqual "Should work for simple case" expecto result
|
||||||
|
|
||||||
expectedLexicalScope :: (Has ScopeGraph sig m) => m Result
|
expectedReference :: ScopeGraphEff sig m => m Result
|
||||||
expectedLexicalScope = do
|
expectedReference = do
|
||||||
_ <- declareFunction (Just $ Name.name "foo") (Props.Function ScopeGraph.Function (Span (Pos 0 0) (Pos 1 24)))
|
declare "x" (Props.Declaration ScopeGraph.Assignment ScopeGraph.Default Nothing (Span (Pos 0 0) (Pos 0 5)))
|
||||||
reference "foo" "foo" Props.Reference {}
|
let refProperties = Props.Reference ScopeGraph.Identifier ScopeGraph.Default (Span (Pos 1 0) (Pos 1 1))
|
||||||
|
newReference "x" refProperties
|
||||||
pure Complete
|
pure Complete
|
||||||
|
|
||||||
expectedFunctionArg :: (Has ScopeGraph sig m) => m Result
|
expectedQualifiedImport :: ScopeGraphEff sig m => m Result
|
||||||
expectedFunctionArg = do
|
expectedQualifiedImport = do
|
||||||
(_, associatedScope) <- declareFunction (Just $ Name.name "foo") (Props.Function ScopeGraph.Function (Span (Pos 0 0) (Pos 1 12)))
|
newEdge ScopeGraph.Import (NonEmpty.fromList ["cheese", "ints"])
|
||||||
withScope associatedScope $ do
|
|
||||||
declare "x" (Props.Declaration ScopeGraph.Identifier ScopeGraph.Default Nothing lowerBound)
|
let refProperties = Props.Reference ScopeGraph.Identifier ScopeGraph.Default (Span (Pos 0 7) (Pos 0 13))
|
||||||
reference "x" "x" Props.Reference
|
newReference (Name.name "cheese") refProperties
|
||||||
pure ()
|
|
||||||
reference "foo" "foo" Props.Reference
|
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
|
pure Complete
|
||||||
|
|
||||||
expectedImportHole :: (Has ScopeGraph sig m) => m Result
|
expectedImportHole :: ScopeGraphEff sig m => m Result
|
||||||
expectedImportHole = do
|
expectedImportHole = do
|
||||||
insertEdge ScopeGraph.Import (NonEmpty.fromList ["cheese", "ints"])
|
newEdge ScopeGraph.Import (NonEmpty.fromList ["cheese", "ints"])
|
||||||
pure Complete
|
pure Complete
|
||||||
|
|
||||||
assertLexicalScope :: HUnit.Assertion
|
assertLexicalScope :: HUnit.Assertion
|
||||||
assertLexicalScope = do
|
assertLexicalScope = do
|
||||||
let path = "semantic-python/test/fixtures/5-02-simple-function.py"
|
let path = "semantic-python/test/fixtures/5-02-simple-function.py"
|
||||||
|
let info = ModuleInfo path "Python" mempty
|
||||||
(graph, _) <- graphFile path
|
(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
|
(expecto, Complete) -> HUnit.assertEqual "Should work for simple case" expecto graph
|
||||||
(_, Todo msg) -> HUnit.assertFailure ("Failed to complete:" <> show msg)
|
(_, 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 :: HUnit.Assertion
|
||||||
assertFunctionArg = do
|
assertFunctionArg = do
|
||||||
let path = "semantic-python/test/fixtures/5-03-function-argument.py"
|
let path = "semantic-python/test/fixtures/5-03-function-argument.py"
|
||||||
(graph, _) <- graphFile path
|
(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
|
(expecto, Complete) -> HUnit.assertEqual "Should work for simple case" expecto graph
|
||||||
(_, Todo msg) -> HUnit.assertFailure ("Failed to complete:" <> show msg)
|
(_, 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 :: HUnit.Assertion
|
||||||
assertImportHole = do
|
assertImportHole = do
|
||||||
let path = "semantic-python/test/fixtures/cheese/6-01-imports.py"
|
let path = "semantic-python/test/fixtures/cheese/6-01-imports.py"
|
||||||
(graph, _) <- graphFile path
|
(graph, _) <- graphFile path
|
||||||
case run (runSketch Nothing expectedImportHole) of
|
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
|
(expecto, Complete) -> HUnit.assertEqual "Should work for simple case" expecto graph
|
||||||
(_, Todo msg) -> HUnit.assertFailure ("Failed to complete:" <> show msg)
|
(_, Todo msg) -> HUnit.assertFailure ("Failed to complete:" <> show msg)
|
||||||
|
|
||||||
@ -159,5 +190,6 @@ main = do
|
|||||||
],
|
],
|
||||||
Tasty.testGroup "imports" [
|
Tasty.testGroup "imports" [
|
||||||
HUnit.testCase "simple function argument" assertImportHole
|
HUnit.testCase "simple function argument" assertImportHole
|
||||||
|
, HUnit.testCase "qualified imports" assertQualifiedImport
|
||||||
]
|
]
|
||||||
]
|
]
|
||||||
|
1
semantic-python/test/fixtures/cheese/6-01-qualified-imports.py
vendored
Normal file
1
semantic-python/test/fixtures/cheese/6-01-qualified-imports.py
vendored
Normal file
@ -0,0 +1 @@
|
|||||||
|
import cheese.ints
|
@ -10,115 +10,46 @@
|
|||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
|
{-# OPTIONS_GHC -fprint-expanded-synonyms #-}
|
||||||
|
|
||||||
-- | This carrier interprets the Sketch effect, keeping track of
|
-- | This carrier interprets the Sketch effect, keeping track of
|
||||||
-- the current scope and in-progress graph internally.
|
-- the current scope and in-progress graph internally.
|
||||||
module Control.Carrier.Sketch.ScopeGraph
|
module Control.Carrier.Sketch.ScopeGraph
|
||||||
( SketchC (..)
|
( SketchC
|
||||||
, runSketch
|
, runSketch
|
||||||
, module Control.Effect.ScopeGraph
|
, module Control.Effect.ScopeGraph
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Analysis.Name (Name)
|
import Analysis.Name (Name)
|
||||||
import qualified Analysis.Name as Name
|
import qualified Analysis.Name as Name
|
||||||
import Control.Algebra
|
|
||||||
import Control.Carrier.Fresh.Strict
|
import Control.Carrier.Fresh.Strict
|
||||||
import Control.Carrier.Reader
|
import Control.Carrier.Reader
|
||||||
import Control.Carrier.State.Strict
|
import Control.Carrier.State.Strict
|
||||||
import Control.Effect.ScopeGraph (ScopeGraphEff (..))
|
import Control.Effect.ScopeGraph
|
||||||
import qualified Control.Effect.ScopeGraph.Properties.Declaration as Props
|
import Data.Module (ModuleInfo)
|
||||||
import Control.Monad.IO.Class
|
|
||||||
import Data.Bifunctor
|
|
||||||
import qualified Data.List.NonEmpty as NonEmpty
|
|
||||||
import Data.Module
|
|
||||||
import Data.ScopeGraph (ScopeGraph)
|
|
||||||
import qualified Data.ScopeGraph as ScopeGraph
|
import qualified Data.ScopeGraph as ScopeGraph
|
||||||
import Data.Semilattice.Lower
|
import Data.Semilattice.Lower
|
||||||
import Source.Span
|
|
||||||
import qualified System.Path as Path
|
|
||||||
|
|
||||||
-- | The state type used to keep track of the in-progress graph and
|
type SketchC addr m
|
||||||
-- positional/contextual information. The name "sketchbook" is meant
|
= StateC (ScopeGraph Name)
|
||||||
-- to invoke an in-progress, concealed work, as well as the
|
( StateC Name
|
||||||
-- "sketching" of a graph.
|
( ReaderC Name
|
||||||
data Sketchbook = Sketchbook
|
( ReaderC ModuleInfo
|
||||||
{ sGraph :: ScopeGraph Name
|
( FreshC m
|
||||||
, 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 (ScopeGraphEff :+: Reader Name :+: Fresh :+: sig) (SketchC Name m) where
|
|
||||||
alg (L (Declare n props k)) = do
|
|
||||||
Sketchbook old current <- SketchC (get @Sketchbook)
|
|
||||||
let Props.Declaration kind relation associatedScope span = props
|
|
||||||
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 (L (InsertEdge label address k)) = do
|
|
||||||
Sketchbook old current <- SketchC get
|
|
||||||
let new = ScopeGraph.addImportEdge label (NonEmpty.toList address) current old
|
|
||||||
SketchC (put (Sketchbook new current))
|
|
||||||
k ()
|
|
||||||
|
|
||||||
alg (R (L a)) = case a of
|
|
||||||
Ask k -> SketchC (gets sCurrentScope) >>= k
|
|
||||||
Local fn go k -> do
|
|
||||||
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 ::
|
runSketch ::
|
||||||
(Functor m)
|
(Functor m)
|
||||||
=> Maybe Path.AbsRelFile
|
=> ModuleInfo
|
||||||
-> SketchC Name m a
|
-> SketchC Name m a
|
||||||
-> m (ScopeGraph Name, a)
|
-> m (ScopeGraph Name, a)
|
||||||
runSketch _rootpath (SketchC go)
|
runSketch info go
|
||||||
= evalFresh 1
|
= evalFresh 0
|
||||||
. fmap (first sGraph)
|
. runReader @ModuleInfo info
|
||||||
. runState lowerBound
|
. runReader @Name rootname
|
||||||
|
. evalState @Name rootname
|
||||||
|
. runState @(ScopeGraph Name) initialGraph
|
||||||
$ go
|
$ go
|
||||||
|
where
|
||||||
|
rootname = Name.nameI 0
|
||||||
|
initialGraph = ScopeGraph.insertScope rootname lowerBound lowerBound
|
||||||
|
@ -1,8 +1,10 @@
|
|||||||
{-# LANGUAGE AllowAmbiguousTypes #-}
|
{-# LANGUAGE AllowAmbiguousTypes #-}
|
||||||
|
{-# LANGUAGE ConstraintKinds #-}
|
||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
{-# LANGUAGE DeriveAnyClass #-}
|
{-# LANGUAGE DeriveAnyClass #-}
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
{-# LANGUAGE DuplicateRecordFields #-}
|
{-# LANGUAGE DuplicateRecordFields #-}
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TypeApplications #-}
|
{-# LANGUAGE TypeApplications #-}
|
||||||
@ -13,11 +15,12 @@
|
|||||||
-- physically sketching the hierarchical outline of a graph.
|
-- physically sketching the hierarchical outline of a graph.
|
||||||
module Control.Effect.ScopeGraph
|
module Control.Effect.ScopeGraph
|
||||||
( ScopeGraph
|
( ScopeGraph
|
||||||
, ScopeGraphEff (..)
|
, ScopeGraphEff
|
||||||
, declare
|
, declare
|
||||||
-- Scope Manipulation
|
-- Scope Manipulation
|
||||||
, currentScope
|
, currentScope
|
||||||
, insertEdge
|
, newEdge
|
||||||
|
, newReference
|
||||||
, newScope
|
, newScope
|
||||||
, withScope
|
, withScope
|
||||||
, declareFunction
|
, declareFunction
|
||||||
@ -31,47 +34,133 @@ import qualified Analysis.Name as Name
|
|||||||
import Control.Algebra
|
import Control.Algebra
|
||||||
import Control.Effect.Fresh
|
import Control.Effect.Fresh
|
||||||
import Control.Effect.Reader
|
import Control.Effect.Reader
|
||||||
|
import Control.Lens
|
||||||
import Data.List.NonEmpty
|
import Data.List.NonEmpty
|
||||||
import Data.Map.Strict (Map)
|
import Data.Map.Strict (Map)
|
||||||
import qualified Data.Map.Strict as Map
|
import qualified Data.Map.Strict as Map
|
||||||
|
import qualified Data.Module as Module
|
||||||
import qualified Data.ScopeGraph as ScopeGraph
|
import qualified Data.ScopeGraph as ScopeGraph
|
||||||
|
import Data.Semilattice.Lower
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import GHC.Generics (Generic, Generic1)
|
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.Declaration as Props
|
||||||
import qualified Control.Effect.ScopeGraph.Properties.Function 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
|
||||||
|
import qualified Control.Effect.ScopeGraph.Properties.Reference as Props.Reference
|
||||||
|
import Control.Effect.State
|
||||||
|
|
||||||
type ScopeGraph
|
-- | Extract the 'Just' of a 'Maybe' in an 'Applicative' context or, given 'Nothing', run the provided action.
|
||||||
= ScopeGraphEff
|
maybeM :: Applicative f => f a -> Maybe a -> f a
|
||||||
:+: Fresh
|
maybeM f = maybe f pure
|
||||||
:+: Reader Name
|
{-# INLINE maybeM #-}
|
||||||
|
|
||||||
data ScopeGraphEff m k =
|
type ScopeGraphEff sig m
|
||||||
Declare Name Props.Declaration (() -> m k)
|
= ( Has (State (ScopeGraph Name)) sig m
|
||||||
| Reference Text Text Props.Reference (() -> m k)
|
, Has (State Name) sig m
|
||||||
| NewScope (Map ScopeGraph.EdgeLabel [Name]) (Name -> m k)
|
, Has (Reader Name) sig m
|
||||||
| InsertEdge ScopeGraph.EdgeLabel (NonEmpty Name) (() -> m k)
|
, Has (Reader Module.ModuleInfo) sig m
|
||||||
deriving (Generic, Generic1, HFunctor, Effect)
|
, Has Fresh sig m
|
||||||
|
)
|
||||||
|
|
||||||
currentScope :: Has (Reader Name) sig m => m Name
|
graphInProgress :: ScopeGraphEff sig m => m (ScopeGraph Name)
|
||||||
|
graphInProgress = get
|
||||||
|
|
||||||
|
currentScope :: ScopeGraphEff sig m => m Name
|
||||||
currentScope = ask
|
currentScope = ask
|
||||||
|
|
||||||
declare :: forall sig m . (Has ScopeGraph sig m) => Name -> Props.Declaration -> m ()
|
withScope :: ScopeGraphEff sig m
|
||||||
declare n props = send (Declare n props pure)
|
=> 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.
|
-- | Establish a reference to a prior declaration.
|
||||||
reference :: forall sig m . (Has ScopeGraph sig m) => Text -> Text -> Props.Reference -> m ()
|
reference :: forall sig m . ScopeGraphEff sig m => Text -> Text -> Props.Reference -> m ()
|
||||||
reference n decl props = send (Reference n decl props pure)
|
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 . Has ScopeGraph sig m => Map ScopeGraph.EdgeLabel [Name] -> m Name
|
newScope :: forall sig m . ScopeGraphEff sig m => Map ScopeGraph.EdgeLabel [Name] -> m Name
|
||||||
newScope edges = send (NewScope edges pure)
|
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.
|
-- | Takes an edge label and a list of names and inserts an import edge to a hole.
|
||||||
insertEdge :: Has ScopeGraph sig m => ScopeGraph.EdgeLabel -> NonEmpty Name -> m ()
|
newEdge :: ScopeGraphEff sig m => ScopeGraph.EdgeLabel -> NonEmpty Name -> m ()
|
||||||
insertEdge label targets = send (InsertEdge label targets pure)
|
newEdge label address = do
|
||||||
|
current <- currentScope
|
||||||
|
old <- graphInProgress
|
||||||
|
let new = ScopeGraph.addImportEdge label (toList address) current old
|
||||||
|
put new
|
||||||
|
|
||||||
declareFunction :: forall sig m . (Has ScopeGraph sig m) => Maybe Name -> Props.Function -> m (Name, Name)
|
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
|
declareFunction name (Props.Function kind span) = do
|
||||||
currentScope' <- currentScope
|
currentScope' <- currentScope
|
||||||
let lexicalEdges = Map.singleton ScopeGraph.Lexical [ currentScope' ]
|
let lexicalEdges = Map.singleton ScopeGraph.Lexical [ currentScope' ]
|
||||||
@ -84,7 +173,7 @@ declareFunction name (Props.Function kind span) = do
|
|||||||
}
|
}
|
||||||
pure (name', associatedScope)
|
pure (name', associatedScope)
|
||||||
|
|
||||||
declareMaybeName :: Has ScopeGraph sig m
|
declareMaybeName :: ScopeGraphEff sig m
|
||||||
=> Maybe Name
|
=> Maybe Name
|
||||||
-> Props.Declaration
|
-> Props.Declaration
|
||||||
-> m Name
|
-> m Name
|
||||||
@ -94,9 +183,3 @@ declareMaybeName maybeName props = do
|
|||||||
_ -> do
|
_ -> do
|
||||||
name <- Name.gensym
|
name <- Name.gensym
|
||||||
name <$ declare name (props { Props.relation = ScopeGraph.Gensym })
|
name <$ declare name (props { Props.relation = ScopeGraph.Gensym })
|
||||||
|
|
||||||
withScope :: Has ScopeGraph sig m
|
|
||||||
=> Name
|
|
||||||
-> m a
|
|
||||||
-> m a
|
|
||||||
withScope scope = local (const scope)
|
|
||||||
|
@ -1,3 +1,7 @@
|
|||||||
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
{-# LANGUAGE TypeApplications #-}
|
||||||
|
|
||||||
-- | The 'Declaration' record type is used by the 'Control.Effect.Sketch' module to keep
|
-- | 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.
|
-- 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
|
-- It is currently unused, but will possess more fields in the future as scope graph
|
||||||
@ -6,4 +10,18 @@ module Control.Effect.ScopeGraph.Properties.Reference
|
|||||||
( Reference (..)
|
( Reference (..)
|
||||||
) where
|
) 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
|
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_ #-}
|
||||||
|
@ -29,6 +29,8 @@ import Scope.Scope
|
|||||||
import Scope.Types
|
import Scope.Types
|
||||||
import Source.Span
|
import Source.Span
|
||||||
|
|
||||||
|
newtype CurrentScope address = CurrentScope { unCurrentScope :: address }
|
||||||
|
|
||||||
newtype ScopeGraph scope = ScopeGraph { unScopeGraph :: Map scope (Scope scope) }
|
newtype ScopeGraph scope = ScopeGraph { unScopeGraph :: Map scope (Scope scope) }
|
||||||
deriving (Eq, Ord, Show)
|
deriving (Eq, Ord, Show)
|
||||||
|
|
||||||
@ -131,6 +133,12 @@ insertReference ref moduleInfo span kind path scope = scope { references = Map.a
|
|||||||
Nothing -> pure ([ ReferenceInfo span kind moduleInfo ], path)
|
Nothing -> pure ([ ReferenceInfo span kind moduleInfo ], path)
|
||||||
Just (refInfos, path) -> pure (ReferenceInfo span kind moduleInfo : refInfos, path)) ref (references scope) }
|
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 :: Ord scopeAddress => Name -> scopeAddress -> ScopeGraph scopeAddress -> Maybe (Info scopeAddress, Position)
|
||||||
lookupDeclaration name scope g = do
|
lookupDeclaration name scope g = do
|
||||||
dataSeq <- ddataOfScope scope g
|
dataSeq <- ddataOfScope scope g
|
||||||
|
@ -20,7 +20,7 @@ import Source.Loc
|
|||||||
|
|
||||||
class Typeable t => ToScopeGraph t where
|
class Typeable t => ToScopeGraph t where
|
||||||
scopeGraph ::
|
scopeGraph ::
|
||||||
( Has ScopeGraph sig m
|
( ScopeGraphEff sig m
|
||||||
)
|
)
|
||||||
=> t Loc
|
=> t Loc
|
||||||
-> m Result
|
-> m Result
|
||||||
|
@ -160,7 +160,6 @@ library
|
|||||||
, Data.Language
|
, Data.Language
|
||||||
, Data.Map.Monoidal
|
, Data.Map.Monoidal
|
||||||
, Data.Maybe.Exts
|
, Data.Maybe.Exts
|
||||||
, Data.Project
|
|
||||||
, Data.Quieterm
|
, Data.Quieterm
|
||||||
, Data.Semigroup.App
|
, Data.Semigroup.App
|
||||||
, Data.Scientific.Exts
|
, Data.Scientific.Exts
|
||||||
|
@ -5,15 +5,12 @@
|
|||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE RecordWildCards #-}
|
{-# LANGUAGE RecordWildCards #-}
|
||||||
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
|
||||||
|
-- | Semantic-specific functionality for blob handling.
|
||||||
module Data.Blob
|
module Data.Blob
|
||||||
( Blob(..)
|
( Blobs(..)
|
||||||
, Blobs(..)
|
|
||||||
, blobLanguage
|
|
||||||
, NoLanguageForBlob (..)
|
, NoLanguageForBlob (..)
|
||||||
, blobPath
|
|
||||||
, decodeBlobs
|
, decodeBlobs
|
||||||
, nullBlob
|
|
||||||
, fromSource
|
|
||||||
, moduleForBlob
|
, moduleForBlob
|
||||||
, noLanguageForBlob
|
, noLanguageForBlob
|
||||||
, BlobPair
|
, BlobPair
|
||||||
@ -23,10 +20,11 @@ module Data.Blob
|
|||||||
, languageTagForBlobPair
|
, languageTagForBlobPair
|
||||||
, pathForBlobPair
|
, pathForBlobPair
|
||||||
, pathKeyForBlobPair
|
, pathKeyForBlobPair
|
||||||
|
, module Analysis.Blob
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
|
||||||
import Analysis.File (File (..))
|
import Analysis.Blob
|
||||||
import Control.Effect.Error
|
import Control.Effect.Error
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
@ -39,44 +37,12 @@ import Data.Maybe.Exts
|
|||||||
import Data.Module
|
import Data.Module
|
||||||
import GHC.Generics (Generic)
|
import GHC.Generics (Generic)
|
||||||
import Source.Language as Language
|
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.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] }
|
newtype Blobs a = Blobs { blobs :: [a] }
|
||||||
deriving (Generic, FromJSON)
|
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 :: BL.ByteString -> Either String [Blob]
|
||||||
decodeBlobs = fmap blobs <$> eitherDecode
|
decodeBlobs = fmap blobs <$> eitherDecode
|
||||||
|
|
||||||
|
@ -7,19 +7,49 @@ module Data.Blob.IO
|
|||||||
, readBlobFromPath
|
, readBlobFromPath
|
||||||
, readBlobsFromDir
|
, readBlobsFromDir
|
||||||
, readFilePair
|
, readFilePair
|
||||||
|
, readProjectFromPaths
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Analysis.Blob
|
||||||
import Analysis.File as File
|
import Analysis.File as File
|
||||||
|
import Analysis.Project
|
||||||
import qualified Control.Concurrent.Async as Async
|
import qualified Control.Concurrent.Async as Async
|
||||||
import Control.Monad.IO.Class
|
import Control.Monad.IO.Class
|
||||||
import Data.Blob
|
import Data.Blob
|
||||||
import qualified Data.ByteString as B
|
import qualified Data.ByteString as B
|
||||||
import Data.Language
|
import Data.Language
|
||||||
import Data.Maybe.Exts
|
import Data.Maybe.Exts
|
||||||
|
import Data.Semilattice.Lower
|
||||||
import Semantic.IO
|
import Semantic.IO
|
||||||
import qualified Source.Source as Source
|
import qualified Source.Source as Source
|
||||||
import qualified System.Path as Path
|
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'.
|
-- | Read a utf8-encoded file to a 'Blob'.
|
||||||
readBlobFromFile :: MonadIO m => File Language -> m (Maybe Blob)
|
readBlobFromFile :: MonadIO m => File Language -> m (Maybe Blob)
|
||||||
readBlobFromFile (File (Path.toString -> "/dev/null") _ _) = pure Nothing
|
readBlobFromFile (File (Path.toString -> "/dev/null") _ _) = pure Nothing
|
||||||
|
@ -3,6 +3,8 @@ module Data.Language
|
|||||||
, LanguageMode(..)
|
, LanguageMode(..)
|
||||||
, PerLanguageModes(..)
|
, PerLanguageModes(..)
|
||||||
, defaultLanguageModes
|
, defaultLanguageModes
|
||||||
|
, preciseLanguageModes
|
||||||
|
, aLaCarteLanguageModes
|
||||||
, codeNavLanguages
|
, codeNavLanguages
|
||||||
, supportedExts
|
, supportedExts
|
||||||
) where
|
) where
|
||||||
@ -36,7 +38,10 @@ data PerLanguageModes = PerLanguageModes
|
|||||||
deriving (Eq, Ord, Show)
|
deriving (Eq, Ord, Show)
|
||||||
|
|
||||||
defaultLanguageModes :: PerLanguageModes
|
defaultLanguageModes :: PerLanguageModes
|
||||||
defaultLanguageModes = PerLanguageModes
|
defaultLanguageModes = preciseLanguageModes
|
||||||
|
|
||||||
|
aLaCarteLanguageModes :: PerLanguageModes
|
||||||
|
aLaCarteLanguageModes = PerLanguageModes
|
||||||
{ pythonMode = ALaCarte
|
{ pythonMode = ALaCarte
|
||||||
, rubyMode = ALaCarte
|
, rubyMode = ALaCarte
|
||||||
, goMode = ALaCarte
|
, goMode = ALaCarte
|
||||||
@ -46,6 +51,17 @@ defaultLanguageModes = PerLanguageModes
|
|||||||
, jsxMode = ALaCarte
|
, jsxMode = ALaCarte
|
||||||
}
|
}
|
||||||
|
|
||||||
|
preciseLanguageModes :: PerLanguageModes
|
||||||
|
preciseLanguageModes = PerLanguageModes
|
||||||
|
{ pythonMode = Precise
|
||||||
|
, rubyMode = Precise
|
||||||
|
, goMode = Precise
|
||||||
|
, typescriptMode = Precise
|
||||||
|
, tsxMode = Precise
|
||||||
|
, javascriptMode = Precise
|
||||||
|
, jsxMode = Precise
|
||||||
|
}
|
||||||
|
|
||||||
data LanguageMode
|
data LanguageMode
|
||||||
= ALaCarte
|
= ALaCarte
|
||||||
| Precise
|
| Precise
|
||||||
|
@ -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
|
|
@ -3,6 +3,7 @@
|
|||||||
module Semantic.CLI (main) where
|
module Semantic.CLI (main) where
|
||||||
|
|
||||||
import qualified Analysis.File as File
|
import qualified Analysis.File as File
|
||||||
|
import Analysis.Project
|
||||||
import qualified Control.Carrier.Parse.Measured as Parse
|
import qualified Control.Carrier.Parse.Measured as Parse
|
||||||
import Control.Carrier.Reader
|
import Control.Carrier.Reader
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
@ -15,7 +16,6 @@ import Data.Handle
|
|||||||
import qualified Data.Language as Language
|
import qualified Data.Language as Language
|
||||||
import Data.List (intercalate)
|
import Data.List (intercalate)
|
||||||
import Data.Maybe.Exts
|
import Data.Maybe.Exts
|
||||||
import Data.Project
|
|
||||||
import Options.Applicative hiding (style)
|
import Options.Applicative hiding (style)
|
||||||
import Semantic.Api hiding (File)
|
import Semantic.Api hiding (File)
|
||||||
import Semantic.Config
|
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"))
|
diffCommand = command "diff" (info diffArgumentsParser (progDesc "Compute changes between paths"))
|
||||||
where
|
where
|
||||||
diffArgumentsParser = do
|
diffArgumentsParser = do
|
||||||
languageModes <- languageModes
|
|
||||||
renderer <- flag (parseDiffBuilder DiffSExpression) (parseDiffBuilder DiffSExpression) (long "sexpression" <> help "Output s-expression diff tree (default)")
|
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 DiffJSONTree) (long "json" <> help "Output JSON diff trees")
|
||||||
<|> flag' (parseDiffBuilder DiffJSONGraph) (long "json-graph" <> 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 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)")
|
<|> 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)
|
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 :: Mod CommandFields (Parse.ParseC Task.TaskC Builder)
|
||||||
parseCommand = command "parse" (info parseArgumentsParser (progDesc "Generate parse trees for path(s)"))
|
parseCommand = command "parse" (info parseArgumentsParser (progDesc "Generate parse trees for path(s)"))
|
||||||
@ -184,7 +183,7 @@ languageModes = Language.PerLanguageModes
|
|||||||
= option auto ( long (shortName <> "-mode")
|
= option auto ( long (shortName <> "-mode")
|
||||||
<> help ("The AST representation to use for " <> fullName <> " sources")
|
<> help ("The AST representation to use for " <> fullName <> " sources")
|
||||||
<> metavar "ALaCarte|Precise"
|
<> metavar "ALaCarte|Precise"
|
||||||
<> value Language.ALaCarte
|
<> value Language.Precise
|
||||||
<> showDefault)
|
<> showDefault)
|
||||||
|
|
||||||
filePathReader :: ReadM (File.File Language.Language)
|
filePathReader :: ReadM (File.File Language.Language)
|
||||||
|
@ -44,6 +44,7 @@ import Analysis.Abstract.Caching.FlowInsensitive
|
|||||||
import Analysis.Abstract.Collecting
|
import Analysis.Abstract.Collecting
|
||||||
import Analysis.Abstract.Graph as Graph
|
import Analysis.Abstract.Graph as Graph
|
||||||
import Analysis.File
|
import Analysis.File
|
||||||
|
import Analysis.Project
|
||||||
import Control.Abstract hiding (String)
|
import Control.Abstract hiding (String)
|
||||||
import Control.Abstract.PythonPackage as PythonPackage
|
import Control.Abstract.PythonPackage as PythonPackage
|
||||||
import Control.Carrier.Fresh.Strict
|
import Control.Carrier.Fresh.Strict
|
||||||
@ -73,7 +74,6 @@ import Data.Language as Language
|
|||||||
import Data.List (find, isPrefixOf)
|
import Data.List (find, isPrefixOf)
|
||||||
import Data.Map (Map)
|
import Data.Map (Map)
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
import Data.Project
|
|
||||||
import Data.Proxy
|
import Data.Proxy
|
||||||
import Data.Text (pack, unpack)
|
import Data.Text (pack, unpack)
|
||||||
import Language.Haskell.HsColour
|
import Language.Haskell.HsColour
|
||||||
|
@ -20,6 +20,7 @@ module Semantic.Resolution
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import Analysis.File as File
|
import Analysis.File as File
|
||||||
|
import Analysis.Project
|
||||||
import Control.Algebra
|
import Control.Algebra
|
||||||
import Control.Monad.IO.Class
|
import Control.Monad.IO.Class
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
@ -30,7 +31,6 @@ import Data.Language
|
|||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
import Data.Map.Strict (Map)
|
import Data.Map.Strict (Map)
|
||||||
import Data.Maybe.Exts
|
import Data.Maybe.Exts
|
||||||
import Data.Project
|
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import GHC.Generics (Generic1)
|
import GHC.Generics (Generic1)
|
||||||
import Semantic.Task.Files
|
import Semantic.Task.Files
|
||||||
|
@ -28,6 +28,7 @@ module Semantic.Task.Files
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import Analysis.File
|
import Analysis.File
|
||||||
|
import Analysis.Project
|
||||||
import Control.Algebra
|
import Control.Algebra
|
||||||
import Control.Effect.Error
|
import Control.Effect.Error
|
||||||
import Control.Exception
|
import Control.Exception
|
||||||
@ -37,7 +38,6 @@ import Data.Blob.IO
|
|||||||
import qualified Data.ByteString.Builder as B
|
import qualified Data.ByteString.Builder as B
|
||||||
import Data.Handle
|
import Data.Handle
|
||||||
import Data.Language
|
import Data.Language
|
||||||
import Data.Project
|
|
||||||
import Prelude hiding (readFile)
|
import Prelude hiding (readFile)
|
||||||
import Semantic.IO
|
import Semantic.IO
|
||||||
import qualified System.IO as IO hiding (withBinaryFile)
|
import qualified System.IO as IO hiding (withBinaryFile)
|
||||||
|
@ -18,6 +18,7 @@ module Semantic.Util
|
|||||||
import Prelude hiding (readFile)
|
import Prelude hiding (readFile)
|
||||||
|
|
||||||
import Analysis.File
|
import Analysis.File
|
||||||
|
import Analysis.Project
|
||||||
import Control.Abstract
|
import Control.Abstract
|
||||||
import Control.Carrier.Fresh.Strict
|
import Control.Carrier.Fresh.Strict
|
||||||
import Control.Carrier.Lift
|
import Control.Carrier.Lift
|
||||||
@ -40,7 +41,6 @@ import Data.Graph.Algebraic (topologicalSort)
|
|||||||
import qualified Data.Language as Language
|
import qualified Data.Language as Language
|
||||||
import Data.List (uncons)
|
import Data.List (uncons)
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Project
|
|
||||||
import Data.Semilattice.Lower
|
import Data.Semilattice.Lower
|
||||||
import Data.Sum
|
import Data.Sum
|
||||||
import Parsing.Parser
|
import Parsing.Parser
|
||||||
|
@ -78,5 +78,5 @@ instance ToSExpression t => GToSExpression (Rec1 t) where
|
|||||||
|
|
||||||
instance (Foldable f, GToSExpression g) => GToSExpression (f :.: g) where
|
instance (Foldable f, GToSExpression g) => GToSExpression (f :.: g) where
|
||||||
gtoSExpression (Comp1 fs) n
|
gtoSExpression (Comp1 fs) n
|
||||||
| null fs = [nl n <> pad n <> "[]"]
|
| null fs = mempty
|
||||||
| otherwise = nl n <> pad n <> "[" : foldMap gtoSExpression fs (n + 1) <> ["]"]
|
| otherwise = foldMap gtoSExpression fs n
|
||||||
|
@ -18,7 +18,7 @@ import Control.Monad
|
|||||||
import Data.Blob
|
import Data.Blob
|
||||||
import Data.Foldable
|
import Data.Foldable
|
||||||
import Data.Int
|
import Data.Int
|
||||||
import Data.Language (LanguageMode (..), PerLanguageModes (..))
|
import Data.Language (LanguageMode (..), PerLanguageModes (..), aLaCarteLanguageModes, preciseLanguageModes)
|
||||||
import Data.List
|
import Data.List
|
||||||
import qualified Data.Text as Text
|
import qualified Data.Text as Text
|
||||||
import Data.Traversable
|
import Data.Traversable
|
||||||
@ -259,28 +259,6 @@ okALaCarteSymbol _ _ = True
|
|||||||
filterALaCarteSymbols :: String -> [Text.Text] -> [Text.Text]
|
filterALaCarteSymbols :: String -> [Text.Text] -> [Text.Text]
|
||||||
filterALaCarteSymbols lang = filter (okALaCarteSymbol lang)
|
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 :: Config.Options
|
||||||
testOptions = defaultOptions
|
testOptions = defaultOptions
|
||||||
{ optionsFailOnWarning = flag FailOnWarning True
|
{ optionsFailOnWarning = flag FailOnWarning True
|
||||||
|
@ -1,30 +1,37 @@
|
|||||||
{-# LANGUAGE DataKinds, FlexibleContexts, MonoLocalBinds, OverloadedStrings, TupleSections, TypeOperators #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE FlexibleContexts #-}
|
||||||
|
{-# LANGUAGE MonoLocalBinds #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE TupleSections #-}
|
||||||
|
{-# LANGUAGE TypeOperators #-}
|
||||||
module Rendering.TOC.Spec (spec) where
|
module Rendering.TOC.Spec (spec) where
|
||||||
|
|
||||||
import Analysis.TOCSummary
|
import Analysis.TOCSummary
|
||||||
import Control.Effect.Parse
|
import Control.Effect.Parse
|
||||||
import Control.Monad.IO.Class
|
import Control.Monad.IO.Class
|
||||||
import Data.Aeson hiding (defaultOptions)
|
import Data.Aeson hiding (defaultOptions)
|
||||||
import Data.Bifunctor
|
import Data.Bifunctor
|
||||||
import Data.Diff
|
import Data.Diff
|
||||||
import Data.Either (isRight)
|
import Data.Either (isRight)
|
||||||
import Data.Sum
|
import Data.Sum
|
||||||
import Data.Term
|
|
||||||
import Data.Text (Text)
|
|
||||||
import Diffing.Interpreter
|
|
||||||
import Prelude
|
|
||||||
import qualified Data.Syntax as Syntax
|
import qualified Data.Syntax as Syntax
|
||||||
import qualified Data.Syntax.Declaration as Declaration
|
import qualified Data.Syntax.Declaration as Declaration
|
||||||
import Rendering.TOC
|
import Data.Term
|
||||||
import Semantic.Api (diffSummaryBuilder, summarizeTerms, summarizeTermParsers)
|
import Data.Text (Text)
|
||||||
import Serializing.Format as Format
|
import Diffing.Interpreter
|
||||||
import Source.Loc
|
import Prelude
|
||||||
import Source.Span
|
import Rendering.TOC
|
||||||
import qualified System.Path as Path
|
import Semantic.Api (diffSummaryBuilder, summarizeTermParsers, summarizeTerms)
|
||||||
|
import Serializing.Format as Format
|
||||||
|
import Source.Loc
|
||||||
|
import Source.Span
|
||||||
import System.Path ((</>))
|
import System.Path ((</>))
|
||||||
|
import qualified System.Path as Path
|
||||||
|
|
||||||
import SpecHelpers
|
import SpecHelpers
|
||||||
|
|
||||||
|
don't :: Applicative m => m a -> m ()
|
||||||
|
don't = const (pure ())
|
||||||
|
|
||||||
spec :: Spec
|
spec :: Spec
|
||||||
spec = do
|
spec = do
|
||||||
@ -135,22 +142,22 @@ spec = do
|
|||||||
describe "diff with ToCDiffRenderer'" $ do
|
describe "diff with ToCDiffRenderer'" $ do
|
||||||
it "produces JSON output" $ do
|
it "produces JSON output" $ do
|
||||||
blobs <- blobsForPaths (Path.relFile "ruby/toc/methods.A.rb") (Path.relFile "ruby/toc/methods.B.rb")
|
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)
|
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")
|
blobs <- blobsForPaths (Path.relFile "ruby/toc/methods.A.rb") (Path.relFile "ruby/toc/methods.X.rb")
|
||||||
output <- runTaskOrDie (runReader defaultLanguageModes (diffSummaryBuilder Format.JSON [blobs]))
|
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)
|
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
|
it "ignores anonymous functions" $ do
|
||||||
blobs <- blobsForPaths (Path.relFile "ruby/toc/lambda.A.rb") (Path.relFile "ruby/toc/lambda.B.rb")
|
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)
|
runBuilder output `shouldBe` ("{\"files\":[{\"path\":\"test/fixtures/ruby/toc/lambda.A.rb -> test/fixtures/ruby/toc/lambda.B.rb\",\"language\":\"Ruby\"}]}\n" :: ByteString)
|
||||||
|
|
||||||
it "summarizes Markdown headings" $ do
|
it "summarizes Markdown headings" $ do
|
||||||
blobs <- blobsForPaths (Path.relFile "markdown/toc/headings.A.md") (Path.relFile "markdown/toc/headings.B.md")
|
blobs <- blobsForPaths (Path.relFile "markdown/toc/headings.A.md") (Path.relFile "markdown/toc/headings.B.md")
|
||||||
output <- runTaskOrDie (runReader defaultLanguageModes (diffSummaryBuilder Format.JSON [blobs]))
|
output <- runTaskOrDie (runReader aLaCarteLanguageModes (diffSummaryBuilder Format.JSON [blobs]))
|
||||||
runBuilder output `shouldBe` ("{\"files\":[{\"path\":\"test/fixtures/markdown/toc/headings.A.md -> test/fixtures/markdown/toc/headings.B.md\",\"language\":\"Markdown\",\"changes\":[{\"category\":\"Heading 1\",\"term\":\"Introduction\",\"span\":{\"start\":{\"line\":1,\"column\":1},\"end\":{\"line\":3,\"column\":16}},\"changeType\":\"REMOVED\"},{\"category\":\"Heading 2\",\"term\":\"Two\",\"span\":{\"start\":{\"line\":5,\"column\":1},\"end\":{\"line\":7,\"column\":4}},\"changeType\":\"MODIFIED\"},{\"category\":\"Heading 3\",\"term\":\"This heading is new\",\"span\":{\"start\":{\"line\":9,\"column\":1},\"end\":{\"line\":11,\"column\":10}},\"changeType\":\"ADDED\"},{\"category\":\"Heading 1\",\"term\":\"Final\",\"span\":{\"start\":{\"line\":13,\"column\":1},\"end\":{\"line\":14,\"column\":4}},\"changeType\":\"ADDED\"}]}]}\n" :: ByteString)
|
runBuilder output `shouldBe` ("{\"files\":[{\"path\":\"test/fixtures/markdown/toc/headings.A.md -> test/fixtures/markdown/toc/headings.B.md\",\"language\":\"Markdown\",\"changes\":[{\"category\":\"Heading 1\",\"term\":\"Introduction\",\"span\":{\"start\":{\"line\":1,\"column\":1},\"end\":{\"line\":3,\"column\":16}},\"changeType\":\"REMOVED\"},{\"category\":\"Heading 2\",\"term\":\"Two\",\"span\":{\"start\":{\"line\":5,\"column\":1},\"end\":{\"line\":7,\"column\":4}},\"changeType\":\"MODIFIED\"},{\"category\":\"Heading 3\",\"term\":\"This heading is new\",\"span\":{\"start\":{\"line\":9,\"column\":1},\"end\":{\"line\":11,\"column\":10}},\"changeType\":\"ADDED\"},{\"category\":\"Heading 1\",\"term\":\"Final\",\"span\":{\"start\":{\"line\":13,\"column\":1},\"end\":{\"line\":14,\"column\":4}},\"changeType\":\"ADDED\"}]}]}\n" :: ByteString)
|
||||||
|
|
||||||
|
|
||||||
@ -219,4 +226,4 @@ summarize
|
|||||||
:: (Has (Error SomeException) sig m, Has Parse sig m, Has Telemetry sig m, MonadIO m)
|
:: (Has (Error SomeException) sig m, Has Parse sig m, Has Telemetry sig m, MonadIO m)
|
||||||
=> BlobPair
|
=> BlobPair
|
||||||
-> m [Either ErrorSummary TOCSummary]
|
-> m [Either ErrorSummary TOCSummary]
|
||||||
summarize = parsePairWith (summarizeTermParsers defaultLanguageModes) summarizeTerms
|
summarize = parsePairWith (summarizeTermParsers aLaCarteLanguageModes) summarizeTerms
|
||||||
|
@ -71,8 +71,8 @@ diffFixtures :: [(String, [BlobPair] -> ParseC TaskC Builder, [(File Language, F
|
|||||||
diffFixtures =
|
diffFixtures =
|
||||||
[ ("json diff", parseDiffBuilder DiffJSONTree, pathMode, prefix </> Path.file "diff-tree.json")
|
[ ("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")
|
, ("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")
|
, ("toc summaries diff", runReader aLaCarteLanguageModes . 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")
|
, ("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)]
|
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"
|
prefix = Path.relDir "test/fixtures/cli"
|
||||||
|
@ -31,4 +31,4 @@ spec = do
|
|||||||
|
|
||||||
it "renders with the specified renderer" $ do
|
it "renders with the specified renderer" $ do
|
||||||
output <- fmap runBuilder . runTaskOrDie . runReader defaultLanguageModes $ parseTermBuilder TermSExpression [methodsBlob]
|
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"
|
||||||
|
@ -26,6 +26,7 @@ module SpecHelpers
|
|||||||
|
|
||||||
import qualified Analysis.File as File
|
import qualified Analysis.File as File
|
||||||
import Analysis.Name as X
|
import Analysis.Name as X
|
||||||
|
import Analysis.Project as X
|
||||||
import Control.Abstract
|
import Control.Abstract
|
||||||
import Control.Carrier.Fresh.Strict
|
import Control.Carrier.Fresh.Strict
|
||||||
import Control.Carrier.Lift
|
import Control.Carrier.Lift
|
||||||
@ -56,7 +57,6 @@ import Data.Language as X hiding (Precise)
|
|||||||
import Data.List.NonEmpty as X (NonEmpty (..))
|
import Data.List.NonEmpty as X (NonEmpty (..))
|
||||||
import Data.Maybe as X
|
import Data.Maybe as X
|
||||||
import Data.Monoid as X (First (..), Last (..), Monoid (..))
|
import Data.Monoid as X (First (..), Last (..), Monoid (..))
|
||||||
import Data.Project as X
|
|
||||||
import Data.Proxy as X
|
import Data.Proxy as X
|
||||||
import Data.Semigroup as X (Semigroup (..))
|
import Data.Semigroup as X (Semigroup (..))
|
||||||
import Data.Semilattice.Lower as X
|
import Data.Semilattice.Lower as X
|
||||||
|
@ -12,27 +12,27 @@ import Tags.Tagging as Tags
|
|||||||
spec :: Spec
|
spec :: Spec
|
||||||
spec = do
|
spec = do
|
||||||
describe "go" $ 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`
|
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 "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 ]
|
, Tag "Hi" Function (Loc (Range 94 107) (Span (Pos 10 1) (Pos 11 2))) "func Hi() {" Nothing ]
|
||||||
|
|
||||||
it "produces tags for methods" $
|
it "produces tags for methods" $
|
||||||
parseTestFile [Method] (Path.relFile "test/fixtures/go/tags/method.go") `shouldReturn`
|
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" $
|
it "produces tags for calls" $
|
||||||
parseTestFile [Call] (Path.relFile "test/fixtures/go/tags/simple_functions.go") `shouldReturn`
|
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]
|
[ Tag "Hi" Call (Loc (Range 86 90) (Span (Pos 7 2) (Pos 7 6))) "Hi()" Nothing]
|
||||||
|
|
||||||
describe "javascript and typescript" $ do
|
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`
|
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" $
|
it "produces tags for classes" $
|
||||||
parseTestFile [Class] (Path.relFile "test/fixtures/typescript/tags/class.ts") `shouldReturn`
|
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" $
|
it "produces tags for modules" $
|
||||||
parseTestFile [Tags.Module] (Path.relFile "test/fixtures/typescript/tags/module.ts") `shouldReturn`
|
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
|
, 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`
|
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`
|
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`
|
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 "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" (Just "# Public: Bar")
|
, 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)" (Just "# Public: baz")
|
, 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 "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 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
|
, Tag "foo" Method (Loc (Range 166 184) (Span (Pos 18 3) (Pos 19 6))) "def self.foo" Nothing
|
||||||
|
95
test/fixtures/go/corpus/array-types.parseA.txt
vendored
95
test/fixtures/go/corpus/array-types.parseA.txt
vendored
@ -1,32 +1,63 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Statements
|
(TypeDeclaration
|
||||||
(Type
|
(TypeSpec
|
||||||
(Identifier)
|
(TypeIdentifier "a")
|
||||||
(Array
|
(Type
|
||||||
(Plus
|
(SimpleType
|
||||||
(Integer)
|
(ArrayType
|
||||||
(Integer))
|
(Expression
|
||||||
(Identifier))))
|
(BinaryExpression
|
||||||
(Statements
|
(Token)
|
||||||
(Type
|
(Expression
|
||||||
(Identifier)
|
(IntLiteral "2"))
|
||||||
(Array
|
(Expression
|
||||||
(Integer)
|
(IntLiteral "2"))))
|
||||||
(Array
|
(Type
|
||||||
(Integer)
|
(SimpleType
|
||||||
(Identifier)))))
|
(TypeIdentifier "x")))))))))
|
||||||
(Statements
|
(Statement
|
||||||
(Type
|
(TypeDeclaration
|
||||||
(Identifier)
|
(TypeSpec
|
||||||
(Array
|
(TypeIdentifier "b")
|
||||||
(Integer)
|
(Type
|
||||||
(Array
|
(SimpleType
|
||||||
(Integer)
|
(ArrayType
|
||||||
(Array
|
(Expression
|
||||||
(Integer)
|
(IntLiteral "3"))
|
||||||
(Identifier)))))))))
|
(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)))
|
||||||
|
95
test/fixtures/go/corpus/array-types.parseB.txt
vendored
95
test/fixtures/go/corpus/array-types.parseB.txt
vendored
@ -1,32 +1,63 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Statements
|
(TypeDeclaration
|
||||||
(Type
|
(TypeSpec
|
||||||
(Identifier)
|
(TypeIdentifier "a")
|
||||||
(Array
|
(Type
|
||||||
(Plus
|
(SimpleType
|
||||||
(Integer)
|
(ArrayType
|
||||||
(Integer))
|
(Expression
|
||||||
(Identifier))))
|
(BinaryExpression
|
||||||
(Statements
|
(Token)
|
||||||
(Type
|
(Expression
|
||||||
(Identifier)
|
(IntLiteral "1"))
|
||||||
(Array
|
(Expression
|
||||||
(Integer)
|
(IntLiteral "1"))))
|
||||||
(Array
|
(Type
|
||||||
(Integer)
|
(SimpleType
|
||||||
(Identifier)))))
|
(TypeIdentifier "y")))))))))
|
||||||
(Statements
|
(Statement
|
||||||
(Type
|
(TypeDeclaration
|
||||||
(Identifier)
|
(TypeSpec
|
||||||
(Array
|
(TypeIdentifier "d")
|
||||||
(Integer)
|
(Type
|
||||||
(Array
|
(SimpleType
|
||||||
(Integer)
|
(ArrayType
|
||||||
(Array
|
(Expression
|
||||||
(Integer)
|
(IntLiteral "6"))
|
||||||
(Identifier)))))))))
|
(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)))
|
||||||
|
@ -1,14 +1,28 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Assignment
|
(Statement
|
||||||
(Identifier)
|
(ConstDeclaration
|
||||||
(Composite
|
(ConstSpec
|
||||||
(Array
|
(ExpressionList
|
||||||
(Identifier))
|
(Expression
|
||||||
(Statements
|
(CompositeLiteral
|
||||||
(Integer)
|
(LiteralValue
|
||||||
(Integer)
|
(Element
|
||||||
(Integer))))))
|
(Expression
|
||||||
|
(IntLiteral "1")))
|
||||||
|
(Element
|
||||||
|
(Expression
|
||||||
|
(IntLiteral "2")))
|
||||||
|
(Element
|
||||||
|
(Expression
|
||||||
|
(IntLiteral "3"))))
|
||||||
|
(ImplicitLengthArrayType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "int")))))))
|
||||||
|
(Identifier "a1")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,14 +1,28 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Assignment
|
(Statement
|
||||||
(Identifier)
|
(ConstDeclaration
|
||||||
(Composite
|
(ConstSpec
|
||||||
(Array
|
(ExpressionList
|
||||||
(Identifier))
|
(Expression
|
||||||
(Statements
|
(CompositeLiteral
|
||||||
(Integer)
|
(LiteralValue
|
||||||
(Integer)
|
(Element
|
||||||
(Integer))))))
|
(Expression
|
||||||
|
(IntLiteral "4")))
|
||||||
|
(Element
|
||||||
|
(Expression
|
||||||
|
(IntLiteral "5")))
|
||||||
|
(Element
|
||||||
|
(Expression
|
||||||
|
(IntLiteral "6"))))
|
||||||
|
(ImplicitLengthArrayType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "int")))))))
|
||||||
|
(Identifier "a1")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,62 +1,133 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(SimpleStatement
|
||||||
(Identifier)
|
(AssignmentStatement
|
||||||
(Integer))
|
(Token)
|
||||||
(AugmentedAssignment
|
(ExpressionList
|
||||||
(Plus
|
(Expression
|
||||||
(Statements
|
(Identifier "a")))
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Identifier))
|
(Expression
|
||||||
(Statements
|
(IntLiteral "1"))))))
|
||||||
(Integer)
|
(Statement
|
||||||
(Integer))))
|
(SimpleStatement
|
||||||
(AugmentedAssignment
|
(AssignmentStatement
|
||||||
(Times
|
(Token)
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Integer)))
|
(Expression
|
||||||
(AugmentedAssignment
|
(Identifier "b"))
|
||||||
(Plus
|
(Expression
|
||||||
(Identifier)
|
(Identifier "c")))
|
||||||
(Integer)))
|
(ExpressionList
|
||||||
(AugmentedAssignment
|
(Expression
|
||||||
(LShift
|
(IntLiteral "2"))
|
||||||
(Identifier)
|
(Expression
|
||||||
(Integer)))
|
(IntLiteral "3"))))))
|
||||||
(AugmentedAssignment
|
(Statement
|
||||||
(RShift
|
(SimpleStatement
|
||||||
(Identifier)
|
(AssignmentStatement
|
||||||
(Integer)))
|
(Token)
|
||||||
(AugmentedAssignment
|
(ExpressionList
|
||||||
(DividedBy
|
(Expression
|
||||||
(Identifier)
|
(Identifier "d")))
|
||||||
(Integer)))
|
(ExpressionList
|
||||||
(AugmentedAssignment
|
(Expression
|
||||||
(BXOr
|
(IntLiteral "3"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Integer)))
|
(SimpleStatement
|
||||||
(AugmentedAssignment
|
(AssignmentStatement
|
||||||
(Modulo
|
(Token)
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Integer)))
|
(Expression
|
||||||
(AugmentedAssignment
|
(Identifier "e")))
|
||||||
(Not
|
(ExpressionList
|
||||||
(BAnd
|
(Expression
|
||||||
(Identifier)
|
(IntLiteral "1"))))))
|
||||||
(Integer))))
|
(Statement
|
||||||
(Assignment
|
(SimpleStatement
|
||||||
(Identifier)
|
(AssignmentStatement
|
||||||
(Statements
|
(Token)
|
||||||
(Pointer
|
(ExpressionList
|
||||||
(Identifier))
|
(Expression
|
||||||
(Reference
|
(Identifier "f")))
|
||||||
(Composite
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements
|
(IntLiteral "1"))))))
|
||||||
(KeyValue
|
(Statement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Integer))))))))))
|
(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)))
|
||||||
|
@ -1,62 +1,133 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(SimpleStatement
|
||||||
(Identifier)
|
(AssignmentStatement
|
||||||
(Integer))
|
(Token)
|
||||||
(AugmentedAssignment
|
(ExpressionList
|
||||||
(Plus
|
(Expression
|
||||||
(Statements
|
(Identifier "l")))
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Identifier))
|
(Expression
|
||||||
(Statements
|
(IntLiteral "1"))))))
|
||||||
(Integer)
|
(Statement
|
||||||
(Integer))))
|
(SimpleStatement
|
||||||
(AugmentedAssignment
|
(AssignmentStatement
|
||||||
(Times
|
(Token)
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Integer)))
|
(Expression
|
||||||
(AugmentedAssignment
|
(Identifier "m"))
|
||||||
(Plus
|
(Expression
|
||||||
(Identifier)
|
(Identifier "n")))
|
||||||
(Integer)))
|
(ExpressionList
|
||||||
(AugmentedAssignment
|
(Expression
|
||||||
(LShift
|
(IntLiteral "2"))
|
||||||
(Identifier)
|
(Expression
|
||||||
(Integer)))
|
(IntLiteral "3"))))))
|
||||||
(AugmentedAssignment
|
(Statement
|
||||||
(RShift
|
(SimpleStatement
|
||||||
(Identifier)
|
(AssignmentStatement
|
||||||
(Integer)))
|
(Token)
|
||||||
(AugmentedAssignment
|
(ExpressionList
|
||||||
(DividedBy
|
(Expression
|
||||||
(Identifier)
|
(Identifier "o")))
|
||||||
(Integer)))
|
(ExpressionList
|
||||||
(AugmentedAssignment
|
(Expression
|
||||||
(BXOr
|
(IntLiteral "3"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Integer)))
|
(SimpleStatement
|
||||||
(AugmentedAssignment
|
(AssignmentStatement
|
||||||
(Modulo
|
(Token)
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Integer)))
|
(Expression
|
||||||
(AugmentedAssignment
|
(Identifier "p")))
|
||||||
(Not
|
(ExpressionList
|
||||||
(BAnd
|
(Expression
|
||||||
(Identifier)
|
(IntLiteral "1"))))))
|
||||||
(Integer))))
|
(Statement
|
||||||
(Assignment
|
(SimpleStatement
|
||||||
(Identifier)
|
(AssignmentStatement
|
||||||
(Statements
|
(Token)
|
||||||
(Pointer
|
(ExpressionList
|
||||||
(Identifier))
|
(Expression
|
||||||
(Reference
|
(Identifier "q")))
|
||||||
(Composite
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements
|
(IntLiteral "1"))))))
|
||||||
(KeyValue
|
(Statement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Integer))))))))))
|
(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)))
|
||||||
|
@ -1,70 +1,178 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Context
|
(SimpleStatement
|
||||||
(Comment)
|
(Expression
|
||||||
(Or
|
(BinaryExpression
|
||||||
(Identifier)
|
(Token)
|
||||||
(Context
|
(Expression
|
||||||
(Comment)
|
(Identifier "a"))
|
||||||
(Identifier))))
|
(Expression
|
||||||
(Context
|
(Identifier "b"))))))
|
||||||
(Comment)
|
(Statement
|
||||||
(And
|
(SimpleStatement
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier)))
|
(BinaryExpression
|
||||||
(Equal
|
(Token)
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(Identifier "c"))
|
||||||
(Not
|
(Expression
|
||||||
(Equal
|
(Identifier "d"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier)))
|
(SimpleStatement
|
||||||
(LessThan
|
(Expression
|
||||||
(Identifier)
|
(BinaryExpression
|
||||||
(Identifier))
|
(Token)
|
||||||
(LessThanEqual
|
(Expression
|
||||||
(Identifier)
|
(Identifier "e"))
|
||||||
(Identifier))
|
(Expression
|
||||||
(GreaterThan
|
(Identifier "f"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier))
|
(SimpleStatement
|
||||||
(GreaterThanEqual
|
(Expression
|
||||||
(Identifier)
|
(BinaryExpression
|
||||||
(Identifier))
|
(Token)
|
||||||
(Plus
|
(Expression
|
||||||
(Identifier)
|
(Identifier "g"))
|
||||||
(Identifier))
|
(Expression
|
||||||
(Minus
|
(Identifier "h"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier))
|
(SimpleStatement
|
||||||
(BOr
|
(Expression
|
||||||
(Identifier)
|
(BinaryExpression
|
||||||
(Identifier))
|
(Token)
|
||||||
(BXOr
|
(Expression
|
||||||
(Identifier)
|
(Identifier "i"))
|
||||||
(Identifier))
|
(Expression
|
||||||
(Times
|
(Identifier "j"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier))
|
(SimpleStatement
|
||||||
(DividedBy
|
(Expression
|
||||||
(Identifier)
|
(BinaryExpression
|
||||||
(Identifier))
|
(Token)
|
||||||
(Modulo
|
(Expression
|
||||||
(Identifier)
|
(Identifier "k"))
|
||||||
(Identifier))
|
(Expression
|
||||||
(LShift
|
(Identifier "l"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier))
|
(SimpleStatement
|
||||||
(RShift
|
(Expression
|
||||||
(Identifier)
|
(BinaryExpression
|
||||||
(Identifier))
|
(Token)
|
||||||
(BAnd
|
(Expression
|
||||||
(Identifier)
|
(Identifier "m"))
|
||||||
(Identifier))
|
(Expression
|
||||||
(BAnd
|
(Identifier "n"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier)))))
|
(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)))
|
||||||
|
@ -1,70 +1,178 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Context
|
(SimpleStatement
|
||||||
(Comment)
|
(Expression
|
||||||
(Or
|
(BinaryExpression
|
||||||
(Identifier)
|
(Token)
|
||||||
(Context
|
(Expression
|
||||||
(Comment)
|
(Identifier "b"))
|
||||||
(Identifier))))
|
(Expression
|
||||||
(Context
|
(Identifier "c"))))))
|
||||||
(Comment)
|
(Statement
|
||||||
(And
|
(SimpleStatement
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier)))
|
(BinaryExpression
|
||||||
(Equal
|
(Token)
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(Identifier "d"))
|
||||||
(Not
|
(Expression
|
||||||
(Equal
|
(Identifier "c"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier)))
|
(SimpleStatement
|
||||||
(LessThan
|
(Expression
|
||||||
(Identifier)
|
(BinaryExpression
|
||||||
(Identifier))
|
(Token)
|
||||||
(LessThanEqual
|
(Expression
|
||||||
(Identifier)
|
(Identifier "f"))
|
||||||
(Identifier))
|
(Expression
|
||||||
(GreaterThan
|
(Identifier "e"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier))
|
(SimpleStatement
|
||||||
(GreaterThanEqual
|
(Expression
|
||||||
(Identifier)
|
(BinaryExpression
|
||||||
(Identifier))
|
(Token)
|
||||||
(Plus
|
(Expression
|
||||||
(Identifier)
|
(Identifier "h"))
|
||||||
(Identifier))
|
(Expression
|
||||||
(Minus
|
(Identifier "g"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier))
|
(SimpleStatement
|
||||||
(BOr
|
(Expression
|
||||||
(Identifier)
|
(BinaryExpression
|
||||||
(Identifier))
|
(Token)
|
||||||
(BXOr
|
(Expression
|
||||||
(Identifier)
|
(Identifier "j"))
|
||||||
(Identifier))
|
(Expression
|
||||||
(Times
|
(Identifier "i"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier))
|
(SimpleStatement
|
||||||
(DividedBy
|
(Expression
|
||||||
(Identifier)
|
(BinaryExpression
|
||||||
(Identifier))
|
(Token)
|
||||||
(Modulo
|
(Expression
|
||||||
(Identifier)
|
(Identifier "l"))
|
||||||
(Identifier))
|
(Expression
|
||||||
(LShift
|
(Identifier "k"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier))
|
(SimpleStatement
|
||||||
(RShift
|
(Expression
|
||||||
(Identifier)
|
(BinaryExpression
|
||||||
(Identifier))
|
(Token)
|
||||||
(BAnd
|
(Expression
|
||||||
(Identifier)
|
(Identifier "n"))
|
||||||
(Identifier))
|
(Expression
|
||||||
(BAnd
|
(Identifier "m"))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier)))))
|
(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)))
|
||||||
|
@ -1,30 +1,49 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Call
|
(SimpleStatement
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Variadic
|
(Identifier "x"))
|
||||||
(Identifier)))
|
(ArgumentList
|
||||||
(Empty))
|
(Expression
|
||||||
(Call
|
(Identifier "b"))
|
||||||
(Identifier)
|
(VariadicArgument
|
||||||
(Statements
|
(Expression
|
||||||
(Identifier)
|
(Identifier "c"))))))))
|
||||||
(Identifier))
|
(Statement
|
||||||
(Empty))
|
(SimpleStatement
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(CallExpression
|
||||||
(Statements
|
(Expression
|
||||||
(Identifier)
|
(Identifier "y"))
|
||||||
(Variadic
|
(ArgumentList
|
||||||
(Identifier)))
|
(Expression
|
||||||
(Empty))
|
(Identifier "b"))
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(Identifier "c")))))))
|
||||||
(Statements)
|
(Statement
|
||||||
(Empty)))))
|
(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)))
|
||||||
|
@ -1,26 +1,42 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Call
|
(SimpleStatement
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Variadic
|
(Identifier "a"))
|
||||||
(Identifier)))
|
(ArgumentList
|
||||||
(Empty))
|
(Expression
|
||||||
(Call
|
(Identifier "b"))
|
||||||
(Identifier)
|
(VariadicArgument
|
||||||
(Statements
|
(Expression
|
||||||
(Identifier)
|
(Identifier "c"))))))))
|
||||||
(Identifier))
|
(Statement
|
||||||
(Empty))
|
(SimpleStatement
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(CallExpression
|
||||||
(Statements
|
(Expression
|
||||||
(Identifier)
|
(Identifier "b"))
|
||||||
(Variadic
|
(ArgumentList
|
||||||
(Identifier)))
|
(Expression
|
||||||
(Empty)))))
|
(Identifier "b"))
|
||||||
|
(Expression
|
||||||
|
(Identifier "c")))))))
|
||||||
|
(Statement
|
||||||
|
(SimpleStatement
|
||||||
|
(Expression
|
||||||
|
(CallExpression
|
||||||
|
(Expression
|
||||||
|
(Identifier "c"))
|
||||||
|
(ArgumentList
|
||||||
|
(Expression
|
||||||
|
(Identifier "b"))
|
||||||
|
(VariadicArgument
|
||||||
|
(Expression
|
||||||
|
(Identifier "c")))))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,8 +1,9 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Match
|
(Statement
|
||||||
(Empty)
|
(ExpressionSwitchStatement)))
|
||||||
(Statements))))
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,43 +1,56 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Match
|
(ExpressionSwitchStatement
|
||||||
(Statements)
|
(ExpressionCase
|
||||||
(Pattern
|
(ExpressionList
|
||||||
(Statements
|
(Expression
|
||||||
(Identifier)
|
(Identifier "foo")))
|
||||||
(Call
|
(Statement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Statements)
|
(Expression
|
||||||
(Empty)))
|
(CallExpression
|
||||||
(Statements)))
|
(Expression
|
||||||
(Match
|
(Identifier "f1"))
|
||||||
(Statements
|
(ArgumentList))))))))
|
||||||
(Identifier))
|
(Statement
|
||||||
(Pattern
|
(ExpressionSwitchStatement
|
||||||
(Statements
|
(Expression
|
||||||
(Statements
|
(Identifier "e"))
|
||||||
(Integer)
|
(ExpressionCase
|
||||||
(Integer))
|
(ExpressionList
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(IntLiteral "1"))
|
||||||
(Statements)
|
(Expression
|
||||||
(Empty))
|
(IntLiteral "2")))
|
||||||
(Call
|
(Statement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Statements)
|
(Expression
|
||||||
(Empty))
|
(CallExpression
|
||||||
(Pattern
|
(Expression
|
||||||
(Identifier)
|
(Identifier "a"))
|
||||||
(Empty)))
|
(ArgumentList)))))
|
||||||
(DefaultPattern
|
(Statement
|
||||||
(Statements
|
(SimpleStatement
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(CallExpression
|
||||||
(Statements)
|
(Expression
|
||||||
(Empty))
|
(Identifier "b"))
|
||||||
(Break
|
(ArgumentList)))))
|
||||||
(Empty)))))))))
|
(Statement
|
||||||
|
(FallthroughStatement "fallthrough")))
|
||||||
|
(DefaultCase
|
||||||
|
(Statement
|
||||||
|
(SimpleStatement
|
||||||
|
(Expression
|
||||||
|
(CallExpression
|
||||||
|
(Expression
|
||||||
|
(Identifier "c"))
|
||||||
|
(ArgumentList)))))
|
||||||
|
(Statement
|
||||||
|
(BreakStatement))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
101
test/fixtures/go/corpus/channel-types.parseA.txt
vendored
101
test/fixtures/go/corpus/channel-types.parseA.txt
vendored
@ -1,34 +1,67 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Type
|
(TypeDeclaration
|
||||||
(Identifier)
|
(TypeSpec
|
||||||
(BidirectionalChannel
|
(TypeIdentifier "c1")
|
||||||
(ReceiveChannel
|
(Type
|
||||||
(Identifier))))
|
(SimpleType
|
||||||
(Type
|
(ChannelType
|
||||||
(Identifier)
|
(Type
|
||||||
(SendChannel
|
(SimpleType
|
||||||
(SendChannel
|
(ChannelType
|
||||||
(Constructor
|
(Type
|
||||||
(Empty)
|
(SimpleType
|
||||||
(Statements)))))
|
(TypeIdentifier "int"))))))))))
|
||||||
(Type
|
(TypeSpec
|
||||||
(Identifier)
|
(TypeIdentifier "c2")
|
||||||
(SendChannel
|
(Type
|
||||||
(ReceiveChannel
|
(SimpleType
|
||||||
(Identifier))))
|
(ChannelType
|
||||||
(Type
|
(Type
|
||||||
(Identifier)
|
(SimpleType
|
||||||
(ReceiveChannel
|
(ChannelType
|
||||||
(ReceiveChannel
|
(Type
|
||||||
(Identifier))))
|
(SimpleType
|
||||||
(Type
|
(StructType
|
||||||
(Identifier)
|
(FieldDeclarationList)))))))))))
|
||||||
(BidirectionalChannel
|
(TypeSpec
|
||||||
(Parenthesized
|
(TypeIdentifier "c3")
|
||||||
(ReceiveChannel
|
(Type
|
||||||
(Identifier))))))))
|
(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)))
|
||||||
|
101
test/fixtures/go/corpus/channel-types.parseB.txt
vendored
101
test/fixtures/go/corpus/channel-types.parseB.txt
vendored
@ -1,34 +1,67 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Type
|
(TypeDeclaration
|
||||||
(Identifier)
|
(TypeSpec
|
||||||
(BidirectionalChannel
|
(TypeIdentifier "c2")
|
||||||
(ReceiveChannel
|
(Type
|
||||||
(Identifier))))
|
(SimpleType
|
||||||
(Type
|
(ChannelType
|
||||||
(Identifier)
|
(Type
|
||||||
(SendChannel
|
(SimpleType
|
||||||
(SendChannel
|
(ChannelType
|
||||||
(Constructor
|
(Type
|
||||||
(Empty)
|
(SimpleType
|
||||||
(Statements)))))
|
(TypeIdentifier "string"))))))))))
|
||||||
(Type
|
(TypeSpec
|
||||||
(Identifier)
|
(TypeIdentifier "c3")
|
||||||
(SendChannel
|
(Type
|
||||||
(ReceiveChannel
|
(SimpleType
|
||||||
(Identifier))))
|
(ChannelType
|
||||||
(Type
|
(Type
|
||||||
(Identifier)
|
(SimpleType
|
||||||
(ReceiveChannel
|
(ChannelType
|
||||||
(ReceiveChannel
|
(Type
|
||||||
(Identifier))))
|
(SimpleType
|
||||||
(Type
|
(StructType
|
||||||
(Identifier)
|
(FieldDeclarationList)))))))))))
|
||||||
(BidirectionalChannel
|
(TypeSpec
|
||||||
(Parenthesized
|
(TypeIdentifier "c4")
|
||||||
(ReceiveChannel
|
(Type
|
||||||
(Identifier))))))))
|
(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)))
|
||||||
|
15
test/fixtures/go/corpus/comment.parseA.txt
vendored
15
test/fixtures/go/corpus/comment.parseA.txt
vendored
@ -1,8 +1,7 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block)
|
||||||
(Context
|
(Identifier "main")
|
||||||
(Comment)
|
(ParameterList)))
|
||||||
(Empty))))
|
|
||||||
|
15
test/fixtures/go/corpus/comment.parseB.txt
vendored
15
test/fixtures/go/corpus/comment.parseB.txt
vendored
@ -1,8 +1,7 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block)
|
||||||
(Context
|
(Identifier "main")
|
||||||
(Comment)
|
(ParameterList)))
|
||||||
(Empty))))
|
|
||||||
|
@ -1,11 +1,17 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Assignment
|
(Statement
|
||||||
(Annotation
|
(ConstDeclaration
|
||||||
(Statements
|
(ConstSpec
|
||||||
(Identifier))
|
(ExpressionList
|
||||||
(Identifier))
|
(Expression
|
||||||
(Integer))))
|
(IntLiteral "0")))
|
||||||
|
(Identifier "zero")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "int")))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,14 +1,21 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Assignment
|
(Statement
|
||||||
(Annotation
|
(ConstDeclaration
|
||||||
(Statements
|
(ConstSpec
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Identifier))
|
(Expression
|
||||||
(Identifier))
|
(IntLiteral "1"))
|
||||||
(Statements
|
(Expression
|
||||||
(Integer)
|
(IntLiteral "2")))
|
||||||
(Integer)))))
|
(Identifier "one")
|
||||||
|
(Token)
|
||||||
|
(Identifier "two")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "uiint64")))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,8 +1,14 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Assignment
|
(Statement
|
||||||
(Identifier)
|
(ConstDeclaration
|
||||||
(Integer))))
|
(ConstSpec
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(IntLiteral "0")))
|
||||||
|
(Identifier "zero")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,12 +1,18 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Assignment
|
(Statement
|
||||||
(Statements
|
(ConstDeclaration
|
||||||
(Identifier)
|
(ConstSpec
|
||||||
(Identifier))
|
(ExpressionList
|
||||||
(Statements
|
(Expression
|
||||||
(Integer)
|
(IntLiteral "1"))
|
||||||
(Integer)))))
|
(Expression
|
||||||
|
(IntLiteral "2")))
|
||||||
|
(Identifier "one")
|
||||||
|
(Token)
|
||||||
|
(Identifier "two")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,15 +1,18 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(ConstDeclaration
|
||||||
(Identifier)
|
(ConstSpec
|
||||||
(Identifier))
|
(ExpressionList
|
||||||
(Assignment
|
(Expression
|
||||||
(Identifier)
|
(Identifier "iota")))
|
||||||
(Statements))
|
(Identifier "zero"))
|
||||||
(Assignment
|
(ConstSpec
|
||||||
(Identifier)
|
(Identifier "one"))
|
||||||
(Statements)))))
|
(ConstSpec
|
||||||
|
(Identifier "two")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,15 +1,18 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(ConstDeclaration
|
||||||
(Identifier)
|
(ConstSpec
|
||||||
(Identifier))
|
(ExpressionList
|
||||||
(Assignment
|
(Expression
|
||||||
(Identifier)
|
(Identifier "iota")))
|
||||||
(Statements))
|
(Identifier "a"))
|
||||||
(Assignment
|
(ConstSpec
|
||||||
(Identifier)
|
(Identifier "b"))
|
||||||
(Statements)))))
|
(ConstSpec
|
||||||
|
(Identifier "c")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
109
test/fixtures/go/corpus/constructors.parseA.txt
vendored
109
test/fixtures/go/corpus/constructors.parseA.txt
vendored
@ -1,34 +1,75 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Call
|
(SimpleStatement
|
||||||
(Identifier)
|
(Expression
|
||||||
(SendChannel
|
(CallExpression
|
||||||
(Identifier))
|
(Expression
|
||||||
(Empty))
|
(Identifier "make"))
|
||||||
(Call
|
(ArgumentList
|
||||||
(Identifier)
|
(Type
|
||||||
(Statements
|
(SimpleType
|
||||||
(SendChannel
|
(ChannelType
|
||||||
(Identifier))
|
(Type
|
||||||
(Minus
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "int")))))))))))
|
||||||
(Identifier)))
|
(Statement
|
||||||
(Empty))
|
(SimpleStatement
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(CallExpression
|
||||||
(Statements
|
(Expression
|
||||||
(SendChannel
|
(Identifier "make"))
|
||||||
(Identifier))
|
(ArgumentList
|
||||||
(Integer)
|
(Type
|
||||||
(Integer))
|
(SimpleType
|
||||||
(Empty))
|
(ChannelType
|
||||||
(Call
|
(Type
|
||||||
(Identifier)
|
(SimpleType
|
||||||
(Map
|
(TypeIdentifier "int"))))))
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(ParenthesizedExpression
|
||||||
(Empty)))))
|
(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)))
|
||||||
|
109
test/fixtures/go/corpus/constructors.parseB.txt
vendored
109
test/fixtures/go/corpus/constructors.parseB.txt
vendored
@ -1,34 +1,75 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Call
|
(SimpleStatement
|
||||||
(Identifier)
|
(Expression
|
||||||
(SendChannel
|
(CallExpression
|
||||||
(Identifier))
|
(Expression
|
||||||
(Empty))
|
(Identifier "make"))
|
||||||
(Call
|
(ArgumentList
|
||||||
(Identifier)
|
(Type
|
||||||
(Statements
|
(SimpleType
|
||||||
(SendChannel
|
(ChannelType
|
||||||
(Identifier))
|
(Type
|
||||||
(Minus
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "string")))))))))))
|
||||||
(Identifier)))
|
(Statement
|
||||||
(Empty))
|
(SimpleStatement
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(CallExpression
|
||||||
(Statements
|
(Expression
|
||||||
(SendChannel
|
(Identifier "make"))
|
||||||
(Identifier))
|
(ArgumentList
|
||||||
(Integer)
|
(Type
|
||||||
(Integer))
|
(SimpleType
|
||||||
(Empty))
|
(ChannelType
|
||||||
(Call
|
(Type
|
||||||
(Identifier)
|
(SimpleType
|
||||||
(Map
|
(TypeIdentifier "string"))))))
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(ParenthesizedExpression
|
||||||
(Empty)))))
|
(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)))
|
||||||
|
@ -1,21 +1,57 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(SimpleStatement
|
||||||
(Identifier)
|
(AssignmentStatement
|
||||||
(Float))
|
(Token)
|
||||||
(Assignment
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Float))
|
(Identifier "f1")))
|
||||||
(Assignment
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Float))
|
(FloatLiteral "1.5"))))))
|
||||||
(Assignment
|
(Statement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Float))
|
(AssignmentStatement
|
||||||
(Assignment
|
(Token)
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Float)))))
|
(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)))
|
||||||
|
@ -1,21 +1,57 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(SimpleStatement
|
||||||
(Identifier)
|
(AssignmentStatement
|
||||||
(Float))
|
(Token)
|
||||||
(Assignment
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Float))
|
(Identifier "f1")))
|
||||||
(Assignment
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Float))
|
(FloatLiteral "2.6"))))))
|
||||||
(Assignment
|
(Statement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Float))
|
(AssignmentStatement
|
||||||
(Assignment
|
(Token)
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Float)))))
|
(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)))
|
||||||
|
282
test/fixtures/go/corpus/for-statements.parseA.txt
vendored
282
test/fixtures/go/corpus/for-statements.parseA.txt
vendored
@ -1,104 +1,178 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(For
|
(ForStatement
|
||||||
(Empty)
|
(Block
|
||||||
(Empty)
|
(Statement
|
||||||
(Empty)
|
(SimpleStatement
|
||||||
(Statements
|
(Expression
|
||||||
(Call
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements)
|
(Identifier "a"))
|
||||||
(Empty))
|
(ArgumentList)))))
|
||||||
(Goto
|
(Statement
|
||||||
(Identifier))))
|
(GotoStatement
|
||||||
(For
|
(LabelName "loop"))))))
|
||||||
(Assignment
|
(Statement
|
||||||
(Identifier)
|
(ForStatement
|
||||||
(Integer))
|
(Block
|
||||||
(LessThan
|
(Statement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Integer))
|
(Expression
|
||||||
(PostIncrement
|
(CallExpression
|
||||||
(Identifier))
|
(Expression
|
||||||
(Statements
|
(Identifier "a"))
|
||||||
(Call
|
(ArgumentList)))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Statements)
|
(BreakStatement
|
||||||
(Empty))
|
(LabelName "loop"))))
|
||||||
(Break
|
(ForClause
|
||||||
(Identifier))))
|
(SimpleStatement
|
||||||
(For
|
(ShortVarDeclaration
|
||||||
(LessThan
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Integer))
|
(Identifier "i")))
|
||||||
(PostIncrement
|
(ExpressionList
|
||||||
(Identifier))
|
(Expression
|
||||||
(Empty)
|
(IntLiteral "0")))))
|
||||||
(Statements
|
(Expression
|
||||||
(Call
|
(BinaryExpression
|
||||||
(Identifier)
|
(Token)
|
||||||
(Statements)
|
(Expression
|
||||||
(Empty))
|
(Identifier "i"))
|
||||||
(Continue
|
(Expression
|
||||||
(Identifier))))
|
(IntLiteral "5"))))
|
||||||
(For
|
(SimpleStatement
|
||||||
(Empty)
|
(IncStatement
|
||||||
(Empty)
|
(Expression
|
||||||
(Empty)
|
(Identifier "i")))))))
|
||||||
(Statements
|
(Statement
|
||||||
(Call
|
(ForStatement
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements)
|
(Statement
|
||||||
(Empty))
|
(SimpleStatement
|
||||||
(Continue
|
(Expression
|
||||||
(Empty))))
|
(CallExpression
|
||||||
(ForEach
|
(Expression
|
||||||
(Identifier)
|
(Identifier "a"))
|
||||||
(Identifier)
|
(ArgumentList)))))
|
||||||
(Statements
|
(Statement
|
||||||
(Call
|
(ContinueStatement
|
||||||
(Identifier)
|
(LabelName "loop2"))))
|
||||||
(Identifier)
|
(ForClause
|
||||||
(Empty))
|
(Expression
|
||||||
(Break
|
(BinaryExpression
|
||||||
(Empty))))
|
(Token)
|
||||||
(ForEach
|
(Expression
|
||||||
(Statements
|
(Identifier "i"))
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(IntLiteral "10"))))
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Call
|
(IncStatement
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements
|
(Identifier "i")))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier))
|
(ForStatement
|
||||||
(Empty)))
|
(Block
|
||||||
(ForEach
|
(Statement
|
||||||
(Statements
|
(SimpleStatement
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Call
|
(Identifier "a"))
|
||||||
(Identifier)
|
(ArgumentList)))))
|
||||||
(Statements
|
(Statement
|
||||||
(Identifier)
|
(ContinueStatement)))
|
||||||
(Identifier))
|
(ForClause)))
|
||||||
(Empty)))
|
(Statement
|
||||||
(For
|
(ForStatement
|
||||||
(Empty)
|
(Block
|
||||||
(LessThan
|
(Statement
|
||||||
(Integer)
|
(SimpleStatement
|
||||||
(Integer))
|
(Expression
|
||||||
(Empty)
|
(CallExpression
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(Identifier "a"))
|
||||||
(Statements)
|
(ArgumentList
|
||||||
(Empty)))
|
(Expression
|
||||||
(ForEach
|
(Identifier "x")))))))
|
||||||
(Empty)
|
(Statement
|
||||||
(Identifier)
|
(BreakStatement)))
|
||||||
(Statements)))))
|
(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)))
|
||||||
|
258
test/fixtures/go/corpus/for-statements.parseB.txt
vendored
258
test/fixtures/go/corpus/for-statements.parseB.txt
vendored
@ -1,99 +1,159 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(For
|
(ForStatement
|
||||||
(Empty)
|
(Block
|
||||||
(Empty)
|
(Statement
|
||||||
(Empty)
|
(SimpleStatement
|
||||||
(Statements
|
(Expression
|
||||||
(Call
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements)
|
(Identifier "a"))
|
||||||
(Empty))
|
(ArgumentList)))))
|
||||||
(Goto
|
(Statement
|
||||||
(Identifier))))
|
(GotoStatement
|
||||||
(ForEach
|
(LabelName "loop"))))
|
||||||
(Identifier)
|
(ForClause)))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Statements
|
(ForStatement
|
||||||
(Call
|
(Block
|
||||||
(Identifier)
|
(Statement
|
||||||
(Statements)
|
(SimpleStatement
|
||||||
(Empty))
|
(Expression
|
||||||
(Break
|
(CallExpression
|
||||||
(Identifier))))
|
(Expression
|
||||||
(For
|
(Identifier "a"))
|
||||||
(Empty)
|
(ArgumentList)))))
|
||||||
(Empty)
|
(Statement
|
||||||
(Empty)
|
(BreakStatement
|
||||||
(Statements
|
(LabelName "loop"))))
|
||||||
(Call
|
(RangeClause
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Statements)
|
(Expression
|
||||||
(Empty))
|
(Identifier "x")))
|
||||||
(Continue
|
(Expression
|
||||||
(Identifier))))
|
(Identifier "y")))))
|
||||||
(For
|
(Statement
|
||||||
(LessThan
|
(ForStatement
|
||||||
(Identifier)
|
(Block
|
||||||
(Integer))
|
(Statement
|
||||||
(PostIncrement
|
(SimpleStatement
|
||||||
(Identifier))
|
(Expression
|
||||||
(Empty)
|
(CallExpression
|
||||||
(Statements
|
(Expression
|
||||||
(Call
|
(Identifier "a"))
|
||||||
(Identifier)
|
(ArgumentList)))))
|
||||||
(Statements)
|
(Statement
|
||||||
(Empty))
|
(ContinueStatement
|
||||||
(Continue
|
(LabelName "loop2"))))
|
||||||
(Empty))))
|
(ForClause)))
|
||||||
(For
|
(Statement
|
||||||
(Empty)
|
(ForStatement
|
||||||
(Empty)
|
(Block
|
||||||
(Empty)
|
(Statement
|
||||||
(Statements
|
(SimpleStatement
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Empty))
|
(Identifier "a"))
|
||||||
(Break
|
(ArgumentList)))))
|
||||||
(Empty))))
|
(Statement
|
||||||
(ForEach
|
(ContinueStatement)))
|
||||||
(Statements
|
(ForClause
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(BinaryExpression
|
||||||
(Identifier)
|
(Token)
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(Identifier "i"))
|
||||||
(Statements
|
(Expression
|
||||||
(Identifier)
|
(IntLiteral "10"))))
|
||||||
(Identifier))
|
(SimpleStatement
|
||||||
(Empty)))
|
(IncStatement
|
||||||
(ForEach
|
(Expression
|
||||||
(Statements
|
(Identifier "i")))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier))
|
(ForStatement
|
||||||
(Identifier)
|
(Block
|
||||||
(Call
|
(Statement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Statements
|
(Expression
|
||||||
(Identifier)
|
(CallExpression
|
||||||
(Identifier))
|
(Expression
|
||||||
(Empty)))
|
(Identifier "a"))
|
||||||
(For
|
(ArgumentList
|
||||||
(Empty)
|
(Expression
|
||||||
(LessThan
|
(Identifier "x")))))))
|
||||||
(Integer)
|
(Statement
|
||||||
(Integer))
|
(BreakStatement)))))
|
||||||
(Empty)
|
(Statement
|
||||||
(Call
|
(ForStatement
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements)
|
(Statement
|
||||||
(Empty)))
|
(SimpleStatement
|
||||||
(ForEach
|
(Expression
|
||||||
(Empty)
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements)))))
|
(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)))
|
||||||
|
@ -1,53 +1,76 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block)
|
||||||
(Statements))
|
(Identifier "main")
|
||||||
(Function
|
(ParameterList))
|
||||||
(Identifier)
|
(FunctionDeclaration
|
||||||
(Statements))
|
(Block)
|
||||||
(Function
|
(Identifier "f1")
|
||||||
(Identifier)
|
(ParameterList))
|
||||||
(Identifier)
|
(FunctionDeclaration
|
||||||
(Statements
|
(Block)
|
||||||
(Identifier)
|
(SimpleType
|
||||||
(Identifier))
|
(TypeIdentifier "int"))
|
||||||
(Statements
|
(Identifier "f2")
|
||||||
(Identifier)
|
(ParameterList
|
||||||
(Identifier)
|
(ParameterDeclaration
|
||||||
(Identifier)
|
(Identifier "a")
|
||||||
(Identifier))
|
(Type
|
||||||
(Statements))
|
(SimpleType
|
||||||
(Function
|
(TypeIdentifier "int"))))
|
||||||
(Statements
|
(ParameterDeclaration
|
||||||
(Statements
|
(Identifier "b")
|
||||||
(Identifier))
|
(Token)
|
||||||
(Statements
|
(Identifier "c")
|
||||||
(Identifier)))
|
(Token)
|
||||||
(Identifier)
|
(Identifier "d")
|
||||||
(Statements))
|
(Type
|
||||||
(Function
|
(SimpleType
|
||||||
(Statements
|
(TypeIdentifier "string"))))))
|
||||||
(Statements
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block)
|
||||||
(Identifier))
|
(ParameterList
|
||||||
(Statements
|
(ParameterDeclaration
|
||||||
(Identifier)
|
(Type
|
||||||
(Identifier)))
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "int"))))
|
||||||
(Statements))
|
(ParameterDeclaration
|
||||||
(Function
|
(Type
|
||||||
(Identifier)
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "error")))))
|
||||||
(Empty))
|
(Identifier "f2")
|
||||||
(Function
|
(ParameterList))
|
||||||
(Context
|
(FunctionDeclaration
|
||||||
(Comment)
|
(Block)
|
||||||
(Empty))
|
(ParameterList
|
||||||
(Identifier)
|
(ParameterDeclaration
|
||||||
(Statements
|
(Identifier "result")
|
||||||
(Identifier)
|
(Type
|
||||||
(Pointer
|
(SimpleType
|
||||||
(Identifier)))
|
(TypeIdentifier "int"))))
|
||||||
(Statements)))
|
(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"))))))))))
|
||||||
|
@ -1,58 +1,83 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block)
|
||||||
(Statements))
|
(Identifier "main")
|
||||||
(Function
|
(ParameterList))
|
||||||
(Identifier)
|
(FunctionDeclaration
|
||||||
(Statements))
|
(Block)
|
||||||
(Function
|
(Identifier "fa")
|
||||||
(Identifier)
|
(ParameterList))
|
||||||
(Identifier)
|
(FunctionDeclaration
|
||||||
(Statements
|
(Block)
|
||||||
(Identifier)
|
(SimpleType
|
||||||
(Identifier))
|
(TypeIdentifier "int"))
|
||||||
(Statements
|
(Identifier "fb")
|
||||||
(Identifier)
|
(ParameterList
|
||||||
(Identifier)
|
(ParameterDeclaration
|
||||||
(Identifier)
|
(Identifier "a")
|
||||||
(Identifier))
|
(Type
|
||||||
(Statements))
|
(SimpleType
|
||||||
(Function
|
(TypeIdentifier "int"))))
|
||||||
(Statements
|
(ParameterDeclaration
|
||||||
(Statements
|
(Identifier "b")
|
||||||
(Identifier))
|
(Token)
|
||||||
(Statements
|
(Identifier "c")
|
||||||
(Identifier)))
|
(Token)
|
||||||
(Identifier)
|
(Identifier "d")
|
||||||
(Statements))
|
(Type
|
||||||
(Function
|
(SimpleType
|
||||||
(Statements
|
(TypeIdentifier "string"))))))
|
||||||
(Statements
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block)
|
||||||
(Identifier))
|
(ParameterList
|
||||||
(Statements
|
(ParameterDeclaration
|
||||||
(Identifier)
|
(Type
|
||||||
(Identifier)))
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "int"))))
|
||||||
(Statements))
|
(ParameterDeclaration
|
||||||
(Function
|
(Type
|
||||||
(Statements)
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "error")))))
|
||||||
(NoOp
|
(Identifier "fc")
|
||||||
(Empty)))
|
(ParameterList))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block)
|
||||||
(Identifier)
|
(ParameterList
|
||||||
(Empty))
|
(ParameterDeclaration
|
||||||
(Function
|
(Identifier "result")
|
||||||
(Context
|
(Type
|
||||||
(Comment)
|
(SimpleType
|
||||||
(Empty))
|
(TypeIdentifier "int"))))
|
||||||
(Identifier)
|
(ParameterDeclaration
|
||||||
(Statements
|
(Identifier "err")
|
||||||
(Identifier)
|
(Type
|
||||||
(Pointer
|
(SimpleType
|
||||||
(Identifier)))
|
(TypeIdentifier "error")))))
|
||||||
(Statements)))
|
(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"))))))))))
|
||||||
|
@ -1,21 +1,37 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Assignment
|
(Statement
|
||||||
(Identifier)
|
(ConstDeclaration
|
||||||
(Function
|
(ConstSpec
|
||||||
(Statements
|
(ExpressionList
|
||||||
(Statements
|
(Expression
|
||||||
(Identifier))
|
(FuncLiteral
|
||||||
(Statements
|
(Block
|
||||||
(Identifier)))
|
(Statement
|
||||||
(Empty)
|
(ReturnStatement
|
||||||
(Statements
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(IntLiteral "1"))
|
||||||
(Return
|
(Expression
|
||||||
(Statements
|
(IntLiteral "2"))))))
|
||||||
(Integer)
|
(ParameterList
|
||||||
(Integer)))))))
|
(ParameterDeclaration
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "int"))))
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "int")))))
|
||||||
|
(ParameterList
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Identifier "s")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "string"))))))))
|
||||||
|
(Identifier "s1")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,21 +1,37 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Assignment
|
(Statement
|
||||||
(Identifier)
|
(ConstDeclaration
|
||||||
(Function
|
(ConstSpec
|
||||||
(Statements
|
(ExpressionList
|
||||||
(Statements
|
(Expression
|
||||||
(Identifier))
|
(FuncLiteral
|
||||||
(Statements
|
(Block
|
||||||
(Identifier)))
|
(Statement
|
||||||
(Empty)
|
(ReturnStatement
|
||||||
(Statements
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(IntLiteral "1"))
|
||||||
(Return
|
(Expression
|
||||||
(Statements
|
(IntLiteral "2"))))))
|
||||||
(Integer)
|
(ParameterList
|
||||||
(Integer)))))))
|
(ParameterDeclaration
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "string"))))
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "string")))))
|
||||||
|
(ParameterList
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Identifier "b")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "int"))))))))
|
||||||
|
(Identifier "s1")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,24 +1,44 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Type
|
(TypeDeclaration
|
||||||
(Identifier)
|
(TypeSpec
|
||||||
(Function
|
(TypeIdentifier "a")
|
||||||
(Statements
|
(Type
|
||||||
(Identifier))
|
(SimpleType
|
||||||
(Identifier)))
|
(FunctionType
|
||||||
(Type
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "int"))
|
||||||
(Function
|
(ParameterList
|
||||||
(Statements
|
(ParameterDeclaration
|
||||||
(Identifier))
|
(Type
|
||||||
(Statements
|
(SimpleType
|
||||||
(Identifier))
|
(TypeIdentifier "int")))))))))
|
||||||
(Statements
|
(TypeSpec
|
||||||
(Statements
|
(TypeIdentifier "b")
|
||||||
(Identifier))
|
(Type
|
||||||
(Statements
|
(SimpleType
|
||||||
(Identifier))))))))
|
(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)))
|
||||||
|
@ -1,25 +1,47 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Type
|
(TypeDeclaration
|
||||||
(Identifier)
|
(TypeSpec
|
||||||
(Function
|
(TypeIdentifier "x")
|
||||||
(Statements
|
(Type
|
||||||
(Identifier))
|
(SimpleType
|
||||||
(Identifier)))
|
(FunctionType
|
||||||
(Type
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "string"))
|
||||||
(Function
|
(ParameterList
|
||||||
(Statements
|
(ParameterDeclaration
|
||||||
(Identifier))
|
(Type
|
||||||
(Statements
|
(SimpleType
|
||||||
(Identifier))
|
(TypeIdentifier "string")))))))))
|
||||||
(Statements
|
(TypeSpec
|
||||||
(Statements
|
(TypeIdentifier "y")
|
||||||
(BidirectionalChannel
|
(Type
|
||||||
(Identifier)))
|
(SimpleType
|
||||||
(Statements
|
(FunctionType
|
||||||
(Identifier))))))))
|
(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)))
|
||||||
|
@ -1,20 +1,27 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Defer
|
(DeferStatement
|
||||||
(Call
|
(Expression
|
||||||
(MemberAccess
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(SelectorExpression
|
||||||
(Statements)
|
(FieldIdentifier "y")
|
||||||
(Empty)))
|
(Expression
|
||||||
(Go
|
(Identifier "x"))))
|
||||||
(Call
|
(ArgumentList)))))
|
||||||
(MemberAccess
|
(Statement
|
||||||
(Identifier)
|
(GoStatement
|
||||||
(Identifier))
|
(Expression
|
||||||
(Statements)
|
(CallExpression
|
||||||
(Empty))))))
|
(Expression
|
||||||
|
(SelectorExpression
|
||||||
|
(FieldIdentifier "y")
|
||||||
|
(Expression
|
||||||
|
(Identifier "x"))))
|
||||||
|
(ArgumentList))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,20 +1,27 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Defer
|
(DeferStatement
|
||||||
(Call
|
(Expression
|
||||||
(MemberAccess
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(SelectorExpression
|
||||||
(Statements)
|
(FieldIdentifier "b")
|
||||||
(Empty)))
|
(Expression
|
||||||
(Go
|
(Identifier "a"))))
|
||||||
(Call
|
(ArgumentList)))))
|
||||||
(MemberAccess
|
(Statement
|
||||||
(Identifier)
|
(GoStatement
|
||||||
(Identifier))
|
(Expression
|
||||||
(Statements)
|
(CallExpression
|
||||||
(Empty))))))
|
(Expression
|
||||||
|
(SelectorExpression
|
||||||
|
(FieldIdentifier "d")
|
||||||
|
(Expression
|
||||||
|
(Identifier "c"))))
|
||||||
|
(ArgumentList))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,13 +1,17 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Statements
|
(ImportDeclaration
|
||||||
(QualifiedImport
|
(ImportSpecList
|
||||||
(Identifier))
|
(ImportSpec
|
||||||
(Import
|
(InterpretedStringLiteral))
|
||||||
(TextElement))
|
(ImportSpec
|
||||||
(QualifiedImport
|
(InterpretedStringLiteral)
|
||||||
(Identifier)))
|
(Dot "."))
|
||||||
(Function
|
(ImportSpec
|
||||||
(Identifier)
|
(InterpretedStringLiteral)
|
||||||
(Statements)))
|
(PackageIdentifier "alias"))))
|
||||||
|
(FunctionDeclaration
|
||||||
|
(Block)
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,13 +1,17 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Statements
|
(ImportDeclaration
|
||||||
(QualifiedImport
|
(ImportSpecList
|
||||||
(Identifier))
|
(ImportSpec
|
||||||
(Import
|
(InterpretedStringLiteral))
|
||||||
(TextElement))
|
(ImportSpec
|
||||||
(QualifiedImport
|
(InterpretedStringLiteral)
|
||||||
(Identifier)))
|
(Dot "."))
|
||||||
(Function
|
(ImportSpec
|
||||||
(Identifier)
|
(InterpretedStringLiteral)
|
||||||
(Statements)))
|
(PackageIdentifier "alias"))))
|
||||||
|
(FunctionDeclaration
|
||||||
|
(Block)
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,12 +1,19 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(VarDeclaration
|
||||||
(Identifier)
|
(VarSpec
|
||||||
(Integer))
|
(ExpressionList
|
||||||
(Assignment
|
(Expression
|
||||||
(Identifier)
|
(IntLiteral "0")))
|
||||||
(Integer)))))
|
(Identifier "zero"))
|
||||||
|
(VarSpec
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(IntLiteral "1")))
|
||||||
|
(Identifier "one")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,12 +1,19 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(VarDeclaration
|
||||||
(Identifier)
|
(VarSpec
|
||||||
(Integer))
|
(ExpressionList
|
||||||
(Assignment
|
(Expression
|
||||||
(Identifier)
|
(IntLiteral "0")))
|
||||||
(Integer)))))
|
(Identifier "a"))
|
||||||
|
(VarSpec
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(IntLiteral "1")))
|
||||||
|
(Identifier "b")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
202
test/fixtures/go/corpus/if-statements.parseA.txt
vendored
202
test/fixtures/go/corpus/if-statements.parseA.txt
vendored
@ -1,79 +1,123 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(If
|
(IfStatement
|
||||||
(Statements
|
(Block
|
||||||
(Call
|
(Statement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Statements)
|
(Expression
|
||||||
(Empty)))
|
(CallExpression
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(Identifier "b"))
|
||||||
(Statements)
|
(ArgumentList))))))
|
||||||
(Empty))
|
(Expression
|
||||||
(Empty))
|
(CallExpression
|
||||||
(If
|
(Expression
|
||||||
(Statements
|
(Identifier "a"))
|
||||||
(Assignment
|
(ArgumentList)))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Call
|
(IfStatement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Statements)
|
(ShortVarDeclaration
|
||||||
(Empty)))
|
(ExpressionList
|
||||||
(Identifier))
|
(Expression
|
||||||
(Call
|
(Identifier "a")))
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Statements)
|
(Expression
|
||||||
(Empty))
|
(CallExpression
|
||||||
(Empty))
|
(Expression
|
||||||
(If
|
(Identifier "b"))
|
||||||
(Statements
|
(ArgumentList))))))
|
||||||
(Call
|
(Block
|
||||||
(Identifier)
|
(Statement
|
||||||
(Statements)
|
(SimpleStatement
|
||||||
(Empty)))
|
(Expression
|
||||||
(Call
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements)
|
(Identifier "d"))
|
||||||
(Empty))
|
(ArgumentList))))))
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(Identifier "c"))))
|
||||||
(Statements)
|
(Statement
|
||||||
(Empty)))
|
(IfStatement
|
||||||
(If
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(SimpleStatement
|
||||||
(Identifier)
|
(Expression
|
||||||
(Integer))
|
(CallExpression
|
||||||
(LessThan
|
(Expression
|
||||||
(Identifier)
|
(Identifier "c"))
|
||||||
(Integer)))
|
(ArgumentList))))))
|
||||||
(Call
|
(Block
|
||||||
(Identifier)
|
(Statement
|
||||||
(Statements)
|
(SimpleStatement
|
||||||
(Empty))
|
(Expression
|
||||||
(If
|
(CallExpression
|
||||||
(Statements
|
(Expression
|
||||||
(LessThan
|
(Identifier "b"))
|
||||||
(Identifier)
|
(ArgumentList))))))
|
||||||
(Integer)))
|
(Expression
|
||||||
(Call
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements)
|
(Identifier "a"))
|
||||||
(Empty))
|
(ArgumentList)))))
|
||||||
(Context
|
(Statement
|
||||||
(Comment)
|
(IfStatement
|
||||||
(If
|
(IfStatement
|
||||||
(Statements
|
(IfStatement
|
||||||
(Call
|
(Block
|
||||||
(Identifier)
|
(Statement
|
||||||
(Statements)
|
(SimpleStatement
|
||||||
(Empty)))
|
(Expression
|
||||||
(Call
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements)
|
(Identifier "g"))
|
||||||
(Empty))
|
(ArgumentList))))))
|
||||||
(Empty))))))))
|
(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)))
|
||||||
|
189
test/fixtures/go/corpus/if-statements.parseB.txt
vendored
189
test/fixtures/go/corpus/if-statements.parseB.txt
vendored
@ -1,72 +1,117 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(If
|
(IfStatement
|
||||||
(Statements
|
(Block
|
||||||
(Call
|
(Statement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Statements)
|
(Expression
|
||||||
(Empty)))
|
(CallExpression
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(Identifier "b"))
|
||||||
(Statements)
|
(ArgumentList))))))
|
||||||
(Empty))
|
(Expression
|
||||||
(Empty))
|
(CallExpression
|
||||||
(If
|
(Expression
|
||||||
(Statements
|
(Identifier "x"))
|
||||||
(Assignment
|
(ArgumentList)))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Call
|
(IfStatement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Statements)
|
(ShortVarDeclaration
|
||||||
(Empty)))
|
(ExpressionList
|
||||||
(Identifier))
|
(Expression
|
||||||
(Call
|
(Identifier "y")))
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Statements)
|
(Expression
|
||||||
(Empty))
|
(CallExpression
|
||||||
(Empty))
|
(Expression
|
||||||
(If
|
(Identifier "b"))
|
||||||
(Statements
|
(ArgumentList))))))
|
||||||
(Call
|
(Block
|
||||||
(Identifier)
|
(Statement
|
||||||
(Statements)
|
(SimpleStatement
|
||||||
(Empty)))
|
(Expression
|
||||||
(Call
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements)
|
(Identifier "d"))
|
||||||
(Empty))
|
(ArgumentList))))))
|
||||||
(Call
|
(Expression
|
||||||
(Identifier)
|
(Identifier "c"))))
|
||||||
(Statements)
|
(Statement
|
||||||
(Empty)))
|
(IfStatement
|
||||||
(If
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(SimpleStatement
|
||||||
(Identifier)
|
(Expression
|
||||||
(Integer))
|
(CallExpression
|
||||||
(LessThan
|
(Expression
|
||||||
(Identifier)
|
(Identifier "c"))
|
||||||
(Integer)))
|
(ArgumentList))))))
|
||||||
(Call
|
(Block
|
||||||
(Identifier)
|
(Statement
|
||||||
(Statements)
|
(SimpleStatement
|
||||||
(Empty))
|
(Expression
|
||||||
(Context
|
(CallExpression
|
||||||
(Comment)
|
(Expression
|
||||||
(If
|
(Identifier "b"))
|
||||||
(Statements
|
(ArgumentList))))))
|
||||||
(LessThan
|
(Expression
|
||||||
(Identifier)
|
(CallExpression
|
||||||
(Integer)))
|
(Expression
|
||||||
(Call
|
(Identifier "z"))
|
||||||
(Identifier)
|
(ArgumentList)))))
|
||||||
(Statements)
|
(Statement
|
||||||
(Empty))
|
(IfStatement
|
||||||
(Call
|
(IfStatement
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements)
|
(Statement
|
||||||
(Empty))))))))
|
(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)))
|
||||||
|
@ -1,12 +1,19 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(ConstDeclaration
|
||||||
(Identifier)
|
(ConstSpec
|
||||||
(Complex))
|
(ExpressionList
|
||||||
(Assignment
|
(Expression
|
||||||
(Identifier)
|
(ImaginaryLiteral "01i")))
|
||||||
(Complex)))))
|
(Identifier "a"))
|
||||||
|
(ConstSpec
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(ImaginaryLiteral "1.e+100i")))
|
||||||
|
(Identifier "b")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,12 +1,19 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(ConstDeclaration
|
||||||
(Identifier)
|
(ConstSpec
|
||||||
(Complex))
|
(ExpressionList
|
||||||
(Assignment
|
(Expression
|
||||||
(Identifier)
|
(ImaginaryLiteral "02i")))
|
||||||
(Complex)))))
|
(Identifier "a"))
|
||||||
|
(ConstSpec
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(ImaginaryLiteral "1.e+103i")))
|
||||||
|
(Identifier "b")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,12 +1,11 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Statements
|
(ImportDeclaration
|
||||||
(Comment)
|
(ImportSpecList
|
||||||
(Comment)
|
(ImportSpec
|
||||||
(QualifiedImport
|
(InterpretedStringLiteral))))
|
||||||
(Identifier))
|
(FunctionDeclaration
|
||||||
(Comment))
|
(Block)
|
||||||
(Function
|
(Identifier "main")
|
||||||
(Identifier)
|
(ParameterList)))
|
||||||
(Statements)))
|
|
||||||
|
@ -1,12 +1,11 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Statements
|
(ImportDeclaration
|
||||||
(Comment)
|
(ImportSpecList
|
||||||
(Comment)
|
(ImportSpec
|
||||||
(QualifiedImport
|
(InterpretedStringLiteral))))
|
||||||
(Identifier))
|
(FunctionDeclaration
|
||||||
(Comment))
|
(Block)
|
||||||
(Function
|
(Identifier "main")
|
||||||
(Identifier)
|
(ParameterList)))
|
||||||
(Statements)))
|
|
||||||
|
@ -1,10 +1,17 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(PostIncrement
|
(SimpleStatement
|
||||||
(Identifier))
|
(IncStatement
|
||||||
(PostDecrement
|
(Expression
|
||||||
(Identifier)))))
|
(Identifier "i")))))
|
||||||
|
(Statement
|
||||||
|
(SimpleStatement
|
||||||
|
(DecStatement
|
||||||
|
(Expression
|
||||||
|
(Identifier "j"))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,10 +1,17 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(PostIncrement
|
(SimpleStatement
|
||||||
(Identifier))
|
(IncStatement
|
||||||
(PostIncrement
|
(Expression
|
||||||
(Identifier)))))
|
(Identifier "foo")))))
|
||||||
|
(Statement
|
||||||
|
(SimpleStatement
|
||||||
|
(IncStatement
|
||||||
|
(Expression
|
||||||
|
(Identifier "x"))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
39
test/fixtures/go/corpus/int-literals.parseA.txt
vendored
39
test/fixtures/go/corpus/int-literals.parseA.txt
vendored
@ -1,15 +1,24 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(ConstDeclaration
|
||||||
(Identifier)
|
(ConstSpec
|
||||||
(Integer))
|
(ExpressionList
|
||||||
(Assignment
|
(Expression
|
||||||
(Identifier)
|
(IntLiteral "1")))
|
||||||
(Integer))
|
(Identifier "a"))
|
||||||
(Assignment
|
(ConstSpec
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Integer)))))
|
(Expression
|
||||||
|
(IntLiteral "2")))
|
||||||
|
(Identifier "b"))
|
||||||
|
(ConstSpec
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(IntLiteral "3")))
|
||||||
|
(Identifier "c")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
39
test/fixtures/go/corpus/int-literals.parseB.txt
vendored
39
test/fixtures/go/corpus/int-literals.parseB.txt
vendored
@ -1,15 +1,24 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Assignment
|
(ConstDeclaration
|
||||||
(Identifier)
|
(ConstSpec
|
||||||
(Integer))
|
(ExpressionList
|
||||||
(Assignment
|
(Expression
|
||||||
(Identifier)
|
(IntLiteral "4")))
|
||||||
(Integer))
|
(Identifier "a"))
|
||||||
(Assignment
|
(ConstSpec
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Integer)))))
|
(Expression
|
||||||
|
(IntLiteral "5")))
|
||||||
|
(Identifier "b"))
|
||||||
|
(ConstSpec
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(IntLiteral "6")))
|
||||||
|
(Identifier "c")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
101
test/fixtures/go/corpus/interface-types.parseA.txt
vendored
101
test/fixtures/go/corpus/interface-types.parseA.txt
vendored
@ -1,42 +1,59 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Statements
|
(TypeDeclaration
|
||||||
(Type
|
(TypeSpec
|
||||||
(Identifier)
|
(TypeIdentifier "i1")
|
||||||
(Interface
|
(Type
|
||||||
(Statements))))
|
(SimpleType
|
||||||
(Statements
|
(InterfaceType
|
||||||
(Type
|
(MethodSpecList)))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Interface
|
(TypeDeclaration
|
||||||
(MemberAccess
|
(TypeSpec
|
||||||
(Identifier)
|
(TypeIdentifier "i2")
|
||||||
(Identifier)))))
|
(Type
|
||||||
(Statements
|
(SimpleType
|
||||||
(Type
|
(InterfaceType
|
||||||
(Identifier)
|
(MethodSpecList
|
||||||
(Interface
|
(QualifiedType
|
||||||
(Statements
|
(TypeIdentifier "Reader")
|
||||||
(Identifier)
|
(PackageIdentifier "io")))))))))
|
||||||
(MemberAccess
|
(Statement
|
||||||
(Identifier)
|
(TypeDeclaration
|
||||||
(Identifier))
|
(TypeSpec
|
||||||
(MethodSignature
|
(TypeIdentifier "i3")
|
||||||
(Identifier)
|
(Type
|
||||||
(Identifier)
|
(SimpleType
|
||||||
(Statements
|
(InterfaceType
|
||||||
(Identifier)
|
(MethodSpecList
|
||||||
(Identifier)))))))
|
(TypeIdentifier "i1")
|
||||||
(Context
|
(QualifiedType
|
||||||
(Comment)
|
(TypeIdentifier "Reader")
|
||||||
(Statements
|
(PackageIdentifier "io"))
|
||||||
(Type
|
(MethodSpec
|
||||||
(Identifier)
|
(SimpleType
|
||||||
(Interface
|
(TypeIdentifier "error"))
|
||||||
(MethodSignature
|
(FieldIdentifier "SomeMethod")
|
||||||
(Empty)
|
(ParameterList
|
||||||
(Identifier)))))))))
|
(ParameterDeclaration
|
||||||
|
(Identifier "s")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "string")))))))))))))
|
||||||
|
(Statement
|
||||||
|
(TypeDeclaration
|
||||||
|
(TypeSpec
|
||||||
|
(TypeIdentifier "OptionA")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(InterfaceType
|
||||||
|
(MethodSpecList
|
||||||
|
(MethodSpec
|
||||||
|
(FieldIdentifier "public")
|
||||||
|
(ParameterList))))))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
101
test/fixtures/go/corpus/interface-types.parseB.txt
vendored
101
test/fixtures/go/corpus/interface-types.parseB.txt
vendored
@ -1,42 +1,59 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Statements
|
(TypeDeclaration
|
||||||
(Type
|
(TypeSpec
|
||||||
(Identifier)
|
(TypeIdentifier "j1")
|
||||||
(Interface
|
(Type
|
||||||
(Statements))))
|
(SimpleType
|
||||||
(Statements
|
(InterfaceType
|
||||||
(Type
|
(MethodSpecList)))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Interface
|
(TypeDeclaration
|
||||||
(MemberAccess
|
(TypeSpec
|
||||||
(Identifier)
|
(TypeIdentifier "j2")
|
||||||
(Identifier)))))
|
(Type
|
||||||
(Statements
|
(SimpleType
|
||||||
(Type
|
(InterfaceType
|
||||||
(Identifier)
|
(MethodSpecList
|
||||||
(Interface
|
(QualifiedType
|
||||||
(Statements
|
(TypeIdentifier "Reader")
|
||||||
(Identifier)
|
(PackageIdentifier "io")))))))))
|
||||||
(MemberAccess
|
(Statement
|
||||||
(Identifier)
|
(TypeDeclaration
|
||||||
(Identifier))
|
(TypeSpec
|
||||||
(MethodSignature
|
(TypeIdentifier "j3")
|
||||||
(Identifier)
|
(Type
|
||||||
(Identifier)
|
(SimpleType
|
||||||
(Statements
|
(InterfaceType
|
||||||
(Identifier)
|
(MethodSpecList
|
||||||
(Identifier)))))))
|
(TypeIdentifier "i1")
|
||||||
(Context
|
(QualifiedType
|
||||||
(Comment)
|
(TypeIdentifier "Reader")
|
||||||
(Statements
|
(PackageIdentifier "io"))
|
||||||
(Type
|
(MethodSpec
|
||||||
(Identifier)
|
(SimpleType
|
||||||
(Interface
|
(TypeIdentifier "error"))
|
||||||
(MethodSignature
|
(FieldIdentifier "SomeMethod")
|
||||||
(Empty)
|
(ParameterList
|
||||||
(Identifier)))))))))
|
(ParameterDeclaration
|
||||||
|
(Identifier "s")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "string")))))))))))))
|
||||||
|
(Statement
|
||||||
|
(TypeDeclaration
|
||||||
|
(TypeSpec
|
||||||
|
(TypeIdentifier "OptionB")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(InterfaceType
|
||||||
|
(MethodSpecList
|
||||||
|
(MethodSpec
|
||||||
|
(FieldIdentifier "private")
|
||||||
|
(ParameterList))))))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,38 +1,57 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Label
|
(LabeledStatement
|
||||||
(Identifier)
|
(LabelName "L")
|
||||||
(NoOp
|
(Statement
|
||||||
(Empty)))
|
(EmptyStatement ";"))))
|
||||||
(Context
|
(Statement
|
||||||
(Comment)
|
(LabeledStatement
|
||||||
(Label
|
(LabelName "L1")
|
||||||
(Identifier)
|
(Statement
|
||||||
(Context
|
(Block
|
||||||
(Comment)
|
(Statement
|
||||||
(For
|
(ForStatement
|
||||||
(Assignment
|
(Block
|
||||||
(Identifier)
|
(Statement
|
||||||
(Integer))
|
(SimpleStatement
|
||||||
(LessThan
|
(Expression
|
||||||
(Identifier)
|
(CallExpression
|
||||||
(Integer))
|
(Expression
|
||||||
(PostIncrement
|
(Identifier "println"))
|
||||||
(Identifier))
|
(ArgumentList
|
||||||
(Statements
|
(Expression
|
||||||
(Call
|
(Identifier "i")))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier)
|
(BreakStatement
|
||||||
(Empty))
|
(LabelName "L1"))))
|
||||||
(Break
|
(ForClause
|
||||||
(Identifier))
|
(SimpleStatement
|
||||||
(Context
|
(ShortVarDeclaration
|
||||||
(Comment)
|
(ExpressionList
|
||||||
(Empty)))))))
|
(Expression
|
||||||
(Label
|
(Identifier "i")))
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Empty)))))
|
(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)))
|
||||||
|
@ -1,38 +1,57 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Label
|
(LabeledStatement
|
||||||
(Identifier)
|
(LabelName "M")
|
||||||
(NoOp
|
(Statement
|
||||||
(Empty)))
|
(EmptyStatement ";"))))
|
||||||
(Context
|
(Statement
|
||||||
(Comment)
|
(LabeledStatement
|
||||||
(Label
|
(LabelName "M1")
|
||||||
(Identifier)
|
(Statement
|
||||||
(Context
|
(Block
|
||||||
(Comment)
|
(Statement
|
||||||
(For
|
(ForStatement
|
||||||
(Assignment
|
(Block
|
||||||
(Identifier)
|
(Statement
|
||||||
(Integer))
|
(SimpleStatement
|
||||||
(LessThan
|
(Expression
|
||||||
(Identifier)
|
(CallExpression
|
||||||
(Integer))
|
(Expression
|
||||||
(PostIncrement
|
(Identifier "println"))
|
||||||
(Identifier))
|
(ArgumentList
|
||||||
(Statements
|
(Expression
|
||||||
(Call
|
(Identifier "i")))))))
|
||||||
(Identifier)
|
(Statement
|
||||||
(Identifier)
|
(BreakStatement
|
||||||
(Empty))
|
(LabelName "M1"))))
|
||||||
(Break
|
(ForClause
|
||||||
(Identifier))
|
(SimpleStatement
|
||||||
(Context
|
(ShortVarDeclaration
|
||||||
(Comment)
|
(ExpressionList
|
||||||
(Empty)))))))
|
(Expression
|
||||||
(Label
|
(Identifier "i")))
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Empty)))))
|
(Expression
|
||||||
|
(IntLiteral "0")))))
|
||||||
|
(Expression
|
||||||
|
(BinaryExpression
|
||||||
|
(Token)
|
||||||
|
(Expression
|
||||||
|
(Identifier "i"))
|
||||||
|
(Expression
|
||||||
|
(IntLiteral "10"))))
|
||||||
|
(SimpleStatement
|
||||||
|
(IncStatement
|
||||||
|
(Expression
|
||||||
|
(Identifier "i")))))))))))
|
||||||
|
(Statement
|
||||||
|
(Block
|
||||||
|
(Statement
|
||||||
|
(LabeledStatement
|
||||||
|
(LabelName "replacement"))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
50
test/fixtures/go/corpus/map-literals.parseA.txt
vendored
50
test/fixtures/go/corpus/map-literals.parseA.txt
vendored
@ -1,18 +1,32 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Assignment
|
(Statement
|
||||||
(Identifier)
|
(ConstDeclaration
|
||||||
(Composite
|
(ConstSpec
|
||||||
(Map
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(CompositeLiteral
|
||||||
(Statements
|
(LiteralValue
|
||||||
(KeyValue
|
(KeyedElement
|
||||||
(TextElement)
|
(Expression
|
||||||
(TextElement))
|
(InterpretedStringLiteral))
|
||||||
(KeyValue
|
(Expression
|
||||||
(TextElement)
|
(InterpretedStringLiteral)))
|
||||||
(TextElement)))))))
|
(KeyedElement
|
||||||
|
(Expression
|
||||||
|
(InterpretedStringLiteral))
|
||||||
|
(Expression
|
||||||
|
(InterpretedStringLiteral))))
|
||||||
|
(MapType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "string")))
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "string")))))))
|
||||||
|
(Identifier "s")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
50
test/fixtures/go/corpus/map-literals.parseB.txt
vendored
50
test/fixtures/go/corpus/map-literals.parseB.txt
vendored
@ -1,18 +1,32 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Assignment
|
(Statement
|
||||||
(Identifier)
|
(ConstDeclaration
|
||||||
(Composite
|
(ConstSpec
|
||||||
(Map
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(CompositeLiteral
|
||||||
(Statements
|
(LiteralValue
|
||||||
(KeyValue
|
(KeyedElement
|
||||||
(TextElement)
|
(Expression
|
||||||
(TextElement))
|
(InterpretedStringLiteral))
|
||||||
(KeyValue
|
(Expression
|
||||||
(TextElement)
|
(InterpretedStringLiteral)))
|
||||||
(TextElement)))))))
|
(KeyedElement
|
||||||
|
(Expression
|
||||||
|
(InterpretedStringLiteral))
|
||||||
|
(Expression
|
||||||
|
(InterpretedStringLiteral))))
|
||||||
|
(MapType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "int")))
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "string")))))))
|
||||||
|
(Identifier "s")))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
31
test/fixtures/go/corpus/map-types.parseA.txt
vendored
31
test/fixtures/go/corpus/map-types.parseA.txt
vendored
@ -1,11 +1,20 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Type
|
(TypeDeclaration
|
||||||
(Identifier)
|
(TypeSpec
|
||||||
(Map
|
(TypeIdentifier "m1")
|
||||||
(Identifier)
|
(Type
|
||||||
(Identifier))))))
|
(SimpleType
|
||||||
|
(MapType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "error")))
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "string"))))))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
31
test/fixtures/go/corpus/map-types.parseB.txt
vendored
31
test/fixtures/go/corpus/map-types.parseB.txt
vendored
@ -1,11 +1,20 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Type
|
(TypeDeclaration
|
||||||
(Identifier)
|
(TypeSpec
|
||||||
(Map
|
(TypeIdentifier "m1")
|
||||||
(Identifier)
|
(Type
|
||||||
(Identifier))))))
|
(SimpleType
|
||||||
|
(MapType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "error")))
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "int"))))))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,84 +1,153 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block)
|
||||||
(Statements))
|
(Identifier "main")
|
||||||
(Method
|
(ParameterList))
|
||||||
(Statements
|
(MethodDeclaration
|
||||||
(Identifier))
|
(ParameterList
|
||||||
(Identifier)
|
(ParameterDeclaration
|
||||||
(Empty))
|
(Type
|
||||||
(Method
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "s")))))
|
||||||
(Statements
|
(FieldIdentifier "Method")
|
||||||
(Identifier)
|
(ParameterList))
|
||||||
(Identifier))
|
(MethodDeclaration
|
||||||
(Identifier)
|
(Block)
|
||||||
(Statements
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "bool"))
|
||||||
(Identifier))
|
(ParameterList
|
||||||
(Statements))
|
(ParameterDeclaration
|
||||||
(Method
|
(Identifier "self")
|
||||||
(Identifier)
|
(Type
|
||||||
(Statements
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "Person")))))
|
||||||
(Pointer
|
(FieldIdentifier "Equals")
|
||||||
(Identifier)))
|
(ParameterList
|
||||||
(Identifier)
|
(ParameterDeclaration
|
||||||
(Return
|
(Identifier "other")
|
||||||
(Call
|
(Type
|
||||||
(MemberAccess
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "Person"))))))
|
||||||
(Identifier))
|
(MethodDeclaration
|
||||||
(Plus
|
(Block
|
||||||
(Times
|
(Statement
|
||||||
(MemberAccess
|
(ReturnStatement
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Identifier))
|
(Expression
|
||||||
(MemberAccess
|
(CallExpression
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier)))
|
(SelectorExpression
|
||||||
(Times
|
(FieldIdentifier "Sqrt")
|
||||||
(MemberAccess
|
(Expression
|
||||||
(Identifier)
|
(Identifier "math"))))
|
||||||
(Identifier))
|
(ArgumentList
|
||||||
(MemberAccess
|
(Expression
|
||||||
(Identifier)
|
(BinaryExpression
|
||||||
(Identifier))))
|
(Token)
|
||||||
(Empty))))
|
(Expression
|
||||||
(Method
|
(BinaryExpression
|
||||||
(Statements
|
(Token)
|
||||||
(AugmentedAssignment
|
(Expression
|
||||||
(Times
|
(SelectorExpression
|
||||||
(MemberAccess
|
(FieldIdentifier "x")
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(Identifier "p"))))
|
||||||
(Identifier)))
|
(Expression
|
||||||
(AugmentedAssignment
|
(SelectorExpression
|
||||||
(Times
|
(FieldIdentifier "x")
|
||||||
(MemberAccess
|
(Expression
|
||||||
(Identifier)
|
(Identifier "p"))))))
|
||||||
(Identifier))
|
(Expression
|
||||||
(Identifier))))
|
(BinaryExpression
|
||||||
(Statements
|
(Token)
|
||||||
(Identifier)
|
(Expression
|
||||||
(Pointer
|
(SelectorExpression
|
||||||
(Identifier)))
|
(FieldIdentifier "y")
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements
|
(Identifier "p"))))
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(SelectorExpression
|
||||||
(Empty))
|
(FieldIdentifier "y")
|
||||||
(Method
|
(Expression
|
||||||
(Identifier)
|
(Identifier "p")))))))))))))))
|
||||||
(Statements
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "float64"))
|
||||||
(Pointer
|
(ParameterList
|
||||||
(Identifier)))
|
(ParameterDeclaration
|
||||||
(Identifier)
|
(Identifier "p")
|
||||||
(Statements
|
(Type
|
||||||
(Identifier)
|
(SimpleType
|
||||||
(Identifier)
|
(PointerType
|
||||||
(Identifier))
|
(Type
|
||||||
(Statements)))
|
(SimpleType
|
||||||
|
(TypeIdentifier "Point"))))))))
|
||||||
|
(FieldIdentifier "Length")
|
||||||
|
(ParameterList))
|
||||||
|
(MethodDeclaration
|
||||||
|
(Block
|
||||||
|
(Statement
|
||||||
|
(SimpleStatement
|
||||||
|
(AssignmentStatement
|
||||||
|
(Token)
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(SelectorExpression
|
||||||
|
(FieldIdentifier "x")
|
||||||
|
(Expression
|
||||||
|
(Identifier "p")))))
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(Identifier "factor"))))))
|
||||||
|
(Statement
|
||||||
|
(SimpleStatement
|
||||||
|
(AssignmentStatement
|
||||||
|
(Token)
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(SelectorExpression
|
||||||
|
(FieldIdentifier "y")
|
||||||
|
(Expression
|
||||||
|
(Identifier "p")))))
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(Identifier "factor")))))))
|
||||||
|
(ParameterList
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Identifier "p")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(PointerType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "Point"))))))))
|
||||||
|
(FieldIdentifier "Scale")
|
||||||
|
(ParameterList
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Identifier "factor")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "float64"))))))
|
||||||
|
(MethodDeclaration
|
||||||
|
(Block)
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "bool"))
|
||||||
|
(ParameterList
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Identifier "f")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(PointerType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "Field"))))))))
|
||||||
|
(FieldIdentifier "Alive")
|
||||||
|
(ParameterList
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Identifier "x")
|
||||||
|
(Token)
|
||||||
|
(Identifier "y")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "int")))))))
|
||||||
|
@ -1,98 +1,173 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block)
|
||||||
(Statements))
|
(Identifier "main")
|
||||||
(Method
|
(ParameterList))
|
||||||
(Statements
|
(MethodDeclaration
|
||||||
(Identifier))
|
(ParameterList
|
||||||
(Identifier)
|
(ParameterDeclaration
|
||||||
(Empty))
|
(Type
|
||||||
(Method
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "s")))))
|
||||||
(Statements
|
(FieldIdentifier "Methods")
|
||||||
(Identifier)
|
(ParameterList))
|
||||||
(Identifier))
|
(MethodDeclaration
|
||||||
(Identifier)
|
(Block)
|
||||||
(Statements
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "bool"))
|
||||||
(Identifier))
|
(ParameterList
|
||||||
(Statements))
|
(ParameterDeclaration
|
||||||
(Method
|
(Identifier "self")
|
||||||
(Identifier)
|
(Type
|
||||||
(Statements
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "Num")))))
|
||||||
(Pointer
|
(FieldIdentifier "Equals")
|
||||||
(Identifier)))
|
(ParameterList
|
||||||
(Identifier)
|
(ParameterDeclaration
|
||||||
(Return
|
(Identifier "other")
|
||||||
(Call
|
(Type
|
||||||
(MemberAccess
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "Num"))))))
|
||||||
(Identifier))
|
(MethodDeclaration
|
||||||
(Plus
|
(Block
|
||||||
(Plus
|
(Statement
|
||||||
(Plus
|
(ReturnStatement
|
||||||
(Call
|
(ExpressionList
|
||||||
(MemberAccess
|
(Expression
|
||||||
(Identifier)
|
(CallExpression
|
||||||
(Identifier))
|
(Expression
|
||||||
(Statements
|
(SelectorExpression
|
||||||
(MemberAccess
|
(FieldIdentifier "Sqrt")
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(Identifier "math"))))
|
||||||
(Integer))
|
(ArgumentList
|
||||||
(Empty))
|
(Expression
|
||||||
(MemberAccess
|
(BinaryExpression
|
||||||
(Identifier)
|
(Token)
|
||||||
(Identifier)))
|
(Expression
|
||||||
(Call
|
(BinaryExpression
|
||||||
(MemberAccess
|
(Token)
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(BinaryExpression
|
||||||
(Statements
|
(Token)
|
||||||
(MemberAccess
|
(Expression
|
||||||
(Identifier)
|
(CallExpression
|
||||||
(Identifier))
|
(Expression
|
||||||
(Integer))
|
(SelectorExpression
|
||||||
(Empty)))
|
(FieldIdentifier "Pow")
|
||||||
(MemberAccess
|
(Expression
|
||||||
(Identifier)
|
(Identifier "math"))))
|
||||||
(Identifier)))
|
(ArgumentList
|
||||||
(Empty))))
|
(Expression
|
||||||
(Method
|
(SelectorExpression
|
||||||
(Statements
|
(FieldIdentifier "x")
|
||||||
(AugmentedAssignment
|
(Expression
|
||||||
(Times
|
(Identifier "p"))))
|
||||||
(MemberAccess
|
(Expression
|
||||||
(Identifier)
|
(IntLiteral "2")))))
|
||||||
(Identifier))
|
(Expression
|
||||||
(Identifier)))
|
(SelectorExpression
|
||||||
(AugmentedAssignment
|
(FieldIdentifier "x")
|
||||||
(Times
|
(Expression
|
||||||
(MemberAccess
|
(Identifier "p"))))))
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))
|
(CallExpression
|
||||||
(Identifier))))
|
(Expression
|
||||||
(Statements
|
(SelectorExpression
|
||||||
(Identifier)
|
(FieldIdentifier "Pow")
|
||||||
(Pointer
|
(Expression
|
||||||
(Identifier)))
|
(Identifier "math"))))
|
||||||
(Identifier)
|
(ArgumentList
|
||||||
(Statements
|
(Expression
|
||||||
(Identifier)
|
(SelectorExpression
|
||||||
(Identifier))
|
(FieldIdentifier "y")
|
||||||
(Empty))
|
(Expression
|
||||||
(Method
|
(Identifier "p"))))
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements
|
(IntLiteral "2")))))))
|
||||||
(Identifier)
|
(Expression
|
||||||
(Pointer
|
(SelectorExpression
|
||||||
(Identifier)))
|
(FieldIdentifier "y")
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements
|
(Identifier "p")))))))))))))
|
||||||
(Identifier)
|
(SimpleType
|
||||||
(Identifier)
|
(TypeIdentifier "float64"))
|
||||||
(Identifier))
|
(ParameterList
|
||||||
(Statements)))
|
(ParameterDeclaration
|
||||||
|
(Identifier "p")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(PointerType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "Point"))))))))
|
||||||
|
(FieldIdentifier "OtherLength")
|
||||||
|
(ParameterList))
|
||||||
|
(MethodDeclaration
|
||||||
|
(Block
|
||||||
|
(Statement
|
||||||
|
(SimpleStatement
|
||||||
|
(AssignmentStatement
|
||||||
|
(Token)
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(SelectorExpression
|
||||||
|
(FieldIdentifier "x")
|
||||||
|
(Expression
|
||||||
|
(Identifier "p")))))
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(Identifier "factor"))))))
|
||||||
|
(Statement
|
||||||
|
(SimpleStatement
|
||||||
|
(AssignmentStatement
|
||||||
|
(Token)
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(SelectorExpression
|
||||||
|
(FieldIdentifier "y")
|
||||||
|
(Expression
|
||||||
|
(Identifier "p")))))
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(Identifier "factor")))))))
|
||||||
|
(ParameterList
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Identifier "q")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(PointerType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "Point"))))))))
|
||||||
|
(FieldIdentifier "Scale")
|
||||||
|
(ParameterList
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Identifier "factor")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "int"))))))
|
||||||
|
(MethodDeclaration
|
||||||
|
(Block)
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "bool"))
|
||||||
|
(ParameterList
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Identifier "f")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(PointerType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "Field"))))))))
|
||||||
|
(FieldIdentifier "Alive")
|
||||||
|
(ParameterList
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Identifier "z")
|
||||||
|
(Token)
|
||||||
|
(Identifier "h")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "int")))))))
|
||||||
|
@ -1,14 +1,25 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Assignment
|
(Statement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Reference
|
(ShortVarDeclaration
|
||||||
(Composite
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements
|
(Identifier "ctx")))
|
||||||
(KeyValue
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Identifier))))))))
|
(UnaryExpression
|
||||||
|
(Token)
|
||||||
|
(Expression
|
||||||
|
(CompositeLiteral
|
||||||
|
(LiteralValue
|
||||||
|
(KeyedElement
|
||||||
|
(FieldIdentifier "Remote")
|
||||||
|
(Expression
|
||||||
|
(Identifier "remote"))))
|
||||||
|
(TypeIdentifier "uploadContext"))))))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,19 +1,33 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Assignment
|
(Statement
|
||||||
(Identifier)
|
(SimpleStatement
|
||||||
(Reference
|
(ShortVarDeclaration
|
||||||
(Composite
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Statements
|
(Identifier "ctx")))
|
||||||
(KeyValue
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Call
|
(UnaryExpression
|
||||||
(Identifier)
|
(Token)
|
||||||
(MemberAccess
|
(Expression
|
||||||
(Identifier)
|
(CompositeLiteral
|
||||||
(Identifier))
|
(LiteralValue
|
||||||
(Empty)))))))))
|
(KeyedElement
|
||||||
|
(FieldIdentifier "trackedLocksMu")
|
||||||
|
(Expression
|
||||||
|
(CallExpression
|
||||||
|
(Expression
|
||||||
|
(Identifier "new"))
|
||||||
|
(ArgumentList
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(QualifiedType
|
||||||
|
(TypeIdentifier "Mutex")
|
||||||
|
(PackageIdentifier "sync")))))))))
|
||||||
|
(TypeIdentifier "uploadContext"))))))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,15 +1,21 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block)
|
||||||
(Statements))
|
(Identifier "main")
|
||||||
(Function
|
(ParameterList))
|
||||||
(Identifier)
|
(FunctionDeclaration
|
||||||
(Statements
|
(Block)
|
||||||
(Identifier)
|
(Identifier "foo")
|
||||||
(Identifier))
|
(ParameterList
|
||||||
(Statements
|
(ParameterDeclaration
|
||||||
(Identifier)
|
(Identifier "a")
|
||||||
(Identifier))
|
(Type
|
||||||
(Statements)))
|
(SimpleType
|
||||||
|
(TypeIdentifier "int"))))
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Identifier "b")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "string")))))))
|
||||||
|
@ -1,15 +1,21 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block)
|
||||||
(Statements))
|
(Identifier "main")
|
||||||
(Function
|
(ParameterList))
|
||||||
(Identifier)
|
(FunctionDeclaration
|
||||||
(Statements
|
(Block)
|
||||||
(Identifier)
|
(Identifier "foo")
|
||||||
(Identifier))
|
(ParameterList
|
||||||
(Statements
|
(ParameterDeclaration
|
||||||
(Identifier)
|
(Identifier "x")
|
||||||
(Identifier))
|
(Type
|
||||||
(Statements)))
|
(SimpleType
|
||||||
|
(TypeIdentifier "string"))))
|
||||||
|
(ParameterDeclaration
|
||||||
|
(Identifier "y")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "uint64")))))))
|
||||||
|
43
test/fixtures/go/corpus/pointer-types.parseA.txt
vendored
43
test/fixtures/go/corpus/pointer-types.parseA.txt
vendored
@ -1,15 +1,28 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Type
|
(TypeDeclaration
|
||||||
(Identifier)
|
(TypeSpec
|
||||||
(Pointer
|
(TypeIdentifier "p1")
|
||||||
(Identifier)))
|
(Type
|
||||||
(Type
|
(SimpleType
|
||||||
(Identifier)
|
(PointerType
|
||||||
(Pointer
|
(Type
|
||||||
(Pointer
|
(SimpleType
|
||||||
(Identifier)))))))
|
(TypeIdentifier "string")))))))
|
||||||
|
(TypeSpec
|
||||||
|
(TypeIdentifier "p2")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(PointerType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(PointerType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "p1")))))))))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
43
test/fixtures/go/corpus/pointer-types.parseB.txt
vendored
43
test/fixtures/go/corpus/pointer-types.parseB.txt
vendored
@ -1,15 +1,28 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Type
|
(TypeDeclaration
|
||||||
(Identifier)
|
(TypeSpec
|
||||||
(Pointer
|
(TypeIdentifier "p1")
|
||||||
(Identifier)))
|
(Type
|
||||||
(Type
|
(SimpleType
|
||||||
(Identifier)
|
(PointerType
|
||||||
(Pointer
|
(Type
|
||||||
(Pointer
|
(SimpleType
|
||||||
(Identifier)))))))
|
(TypeIdentifier "int")))))))
|
||||||
|
(TypeSpec
|
||||||
|
(TypeIdentifier "p2")
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(PointerType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(PointerType
|
||||||
|
(Type
|
||||||
|
(SimpleType
|
||||||
|
(TypeIdentifier "p3")))))))))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,11 +1,16 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Type
|
(TypeDeclaration
|
||||||
(Identifier)
|
(TypeSpec
|
||||||
(MemberAccess
|
(TypeIdentifier "a")
|
||||||
(Identifier)
|
(Type
|
||||||
(Identifier))))))
|
(SimpleType
|
||||||
|
(QualifiedType
|
||||||
|
(TypeIdentifier "c")
|
||||||
|
(PackageIdentifier "b"))))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
@ -1,11 +1,16 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Function
|
(FunctionDeclaration
|
||||||
(Identifier)
|
(Block
|
||||||
(Statements
|
(Statement
|
||||||
(Type
|
(TypeDeclaration
|
||||||
(Identifier)
|
(TypeSpec
|
||||||
(MemberAccess
|
(TypeIdentifier "x")
|
||||||
(Identifier)
|
(Type
|
||||||
(Identifier))))))
|
(SimpleType
|
||||||
|
(QualifiedType
|
||||||
|
(TypeIdentifier "z")
|
||||||
|
(PackageIdentifier "y"))))))))
|
||||||
|
(Identifier "main")
|
||||||
|
(ParameterList)))
|
||||||
|
56
test/fixtures/go/corpus/rune-literals.parseA.txt
vendored
56
test/fixtures/go/corpus/rune-literals.parseA.txt
vendored
@ -1,22 +1,34 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Statements
|
(ConstDeclaration
|
||||||
(Assignment
|
(ConstSpec
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Rune))
|
(Expression
|
||||||
(Assignment
|
(RuneLiteral "'\948'")))
|
||||||
(Identifier)
|
(Identifier "a"))
|
||||||
(Rune))
|
(ConstSpec
|
||||||
(Assignment
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Rune))
|
(RuneLiteral "'\8984'")))
|
||||||
(Assignment
|
(Identifier "b"))
|
||||||
(Identifier)
|
(ConstSpec
|
||||||
(Rune))
|
(ExpressionList
|
||||||
(Assignment
|
(Expression
|
||||||
(Identifier)
|
(RuneLiteral "'\8984'")))
|
||||||
(Rune))
|
(Identifier "c"))
|
||||||
(Assignment
|
(ConstSpec
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Rune))))
|
(Expression
|
||||||
|
(RuneLiteral "'\8984'")))
|
||||||
|
(Identifier "d"))
|
||||||
|
(ConstSpec
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(RuneLiteral "'\8984'")))
|
||||||
|
(Identifier "e"))
|
||||||
|
(ConstSpec
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(RuneLiteral "'\8984'")))
|
||||||
|
(Identifier "f"))))
|
||||||
|
56
test/fixtures/go/corpus/rune-literals.parseB.txt
vendored
56
test/fixtures/go/corpus/rune-literals.parseB.txt
vendored
@ -1,22 +1,34 @@
|
|||||||
(Statements
|
(SourceFile
|
||||||
(Package
|
(PackageClause
|
||||||
(Identifier))
|
(PackageIdentifier "main"))
|
||||||
(Statements
|
(ConstDeclaration
|
||||||
(Assignment
|
(ConstSpec
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Rune))
|
(Expression
|
||||||
(Assignment
|
(RuneLiteral "'\169'")))
|
||||||
(Identifier)
|
(Identifier "a"))
|
||||||
(Rune))
|
(ConstSpec
|
||||||
(Assignment
|
(ExpressionList
|
||||||
(Identifier)
|
(Expression
|
||||||
(Rune))
|
(RuneLiteral "'\169'")))
|
||||||
(Assignment
|
(Identifier "b"))
|
||||||
(Identifier)
|
(ConstSpec
|
||||||
(Rune))
|
(ExpressionList
|
||||||
(Assignment
|
(Expression
|
||||||
(Identifier)
|
(RuneLiteral "'\169'")))
|
||||||
(Rune))
|
(Identifier "c"))
|
||||||
(Assignment
|
(ConstSpec
|
||||||
(Identifier)
|
(ExpressionList
|
||||||
(Rune))))
|
(Expression
|
||||||
|
(RuneLiteral "'\169'")))
|
||||||
|
(Identifier "d"))
|
||||||
|
(ConstSpec
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(RuneLiteral "'\169'")))
|
||||||
|
(Identifier "e"))
|
||||||
|
(ConstSpec
|
||||||
|
(ExpressionList
|
||||||
|
(Expression
|
||||||
|
(RuneLiteral "'\169'")))
|
||||||
|
(Identifier "f"))))
|
||||||
|
Some files were not shown because too many files have changed in this diff Show More
Loading…
Reference in New Issue
Block a user