mirror of
https://github.com/github/semantic.git
synced 2024-12-26 08:25:19 +03:00
Merge remote-tracking branch 'origin/go-assignment' into 🔥-monolithic-syntax
This commit is contained in:
commit
2ddd0fafdc
@ -50,6 +50,7 @@ library
|
||||
, Language.Markdown.Assignment
|
||||
, Language.Markdown.Syntax
|
||||
, Language.Go.Grammar
|
||||
, Language.Go.Assignment
|
||||
, Language.Go.Syntax
|
||||
, Language.JSON.Grammar
|
||||
, Language.JSON.Assignment
|
||||
|
@ -152,7 +152,7 @@ tracing f = case getCallStack callStack of
|
||||
|
||||
-- | Zero-width production of the current location.
|
||||
--
|
||||
-- If assigning at the end of input or at the end of a list of children, the loccation will be returned as an empty Range and Span at the current offset. Otherwise, it will be the Range and Span of the current node.
|
||||
-- If assigning at the end of input or at the end of a list of children, the location will be returned as an empty Range and Span at the current offset. Otherwise, it will be the Range and Span of the current node.
|
||||
location :: HasCallStack => Assignment ast grammar (Record Location)
|
||||
location = tracing Location `Then` return
|
||||
|
||||
|
@ -99,12 +99,6 @@ instance Eq1 Module where liftEq = genericLiftEq
|
||||
instance Ord1 Module where liftCompare = genericLiftCompare
|
||||
instance Show1 Module where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data Interface a = Interface { interfaceIdentifier :: !a, interfaceBody :: ![a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
|
||||
instance Eq1 Interface where liftEq = genericLiftEq
|
||||
instance Show1 Interface where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A decorator in Python
|
||||
data Decorator a = Decorator { decoratorIdentifier :: !a, decoratorParamaters :: ![a], decoratorBody :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
@ -180,17 +180,3 @@ data Cast a = Cast { castSubject :: !a, castType :: !a }
|
||||
instance Eq1 Cast where liftEq = genericLiftEq
|
||||
instance Ord1 Cast where liftCompare = genericLiftCompare
|
||||
instance Show1 Cast where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | Increment (e.g. 1++ in C or Go).
|
||||
newtype Increment a = Increment a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Show, Traversable)
|
||||
|
||||
instance Eq1 Increment where liftEq = genericLiftEq
|
||||
instance Show1 Increment where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | Decrement (e.g. 1-- in C or Go).
|
||||
newtype Decrement a = Decrement a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Show, Traversable)
|
||||
|
||||
instance Eq1 Decrement where liftEq = genericLiftEq
|
||||
instance Show1 Decrement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
@ -159,20 +159,42 @@ instance Eq1 Set where liftEq = genericLiftEq
|
||||
instance Ord1 Set where liftCompare = genericLiftCompare
|
||||
instance Show1 Set where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
|
||||
-- Pointers
|
||||
|
||||
-- | A declared pointer (e.g. var pointer *int in Go)
|
||||
newtype Pointer a = Pointer a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Pointer where liftEq = genericLiftEq
|
||||
instance Ord1 Pointer where liftCompare = genericLiftCompare
|
||||
instance Show1 Pointer where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A reference to a pointer's address (e.g. &pointer in Go)
|
||||
newtype Reference a = Reference a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Reference where liftEq = genericLiftEq
|
||||
instance Ord1 Reference where liftCompare = genericLiftCompare
|
||||
instance Show1 Reference where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
|
||||
-- Misc
|
||||
|
||||
-- A channel literal in Go
|
||||
newtype Channel a = Channel { channelContent :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Channel where liftEq = genericLiftEq
|
||||
instance Ord1 Channel where liftCompare = genericLiftCompare
|
||||
instance Show1 Channel where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- A composite literal in Go
|
||||
data Composite a = Composite { compositeType :: !a, compositeElement :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Composite where liftEq = genericLiftEq
|
||||
instance Ord1 Composite where liftCompare = genericLiftCompare
|
||||
instance Show1 Composite where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Object literals as distinct from hash literals? Or coalesce object/hash literals into “key-value literals”?
|
||||
|
@ -26,9 +26,10 @@ instance Ord1 Else where liftCompare = genericLiftCompare
|
||||
instance Show1 Else where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Goto a = Goto { gotoLocation :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Goto where liftEq = genericLiftEq
|
||||
instance Ord1 Goto where liftCompare = genericLiftCompare
|
||||
instance Show1 Goto where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- TODO: Alternative definition would flatten if/else if/else chains: data If a = If ![(a, a)] !(Maybe a)
|
||||
@ -194,3 +195,19 @@ newtype ScopeExit a = ScopeExit [a]
|
||||
instance Eq1 ScopeExit where liftEq = genericLiftEq
|
||||
instance Ord1 ScopeExit where liftCompare = genericLiftCompare
|
||||
instance Show1 ScopeExit where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | Post increment operator (e.g. 1++ in Go, or i++ in C).
|
||||
newtype PostIncrement a = PostIncrement a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 PostIncrement where liftEq = genericLiftEq
|
||||
instance Ord1 PostIncrement where liftCompare = genericLiftCompare
|
||||
instance Show1 PostIncrement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | Post decrement operator (e.g. 1-- in Go, or i-- in C).
|
||||
newtype PostDecrement a = PostDecrement a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 PostDecrement where liftEq = genericLiftEq
|
||||
instance Ord1 PostDecrement where liftCompare = genericLiftCompare
|
||||
instance Show1 PostDecrement where liftShowsPrec = genericLiftShowsPrec
|
||||
|
@ -16,10 +16,18 @@ instance Eq1 Annotation where liftEq = genericLiftEq
|
||||
instance Ord1 Annotation where liftCompare = genericLiftCompare
|
||||
instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data Alias a = Alias { aliasSubject :: !a, aliasType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Alias where liftEq = genericLiftEq
|
||||
instance Ord1 Alias where liftCompare = genericLiftCompare
|
||||
instance Show1 Alias where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data Function a = Function { functionParameters :: [a], functionReturn :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Function where liftEq = genericLiftEq
|
||||
instance Ord1 Function where liftCompare = genericLiftCompare
|
||||
instance Show1 Function where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Product a = Product { productElements :: [a] }
|
||||
@ -30,51 +38,59 @@ instance Ord1 Product where liftCompare = genericLiftCompare
|
||||
instance Show1 Product where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data Array a = Array { arraySize :: Maybe a, arrayElementType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Array where liftEq = genericLiftEq
|
||||
instance Ord1 Array where liftCompare = genericLiftCompare
|
||||
instance Show1 Array where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype BiDirectionalChannel a = BiDirectionalChannel { biDirectionalChannelElementType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 BiDirectionalChannel where liftEq = genericLiftEq
|
||||
instance Ord1 BiDirectionalChannel where liftCompare = genericLiftCompare
|
||||
instance Show1 BiDirectionalChannel where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Interface a = Interface { interfaceElements :: [a] }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Interface where liftEq = genericLiftEq
|
||||
instance Ord1 Interface where liftCompare = genericLiftCompare
|
||||
instance Show1 Interface where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data Map a = Map { mapKeyType :: a, mapElementType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Map where liftEq = genericLiftEq
|
||||
instance Ord1 Map where liftCompare = genericLiftCompare
|
||||
instance Show1 Map where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Pointer a = Pointer { pointerType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Pointer where liftEq = genericLiftEq
|
||||
instance Ord1 Pointer where liftCompare = genericLiftCompare
|
||||
instance Show1 Pointer where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype ReceiveChannel a = ReceiveChannel { receiveChannelElementType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 ReceiveChannel where liftEq = genericLiftEq
|
||||
instance Ord1 ReceiveChannel where liftCompare = genericLiftCompare
|
||||
instance Show1 ReceiveChannel where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype SendChannel a = SendChannel { sendChannelElementType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 SendChannel where liftEq = genericLiftEq
|
||||
instance Ord1 SendChannel where liftCompare = genericLiftCompare
|
||||
instance Show1 SendChannel where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
newtype Slice a = Slice { sliceElementType :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Show, Traversable)
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Slice where liftEq = genericLiftEq
|
||||
instance Ord1 Slice where liftCompare = genericLiftCompare
|
||||
instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
data TypeParameters a = TypeParameters { typeParameters :: ![a] }
|
||||
|
649
src/Language/Go/Assignment.hs
Normal file
649
src/Language/Go/Assignment.hs
Normal file
@ -0,0 +1,649 @@
|
||||
{-# LANGUAGE DataKinds, DeriveAnyClass, RankNTypes, TupleSections, TypeOperators #-}
|
||||
module Language.Go.Assignment
|
||||
( assignment
|
||||
, Syntax
|
||||
, Grammar
|
||||
, Term
|
||||
) where
|
||||
|
||||
import Data.Functor (void)
|
||||
import Data.List.NonEmpty (some1)
|
||||
import Data.Record
|
||||
import Data.Syntax (contextualize, emptyTerm, parseError, handleError, infixContext, makeTerm, makeTerm', makeTerm1)
|
||||
import qualified Data.Syntax as Syntax
|
||||
import Data.Syntax.Assignment hiding (Assignment, Error)
|
||||
import qualified Data.Syntax.Assignment as Assignment
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
import qualified Data.Syntax.Expression as Expression
|
||||
import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Syntax.Type as Type
|
||||
import qualified Data.Term as Term
|
||||
import Data.Union
|
||||
import GHC.Stack
|
||||
import Language.Go.Grammar as Grammar
|
||||
import Language.Go.Syntax as Go.Syntax
|
||||
|
||||
type Syntax =
|
||||
'[ Comment.Comment
|
||||
, Declaration.Constructor
|
||||
, Declaration.Function
|
||||
, Declaration.Import
|
||||
, Declaration.Method
|
||||
, Declaration.Module
|
||||
, Expression.Arithmetic
|
||||
, Expression.Bitwise
|
||||
, Expression.Boolean
|
||||
, Expression.Call
|
||||
, Expression.Comparison
|
||||
, Expression.Subscript
|
||||
, Statement.PostDecrement
|
||||
, Statement.PostIncrement
|
||||
, Expression.MemberAccess
|
||||
, Go.Syntax.DefaultPattern
|
||||
, Go.Syntax.Defer
|
||||
, Go.Syntax.Field
|
||||
, Go.Syntax.Go
|
||||
, Go.Syntax.Label
|
||||
, Go.Syntax.ParenthesizedType
|
||||
, Go.Syntax.Receive
|
||||
, Go.Syntax.RuneLiteral
|
||||
, Go.Syntax.Select
|
||||
, Go.Syntax.Send
|
||||
, Go.Syntax.Slice
|
||||
, Go.Syntax.TypeAssertion
|
||||
, Go.Syntax.TypeConversion
|
||||
, Go.Syntax.TypeSwitch
|
||||
, Go.Syntax.TypeSwitchGuard
|
||||
, Go.Syntax.Variadic
|
||||
, Literal.Array
|
||||
, Literal.Channel
|
||||
, Literal.Complex
|
||||
, Literal.Composite
|
||||
, Literal.Float
|
||||
, Literal.Hash
|
||||
, Literal.Integer
|
||||
, Literal.KeyValue
|
||||
, Literal.Pointer
|
||||
, Literal.Reference
|
||||
, Literal.TextElement
|
||||
, Statement.Assignment
|
||||
, Statement.Break
|
||||
, Statement.Continue
|
||||
, Statement.For
|
||||
, Statement.ForEach
|
||||
, Statement.Goto
|
||||
, Statement.If
|
||||
, Statement.Match
|
||||
, Statement.NoOp
|
||||
, Statement.Pattern
|
||||
, Statement.Return
|
||||
, Syntax.Context
|
||||
, Syntax.Error
|
||||
, Syntax.Empty
|
||||
, Syntax.Identifier
|
||||
, Syntax.Program
|
||||
, Type.Alias
|
||||
, Type.Annotation
|
||||
, Type.Array
|
||||
, Type.BiDirectionalChannel
|
||||
, Type.Function
|
||||
, Type.Interface
|
||||
, Type.Map
|
||||
, Type.Pointer
|
||||
, Type.ReceiveChannel
|
||||
, Type.SendChannel
|
||||
, Type.Slice
|
||||
, []
|
||||
]
|
||||
|
||||
type Term = Term.Term (Union Syntax) (Record Location)
|
||||
type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term
|
||||
|
||||
-- | Assignment from AST in Go's grammar onto a program in Go's syntax.
|
||||
assignment :: Assignment
|
||||
assignment = handleError $ makeTerm <$> symbol SourceFile <*> children (Syntax.Program <$> many expression) <|> parseError
|
||||
|
||||
expression :: Assignment
|
||||
expression = term (handleError (choice expressionChoices))
|
||||
|
||||
expressionChoices :: [Assignment.Assignment [] Grammar Term]
|
||||
expressionChoices =
|
||||
[ assignment'
|
||||
, arrayType
|
||||
, binaryExpression
|
||||
, block
|
||||
, breakStatement
|
||||
, callExpression
|
||||
, channelType
|
||||
, comment
|
||||
, communicationClause
|
||||
, compositeLiteral
|
||||
, continueStatement
|
||||
, varDeclaration
|
||||
, varSpecification
|
||||
, decStatement
|
||||
, defaultCase
|
||||
, deferStatement
|
||||
, element
|
||||
, elseClause
|
||||
, emptyStatement
|
||||
, expressionCaseClause
|
||||
, expressionList
|
||||
, expressionSwitchStatement
|
||||
, fallThroughStatement
|
||||
, fieldDeclaration
|
||||
, fieldIdentifier
|
||||
, floatLiteral
|
||||
, forStatement
|
||||
, functionDeclaration
|
||||
, functionType
|
||||
, goStatement
|
||||
, gotoStatement
|
||||
, ifInitializer
|
||||
, ifStatement
|
||||
, imaginaryLiteral
|
||||
, incStatement
|
||||
, identifier
|
||||
, implicitLengthArrayType
|
||||
, importDeclaration
|
||||
, importSpec
|
||||
, indexExpression
|
||||
, interfaceType
|
||||
, interpretedStringLiteral
|
||||
, intLiteral
|
||||
, keyedElement
|
||||
, labelName'
|
||||
, labelStatement'
|
||||
, literalValue
|
||||
, mapType
|
||||
, methodDeclaration
|
||||
, methodSpec
|
||||
, packageClause
|
||||
, packageIdentifier
|
||||
, parameterDeclaration
|
||||
, parameters
|
||||
, parenthesizedExpression
|
||||
, parenthesizedType
|
||||
, pointerType
|
||||
, qualifiedType
|
||||
, rawStringLiteral
|
||||
, receiveStatement
|
||||
, returnStatement
|
||||
, runeLiteral
|
||||
, selectStatement
|
||||
, selectorExpression
|
||||
, sendStatement
|
||||
, shortVarDeclaration
|
||||
, sliceExpression
|
||||
, sliceType
|
||||
, structType
|
||||
, typeAssertion
|
||||
, typeConversion
|
||||
, typeDeclaration
|
||||
, typeIdentifier
|
||||
, typeSwitchStatement
|
||||
, typeSwitchGuard
|
||||
, typeCase
|
||||
, typeCaseClause
|
||||
, unaryExpression
|
||||
, variadicArgument
|
||||
, variadicParameterDeclaration
|
||||
]
|
||||
|
||||
identifiers :: Assignment
|
||||
identifiers = mk <$> location <*> many identifier
|
||||
where
|
||||
mk _ [a] = a
|
||||
mk loc children = makeTerm loc children
|
||||
|
||||
expressions :: Assignment
|
||||
expressions = mk <$> location <*> many expression
|
||||
where
|
||||
mk _ [a] = a
|
||||
mk loc children = makeTerm loc children
|
||||
|
||||
types :: Assignment
|
||||
types = arrayType
|
||||
<|> channelType
|
||||
<|> functionType
|
||||
<|> implicitLengthArrayType
|
||||
<|> interfaceType
|
||||
<|> mapType
|
||||
<|> parenthesizedType
|
||||
<|> pointerType
|
||||
<|> qualifiedType
|
||||
<|> sliceType
|
||||
<|> structType
|
||||
<|> typeAssertion
|
||||
<|> typeConversion
|
||||
<|> typeDeclaration
|
||||
<|> typeIdentifier
|
||||
<|> typeCase
|
||||
<|> typeCaseClause
|
||||
<|> typeSwitchGuard
|
||||
<|> typeSwitchStatement
|
||||
|
||||
-- Literals
|
||||
|
||||
element :: Assignment
|
||||
element = symbol Element *> children expression
|
||||
|
||||
imaginaryLiteral :: Assignment
|
||||
imaginaryLiteral = makeTerm <$> symbol ImaginaryLiteral <*> (Literal.Complex <$> source)
|
||||
|
||||
literalValue :: Assignment
|
||||
literalValue = makeTerm <$> symbol LiteralValue <*> children (many expression)
|
||||
|
||||
compositeLiteral :: Assignment
|
||||
compositeLiteral = makeTerm <$> symbol CompositeLiteral <*> children (Literal.Composite <$> expression <*> expression)
|
||||
|
||||
intLiteral :: Assignment
|
||||
intLiteral = makeTerm <$> symbol IntLiteral <*> (Literal.Integer <$> source)
|
||||
|
||||
floatLiteral :: Assignment
|
||||
floatLiteral = makeTerm <$> symbol FloatLiteral <*> (Literal.Float <$> source)
|
||||
|
||||
rawStringLiteral :: Assignment
|
||||
rawStringLiteral = makeTerm <$> symbol RawStringLiteral <*> (Literal.TextElement <$> source)
|
||||
|
||||
typeIdentifier :: Assignment
|
||||
typeIdentifier = makeTerm <$> symbol TypeIdentifier <*> (Syntax.Identifier <$> source)
|
||||
|
||||
identifier :: Assignment
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier <$> source)
|
||||
|
||||
fieldIdentifier :: Assignment
|
||||
fieldIdentifier = makeTerm <$> symbol FieldIdentifier <*> (Syntax.Identifier <$> source)
|
||||
|
||||
packageIdentifier :: Assignment
|
||||
packageIdentifier = makeTerm <$> symbol PackageIdentifier <*> (Syntax.Identifier <$> source)
|
||||
|
||||
parenthesizedType :: Assignment
|
||||
parenthesizedType = makeTerm <$> symbol Grammar.ParenthesizedType <*> children (Go.Syntax.ParenthesizedType <$> expression)
|
||||
|
||||
interpretedStringLiteral :: Assignment
|
||||
interpretedStringLiteral = makeTerm <$> symbol InterpretedStringLiteral <*> (Literal.TextElement <$> source)
|
||||
|
||||
comment :: Assignment
|
||||
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||
|
||||
runeLiteral :: Assignment
|
||||
runeLiteral = makeTerm <$> symbol Grammar.RuneLiteral <*> (Go.Syntax.RuneLiteral <$> source)
|
||||
|
||||
|
||||
-- Primitive Types
|
||||
|
||||
qualifiedType :: Assignment
|
||||
qualifiedType = makeTerm <$> symbol QualifiedType <*> children (Expression.MemberAccess <$> expression <*> expression)
|
||||
|
||||
arrayType :: Assignment
|
||||
arrayType = makeTerm <$> symbol ArrayType <*> children (Type.Array . Just <$> expression <*> (expression <|> arrayType))
|
||||
|
||||
implicitLengthArrayType :: Assignment
|
||||
implicitLengthArrayType = makeTerm <$> symbol ImplicitLengthArrayType <*> children (Type.Array Nothing <$> expression)
|
||||
|
||||
functionType :: Assignment
|
||||
functionType = makeTerm <$> symbol FunctionType <*> children (Type.Function <$> many parameters <*> returnType)
|
||||
where
|
||||
returnType = symbol Parameters *> children expressions <|> expression <|> emptyTerm
|
||||
|
||||
sliceType :: Assignment
|
||||
sliceType = makeTerm <$> symbol SliceType <*> children (Type.Slice <$> expression)
|
||||
|
||||
channelType :: Assignment
|
||||
channelType = (makeTerm <$> symbol ChannelType <*> children (token AnonLAngleMinus *> token AnonChan *> (Type.ReceiveChannel <$> expression)))
|
||||
<|> (makeTerm <$> symbol ChannelType <*> children (token AnonChan *> token AnonLAngleMinus *> (Type.SendChannel <$> expression)))
|
||||
<|> (makeTerm <$> symbol ChannelType <*> children (token AnonChan *> (Type.BiDirectionalChannel <$> expression)))
|
||||
|
||||
structType :: Assignment
|
||||
structType = handleError $ makeTerm <$> symbol StructType <*> children (Declaration.Constructor <$> emptyTerm <*> many expression)
|
||||
|
||||
interfaceType :: Assignment
|
||||
interfaceType = handleError $ makeTerm <$> symbol InterfaceType <*> children (Type.Interface <$> many expression)
|
||||
|
||||
mapType :: Assignment
|
||||
mapType = handleError $ makeTerm <$> symbol MapType <*> children (Type.Map <$> expression <*> expression)
|
||||
|
||||
pointerType :: Assignment
|
||||
pointerType = handleError $ makeTerm <$> symbol PointerType <*> children (Type.Pointer <$> expression)
|
||||
|
||||
fieldDeclaration :: Assignment
|
||||
fieldDeclaration = mkFieldDeclarationWithTag <$> symbol FieldDeclaration <*> children ((,,) <$> (manyTermsTill expression (void (symbol TypeIdentifier)) <|> (many expression)) <*> optional expression <*> optional expression)
|
||||
where
|
||||
mkFieldDeclarationWithTag loc (fields, (Just type'), (Just tag)) = makeTerm loc $ Go.Syntax.Field [type', tag] (makeTerm loc fields) --Type.Annotation (makeTerm loc (Type.Annotation (makeTerm loc fields) type')) tag
|
||||
mkFieldDeclarationWithTag loc (fields, (Just type'), Nothing) = makeTerm loc $ Go.Syntax.Field [type'] (makeTerm loc fields)
|
||||
mkFieldDeclarationWithTag loc (fields, Nothing, (Just tag)) = makeTerm loc $ Go.Syntax.Field [tag] (makeTerm loc fields)
|
||||
mkFieldDeclarationWithTag loc (fields, Nothing, Nothing) = makeTerm loc $ Go.Syntax.Field [] (makeTerm loc fields)
|
||||
|
||||
|
||||
-- Type Declarations
|
||||
|
||||
channelTypeDeclaration :: Assignment
|
||||
channelTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> channelType)
|
||||
|
||||
functionTypeDeclaration :: Assignment
|
||||
functionTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> functionType)
|
||||
|
||||
interfaceTypeDeclaration :: Assignment
|
||||
interfaceTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> interfaceType)
|
||||
|
||||
mapTypeDeclaration :: Assignment
|
||||
mapTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> mapType)
|
||||
|
||||
structTypeDeclaration :: Assignment
|
||||
structTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> structType)
|
||||
|
||||
qualifiedTypeDeclaration :: Assignment
|
||||
qualifiedTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> qualifiedType)
|
||||
|
||||
arrayTypeDeclaration :: Assignment
|
||||
arrayTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> arrayType)
|
||||
|
||||
sliceTypeDeclaration :: Assignment
|
||||
sliceTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> sliceType)
|
||||
|
||||
pointerTypeDeclaration :: Assignment
|
||||
pointerTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> pointerType)
|
||||
|
||||
typeAlias :: Assignment
|
||||
typeAlias = makeTerm <$> symbol TypeAlias <*> children (Type.Alias <$> expression <*> expression)
|
||||
|
||||
typeIdentifierDeclaration :: Assignment
|
||||
typeIdentifierDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> expression)
|
||||
|
||||
typeDeclaration :: Assignment
|
||||
typeDeclaration = handleError $ makeTerm <$> symbol TypeDeclaration <*> children (many ( arrayTypeDeclaration
|
||||
<|> channelTypeDeclaration
|
||||
<|> functionTypeDeclaration
|
||||
<|> interfaceTypeDeclaration
|
||||
<|> qualifiedTypeDeclaration
|
||||
<|> pointerTypeDeclaration
|
||||
<|> sliceTypeDeclaration
|
||||
<|> structTypeDeclaration
|
||||
<|> mapTypeDeclaration
|
||||
<|> typeAlias
|
||||
<|> typeIdentifierDeclaration ))
|
||||
|
||||
|
||||
-- Expressions
|
||||
|
||||
indexExpression :: Assignment
|
||||
indexExpression = makeTerm <$> symbol IndexExpression <*> children (Expression.Subscript <$> expression <*> many expression)
|
||||
|
||||
sliceExpression :: Assignment
|
||||
sliceExpression = makeTerm <$> symbol SliceExpression <*> children ( (Go.Syntax.Slice <$> expression <*> expression <*> expression <*> expression)
|
||||
<|> (Go.Syntax.Slice <$> expression <*> emptyTerm <* symbol AnonColon <*> expression <* symbol AnonColon <*> expression)
|
||||
<|> (Go.Syntax.Slice <$> expression <*> emptyTerm <* symbol AnonColon <*> expression <*> emptyTerm)
|
||||
<|> (Go.Syntax.Slice <$> expression <*> expression <*> expression <*> emptyTerm)
|
||||
<|> (Go.Syntax.Slice <$> expression <*> expression <*> emptyTerm <*> emptyTerm)
|
||||
<|> (Go.Syntax.Slice <$> expression <*> emptyTerm <*> emptyTerm <*> emptyTerm))
|
||||
|
||||
parenthesizedExpression :: Assignment
|
||||
parenthesizedExpression = symbol ParenthesizedExpression *> children expressions
|
||||
|
||||
selectorExpression :: Assignment
|
||||
selectorExpression = makeTerm <$> symbol SelectorExpression <*> children (Expression.MemberAccess <$> expression <*> expression)
|
||||
|
||||
typeAssertion :: Assignment
|
||||
typeAssertion = makeTerm <$> symbol TypeAssertionExpression <*> children (Go.Syntax.TypeAssertion <$> expression <*> expression)
|
||||
|
||||
typeConversion :: Assignment
|
||||
typeConversion = makeTerm <$> symbol TypeConversionExpression <*> children (Go.Syntax.TypeConversion <$> expression <*> expression)
|
||||
|
||||
unaryExpression :: Assignment
|
||||
unaryExpression = symbol UnaryExpression >>= \ location -> (notExpression location) <|> (unaryMinus location) <|> unaryPlus <|> unaryAmpersand <|> unaryReceive <|> unaryPointer <|> unaryComplement
|
||||
where
|
||||
notExpression location = makeTerm location . Expression.Not <$> children (symbol AnonBang *> expression)
|
||||
unaryMinus location = makeTerm location . Expression.Negate <$> children (symbol AnonMinus *> expression)
|
||||
unaryPlus = children (symbol AnonPlus *> expression)
|
||||
unaryAmpersand = children (makeTerm <$> symbol AnonAmpersand <*> (Literal.Reference <$> expression))
|
||||
unaryReceive = children (makeTerm <$> symbol AnonLAngleMinus <*> (Go.Syntax.Receive <$> emptyTerm <*> expression))
|
||||
unaryPointer = children (makeTerm <$> symbol AnonStar <*> (Literal.Pointer <$> expression))
|
||||
unaryComplement = children (makeTerm <$> symbol AnonCaret <*> (Expression.Complement <$> expression))
|
||||
|
||||
binaryExpression :: Assignment
|
||||
binaryExpression = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expression expression
|
||||
[ (inj .) . Expression.Plus <$ symbol AnonPlus
|
||||
, (inj .) . Expression.Minus <$ symbol AnonMinus
|
||||
, (inj .) . Expression.Times <$ symbol AnonStar
|
||||
, (inj .) . Expression.DividedBy <$ symbol AnonSlash
|
||||
, (inj .) . Expression.Modulo <$ symbol AnonPercent
|
||||
, (inj .) . Expression.Or <$ symbol AnonPipePipe
|
||||
, (inj .) . Expression.And <$ symbol AnonAmpersandAmpersand
|
||||
, (inj .) . Expression.LessThan <$ symbol AnonLAngle
|
||||
, (inj .) . Expression.LessThanEqual <$ symbol AnonLAngleEqual
|
||||
, (inj .) . Expression.GreaterThan <$ symbol AnonRAngle
|
||||
, (inj .) . Expression.GreaterThanEqual <$ symbol AnonRAngleEqual
|
||||
, (inj .) . invert Expression.Equal <$ symbol AnonBangEqual
|
||||
, (inj .) . Expression.Equal <$ symbol AnonEqualEqual
|
||||
, (inj .) . Expression.BOr <$ symbol AnonPipe
|
||||
, (inj .) . Expression.BAnd <$ symbol AnonAmpersand
|
||||
, (inj .) . Expression.BAnd <$ symbol AnonAmpersandCaret
|
||||
, (inj .) . Expression.BXOr <$ symbol AnonCaret
|
||||
, (inj .) . Expression.LShift <$ symbol AnonLAngleLAngle
|
||||
, (inj .) . Expression.RShift <$ symbol AnonRAngleRAngle
|
||||
])
|
||||
where
|
||||
invert cons a b = Expression.Not (makeTerm1 (cons a b))
|
||||
|
||||
block :: Assignment
|
||||
block = symbol Block *> children expressions
|
||||
|
||||
expressionCase :: Assignment
|
||||
expressionCase = makeTerm <$> symbol ExpressionCase <*> (Statement.Pattern <$> children expressions <*> expressions)
|
||||
|
||||
defaultCase :: Assignment
|
||||
defaultCase = makeTerm <$> symbol DefaultCase <*> children (Go.Syntax.DefaultPattern <$> (expressions <|> emptyTerm))
|
||||
|
||||
defaultExpressionCase :: Assignment
|
||||
defaultExpressionCase = makeTerm <$> symbol DefaultCase <*> (Go.Syntax.DefaultPattern <$ source <*> (expressions <|> emptyTerm))
|
||||
|
||||
expressionCaseClause :: Assignment
|
||||
expressionCaseClause = symbol ExpressionCaseClause *> children (expressionCase <|> defaultExpressionCase)
|
||||
|
||||
expressionSwitchStatement :: Assignment
|
||||
expressionSwitchStatement = makeTerm <$> symbol ExpressionSwitchStatement <*> children (Statement.Match <$> (expression <|> emptyTerm) <*> (expressionCaseClauses <|> emptyTerm))
|
||||
where
|
||||
expressionCaseClauses = makeTerm <$> location <*> many expressionCaseClause
|
||||
|
||||
typeSwitchStatement :: Assignment
|
||||
typeSwitchStatement = makeTerm <$> symbol TypeSwitchStatement <*> children (Go.Syntax.TypeSwitch <$> _typeSwitchSubject <*> expressions)
|
||||
where
|
||||
_typeSwitchSubject = makeTerm <$> location <*> manyTermsTill expression (void (symbol TypeCaseClause))
|
||||
|
||||
typeSwitchGuard :: Assignment
|
||||
typeSwitchGuard = makeTerm <$> symbol Grammar.TypeSwitchGuard <*> children (Go.Syntax.TypeSwitchGuard <$> expressions)
|
||||
|
||||
typeCaseClause :: Assignment
|
||||
typeCaseClause = makeTerm <$> symbol TypeCaseClause <*> children (Statement.Pattern <$> expression <*> expressions)
|
||||
|
||||
typeCase :: Assignment
|
||||
typeCase = symbol TypeCase *> children expression
|
||||
|
||||
fallThroughStatement :: Assignment
|
||||
fallThroughStatement = makeTerm <$> symbol FallthroughStatement <*> (Statement.Pattern <$> (makeTerm <$> location <*> (Syntax.Identifier <$> source)) <*> emptyTerm)
|
||||
|
||||
variadicArgument :: Assignment
|
||||
variadicArgument = makeTerm <$> symbol VariadicArgument <*> children (Go.Syntax.Variadic <$> pure [] <*> expression)
|
||||
|
||||
callExpression :: Assignment
|
||||
callExpression = makeTerm <$> symbol CallExpression <*> children (Expression.Call <$> pure [] <*> expression <*> many expression <*> emptyTerm)
|
||||
|
||||
varDeclaration :: Assignment
|
||||
varDeclaration = (symbol ConstDeclaration <|> symbol VarDeclaration) *> children expressions
|
||||
|
||||
varSpecification :: Assignment
|
||||
varSpecification = makeTerm <$> (symbol ConstSpec <|> symbol VarSpec) <*> children (Statement.Assignment <$> pure [] <*> (annotatedLHS <|> identifiers) <*> expressions)
|
||||
where
|
||||
annotatedLHS = makeTerm <$> location <*> (Type.Annotation <$> (makeTerm <$> location <*> (manyTermsTill identifier (void (symbol TypeIdentifier)))) <*> expression)
|
||||
|
||||
expressionList :: Assignment
|
||||
expressionList = symbol ExpressionList *> children expressions
|
||||
|
||||
functionDeclaration :: Assignment
|
||||
functionDeclaration = mkTypedFunctionDeclaration <$> symbol FunctionDeclaration <*> children ((,,,) <$> expression <*> many parameters <*> optional (types <|> identifier <|> returnParameters) <*> optional block)
|
||||
<|> mkTypedFunctionLiteral <$> symbol FuncLiteral <*> children ((,,,) <$> emptyTerm <*> many parameters <*> optional (types <|> identifier <|> returnParameters) <*> block)
|
||||
where
|
||||
mkTypedFunctionDeclaration loc (name', params', types', block') = makeTerm loc (Declaration.Function [(maybe (makeTerm loc Syntax.Empty) id types')] name' params' (maybe (makeTerm loc Syntax.Empty) id block'))
|
||||
mkTypedFunctionLiteral loc (name', params', types', block') = makeTerm loc (Declaration.Function [(maybe (makeTerm loc Syntax.Empty) id types')] name' params' block')
|
||||
returnParameters = makeTerm <$> symbol Parameters <*> children (many expression)
|
||||
|
||||
variadicParameterDeclaration :: Assignment
|
||||
variadicParameterDeclaration = mkVariadic <$> symbol VariadicParameterDeclaration <*> children ((,) <$> emptyTerm <*> expression)
|
||||
<|> mkVariadic <$> symbol VariadicParameterDeclaration <*> children ((,) <$> expression <*> expression)
|
||||
where
|
||||
mkVariadic loc (identifier', typeIdentifier') = makeTerm loc (Go.Syntax.Variadic [typeIdentifier'] identifier')
|
||||
|
||||
importDeclaration :: Assignment
|
||||
importDeclaration = makeTerm <$> symbol ImportDeclaration <*> children (Declaration.Import <$> many expression)
|
||||
|
||||
importSpec :: Assignment
|
||||
importSpec = symbol ImportSpec *> children expressions
|
||||
|
||||
parameters :: Assignment
|
||||
parameters = makeTerm <$> symbol Parameters <*> children (many expression)
|
||||
|
||||
parameterDeclaration :: Assignment
|
||||
parameterDeclaration = makeTerm <$> symbol ParameterDeclaration <*> children (many expression)
|
||||
|
||||
methodDeclaration :: Assignment
|
||||
methodDeclaration = mkTypedMethodDeclaration <$> symbol MethodDeclaration <*> children ((,,,,) <$> receiver <*> fieldIdentifier <*> many parameters <*> (expression <|> emptyTerm) <*> block)
|
||||
where
|
||||
receiver = symbol Parameters *> children ((symbol ParameterDeclaration *> children expressions) <|> expressions)
|
||||
mkTypedMethodDeclaration loc (receiver', name', parameters', type'', body') = makeTerm loc (Declaration.Method [type''] receiver' name' parameters' body')
|
||||
|
||||
methodSpec :: Assignment
|
||||
methodSpec = mkMethodSpec <$> symbol MethodSpec <*> children ((,,,,) <$> empty <*> expression <*> parameters <*> (expression <|> parameters <|> emptyTerm) <*> empty)
|
||||
where
|
||||
empty = makeTerm <$> location <*> pure Syntax.Empty
|
||||
mkMethodSpec loc (receiver', name', params, optionaltypeLiteral, body') = makeTerm loc $ Type.Annotation (mkMethod loc receiver' name' params body') optionaltypeLiteral
|
||||
mkMethod loc empty' name' params empty'' = makeTerm loc $ Declaration.Method [] empty' name' (pure params) empty''
|
||||
|
||||
packageClause :: Assignment
|
||||
packageClause = makeTerm <$> symbol PackageClause <*> children (Declaration.Module <$> expression <*> pure [])
|
||||
|
||||
|
||||
-- Statements
|
||||
|
||||
assignment' :: Assignment
|
||||
assignment' = makeTerm' <$> symbol AssignmentStatement <*> children (infixTerm expressionList expressionList
|
||||
[ assign <$ symbol AnonEqual
|
||||
, augmentedAssign Expression.Plus <$ symbol AnonPlusEqual
|
||||
, augmentedAssign Expression.Minus <$ symbol AnonMinusEqual
|
||||
, augmentedAssign Expression.Times <$ symbol AnonStarEqual
|
||||
, augmentedAssign Expression.DividedBy <$ symbol AnonSlashEqual
|
||||
, augmentedAssign Expression.BOr <$ symbol AnonPipeEqual
|
||||
, augmentedAssign Expression.BAnd <$ symbol AnonAmpersandEqual
|
||||
, augmentedAssign Expression.Modulo <$ symbol AnonPercentEqual
|
||||
, augmentedAssign Expression.RShift <$ symbol AnonRAngleRAngleEqual
|
||||
, augmentedAssign Expression.LShift <$ symbol AnonLAngleLAngleEqual
|
||||
, augmentedAssign Expression.BXOr <$ symbol AnonCaretEqual
|
||||
, augmentedAssign (invert Expression.BAnd) <$ symbol AnonAmpersandCaretEqual
|
||||
])
|
||||
where
|
||||
assign :: Term -> Term -> Union Syntax Term
|
||||
assign l r = inj (Statement.Assignment [] l r)
|
||||
|
||||
augmentedAssign :: f :< Syntax => (Term -> Term -> f Term) -> Term -> Term -> Union Syntax Term
|
||||
augmentedAssign c l r = assign l (makeTerm1 (c l r))
|
||||
|
||||
invert cons a b = Expression.Not (makeTerm1 (cons a b))
|
||||
|
||||
emptyStatement :: Assignment
|
||||
emptyStatement = makeTerm <$> token EmptyStatement <*> (Statement.NoOp <$> emptyTerm)
|
||||
|
||||
shortVarDeclaration :: Assignment
|
||||
shortVarDeclaration = makeTerm <$> symbol ShortVarDeclaration <*> children (Statement.Assignment <$> pure [] <*> expression <*> expression)
|
||||
|
||||
sendStatement :: Assignment
|
||||
sendStatement = makeTerm <$> symbol SendStatement <*> children (Go.Syntax.Send <$> expression <*> expression)
|
||||
|
||||
breakStatement :: Assignment
|
||||
breakStatement = makeTerm <$> symbol BreakStatement <*> children (Statement.Break <$> (labelName' <|> emptyTerm))
|
||||
|
||||
continueStatement :: Assignment
|
||||
continueStatement = makeTerm <$> symbol ContinueStatement <*> children (Statement.Continue <$> (labelName' <|> emptyTerm))
|
||||
|
||||
decStatement :: Assignment
|
||||
decStatement = makeTerm <$> symbol DecStatement <*> children (Statement.PostDecrement <$> expression)
|
||||
|
||||
deferStatement :: Assignment
|
||||
deferStatement = makeTerm <$> symbol DeferStatement <*> children (Go.Syntax.Defer <$> expression)
|
||||
|
||||
goStatement :: Assignment
|
||||
goStatement = makeTerm <$> symbol GoStatement <*> children (Go.Syntax.Go <$> expression)
|
||||
|
||||
gotoStatement :: Assignment
|
||||
gotoStatement = makeTerm <$> symbol GotoStatement <*> children (Statement.Goto <$> expression)
|
||||
|
||||
ifStatement :: Assignment
|
||||
ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> (makeTerm <$> location <*> manyTermsTill expression (void (symbol Block))) <*> expression <*> (expression <|> emptyTerm))
|
||||
|
||||
ifInitializer :: Assignment
|
||||
ifInitializer = symbol IfInitializer *> children expression
|
||||
|
||||
elseClause :: Assignment
|
||||
elseClause = symbol ElseClause *> children expression
|
||||
|
||||
forStatement :: Assignment
|
||||
forStatement = mkForStatement <$> symbol ForStatement <*> children ((,) <$> (forClause <|> rangeClause <|> for <|> emptyClause) <*> expression)
|
||||
where
|
||||
mkForStatement loc ((constructor, a, b, c), block') = case (constructor :: [Char]) of
|
||||
"forEach" -> makeTerm loc $ (Statement.ForEach a b block')
|
||||
_ -> makeTerm loc $ (Statement.For a b c block')
|
||||
emptyClause = children (("for",,,) <$> emptyTerm <*> emptyTerm <*> emptyTerm)
|
||||
rangeClause = symbol RangeClause *> children ( (("forEach",,,) <$> expression <*> expression <*> emptyTerm)
|
||||
<|> (("forEach",,,) <$> emptyTerm <*> expression <*> emptyTerm))
|
||||
forClause = symbol ForClause *> children ( (("for",,,) <$> expression <*> expression <*> expression)
|
||||
<|> (("for",,,) <$> expression <*> expression <*> emptyTerm)
|
||||
<|> (("for",,,) <$> expression <*> emptyTerm <*> emptyTerm)
|
||||
<|> (("for",,,) <$> emptyTerm <*> emptyTerm <*> emptyTerm))
|
||||
for = ("for",,,) <$> emptyTerm <*> expression <*> emptyTerm
|
||||
|
||||
incStatement :: Assignment
|
||||
incStatement = makeTerm <$> symbol IncStatement <*> children (Statement.PostIncrement <$> expression)
|
||||
|
||||
keyedElement :: Assignment
|
||||
keyedElement = makeTerm <$> symbol KeyedElement <*> children (Literal.KeyValue <$> expression <*> expression)
|
||||
|
||||
labelName' :: Assignment
|
||||
labelName' = makeTerm <$> symbol LabelName <*> (Syntax.Identifier <$> source)
|
||||
|
||||
labelStatement' :: Assignment
|
||||
labelStatement' = makeTerm <$> symbol LabelStatement <*> children (Go.Syntax.Label <$> expression <*> (expression <|> emptyTerm))
|
||||
|
||||
returnStatement :: Assignment
|
||||
returnStatement = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> (expression <|> emptyTerm))
|
||||
|
||||
receiveStatement :: Assignment
|
||||
receiveStatement = makeTerm <$> symbol ReceiveStatement <*> children ( (Go.Syntax.Receive <$> expression <*> expression)
|
||||
<|> (Go.Syntax.Receive <$> emptyTerm <*> expression))
|
||||
|
||||
selectStatement :: Assignment
|
||||
selectStatement = makeTerm <$> symbol SelectStatement <*> children (Go.Syntax.Select <$> expressions)
|
||||
|
||||
communicationClause :: Assignment
|
||||
communicationClause = makeTerm <$> symbol CommunicationClause <*> children (Statement.Pattern <$> (communicationCase <|> defaultCase) <*> (expression <|> emptyTerm))
|
||||
where
|
||||
communicationCase = symbol CommunicationCase *> children expression
|
||||
|
||||
|
||||
-- Helpers
|
||||
|
||||
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.
|
||||
infixTerm :: HasCallStack
|
||||
=> Assignment
|
||||
-> Assignment
|
||||
-> [Assignment.Assignment [] Grammar (Term -> Term -> Union Syntax Term)]
|
||||
-> Assignment.Assignment [] Grammar (Union Syntax Term)
|
||||
infixTerm = infixContext comment
|
||||
|
||||
-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present.
|
||||
term :: Assignment -> Assignment
|
||||
term term = contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)
|
||||
|
||||
-- | Match a series of terms or comments until a delimiter is matched
|
||||
manyTermsTill :: Show b => Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term]
|
||||
manyTermsTill step end = manyTill (step <|> comment) end
|
@ -1,420 +1,137 @@
|
||||
{-# LANGUAGE DataKinds, DeriveAnyClass, RankNTypes, TypeOperators #-}
|
||||
module Language.Go.Syntax
|
||||
( assignment
|
||||
, Syntax
|
||||
, Grammar
|
||||
, Term
|
||||
) where
|
||||
|
||||
import Data.Functor (void)
|
||||
import Data.List.NonEmpty (some1)
|
||||
import Data.Record
|
||||
import Data.Syntax (contextualize, postContextualize, emptyTerm, parseError, handleError, infixContext, makeTerm, makeTerm', makeTerm1)
|
||||
import qualified Data.Syntax as Syntax
|
||||
import Data.Syntax.Assignment hiding (Assignment, Error)
|
||||
import qualified Data.Syntax.Assignment as Assignment
|
||||
import qualified Data.Syntax.Comment as Comment
|
||||
import qualified Data.Syntax.Declaration as Declaration
|
||||
import qualified Data.Syntax.Expression as Expression
|
||||
import qualified Data.Syntax.Literal as Literal
|
||||
import qualified Data.Syntax.Statement as Statement
|
||||
import qualified Data.Syntax.Type as Type
|
||||
import qualified Data.Term as Term
|
||||
import Data.Union
|
||||
import GHC.Stack
|
||||
import Language.Go.Grammar as Grammar
|
||||
|
||||
type Syntax =
|
||||
'[ Comment.Comment
|
||||
, Declaration.Constructor
|
||||
, Declaration.Function
|
||||
, Declaration.Import
|
||||
, Declaration.Interface
|
||||
, Declaration.Method
|
||||
, Declaration.Module
|
||||
, Expression.Arithmetic
|
||||
, Expression.Bitwise
|
||||
, Expression.Boolean
|
||||
, Expression.Call
|
||||
, Expression.Comparison
|
||||
, Expression.Decrement
|
||||
, Expression.Increment
|
||||
, Expression.MemberAccess
|
||||
, Literal.Array
|
||||
, Literal.Channel
|
||||
, Literal.Composite
|
||||
, Literal.Hash
|
||||
, Literal.Integer
|
||||
, Literal.KeyValue
|
||||
, Literal.TextElement
|
||||
, Statement.Assignment
|
||||
, Statement.Break
|
||||
, Statement.Goto
|
||||
, Statement.If
|
||||
, Statement.Return
|
||||
, Syntax.Context
|
||||
, Syntax.Error
|
||||
, Syntax.Empty
|
||||
, Syntax.Identifier
|
||||
, Syntax.Program
|
||||
, Type.Annotation
|
||||
, Type.Array
|
||||
, Type.BiDirectionalChannel
|
||||
, Type.Function
|
||||
, Type.Interface
|
||||
, Type.Map
|
||||
, Type.Pointer
|
||||
, Type.ReceiveChannel
|
||||
, Type.SendChannel
|
||||
, Type.Slice
|
||||
, []
|
||||
]
|
||||
|
||||
type Term = Term.Term (Union Syntax) (Record Location)
|
||||
type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term
|
||||
|
||||
-- | Assignment from AST in Go's grammar onto a program in Go's syntax.
|
||||
assignment :: Assignment
|
||||
assignment = handleError $ makeTerm <$> symbol SourceFile <*> children (Syntax.Program <$> many expression) <|> parseError
|
||||
|
||||
expression :: Assignment
|
||||
expression = term (handleError (choice expressionChoices))
|
||||
|
||||
expressionChoices :: [Assignment.Assignment [] Grammar Term]
|
||||
expressionChoices =
|
||||
[ assignment'
|
||||
, binaryExpression
|
||||
, block
|
||||
, breakStatement
|
||||
, callExpression
|
||||
, channelType
|
||||
, comment
|
||||
, compositeLiteral
|
||||
, constVarDeclaration
|
||||
, constVarSpecification
|
||||
, decStatement
|
||||
, element
|
||||
, expressionList
|
||||
, fieldDeclaration
|
||||
, fieldIdentifier
|
||||
, functionDeclaration
|
||||
, functionType
|
||||
, gotoStatement
|
||||
, ifStatement
|
||||
, incStatement
|
||||
, identifier
|
||||
, implicitLengthArrayType
|
||||
, importDeclaration
|
||||
, importSpec
|
||||
, interfaceType
|
||||
, interpretedStringLiteral
|
||||
, intLiteral
|
||||
, labelName
|
||||
, literalValue
|
||||
, mapType
|
||||
, methodDeclaration
|
||||
, methodSpec
|
||||
, packageClause
|
||||
, packageIdentifier
|
||||
, parameterDeclaration
|
||||
, parenthesizedExpression
|
||||
, parenthesizedType
|
||||
, pointerType
|
||||
, rawStringLiteral
|
||||
, returnStatement
|
||||
, shortVarDeclaration
|
||||
, sliceType
|
||||
, structType
|
||||
, typeDeclaration
|
||||
, typeIdentifier
|
||||
, unaryExpression
|
||||
]
|
||||
|
||||
identifiers :: Assignment
|
||||
identifiers = mk <$> location <*> many identifier
|
||||
where mk _ [a] = a
|
||||
mk loc children = makeTerm loc children
|
||||
|
||||
expressions :: Assignment
|
||||
expressions = mk <$> location <*> many expression
|
||||
where mk _ [a] = a
|
||||
mk loc children = makeTerm loc children
|
||||
|
||||
|
||||
-- Literals
|
||||
|
||||
element :: Assignment
|
||||
element = symbol Element *> children expression
|
||||
|
||||
literalValue :: Assignment
|
||||
literalValue = makeTerm <$> symbol LiteralValue <*> children (many expression)
|
||||
|
||||
compositeLiteral :: Assignment
|
||||
compositeLiteral = makeTerm <$> symbol CompositeLiteral <*> children (Literal.Composite <$> expression <*> expression)
|
||||
|
||||
intLiteral :: Assignment
|
||||
intLiteral = makeTerm <$> symbol IntLiteral <*> (Literal.Integer <$> source)
|
||||
|
||||
rawStringLiteral :: Assignment
|
||||
rawStringLiteral = makeTerm <$> symbol RawStringLiteral <*> (Literal.TextElement <$> source)
|
||||
|
||||
typeIdentifier :: Assignment
|
||||
typeIdentifier = makeTerm <$> symbol TypeIdentifier <*> (Syntax.Identifier <$> source)
|
||||
|
||||
identifier :: Assignment
|
||||
identifier = makeTerm <$> symbol Identifier <*> (Syntax.Identifier <$> source)
|
||||
|
||||
fieldIdentifier :: Assignment
|
||||
fieldIdentifier = makeTerm <$> symbol FieldIdentifier <*> (Syntax.Identifier <$> source)
|
||||
|
||||
packageIdentifier :: Assignment
|
||||
packageIdentifier = makeTerm <$> symbol PackageIdentifier <*> (Syntax.Identifier <$> source)
|
||||
|
||||
parenthesizedType :: Assignment
|
||||
parenthesizedType = makeTerm <$> symbol ParenthesizedType <*> (Syntax.Identifier <$> source)
|
||||
|
||||
interpretedStringLiteral :: Assignment
|
||||
interpretedStringLiteral = makeTerm <$> symbol InterpretedStringLiteral <*> (Literal.TextElement <$> source)
|
||||
|
||||
comment :: Assignment
|
||||
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||
|
||||
|
||||
-- Primitive Types
|
||||
|
||||
qualifiedType :: Assignment
|
||||
qualifiedType = makeTerm <$> symbol QualifiedType <*> children (Expression.MemberAccess <$> expression <*> expression)
|
||||
|
||||
arrayType :: Assignment
|
||||
arrayType = makeTerm <$> symbol ArrayType <*> children (Type.Array . Just <$> expression <*> expression)
|
||||
|
||||
implicitLengthArrayType :: Assignment
|
||||
implicitLengthArrayType = makeTerm <$> symbol ImplicitLengthArrayType <*> children (Type.Array Nothing <$> expression)
|
||||
|
||||
functionType :: Assignment
|
||||
functionType = makeTerm <$> symbol FunctionType <*> children (Type.Function <$> parameters <*> returnType)
|
||||
where parameters = symbol Parameters *> children (many expression)
|
||||
returnType = symbol Parameters *> children expressions <|> expression <|> emptyTerm
|
||||
|
||||
sliceType :: Assignment
|
||||
sliceType = makeTerm <$> symbol SliceType <*> children (Type.Slice <$> expression)
|
||||
|
||||
channelType :: Assignment
|
||||
channelType = handleError
|
||||
$ (makeTerm <$> symbol ChannelType <*> (children (token AnonLAngleMinus *> token AnonChan *> (Type.ReceiveChannel <$> expression))))
|
||||
<|> (makeTerm <$> symbol ChannelType <*> (children (token AnonChan *> token AnonLAngleMinus *> (Type.SendChannel <$> expression))))
|
||||
<|> (makeTerm <$> symbol ChannelType <*> (children (token AnonChan *> (Type.BiDirectionalChannel <$> expression))))
|
||||
|
||||
structType :: Assignment
|
||||
structType = handleError $ makeTerm <$> symbol StructType <*> children (Declaration.Constructor <$> emptyTerm <*> many expression)
|
||||
|
||||
interfaceType :: Assignment
|
||||
interfaceType = handleError $ makeTerm <$> symbol InterfaceType <*> children (Type.Interface <$> many expression)
|
||||
|
||||
mapType :: Assignment
|
||||
mapType = handleError $ makeTerm <$> symbol MapType <*> children (Type.Map <$> expression <*> expression)
|
||||
|
||||
pointerType :: Assignment
|
||||
pointerType = handleError $ makeTerm <$> symbol PointerType <*> children (Type.Pointer <$> expression)
|
||||
|
||||
fieldDeclaration :: Assignment
|
||||
fieldDeclaration = mkFieldDeclarationWithTag <$> symbol FieldDeclaration <*> children ((,,) <$> many identifier <*> expression <*> optional expression)
|
||||
where
|
||||
mkFieldDeclarationWithTag loc (fields, type', (Just tag)) = makeTerm loc $ Type.Annotation (makeTerm loc (Type.Annotation (makeTerm loc fields) type')) tag
|
||||
mkFieldDeclarationWithTag loc (fields, type', Nothing) = makeTerm loc $ Type.Annotation (makeTerm loc fields) type'
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
module Language.Go.Syntax where
|
||||
|
||||
import Algorithm
|
||||
import Data.Align.Generic
|
||||
import Data.ByteString (ByteString)
|
||||
import Data.Functor.Classes.Eq.Generic
|
||||
import Data.Functor.Classes.Ord.Generic
|
||||
import Data.Functor.Classes.Show.Generic
|
||||
import Data.Mergeable
|
||||
import GHC.Generics
|
||||
|
||||
-- | Variadic arguments and parameters in Go (e.g. parameter: `param ...Type`, argument: `Type...`).
|
||||
data Variadic a = Variadic { variadicContext :: [a], variadicIdentifier :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Variadic where liftEq = genericLiftEq
|
||||
instance Ord1 Variadic where liftCompare = genericLiftCompare
|
||||
instance Show1 Variadic where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A default pattern in a Go select or switch statement (e.g. `switch { default: s() }`).
|
||||
newtype DefaultPattern a = DefaultPattern { defaultPatternBody :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 DefaultPattern where liftEq = genericLiftEq
|
||||
instance Ord1 DefaultPattern where liftCompare = genericLiftCompare
|
||||
instance Show1 DefaultPattern where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A rune literal in Go (e.g. `'⌘'`).
|
||||
newtype RuneLiteral a = RuneLiteral { runeLiteralContent :: ByteString }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 RuneLiteral where liftEq = genericLiftEq
|
||||
instance Ord1 RuneLiteral where liftCompare = genericLiftCompare
|
||||
instance Show1 RuneLiteral where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A label statement in Go (e.g. `label:continue`).
|
||||
data Label a = Label { labelName :: !a, labelStatement :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Label where liftEq = genericLiftEq
|
||||
instance Ord1 Label where liftCompare = genericLiftCompare
|
||||
instance Show1 Label where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A send statement in Go (e.g. `channel <- value`).
|
||||
data Send a = Send { sendReceiver :: !a, sendValue :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Send where liftEq = genericLiftEq
|
||||
instance Ord1 Send where liftCompare = genericLiftCompare
|
||||
instance Show1 Send where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A defer statement in Go (e.g. `defer x()`).
|
||||
newtype Defer a = Defer { deferBody :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Defer where liftEq = genericLiftEq
|
||||
instance Ord1 Defer where liftCompare = genericLiftCompare
|
||||
instance Show1 Defer where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A go statement (i.e. go routine) in Go (e.g. `go x()`).
|
||||
newtype Go a = Go { goBody :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Go where liftEq = genericLiftEq
|
||||
instance Ord1 Go where liftCompare = genericLiftCompare
|
||||
instance Show1 Go where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A slice expression in Go (e.g. `a[1:4:3]` where a is a list, 1 is the low bound, 4 is the high bound, and 3 is the max capacity).
|
||||
data Slice a = Slice { sliceName :: !a, sliceLow :: !a, sliceHigh :: !a, sliceCapacity :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Slice where liftEq = genericLiftEq
|
||||
instance Ord1 Slice where liftCompare = genericLiftCompare
|
||||
instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A select statement in Go (e.g. `select { case x := <-c: x() }` where each case is a send or receive operation on channels).
|
||||
data Select a = Select { selectCases :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Select where liftEq = genericLiftEq
|
||||
instance Ord1 Select where liftCompare = genericLiftCompare
|
||||
instance Show1 Select where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A type switch statement in Go (e.g. `switch x.(type) { // cases }`).
|
||||
data TypeSwitch a = TypeSwitch { typeSwitchSubject :: !a, typeSwitchCases :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 TypeSwitch where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSwitch where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeSwitch where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A type switch guard statement in a Go type switch statement (e.g. `switch i := x.(type) { // cases}`).
|
||||
newtype TypeSwitchGuard a = TypeSwitchGuard { typeSwitchGuardSubject :: a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 TypeSwitchGuard where liftEq = genericLiftEq
|
||||
instance Ord1 TypeSwitchGuard where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeSwitchGuard where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- | A receive statement in Go (e.g. `value = <-channel` )
|
||||
data Receive a = Receive { receiveSubject :: !a, receiveExpression :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
instance Eq1 Receive where liftEq = genericLiftEq
|
||||
instance Ord1 Receive where liftCompare = genericLiftCompare
|
||||
instance Show1 Receive where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
-- Type Declarations
|
||||
-- | A field declaration in a Go struct type declaration.
|
||||
data Field a = Field { fieldContext :: ![a], fieldName :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
channelTypeDeclaration :: Assignment
|
||||
channelTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> channelType)
|
||||
instance Eq1 Field where liftEq = genericLiftEq
|
||||
instance Ord1 Field where liftCompare = genericLiftCompare
|
||||
instance Show1 Field where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
functionTypeDeclaration :: Assignment
|
||||
functionTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> functionType)
|
||||
-- | A type assertion in Go (e.g. x.(T) where the value of x is not nil and is of type T).
|
||||
data TypeAssertion a = TypeAssertion { typeAssertionSubject :: !a, typeAssertionType :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
interfaceTypeDeclaration :: Assignment
|
||||
interfaceTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> interfaceType)
|
||||
instance Eq1 TypeAssertion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeAssertion where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
mapTypeDeclaration :: Assignment
|
||||
mapTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> mapType)
|
||||
data TypeConversion a = TypeConversion { typeConversionType :: !a, typeConversionSubject :: !a }
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
structTypeDeclaration :: Assignment
|
||||
structTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> structType)
|
||||
instance Eq1 TypeConversion where liftEq = genericLiftEq
|
||||
instance Ord1 TypeConversion where liftCompare = genericLiftCompare
|
||||
instance Show1 TypeConversion where liftShowsPrec = genericLiftShowsPrec
|
||||
|
||||
qualifiedTypeDeclaration :: Assignment
|
||||
qualifiedTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> qualifiedType)
|
||||
newtype ParenthesizedType a = ParenthesizedType a
|
||||
deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable)
|
||||
|
||||
arrayTypeDeclaration :: Assignment
|
||||
arrayTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> arrayType)
|
||||
|
||||
sliceTypeDeclaration :: Assignment
|
||||
sliceTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> sliceType)
|
||||
|
||||
pointerTypeDeclaration :: Assignment
|
||||
pointerTypeDeclaration = makeTerm <$> symbol TypeSpec <*> children (Type.Annotation <$> typeIdentifier <*> pointerType)
|
||||
|
||||
typeDeclaration :: Assignment
|
||||
typeDeclaration = handleError $ makeTerm <$> symbol TypeDeclaration <*> children (many ( arrayTypeDeclaration
|
||||
<|> channelTypeDeclaration
|
||||
<|> functionTypeDeclaration
|
||||
<|> interfaceTypeDeclaration
|
||||
<|> qualifiedTypeDeclaration
|
||||
<|> pointerTypeDeclaration
|
||||
<|> sliceTypeDeclaration
|
||||
<|> structTypeDeclaration
|
||||
<|> mapTypeDeclaration ))
|
||||
|
||||
|
||||
-- Expressions
|
||||
|
||||
parenthesizedExpression :: Assignment
|
||||
parenthesizedExpression = symbol ParenthesizedExpression *> children expressions
|
||||
|
||||
unaryExpression :: Assignment
|
||||
unaryExpression = symbol UnaryExpression >>= \ location -> (notExpression location) <|> (unaryMinus location) <|> unaryPlus
|
||||
where notExpression location = makeTerm location . Expression.Not <$> children (symbol AnonBang *> expression)
|
||||
unaryMinus location = makeTerm location . Expression.Negate <$> children (symbol AnonMinus *> expression)
|
||||
unaryPlus = children (symbol AnonPlus *> expression)
|
||||
|
||||
binaryExpression :: Assignment
|
||||
binaryExpression = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm expression expression
|
||||
[ (inj .) . Expression.Plus <$ symbol AnonPlus
|
||||
, (inj .) . Expression.Minus <$ symbol AnonMinus
|
||||
, (inj .) . Expression.Times <$ symbol AnonStar
|
||||
, (inj .) . Expression.DividedBy <$ symbol AnonSlash
|
||||
, (inj .) . Expression.Modulo <$ symbol AnonPercent
|
||||
, (inj .) . Expression.Or <$ symbol AnonPipePipe
|
||||
, (inj .) . Expression.And <$ symbol AnonAmpersandAmpersand
|
||||
, (inj .) . Expression.LessThan <$ symbol AnonLAngle
|
||||
, (inj .) . Expression.LessThanEqual <$ symbol AnonLAngleEqual
|
||||
, (inj .) . Expression.GreaterThan <$ symbol AnonRAngle
|
||||
, (inj .) . Expression.GreaterThanEqual <$ symbol AnonRAngleEqual
|
||||
, (inj .) . invert Expression.Equal <$ symbol AnonBangEqual
|
||||
, (inj .) . Expression.Equal <$ symbol AnonEqualEqual
|
||||
, (inj .) . Expression.BOr <$ symbol AnonPipe
|
||||
, (inj .) . Expression.BAnd <$ symbol AnonAmpersand
|
||||
, (inj .) . Expression.BAnd <$ symbol AnonAmpersandCaret
|
||||
, (inj .) . Expression.BXOr <$ symbol AnonCaret
|
||||
, (inj .) . Expression.LShift <$ symbol AnonLAngleLAngle
|
||||
, (inj .) . Expression.RShift <$ symbol AnonRAngleRAngle
|
||||
])
|
||||
where invert cons a b = Expression.Not (makeTerm1 (cons a b))
|
||||
|
||||
block :: Assignment
|
||||
block = symbol Block *> children expressions
|
||||
|
||||
callExpression :: Assignment
|
||||
callExpression = makeTerm <$> symbol CallExpression <*> children (Expression.Call <$> pure [] <*> identifier <*> pure [] <*> emptyTerm)
|
||||
|
||||
constVarDeclaration :: Assignment
|
||||
constVarDeclaration = (symbol ConstDeclaration <|> symbol VarDeclaration) *> children expressions
|
||||
|
||||
constVarSpecification :: Assignment
|
||||
constVarSpecification = makeTerm <$> (symbol ConstSpec <|> symbol VarSpec) <*> children (Statement.Assignment
|
||||
<$> pure []
|
||||
<*> (annotatedLHS <|> identifiers)
|
||||
<*> expressions)
|
||||
where
|
||||
annotatedLHS = makeTerm <$> location <*> (Type.Annotation
|
||||
<$> (makeTerm <$> location <*> (manyTermsTill identifier (void (symbol TypeIdentifier))))
|
||||
<*> expression)
|
||||
|
||||
expressionList :: Assignment
|
||||
expressionList = symbol ExpressionList *> children expressions
|
||||
|
||||
functionDeclaration :: Assignment
|
||||
functionDeclaration = mkTypedFunctionDeclaration <$> symbol FunctionDeclaration <*> children ((,,,) <$> expression <*> parameters <*> (expression <|> emptyTerm) <*> block)
|
||||
where mkTypedFunctionDeclaration loc (name', params', types', block') = makeTerm loc (Declaration.Function [types'] name' params' block')
|
||||
parameters = symbol Parameters *> children (many expression)
|
||||
|
||||
importDeclaration :: Assignment
|
||||
importDeclaration = makeTerm <$> symbol ImportDeclaration <*> children (Declaration.Import <$> many expression)
|
||||
|
||||
importSpec :: Assignment
|
||||
importSpec = symbol ImportSpec *> children expressions
|
||||
|
||||
methodDeclaration :: Assignment
|
||||
methodDeclaration = mkTypedMethodDeclaration <$> symbol MethodDeclaration <*> children ((,,,,) <$> receiver <*> fieldIdentifier <*> parameters <*> typeIdentifier <*> block)
|
||||
where parameters = symbol Parameters *> children (symbol ParameterDeclaration *> children (many expression))
|
||||
receiver = symbol Parameters *> children (symbol ParameterDeclaration *> children expressions)
|
||||
mkTypedMethodDeclaration loc (receiver', name', parameters', type'', body') = makeTerm loc (Declaration.Method [type''] receiver' name' parameters' body')
|
||||
|
||||
methodSpec :: Assignment
|
||||
methodSpec = mkMethodSpec <$> symbol MethodSpec <*> children ((,,,,) <$> empty <*> identifier <*> parameters <*> (expression <|> parameters <|> emptyTerm) <*> empty)
|
||||
where parameters = makeTerm <$> symbol Parameters <*> children (many expression)
|
||||
empty = makeTerm <$> location <*> pure Syntax.Empty
|
||||
mkMethodSpec loc (receiver', name', params, optionaltypeLiteral, body') = makeTerm loc $ Type.Annotation (mkMethod loc receiver' name' params body') optionaltypeLiteral
|
||||
mkMethod loc empty' name' params empty'' = makeTerm loc $ Declaration.Method [] empty' name' (pure params) empty''
|
||||
|
||||
packageClause :: Assignment
|
||||
packageClause = makeTerm <$> symbol PackageClause <*> children (Declaration.Module <$> expression <*> pure [])
|
||||
|
||||
parameterDeclaration :: Assignment
|
||||
parameterDeclaration = symbol ParameterDeclaration *> children expressions
|
||||
|
||||
|
||||
-- Statements
|
||||
|
||||
assignment' :: Assignment
|
||||
assignment' = makeTerm' <$> symbol AssignmentStatement <*> children (infixTerm expressionList expressionList
|
||||
[ assign <$ symbol AnonEqual
|
||||
, augmentedAssign Expression.Plus <$ symbol AnonPlusEqual
|
||||
, augmentedAssign Expression.Minus <$ symbol AnonMinusEqual
|
||||
, augmentedAssign Expression.Times <$ symbol AnonStarEqual
|
||||
, augmentedAssign Expression.DividedBy <$ symbol AnonSlashEqual
|
||||
, augmentedAssign Expression.BOr <$ symbol AnonPipeEqual
|
||||
, augmentedAssign Expression.BAnd <$ symbol AnonAmpersandEqual
|
||||
, augmentedAssign Expression.Modulo <$ symbol AnonPercentEqual
|
||||
, augmentedAssign Expression.RShift <$ symbol AnonRAngleRAngleEqual
|
||||
, augmentedAssign Expression.LShift <$ symbol AnonLAngleLAngleEqual
|
||||
, augmentedAssign Expression.BXOr <$ symbol AnonCaretEqual
|
||||
, augmentedAssign (invert Expression.BAnd) <$ symbol AnonAmpersandCaretEqual
|
||||
])
|
||||
where
|
||||
assign :: Term -> Term -> Union Syntax Term
|
||||
assign l r = inj (Statement.Assignment [] l r)
|
||||
|
||||
augmentedAssign :: f :< Syntax => (Term -> Term -> f Term) -> Term -> Term -> Union Syntax Term
|
||||
augmentedAssign c l r = assign l (makeTerm1 (c l r))
|
||||
|
||||
invert cons a b = Expression.Not (makeTerm1 (cons a b))
|
||||
|
||||
shortVarDeclaration :: Assignment
|
||||
shortVarDeclaration = makeTerm <$> symbol ShortVarDeclaration <*> children (Statement.Assignment <$> pure [] <*> expression <*> expression)
|
||||
|
||||
breakStatement :: Assignment
|
||||
breakStatement = makeTerm <$> symbol BreakStatement <*> children (Statement.Break <$> labelName)
|
||||
|
||||
decStatement :: Assignment
|
||||
decStatement = makeTerm <$> symbol DecStatement <*> children (Expression.Decrement <$> expression)
|
||||
|
||||
gotoStatement :: Assignment
|
||||
gotoStatement = makeTerm <$> symbol GotoStatement <*> children (Statement.Goto <$> expression)
|
||||
|
||||
ifStatement :: Assignment
|
||||
ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> expression <*> expression <*> (expression <|> emptyTerm))
|
||||
incStatement :: Assignment
|
||||
incStatement = makeTerm <$> symbol IncStatement <*> children (Expression.Increment <$> expression)
|
||||
|
||||
labelName :: Assignment
|
||||
labelName = makeTerm <$> symbol LabelName <*> (Syntax.Identifier <$> source)
|
||||
|
||||
returnStatement :: Assignment
|
||||
returnStatement = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> (expression <|> emptyTerm))
|
||||
|
||||
-- Helpers
|
||||
|
||||
-- | Match infix terms separated by any of a list of operators, assigning any comments following each operand.
|
||||
infixTerm :: HasCallStack
|
||||
=> Assignment
|
||||
-> Assignment
|
||||
-> [Assignment.Assignment [] Grammar (Term -> Term -> Union Syntax Term)]
|
||||
-> Assignment.Assignment [] Grammar (Union Syntax Term)
|
||||
infixTerm = infixContext comment
|
||||
|
||||
-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present.
|
||||
term :: Assignment -> Assignment
|
||||
term term = contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)
|
||||
|
||||
-- | Match a series of terms or comments until a delimiter is matched
|
||||
manyTermsTill :: Show b => Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term]
|
||||
manyTermsTill step end = manyTill (step <|> comment) end
|
||||
instance Eq1 ParenthesizedType where liftEq = genericLiftEq
|
||||
instance Ord1 ParenthesizedType where liftCompare = genericLiftCompare
|
||||
instance Show1 ParenthesizedType where liftShowsPrec = genericLiftShowsPrec
|
||||
|
@ -22,7 +22,7 @@ import Data.Term
|
||||
import Data.Union
|
||||
import Foreign.Ptr
|
||||
import Language
|
||||
import qualified Language.Go.Syntax as Go
|
||||
import qualified Language.Go.Assignment as Go
|
||||
import qualified Language.JSON.Assignment as JSON
|
||||
import qualified Language.Markdown.Assignment as Markdown
|
||||
import qualified Language.Python.Assignment as Python
|
||||
|
2
test/fixtures/go/array-types.A.go
vendored
2
test/fixtures/go/array-types.A.go
vendored
@ -2,4 +2,6 @@ package main
|
||||
|
||||
func main() {
|
||||
type a [2+2]x
|
||||
type b [3][5]int
|
||||
type c [2][2][2]float64
|
||||
}
|
||||
|
2
test/fixtures/go/array-types.B.go
vendored
2
test/fixtures/go/array-types.B.go
vendored
@ -2,4 +2,6 @@ package main
|
||||
|
||||
func main() {
|
||||
type a [1+1]y
|
||||
type d [6][9]int
|
||||
type e [1][2][3]float64
|
||||
}
|
||||
|
49
test/fixtures/go/array-types.diffA-B.txt
vendored
49
test/fixtures/go/array-types.diffA-B.txt
vendored
@ -2,17 +2,42 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "type_declaration"
|
||||
(TypeDecl
|
||||
(Identifier)
|
||||
(ArrayTy
|
||||
(RelationalOperator
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) }
|
||||
(Other "+")
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) })
|
||||
([])
|
||||
(
|
||||
(
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Plus
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
->(Integer) })
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(
|
||||
(Annotation
|
||||
{ (Identifier)
|
||||
->(Identifier) })))))
|
||||
->(Identifier) }
|
||||
(Array
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(Array
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(Identifier)))))
|
||||
(
|
||||
(Annotation
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Array
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(Array
|
||||
(Integer)
|
||||
(Array
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(Identifier)))))))))
|
||||
|
49
test/fixtures/go/array-types.diffB-A.txt
vendored
49
test/fixtures/go/array-types.diffB-A.txt
vendored
@ -2,17 +2,42 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "type_declaration"
|
||||
(TypeDecl
|
||||
(Identifier)
|
||||
(ArrayTy
|
||||
(RelationalOperator
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) }
|
||||
(Other "+")
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) })
|
||||
([])
|
||||
(
|
||||
(
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Plus
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
->(Integer) })
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(
|
||||
(Annotation
|
||||
{ (Identifier)
|
||||
->(Identifier) })))))
|
||||
->(Identifier) }
|
||||
(Array
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(Array
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(Identifier)))))
|
||||
(
|
||||
(Annotation
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Array
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(Array
|
||||
(Integer)
|
||||
(Array
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(Identifier)))))))))
|
||||
|
39
test/fixtures/go/array-types.parseA.txt
vendored
39
test/fixtures/go/array-types.parseA.txt
vendored
@ -2,14 +2,33 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "type_declaration"
|
||||
(TypeDecl
|
||||
(Identifier)
|
||||
(ArrayTy
|
||||
(RelationalOperator
|
||||
(NumberLiteral)
|
||||
(Other "+")
|
||||
(NumberLiteral))
|
||||
(Identifier))))))
|
||||
([])
|
||||
(
|
||||
(
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Plus
|
||||
(Integer)
|
||||
(Integer))
|
||||
(Identifier))))
|
||||
(
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Integer)
|
||||
(Array
|
||||
(Integer)
|
||||
(Identifier)))))
|
||||
(
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Integer)
|
||||
(Array
|
||||
(Integer)
|
||||
(Array
|
||||
(Integer)
|
||||
(Identifier)))))))))
|
||||
|
39
test/fixtures/go/array-types.parseB.txt
vendored
39
test/fixtures/go/array-types.parseB.txt
vendored
@ -2,14 +2,33 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "type_declaration"
|
||||
(TypeDecl
|
||||
(Identifier)
|
||||
(ArrayTy
|
||||
(RelationalOperator
|
||||
(NumberLiteral)
|
||||
(Other "+")
|
||||
(NumberLiteral))
|
||||
(Identifier))))))
|
||||
([])
|
||||
(
|
||||
(
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Plus
|
||||
(Integer)
|
||||
(Integer))
|
||||
(Identifier))))
|
||||
(
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Integer)
|
||||
(Array
|
||||
(Integer)
|
||||
(Identifier)))))
|
||||
(
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(Array
|
||||
(Integer)
|
||||
(Array
|
||||
(Integer)
|
||||
(Array
|
||||
(Integer)
|
||||
(Identifier)))))))))
|
||||
|
@ -2,18 +2,18 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(Other "composite_literal"
|
||||
(ArrayTy
|
||||
(Identifier))
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) }
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) }
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) }))))))
|
||||
([])
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Composite
|
||||
(Array
|
||||
(Identifier))
|
||||
(
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
->(Integer) })))))
|
||||
|
@ -2,18 +2,18 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(Other "composite_literal"
|
||||
(ArrayTy
|
||||
(Identifier))
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) }
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) }
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) }))))))
|
||||
([])
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Composite
|
||||
(Array
|
||||
(Identifier))
|
||||
(
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
->(Integer) })))))
|
||||
|
@ -2,15 +2,15 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(Other "composite_literal"
|
||||
(ArrayTy
|
||||
(Identifier))
|
||||
(NumberLiteral)
|
||||
(NumberLiteral)
|
||||
(NumberLiteral)))))))
|
||||
([])
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Composite
|
||||
(Array
|
||||
(Identifier))
|
||||
(
|
||||
(Integer)
|
||||
(Integer)
|
||||
(Integer))))))
|
||||
|
@ -2,15 +2,15 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(Other "composite_literal"
|
||||
(ArrayTy
|
||||
(Identifier))
|
||||
(NumberLiteral)
|
||||
(NumberLiteral)
|
||||
(NumberLiteral)))))))
|
||||
([])
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Composite
|
||||
(Array
|
||||
(Identifier))
|
||||
(
|
||||
(Integer)
|
||||
(Integer)
|
||||
(Integer))))))
|
||||
|
8
test/fixtures/go/assignment-statements.A.go
vendored
8
test/fixtures/go/assignment-statements.A.go
vendored
@ -5,4 +5,12 @@ a = 1
|
||||
b, c += 2, 3
|
||||
d *= 3
|
||||
e += 1
|
||||
f <<= 1
|
||||
g >>= 2
|
||||
h /= 2
|
||||
i ^= 2
|
||||
j %= 2
|
||||
k &^= 2
|
||||
|
||||
var pointer *Point3D = &Point3D{y: 1000}
|
||||
}
|
||||
|
16
test/fixtures/go/assignment-statements.B.go
vendored
16
test/fixtures/go/assignment-statements.B.go
vendored
@ -1,8 +1,16 @@
|
||||
package main
|
||||
|
||||
func main() {
|
||||
x = 1
|
||||
y, c += 2, 3
|
||||
z *= 3
|
||||
h += 1
|
||||
h = 1
|
||||
f, g += 2, 3
|
||||
e *= 3
|
||||
d += 1
|
||||
c <<= 1
|
||||
b >>= 2
|
||||
a /= 2
|
||||
z ^= 2
|
||||
y %= 2
|
||||
x &^= 2
|
||||
|
||||
var pointer *Point2D = &Point2D{x: 1000}
|
||||
}
|
||||
|
151
test/fixtures/go/assignment-statements.diffA-B.txt
vendored
151
test/fixtures/go/assignment-statements.diffA-B.txt
vendored
@ -2,31 +2,132 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)
|
||||
(NumberLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))))
|
||||
(Integer))
|
||||
(Assignment
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Plus
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(
|
||||
(Integer)
|
||||
(Integer))))
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Times
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Plus
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(LShift
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(RShift
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(DividedBy
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(BXOr
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Modulo
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Not
|
||||
{+(BAnd
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(
|
||||
{+(Pointer
|
||||
{+(Identifier)+})+}
|
||||
{+(Reference
|
||||
{+(Composite
|
||||
{+(Identifier)+}
|
||||
{+(
|
||||
{+(KeyValue
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+})+})+})+})+}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(Times
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(Plus
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(LShift
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(RShift
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(DividedBy
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(BXOr
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(Modulo
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(Not
|
||||
{-(BAnd
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(
|
||||
{-(Pointer
|
||||
{-(Identifier)-})-}
|
||||
{-(Reference
|
||||
{-(Composite
|
||||
{-(Identifier)-}
|
||||
{-(
|
||||
{-(KeyValue
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-})-})-})-})-})))
|
||||
|
149
test/fixtures/go/assignment-statements.diffB-A.txt
vendored
149
test/fixtures/go/assignment-statements.diffB-A.txt
vendored
@ -2,31 +2,130 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)
|
||||
(NumberLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))))
|
||||
(Integer))
|
||||
(Assignment
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Plus
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(
|
||||
(Integer)
|
||||
(Integer))))
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Times
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (Times
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})
|
||||
->(Plus
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+}) })
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(LShift
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(RShift
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(DividedBy
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(BXOr
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Modulo
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Not
|
||||
{+(BAnd
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+})+}
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(
|
||||
{+(Pointer
|
||||
{+(Identifier)+})+}
|
||||
{+(Reference
|
||||
{+(Composite
|
||||
{+(Identifier)+}
|
||||
{+(
|
||||
{+(KeyValue
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+})+})+})+})+})+}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(Plus
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(LShift
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(RShift
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(DividedBy
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(BXOr
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(Modulo
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(Not
|
||||
{-(BAnd
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-})-}
|
||||
{-(Assignment
|
||||
{-(Identifier)-}
|
||||
{-(
|
||||
{-(Pointer
|
||||
{-(Identifier)-})-}
|
||||
{-(Reference
|
||||
{-(Composite
|
||||
{-(Identifier)-}
|
||||
{-(
|
||||
{-(KeyValue
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-})-})-})-})-})-})))
|
||||
|
@ -2,27 +2,74 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)
|
||||
(NumberLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))))
|
||||
(Integer))
|
||||
(Assignment
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Plus
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Integer)
|
||||
(Integer))))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Times
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Plus
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(LShift
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(RShift
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(DividedBy
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(BXOr
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Modulo
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Not
|
||||
(BAnd
|
||||
(Identifier)
|
||||
(Integer))))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(
|
||||
(Pointer
|
||||
(Identifier))
|
||||
(Reference
|
||||
(Composite
|
||||
(Identifier)
|
||||
(
|
||||
(KeyValue
|
||||
(Identifier)
|
||||
(Integer))))))))))
|
||||
|
@ -2,27 +2,74 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)
|
||||
(NumberLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))))
|
||||
(Integer))
|
||||
(Assignment
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Plus
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(
|
||||
(Integer)
|
||||
(Integer))))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Times
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Plus
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(LShift
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(RShift
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(DividedBy
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(BXOr
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Modulo
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Not
|
||||
(BAnd
|
||||
(Identifier)
|
||||
(Integer))))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(
|
||||
(Pointer
|
||||
(Identifier))
|
||||
(Reference
|
||||
(Composite
|
||||
(Identifier)
|
||||
(
|
||||
(KeyValue
|
||||
(Identifier)
|
||||
(Integer))))))))))
|
||||
|
41
test/fixtures/go/call-expressions.diffA-B.txt
vendored
41
test/fixtures/go/call-expressions.diffA-B.txt
vendored
@ -2,22 +2,27 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(FunctionCall
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)
|
||||
(Other "variadic_argument"
|
||||
(Identifier)))
|
||||
(FunctionCall
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(FunctionCall
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)
|
||||
(Other "variadic_argument"
|
||||
(Identifier)))))
|
||||
([])
|
||||
(
|
||||
(Call
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)
|
||||
(Variadic
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Call
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Call
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)
|
||||
(Variadic
|
||||
(Identifier))
|
||||
(Empty)))))
|
||||
|
41
test/fixtures/go/call-expressions.diffB-A.txt
vendored
41
test/fixtures/go/call-expressions.diffB-A.txt
vendored
@ -2,22 +2,27 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(FunctionCall
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)
|
||||
(Other "variadic_argument"
|
||||
(Identifier)))
|
||||
(FunctionCall
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(FunctionCall
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)
|
||||
(Other "variadic_argument"
|
||||
(Identifier)))))
|
||||
([])
|
||||
(
|
||||
(Call
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)
|
||||
(Variadic
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Call
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Call
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Identifier)
|
||||
(Variadic
|
||||
(Identifier))
|
||||
(Empty)))))
|
||||
|
35
test/fixtures/go/call-expressions.parseA.txt
vendored
35
test/fixtures/go/call-expressions.parseA.txt
vendored
@ -2,19 +2,24 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Other "variadic_argument"
|
||||
(Identifier)))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Other "variadic_argument"
|
||||
(Identifier)))))
|
||||
([])
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Variadic
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Variadic
|
||||
(Identifier))
|
||||
(Empty)))))
|
||||
|
35
test/fixtures/go/call-expressions.parseB.txt
vendored
35
test/fixtures/go/call-expressions.parseB.txt
vendored
@ -2,19 +2,24 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Other "variadic_argument"
|
||||
(Identifier)))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Other "variadic_argument"
|
||||
(Identifier)))))
|
||||
([])
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Variadic
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Variadic
|
||||
(Identifier))
|
||||
(Empty)))))
|
||||
|
9
test/fixtures/go/case-statements.B.go
vendored
9
test/fixtures/go/case-statements.B.go
vendored
@ -2,4 +2,13 @@ package main
|
||||
|
||||
func main() {
|
||||
switch { case foo: f1() }
|
||||
switch e {
|
||||
case 1, 2:
|
||||
a()
|
||||
b()
|
||||
fallthrough
|
||||
default:
|
||||
c()
|
||||
break
|
||||
}
|
||||
}
|
||||
|
45
test/fixtures/go/case-statements.diffA-B.txt
vendored
45
test/fixtures/go/case-statements.diffA-B.txt
vendored
@ -2,12 +2,41 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Switch
|
||||
{+(Case
|
||||
{+(Case
|
||||
{+(Other "expression_list"
|
||||
{+(Identifier)+})+})+}
|
||||
{+(FunctionCall
|
||||
{+(Identifier)+})+})+})))
|
||||
([])
|
||||
{ (Match
|
||||
{-(Empty)-}
|
||||
{-([])-})
|
||||
->(
|
||||
{+(Match
|
||||
{+(Pattern
|
||||
{+(Identifier)+}
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+})+}
|
||||
{+([])+})+}
|
||||
{+(Match
|
||||
{+(Identifier)+}
|
||||
{+(
|
||||
{+(Pattern
|
||||
{+(
|
||||
{+(Integer)+}
|
||||
{+(Integer)+})+}
|
||||
{+(
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Pattern
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+})+})+}
|
||||
{+(DefaultPattern
|
||||
{+(
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Break
|
||||
{+(Empty)+})+})+})+})+})+}) }))
|
||||
|
45
test/fixtures/go/case-statements.diffB-A.txt
vendored
45
test/fixtures/go/case-statements.diffB-A.txt
vendored
@ -2,12 +2,41 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Switch
|
||||
{-(Case
|
||||
{-(Case
|
||||
{-(Other "expression_list"
|
||||
{-(Identifier)-})-})-}
|
||||
{-(FunctionCall
|
||||
{-(Identifier)-})-})-})))
|
||||
([])
|
||||
{ (
|
||||
{-(Match
|
||||
{-(Pattern
|
||||
{-(Identifier)-}
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})-}
|
||||
{-([])-})-}
|
||||
{-(Match
|
||||
{-(Identifier)-}
|
||||
{-(
|
||||
{-(Pattern
|
||||
{-(
|
||||
{-(Integer)-}
|
||||
{-(Integer)-})-}
|
||||
{-(
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Pattern
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})-})-}
|
||||
{-(DefaultPattern
|
||||
{-(
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Break
|
||||
{-(Empty)-})-})-})-})-})-})
|
||||
->(Match
|
||||
{+(Empty)+}
|
||||
{+([])+}) }))
|
||||
|
7
test/fixtures/go/case-statements.parseA.txt
vendored
7
test/fixtures/go/case-statements.parseA.txt
vendored
@ -2,6 +2,9 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Switch)))
|
||||
([])
|
||||
(Match
|
||||
(Empty)
|
||||
([]))))
|
||||
|
42
test/fixtures/go/case-statements.parseB.txt
vendored
42
test/fixtures/go/case-statements.parseB.txt
vendored
@ -2,12 +2,38 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Switch
|
||||
(Case
|
||||
(Case
|
||||
(Other "expression_list"
|
||||
(Identifier)))
|
||||
(FunctionCall
|
||||
(Identifier))))))
|
||||
([])
|
||||
(
|
||||
(Match
|
||||
(Pattern
|
||||
(Identifier)
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
([]))
|
||||
(Match
|
||||
(Identifier)
|
||||
(
|
||||
(Pattern
|
||||
(
|
||||
(Integer)
|
||||
(Integer))
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Pattern
|
||||
(Identifier)
|
||||
(Empty))))
|
||||
(DefaultPattern
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Break
|
||||
(Empty)))))))))
|
||||
|
2
test/fixtures/go/channel-types.A.go
vendored
2
test/fixtures/go/channel-types.A.go
vendored
@ -5,5 +5,7 @@ type (
|
||||
c1 chan<- chan int
|
||||
c2 chan<- chan<- struct{}
|
||||
c3 chan<- <-chan int
|
||||
c4 <-chan <-chan int
|
||||
c5 chan (<-chan int)
|
||||
)
|
||||
}
|
||||
|
2
test/fixtures/go/channel-types.B.go
vendored
2
test/fixtures/go/channel-types.B.go
vendored
@ -5,5 +5,7 @@ type (
|
||||
c2 chan<- chan string
|
||||
c3 chan<- chan<- struct{}
|
||||
c4 chan<- <-chan string
|
||||
c4 <-chan <-chan string
|
||||
c5 chan (<-chan string)
|
||||
)
|
||||
}
|
||||
|
54
test/fixtures/go/channel-types.diffA-B.txt
vendored
54
test/fixtures/go/channel-types.diffA-B.txt
vendored
@ -2,26 +2,52 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "type_declaration"
|
||||
(TypeDecl
|
||||
([])
|
||||
(
|
||||
(Annotation
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(ChannelTy
|
||||
(ChannelTy
|
||||
(BiDirectionalChannel
|
||||
(ReceiveChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(TypeDecl
|
||||
(Annotation
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(ChannelTy
|
||||
(ChannelTy
|
||||
(StructTy))))
|
||||
(TypeDecl
|
||||
(SendChannel
|
||||
(BiDirectionalChannel
|
||||
(Constructor
|
||||
(Empty)))))
|
||||
{+(Annotation
|
||||
{+(Identifier)+}
|
||||
{+(SendChannel
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+})+})+}
|
||||
(Annotation
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(ChannelTy
|
||||
(ChannelTy
|
||||
{ (Identifier)
|
||||
->(Identifier) }))))))
|
||||
{ (SendChannel
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})
|
||||
->(ReceiveChannel
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+}) })
|
||||
{+(Annotation
|
||||
{+(Identifier)+}
|
||||
{+(BiDirectionalChannel
|
||||
{+(ParenthesizedType
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+})+})+})+}
|
||||
{-(Annotation
|
||||
{-(Identifier)-}
|
||||
{-(ReceiveChannel
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(Annotation
|
||||
{-(Identifier)-}
|
||||
{-(BiDirectionalChannel
|
||||
{-(ParenthesizedType
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})-})-})-})))
|
||||
|
59
test/fixtures/go/channel-types.diffB-A.txt
vendored
59
test/fixtures/go/channel-types.diffB-A.txt
vendored
@ -2,26 +2,53 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "type_declaration"
|
||||
(TypeDecl
|
||||
([])
|
||||
(
|
||||
(Annotation
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(ChannelTy
|
||||
(ChannelTy
|
||||
(BiDirectionalChannel
|
||||
(ReceiveChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(TypeDecl
|
||||
(Annotation
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(ChannelTy
|
||||
(ChannelTy
|
||||
(StructTy))))
|
||||
(TypeDecl
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(ChannelTy
|
||||
(ChannelTy
|
||||
{ (Identifier)
|
||||
->(Identifier) }))))))
|
||||
(SendChannel
|
||||
(BiDirectionalChannel
|
||||
(Constructor
|
||||
(Empty)))))
|
||||
{+(Annotation
|
||||
{+(Identifier)+}
|
||||
{+(SendChannel
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(Annotation
|
||||
{+(Identifier)+}
|
||||
{+(ReceiveChannel
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(Annotation
|
||||
{+(Identifier)+}
|
||||
{+(BiDirectionalChannel
|
||||
{+(ParenthesizedType
|
||||
{+(ReceiveChannel
|
||||
{+(Identifier)+})+})+})+})+}
|
||||
{-(Annotation
|
||||
{-(Identifier)-}
|
||||
{-(SendChannel
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(Annotation
|
||||
{-(Identifier)-}
|
||||
{-(ReceiveChannel
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(Annotation
|
||||
{-(Identifier)-}
|
||||
{-(BiDirectionalChannel
|
||||
{-(ParenthesizedType
|
||||
{-(ReceiveChannel
|
||||
{-(Identifier)-})-})-})-})-})))
|
||||
|
39
test/fixtures/go/channel-types.parseA.txt
vendored
39
test/fixtures/go/channel-types.parseA.txt
vendored
@ -2,21 +2,34 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "type_declaration"
|
||||
(TypeDecl
|
||||
([])
|
||||
(
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
(ChannelTy
|
||||
(BiDirectionalChannel
|
||||
(ReceiveChannel
|
||||
(Identifier))))
|
||||
(TypeDecl
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
(ChannelTy
|
||||
(StructTy))))
|
||||
(TypeDecl
|
||||
(SendChannel
|
||||
(BiDirectionalChannel
|
||||
(Constructor
|
||||
(Empty)))))
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
(ChannelTy
|
||||
(Identifier)))))))
|
||||
(SendChannel
|
||||
(ReceiveChannel
|
||||
(Identifier))))
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(ReceiveChannel
|
||||
(ReceiveChannel
|
||||
(Identifier))))
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(BiDirectionalChannel
|
||||
(ParenthesizedType
|
||||
(ReceiveChannel
|
||||
(Identifier))))))))
|
||||
|
39
test/fixtures/go/channel-types.parseB.txt
vendored
39
test/fixtures/go/channel-types.parseB.txt
vendored
@ -2,21 +2,34 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "type_declaration"
|
||||
(TypeDecl
|
||||
([])
|
||||
(
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
(ChannelTy
|
||||
(BiDirectionalChannel
|
||||
(ReceiveChannel
|
||||
(Identifier))))
|
||||
(TypeDecl
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
(ChannelTy
|
||||
(StructTy))))
|
||||
(TypeDecl
|
||||
(SendChannel
|
||||
(BiDirectionalChannel
|
||||
(Constructor
|
||||
(Empty)))))
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
(ChannelTy
|
||||
(Identifier)))))))
|
||||
(SendChannel
|
||||
(ReceiveChannel
|
||||
(Identifier))))
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(ReceiveChannel
|
||||
(ReceiveChannel
|
||||
(Identifier))))
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(BiDirectionalChannel
|
||||
(ParenthesizedType
|
||||
(ReceiveChannel
|
||||
(Identifier))))))))
|
||||
|
3
test/fixtures/go/comment.diffA-B.txt
vendored
3
test/fixtures/go/comment.diffA-B.txt
vendored
@ -2,7 +2,8 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
([])
|
||||
{ (Comment)
|
||||
->(Comment) }))
|
||||
|
3
test/fixtures/go/comment.diffB-A.txt
vendored
3
test/fixtures/go/comment.diffB-A.txt
vendored
@ -2,7 +2,8 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
([])
|
||||
{ (Comment)
|
||||
->(Comment) }))
|
||||
|
3
test/fixtures/go/comment.parseA.txt
vendored
3
test/fixtures/go/comment.parseA.txt
vendored
@ -2,6 +2,7 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
([])
|
||||
(Comment)))
|
||||
|
3
test/fixtures/go/comment.parseB.txt
vendored
3
test/fixtures/go/comment.parseB.txt
vendored
@ -2,6 +2,7 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
([])
|
||||
(Comment)))
|
||||
|
@ -2,16 +2,18 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
{+(Identifier)+}
|
||||
([])
|
||||
(Assignment
|
||||
(Annotation
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{+(Identifier)+})
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Other "expression_list"
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) }
|
||||
{+(NumberLiteral)+})))))
|
||||
->(Identifier) })
|
||||
{ (Integer)
|
||||
->(
|
||||
{+(Integer)+}
|
||||
{+(Integer)+}) })))
|
||||
|
@ -2,17 +2,18 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Other "expression_list"
|
||||
{+(NumberLiteral)+})+}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Other "expression_list"
|
||||
{-(NumberLiteral)-}
|
||||
{-(NumberLiteral)-})-}))))
|
||||
([])
|
||||
(Assignment
|
||||
(Annotation
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{-(Identifier)-})
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (
|
||||
{-(Integer)-}
|
||||
{-(Integer)-})
|
||||
->(Integer) })))
|
||||
|
@ -2,11 +2,12 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(NumberLiteral))))))
|
||||
([])
|
||||
(Assignment
|
||||
(Annotation
|
||||
(
|
||||
(Identifier))
|
||||
(Identifier))
|
||||
(Integer))))
|
||||
|
@ -2,13 +2,15 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)
|
||||
(NumberLiteral))))))
|
||||
([])
|
||||
(Assignment
|
||||
(Annotation
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier))
|
||||
(
|
||||
(Integer)
|
||||
(Integer)))))
|
||||
|
@ -2,16 +2,15 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
{ (VarAssignment
|
||||
{-(Identifier)-}
|
||||
{-(Other "expression_list"
|
||||
{-(NumberLiteral)-})-})
|
||||
->(VarAssignment
|
||||
([])
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Other "expression_list"
|
||||
{+(NumberLiteral)+}
|
||||
{+(NumberLiteral)+})+}) })))
|
||||
{+(Identifier)+}) }
|
||||
{ (Integer)
|
||||
->(
|
||||
{+(Integer)+}
|
||||
{+(Integer)+}) })))
|
||||
|
@ -2,16 +2,15 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
{ (VarAssignment
|
||||
([])
|
||||
(Assignment
|
||||
{ (
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Other "expression_list"
|
||||
{-(NumberLiteral)-}
|
||||
{-(NumberLiteral)-})-})
|
||||
->(VarAssignment
|
||||
{+(Identifier)+}
|
||||
{+(Other "expression_list"
|
||||
{+(NumberLiteral)+})+}) })))
|
||||
{-(Identifier)-})
|
||||
->(Identifier) }
|
||||
{ (
|
||||
{-(Integer)-}
|
||||
{-(Integer)-})
|
||||
->(Integer) })))
|
||||
|
@ -2,10 +2,9 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(NumberLiteral))))))
|
||||
([])
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Integer))))
|
||||
|
@ -2,12 +2,13 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
([])
|
||||
(Assignment
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)
|
||||
(NumberLiteral))))))
|
||||
(Identifier))
|
||||
(
|
||||
(Integer)
|
||||
(Integer)))))
|
||||
|
@ -2,17 +2,19 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Other "expression_list"
|
||||
(Identifier)))
|
||||
(VarAssignment
|
||||
(Identifier))
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(VarAssignment
|
||||
->(Identifier) }
|
||||
([]))
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }))))
|
||||
->(Identifier) }
|
||||
([])))))
|
||||
|
@ -2,17 +2,19 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Other "expression_list"
|
||||
(Identifier)))
|
||||
(VarAssignment
|
||||
(Identifier))
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(VarAssignment
|
||||
->(Identifier) }
|
||||
([]))
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }))))
|
||||
->(Identifier) }
|
||||
([])))))
|
||||
|
@ -2,14 +2,16 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(Identifier)))
|
||||
(VarAssignment
|
||||
(Identifier))
|
||||
(VarAssignment
|
||||
(Identifier)))))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
([]))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
([])))))
|
||||
|
@ -2,14 +2,16 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(Identifier)))
|
||||
(VarAssignment
|
||||
(Identifier))
|
||||
(VarAssignment
|
||||
(Identifier)))))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
([]))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
([])))))
|
||||
|
65
test/fixtures/go/constructors.diffA-B.txt
vendored
65
test/fixtures/go/constructors.diffA-B.txt
vendored
@ -2,35 +2,40 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(RelationalOperator
|
||||
([])
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Other "-")
|
||||
(Identifier)))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) }
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) })
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(DictionaryTy
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) }))))
|
||||
(BiDirectionalChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(BiDirectionalChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Minus
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(BiDirectionalChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Map
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Empty)))))
|
||||
|
65
test/fixtures/go/constructors.diffB-A.txt
vendored
65
test/fixtures/go/constructors.diffB-A.txt
vendored
@ -2,35 +2,40 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(RelationalOperator
|
||||
([])
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Other "-")
|
||||
(Identifier)))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) }
|
||||
{ (NumberLiteral)
|
||||
->(NumberLiteral) })
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(DictionaryTy
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) }))))
|
||||
(BiDirectionalChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(BiDirectionalChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Minus
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(BiDirectionalChannel
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
{ (Integer)
|
||||
->(Integer) }
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Map
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Empty)))))
|
||||
|
49
test/fixtures/go/constructors.parseA.txt
vendored
49
test/fixtures/go/constructors.parseA.txt
vendored
@ -2,28 +2,33 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
(Identifier)))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
(Identifier))
|
||||
(RelationalOperator
|
||||
([])
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Other "-")
|
||||
(Identifier)))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
(Identifier))
|
||||
(NumberLiteral)
|
||||
(NumberLiteral))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(DictionaryTy
|
||||
(BiDirectionalChannel
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)))))
|
||||
(BiDirectionalChannel
|
||||
(Identifier))
|
||||
(Minus
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(BiDirectionalChannel
|
||||
(Identifier))
|
||||
(Integer)
|
||||
(Integer)
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Map
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty)))))
|
||||
|
49
test/fixtures/go/constructors.parseB.txt
vendored
49
test/fixtures/go/constructors.parseB.txt
vendored
@ -2,28 +2,33 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
(Identifier)))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
(Identifier))
|
||||
(RelationalOperator
|
||||
([])
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Other "-")
|
||||
(Identifier)))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(ChannelTy
|
||||
(Identifier))
|
||||
(NumberLiteral)
|
||||
(NumberLiteral))
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(DictionaryTy
|
||||
(BiDirectionalChannel
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)))))
|
||||
(BiDirectionalChannel
|
||||
(Identifier))
|
||||
(Minus
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(BiDirectionalChannel
|
||||
(Identifier))
|
||||
(Integer)
|
||||
(Integer)
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Map
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty)))))
|
||||
|
54
test/fixtures/go/float-literals.diffA-B.txt
vendored
54
test/fixtures/go/float-literals.diffA-B.txt
vendored
@ -2,35 +2,27 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
{ (FloatLiteral)
|
||||
->(FloatLiteral) }))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
{ (FloatLiteral)
|
||||
->(FloatLiteral) }))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
{ (FloatLiteral)
|
||||
->(FloatLiteral) }))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
{ (FloatLiteral)
|
||||
->(FloatLiteral) }))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
{ (FloatLiteral)
|
||||
->(FloatLiteral) }))))
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (Float)
|
||||
->(Float) })
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (Float)
|
||||
->(Float) })
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (Float)
|
||||
->(Float) })
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (Float)
|
||||
->(Float) })
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (Float)
|
||||
->(Float) }))))
|
||||
|
54
test/fixtures/go/float-literals.diffB-A.txt
vendored
54
test/fixtures/go/float-literals.diffB-A.txt
vendored
@ -2,35 +2,27 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
{ (FloatLiteral)
|
||||
->(FloatLiteral) }))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
{ (FloatLiteral)
|
||||
->(FloatLiteral) }))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
{ (FloatLiteral)
|
||||
->(FloatLiteral) }))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
{ (FloatLiteral)
|
||||
->(FloatLiteral) }))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
{ (FloatLiteral)
|
||||
->(FloatLiteral) }))))
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (Float)
|
||||
->(Float) })
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (Float)
|
||||
->(Float) })
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (Float)
|
||||
->(Float) })
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (Float)
|
||||
->(Float) })
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (Float)
|
||||
->(Float) }))))
|
||||
|
44
test/fixtures/go/float-literals.parseA.txt
vendored
44
test/fixtures/go/float-literals.parseA.txt
vendored
@ -2,30 +2,22 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(FloatLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(FloatLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(FloatLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(FloatLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(FloatLiteral)))))
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Float))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Float))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Float))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Float))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Float)))))
|
||||
|
44
test/fixtures/go/float-literals.parseB.txt
vendored
44
test/fixtures/go/float-literals.parseB.txt
vendored
@ -2,30 +2,22 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(FloatLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(FloatLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(FloatLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(FloatLiteral)))
|
||||
(Assignment
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(FloatLiteral)))))
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Float))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Float))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Float))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Float))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Float)))))
|
||||
|
10
test/fixtures/go/for-statements.A.go
vendored
10
test/fixtures/go/for-statements.A.go
vendored
@ -21,4 +21,14 @@ for x := range y {
|
||||
a(x)
|
||||
break
|
||||
}
|
||||
for i, s := range a {
|
||||
g(i, s)
|
||||
}
|
||||
for key, val = range m {
|
||||
h(key, val)
|
||||
}
|
||||
for 1 < 2 {
|
||||
i()
|
||||
}
|
||||
for range ch {}
|
||||
}
|
||||
|
10
test/fixtures/go/for-statements.B.go
vendored
10
test/fixtures/go/for-statements.B.go
vendored
@ -21,4 +21,14 @@ for {
|
||||
a(x)
|
||||
break
|
||||
}
|
||||
for s, i := range b {
|
||||
g(i, s)
|
||||
}
|
||||
for k, v = range m {
|
||||
h(k, v)
|
||||
}
|
||||
for 2 < 1 {
|
||||
j()
|
||||
}
|
||||
for range b {}
|
||||
}
|
||||
|
228
test/fixtures/go/for-statements.diffA-B.txt
vendored
228
test/fixtures/go/for-statements.diffA-B.txt
vendored
@ -2,81 +2,169 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
{ (For
|
||||
{-(ExpressionStatements
|
||||
{-(FunctionCall
|
||||
{-(Identifier)-})-}
|
||||
{-(Other "goto_statement"
|
||||
{-(Identifier)-})-})-})
|
||||
->(For
|
||||
{+(FunctionCall
|
||||
{+(Identifier)+})+}
|
||||
{+(Other "goto_statement"
|
||||
{+(Identifier)+})+}) }
|
||||
{+(For
|
||||
{+(Other "expression_list"
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(FunctionCall
|
||||
{+(Identifier)+})+}
|
||||
{+(Break
|
||||
{+(Identifier)+})+})+}
|
||||
{+(For
|
||||
{+(FunctionCall
|
||||
{+(Identifier)+})+}
|
||||
{+(Continue
|
||||
{+(Identifier)+})+})+}
|
||||
{+(For
|
||||
{+(RelationalOperator
|
||||
([])
|
||||
(
|
||||
(For
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Goto
|
||||
(Identifier))))
|
||||
{+(ForEach
|
||||
{+(Identifier)+}
|
||||
{+(Other "<")+}
|
||||
{+(NumberLiteral)+})+}
|
||||
{+(IncrementStatement)+}
|
||||
{+(FunctionCall
|
||||
{+(Identifier)+})+}
|
||||
{+(Continue)+})+}
|
||||
{+(For
|
||||
{+(ExpressionStatements
|
||||
{+(FunctionCall
|
||||
{+(Identifier)+}
|
||||
{+(
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Break
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(For
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Continue
|
||||
{+(Identifier)+})+})+})+}
|
||||
(For
|
||||
{ (Assignment
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})
|
||||
->(LessThan
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+}) }
|
||||
{ (LessThan
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})
|
||||
->(PostIncrement
|
||||
{+(Identifier)+}) }
|
||||
{ (PostIncrement
|
||||
{-(Identifier)-})
|
||||
->(Empty) }
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
{+(Continue
|
||||
{+(Empty)+})+}
|
||||
{-(Break
|
||||
{-(Identifier)-})-}))
|
||||
{+(For
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Break
|
||||
{+(Empty)+})+})+})+}
|
||||
{+(ForEach
|
||||
{+(
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Break)+})+})+}
|
||||
{-(For
|
||||
{-(VarDecl
|
||||
{-(Other "expression_list"
|
||||
{+(Identifier)+}
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+})+}
|
||||
{+(ForEach
|
||||
{+(
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+})+}
|
||||
{+(For
|
||||
{+(Empty)+}
|
||||
{+(LessThan
|
||||
{+(Integer)+}
|
||||
{+(Integer)+})+}
|
||||
{+(Empty)+}
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+})+}
|
||||
{+(ForEach
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+([])+})+}
|
||||
{-(For
|
||||
{-(LessThan
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-}
|
||||
{-(PostIncrement
|
||||
{-(Identifier)-})-}
|
||||
{-(Other "expression_list"
|
||||
{-(NumberLiteral)-})-})-}
|
||||
{-(RelationalOperator
|
||||
{-(Empty)-}
|
||||
{-(
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Continue
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(For
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Continue
|
||||
{-(Empty)-})-})-})-}
|
||||
{-(ForEach
|
||||
{-(Identifier)-}
|
||||
{-(Other "<")-}
|
||||
{-(NumberLiteral)-})-}
|
||||
{-(IncrementStatement)-}
|
||||
{-(FunctionCall
|
||||
{-(Identifier)-})-}
|
||||
{-(Break
|
||||
{-(Identifier)-})-})-}
|
||||
{-(For
|
||||
{-(RelationalOperator
|
||||
{-(Identifier)-}
|
||||
{-(Other "<")-}
|
||||
{-(NumberLiteral)-})-}
|
||||
{-(IncrementStatement)-}
|
||||
{-(FunctionCall
|
||||
{-(Identifier)-})-}
|
||||
{-(Continue
|
||||
{-(Identifier)-})-})-}
|
||||
{-(For
|
||||
{-(FunctionCall
|
||||
{-(Identifier)-})-}
|
||||
{-(Continue)-})-}
|
||||
{-(For
|
||||
{-(Other "expression_list"
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(FunctionCall
|
||||
{-(
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Break
|
||||
{-(Empty)-})-})-})-}
|
||||
{-(ForEach
|
||||
{-(
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Break)-})-}))
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})-}
|
||||
{-(ForEach
|
||||
{-(
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})-}
|
||||
{-(For
|
||||
{-(Empty)-}
|
||||
{-(LessThan
|
||||
{-(Integer)-}
|
||||
{-(Integer)-})-}
|
||||
{-(Empty)-}
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})-}
|
||||
{-(ForEach
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-([])-})-})))
|
||||
|
222
test/fixtures/go/for-statements.diffB-A.txt
vendored
222
test/fixtures/go/for-statements.diffB-A.txt
vendored
@ -2,74 +2,166 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
{ (For
|
||||
{-(FunctionCall
|
||||
{-(Identifier)-})-}
|
||||
{-(Other "goto_statement"
|
||||
{-(Identifier)-})-})
|
||||
->(For
|
||||
{+(ExpressionStatements
|
||||
{+(FunctionCall
|
||||
([])
|
||||
(
|
||||
(For
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Goto
|
||||
(Identifier))))
|
||||
{+(For
|
||||
{+(Assignment
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+}
|
||||
{+(LessThan
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+}
|
||||
{+(PostIncrement
|
||||
{+(Identifier)+})+}
|
||||
{+(Other "goto_statement"
|
||||
{+(Identifier)+})+})+}) }
|
||||
{+(For
|
||||
{+(VarDecl
|
||||
{+(Other "expression_list"
|
||||
{+(
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Break
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(For
|
||||
{+(LessThan
|
||||
{+(Identifier)+}
|
||||
{+(Integer)+})+}
|
||||
{+(PostIncrement
|
||||
{+(Identifier)+})+}
|
||||
{+(Other "expression_list"
|
||||
{+(NumberLiteral)+})+})+}
|
||||
{+(RelationalOperator
|
||||
{+(Identifier)+}
|
||||
{+(Other "<")+}
|
||||
{+(NumberLiteral)+})+}
|
||||
{+(IncrementStatement)+}
|
||||
{+(FunctionCall
|
||||
{+(Identifier)+})+}
|
||||
{+(Break
|
||||
{+(Identifier)+})+})+}
|
||||
{+(For
|
||||
{+(RelationalOperator
|
||||
{+(Identifier)+}
|
||||
{+(Other "<")+}
|
||||
{+(NumberLiteral)+})+}
|
||||
{+(IncrementStatement)+}
|
||||
{+(FunctionCall
|
||||
{+(Identifier)+})+}
|
||||
{+(Continue
|
||||
{+(Identifier)+})+})+}
|
||||
{+(For
|
||||
{+(FunctionCall
|
||||
{+(Identifier)+})+}
|
||||
{+(Continue)+})+}
|
||||
(For
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(FunctionCall
|
||||
{+(Empty)+}
|
||||
{+(
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Continue
|
||||
{+(Identifier)+})+})+})+}
|
||||
{+(For
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(Empty)+}
|
||||
{+(
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+}
|
||||
{+(Continue
|
||||
{+(Empty)+})+})+})+}
|
||||
(ForEach
|
||||
(Identifier)
|
||||
{+(Identifier)+})
|
||||
(Break
|
||||
{-(Identifier)-}))
|
||||
{-(For
|
||||
{-(FunctionCall
|
||||
{-(Identifier)-})-}
|
||||
{-(Continue
|
||||
{-(Identifier)-})-})-}
|
||||
{-(For
|
||||
{-(RelationalOperator
|
||||
{-(Identifier)-}
|
||||
{-(Other "<")-}
|
||||
{-(NumberLiteral)-})-}
|
||||
{-(IncrementStatement)-}
|
||||
{-(FunctionCall
|
||||
{-(Identifier)-})-}
|
||||
{-(Continue)-})-}
|
||||
{-(For
|
||||
{-(ExpressionStatements
|
||||
{-(FunctionCall
|
||||
(Identifier)
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
{+(Identifier)+}
|
||||
(Empty))
|
||||
(Break
|
||||
{ (Identifier)
|
||||
->(Empty) })))
|
||||
{+(ForEach
|
||||
{+(
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+})+}
|
||||
{+(ForEach
|
||||
{+(
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+})+}
|
||||
{+(Identifier)+}
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+})+}
|
||||
{+(For
|
||||
{+(Empty)+}
|
||||
{+(LessThan
|
||||
{+(Integer)+}
|
||||
{+(Integer)+})+}
|
||||
{+(Empty)+}
|
||||
{+(Call
|
||||
{+(Identifier)+}
|
||||
{+(Empty)+})+})+}
|
||||
{+(ForEach
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+([])+})+}
|
||||
{-(For
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Continue
|
||||
{-(Identifier)-})-})-})-}
|
||||
{-(For
|
||||
{-(LessThan
|
||||
{-(Identifier)-}
|
||||
{-(Integer)-})-}
|
||||
{-(PostIncrement
|
||||
{-(Identifier)-})-}
|
||||
{-(Empty)-}
|
||||
{-(
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Continue
|
||||
{-(Empty)-})-})-})-}
|
||||
{-(For
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(Empty)-}
|
||||
{-(
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-}
|
||||
{-(Break
|
||||
{-(Empty)-})-})-})-}
|
||||
{-(ForEach
|
||||
{-(
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Break)-})-})-}))
|
||||
{-(Identifier)-}
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})-}
|
||||
{-(ForEach
|
||||
{-(
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-})-}
|
||||
{-(Identifier)-}
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})-}
|
||||
{-(For
|
||||
{-(Empty)-}
|
||||
{-(LessThan
|
||||
{-(Integer)-}
|
||||
{-(Integer)-})-}
|
||||
{-(Empty)-}
|
||||
{-(Call
|
||||
{-(Identifier)-}
|
||||
{-(Empty)-})-})-}
|
||||
{-(ForEach
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-([])-})-})))
|
||||
|
128
test/fixtures/go/for-statements.parseA.txt
vendored
128
test/fixtures/go/for-statements.parseA.txt
vendored
@ -2,48 +2,98 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(For
|
||||
(ExpressionStatements
|
||||
(FunctionCall
|
||||
([])
|
||||
(
|
||||
(For
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Goto
|
||||
(Identifier))))
|
||||
(For
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Integer))
|
||||
(LessThan
|
||||
(Identifier)
|
||||
(Integer))
|
||||
(PostIncrement
|
||||
(Identifier))
|
||||
(Other "goto_statement"
|
||||
(Identifier))))
|
||||
(For
|
||||
(VarDecl
|
||||
(Other "expression_list"
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Break
|
||||
(Identifier))))
|
||||
(For
|
||||
(LessThan
|
||||
(Identifier)
|
||||
(Integer))
|
||||
(PostIncrement
|
||||
(Identifier))
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))
|
||||
(RelationalOperator
|
||||
(Empty)
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Continue
|
||||
(Identifier))))
|
||||
(For
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Continue
|
||||
(Empty))))
|
||||
(ForEach
|
||||
(Identifier)
|
||||
(Other "<")
|
||||
(NumberLiteral))
|
||||
(IncrementStatement)
|
||||
(FunctionCall
|
||||
(Identifier))
|
||||
(Break
|
||||
(Identifier)))
|
||||
(For
|
||||
(RelationalOperator
|
||||
(Identifier)
|
||||
(Other "<")
|
||||
(NumberLiteral))
|
||||
(IncrementStatement)
|
||||
(FunctionCall
|
||||
(Identifier))
|
||||
(Continue
|
||||
(Identifier)))
|
||||
(For
|
||||
(FunctionCall
|
||||
(Identifier))
|
||||
(Continue))
|
||||
(For
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(FunctionCall
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Break
|
||||
(Empty))))
|
||||
(ForEach
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Break))))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(ForEach
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(For
|
||||
(Empty)
|
||||
(LessThan
|
||||
(Integer)
|
||||
(Integer))
|
||||
(Empty)
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(ForEach
|
||||
(Empty)
|
||||
(Identifier)
|
||||
([])))))
|
||||
|
117
test/fixtures/go/for-statements.parseB.txt
vendored
117
test/fixtures/go/for-statements.parseB.txt
vendored
@ -2,38 +2,93 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(For
|
||||
(FunctionCall
|
||||
(Identifier))
|
||||
(Other "goto_statement"
|
||||
(Identifier)))
|
||||
(For
|
||||
(Other "expression_list"
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(FunctionCall
|
||||
(Identifier))
|
||||
(Break
|
||||
(Identifier)))
|
||||
(For
|
||||
(FunctionCall
|
||||
(Identifier))
|
||||
(Continue
|
||||
(Identifier)))
|
||||
(For
|
||||
(RelationalOperator
|
||||
([])
|
||||
(
|
||||
(For
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Goto
|
||||
(Identifier))))
|
||||
(ForEach
|
||||
(Identifier)
|
||||
(Other "<")
|
||||
(NumberLiteral))
|
||||
(IncrementStatement)
|
||||
(FunctionCall
|
||||
(Identifier))
|
||||
(Continue))
|
||||
(For
|
||||
(ExpressionStatements
|
||||
(FunctionCall
|
||||
(Identifier)
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Break
|
||||
(Identifier))))
|
||||
(For
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Continue
|
||||
(Identifier))))
|
||||
(For
|
||||
(LessThan
|
||||
(Identifier)
|
||||
(Integer))
|
||||
(PostIncrement
|
||||
(Identifier))
|
||||
(Empty)
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Continue
|
||||
(Empty))))
|
||||
(For
|
||||
(Empty)
|
||||
(Empty)
|
||||
(Empty)
|
||||
(
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Break
|
||||
(Empty))))
|
||||
(ForEach
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Break)))))
|
||||
(Identifier)
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(ForEach
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Call
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(For
|
||||
(Empty)
|
||||
(LessThan
|
||||
(Integer)
|
||||
(Integer))
|
||||
(Empty)
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(ForEach
|
||||
(Empty)
|
||||
(Identifier)
|
||||
([])))))
|
||||
|
1
test/fixtures/go/function-declarations.A.go
vendored
1
test/fixtures/go/function-declarations.A.go
vendored
@ -5,3 +5,4 @@ func f1() {}
|
||||
func f2(a int, b, c, d string) int {}
|
||||
func f2() (int, error) {}
|
||||
func f2() (result int, err error) {}
|
||||
func lockedOSThread() bool
|
||||
|
2
test/fixtures/go/function-declarations.B.go
vendored
2
test/fixtures/go/function-declarations.B.go
vendored
@ -5,3 +5,5 @@ func fa() {}
|
||||
func fb(a int, b, c, d string) int {}
|
||||
func fc() (int, error) {}
|
||||
func fd() (result int, err error) {}
|
||||
func fe() () {;}
|
||||
func lockOSThread() int
|
||||
|
@ -2,40 +2,63 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args))
|
||||
([])
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Args))
|
||||
([])
|
||||
([]))
|
||||
(Function
|
||||
(Identifier)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Args
|
||||
(ParameterDecl
|
||||
(
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(ParameterDecl
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Args)
|
||||
(Args
|
||||
([])
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Args)
|
||||
(Args
|
||||
(ParameterDecl
|
||||
([])
|
||||
(
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(ParameterDecl
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))))
|
||||
(Identifier)))
|
||||
([]))
|
||||
{+(Function
|
||||
{+(Empty)+}
|
||||
{+(Identifier)+}
|
||||
{+([])+}
|
||||
{+([])+}
|
||||
{+(NoOp
|
||||
{+(Empty)+})+})+}
|
||||
(Function
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
([])
|
||||
(Empty)))
|
||||
|
@ -2,40 +2,66 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args))
|
||||
([])
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Args))
|
||||
([])
|
||||
([]))
|
||||
(Function
|
||||
(Identifier)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Args
|
||||
(ParameterDecl
|
||||
(
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(ParameterDecl
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Args)
|
||||
(Args
|
||||
([])
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Args)
|
||||
(Args
|
||||
(ParameterDecl
|
||||
([])
|
||||
(
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(ParameterDecl
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))))
|
||||
(Identifier)))
|
||||
([]))
|
||||
{+(Function
|
||||
{+(Identifier)+}
|
||||
{+(Identifier)+}
|
||||
{+([])+}
|
||||
{+(Empty)+})+}
|
||||
{-(Function
|
||||
{-(Empty)-}
|
||||
{-(Identifier)-}
|
||||
{-([])-}
|
||||
{-([])-}
|
||||
{-(NoOp
|
||||
{-(Empty)-})-})-}
|
||||
{-(Function
|
||||
{-(Identifier)-}
|
||||
{-(Identifier)-}
|
||||
{-([])-}
|
||||
{-(Empty)-})-})
|
||||
|
@ -2,36 +2,50 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args))
|
||||
([])
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
([])
|
||||
([]))
|
||||
(Function
|
||||
(Identifier)
|
||||
(Args))
|
||||
(Function
|
||||
(Identifier)
|
||||
(Args
|
||||
(ParameterDecl
|
||||
(
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(ParameterDecl
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Args
|
||||
([])
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Args
|
||||
(ParameterDecl
|
||||
([])
|
||||
(
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(ParameterDecl
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))))
|
||||
(Identifier)))
|
||||
([]))
|
||||
(Function
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
([])
|
||||
(Empty)))
|
||||
|
@ -2,36 +2,57 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args))
|
||||
([])
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
([])
|
||||
([]))
|
||||
(Function
|
||||
(Identifier)
|
||||
(Args))
|
||||
(Function
|
||||
(Identifier)
|
||||
(Args
|
||||
(ParameterDecl
|
||||
(
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(ParameterDecl
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Args
|
||||
([])
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))
|
||||
(Identifier))
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Args
|
||||
(ParameterDecl
|
||||
([])
|
||||
(
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(ParameterDecl
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))))
|
||||
(Identifier)))
|
||||
([]))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
([])
|
||||
([])
|
||||
(NoOp
|
||||
(Empty)))
|
||||
(Function
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
([])
|
||||
(Empty)))
|
||||
|
30
test/fixtures/go/function-literals.diffA-B.txt
vendored
30
test/fixtures/go/function-literals.diffA-B.txt
vendored
@ -2,18 +2,26 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(AnonymousFunction
|
||||
([])
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Function
|
||||
(Empty)
|
||||
(Empty)
|
||||
(
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Return
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)
|
||||
(NumberLiteral)))))))))
|
||||
->(Identifier) }))
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Return
|
||||
(
|
||||
(Integer)
|
||||
(Integer)))))))
|
||||
|
30
test/fixtures/go/function-literals.diffB-A.txt
vendored
30
test/fixtures/go/function-literals.diffB-A.txt
vendored
@ -2,18 +2,26 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(AnonymousFunction
|
||||
([])
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Function
|
||||
(Empty)
|
||||
(Empty)
|
||||
(
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Return
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)
|
||||
(NumberLiteral)))))))))
|
||||
->(Identifier) }))
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Return
|
||||
(
|
||||
(Integer)
|
||||
(Integer)))))))
|
||||
|
28
test/fixtures/go/function-literals.parseA.txt
vendored
28
test/fixtures/go/function-literals.parseA.txt
vendored
@ -2,16 +2,22 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(AnonymousFunction
|
||||
([])
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Function
|
||||
(Empty)
|
||||
(Empty)
|
||||
(
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Return
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)
|
||||
(NumberLiteral)))))))))
|
||||
(Identifier)))
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Return
|
||||
(
|
||||
(Integer)
|
||||
(Integer)))))))
|
||||
|
28
test/fixtures/go/function-literals.parseB.txt
vendored
28
test/fixtures/go/function-literals.parseB.txt
vendored
@ -2,16 +2,22 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "const_declaration"
|
||||
(VarAssignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(AnonymousFunction
|
||||
([])
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Function
|
||||
(Empty)
|
||||
(Empty)
|
||||
(
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)
|
||||
(Return
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)
|
||||
(NumberLiteral)))))))))
|
||||
(Identifier)))
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Return
|
||||
(
|
||||
(Integer)
|
||||
(Integer)))))))
|
||||
|
26
test/fixtures/go/function-types.diffA-B.txt
vendored
26
test/fixtures/go/function-types.diffA-B.txt
vendored
@ -2,29 +2,31 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "type_declaration"
|
||||
(TypeDecl
|
||||
([])
|
||||
(
|
||||
(Annotation
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(FunctionTy
|
||||
(Args
|
||||
(Function
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
||||
(TypeDecl
|
||||
(Annotation
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(FunctionTy
|
||||
(Args
|
||||
(Function
|
||||
(
|
||||
{-(Identifier)-}
|
||||
(Identifier)
|
||||
{+(Identifier)+})
|
||||
(Args
|
||||
{+(ParameterDecl
|
||||
{+(ChannelTy
|
||||
(
|
||||
{+(
|
||||
{+(BiDirectionalChannel
|
||||
{+(Identifier)+})+})+}
|
||||
{-(Identifier)-}
|
||||
(Identifier)))))))
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
|
26
test/fixtures/go/function-types.diffB-A.txt
vendored
26
test/fixtures/go/function-types.diffB-A.txt
vendored
@ -2,29 +2,31 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "type_declaration"
|
||||
(TypeDecl
|
||||
([])
|
||||
(
|
||||
(Annotation
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(FunctionTy
|
||||
(Args
|
||||
(Function
|
||||
(
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
||||
(TypeDecl
|
||||
(Annotation
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(FunctionTy
|
||||
(Args
|
||||
(Function
|
||||
(
|
||||
{-(Identifier)-}
|
||||
(Identifier)
|
||||
{+(Identifier)+})
|
||||
(Args
|
||||
(
|
||||
{+(Identifier)+}
|
||||
{-(ParameterDecl
|
||||
{-(ChannelTy
|
||||
{-(
|
||||
{-(BiDirectionalChannel
|
||||
{-(Identifier)-})-})-}
|
||||
(Identifier)))))))
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
|
22
test/fixtures/go/function-types.parseA.txt
vendored
22
test/fixtures/go/function-types.parseA.txt
vendored
@ -2,21 +2,23 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "type_declaration"
|
||||
(TypeDecl
|
||||
([])
|
||||
(
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(FunctionTy
|
||||
(Args
|
||||
(Function
|
||||
(
|
||||
(Identifier))
|
||||
(Identifier)))
|
||||
(TypeDecl
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(FunctionTy
|
||||
(Args
|
||||
(Function
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Args
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier)))))))
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
|
26
test/fixtures/go/function-types.parseB.txt
vendored
26
test/fixtures/go/function-types.parseB.txt
vendored
@ -2,23 +2,25 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "type_declaration"
|
||||
(TypeDecl
|
||||
([])
|
||||
(
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(FunctionTy
|
||||
(Args
|
||||
(Function
|
||||
(
|
||||
(Identifier))
|
||||
(Identifier)))
|
||||
(TypeDecl
|
||||
(Annotation
|
||||
(Identifier)
|
||||
(FunctionTy
|
||||
(Args
|
||||
(Function
|
||||
(
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Args
|
||||
(ParameterDecl
|
||||
(ChannelTy
|
||||
(
|
||||
(
|
||||
(BiDirectionalChannel
|
||||
(Identifier)))
|
||||
(Identifier)))))))
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
|
@ -2,19 +2,23 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Defer
|
||||
(FunctionCall
|
||||
(SubscriptAccess
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(Go
|
||||
(FunctionCall
|
||||
(SubscriptAccess
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })))))
|
||||
([])
|
||||
(
|
||||
(Defer
|
||||
(Call
|
||||
(MemberAccess
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Empty)))
|
||||
(Go
|
||||
(Call
|
||||
(MemberAccess
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Empty))))))
|
||||
|
@ -2,19 +2,23 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Defer
|
||||
(FunctionCall
|
||||
(SubscriptAccess
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })))
|
||||
(Go
|
||||
(FunctionCall
|
||||
(SubscriptAccess
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })))))
|
||||
([])
|
||||
(
|
||||
(Defer
|
||||
(Call
|
||||
(MemberAccess
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Empty)))
|
||||
(Go
|
||||
(Call
|
||||
(MemberAccess
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Empty))))))
|
||||
|
@ -2,15 +2,19 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Defer
|
||||
(FunctionCall
|
||||
(SubscriptAccess
|
||||
(Identifier)
|
||||
(Identifier))))
|
||||
(Go
|
||||
(FunctionCall
|
||||
(SubscriptAccess
|
||||
(Identifier)
|
||||
(Identifier))))))
|
||||
([])
|
||||
(
|
||||
(Defer
|
||||
(Call
|
||||
(MemberAccess
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty)))
|
||||
(Go
|
||||
(Call
|
||||
(MemberAccess
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
|
@ -2,15 +2,19 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Defer
|
||||
(FunctionCall
|
||||
(SubscriptAccess
|
||||
(Identifier)
|
||||
(Identifier))))
|
||||
(Go
|
||||
(FunctionCall
|
||||
(SubscriptAccess
|
||||
(Identifier)
|
||||
(Identifier))))))
|
||||
([])
|
||||
(
|
||||
(Defer
|
||||
(Call
|
||||
(MemberAccess
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty)))
|
||||
(Go
|
||||
(Call
|
||||
(MemberAccess
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(Empty))))))
|
||||
|
@ -1,17 +1,17 @@
|
||||
(Program
|
||||
(Module
|
||||
(Identifier))
|
||||
(Other "import_declaration"
|
||||
(Import
|
||||
{ (StringLiteral)
|
||||
->(StringLiteral) })
|
||||
(Import
|
||||
{ (StringLiteral)
|
||||
->(StringLiteral) })
|
||||
(Import
|
||||
(Import
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(
|
||||
(Identifier)
|
||||
{ (StringLiteral)
|
||||
->(StringLiteral) }))
|
||||
{ (TextElement)
|
||||
->(TextElement) }))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)))
|
||||
([])
|
||||
([])))
|
||||
|
@ -1,17 +1,17 @@
|
||||
(Program
|
||||
(Module
|
||||
(Identifier))
|
||||
(Other "import_declaration"
|
||||
(Import
|
||||
{ (StringLiteral)
|
||||
->(StringLiteral) })
|
||||
(Import
|
||||
{ (StringLiteral)
|
||||
->(StringLiteral) })
|
||||
(Import
|
||||
(Import
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
{ (TextElement)
|
||||
->(TextElement) }
|
||||
(
|
||||
(Identifier)
|
||||
{ (StringLiteral)
|
||||
->(StringLiteral) }))
|
||||
{ (TextElement)
|
||||
->(TextElement) }))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)))
|
||||
([])
|
||||
([])))
|
||||
|
@ -1,14 +1,14 @@
|
||||
(Program
|
||||
(Module
|
||||
(Identifier))
|
||||
(Other "import_declaration"
|
||||
(Import
|
||||
(StringLiteral))
|
||||
(Import
|
||||
(StringLiteral))
|
||||
(Import
|
||||
(Import
|
||||
(TextElement)
|
||||
(TextElement)
|
||||
(
|
||||
(Identifier)
|
||||
(StringLiteral)))
|
||||
(TextElement)))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)))
|
||||
([])
|
||||
([])))
|
||||
|
@ -1,14 +1,14 @@
|
||||
(Program
|
||||
(Module
|
||||
(Identifier))
|
||||
(Other "import_declaration"
|
||||
(Import
|
||||
(StringLiteral))
|
||||
(Import
|
||||
(StringLiteral))
|
||||
(Import
|
||||
(Import
|
||||
(TextElement)
|
||||
(TextElement)
|
||||
(
|
||||
(Identifier)
|
||||
(StringLiteral)))
|
||||
(TextElement)))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)))
|
||||
([])
|
||||
([])))
|
||||
|
@ -2,16 +2,15 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "var_declaration"
|
||||
(VarAssignment
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))
|
||||
(VarAssignment
|
||||
(Integer))
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Other "expression_list"
|
||||
(NumberLiteral))))))
|
||||
(Integer)))))
|
||||
|
@ -2,16 +2,15 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "var_declaration"
|
||||
(VarAssignment
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))
|
||||
(VarAssignment
|
||||
(Integer))
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Other "expression_list"
|
||||
(NumberLiteral))))))
|
||||
(Integer)))))
|
||||
|
@ -2,14 +2,13 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "var_declaration"
|
||||
(VarAssignment
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))
|
||||
(VarAssignment
|
||||
(Integer))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(NumberLiteral))))))
|
||||
(Integer)))))
|
||||
|
@ -2,14 +2,13 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(Other "var_declaration"
|
||||
(VarAssignment
|
||||
([])
|
||||
(
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(NumberLiteral)))
|
||||
(VarAssignment
|
||||
(Integer))
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(Other "expression_list"
|
||||
(NumberLiteral))))))
|
||||
(Integer)))))
|
||||
|
7
test/fixtures/go/if-statements.A.go
vendored
7
test/fixtures/go/if-statements.A.go
vendored
@ -12,4 +12,11 @@ b()
|
||||
} else {
|
||||
c()
|
||||
}
|
||||
if num := 9; num < 0 {
|
||||
d()
|
||||
} else if num < 10 {
|
||||
e()
|
||||
} else {
|
||||
f()
|
||||
}
|
||||
}
|
||||
|
7
test/fixtures/go/if-statements.B.go
vendored
7
test/fixtures/go/if-statements.B.go
vendored
@ -12,4 +12,11 @@ b()
|
||||
} else {
|
||||
c()
|
||||
}
|
||||
if num := 10; num < 0 {
|
||||
f()
|
||||
} else if num < 100 {
|
||||
g()
|
||||
} else {
|
||||
h()
|
||||
}
|
||||
}
|
||||
|
95
test/fixtures/go/if-statements.diffA-B.txt
vendored
95
test/fixtures/go/if-statements.diffA-B.txt
vendored
@ -2,36 +2,69 @@
|
||||
(Module
|
||||
(Identifier))
|
||||
(Function
|
||||
(Empty)
|
||||
(Identifier)
|
||||
(Args)
|
||||
(If
|
||||
(FunctionCall
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(ExpressionStatements
|
||||
(FunctionCall
|
||||
(Identifier))))
|
||||
(If
|
||||
(Other "if_initializer"
|
||||
(VarDecl
|
||||
(Other "expression_list"
|
||||
([])
|
||||
(
|
||||
(If
|
||||
(
|
||||
(Call
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(Other "expression_list"
|
||||
(FunctionCall
|
||||
(Identifier)))))
|
||||
(Identifier)
|
||||
(ExpressionStatements
|
||||
(FunctionCall
|
||||
(Identifier))))
|
||||
(If
|
||||
(FunctionCall
|
||||
{ (Identifier)
|
||||
->(Identifier) })
|
||||
(ExpressionStatements
|
||||
(FunctionCall
|
||||
(Identifier)))
|
||||
(Other "else_clause"
|
||||
(ExpressionStatements
|
||||
(FunctionCall
|
||||
(Identifier)))))))
|
||||
->(Identifier) }
|
||||
(Empty)))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Empty))
|
||||
(If
|
||||
(
|
||||
(Assignment
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(Identifier))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Empty))
|
||||
(If
|
||||
(
|
||||
(Call
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty)))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty))
|
||||
(Call
|
||||
(Identifier)
|
||||
(Empty)))
|
||||
(If
|
||||
(
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (Integer)
|
||||
->(Integer) })
|
||||
(LessThan
|
||||
(Identifier)
|
||||
(Integer)))
|
||||
(Call
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty))
|
||||
(If
|
||||
(
|
||||
(LessThan
|
||||
(Identifier)
|
||||
{ (Integer)
|
||||
->(Integer) }))
|
||||
(Call
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty))
|
||||
(Call
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
(Empty)))))))
|
||||
|
Some files were not shown because too many files have changed in this diff Show More
Loading…
Reference in New Issue
Block a user