diff --git a/semantic.cabal b/semantic.cabal index 1aa7f9d1f..359b385eb 100644 --- a/semantic.cabal +++ b/semantic.cabal @@ -29,7 +29,6 @@ library , Analysis.CyclomaticComplexity , Analysis.Decorator , Analysis.Declaration - , Analysis.IdentifierName , Analysis.PackageDef -- Semantic assignment , Assigning.Assignment diff --git a/src/Analysis/ConstructorName.hs b/src/Analysis/ConstructorName.hs index 39473b755..df233b44f 100644 --- a/src/Analysis/ConstructorName.hs +++ b/src/Analysis/ConstructorName.hs @@ -1,32 +1,11 @@ {-# LANGUAGE ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-} module Analysis.ConstructorName ( ConstructorName(..) -, ConstructorLabel(..) -, constructorLabel ) where -import Data.Aeson -import Data.ByteString.Char8 (ByteString, pack, unpack) -import Data.JSON.Fields import Data.Sum -import Data.Term -import Data.Text.Encoding (decodeUtf8) import Prologue --- | Compute a 'ConstructorLabel' label for a 'Term'. -constructorLabel :: ConstructorName syntax => TermF syntax a b -> ConstructorLabel -constructorLabel (In _ s) = ConstructorLabel $ pack (constructorName s) - - -newtype ConstructorLabel = ConstructorLabel { unConstructorLabel :: ByteString } - -instance Show ConstructorLabel where - showsPrec _ (ConstructorLabel s) = showString (unpack s) - -instance ToJSONFields ConstructorLabel where - toJSONFields (ConstructorLabel s) = [ "category" .= decodeUtf8 s ] - - -- | A typeclass to retrieve the name of the data constructor for a value. -- -- This typeclass employs the Advanced Overlap techniques designed by Oleg Kiselyov & Simon Peyton Jones: https://wiki.haskell.org/GHC/AdvancedOverlap; see also src/Analysis/Declaration.hs for discussion of the details of the mechanism. @@ -40,8 +19,7 @@ instance Apply ConstructorName fs => ConstructorNameWithStrategy 'Custom (Sum fs constructorNameWithStrategy _ = apply @ConstructorName constructorName instance ConstructorNameWithStrategy 'Custom [] where - constructorNameWithStrategy _ [] = "[]" - constructorNameWithStrategy _ _ = "" + constructorNameWithStrategy _ _ = "Statements" data Strategy = Default | Custom diff --git a/src/Analysis/IdentifierName.hs b/src/Analysis/IdentifierName.hs deleted file mode 100644 index f98d13fef..000000000 --- a/src/Analysis/IdentifierName.hs +++ /dev/null @@ -1,60 +0,0 @@ -{-# LANGUAGE ScopedTypeVariables, TypeFamilies, TypeOperators, UndecidableInstances #-} -module Analysis.IdentifierName -( IdentifierName(..) -, IdentifierLabel(..) -, identifierLabel -) where - -import Data.Abstract.Name (unName) -import Data.Aeson -import Data.JSON.Fields -import Data.Sum -import qualified Data.Syntax -import Data.Term -import Data.Text.Encoding (decodeUtf8) -import Prologue - --- | Compute a 'IdentifierLabel' label for a 'Term'. -identifierLabel :: IdentifierName syntax => TermF syntax a b -> Maybe IdentifierLabel -identifierLabel (In _ s) = IdentifierLabel <$> identifierName s - -newtype IdentifierLabel = IdentifierLabel ByteString - deriving (Show) - -instance ToJSONFields IdentifierLabel where - toJSONFields (IdentifierLabel s) = [ "name" .= decodeUtf8 s ] - - --- | A typeclass to retrieve the name of syntax identifiers. --- --- This typeclass employs the Advanced Overlap techniques designed by Oleg Kiselyov & Simon Peyton Jones: https://wiki.haskell.org/GHC/AdvancedOverlap; see also src/Analysis/Declaration.hs for discussion of the details of the mechanism. -class IdentifierName syntax where - identifierName :: syntax a -> Maybe ByteString - -instance (IdentifierNameStrategy syntax ~ strategy, IdentifierNameWithStrategy strategy syntax) => IdentifierName syntax where - identifierName = identifierNameWithStrategy (Proxy :: Proxy strategy) - -class CustomIdentifierName syntax where - customIdentifierName :: syntax a -> Maybe ByteString - -instance Apply IdentifierName fs => CustomIdentifierName (Sum fs) where - customIdentifierName = apply @IdentifierName identifierName - -instance CustomIdentifierName Data.Syntax.Identifier where - customIdentifierName (Data.Syntax.Identifier name) = Just (unName name) - -data Strategy = Default | Custom - -type family IdentifierNameStrategy syntax where - IdentifierNameStrategy (Sum _) = 'Custom - IdentifierNameStrategy Data.Syntax.Identifier = 'Custom - IdentifierNameStrategy syntax = 'Default - -class IdentifierNameWithStrategy (strategy :: Strategy) syntax where - identifierNameWithStrategy :: proxy strategy -> syntax a -> Maybe ByteString - -instance IdentifierNameWithStrategy 'Default syntax where - identifierNameWithStrategy _ _ = Nothing - -instance (CustomIdentifierName syntax) => IdentifierNameWithStrategy 'Custom syntax where - identifierNameWithStrategy _ = customIdentifierName diff --git a/src/Data/Abstract/Name.hs b/src/Data/Abstract/Name.hs index 46bf635ee..0c2a73f25 100644 --- a/src/Data/Abstract/Name.hs +++ b/src/Data/Abstract/Name.hs @@ -6,11 +6,12 @@ module Data.Abstract.Name , unName ) where +import Data.Aeson import qualified Data.ByteString.Char8 as BC import qualified Data.Char as Char +import Data.String import qualified Data.Text as Text import qualified Data.Text.Encoding as Text -import Data.String import Prologue -- | The type of variable names. @@ -53,3 +54,7 @@ instance Show Name where instance Hashable Name where hashWithSalt salt (Name name) = hashWithSalt salt name hashWithSalt salt (I i) = salt `hashWithSalt` (1 :: Int) `hashWithSalt` i + +instance ToJSON Name where + toJSON = toJSON . Text.decodeUtf8 . unName + toEncoding = toEncoding . Text.decodeUtf8 . unName diff --git a/src/Data/JSON/Fields.hs b/src/Data/JSON/Fields.hs index bf4a56d8b..99690b9cf 100644 --- a/src/Data/JSON/Fields.hs +++ b/src/Data/JSON/Fields.hs @@ -1,4 +1,5 @@ -{-# LANGUAGE DefaultSignatures, MultiParamTypeClasses, TypeOperators, UndecidableInstances #-} +{-# LANGUAGE DefaultSignatures, MultiParamTypeClasses, TypeOperators, UndecidableInstances, GADTs #-} +{-# OPTIONS_GHC -fno-warn-orphans #-} -- FIXME module Data.JSON.Fields ( JSONFields (..) , JSONFields1 (..) @@ -9,17 +10,20 @@ module Data.JSON.Fields , withChildren ) where -import Data.Aeson -import Data.Sum (Apply(..), Sum) -import Prologue +import Data.Aeson +import Data.Sum (Apply (..), Sum) +import qualified Data.Text as Text +import qualified Data.Text.Encoding as Text +import Prologue class ToJSONFields a where toJSONFields :: KeyValue kv => a -> [kv] class ToJSONFields1 f where toJSONFields1 :: (KeyValue kv, ToJSON a) => f a -> [kv] - default toJSONFields1 :: (KeyValue kv, ToJSON a, Foldable f) => f a -> [kv] - toJSONFields1 f = ["children" .= toList f] + default toJSONFields1 :: (KeyValue kv, ToJSON a, GToJSONFields1 (Rep1 f), GConstructorName1 (Rep1 f), Generic1 f) => f a -> [kv] + toJSONFields1 s = let r = from1 s in + "term" .= gconstructorName1 r : gtoJSONFields1 r withChildren :: (KeyValue kv, ToJSON a, Foldable f) => f a -> [kv] -> [kv] withChildren f ks = ("children" .= toList f) : ks @@ -67,3 +71,82 @@ instance (ToJSON a, ToJSONFields1 f) => ToJSONFields (JSONFields1 f a) where instance (ToJSON a, ToJSONFields1 f) => ToJSON (JSONFields1 f a) where toJSON = object . toJSONFields1 . unJSONFields1 toEncoding = pairs . mconcat . toJSONFields1 . unJSONFields1 + + +-- | A typeclass to retrieve the name of a data constructor. +class GConstructorName1 f where + gconstructorName1 :: f a -> String + +instance Apply GConstructorName1 fs => GConstructorName1 (Sum fs) where + gconstructorName1 = apply @GConstructorName1 gconstructorName1 + +instance GConstructorName1 f => GConstructorName1 (M1 D c f) where + gconstructorName1 = gconstructorName1 . unM1 + +instance Constructor c => GConstructorName1 (M1 C c f) where + gconstructorName1 = conName + +instance (GConstructorName1 f, GConstructorName1 g) => GConstructorName1 (f :+: g) where + gconstructorName1 (L1 l) = gconstructorName1 l + gconstructorName1 (R1 r) = gconstructorName1 r + + +-- | A typeclass to calculate a list of 'KeyValue's describing the record selector names and associated values on a datatype. +class GToJSONFields1 f where + gtoJSONFields1 :: (KeyValue kv, ToJSON a) => f a -> [kv] + +instance GToJSONFields1 f => GToJSONFields1 (M1 D c f) where + gtoJSONFields1 = gtoJSONFields1 . unM1 + +instance GToJSONFields1 f => GToJSONFields1 (M1 C c f) where + gtoJSONFields1 = gtoJSONFields1 . unM1 + +instance GToJSONFields1 U1 where + gtoJSONFields1 _ = [] + +instance (Selector c, GSelectorJSONValue1 f) => GToJSONFields1 (M1 S c f) where + gtoJSONFields1 m1 = case selName m1 of + "" -> [ "children" .= json ] + n -> [ Text.pack n .= json ] + where json = gselectorJSONValue1 (unM1 m1) + +instance (GToJSONFields1 f, GToJSONFields1 g) => GToJSONFields1 (f :+: g) where + gtoJSONFields1 (L1 l) = gtoJSONFields1 l + gtoJSONFields1 (R1 r) = gtoJSONFields1 r + +instance (GToJSONFields1 f, GToJSONFields1 g) => GToJSONFields1 (f :*: g) where + gtoJSONFields1 (x :*: y) = gtoJSONFields1 x <> gtoJSONFields1 y + +-- | A typeclass to retrieve the JSON 'Value' of a record selector. +class GSelectorJSONValue1 f where + gselectorJSONValue1 :: ToJSON a => f a -> SomeJSON + +instance GSelectorJSONValue1 Par1 where + gselectorJSONValue1 = SomeJSON . unPar1 + +instance ToJSON1 f => GSelectorJSONValue1 (Rec1 f) where + gselectorJSONValue1 = SomeJSON . SomeJSON1 . unRec1 + +instance ToJSON k => GSelectorJSONValue1 (K1 r k) where + gselectorJSONValue1 = SomeJSON . unK1 + + +-- TODO: Fix this orphan instance. +instance ToJSON ByteString where + toJSON = toJSON . Text.decodeUtf8 + toEncoding = toEncoding . Text.decodeUtf8 + + +data SomeJSON where + SomeJSON :: ToJSON a => a -> SomeJSON + +instance ToJSON SomeJSON where + toJSON (SomeJSON a) = toJSON a + toEncoding (SomeJSON a) = toEncoding a + +data SomeJSON1 where + SomeJSON1 :: (ToJSON1 f, ToJSON a) => f a -> SomeJSON1 + +instance ToJSON SomeJSON1 where + toJSON (SomeJSON1 fa) = toJSON1 fa + toEncoding (SomeJSON1 fa) = toEncoding1 fa diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index 6cbc8a201..17c707714 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -101,16 +101,13 @@ infixContext context left right operators = uncurry (&) <$> postContextualizeThr -- Common -- | An identifier of some other construct, whether a containing declaration (e.g. a class name) or a reference (e.g. a variable). -newtype Identifier a = Identifier Name - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) +newtype Identifier a = Identifier { name :: Name } + deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, ToJSONFields1) instance Eq1 Identifier where liftEq = genericLiftEq instance Ord1 Identifier where liftCompare = genericLiftCompare instance Show1 Identifier where liftShowsPrec = genericLiftShowsPrec --- Propagating the identifier name into JSON is handled with the IdentifierName analysis. -instance ToJSONFields1 Identifier - instance Evaluatable Identifier where eval (Identifier name) = pure (LvalLocal name) @@ -120,28 +117,26 @@ instance FreeVariables1 Identifier where instance Declarations1 Identifier where liftDeclaredName _ (Identifier x) = pure x + newtype Program a = Program [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Program where liftEq = genericLiftEq instance Ord1 Program where liftCompare = genericLiftCompare instance Show1 Program where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Program - instance Evaluatable Program where eval (Program xs) = eval xs + -- | An accessibility modifier, e.g. private, public, protected, etc. newtype AccessibilityModifier a = AccessibilityModifier ByteString - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 AccessibilityModifier where liftEq = genericLiftEq instance Ord1 AccessibilityModifier where liftCompare = genericLiftCompare instance Show1 AccessibilityModifier where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 AccessibilityModifier - -- TODO: Implement Eval instance for AccessibilityModifier instance Evaluatable AccessibilityModifier diff --git a/src/Data/Term.hs b/src/Data/Term.hs index 4354c7d7e..cc9cd700f 100644 --- a/src/Data/Term.hs +++ b/src/Data/Term.hs @@ -121,7 +121,7 @@ instance (ToJSONFields a, ToJSONFields1 f) => ToJSONFields (Term f a) where toJSONFields = toJSONFields . unTerm instance (ToJSON b, ToJSONFields a, ToJSONFields1 f) => ToJSONFields (TermF f a b) where - toJSONFields (In a f) = toJSONFields a <> toJSONFields1 f + toJSONFields (In a f) = toJSONFields1 f <> toJSONFields a instance (ToJSON b, ToJSONFields a, ToJSONFields1 f) => ToJSON (TermF f a b) where toJSON = object . toJSONFields diff --git a/src/Language/Go/Syntax.hs b/src/Language/Go/Syntax.hs index b7ca2ab16..9b47e4894 100644 --- a/src/Language/Go/Syntax.hs +++ b/src/Language/Go/Syntax.hs @@ -5,6 +5,7 @@ import Data.Abstract.Evaluatable import Data.Abstract.Module import qualified Data.Abstract.Package as Package import Data.Abstract.Path +import Data.Aeson import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as BC import Data.JSON.Fields @@ -13,10 +14,10 @@ import Prologue import System.FilePath.Posix data Relative = Relative | NonRelative - deriving (Eq, Generic, Hashable, Ord, Show) + deriving (Eq, Generic, Hashable, Ord, Show, ToJSON) data ImportPath = ImportPath { unPath :: FilePath, pathIsRelative :: Relative } - deriving (Eq, Generic, Hashable, Ord, Show) + deriving (Eq, Generic, Hashable, Ord, Show, ToJSON) importPath :: ByteString -> ImportPath importPath str = let path = stripQuotes str in ImportPath (BC.unpack path) (pathType path) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 03593fb99..310f79e6d 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -4,23 +4,24 @@ module Language.Python.Syntax where import Data.Abstract.Environment as Env import Data.Abstract.Evaluatable import Data.Abstract.Module -import qualified Data.ByteString.Char8 as BC +import Data.Aeson import Data.Functor.Classes.Generic import Data.JSON.Fields -import qualified Data.Language as Language -import qualified Data.List.NonEmpty as NonEmpty -import qualified Data.Semigroup.Reducer as Reducer import Data.Mergeable import Diffing.Algorithm import GHC.Generics import Prelude hiding (fail) import Prologue import System.FilePath.Posix +import qualified Data.ByteString.Char8 as BC +import qualified Data.Language as Language +import qualified Data.List.NonEmpty as NonEmpty +import qualified Data.Semigroup.Reducer as Reducer data QualifiedName = QualifiedName (NonEmpty FilePath) | RelativeQualifiedName FilePath (Maybe QualifiedName) - deriving (Eq, Generic, Hashable, Ord, Show) + deriving (Eq, Generic, Hashable, Ord, Show, ToJSON) qualifiedName :: NonEmpty ByteString -> QualifiedName qualifiedName xs = QualifiedName (BC.unpack <$> xs) diff --git a/src/Language/TypeScript/Syntax.hs b/src/Language/TypeScript/Syntax.hs index 6260cbc6b..b05d22bd1 100644 --- a/src/Language/TypeScript/Syntax.hs +++ b/src/Language/TypeScript/Syntax.hs @@ -6,6 +6,7 @@ import Data.Abstract.Evaluatable import qualified Data.Abstract.Module as M import Data.Abstract.Package import Data.Abstract.Path +import Data.Aeson import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as BC import Data.JSON.Fields @@ -18,10 +19,10 @@ import Prologue import System.FilePath.Posix data Relative = Relative | NonRelative - deriving (Eq, Generic, Hashable, Ord, Show) + deriving (Eq, Generic, Hashable, Ord, Show, ToJSON) data ImportPath = ImportPath { unPath :: FilePath, pathIsRelative :: Relative } - deriving (Eq, Generic, Hashable, Ord, Show) + deriving (Eq, Generic, Hashable, Ord, Show, ToJSON) importPath :: ByteString -> ImportPath importPath str = let path = stripQuotes str in ImportPath (BC.unpack path) (pathType path) diff --git a/src/Rendering/JSON.hs b/src/Rendering/JSON.hs index 733eea92e..7ecaf84aa 100644 --- a/src/Rendering/JSON.hs +++ b/src/Rendering/JSON.hs @@ -52,8 +52,8 @@ data JSONTerm a = JSONTerm { jsonTermBlob :: Blob, jsonTerm :: a } deriving (Eq, Show) instance ToJSON a => ToJSON (JSONTerm a) where - toJSON JSONTerm{..} = object ("programNode" .= jsonTerm : toJSONFields jsonTermBlob) - toEncoding JSONTerm{..} = pairs (fold ("programNode" .= jsonTerm : toJSONFields jsonTermBlob)) + toJSON JSONTerm{..} = object ("tree" .= jsonTerm : toJSONFields jsonTermBlob) + toEncoding JSONTerm{..} = pairs (fold ("tree" .= jsonTerm : toJSONFields jsonTermBlob)) renderJSONAST :: ToJSON a => Blob -> a -> JSON "trees" SomeJSON diff --git a/src/Semantic/Diff.hs b/src/Semantic/Diff.hs index 1627ac36e..8e9046794 100644 --- a/src/Semantic/Diff.hs +++ b/src/Semantic/Diff.hs @@ -1,8 +1,7 @@ {-# LANGUAGE ConstraintKinds, GADTs, RankNTypes, ScopedTypeVariables #-} module Semantic.Diff where -import Analysis.ConstructorName (ConstructorName, constructorLabel) -import Analysis.IdentifierName (IdentifierName, identifierLabel) +import Analysis.ConstructorName (ConstructorName) import Analysis.Declaration (HasDeclaration, declarationAlgebra) import Data.AST import Data.Blob @@ -22,7 +21,7 @@ import Serializing.Format runDiff :: (Member (Distribute WrappedTask) effs, Member Task effs) => DiffRenderer output -> [BlobPair] -> Eff effs Builder runDiff ToCDiffRenderer = withParsedBlobPairs (decorate . declarationAlgebra) (render . renderToCDiff) >=> serialize JSON -runDiff JSONDiffRenderer = withParsedBlobPairs (const (decorate constructorLabel >=> decorate identifierLabel)) (render . renderJSONDiff) >=> serialize JSON +runDiff JSONDiffRenderer = withParsedBlobPairs (const pure) (render . renderJSONDiff) >=> serialize JSON runDiff SExpressionDiffRenderer = withParsedBlobPairs (const pure) (const (serialize (SExpression ByConstructorName))) runDiff ShowDiffRenderer = withParsedBlobPairs (const pure) (const (serialize Show)) runDiff DOTDiffRenderer = withParsedBlobPairs (const pure) (const (render renderTreeGraph)) >=> serialize (DOT (diffStyle "diffs")) @@ -36,7 +35,7 @@ withSomeTermPair with (SomeTermPair terms) = with terms diffBlobTOCPairs :: Member (Distribute WrappedTask) effs => [BlobPair] -> Eff effs ([TOCSummary], [TOCSummary]) diffBlobTOCPairs = withParsedBlobPairs (decorate . declarationAlgebra) (render . renderRPCToCDiff) -type CanDiff syntax = (ConstructorName syntax, Diffable syntax, Eq1 syntax, HasDeclaration syntax, IdentifierName syntax, Hashable1 syntax, Show1 syntax, ToJSONFields1 syntax, Traversable syntax) +type CanDiff syntax = (ConstructorName syntax, Diffable syntax, Eq1 syntax, HasDeclaration syntax, Hashable1 syntax, Show1 syntax, ToJSONFields1 syntax, Traversable syntax) withParsedBlobPairs :: (Member (Distribute WrappedTask) effs, Monoid output) => (forall syntax . CanDiff syntax => Blob -> Term syntax (Record Location) -> TaskEff (Term syntax (Record fields))) @@ -53,8 +52,8 @@ withParsedBlobPairs decorate render = distributeFoldMap (\ blobs -> WrapTask (wi withParsedBlobPair :: (Member (Distribute WrappedTask) effs, Member (Exc SomeException) effs) => (forall syntax . (CanDiff syntax) => Blob -> Term syntax (Record Location) -> TaskEff (Term syntax (Record fields))) -> BlobPair - -> Eff effs (SomeTermPair '[ConstructorName, Diffable, Eq1, HasDeclaration, Hashable1, IdentifierName, Show1, ToJSONFields1, Traversable] (Record fields)) + -> Eff effs (SomeTermPair '[ConstructorName, Diffable, Eq1, HasDeclaration, Hashable1, Show1, ToJSONFields1, Traversable] (Record fields)) withParsedBlobPair decorate blobs - | Just (SomeParser parser) <- someParser @'[ConstructorName, Diffable, Eq1, HasDeclaration, Hashable1, IdentifierName, Show1, ToJSONFields1, Traversable] <$> languageForBlobPair blobs + | Just (SomeParser parser) <- someParser @'[ConstructorName, Diffable, Eq1, HasDeclaration, Hashable1, Show1, ToJSONFields1, Traversable] <$> languageForBlobPair blobs = SomeTermPair <$> distributeFor blobs (\ blob -> WrapTask (parse parser blob >>= decorate blob)) | otherwise = noLanguageForBlob (pathForBlobPair blobs) diff --git a/src/Semantic/Parse.hs b/src/Semantic/Parse.hs index 122c037bf..a6e54ece0 100644 --- a/src/Semantic/Parse.hs +++ b/src/Semantic/Parse.hs @@ -1,8 +1,7 @@ {-# LANGUAGE GADTs, RankNTypes #-} module Semantic.Parse where -import Analysis.ConstructorName (ConstructorName, constructorLabel) -import Analysis.IdentifierName (IdentifierName, identifierLabel) +import Analysis.ConstructorName (ConstructorName) import Analysis.Declaration (HasDeclaration, declarationAlgebra) import Analysis.PackageDef (HasPackageDef, packageDefAlgebra) import Data.AST @@ -19,7 +18,7 @@ import Semantic.Task import Serializing.Format runParse :: (Member (Distribute WrappedTask) effs, Member Task effs) => TermRenderer output -> [Blob] -> Eff effs Builder -runParse JSONTermRenderer = withParsedBlobs (\ blob -> decorate constructorLabel >=> decorate identifierLabel >=> render (renderJSONTerm blob)) >=> serialize JSON +runParse JSONTermRenderer = withParsedBlobs (render . renderJSONTerm) >=> serialize JSON runParse SExpressionTermRenderer = withParsedBlobs (const (serialize (SExpression ByConstructorName))) runParse ShowTermRenderer = withParsedBlobs (const (serialize Show)) runParse TagsTermRenderer = withParsedBlobs (\ blob -> decorate (declarationAlgebra blob) >=> render (renderToTags blob)) >=> serialize JSON @@ -27,8 +26,8 @@ runParse ImportsTermRenderer = withParsedBlobs (\ blob -> decorate (dec runParse (SymbolsTermRenderer fields) = withParsedBlobs (\ blob -> decorate (declarationAlgebra blob) >=> render (renderSymbolTerms . renderToSymbols fields blob)) >=> serialize JSON runParse DOTTermRenderer = withParsedBlobs (const (render renderTreeGraph)) >=> serialize (DOT (termStyle "terms")) -withParsedBlobs :: (Member (Distribute WrappedTask) effs, Monoid output) => (forall syntax . (ConstructorName syntax, Foldable syntax, Functor syntax, HasDeclaration syntax, HasPackageDef syntax, IdentifierName syntax, Show1 syntax, ToJSONFields1 syntax) => Blob -> Term syntax (Record Location) -> TaskEff output) -> [Blob] -> Eff effs output +withParsedBlobs :: (Member (Distribute WrappedTask) effs, Monoid output) => (forall syntax . (ConstructorName syntax, Foldable syntax, Functor syntax, HasDeclaration syntax, HasPackageDef syntax, Show1 syntax, ToJSONFields1 syntax) => Blob -> Term syntax (Record Location) -> TaskEff output) -> [Blob] -> Eff effs output withParsedBlobs render = distributeFoldMap (\ blob -> WrapTask (parseSomeBlob blob >>= withSomeTerm (render blob))) -parseSomeBlob :: (Member (Exc SomeException) effs, Member Task effs) => Blob -> Eff effs (SomeTerm '[ConstructorName, Foldable, Functor, HasDeclaration, HasPackageDef, IdentifierName, Show1, ToJSONFields1] (Record Location)) +parseSomeBlob :: (Member (Exc SomeException) effs, Member Task effs) => Blob -> Eff effs (SomeTerm '[ConstructorName, Foldable, Functor, HasDeclaration, HasPackageDef, Show1, ToJSONFields1] (Record Location)) parseSomeBlob blob@Blob{..} = maybe (noLanguageForBlob blobPath) (flip parse blob . someParser) blobLanguage diff --git a/test/Semantic/CLI/Spec.hs b/test/Semantic/CLI/Spec.hs index 8c1483077..f0799501e 100644 --- a/test/Semantic/CLI/Spec.hs +++ b/test/Semantic/CLI/Spec.hs @@ -41,8 +41,8 @@ parseFixtures = pathMode' = [File "test/fixtures/ruby/corpus/and-or.A.rb" (Just Ruby), File "test/fixtures/ruby/corpus/and-or.B.rb" (Just Ruby)] sExpressionParseTreeOutput = "(Program\n (LowAnd\n (Send\n (Identifier))\n (Send\n (Identifier))))\n" - jsonParseTreeOutput = "{\"trees\":[{\"programNode\":{\"category\":\"Program\",\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,1]},\"children\":[{\"category\":\"LowAnd\",\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,12]},\"children\":[{\"category\":\"Send\",\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]},\"children\":[{\"name\":\"foo\",\"category\":\"Identifier\",\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]},\"children\":[]}]},{\"category\":\"Send\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]},\"children\":[{\"name\":\"bar\",\"category\":\"Identifier\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]},\"children\":[]}]}]}]},\"path\":\"test/fixtures/ruby/corpus/and-or.A.rb\",\"language\":\"Ruby\"}]}\n" - jsonParseTreeOutput' = "{\"trees\":[{\"programNode\":{\"category\":\"Program\",\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,1]},\"children\":[{\"category\":\"LowAnd\",\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,12]},\"children\":[{\"category\":\"Send\",\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]},\"children\":[{\"name\":\"foo\",\"category\":\"Identifier\",\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]},\"children\":[]}]},{\"category\":\"Send\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]},\"children\":[{\"name\":\"bar\",\"category\":\"Identifier\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]},\"children\":[]}]}]}]},\"path\":\"test/fixtures/ruby/corpus/and-or.A.rb\",\"language\":\"Ruby\"},{\"programNode\":{\"category\":\"Program\",\"sourceRange\":[0,24],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,1]},\"children\":[{\"category\":\"LowOr\",\"sourceRange\":[0,10],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,11]},\"children\":[{\"category\":\"Send\",\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]},\"children\":[{\"name\":\"foo\",\"category\":\"Identifier\",\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]},\"children\":[]}]},{\"category\":\"Send\",\"sourceRange\":[7,10],\"sourceSpan\":{\"start\":[1,8],\"end\":[1,11]},\"children\":[{\"name\":\"bar\",\"category\":\"Identifier\",\"sourceRange\":[7,10],\"sourceSpan\":{\"start\":[1,8],\"end\":[1,11]},\"children\":[]}]}]},{\"category\":\"LowAnd\",\"sourceRange\":[11,23],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,13]},\"children\":[{\"category\":\"LowOr\",\"sourceRange\":[11,17],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,7]},\"children\":[{\"category\":\"Send\",\"sourceRange\":[11,12],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,2]},\"children\":[{\"name\":\"a\",\"category\":\"Identifier\",\"sourceRange\":[11,12],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,2]},\"children\":[]}]},{\"category\":\"Send\",\"sourceRange\":[16,17],\"sourceSpan\":{\"start\":[2,6],\"end\":[2,7]},\"children\":[{\"name\":\"b\",\"category\":\"Identifier\",\"sourceRange\":[16,17],\"sourceSpan\":{\"start\":[2,6],\"end\":[2,7]},\"children\":[]}]}]},{\"category\":\"Send\",\"sourceRange\":[22,23],\"sourceSpan\":{\"start\":[2,12],\"end\":[2,13]},\"children\":[{\"name\":\"c\",\"category\":\"Identifier\",\"sourceRange\":[22,23],\"sourceSpan\":{\"start\":[2,12],\"end\":[2,13]},\"children\":[]}]}]}]},\"path\":\"test/fixtures/ruby/corpus/and-or.B.rb\",\"language\":\"Ruby\"}]}\n" + jsonParseTreeOutput = "{\"trees\":[{\"tree\":{\"term\":\"Program\",\"children\":[{\"term\":\"LowAnd\",\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"foo\",\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}},\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,12]}}],\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,1]}},\"path\":\"test/fixtures/ruby/corpus/and-or.A.rb\",\"language\":\"Ruby\"}]}\n" + jsonParseTreeOutput' = "{\"trees\":[{\"tree\":{\"term\":\"Program\",\"children\":[{\"term\":\"LowAnd\",\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"foo\",\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}},\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,12]}}],\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,1]}},\"path\":\"test/fixtures/ruby/corpus/and-or.A.rb\",\"language\":\"Ruby\"},{\"tree\":{\"term\":\"Program\",\"children\":[{\"term\":\"LowOr\",\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"foo\",\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[7,10],\"sourceSpan\":{\"start\":[1,8],\"end\":[1,11]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[7,10],\"sourceSpan\":{\"start\":[1,8],\"end\":[1,11]}},\"sourceRange\":[0,10],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,11]}},{\"term\":\"LowAnd\",\"children\":{\"term\":\"LowOr\",\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"a\",\"sourceRange\":[11,12],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,2]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[11,12],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,2]}},\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"b\",\"sourceRange\":[16,17],\"sourceSpan\":{\"start\":[2,6],\"end\":[2,7]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[16,17],\"sourceSpan\":{\"start\":[2,6],\"end\":[2,7]}},\"sourceRange\":[11,17],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,7]}},\"children\":{\"term\":\"Send\",\"sendReceiver\":null,\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"c\",\"sourceRange\":[22,23],\"sourceSpan\":{\"start\":[2,12],\"end\":[2,13]}},\"sendArgs\":[],\"sendBlock\":null,\"sourceRange\":[22,23],\"sourceSpan\":{\"start\":[2,12],\"end\":[2,13]}},\"sourceRange\":[11,23],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,13]}}],\"sourceRange\":[0,24],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,1]}},\"path\":\"test/fixtures/ruby/corpus/and-or.B.rb\",\"language\":\"Ruby\"}]}\n" emptyJsonParseTreeOutput = "{\"trees\":[]}\n" symbolsOutput = "{\"files\":[{\"path\":\"test/fixtures/ruby/corpus/method-declaration.A.rb\",\"symbols\":[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"kind\":\"Method\",\"symbol\":\"foo\"}],\"language\":\"Ruby\"}]}\n" tagsOutput = "[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"path\":\"test/fixtures/ruby/corpus/method-declaration.A.rb\",\"kind\":\"Method\",\"symbol\":\"foo\",\"line\":\"def foo\",\"language\":\"Ruby\"}]\n" @@ -56,6 +56,6 @@ diffFixtures = ] where pathMode = [both (File "test/fixtures/ruby/corpus/method-declaration.A.rb" (Just Ruby)) (File "test/fixtures/ruby/corpus/method-declaration.B.rb" (Just Ruby))] - jsonOutput = "{\"diffs\":[{\"diff\":{\"merge\":{\"before\":{\"category\":\"Program\",\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,1]}},\"after\":{\"category\":\"Program\",\"sourceRange\":[0,21],\"sourceSpan\":{\"start\":[1,1],\"end\":[4,1]}},\"children\":[{\"merge\":{\"before\":{\"category\":\"Method\",\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,4]}},\"after\":{\"category\":\"Method\",\"sourceRange\":[0,20],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,4]}},\"children\":[{\"merge\":{\"before\":{\"category\":\"Empty\",\"sourceRange\":[0,0],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,1]}},\"after\":{\"category\":\"Empty\",\"sourceRange\":[0,0],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,1]}},\"children\":[]}},{\"patch\":{\"replace\":[{\"category\":\"Identifier\",\"children\":[],\"name\":\"foo\",\"sourceRange\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}},{\"category\":\"Identifier\",\"children\":[],\"name\":\"bar\",\"sourceRange\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}}]}},{\"patch\":{\"insert\":{\"category\":\"Identifier\",\"children\":[],\"name\":\"a\",\"sourceRange\":[8,9],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,10]}}}},{\"merge\":{\"before\":{\"category\":\"[]\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,4]}},\"after\":{\"category\":\"\",\"sourceRange\":[13,16],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,6]}},\"children\":[{\"patch\":{\"insert\":{\"category\":\"Send\",\"children\":[{\"patch\":{\"insert\":{\"category\":\"Identifier\",\"children\":[],\"name\":\"baz\",\"sourceRange\":[13,16],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,6]}}}}],\"sourceRange\":[13,16],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,6]}}}}]}}]}}]}},\"stat\":{\"path\":\"test/fixtures/ruby/corpus/method-declaration.A.rb -> test/fixtures/ruby/corpus/method-declaration.B.rb\",\"replace\":[{\"path\":\"test/fixtures/ruby/corpus/method-declaration.A.rb\",\"language\":\"Ruby\"},{\"path\":\"test/fixtures/ruby/corpus/method-declaration.B.rb\",\"language\":\"Ruby\"}]}}]}\n" - sExpressionOutput = "(Program\n (Method\n (Empty)\n { (Identifier)\n ->(Identifier) }\n {+(Identifier)+}\n (\n {+(Send\n {+(Identifier)+})+})))\n" + jsonOutput = "{\"diffs\":[{\"diff\":{\"merge\":{\"term\":\"Program\",\"children\":[{\"merge\":{\"term\":\"Method\",\"methodContext\":[],\"methodReceiver\":{\"merge\":{\"term\":\"Empty\",\"before\":{\"sourceRange\":[0,0],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,1]}},\"after\":{\"sourceRange\":[0,0],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,1]}}}},\"methodName\":{\"patch\":{\"replace\":[{\"term\":\"Identifier\",\"name\":\"foo\",\"sourceRange\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}},{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}}]}},\"methodParameters\":[{\"patch\":{\"insert\":{\"term\":\"Identifier\",\"name\":\"a\",\"sourceRange\":[8,9],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,10]}}}}],\"methodBody\":{\"merge\":{\"children\":[{\"patch\":{\"insert\":{\"term\":\"Send\",\"sourceRange\":[13,16],\"sendReceiver\":null,\"sendBlock\":null,\"sendArgs\":[],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,6]},\"sendSelector\":{\"patch\":{\"insert\":{\"term\":\"Identifier\",\"name\":\"baz\",\"sourceRange\":[13,16],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,6]}}}}}}}],\"before\":{\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,4]}},\"after\":{\"sourceRange\":[13,16],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,6]}}}},\"before\":{\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,4]}},\"after\":{\"sourceRange\":[0,20],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,4]}}}}],\"before\":{\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,1]}},\"after\":{\"sourceRange\":[0,21],\"sourceSpan\":{\"start\":[1,1],\"end\":[4,1]}}}},\"stat\":{\"path\":\"test/fixtures/ruby/corpus/method-declaration.A.rb -> test/fixtures/ruby/corpus/method-declaration.B.rb\",\"replace\":[{\"path\":\"test/fixtures/ruby/corpus/method-declaration.A.rb\",\"language\":\"Ruby\"},{\"path\":\"test/fixtures/ruby/corpus/method-declaration.B.rb\",\"language\":\"Ruby\"}]}}]}\n" + sExpressionOutput = "(Program\n (Method\n (Empty)\n { (Identifier)\n ->(Identifier) }\n {+(Identifier)+}\n (Statements\n {+(Send\n {+(Identifier)+})+})))\n" tocOutput = "{\"changes\":{\"test/fixtures/ruby/corpus/method-declaration.A.rb -> test/fixtures/ruby/corpus/method-declaration.B.rb\":[{\"span\":{\"start\":[1,1],\"end\":[3,4]},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"modified\"}]},\"errors\":{}}\n" diff --git a/test/Semantic/Spec.hs b/test/Semantic/Spec.hs index abacf6598..b620a92a6 100644 --- a/test/Semantic/Spec.hs +++ b/test/Semantic/Spec.hs @@ -18,6 +18,6 @@ spec = parallel $ do it "renders with the specified renderer" $ do output <- fmap runBuilder . runTask $ runParse SExpressionTermRenderer [methodsBlob] - output `shouldBe` "(Program\n (Method\n (Empty)\n (Identifier)\n ([])))\n" + output `shouldBe` "(Program\n (Method\n (Empty)\n (Identifier)\n (Statements)))\n" where methodsBlob = Blob "def foo\nend\n" "methods.rb" (Just Ruby) diff --git a/test/fixtures/go/corpus/array-types.diffA-B.txt b/test/fixtures/go/corpus/array-types.diffA-B.txt index 08453d71a..56be1c980 100644 --- a/test/fixtures/go/corpus/array-types.diffA-B.txt +++ b/test/fixtures/go/corpus/array-types.diffA-B.txt @@ -4,9 +4,9 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Array @@ -17,7 +17,7 @@ ->(Integer) }) { (Identifier) ->(Identifier) }))) - ( + (Statements (Type { (Identifier) ->(Identifier) } @@ -28,7 +28,7 @@ { (Integer) ->(Integer) } (Identifier))))) - ( + (Statements (Type { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/array-types.diffB-A.txt b/test/fixtures/go/corpus/array-types.diffB-A.txt index 08453d71a..56be1c980 100644 --- a/test/fixtures/go/corpus/array-types.diffB-A.txt +++ b/test/fixtures/go/corpus/array-types.diffB-A.txt @@ -4,9 +4,9 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Array @@ -17,7 +17,7 @@ ->(Integer) }) { (Identifier) ->(Identifier) }))) - ( + (Statements (Type { (Identifier) ->(Identifier) } @@ -28,7 +28,7 @@ { (Integer) ->(Integer) } (Identifier))))) - ( + (Statements (Type { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/array-types.parseA.txt b/test/fixtures/go/corpus/array-types.parseA.txt index b549b8739..84a768d0e 100644 --- a/test/fixtures/go/corpus/array-types.parseA.txt +++ b/test/fixtures/go/corpus/array-types.parseA.txt @@ -4,9 +4,9 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Array @@ -14,7 +14,7 @@ (Integer) (Integer)) (Identifier)))) - ( + (Statements (Type (Identifier) (Array @@ -22,7 +22,7 @@ (Array (Integer) (Identifier))))) - ( + (Statements (Type (Identifier) (Array diff --git a/test/fixtures/go/corpus/array-types.parseB.txt b/test/fixtures/go/corpus/array-types.parseB.txt index b549b8739..84a768d0e 100644 --- a/test/fixtures/go/corpus/array-types.parseB.txt +++ b/test/fixtures/go/corpus/array-types.parseB.txt @@ -4,9 +4,9 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Array @@ -14,7 +14,7 @@ (Integer) (Integer)) (Identifier)))) - ( + (Statements (Type (Identifier) (Array @@ -22,7 +22,7 @@ (Array (Integer) (Identifier))))) - ( + (Statements (Type (Identifier) (Array diff --git a/test/fixtures/go/corpus/array-with-implicit-length.diffA-B.txt b/test/fixtures/go/corpus/array-with-implicit-length.diffA-B.txt index 86a1afb3e..c7bcedee0 100644 --- a/test/fixtures/go/corpus/array-with-implicit-length.diffA-B.txt +++ b/test/fixtures/go/corpus/array-with-implicit-length.diffA-B.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Composite (Array (Identifier)) - ( + (Statements {+(Integer)+} {+(Integer)+} { (Integer) diff --git a/test/fixtures/go/corpus/array-with-implicit-length.diffB-A.txt b/test/fixtures/go/corpus/array-with-implicit-length.diffB-A.txt index 0a6a38f42..cc7f5639b 100644 --- a/test/fixtures/go/corpus/array-with-implicit-length.diffB-A.txt +++ b/test/fixtures/go/corpus/array-with-implicit-length.diffB-A.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Composite (Array (Identifier)) - ( + (Statements {+(Integer)+} { (Integer) ->(Integer) } diff --git a/test/fixtures/go/corpus/array-with-implicit-length.parseA.txt b/test/fixtures/go/corpus/array-with-implicit-length.parseA.txt index 3d66382a0..d6cb95c51 100644 --- a/test/fixtures/go/corpus/array-with-implicit-length.parseA.txt +++ b/test/fixtures/go/corpus/array-with-implicit-length.parseA.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Composite (Array (Identifier)) - ( + (Statements (Integer) (Integer) (Integer)))))) diff --git a/test/fixtures/go/corpus/array-with-implicit-length.parseB.txt b/test/fixtures/go/corpus/array-with-implicit-length.parseB.txt index 3d66382a0..d6cb95c51 100644 --- a/test/fixtures/go/corpus/array-with-implicit-length.parseB.txt +++ b/test/fixtures/go/corpus/array-with-implicit-length.parseB.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Composite (Array (Identifier)) - ( + (Statements (Integer) (Integer) (Integer)))))) diff --git a/test/fixtures/go/corpus/assignment-statements.diffA-B.txt b/test/fixtures/go/corpus/assignment-statements.diffA-B.txt index a6bc14a38..124828615 100644 --- a/test/fixtures/go/corpus/assignment-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/assignment-statements.diffA-B.txt @@ -4,25 +4,25 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment { (Identifier) ->(Identifier) } (Integer)) (Assignment - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) (Plus - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) - ( + (Statements (Integer) (Integer)))) {+(Assignment @@ -68,13 +68,13 @@ {+(Integer)+})+})+})+} {+(Assignment {+(Identifier)+} - {+( + {+(Statements {+(Pointer {+(Identifier)+})+} {+(Reference {+(Composite {+(Identifier)+} - {+( + {+(Statements {+(KeyValue {+(Identifier)+} {+(Integer)+})+})+})+})+})+})+} @@ -121,13 +121,13 @@ {-(Integer)-})-})-})-} {-(Assignment {-(Identifier)-} - {-( + {-(Statements {-(Pointer {-(Identifier)-})-} {-(Reference {-(Composite {-(Identifier)-} - {-( + {-(Statements {-(KeyValue {-(Identifier)-} {-(Integer)-})-})-})-})-})-})-}))) diff --git a/test/fixtures/go/corpus/assignment-statements.diffB-A.txt b/test/fixtures/go/corpus/assignment-statements.diffB-A.txt index a6bc14a38..124828615 100644 --- a/test/fixtures/go/corpus/assignment-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/assignment-statements.diffB-A.txt @@ -4,25 +4,25 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment { (Identifier) ->(Identifier) } (Integer)) (Assignment - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) (Plus - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) - ( + (Statements (Integer) (Integer)))) {+(Assignment @@ -68,13 +68,13 @@ {+(Integer)+})+})+})+} {+(Assignment {+(Identifier)+} - {+( + {+(Statements {+(Pointer {+(Identifier)+})+} {+(Reference {+(Composite {+(Identifier)+} - {+( + {+(Statements {+(KeyValue {+(Identifier)+} {+(Integer)+})+})+})+})+})+})+} @@ -121,13 +121,13 @@ {-(Integer)-})-})-})-} {-(Assignment {-(Identifier)-} - {-( + {-(Statements {-(Pointer {-(Identifier)-})-} {-(Reference {-(Composite {-(Identifier)-} - {-( + {-(Statements {-(KeyValue {-(Identifier)-} {-(Integer)-})-})-})-})-})-})-}))) diff --git a/test/fixtures/go/corpus/assignment-statements.parseA.txt b/test/fixtures/go/corpus/assignment-statements.parseA.txt index 532358d02..b791f8bea 100644 --- a/test/fixtures/go/corpus/assignment-statements.parseA.txt +++ b/test/fixtures/go/corpus/assignment-statements.parseA.txt @@ -4,20 +4,20 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Integer)) (Assignment - ( + (Statements (Identifier) (Identifier)) (Plus - ( + (Statements (Identifier) (Identifier)) - ( + (Statements (Integer) (Integer)))) (Assignment @@ -63,13 +63,13 @@ (Integer)))) (Assignment (Identifier) - ( + (Statements (Pointer (Identifier)) (Reference (Composite (Identifier) - ( + (Statements (KeyValue (Identifier) (Integer)))))))))) diff --git a/test/fixtures/go/corpus/assignment-statements.parseB.txt b/test/fixtures/go/corpus/assignment-statements.parseB.txt index 532358d02..b791f8bea 100644 --- a/test/fixtures/go/corpus/assignment-statements.parseB.txt +++ b/test/fixtures/go/corpus/assignment-statements.parseB.txt @@ -4,20 +4,20 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Integer)) (Assignment - ( + (Statements (Identifier) (Identifier)) (Plus - ( + (Statements (Identifier) (Identifier)) - ( + (Statements (Integer) (Integer)))) (Assignment @@ -63,13 +63,13 @@ (Integer)))) (Assignment (Identifier) - ( + (Statements (Pointer (Identifier)) (Reference (Composite (Identifier) - ( + (Statements (KeyValue (Identifier) (Integer)))))))))) diff --git a/test/fixtures/go/corpus/binary-expressions.diffA-B.txt b/test/fixtures/go/corpus/binary-expressions.diffA-B.txt index 87826e83a..b917e06f7 100644 --- a/test/fixtures/go/corpus/binary-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/binary-expressions.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Context (Comment) (Or diff --git a/test/fixtures/go/corpus/binary-expressions.diffB-A.txt b/test/fixtures/go/corpus/binary-expressions.diffB-A.txt index 87826e83a..b917e06f7 100644 --- a/test/fixtures/go/corpus/binary-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/binary-expressions.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Context (Comment) (Or diff --git a/test/fixtures/go/corpus/binary-expressions.parseA.txt b/test/fixtures/go/corpus/binary-expressions.parseA.txt index cf4a2e6fc..44e685fd0 100644 --- a/test/fixtures/go/corpus/binary-expressions.parseA.txt +++ b/test/fixtures/go/corpus/binary-expressions.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Context (Comment) (Or diff --git a/test/fixtures/go/corpus/binary-expressions.parseB.txt b/test/fixtures/go/corpus/binary-expressions.parseB.txt index cf4a2e6fc..44e685fd0 100644 --- a/test/fixtures/go/corpus/binary-expressions.parseB.txt +++ b/test/fixtures/go/corpus/binary-expressions.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Context (Comment) (Or diff --git a/test/fixtures/go/corpus/call-expressions.diffA-B.txt b/test/fixtures/go/corpus/call-expressions.diffA-B.txt index 55b943cf5..3c48543b6 100644 --- a/test/fixtures/go/corpus/call-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/call-expressions.diffA-B.txt @@ -4,12 +4,12 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Call { (Identifier) ->(Identifier) } - ( + (Statements (Identifier) (Variadic (Identifier))) @@ -17,25 +17,25 @@ (Call { (Identifier) ->(Identifier) } - ( + (Statements (Identifier) (Identifier)) (Empty)) {+(Call {+(Identifier)+} - {+( + {+(Statements {+(Identifier)+} {+(Variadic {+(Identifier)+})+})+} {+(Empty)+})+} {-(Call {-(Identifier)-} - {-( + {-(Statements {-(Identifier)-} {-(Variadic {-(Identifier)-})-})-} {-(Empty)-})-} {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-}))) diff --git a/test/fixtures/go/corpus/call-expressions.diffB-A.txt b/test/fixtures/go/corpus/call-expressions.diffB-A.txt index 890ada670..2c96f544d 100644 --- a/test/fixtures/go/corpus/call-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/call-expressions.diffB-A.txt @@ -4,12 +4,12 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Call { (Identifier) ->(Identifier) } - ( + (Statements (Identifier) (Variadic (Identifier))) @@ -17,13 +17,13 @@ (Call { (Identifier) ->(Identifier) } - ( + (Statements (Identifier) (Identifier)) (Empty)) {+(Call {+(Identifier)+} - {+( + {+(Statements {+(Identifier)+} {+(Variadic {+(Identifier)+})+})+} @@ -31,8 +31,8 @@ (Call { (Identifier) ->(Identifier) } - {+([])+} - {-( + {+(Statements)+} + {-(Statements {-(Identifier)-} {-(Variadic {-(Identifier)-})-})-} diff --git a/test/fixtures/go/corpus/call-expressions.parseA.txt b/test/fixtures/go/corpus/call-expressions.parseA.txt index f53821488..d3a17acc0 100644 --- a/test/fixtures/go/corpus/call-expressions.parseA.txt +++ b/test/fixtures/go/corpus/call-expressions.parseA.txt @@ -4,29 +4,29 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Call (Identifier) - ( + (Statements (Identifier) (Variadic (Identifier))) (Empty)) (Call (Identifier) - ( + (Statements (Identifier) (Identifier)) (Empty)) (Call (Identifier) - ( + (Statements (Identifier) (Variadic (Identifier))) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty))))) diff --git a/test/fixtures/go/corpus/call-expressions.parseB.txt b/test/fixtures/go/corpus/call-expressions.parseB.txt index 6487b619b..405ccd9f8 100644 --- a/test/fixtures/go/corpus/call-expressions.parseB.txt +++ b/test/fixtures/go/corpus/call-expressions.parseB.txt @@ -4,24 +4,24 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Call (Identifier) - ( + (Statements (Identifier) (Variadic (Identifier))) (Empty)) (Call (Identifier) - ( + (Statements (Identifier) (Identifier)) (Empty)) (Call (Identifier) - ( + (Statements (Identifier) (Variadic (Identifier))) diff --git a/test/fixtures/go/corpus/case-statements.diffA-B.txt b/test/fixtures/go/corpus/case-statements.diffA-B.txt index 9cc79540d..fff31dbb0 100644 --- a/test/fixtures/go/corpus/case-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/case-statements.diffA-B.txt @@ -4,44 +4,44 @@ (Function (Empty) (Identifier) - ([]) + (Statements) { (Match {-(Empty)-} - {-([])-}) - ->( + {-(Statements)-}) + ->(Statements {+(Match - {+([])+} + {+(Statements)+} {+(Pattern {+(Identifier)+} {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+})+})+} {+(Match - {+( + {+(Statements {+(Identifier)+})+} - {+( + {+(Statements {+(Pattern - {+( + {+(Statements {+(Integer)+} {+(Integer)+})+} - {+( + {+(Statements {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+} {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+} {+(Pattern {+(Identifier)+} {+(Empty)+})+})+})+} {+(DefaultPattern - {+( + {+(Statements {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+} {+(Break {+(Empty)+})+})+})+})+})+}) })) diff --git a/test/fixtures/go/corpus/case-statements.diffB-A.txt b/test/fixtures/go/corpus/case-statements.diffB-A.txt index 4aa746b3d..58e3ab7f4 100644 --- a/test/fixtures/go/corpus/case-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/case-statements.diffB-A.txt @@ -4,44 +4,44 @@ (Function (Empty) (Identifier) - ([]) - { ( + (Statements) + { (Statements {-(Match - {-([])-} + {-(Statements)-} {-(Pattern {-(Identifier)-} {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-})-})-} {-(Match - {-( + {-(Statements {-(Identifier)-})-} - {-( + {-(Statements {-(Pattern - {-( + {-(Statements {-(Integer)-} {-(Integer)-})-} - {-( + {-(Statements {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-} {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-} {-(Pattern {-(Identifier)-} {-(Empty)-})-})-})-} {-(DefaultPattern - {-( + {-(Statements {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-} {-(Break {-(Empty)-})-})-})-})-})-}) ->(Match {+(Empty)+} - {+([])+}) })) + {+(Statements)+}) })) diff --git a/test/fixtures/go/corpus/case-statements.parseA.txt b/test/fixtures/go/corpus/case-statements.parseA.txt index 980232bc1..b5290544a 100644 --- a/test/fixtures/go/corpus/case-statements.parseA.txt +++ b/test/fixtures/go/corpus/case-statements.parseA.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Match (Empty) - ([])))) + (Statements)))) diff --git a/test/fixtures/go/corpus/case-statements.parseB.txt b/test/fixtures/go/corpus/case-statements.parseB.txt index 1110f6725..30ac23d2c 100644 --- a/test/fixtures/go/corpus/case-statements.parseB.txt +++ b/test/fixtures/go/corpus/case-statements.parseB.txt @@ -4,41 +4,41 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Match - ([]) + (Statements) (Pattern (Identifier) (Call (Identifier) - ([]) + (Statements) (Empty)))) (Match - ( + (Statements (Identifier)) - ( + (Statements (Pattern - ( + (Statements (Integer) (Integer)) - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty)) (Pattern (Identifier) (Empty)))) (DefaultPattern - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Break (Empty))))))))) diff --git a/test/fixtures/go/corpus/channel-types.diffA-B.txt b/test/fixtures/go/corpus/channel-types.diffA-B.txt index 2f198a1aa..d5317887d 100644 --- a/test/fixtures/go/corpus/channel-types.diffA-B.txt +++ b/test/fixtures/go/corpus/channel-types.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements {+(Type {+(Identifier)+} {+(BidirectionalChannel @@ -17,7 +17,7 @@ {+(SendChannel {+(Constructor {+(Empty)+} - {+([])+})+})+})+})+} + {+(Statements)+})+})+})+})+} (Type { (Identifier) ->(Identifier) } @@ -44,7 +44,7 @@ {-(SendChannel {-(Constructor {-(Empty)-} - {-([])-})-})-})-})-} + {-(Statements)-})-})-})-})-} {-(Type {-(Identifier)-} {-(SendChannel diff --git a/test/fixtures/go/corpus/channel-types.diffB-A.txt b/test/fixtures/go/corpus/channel-types.diffB-A.txt index d79b712da..51a49dc4b 100644 --- a/test/fixtures/go/corpus/channel-types.diffB-A.txt +++ b/test/fixtures/go/corpus/channel-types.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements {+(Type {+(Identifier)+} {+(BidirectionalChannel @@ -17,7 +17,7 @@ {+(SendChannel {+(Constructor {+(Empty)+} - {+([])+})+})+})+})+} + {+(Statements)+})+})+})+})+} {+(Type {+(Identifier)+} {+(SendChannel @@ -45,7 +45,7 @@ {-(SendChannel {-(Constructor {-(Empty)-} - {-([])-})-})-})-})-} + {-(Statements)-})-})-})-})-} {-(Type {-(Identifier)-} {-(SendChannel diff --git a/test/fixtures/go/corpus/channel-types.parseA.txt b/test/fixtures/go/corpus/channel-types.parseA.txt index 942edbd92..1396ee35f 100644 --- a/test/fixtures/go/corpus/channel-types.parseA.txt +++ b/test/fixtures/go/corpus/channel-types.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (BidirectionalChannel @@ -17,7 +17,7 @@ (SendChannel (Constructor (Empty) - ([]))))) + (Statements))))) (Type (Identifier) (SendChannel diff --git a/test/fixtures/go/corpus/channel-types.parseB.txt b/test/fixtures/go/corpus/channel-types.parseB.txt index 942edbd92..1396ee35f 100644 --- a/test/fixtures/go/corpus/channel-types.parseB.txt +++ b/test/fixtures/go/corpus/channel-types.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (BidirectionalChannel @@ -17,7 +17,7 @@ (SendChannel (Constructor (Empty) - ([]))))) + (Statements))))) (Type (Identifier) (SendChannel diff --git a/test/fixtures/go/corpus/comment.diffA-B.txt b/test/fixtures/go/corpus/comment.diffA-B.txt index 96549b84b..58437db7e 100644 --- a/test/fixtures/go/corpus/comment.diffA-B.txt +++ b/test/fixtures/go/corpus/comment.diffA-B.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Context { (Comment) ->(Comment) } diff --git a/test/fixtures/go/corpus/comment.diffB-A.txt b/test/fixtures/go/corpus/comment.diffB-A.txt index 96549b84b..58437db7e 100644 --- a/test/fixtures/go/corpus/comment.diffB-A.txt +++ b/test/fixtures/go/corpus/comment.diffB-A.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Context { (Comment) ->(Comment) } diff --git a/test/fixtures/go/corpus/comment.parseA.txt b/test/fixtures/go/corpus/comment.parseA.txt index f58487c8e..5972880e0 100644 --- a/test/fixtures/go/corpus/comment.parseA.txt +++ b/test/fixtures/go/corpus/comment.parseA.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Context (Comment) (Empty)))) diff --git a/test/fixtures/go/corpus/comment.parseB.txt b/test/fixtures/go/corpus/comment.parseB.txt index f58487c8e..5972880e0 100644 --- a/test/fixtures/go/corpus/comment.parseB.txt +++ b/test/fixtures/go/corpus/comment.parseB.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Context (Comment) (Empty)))) diff --git a/test/fixtures/go/corpus/const-declarations-with-types.diffA-B.txt b/test/fixtures/go/corpus/const-declarations-with-types.diffA-B.txt index c5d1763f7..25059d86c 100644 --- a/test/fixtures/go/corpus/const-declarations-with-types.diffA-B.txt +++ b/test/fixtures/go/corpus/const-declarations-with-types.diffA-B.txt @@ -4,16 +4,16 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Annotation - ( + (Statements { (Identifier) ->(Identifier) } {+(Identifier)+}) { (Identifier) ->(Identifier) }) { (Integer) - ->( + ->(Statements {+(Integer)+} {+(Integer)+}) }))) diff --git a/test/fixtures/go/corpus/const-declarations-with-types.diffB-A.txt b/test/fixtures/go/corpus/const-declarations-with-types.diffB-A.txt index 58fad7073..409f37825 100644 --- a/test/fixtures/go/corpus/const-declarations-with-types.diffB-A.txt +++ b/test/fixtures/go/corpus/const-declarations-with-types.diffB-A.txt @@ -4,16 +4,16 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Annotation - ( + (Statements { (Identifier) ->(Identifier) } {-(Identifier)-}) { (Identifier) ->(Identifier) }) - { ( + { (Statements {-(Integer)-} {-(Integer)-}) ->(Integer) }))) diff --git a/test/fixtures/go/corpus/const-declarations-with-types.parseA.txt b/test/fixtures/go/corpus/const-declarations-with-types.parseA.txt index ee7fdc4f9..83a22058d 100644 --- a/test/fixtures/go/corpus/const-declarations-with-types.parseA.txt +++ b/test/fixtures/go/corpus/const-declarations-with-types.parseA.txt @@ -4,10 +4,10 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Annotation - ( + (Statements (Identifier)) (Identifier)) (Integer)))) diff --git a/test/fixtures/go/corpus/const-declarations-with-types.parseB.txt b/test/fixtures/go/corpus/const-declarations-with-types.parseB.txt index 481f6d749..23d0ec50b 100644 --- a/test/fixtures/go/corpus/const-declarations-with-types.parseB.txt +++ b/test/fixtures/go/corpus/const-declarations-with-types.parseB.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Annotation - ( + (Statements (Identifier) (Identifier)) (Identifier)) - ( + (Statements (Integer) (Integer))))) diff --git a/test/fixtures/go/corpus/const-declarations-without-types.diffA-B.txt b/test/fixtures/go/corpus/const-declarations-without-types.diffA-B.txt index e1320a947..2d984aebb 100644 --- a/test/fixtures/go/corpus/const-declarations-without-types.diffA-B.txt +++ b/test/fixtures/go/corpus/const-declarations-without-types.diffA-B.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment { (Identifier) - ->( + ->(Statements {+(Identifier)+} {+(Identifier)+}) } { (Integer) - ->( + ->(Statements {+(Integer)+} {+(Integer)+}) }))) diff --git a/test/fixtures/go/corpus/const-declarations-without-types.diffB-A.txt b/test/fixtures/go/corpus/const-declarations-without-types.diffB-A.txt index 6d0e73d9d..06f1fa789 100644 --- a/test/fixtures/go/corpus/const-declarations-without-types.diffB-A.txt +++ b/test/fixtures/go/corpus/const-declarations-without-types.diffB-A.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment - { ( + { (Statements {-(Identifier)-} {-(Identifier)-}) ->(Identifier) } - { ( + { (Statements {-(Integer)-} {-(Integer)-}) ->(Integer) }))) diff --git a/test/fixtures/go/corpus/const-declarations-without-types.parseA.txt b/test/fixtures/go/corpus/const-declarations-without-types.parseA.txt index 9d343e9ba..d49580f45 100644 --- a/test/fixtures/go/corpus/const-declarations-without-types.parseA.txt +++ b/test/fixtures/go/corpus/const-declarations-without-types.parseA.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Integer)))) diff --git a/test/fixtures/go/corpus/const-declarations-without-types.parseB.txt b/test/fixtures/go/corpus/const-declarations-without-types.parseB.txt index ac7eb7599..bbacb990a 100644 --- a/test/fixtures/go/corpus/const-declarations-without-types.parseB.txt +++ b/test/fixtures/go/corpus/const-declarations-without-types.parseB.txt @@ -4,11 +4,11 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment - ( + (Statements (Identifier) (Identifier)) - ( + (Statements (Integer) (Integer))))) diff --git a/test/fixtures/go/corpus/const-with-implicit-values.diffA-B.txt b/test/fixtures/go/corpus/const-with-implicit-values.diffA-B.txt index 20efc4b51..a9e14b08e 100644 --- a/test/fixtures/go/corpus/const-with-implicit-values.diffA-B.txt +++ b/test/fixtures/go/corpus/const-with-implicit-values.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements {+(Assignment {+(Identifier)+} {+(Identifier)+})+} @@ -13,13 +13,13 @@ { (Identifier) ->(Identifier) } { (Identifier) - ->([]) }) + ->(Statements) }) {+(Assignment {+(Identifier)+} - {+([])+})+} + {+(Statements)+})+} {-(Assignment {-(Identifier)-} - {-([])-})-} + {-(Statements)-})-} {-(Assignment {-(Identifier)-} - {-([])-})-}))) + {-(Statements)-})-}))) diff --git a/test/fixtures/go/corpus/const-with-implicit-values.diffB-A.txt b/test/fixtures/go/corpus/const-with-implicit-values.diffB-A.txt index 20efc4b51..a9e14b08e 100644 --- a/test/fixtures/go/corpus/const-with-implicit-values.diffB-A.txt +++ b/test/fixtures/go/corpus/const-with-implicit-values.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements {+(Assignment {+(Identifier)+} {+(Identifier)+})+} @@ -13,13 +13,13 @@ { (Identifier) ->(Identifier) } { (Identifier) - ->([]) }) + ->(Statements) }) {+(Assignment {+(Identifier)+} - {+([])+})+} + {+(Statements)+})+} {-(Assignment {-(Identifier)-} - {-([])-})-} + {-(Statements)-})-} {-(Assignment {-(Identifier)-} - {-([])-})-}))) + {-(Statements)-})-}))) diff --git a/test/fixtures/go/corpus/const-with-implicit-values.parseA.txt b/test/fixtures/go/corpus/const-with-implicit-values.parseA.txt index 9e234e834..d74622291 100644 --- a/test/fixtures/go/corpus/const-with-implicit-values.parseA.txt +++ b/test/fixtures/go/corpus/const-with-implicit-values.parseA.txt @@ -4,14 +4,14 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Identifier)) (Assignment (Identifier) - ([])) + (Statements)) (Assignment (Identifier) - ([]))))) + (Statements))))) diff --git a/test/fixtures/go/corpus/const-with-implicit-values.parseB.txt b/test/fixtures/go/corpus/const-with-implicit-values.parseB.txt index 9e234e834..d74622291 100644 --- a/test/fixtures/go/corpus/const-with-implicit-values.parseB.txt +++ b/test/fixtures/go/corpus/const-with-implicit-values.parseB.txt @@ -4,14 +4,14 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Identifier)) (Assignment (Identifier) - ([])) + (Statements)) (Assignment (Identifier) - ([]))))) + (Statements))))) diff --git a/test/fixtures/go/corpus/constructors.diffA-B.txt b/test/fixtures/go/corpus/constructors.diffA-B.txt index d50283017..7ff5225d7 100644 --- a/test/fixtures/go/corpus/constructors.diffA-B.txt +++ b/test/fixtures/go/corpus/constructors.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Call (Identifier) (SendChannel @@ -14,7 +14,7 @@ (Empty)) (Call (Identifier) - ( + (Statements (SendChannel { (Identifier) ->(Identifier) }) @@ -24,7 +24,7 @@ (Empty)) (Call (Identifier) - ( + (Statements (SendChannel { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/go/corpus/constructors.diffB-A.txt b/test/fixtures/go/corpus/constructors.diffB-A.txt index d50283017..7ff5225d7 100644 --- a/test/fixtures/go/corpus/constructors.diffB-A.txt +++ b/test/fixtures/go/corpus/constructors.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Call (Identifier) (SendChannel @@ -14,7 +14,7 @@ (Empty)) (Call (Identifier) - ( + (Statements (SendChannel { (Identifier) ->(Identifier) }) @@ -24,7 +24,7 @@ (Empty)) (Call (Identifier) - ( + (Statements (SendChannel { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/go/corpus/constructors.parseA.txt b/test/fixtures/go/corpus/constructors.parseA.txt index 62a19364a..67a463345 100644 --- a/test/fixtures/go/corpus/constructors.parseA.txt +++ b/test/fixtures/go/corpus/constructors.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Call (Identifier) (SendChannel @@ -13,7 +13,7 @@ (Empty)) (Call (Identifier) - ( + (Statements (SendChannel (Identifier)) (Minus @@ -22,7 +22,7 @@ (Empty)) (Call (Identifier) - ( + (Statements (SendChannel (Identifier)) (Integer) diff --git a/test/fixtures/go/corpus/constructors.parseB.txt b/test/fixtures/go/corpus/constructors.parseB.txt index 62a19364a..67a463345 100644 --- a/test/fixtures/go/corpus/constructors.parseB.txt +++ b/test/fixtures/go/corpus/constructors.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Call (Identifier) (SendChannel @@ -13,7 +13,7 @@ (Empty)) (Call (Identifier) - ( + (Statements (SendChannel (Identifier)) (Minus @@ -22,7 +22,7 @@ (Empty)) (Call (Identifier) - ( + (Statements (SendChannel (Identifier)) (Integer) diff --git a/test/fixtures/go/corpus/float-literals.diffA-B.txt b/test/fixtures/go/corpus/float-literals.diffA-B.txt index a66af57a0..07225a1f4 100644 --- a/test/fixtures/go/corpus/float-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/float-literals.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) { (Float) diff --git a/test/fixtures/go/corpus/float-literals.diffB-A.txt b/test/fixtures/go/corpus/float-literals.diffB-A.txt index a66af57a0..07225a1f4 100644 --- a/test/fixtures/go/corpus/float-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/float-literals.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) { (Float) diff --git a/test/fixtures/go/corpus/float-literals.parseA.txt b/test/fixtures/go/corpus/float-literals.parseA.txt index b1c15a990..1bb8f4561 100644 --- a/test/fixtures/go/corpus/float-literals.parseA.txt +++ b/test/fixtures/go/corpus/float-literals.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Float)) diff --git a/test/fixtures/go/corpus/float-literals.parseB.txt b/test/fixtures/go/corpus/float-literals.parseB.txt index b1c15a990..1bb8f4561 100644 --- a/test/fixtures/go/corpus/float-literals.parseB.txt +++ b/test/fixtures/go/corpus/float-literals.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Float)) diff --git a/test/fixtures/go/corpus/for-statements.diffA-B.txt b/test/fixtures/go/corpus/for-statements.diffA-B.txt index 02cbf7287..34a068f3f 100644 --- a/test/fixtures/go/corpus/for-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/for-statements.diffA-B.txt @@ -4,26 +4,26 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (For (Empty) (Empty) (Empty) - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Goto (Identifier)))) {+(ForEach {+(Identifier)+} {+(Identifier)+} - {+( + {+(Statements {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+} {+(Break {+(Identifier)+})+})+})+} @@ -31,10 +31,10 @@ {+(Empty)+} {+(Empty)+} {+(Empty)+} - {+( + {+(Statements {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+} {+(Continue {+(Identifier)+})+})+})+} @@ -53,10 +53,10 @@ { (PostIncrement {-(Identifier)-}) ->(Empty) } - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) {+(Continue {+(Empty)+})+} @@ -66,7 +66,7 @@ {+(Empty)+} {+(Empty)+} {+(Empty)+} - {+( + {+(Statements {+(Call {+(Identifier)+} {+(Identifier)+} @@ -74,24 +74,24 @@ {+(Break {+(Empty)+})+})+})+} {+(ForEach - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Identifier)+} {+(Call {+(Identifier)+} - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Empty)+})+})+} {+(ForEach - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Identifier)+} {+(Call {+(Identifier)+} - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Empty)+})+})+} @@ -103,12 +103,12 @@ {+(Empty)+} {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+})+} {+(ForEach {+(Empty)+} {+(Identifier)+} - {+([])+})+} + {+(Statements)+})+} {-(For {-(LessThan {-(Identifier)-} @@ -116,10 +116,10 @@ {-(PostIncrement {-(Identifier)-})-} {-(Empty)-} - {-( + {-(Statements {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-} {-(Continue {-(Identifier)-})-})-})-} @@ -127,17 +127,17 @@ {-(Empty)-} {-(Empty)-} {-(Empty)-} - {-( + {-(Statements {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-} {-(Continue {-(Empty)-})-})-})-} {-(ForEach {-(Identifier)-} {-(Identifier)-} - {-( + {-(Statements {-(Call {-(Identifier)-} {-(Identifier)-} @@ -145,24 +145,24 @@ {-(Break {-(Empty)-})-})-})-} {-(ForEach - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Identifier)-} {-(Call {-(Identifier)-} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Empty)-})-})-} {-(ForEach - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Identifier)-} {-(Call {-(Identifier)-} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Empty)-})-})-} @@ -174,9 +174,9 @@ {-(Empty)-} {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-})-} {-(ForEach {-(Empty)-} {-(Identifier)-} - {-([])-})-}))) + {-(Statements)-})-}))) diff --git a/test/fixtures/go/corpus/for-statements.diffB-A.txt b/test/fixtures/go/corpus/for-statements.diffB-A.txt index b5425f99e..702a21acd 100644 --- a/test/fixtures/go/corpus/for-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/for-statements.diffB-A.txt @@ -4,16 +4,16 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (For (Empty) (Empty) (Empty) - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Goto (Identifier)))) @@ -26,10 +26,10 @@ {+(Integer)+})+} {+(PostIncrement {+(Identifier)+})+} - {+( + {+(Statements {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+} {+(Break {+(Identifier)+})+})+})+} @@ -40,10 +40,10 @@ {+(PostIncrement {+(Identifier)+})+} {+(Empty)+} - {+( + {+(Statements {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+} {+(Continue {+(Identifier)+})+})+})+} @@ -51,44 +51,44 @@ {+(Empty)+} {+(Empty)+} {+(Empty)+} - {+( + {+(Statements {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+} {+(Continue {+(Empty)+})+})+})+} (ForEach (Identifier) (Identifier) - ( + (Statements (Call (Identifier) {+(Identifier)+} - {-([])-} + {-(Statements)-} (Empty)) (Break { (Identifier) ->(Empty) }))) {+(ForEach - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Identifier)+} {+(Call {+(Identifier)+} - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Empty)+})+})+} {+(ForEach - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Identifier)+} {+(Call {+(Identifier)+} - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Empty)+})+})+} @@ -100,20 +100,20 @@ {+(Empty)+} {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+})+} {+(ForEach {+(Empty)+} {+(Identifier)+} - {+([])+})+} + {+(Statements)+})+} {-(For {-(Empty)-} {-(Empty)-} {-(Empty)-} - {-( + {-(Statements {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-} {-(Continue {-(Identifier)-})-})-})-} @@ -124,10 +124,10 @@ {-(PostIncrement {-(Identifier)-})-} {-(Empty)-} - {-( + {-(Statements {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-} {-(Continue {-(Empty)-})-})-})-} @@ -135,7 +135,7 @@ {-(Empty)-} {-(Empty)-} {-(Empty)-} - {-( + {-(Statements {-(Call {-(Identifier)-} {-(Identifier)-} @@ -143,24 +143,24 @@ {-(Break {-(Empty)-})-})-})-} {-(ForEach - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Identifier)-} {-(Call {-(Identifier)-} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Empty)-})-})-} {-(ForEach - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Identifier)-} {-(Call {-(Identifier)-} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Empty)-})-})-} @@ -172,9 +172,9 @@ {-(Empty)-} {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-})-} {-(ForEach {-(Empty)-} {-(Identifier)-} - {-([])-})-}))) + {-(Statements)-})-}))) diff --git a/test/fixtures/go/corpus/for-statements.parseA.txt b/test/fixtures/go/corpus/for-statements.parseA.txt index 74701793f..5f6668119 100644 --- a/test/fixtures/go/corpus/for-statements.parseA.txt +++ b/test/fixtures/go/corpus/for-statements.parseA.txt @@ -4,16 +4,16 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (For (Empty) (Empty) (Empty) - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Goto (Identifier)))) @@ -26,10 +26,10 @@ (Integer)) (PostIncrement (Identifier)) - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Break (Identifier)))) @@ -40,10 +40,10 @@ (PostIncrement (Identifier)) (Empty) - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Continue (Identifier)))) @@ -51,17 +51,17 @@ (Empty) (Empty) (Empty) - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Continue (Empty)))) (ForEach (Identifier) (Identifier) - ( + (Statements (Call (Identifier) (Identifier) @@ -69,24 +69,24 @@ (Break (Empty)))) (ForEach - ( + (Statements (Identifier) (Identifier)) (Identifier) (Call (Identifier) - ( + (Statements (Identifier) (Identifier)) (Empty))) (ForEach - ( + (Statements (Identifier) (Identifier)) (Identifier) (Call (Identifier) - ( + (Statements (Identifier) (Identifier)) (Empty))) @@ -98,9 +98,9 @@ (Empty) (Call (Identifier) - ([]) + (Statements) (Empty))) (ForEach (Empty) (Identifier) - ([]))))) + (Statements))))) diff --git a/test/fixtures/go/corpus/for-statements.parseB.txt b/test/fixtures/go/corpus/for-statements.parseB.txt index 56c7408ab..93ce681f2 100644 --- a/test/fixtures/go/corpus/for-statements.parseB.txt +++ b/test/fixtures/go/corpus/for-statements.parseB.txt @@ -4,26 +4,26 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (For (Empty) (Empty) (Empty) - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Goto (Identifier)))) (ForEach (Identifier) (Identifier) - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Break (Identifier)))) @@ -31,10 +31,10 @@ (Empty) (Empty) (Empty) - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Continue (Identifier)))) @@ -45,10 +45,10 @@ (PostIncrement (Identifier)) (Empty) - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Continue (Empty)))) @@ -56,7 +56,7 @@ (Empty) (Empty) (Empty) - ( + (Statements (Call (Identifier) (Identifier) @@ -64,24 +64,24 @@ (Break (Empty)))) (ForEach - ( + (Statements (Identifier) (Identifier)) (Identifier) (Call (Identifier) - ( + (Statements (Identifier) (Identifier)) (Empty))) (ForEach - ( + (Statements (Identifier) (Identifier)) (Identifier) (Call (Identifier) - ( + (Statements (Identifier) (Identifier)) (Empty))) @@ -93,9 +93,9 @@ (Empty) (Call (Identifier) - ([]) + (Statements) (Empty))) (ForEach (Empty) (Identifier) - ([]))))) + (Statements))))) diff --git a/test/fixtures/go/corpus/function-declarations.diffA-B.txt b/test/fixtures/go/corpus/function-declarations.diffA-B.txt index 475dc3cc7..f65f31e62 100644 --- a/test/fixtures/go/corpus/function-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/function-declarations.diffA-B.txt @@ -4,57 +4,57 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) { (Identifier) ->(Identifier) } - ([]) - ([])) + (Statements) + (Statements)) (Function (Identifier) { (Identifier) ->(Identifier) } - ( - ( + (Statements + (Statements (Identifier) (Identifier)) - ( + (Statements (Identifier) (Identifier) (Identifier) (Identifier))) - ([])) + (Statements)) (Function (Empty) { (Identifier) ->(Identifier) } - ([]) - ( - ( + (Statements) + (Statements + (Statements (Identifier)) - ( + (Statements (Identifier))) - ([])) + (Statements)) (Function (Empty) { (Identifier) ->(Identifier) } - ([]) - ( - ( + (Statements) + (Statements + (Statements (Identifier) (Identifier)) - ( + (Statements (Identifier) (Identifier))) - ([])) + (Statements)) {+(Function {+(Empty)+} {+(Identifier)+} - {+([])+} - {+([])+} + {+(Statements)+} + {+(Statements)+} {+(NoOp {+(Empty)+})+})+} (Function @@ -62,17 +62,17 @@ ->(Identifier) } { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty)) (Function (Empty) { (Identifier) ->(Identifier) } - ( + (Statements (Identifier) (Pointer (Identifier))) (Context (Comment) (Empty)) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/function-declarations.diffB-A.txt b/test/fixtures/go/corpus/function-declarations.diffB-A.txt index b17bc908b..1056ed0be 100644 --- a/test/fixtures/go/corpus/function-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/function-declarations.diffB-A.txt @@ -4,88 +4,88 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) { (Identifier) ->(Identifier) } - ([]) - ([])) + (Statements) + (Statements)) (Function (Identifier) { (Identifier) ->(Identifier) } - ( - ( + (Statements + (Statements (Identifier) (Identifier)) - ( + (Statements (Identifier) (Identifier) (Identifier) (Identifier))) - ([])) + (Statements)) (Function (Empty) { (Identifier) ->(Identifier) } - ([]) - ( - ( + (Statements) + (Statements + (Statements (Identifier)) - ( + (Statements (Identifier))) - ([])) + (Statements)) (Function (Empty) { (Identifier) ->(Identifier) } - ([]) - ( - ( + (Statements) + (Statements + (Statements (Identifier) (Identifier)) - ( + (Statements (Identifier) (Identifier))) - ([])) + (Statements)) {+(Function {+(Identifier)+} {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+} {+(Function {+(Empty)+} {+(Identifier)+} - {+( + {+(Statements {+(Identifier)+} {+(Pointer {+(Identifier)+})+})+} {+(Context {+(Comment)+} {+(Empty)+})+} - {+([])+})+} + {+(Statements)+})+} {-(Function {-(Empty)-} {-(Identifier)-} - {-([])-} - {-([])-} + {-(Statements)-} + {-(Statements)-} {-(NoOp {-(Empty)-})-})-} {-(Function {-(Identifier)-} {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-} {-(Function {-(Empty)-} {-(Identifier)-} - {-( + {-(Statements {-(Identifier)-} {-(Pointer {-(Identifier)-})-})-} {-(Context {-(Comment)-} {-(Empty)-})-} - {-([])-})-}) + {-(Statements)-})-}) diff --git a/test/fixtures/go/corpus/function-declarations.parseA.txt b/test/fixtures/go/corpus/function-declarations.parseA.txt index 8038aba6e..452629f0e 100644 --- a/test/fixtures/go/corpus/function-declarations.parseA.txt +++ b/test/fixtures/go/corpus/function-declarations.parseA.txt @@ -4,61 +4,61 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Identifier) (Identifier) - ( - ( + (Statements + (Statements (Identifier) (Identifier)) - ( + (Statements (Identifier) (Identifier) (Identifier) (Identifier))) - ([])) + (Statements)) (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Identifier)) - ( + (Statements (Identifier))) - ([])) + (Statements)) (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Identifier) (Identifier)) - ( + (Statements (Identifier) (Identifier))) - ([])) + (Statements)) (Function (Identifier) (Identifier) - ([]) + (Statements) (Empty)) (Function (Empty) (Identifier) - ( + (Statements (Identifier) (Pointer (Identifier))) (Context (Comment) (Empty)) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/function-declarations.parseB.txt b/test/fixtures/go/corpus/function-declarations.parseB.txt index 0c2eb34f5..8c9ffbe9a 100644 --- a/test/fixtures/go/corpus/function-declarations.parseB.txt +++ b/test/fixtures/go/corpus/function-declarations.parseB.txt @@ -4,68 +4,68 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Identifier) (Identifier) - ( - ( + (Statements + (Statements (Identifier) (Identifier)) - ( + (Statements (Identifier) (Identifier) (Identifier) (Identifier))) - ([])) + (Statements)) (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Identifier)) - ( + (Statements (Identifier))) - ([])) + (Statements)) (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Identifier) (Identifier)) - ( + (Statements (Identifier) (Identifier))) - ([])) + (Statements)) (Function (Empty) (Identifier) - ([]) - ([]) + (Statements) + (Statements) (NoOp (Empty))) (Function (Identifier) (Identifier) - ([]) + (Statements) (Empty)) (Function (Empty) (Identifier) - ( + (Statements (Identifier) (Pointer (Identifier))) (Context (Comment) (Empty)) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/function-literals.diffA-B.txt b/test/fixtures/go/corpus/function-literals.diffA-B.txt index cc274008c..92470cd71 100644 --- a/test/fixtures/go/corpus/function-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/function-literals.diffA-B.txt @@ -4,25 +4,25 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Function (Empty) (Empty) - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) - ( - ( + (Statements + (Statements { (Identifier) ->(Identifier) }) - ( + (Statements { (Identifier) ->(Identifier) })) (Return - ( + (Statements (Integer) (Integer))))))) diff --git a/test/fixtures/go/corpus/function-literals.diffB-A.txt b/test/fixtures/go/corpus/function-literals.diffB-A.txt index cc274008c..92470cd71 100644 --- a/test/fixtures/go/corpus/function-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/function-literals.diffB-A.txt @@ -4,25 +4,25 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Function (Empty) (Empty) - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) - ( - ( + (Statements + (Statements { (Identifier) ->(Identifier) }) - ( + (Statements { (Identifier) ->(Identifier) })) (Return - ( + (Statements (Integer) (Integer))))))) diff --git a/test/fixtures/go/corpus/function-literals.parseA.txt b/test/fixtures/go/corpus/function-literals.parseA.txt index 31c68c5ff..978efb513 100644 --- a/test/fixtures/go/corpus/function-literals.parseA.txt +++ b/test/fixtures/go/corpus/function-literals.parseA.txt @@ -4,21 +4,21 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Function (Empty) (Empty) - ( + (Statements (Identifier) (Identifier)) - ( - ( + (Statements + (Statements (Identifier)) - ( + (Statements (Identifier))) (Return - ( + (Statements (Integer) (Integer))))))) diff --git a/test/fixtures/go/corpus/function-literals.parseB.txt b/test/fixtures/go/corpus/function-literals.parseB.txt index 31c68c5ff..978efb513 100644 --- a/test/fixtures/go/corpus/function-literals.parseB.txt +++ b/test/fixtures/go/corpus/function-literals.parseB.txt @@ -4,21 +4,21 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Function (Empty) (Empty) - ( + (Statements (Identifier) (Identifier)) - ( - ( + (Statements + (Statements (Identifier)) - ( + (Statements (Identifier))) (Return - ( + (Statements (Integer) (Integer))))))) diff --git a/test/fixtures/go/corpus/function-types.diffA-B.txt b/test/fixtures/go/corpus/function-types.diffA-B.txt index d925a1d60..8a7463671 100644 --- a/test/fixtures/go/corpus/function-types.diffA-B.txt +++ b/test/fixtures/go/corpus/function-types.diffA-B.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type { (Identifier) ->(Identifier) } (Function - ( + (Statements { (Identifier) ->(Identifier) }) { (Identifier) @@ -19,18 +19,18 @@ { (Identifier) ->(Identifier) } (Function - ( - {-( + (Statements + {-(Statements {-(Identifier)-})-} - ( + (Statements (Identifier)) - {+( + {+(Statements {+(Identifier)+})+}) - ( - ( + (Statements + (Statements {+(BidirectionalChannel {+(Identifier)+})+} {-(Identifier)-}) - ( + (Statements (Identifier))) (Empty)))))) diff --git a/test/fixtures/go/corpus/function-types.diffB-A.txt b/test/fixtures/go/corpus/function-types.diffB-A.txt index 70807059c..27129ae93 100644 --- a/test/fixtures/go/corpus/function-types.diffB-A.txt +++ b/test/fixtures/go/corpus/function-types.diffB-A.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type { (Identifier) ->(Identifier) } (Function - ( + (Statements { (Identifier) ->(Identifier) }) { (Identifier) @@ -19,18 +19,18 @@ { (Identifier) ->(Identifier) } (Function - ( - {-( + (Statements + {-(Statements {-(Identifier)-})-} - ( + (Statements (Identifier)) - {+( + {+(Statements {+(Identifier)+})+}) - ( - ( + (Statements + (Statements {+(Identifier)+} {-(BidirectionalChannel {-(Identifier)-})-}) - ( + (Statements (Identifier))) (Empty)))))) diff --git a/test/fixtures/go/corpus/function-types.parseA.txt b/test/fixtures/go/corpus/function-types.parseA.txt index 302111d2d..71ca93ab6 100644 --- a/test/fixtures/go/corpus/function-types.parseA.txt +++ b/test/fixtures/go/corpus/function-types.parseA.txt @@ -4,25 +4,25 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Function - ( + (Statements (Identifier)) (Identifier))) (Type (Identifier) (Function - ( - ( + (Statements + (Statements (Identifier)) - ( + (Statements (Identifier))) - ( - ( + (Statements + (Statements (Identifier)) - ( + (Statements (Identifier))) (Empty)))))) diff --git a/test/fixtures/go/corpus/function-types.parseB.txt b/test/fixtures/go/corpus/function-types.parseB.txt index a00ba801b..2221de55b 100644 --- a/test/fixtures/go/corpus/function-types.parseB.txt +++ b/test/fixtures/go/corpus/function-types.parseB.txt @@ -4,26 +4,26 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Function - ( + (Statements (Identifier)) (Identifier))) (Type (Identifier) (Function - ( - ( + (Statements + (Statements (Identifier)) - ( + (Statements (Identifier))) - ( - ( + (Statements + (Statements (BidirectionalChannel (Identifier))) - ( + (Statements (Identifier))) (Empty)))))) diff --git a/test/fixtures/go/corpus/go-and-defer-statements.diffA-B.txt b/test/fixtures/go/corpus/go-and-defer-statements.diffA-B.txt index 2df88fd8c..6e514bb12 100644 --- a/test/fixtures/go/corpus/go-and-defer-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/go-and-defer-statements.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Defer (Call (MemberAccess @@ -13,7 +13,7 @@ ->(Identifier) } { (Identifier) ->(Identifier) }) - ([]) + (Statements) (Empty))) (Go (Call @@ -22,5 +22,5 @@ ->(Identifier) } { (Identifier) ->(Identifier) }) - ([]) + (Statements) (Empty)))))) diff --git a/test/fixtures/go/corpus/go-and-defer-statements.diffB-A.txt b/test/fixtures/go/corpus/go-and-defer-statements.diffB-A.txt index 2df88fd8c..6e514bb12 100644 --- a/test/fixtures/go/corpus/go-and-defer-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/go-and-defer-statements.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Defer (Call (MemberAccess @@ -13,7 +13,7 @@ ->(Identifier) } { (Identifier) ->(Identifier) }) - ([]) + (Statements) (Empty))) (Go (Call @@ -22,5 +22,5 @@ ->(Identifier) } { (Identifier) ->(Identifier) }) - ([]) + (Statements) (Empty)))))) diff --git a/test/fixtures/go/corpus/go-and-defer-statements.parseA.txt b/test/fixtures/go/corpus/go-and-defer-statements.parseA.txt index 1210e7076..328d1ff21 100644 --- a/test/fixtures/go/corpus/go-and-defer-statements.parseA.txt +++ b/test/fixtures/go/corpus/go-and-defer-statements.parseA.txt @@ -4,19 +4,19 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Defer (Call (MemberAccess (Identifier) (Identifier)) - ([]) + (Statements) (Empty))) (Go (Call (MemberAccess (Identifier) (Identifier)) - ([]) + (Statements) (Empty)))))) diff --git a/test/fixtures/go/corpus/go-and-defer-statements.parseB.txt b/test/fixtures/go/corpus/go-and-defer-statements.parseB.txt index 1210e7076..328d1ff21 100644 --- a/test/fixtures/go/corpus/go-and-defer-statements.parseB.txt +++ b/test/fixtures/go/corpus/go-and-defer-statements.parseB.txt @@ -4,19 +4,19 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Defer (Call (MemberAccess (Identifier) (Identifier)) - ([]) + (Statements) (Empty))) (Go (Call (MemberAccess (Identifier) (Identifier)) - ([]) + (Statements) (Empty)))))) diff --git a/test/fixtures/go/corpus/grouped-import-declarations.diffA-B.txt b/test/fixtures/go/corpus/grouped-import-declarations.diffA-B.txt index d5e6076f3..1a203ec98 100644 --- a/test/fixtures/go/corpus/grouped-import-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/grouped-import-declarations.diffA-B.txt @@ -1,7 +1,7 @@ (Program (Package (Identifier)) - ( + (Statements {+(QualifiedImport {+(Identifier)+})+} {+(Import @@ -17,5 +17,5 @@ (Function (Empty) (Identifier) - ([]) - ([]))) + (Statements) + (Statements))) diff --git a/test/fixtures/go/corpus/grouped-import-declarations.diffB-A.txt b/test/fixtures/go/corpus/grouped-import-declarations.diffB-A.txt index d5e6076f3..1a203ec98 100644 --- a/test/fixtures/go/corpus/grouped-import-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/grouped-import-declarations.diffB-A.txt @@ -1,7 +1,7 @@ (Program (Package (Identifier)) - ( + (Statements {+(QualifiedImport {+(Identifier)+})+} {+(Import @@ -17,5 +17,5 @@ (Function (Empty) (Identifier) - ([]) - ([]))) + (Statements) + (Statements))) diff --git a/test/fixtures/go/corpus/grouped-import-declarations.parseA.txt b/test/fixtures/go/corpus/grouped-import-declarations.parseA.txt index a42c1120b..3056c74a1 100644 --- a/test/fixtures/go/corpus/grouped-import-declarations.parseA.txt +++ b/test/fixtures/go/corpus/grouped-import-declarations.parseA.txt @@ -1,7 +1,7 @@ (Program (Package (Identifier)) - ( + (Statements (QualifiedImport (Identifier)) (Import @@ -11,5 +11,5 @@ (Function (Empty) (Identifier) - ([]) - ([]))) + (Statements) + (Statements))) diff --git a/test/fixtures/go/corpus/grouped-import-declarations.parseB.txt b/test/fixtures/go/corpus/grouped-import-declarations.parseB.txt index a42c1120b..3056c74a1 100644 --- a/test/fixtures/go/corpus/grouped-import-declarations.parseB.txt +++ b/test/fixtures/go/corpus/grouped-import-declarations.parseB.txt @@ -1,7 +1,7 @@ (Program (Package (Identifier)) - ( + (Statements (QualifiedImport (Identifier)) (Import @@ -11,5 +11,5 @@ (Function (Empty) (Identifier) - ([]) - ([]))) + (Statements) + (Statements))) diff --git a/test/fixtures/go/corpus/grouped-var-declarations.diffA-B.txt b/test/fixtures/go/corpus/grouped-var-declarations.diffA-B.txt index 7c9cb8c9a..34b5a2048 100644 --- a/test/fixtures/go/corpus/grouped-var-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/grouped-var-declarations.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/grouped-var-declarations.diffB-A.txt b/test/fixtures/go/corpus/grouped-var-declarations.diffB-A.txt index 7c9cb8c9a..34b5a2048 100644 --- a/test/fixtures/go/corpus/grouped-var-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/grouped-var-declarations.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/grouped-var-declarations.parseA.txt b/test/fixtures/go/corpus/grouped-var-declarations.parseA.txt index 4275a124d..e2b812db4 100644 --- a/test/fixtures/go/corpus/grouped-var-declarations.parseA.txt +++ b/test/fixtures/go/corpus/grouped-var-declarations.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Integer)) diff --git a/test/fixtures/go/corpus/grouped-var-declarations.parseB.txt b/test/fixtures/go/corpus/grouped-var-declarations.parseB.txt index 4275a124d..e2b812db4 100644 --- a/test/fixtures/go/corpus/grouped-var-declarations.parseB.txt +++ b/test/fixtures/go/corpus/grouped-var-declarations.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Integer)) diff --git a/test/fixtures/go/corpus/if-statements.diffA-B.txt b/test/fixtures/go/corpus/if-statements.diffA-B.txt index 9010006ab..85aa397a7 100644 --- a/test/fixtures/go/corpus/if-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/if-statements.diffA-B.txt @@ -4,52 +4,52 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (If - ( + (Statements (Call { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty))) (Call (Identifier) - ([]) + (Statements) (Empty)) (Empty)) (If - ( + (Statements (Assignment { (Identifier) ->(Identifier) } (Call (Identifier) - ([]) + (Statements) (Empty))) (Identifier)) (Call (Identifier) - ([]) + (Statements) (Empty)) (Empty)) (If - ( + (Statements (Call { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty))) (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty))) (If - ( + (Statements (Assignment (Identifier) { (Integer) @@ -60,12 +60,12 @@ (Call { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty)) {+(Context {+(Comment)+} (If - ( + (Statements (LessThan (Identifier) { (Integer) @@ -73,22 +73,22 @@ (Call { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty)) { (Context {-(Comment)-} {-(If - {-( + {-(Statements {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-})-} {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-} {-(Empty)-})-}) ->(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+}) }))+})))) diff --git a/test/fixtures/go/corpus/if-statements.diffB-A.txt b/test/fixtures/go/corpus/if-statements.diffB-A.txt index a815344d1..5dfcda691 100644 --- a/test/fixtures/go/corpus/if-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/if-statements.diffB-A.txt @@ -4,52 +4,52 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (If - ( + (Statements (Call { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty))) (Call (Identifier) - ([]) + (Statements) (Empty)) (Empty)) (If - ( + (Statements (Assignment { (Identifier) ->(Identifier) } (Call (Identifier) - ([]) + (Statements) (Empty))) (Identifier)) (Call (Identifier) - ([]) + (Statements) (Empty)) (Empty)) (If - ( + (Statements (Call { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty))) (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty))) (If - ( + (Statements (Assignment (Identifier) { (Integer) @@ -60,12 +60,12 @@ (Call { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty)) {-(Context {-(Comment)-} (If - ( + (Statements (LessThan (Identifier) { (Integer) @@ -73,22 +73,22 @@ (Call { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty)) { (Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-}) ->(Context {+(Comment)+} {+(If - {+( + {+(Statements {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+})+} {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+} {+(Empty)+})+}) }))-})))) diff --git a/test/fixtures/go/corpus/if-statements.parseA.txt b/test/fixtures/go/corpus/if-statements.parseA.txt index ef33b5738..1736450cf 100644 --- a/test/fixtures/go/corpus/if-statements.parseA.txt +++ b/test/fixtures/go/corpus/if-statements.parseA.txt @@ -4,49 +4,49 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (If - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty))) (Call (Identifier) - ([]) + (Statements) (Empty)) (Empty)) (If - ( + (Statements (Assignment (Identifier) (Call (Identifier) - ([]) + (Statements) (Empty))) (Identifier)) (Call (Identifier) - ([]) + (Statements) (Empty)) (Empty)) (If - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty))) (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty))) (If - ( + (Statements (Assignment (Identifier) (Integer)) @@ -55,27 +55,27 @@ (Integer))) (Call (Identifier) - ([]) + (Statements) (Empty)) (If - ( + (Statements (LessThan (Identifier) (Integer))) (Call (Identifier) - ([]) + (Statements) (Empty)) (Context (Comment) (If - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty))) (Call (Identifier) - ([]) + (Statements) (Empty)) (Empty)))))))) diff --git a/test/fixtures/go/corpus/if-statements.parseB.txt b/test/fixtures/go/corpus/if-statements.parseB.txt index 42d082648..57ddb0dc8 100644 --- a/test/fixtures/go/corpus/if-statements.parseB.txt +++ b/test/fixtures/go/corpus/if-statements.parseB.txt @@ -4,49 +4,49 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (If - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty))) (Call (Identifier) - ([]) + (Statements) (Empty)) (Empty)) (If - ( + (Statements (Assignment (Identifier) (Call (Identifier) - ([]) + (Statements) (Empty))) (Identifier)) (Call (Identifier) - ([]) + (Statements) (Empty)) (Empty)) (If - ( + (Statements (Call (Identifier) - ([]) + (Statements) (Empty))) (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty))) (If - ( + (Statements (Assignment (Identifier) (Integer)) @@ -55,20 +55,20 @@ (Integer))) (Call (Identifier) - ([]) + (Statements) (Empty)) (Context (Comment) (If - ( + (Statements (LessThan (Identifier) (Integer))) (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty)))))))) diff --git a/test/fixtures/go/corpus/imaginary-literals.diffA-B.txt b/test/fixtures/go/corpus/imaginary-literals.diffA-B.txt index e4b43e22b..5effba7cf 100644 --- a/test/fixtures/go/corpus/imaginary-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/imaginary-literals.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) { (Complex) diff --git a/test/fixtures/go/corpus/imaginary-literals.diffB-A.txt b/test/fixtures/go/corpus/imaginary-literals.diffB-A.txt index e4b43e22b..5effba7cf 100644 --- a/test/fixtures/go/corpus/imaginary-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/imaginary-literals.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) { (Complex) diff --git a/test/fixtures/go/corpus/imaginary-literals.parseA.txt b/test/fixtures/go/corpus/imaginary-literals.parseA.txt index c21f33e57..f7a8584b2 100644 --- a/test/fixtures/go/corpus/imaginary-literals.parseA.txt +++ b/test/fixtures/go/corpus/imaginary-literals.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Complex)) diff --git a/test/fixtures/go/corpus/imaginary-literals.parseB.txt b/test/fixtures/go/corpus/imaginary-literals.parseB.txt index c21f33e57..f7a8584b2 100644 --- a/test/fixtures/go/corpus/imaginary-literals.parseB.txt +++ b/test/fixtures/go/corpus/imaginary-literals.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Complex)) diff --git a/test/fixtures/go/corpus/import-statements.diffA-B.txt b/test/fixtures/go/corpus/import-statements.diffA-B.txt index 5b08d8e40..7a7da2e36 100644 --- a/test/fixtures/go/corpus/import-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/import-statements.diffA-B.txt @@ -1,7 +1,7 @@ (Program (Package (Identifier)) - ( + (Statements (Comment) (Comment) { (QualifiedImport @@ -12,5 +12,5 @@ (Function (Empty) (Identifier) - ([]) - ([]))) + (Statements) + (Statements))) diff --git a/test/fixtures/go/corpus/import-statements.diffB-A.txt b/test/fixtures/go/corpus/import-statements.diffB-A.txt index 5b08d8e40..7a7da2e36 100644 --- a/test/fixtures/go/corpus/import-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/import-statements.diffB-A.txt @@ -1,7 +1,7 @@ (Program (Package (Identifier)) - ( + (Statements (Comment) (Comment) { (QualifiedImport @@ -12,5 +12,5 @@ (Function (Empty) (Identifier) - ([]) - ([]))) + (Statements) + (Statements))) diff --git a/test/fixtures/go/corpus/import-statements.parseA.txt b/test/fixtures/go/corpus/import-statements.parseA.txt index 0c4964ed1..3dee6a1dc 100644 --- a/test/fixtures/go/corpus/import-statements.parseA.txt +++ b/test/fixtures/go/corpus/import-statements.parseA.txt @@ -1,7 +1,7 @@ (Program (Package (Identifier)) - ( + (Statements (Comment) (Comment) (QualifiedImport @@ -10,5 +10,5 @@ (Function (Empty) (Identifier) - ([]) - ([]))) + (Statements) + (Statements))) diff --git a/test/fixtures/go/corpus/import-statements.parseB.txt b/test/fixtures/go/corpus/import-statements.parseB.txt index 0c4964ed1..3dee6a1dc 100644 --- a/test/fixtures/go/corpus/import-statements.parseB.txt +++ b/test/fixtures/go/corpus/import-statements.parseB.txt @@ -1,7 +1,7 @@ (Program (Package (Identifier)) - ( + (Statements (Comment) (Comment) (QualifiedImport @@ -10,5 +10,5 @@ (Function (Empty) (Identifier) - ([]) - ([]))) + (Statements) + (Statements))) diff --git a/test/fixtures/go/corpus/increment-decrement-statements.diffA-B.txt b/test/fixtures/go/corpus/increment-decrement-statements.diffA-B.txt index e0f5fb1fa..45abdcf05 100644 --- a/test/fixtures/go/corpus/increment-decrement-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/increment-decrement-statements.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (PostIncrement { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/go/corpus/increment-decrement-statements.diffB-A.txt b/test/fixtures/go/corpus/increment-decrement-statements.diffB-A.txt index dcc538a29..3235fddb4 100644 --- a/test/fixtures/go/corpus/increment-decrement-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/increment-decrement-statements.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (PostIncrement { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/go/corpus/increment-decrement-statements.parseA.txt b/test/fixtures/go/corpus/increment-decrement-statements.parseA.txt index 0871ed54c..31efb99ab 100644 --- a/test/fixtures/go/corpus/increment-decrement-statements.parseA.txt +++ b/test/fixtures/go/corpus/increment-decrement-statements.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (PostIncrement (Identifier)) (PostDecrement diff --git a/test/fixtures/go/corpus/increment-decrement-statements.parseB.txt b/test/fixtures/go/corpus/increment-decrement-statements.parseB.txt index 8f8b3d7d8..3a5c0c90e 100644 --- a/test/fixtures/go/corpus/increment-decrement-statements.parseB.txt +++ b/test/fixtures/go/corpus/increment-decrement-statements.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (PostIncrement (Identifier)) (PostIncrement diff --git a/test/fixtures/go/corpus/int-literals.diffA-B.txt b/test/fixtures/go/corpus/int-literals.diffA-B.txt index b67722ecc..0509a4b55 100644 --- a/test/fixtures/go/corpus/int-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/int-literals.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) { (Integer) diff --git a/test/fixtures/go/corpus/int-literals.diffB-A.txt b/test/fixtures/go/corpus/int-literals.diffB-A.txt index b67722ecc..0509a4b55 100644 --- a/test/fixtures/go/corpus/int-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/int-literals.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) { (Integer) diff --git a/test/fixtures/go/corpus/int-literals.parseA.txt b/test/fixtures/go/corpus/int-literals.parseA.txt index 994737fb0..866d153dd 100644 --- a/test/fixtures/go/corpus/int-literals.parseA.txt +++ b/test/fixtures/go/corpus/int-literals.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Integer)) diff --git a/test/fixtures/go/corpus/int-literals.parseB.txt b/test/fixtures/go/corpus/int-literals.parseB.txt index 994737fb0..866d153dd 100644 --- a/test/fixtures/go/corpus/int-literals.parseB.txt +++ b/test/fixtures/go/corpus/int-literals.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Integer)) diff --git a/test/fixtures/go/corpus/interface-types.diffA-B.txt b/test/fixtures/go/corpus/interface-types.diffA-B.txt index 2706e9160..7dd0e89fb 100644 --- a/test/fixtures/go/corpus/interface-types.diffA-B.txt +++ b/test/fixtures/go/corpus/interface-types.diffA-B.txt @@ -4,15 +4,15 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type { (Identifier) ->(Identifier) } (Interface - ([])))) - ( + (Statements)))) + (Statements (Type { (Identifier) ->(Identifier) } @@ -20,12 +20,12 @@ (MemberAccess (Identifier) (Identifier))))) - ( + (Statements (Type { (Identifier) ->(Identifier) } (Interface - ( + (Statements (Identifier) (MemberAccess (Identifier) @@ -33,12 +33,12 @@ (MethodSignature (Identifier) (Identifier) - ( + (Statements (Identifier) (Identifier))))))) (Context (Comment) - ( + (Statements (Type { (Identifier) ->(Identifier) } @@ -47,4 +47,4 @@ (Empty) { (Identifier) ->(Identifier) } - ([]))))))))) + (Statements))))))))) diff --git a/test/fixtures/go/corpus/interface-types.diffB-A.txt b/test/fixtures/go/corpus/interface-types.diffB-A.txt index 2706e9160..7dd0e89fb 100644 --- a/test/fixtures/go/corpus/interface-types.diffB-A.txt +++ b/test/fixtures/go/corpus/interface-types.diffB-A.txt @@ -4,15 +4,15 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type { (Identifier) ->(Identifier) } (Interface - ([])))) - ( + (Statements)))) + (Statements (Type { (Identifier) ->(Identifier) } @@ -20,12 +20,12 @@ (MemberAccess (Identifier) (Identifier))))) - ( + (Statements (Type { (Identifier) ->(Identifier) } (Interface - ( + (Statements (Identifier) (MemberAccess (Identifier) @@ -33,12 +33,12 @@ (MethodSignature (Identifier) (Identifier) - ( + (Statements (Identifier) (Identifier))))))) (Context (Comment) - ( + (Statements (Type { (Identifier) ->(Identifier) } @@ -47,4 +47,4 @@ (Empty) { (Identifier) ->(Identifier) } - ([]))))))))) + (Statements))))))))) diff --git a/test/fixtures/go/corpus/interface-types.parseA.txt b/test/fixtures/go/corpus/interface-types.parseA.txt index 10cf5b569..4c29cbcbc 100644 --- a/test/fixtures/go/corpus/interface-types.parseA.txt +++ b/test/fixtures/go/corpus/interface-types.parseA.txt @@ -4,25 +4,25 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Interface - ([])))) - ( + (Statements)))) + (Statements (Type (Identifier) (Interface (MemberAccess (Identifier) (Identifier))))) - ( + (Statements (Type (Identifier) (Interface - ( + (Statements (Identifier) (MemberAccess (Identifier) @@ -30,16 +30,16 @@ (MethodSignature (Identifier) (Identifier) - ( + (Statements (Identifier) (Identifier))))))) (Context (Comment) - ( + (Statements (Type (Identifier) (Interface (MethodSignature (Empty) (Identifier) - ([]))))))))) + (Statements))))))))) diff --git a/test/fixtures/go/corpus/interface-types.parseB.txt b/test/fixtures/go/corpus/interface-types.parseB.txt index 10cf5b569..4c29cbcbc 100644 --- a/test/fixtures/go/corpus/interface-types.parseB.txt +++ b/test/fixtures/go/corpus/interface-types.parseB.txt @@ -4,25 +4,25 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Interface - ([])))) - ( + (Statements)))) + (Statements (Type (Identifier) (Interface (MemberAccess (Identifier) (Identifier))))) - ( + (Statements (Type (Identifier) (Interface - ( + (Statements (Identifier) (MemberAccess (Identifier) @@ -30,16 +30,16 @@ (MethodSignature (Identifier) (Identifier) - ( + (Statements (Identifier) (Identifier))))))) (Context (Comment) - ( + (Statements (Type (Identifier) (Interface (MethodSignature (Empty) (Identifier) - ([]))))))))) + (Statements))))))))) diff --git a/test/fixtures/go/corpus/label-statements.diffA-B.txt b/test/fixtures/go/corpus/label-statements.diffA-B.txt index cc3154157..2b1b97ef6 100644 --- a/test/fixtures/go/corpus/label-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/label-statements.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Label { (Identifier) ->(Identifier) } @@ -29,7 +29,7 @@ (Integer)) (PostIncrement (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/go/corpus/label-statements.diffB-A.txt b/test/fixtures/go/corpus/label-statements.diffB-A.txt index cc3154157..2b1b97ef6 100644 --- a/test/fixtures/go/corpus/label-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/label-statements.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Label { (Identifier) ->(Identifier) } @@ -29,7 +29,7 @@ (Integer)) (PostIncrement (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/go/corpus/label-statements.parseA.txt b/test/fixtures/go/corpus/label-statements.parseA.txt index 6d8a80f9a..c99e5541c 100644 --- a/test/fixtures/go/corpus/label-statements.parseA.txt +++ b/test/fixtures/go/corpus/label-statements.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Label (Identifier) (NoOp @@ -25,7 +25,7 @@ (Integer)) (PostIncrement (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/go/corpus/label-statements.parseB.txt b/test/fixtures/go/corpus/label-statements.parseB.txt index 6d8a80f9a..c99e5541c 100644 --- a/test/fixtures/go/corpus/label-statements.parseB.txt +++ b/test/fixtures/go/corpus/label-statements.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Label (Identifier) (NoOp @@ -25,7 +25,7 @@ (Integer)) (PostIncrement (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/go/corpus/map-literals.diffA-B.txt b/test/fixtures/go/corpus/map-literals.diffA-B.txt index aedcf1301..bb2ce33a2 100644 --- a/test/fixtures/go/corpus/map-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/map-literals.diffA-B.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Composite @@ -12,7 +12,7 @@ (Identifier) { (Identifier) ->(Identifier) }) - ( + (Statements (KeyValue { (TextElement) ->(TextElement) } diff --git a/test/fixtures/go/corpus/map-literals.diffB-A.txt b/test/fixtures/go/corpus/map-literals.diffB-A.txt index aedcf1301..bb2ce33a2 100644 --- a/test/fixtures/go/corpus/map-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/map-literals.diffB-A.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Composite @@ -12,7 +12,7 @@ (Identifier) { (Identifier) ->(Identifier) }) - ( + (Statements (KeyValue { (TextElement) ->(TextElement) } diff --git a/test/fixtures/go/corpus/map-literals.parseA.txt b/test/fixtures/go/corpus/map-literals.parseA.txt index 425fccca1..f3f8dcb3c 100644 --- a/test/fixtures/go/corpus/map-literals.parseA.txt +++ b/test/fixtures/go/corpus/map-literals.parseA.txt @@ -4,14 +4,14 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Composite (Map (Identifier) (Identifier)) - ( + (Statements (KeyValue (TextElement) (TextElement)) diff --git a/test/fixtures/go/corpus/map-literals.parseB.txt b/test/fixtures/go/corpus/map-literals.parseB.txt index 425fccca1..f3f8dcb3c 100644 --- a/test/fixtures/go/corpus/map-literals.parseB.txt +++ b/test/fixtures/go/corpus/map-literals.parseB.txt @@ -4,14 +4,14 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Composite (Map (Identifier) (Identifier)) - ( + (Statements (KeyValue (TextElement) (TextElement)) diff --git a/test/fixtures/go/corpus/map-types.diffA-B.txt b/test/fixtures/go/corpus/map-types.diffA-B.txt index 9155512d9..11c405f5e 100644 --- a/test/fixtures/go/corpus/map-types.diffA-B.txt +++ b/test/fixtures/go/corpus/map-types.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Map diff --git a/test/fixtures/go/corpus/map-types.diffB-A.txt b/test/fixtures/go/corpus/map-types.diffB-A.txt index 9155512d9..11c405f5e 100644 --- a/test/fixtures/go/corpus/map-types.diffB-A.txt +++ b/test/fixtures/go/corpus/map-types.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Map diff --git a/test/fixtures/go/corpus/map-types.parseA.txt b/test/fixtures/go/corpus/map-types.parseA.txt index 62dd40845..6128e1b82 100644 --- a/test/fixtures/go/corpus/map-types.parseA.txt +++ b/test/fixtures/go/corpus/map-types.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Map diff --git a/test/fixtures/go/corpus/map-types.parseB.txt b/test/fixtures/go/corpus/map-types.parseB.txt index 62dd40845..6128e1b82 100644 --- a/test/fixtures/go/corpus/map-types.parseB.txt +++ b/test/fixtures/go/corpus/map-types.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Map diff --git a/test/fixtures/go/corpus/method-declarations.diffA-B.txt b/test/fixtures/go/corpus/method-declarations.diffA-B.txt index 0ae61f435..847454e0e 100644 --- a/test/fixtures/go/corpus/method-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/method-declarations.diffA-B.txt @@ -4,38 +4,38 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Method (Empty) (Identifier) { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty)) (Method - ( + (Statements (Identifier)) - ( + (Statements (Identifier) { (Identifier) ->(Identifier) }) (Identifier) - ( + (Statements (Identifier) { (Identifier) ->(Identifier) }) - ([])) + (Statements)) (Method - ( + (Statements (Identifier)) - ( + (Statements (Identifier) (Pointer (Identifier))) { (Identifier) ->(Identifier) } - ([]) + (Statements) (Return (Call (MemberAccess @@ -55,7 +55,7 @@ {+(MemberAccess {+(Identifier)+} {+(Identifier)+})+} - {+( + {+(Statements {+(MemberAccess {+(Identifier)+} {+(Identifier)+})+} @@ -68,7 +68,7 @@ {+(MemberAccess {+(Identifier)+} {+(Identifier)+})+} - {+( + {+(Statements {+(MemberAccess {+(Identifier)+} {+(Identifier)+})+} @@ -86,18 +86,18 @@ {+(Identifier)+}) }) (Empty)))) (Method - ([]) - ( + (Statements) + (Statements { (Identifier) ->(Identifier) } (Pointer (Identifier))) (Identifier) - ( + (Statements (Identifier) { (Identifier) ->(Identifier) }) - ( + (Statements (Assignment (MemberAccess (Identifier) @@ -117,17 +117,17 @@ (Identifier)) (Identifier))))) (Method - ( + (Statements (Identifier)) - ( + (Statements (Identifier) (Pointer (Identifier))) (Identifier) - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) } (Identifier)) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/method-declarations.diffB-A.txt b/test/fixtures/go/corpus/method-declarations.diffB-A.txt index e751ae62c..6329377d8 100644 --- a/test/fixtures/go/corpus/method-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/method-declarations.diffB-A.txt @@ -4,38 +4,38 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Method (Empty) (Identifier) { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty)) (Method - ( + (Statements (Identifier)) - ( + (Statements (Identifier) { (Identifier) ->(Identifier) }) (Identifier) - ( + (Statements (Identifier) { (Identifier) ->(Identifier) }) - ([])) + (Statements)) (Method - ( + (Statements (Identifier)) - ( + (Statements (Identifier) (Pointer (Identifier))) { (Identifier) ->(Identifier) } - ([]) + (Statements) (Return (Call (MemberAccess @@ -48,7 +48,7 @@ {-(MemberAccess {-(Identifier)-} {-(Identifier)-})-} - {-( + {-(Statements {-(MemberAccess {-(Identifier)-} {-(Identifier)-})-} @@ -61,7 +61,7 @@ {-(MemberAccess {-(Identifier)-} {-(Identifier)-})-} - {-( + {-(Statements {-(MemberAccess {-(Identifier)-} {-(Identifier)-})-} @@ -86,18 +86,18 @@ {+(Identifier)+})+}) }) (Empty)))) (Method - ([]) - ( + (Statements) + (Statements { (Identifier) ->(Identifier) } (Pointer (Identifier))) (Identifier) - ( + (Statements (Identifier) { (Identifier) ->(Identifier) }) - ( + (Statements (Assignment (MemberAccess (Identifier) @@ -117,17 +117,17 @@ (Identifier)) (Identifier))))) (Method - ( + (Statements (Identifier)) - ( + (Statements (Identifier) (Pointer (Identifier))) (Identifier) - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) } (Identifier)) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/method-declarations.parseA.txt b/test/fixtures/go/corpus/method-declarations.parseA.txt index e50a11066..9fced1d8c 100644 --- a/test/fixtures/go/corpus/method-declarations.parseA.txt +++ b/test/fixtures/go/corpus/method-declarations.parseA.txt @@ -4,34 +4,34 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Method (Empty) (Identifier) (Identifier) - ([]) + (Statements) (Empty)) (Method - ( + (Statements (Identifier)) - ( + (Statements (Identifier) (Identifier)) (Identifier) - ( + (Statements (Identifier) (Identifier)) - ([])) + (Statements)) (Method - ( + (Statements (Identifier)) - ( + (Statements (Identifier) (Pointer (Identifier))) (Identifier) - ([]) + (Statements) (Return (Call (MemberAccess @@ -54,16 +54,16 @@ (Identifier)))) (Empty)))) (Method - ([]) - ( + (Statements) + (Statements (Identifier) (Pointer (Identifier))) (Identifier) - ( + (Statements (Identifier) (Identifier)) - ( + (Statements (Assignment (MemberAccess (Identifier) @@ -83,15 +83,15 @@ (Identifier)) (Identifier))))) (Method - ( + (Statements (Identifier)) - ( + (Statements (Identifier) (Pointer (Identifier))) (Identifier) - ( + (Statements (Identifier) (Identifier) (Identifier)) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/method-declarations.parseB.txt b/test/fixtures/go/corpus/method-declarations.parseB.txt index d1d7704b8..1185a4db2 100644 --- a/test/fixtures/go/corpus/method-declarations.parseB.txt +++ b/test/fixtures/go/corpus/method-declarations.parseB.txt @@ -4,34 +4,34 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Method (Empty) (Identifier) (Identifier) - ([]) + (Statements) (Empty)) (Method - ( + (Statements (Identifier)) - ( + (Statements (Identifier) (Identifier)) (Identifier) - ( + (Statements (Identifier) (Identifier)) - ([])) + (Statements)) (Method - ( + (Statements (Identifier)) - ( + (Statements (Identifier) (Pointer (Identifier))) (Identifier) - ([]) + (Statements) (Return (Call (MemberAccess @@ -44,7 +44,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements (MemberAccess (Identifier) (Identifier)) @@ -57,7 +57,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements (MemberAccess (Identifier) (Identifier)) @@ -68,16 +68,16 @@ (Identifier))) (Empty)))) (Method - ([]) - ( + (Statements) + (Statements (Identifier) (Pointer (Identifier))) (Identifier) - ( + (Statements (Identifier) (Identifier)) - ( + (Statements (Assignment (MemberAccess (Identifier) @@ -97,15 +97,15 @@ (Identifier)) (Identifier))))) (Method - ( + (Statements (Identifier)) - ( + (Statements (Identifier) (Pointer (Identifier))) (Identifier) - ( + (Statements (Identifier) (Identifier) (Identifier)) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/modifying-struct-fields.diffA-B.txt b/test/fixtures/go/corpus/modifying-struct-fields.diffA-B.txt index 62c3996ee..8f06d89dd 100644 --- a/test/fixtures/go/corpus/modifying-struct-fields.diffA-B.txt +++ b/test/fixtures/go/corpus/modifying-struct-fields.diffA-B.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Reference (Composite (Identifier) - ( + (Statements (KeyValue { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/modifying-struct-fields.diffB-A.txt b/test/fixtures/go/corpus/modifying-struct-fields.diffB-A.txt index 8e85bfbbc..239eeee8e 100644 --- a/test/fixtures/go/corpus/modifying-struct-fields.diffB-A.txt +++ b/test/fixtures/go/corpus/modifying-struct-fields.diffB-A.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Reference (Composite (Identifier) - ( + (Statements (KeyValue { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/modifying-struct-fields.parseA.txt b/test/fixtures/go/corpus/modifying-struct-fields.parseA.txt index 7db48260f..9a8d9a7e4 100644 --- a/test/fixtures/go/corpus/modifying-struct-fields.parseA.txt +++ b/test/fixtures/go/corpus/modifying-struct-fields.parseA.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Reference (Composite (Identifier) - ( + (Statements (KeyValue (Identifier) (Identifier)))))))) diff --git a/test/fixtures/go/corpus/modifying-struct-fields.parseB.txt b/test/fixtures/go/corpus/modifying-struct-fields.parseB.txt index f3b7bff5d..79a74af4a 100644 --- a/test/fixtures/go/corpus/modifying-struct-fields.parseB.txt +++ b/test/fixtures/go/corpus/modifying-struct-fields.parseB.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Reference (Composite (Identifier) - ( + (Statements (KeyValue (Identifier) (Call diff --git a/test/fixtures/go/corpus/parameter-declarations-with-types.diffA-B.txt b/test/fixtures/go/corpus/parameter-declarations-with-types.diffA-B.txt index 673ed5806..43e79de42 100644 --- a/test/fixtures/go/corpus/parameter-declarations-with-types.diffA-B.txt +++ b/test/fixtures/go/corpus/parameter-declarations-with-types.diffA-B.txt @@ -4,20 +4,20 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) (Identifier) - ( - ( + (Statements + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) })) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/parameter-declarations-with-types.diffB-A.txt b/test/fixtures/go/corpus/parameter-declarations-with-types.diffB-A.txt index 673ed5806..43e79de42 100644 --- a/test/fixtures/go/corpus/parameter-declarations-with-types.diffB-A.txt +++ b/test/fixtures/go/corpus/parameter-declarations-with-types.diffB-A.txt @@ -4,20 +4,20 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) (Identifier) - ( - ( + (Statements + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) })) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/parameter-declarations-with-types.parseA.txt b/test/fixtures/go/corpus/parameter-declarations-with-types.parseA.txt index 63501f187..dcbdb5c2b 100644 --- a/test/fixtures/go/corpus/parameter-declarations-with-types.parseA.txt +++ b/test/fixtures/go/corpus/parameter-declarations-with-types.parseA.txt @@ -4,16 +4,16 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) (Identifier) - ( - ( + (Statements + (Statements (Identifier) (Identifier)) - ( + (Statements (Identifier) (Identifier))) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/parameter-declarations-with-types.parseB.txt b/test/fixtures/go/corpus/parameter-declarations-with-types.parseB.txt index 63501f187..dcbdb5c2b 100644 --- a/test/fixtures/go/corpus/parameter-declarations-with-types.parseB.txt +++ b/test/fixtures/go/corpus/parameter-declarations-with-types.parseB.txt @@ -4,16 +4,16 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) (Identifier) - ( - ( + (Statements + (Statements (Identifier) (Identifier)) - ( + (Statements (Identifier) (Identifier))) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/pointer-types.diffA-B.txt b/test/fixtures/go/corpus/pointer-types.diffA-B.txt index 3497ebf29..15cb6604f 100644 --- a/test/fixtures/go/corpus/pointer-types.diffA-B.txt +++ b/test/fixtures/go/corpus/pointer-types.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Pointer diff --git a/test/fixtures/go/corpus/pointer-types.diffB-A.txt b/test/fixtures/go/corpus/pointer-types.diffB-A.txt index 3497ebf29..15cb6604f 100644 --- a/test/fixtures/go/corpus/pointer-types.diffB-A.txt +++ b/test/fixtures/go/corpus/pointer-types.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Pointer diff --git a/test/fixtures/go/corpus/pointer-types.parseA.txt b/test/fixtures/go/corpus/pointer-types.parseA.txt index 48e791de6..cd4e58bbf 100644 --- a/test/fixtures/go/corpus/pointer-types.parseA.txt +++ b/test/fixtures/go/corpus/pointer-types.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Pointer diff --git a/test/fixtures/go/corpus/pointer-types.parseB.txt b/test/fixtures/go/corpus/pointer-types.parseB.txt index 48e791de6..cd4e58bbf 100644 --- a/test/fixtures/go/corpus/pointer-types.parseB.txt +++ b/test/fixtures/go/corpus/pointer-types.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Pointer diff --git a/test/fixtures/go/corpus/qualified-types.diffA-B.txt b/test/fixtures/go/corpus/qualified-types.diffA-B.txt index 784a7dd3f..8ad11b154 100644 --- a/test/fixtures/go/corpus/qualified-types.diffA-B.txt +++ b/test/fixtures/go/corpus/qualified-types.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/qualified-types.diffB-A.txt b/test/fixtures/go/corpus/qualified-types.diffB-A.txt index 784a7dd3f..8ad11b154 100644 --- a/test/fixtures/go/corpus/qualified-types.diffB-A.txt +++ b/test/fixtures/go/corpus/qualified-types.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/qualified-types.parseA.txt b/test/fixtures/go/corpus/qualified-types.parseA.txt index 5c8495ebd..2659648a1 100644 --- a/test/fixtures/go/corpus/qualified-types.parseA.txt +++ b/test/fixtures/go/corpus/qualified-types.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (MemberAccess diff --git a/test/fixtures/go/corpus/qualified-types.parseB.txt b/test/fixtures/go/corpus/qualified-types.parseB.txt index 5c8495ebd..2659648a1 100644 --- a/test/fixtures/go/corpus/qualified-types.parseB.txt +++ b/test/fixtures/go/corpus/qualified-types.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (MemberAccess diff --git a/test/fixtures/go/corpus/rune-literals.diffA-B.txt b/test/fixtures/go/corpus/rune-literals.diffA-B.txt index 6c82ffa99..bf009a8d1 100644 --- a/test/fixtures/go/corpus/rune-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/rune-literals.diffA-B.txt @@ -1,7 +1,7 @@ (Program (Package (Identifier)) - ( + (Statements (Assignment (Identifier) { (Rune) diff --git a/test/fixtures/go/corpus/rune-literals.diffB-A.txt b/test/fixtures/go/corpus/rune-literals.diffB-A.txt index 6c82ffa99..bf009a8d1 100644 --- a/test/fixtures/go/corpus/rune-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/rune-literals.diffB-A.txt @@ -1,7 +1,7 @@ (Program (Package (Identifier)) - ( + (Statements (Assignment (Identifier) { (Rune) diff --git a/test/fixtures/go/corpus/rune-literals.parseA.txt b/test/fixtures/go/corpus/rune-literals.parseA.txt index 180677c60..90ad8d2dd 100644 --- a/test/fixtures/go/corpus/rune-literals.parseA.txt +++ b/test/fixtures/go/corpus/rune-literals.parseA.txt @@ -1,7 +1,7 @@ (Program (Package (Identifier)) - ( + (Statements (Assignment (Identifier) (Rune)) diff --git a/test/fixtures/go/corpus/rune-literals.parseB.txt b/test/fixtures/go/corpus/rune-literals.parseB.txt index 180677c60..90ad8d2dd 100644 --- a/test/fixtures/go/corpus/rune-literals.parseB.txt +++ b/test/fixtures/go/corpus/rune-literals.parseB.txt @@ -1,7 +1,7 @@ (Program (Package (Identifier)) - ( + (Statements (Assignment (Identifier) (Rune)) diff --git a/test/fixtures/go/corpus/select-statements.diffA-B.txt b/test/fixtures/go/corpus/select-statements.diffA-B.txt index 87681ac99..12ebaa2dd 100644 --- a/test/fixtures/go/corpus/select-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/select-statements.diffA-B.txt @@ -4,10 +4,10 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Select - ( + (Statements (Pattern (Receive { (Identifier) @@ -38,7 +38,7 @@ { (Integer) ->(Integer) } (Empty)))) - ( + (Statements (Call (Identifier) (Integer) @@ -46,14 +46,14 @@ {+(PostIncrement {+(Identifier)+})+} {+(If - {+( + {+(Statements {+(Identifier)+})+} - {+( + {+(Statements {+(Send {+(Identifier)+} {+(Composite {+(Identifier)+} - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+})+})+} {+(Return @@ -62,14 +62,14 @@ {-(PostDecrement {-(Identifier)-})-} {-(If - {-( + {-(Statements {-(Identifier)-})-} - {-( + {-(Statements {-(Send {-(Identifier)-} {-(Composite {-(Identifier)-} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-})-})-} {-(Return @@ -77,25 +77,25 @@ {-(Empty)-})-})) (Pattern (DefaultPattern - ([])) + (Statements)) (Return (Empty))))) (Select - ( + (Statements (Pattern (Receive (Empty) (ReceiveOperator { (Identifier) ->(Identifier) })) - ([])) + (Statements)) (Pattern (Receive (Empty) (ReceiveOperator (Identifier))) - ([])) + (Statements)) {-(Pattern {-(DefaultPattern - {-([])-})-} - {-([])-})-}))))) + {-(Statements)-})-} + {-(Statements)-})-}))))) diff --git a/test/fixtures/go/corpus/select-statements.diffB-A.txt b/test/fixtures/go/corpus/select-statements.diffB-A.txt index 565ac4a6b..e1fdedccb 100644 --- a/test/fixtures/go/corpus/select-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/select-statements.diffB-A.txt @@ -4,10 +4,10 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Select - ( + (Statements (Pattern (Receive { (Identifier) @@ -38,7 +38,7 @@ { (Integer) ->(Integer) } (Empty)))) - ( + (Statements (Call (Identifier) (Integer) @@ -46,14 +46,14 @@ {+(PostDecrement {+(Identifier)+})+} {+(If - {+( + {+(Statements {+(Identifier)+})+} - {+( + {+(Statements {+(Send {+(Identifier)+} {+(Composite {+(Identifier)+} - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+})+})+} {+(Return @@ -62,14 +62,14 @@ {-(PostIncrement {-(Identifier)-})-} {-(If - {-( + {-(Statements {-(Identifier)-})-} - {-( + {-(Statements {-(Send {-(Identifier)-} {-(Composite {-(Identifier)-} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-})-})-} {-(Return @@ -77,25 +77,25 @@ {-(Empty)-})-})) (Pattern (DefaultPattern - ([])) + (Statements)) (Return (Empty))))) (Select - ( + (Statements (Pattern (Receive (Empty) (ReceiveOperator { (Identifier) ->(Identifier) })) - ([])) + (Statements)) (Pattern (Receive (Empty) (ReceiveOperator (Identifier))) - ([])) + (Statements)) {+(Pattern {+(DefaultPattern - {+([])+})+} - {+([])+})+}))))) + {+(Statements)+})+} + {+(Statements)+})+}))))) diff --git a/test/fixtures/go/corpus/select-statements.parseA.txt b/test/fixtures/go/corpus/select-statements.parseA.txt index ec7db5725..7674928c7 100644 --- a/test/fixtures/go/corpus/select-statements.parseA.txt +++ b/test/fixtures/go/corpus/select-statements.parseA.txt @@ -4,10 +4,10 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Select - ( + (Statements (Pattern (Receive (Identifier) @@ -35,7 +35,7 @@ (Identifier)) (Integer) (Empty)))) - ( + (Statements (Call (Identifier) (Integer) @@ -43,14 +43,14 @@ (PostDecrement (Identifier)) (If - ( + (Statements (Identifier)) - ( + (Statements (Send (Identifier) (Composite (Identifier) - ( + (Statements (Identifier) (Identifier)))) (Return @@ -58,24 +58,24 @@ (Empty)))) (Pattern (DefaultPattern - ([])) + (Statements)) (Return (Empty))))) (Select - ( + (Statements (Pattern (Receive (Empty) (ReceiveOperator (Identifier))) - ([])) + (Statements)) (Pattern (Receive (Empty) (ReceiveOperator (Identifier))) - ([])) + (Statements)) (Pattern (DefaultPattern - ([])) - ([]))))))) + (Statements)) + (Statements))))))) diff --git a/test/fixtures/go/corpus/select-statements.parseB.txt b/test/fixtures/go/corpus/select-statements.parseB.txt index a7a341b50..e5ed101b4 100644 --- a/test/fixtures/go/corpus/select-statements.parseB.txt +++ b/test/fixtures/go/corpus/select-statements.parseB.txt @@ -4,10 +4,10 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Select - ( + (Statements (Pattern (Receive (Identifier) @@ -35,7 +35,7 @@ (Identifier)) (Integer) (Empty)))) - ( + (Statements (Call (Identifier) (Integer) @@ -43,14 +43,14 @@ (PostIncrement (Identifier)) (If - ( + (Statements (Identifier)) - ( + (Statements (Send (Identifier) (Composite (Identifier) - ( + (Statements (Identifier) (Identifier)))) (Return @@ -58,20 +58,20 @@ (Empty)))) (Pattern (DefaultPattern - ([])) + (Statements)) (Return (Empty))))) (Select - ( + (Statements (Pattern (Receive (Empty) (ReceiveOperator (Identifier))) - ([])) + (Statements)) (Pattern (Receive (Empty) (ReceiveOperator (Identifier))) - ([]))))))) + (Statements))))))) diff --git a/test/fixtures/go/corpus/selector-expressions.diffA-B.txt b/test/fixtures/go/corpus/selector-expressions.diffA-B.txt index 11ad10899..7930ef495 100644 --- a/test/fixtures/go/corpus/selector-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/selector-expressions.diffA-B.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Call (MemberAccess (MemberAccess @@ -14,5 +14,5 @@ ->(Identifier) }) { (Identifier) ->(Identifier) }) - ([]) + (Statements) (Empty)))) diff --git a/test/fixtures/go/corpus/selector-expressions.diffB-A.txt b/test/fixtures/go/corpus/selector-expressions.diffB-A.txt index 11ad10899..7930ef495 100644 --- a/test/fixtures/go/corpus/selector-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/selector-expressions.diffB-A.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Call (MemberAccess (MemberAccess @@ -14,5 +14,5 @@ ->(Identifier) }) { (Identifier) ->(Identifier) }) - ([]) + (Statements) (Empty)))) diff --git a/test/fixtures/go/corpus/selector-expressions.parseA.txt b/test/fixtures/go/corpus/selector-expressions.parseA.txt index 4970dc10b..6635631f2 100644 --- a/test/fixtures/go/corpus/selector-expressions.parseA.txt +++ b/test/fixtures/go/corpus/selector-expressions.parseA.txt @@ -4,12 +4,12 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Call (MemberAccess (MemberAccess (Identifier) (Identifier)) (Identifier)) - ([]) + (Statements) (Empty)))) diff --git a/test/fixtures/go/corpus/selector-expressions.parseB.txt b/test/fixtures/go/corpus/selector-expressions.parseB.txt index 4970dc10b..6635631f2 100644 --- a/test/fixtures/go/corpus/selector-expressions.parseB.txt +++ b/test/fixtures/go/corpus/selector-expressions.parseB.txt @@ -4,12 +4,12 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Call (MemberAccess (MemberAccess (Identifier) (Identifier)) (Identifier)) - ([]) + (Statements) (Empty)))) diff --git a/test/fixtures/go/corpus/send-statements.diffA-B.txt b/test/fixtures/go/corpus/send-statements.diffA-B.txt index 3cf96b18b..41e14f0e0 100644 --- a/test/fixtures/go/corpus/send-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/send-statements.diffA-B.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Send { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/send-statements.diffB-A.txt b/test/fixtures/go/corpus/send-statements.diffB-A.txt index 3cf96b18b..41e14f0e0 100644 --- a/test/fixtures/go/corpus/send-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/send-statements.diffB-A.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Send { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/send-statements.parseA.txt b/test/fixtures/go/corpus/send-statements.parseA.txt index fe49f874b..82d99394b 100644 --- a/test/fixtures/go/corpus/send-statements.parseA.txt +++ b/test/fixtures/go/corpus/send-statements.parseA.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Send (Identifier) (Integer)))) diff --git a/test/fixtures/go/corpus/send-statements.parseB.txt b/test/fixtures/go/corpus/send-statements.parseB.txt index fe49f874b..82d99394b 100644 --- a/test/fixtures/go/corpus/send-statements.parseB.txt +++ b/test/fixtures/go/corpus/send-statements.parseB.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Send (Identifier) (Integer)))) diff --git a/test/fixtures/go/corpus/short-var-declarations.diffA-B.txt b/test/fixtures/go/corpus/short-var-declarations.diffA-B.txt index 4ea66cfea..b7a258c18 100644 --- a/test/fixtures/go/corpus/short-var-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/short-var-declarations.diffA-B.txt @@ -4,14 +4,14 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) - ( + (Statements { (Integer) ->(Integer) } { (Integer) diff --git a/test/fixtures/go/corpus/short-var-declarations.diffB-A.txt b/test/fixtures/go/corpus/short-var-declarations.diffB-A.txt index 4ea66cfea..b7a258c18 100644 --- a/test/fixtures/go/corpus/short-var-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/short-var-declarations.diffB-A.txt @@ -4,14 +4,14 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) - ( + (Statements { (Integer) ->(Integer) } { (Integer) diff --git a/test/fixtures/go/corpus/short-var-declarations.parseA.txt b/test/fixtures/go/corpus/short-var-declarations.parseA.txt index ac7eb7599..bbacb990a 100644 --- a/test/fixtures/go/corpus/short-var-declarations.parseA.txt +++ b/test/fixtures/go/corpus/short-var-declarations.parseA.txt @@ -4,11 +4,11 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment - ( + (Statements (Identifier) (Identifier)) - ( + (Statements (Integer) (Integer))))) diff --git a/test/fixtures/go/corpus/short-var-declarations.parseB.txt b/test/fixtures/go/corpus/short-var-declarations.parseB.txt index ac7eb7599..bbacb990a 100644 --- a/test/fixtures/go/corpus/short-var-declarations.parseB.txt +++ b/test/fixtures/go/corpus/short-var-declarations.parseB.txt @@ -4,11 +4,11 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment - ( + (Statements (Identifier) (Identifier)) - ( + (Statements (Integer) (Integer))))) diff --git a/test/fixtures/go/corpus/single-import-declarations.diffA-B.txt b/test/fixtures/go/corpus/single-import-declarations.diffA-B.txt index 708a431ba..838735730 100644 --- a/test/fixtures/go/corpus/single-import-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/single-import-declarations.diffA-B.txt @@ -16,5 +16,5 @@ (Function (Empty) (Identifier) - ([]) - ([]))) + (Statements) + (Statements))) diff --git a/test/fixtures/go/corpus/single-import-declarations.diffB-A.txt b/test/fixtures/go/corpus/single-import-declarations.diffB-A.txt index 708a431ba..838735730 100644 --- a/test/fixtures/go/corpus/single-import-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/single-import-declarations.diffB-A.txt @@ -16,5 +16,5 @@ (Function (Empty) (Identifier) - ([]) - ([]))) + (Statements) + (Statements))) diff --git a/test/fixtures/go/corpus/single-import-declarations.parseA.txt b/test/fixtures/go/corpus/single-import-declarations.parseA.txt index 7e5f7cc1b..dc96d2e05 100644 --- a/test/fixtures/go/corpus/single-import-declarations.parseA.txt +++ b/test/fixtures/go/corpus/single-import-declarations.parseA.txt @@ -10,5 +10,5 @@ (Function (Empty) (Identifier) - ([]) - ([]))) + (Statements) + (Statements))) diff --git a/test/fixtures/go/corpus/single-import-declarations.parseB.txt b/test/fixtures/go/corpus/single-import-declarations.parseB.txt index 7e5f7cc1b..dc96d2e05 100644 --- a/test/fixtures/go/corpus/single-import-declarations.parseB.txt +++ b/test/fixtures/go/corpus/single-import-declarations.parseB.txt @@ -10,5 +10,5 @@ (Function (Empty) (Identifier) - ([]) - ([]))) + (Statements) + (Statements))) diff --git a/test/fixtures/go/corpus/single-line-function-declarations.diffA-B.txt b/test/fixtures/go/corpus/single-line-function-declarations.diffA-B.txt index 3f4cf0364..f18abdfa2 100644 --- a/test/fixtures/go/corpus/single-line-function-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/single-line-function-declarations.diffA-B.txt @@ -4,42 +4,42 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) { (Identifier) ->(Identifier) } - ([]) + (Statements) (Call (Identifier) - ([]) + (Statements) (Empty))) (Function (Empty) { (Identifier) ->(Identifier) } - ([]) - ( + (Statements) + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty)))) (Function (Empty) { (Identifier) ->(Identifier) } - ([]) - ( + (Statements) + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty))))) diff --git a/test/fixtures/go/corpus/single-line-function-declarations.diffB-A.txt b/test/fixtures/go/corpus/single-line-function-declarations.diffB-A.txt index 3f4cf0364..f18abdfa2 100644 --- a/test/fixtures/go/corpus/single-line-function-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/single-line-function-declarations.diffB-A.txt @@ -4,42 +4,42 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) { (Identifier) ->(Identifier) } - ([]) + (Statements) (Call (Identifier) - ([]) + (Statements) (Empty))) (Function (Empty) { (Identifier) ->(Identifier) } - ([]) - ( + (Statements) + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty)))) (Function (Empty) { (Identifier) ->(Identifier) } - ([]) - ( + (Statements) + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty))))) diff --git a/test/fixtures/go/corpus/single-line-function-declarations.parseA.txt b/test/fixtures/go/corpus/single-line-function-declarations.parseA.txt index 5040892e4..d7e7e69ec 100644 --- a/test/fixtures/go/corpus/single-line-function-declarations.parseA.txt +++ b/test/fixtures/go/corpus/single-line-function-declarations.parseA.txt @@ -4,39 +4,39 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) (Identifier) - ([]) + (Statements) (Call (Identifier) - ([]) + (Statements) (Empty))) (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty)))) (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty))))) diff --git a/test/fixtures/go/corpus/single-line-function-declarations.parseB.txt b/test/fixtures/go/corpus/single-line-function-declarations.parseB.txt index 5040892e4..d7e7e69ec 100644 --- a/test/fixtures/go/corpus/single-line-function-declarations.parseB.txt +++ b/test/fixtures/go/corpus/single-line-function-declarations.parseB.txt @@ -4,39 +4,39 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) (Identifier) - ([]) + (Statements) (Call (Identifier) - ([]) + (Statements) (Empty))) (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty)))) (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Call (Identifier) - ([]) + (Statements) (Empty)) (Call (Identifier) - ([]) + (Statements) (Empty))))) diff --git a/test/fixtures/go/corpus/slice-expressions.diffA-B.txt b/test/fixtures/go/corpus/slice-expressions.diffA-B.txt index 8307a41d4..afdd3980e 100644 --- a/test/fixtures/go/corpus/slice-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/slice-expressions.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Slice (Identifier) { (Integer) diff --git a/test/fixtures/go/corpus/slice-expressions.diffB-A.txt b/test/fixtures/go/corpus/slice-expressions.diffB-A.txt index 1a7a99db8..0f1c22f17 100644 --- a/test/fixtures/go/corpus/slice-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/slice-expressions.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Slice (Identifier) { (Integer) diff --git a/test/fixtures/go/corpus/slice-expressions.parseA.txt b/test/fixtures/go/corpus/slice-expressions.parseA.txt index d9eaae91c..b7271293b 100644 --- a/test/fixtures/go/corpus/slice-expressions.parseA.txt +++ b/test/fixtures/go/corpus/slice-expressions.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Slice (Identifier) (Integer) diff --git a/test/fixtures/go/corpus/slice-expressions.parseB.txt b/test/fixtures/go/corpus/slice-expressions.parseB.txt index b00c0ccee..5b69a0f3c 100644 --- a/test/fixtures/go/corpus/slice-expressions.parseB.txt +++ b/test/fixtures/go/corpus/slice-expressions.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Slice (Identifier) (Integer) diff --git a/test/fixtures/go/corpus/slice-literals.diffA-B.txt b/test/fixtures/go/corpus/slice-literals.diffA-B.txt index 5ce5551f4..f0dd4b87f 100644 --- a/test/fixtures/go/corpus/slice-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/slice-literals.diffA-B.txt @@ -4,21 +4,21 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Composite (Slice (Identifier)) - ( + (Statements {+(TextElement)+}))) (Assignment (Identifier) (Composite (Slice (Identifier)) - ( + (Statements { (TextElement) ->(TextElement) }))) (Assignment @@ -26,7 +26,7 @@ (Composite (Slice (Identifier)) - ( + (Statements { (TextElement) ->(TextElement) } { (TextElement) diff --git a/test/fixtures/go/corpus/slice-literals.diffB-A.txt b/test/fixtures/go/corpus/slice-literals.diffB-A.txt index 03b13cc4f..221351ea1 100644 --- a/test/fixtures/go/corpus/slice-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/slice-literals.diffB-A.txt @@ -4,20 +4,21 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Composite (Slice (Identifier)) - ({-(TextElement)-}))) + (Statements + {-(TextElement)-}))) (Assignment (Identifier) (Composite (Slice (Identifier)) - ( + (Statements { (TextElement) ->(TextElement) }))) (Assignment @@ -25,7 +26,7 @@ (Composite (Slice (Identifier)) - ( + (Statements { (TextElement) ->(TextElement) } { (TextElement) diff --git a/test/fixtures/go/corpus/slice-literals.parseA.txt b/test/fixtures/go/corpus/slice-literals.parseA.txt index 620dca48d..9434a9460 100644 --- a/test/fixtures/go/corpus/slice-literals.parseA.txt +++ b/test/fixtures/go/corpus/slice-literals.parseA.txt @@ -4,26 +4,26 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Composite (Slice (Identifier)) - ([]))) + (Statements))) (Assignment (Identifier) (Composite (Slice (Identifier)) - ( + (Statements (TextElement)))) (Assignment (Identifier) (Composite (Slice (Identifier)) - ( + (Statements (TextElement) (TextElement))))))) diff --git a/test/fixtures/go/corpus/slice-literals.parseB.txt b/test/fixtures/go/corpus/slice-literals.parseB.txt index eae07dd5d..c9e74f4fc 100644 --- a/test/fixtures/go/corpus/slice-literals.parseB.txt +++ b/test/fixtures/go/corpus/slice-literals.parseB.txt @@ -4,27 +4,27 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Composite (Slice (Identifier)) - ( + (Statements (TextElement)))) (Assignment (Identifier) (Composite (Slice (Identifier)) - ( + (Statements (TextElement)))) (Assignment (Identifier) (Composite (Slice (Identifier)) - ( + (Statements (TextElement) (TextElement))))))) diff --git a/test/fixtures/go/corpus/slice-types.diffA-B.txt b/test/fixtures/go/corpus/slice-types.diffA-B.txt index 966dd0e14..f546172ad 100644 --- a/test/fixtures/go/corpus/slice-types.diffA-B.txt +++ b/test/fixtures/go/corpus/slice-types.diffA-B.txt @@ -4,16 +4,16 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Slice { (Identifier) ->(Slice {+(Identifier)+}) }))) - ( + (Statements (Type (Identifier) (Slice diff --git a/test/fixtures/go/corpus/slice-types.diffB-A.txt b/test/fixtures/go/corpus/slice-types.diffB-A.txt index 06278c610..2686dc34a 100644 --- a/test/fixtures/go/corpus/slice-types.diffB-A.txt +++ b/test/fixtures/go/corpus/slice-types.diffB-A.txt @@ -4,16 +4,16 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Slice { (Slice {-(Identifier)-}) ->(Identifier) }))) - ( + (Statements (Type (Identifier) (Slice diff --git a/test/fixtures/go/corpus/slice-types.parseA.txt b/test/fixtures/go/corpus/slice-types.parseA.txt index 93cddcbbe..bbed0bb87 100644 --- a/test/fixtures/go/corpus/slice-types.parseA.txt +++ b/test/fixtures/go/corpus/slice-types.parseA.txt @@ -4,14 +4,14 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Slice (Identifier)))) - ( + (Statements (Type (Identifier) (Slice diff --git a/test/fixtures/go/corpus/slice-types.parseB.txt b/test/fixtures/go/corpus/slice-types.parseB.txt index a3763ecde..5573c3321 100644 --- a/test/fixtures/go/corpus/slice-types.parseB.txt +++ b/test/fixtures/go/corpus/slice-types.parseB.txt @@ -4,15 +4,15 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Slice (Slice (Identifier))))) - ( + (Statements (Type (Identifier) (Slice diff --git a/test/fixtures/go/corpus/string-literals.diffA-B.txt b/test/fixtures/go/corpus/string-literals.diffA-B.txt index 53d365c92..1046acf29 100644 --- a/test/fixtures/go/corpus/string-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/string-literals.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) { (TextElement) diff --git a/test/fixtures/go/corpus/string-literals.diffB-A.txt b/test/fixtures/go/corpus/string-literals.diffB-A.txt index 53d365c92..1046acf29 100644 --- a/test/fixtures/go/corpus/string-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/string-literals.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) { (TextElement) diff --git a/test/fixtures/go/corpus/string-literals.parseA.txt b/test/fixtures/go/corpus/string-literals.parseA.txt index f3a68c9c6..9f0a2a1b2 100644 --- a/test/fixtures/go/corpus/string-literals.parseA.txt +++ b/test/fixtures/go/corpus/string-literals.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (TextElement)) diff --git a/test/fixtures/go/corpus/string-literals.parseB.txt b/test/fixtures/go/corpus/string-literals.parseB.txt index f3a68c9c6..9f0a2a1b2 100644 --- a/test/fixtures/go/corpus/string-literals.parseB.txt +++ b/test/fixtures/go/corpus/string-literals.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (TextElement)) diff --git a/test/fixtures/go/corpus/struct-field-declarations.diffA-B.txt b/test/fixtures/go/corpus/struct-field-declarations.diffA-B.txt index ac17285aa..cbc6a9a3b 100644 --- a/test/fixtures/go/corpus/struct-field-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/struct-field-declarations.diffA-B.txt @@ -4,15 +4,15 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Constructor (Empty) (Field (Identifier) - ( + (Statements { (Identifier) ->(Identifier) } {+(Identifier)+}))))))) diff --git a/test/fixtures/go/corpus/struct-field-declarations.diffB-A.txt b/test/fixtures/go/corpus/struct-field-declarations.diffB-A.txt index 9dc3c0f9a..94db2fd9f 100644 --- a/test/fixtures/go/corpus/struct-field-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/struct-field-declarations.diffB-A.txt @@ -4,15 +4,15 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Constructor (Empty) (Field (Identifier) - ( + (Statements { (Identifier) ->(Identifier) } {-(Identifier)-}))))))) diff --git a/test/fixtures/go/corpus/struct-field-declarations.parseA.txt b/test/fixtures/go/corpus/struct-field-declarations.parseA.txt index ad90da591..405ca456d 100644 --- a/test/fixtures/go/corpus/struct-field-declarations.parseA.txt +++ b/test/fixtures/go/corpus/struct-field-declarations.parseA.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Constructor (Empty) (Field (Identifier) - ( + (Statements (Identifier)))))))) diff --git a/test/fixtures/go/corpus/struct-field-declarations.parseB.txt b/test/fixtures/go/corpus/struct-field-declarations.parseB.txt index 46a242423..42235b5b4 100644 --- a/test/fixtures/go/corpus/struct-field-declarations.parseB.txt +++ b/test/fixtures/go/corpus/struct-field-declarations.parseB.txt @@ -4,14 +4,14 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Type (Identifier) (Constructor (Empty) (Field (Identifier) - ( + (Statements (Identifier) (Identifier)))))))) diff --git a/test/fixtures/go/corpus/struct-literals.diffA-B.txt b/test/fixtures/go/corpus/struct-literals.diffA-B.txt index 5013d8da4..7b90f5a0e 100644 --- a/test/fixtures/go/corpus/struct-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/struct-literals.diffA-B.txt @@ -4,14 +4,14 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Composite { (Identifier) ->(Identifier) } - ( + (Statements (KeyValue (Identifier) (TextElement)) @@ -26,9 +26,9 @@ (Field { (Identifier) ->(Identifier) } - ( + (Statements (Identifier)))) - ( + (Statements (KeyValue { (Identifier) ->(Identifier) } @@ -41,4 +41,4 @@ (Identifier) { (Identifier) ->(Identifier) }) - ([])))))) + (Statements)))))) diff --git a/test/fixtures/go/corpus/struct-literals.diffB-A.txt b/test/fixtures/go/corpus/struct-literals.diffB-A.txt index 5013d8da4..7b90f5a0e 100644 --- a/test/fixtures/go/corpus/struct-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/struct-literals.diffB-A.txt @@ -4,14 +4,14 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Composite { (Identifier) ->(Identifier) } - ( + (Statements (KeyValue (Identifier) (TextElement)) @@ -26,9 +26,9 @@ (Field { (Identifier) ->(Identifier) } - ( + (Statements (Identifier)))) - ( + (Statements (KeyValue { (Identifier) ->(Identifier) } @@ -41,4 +41,4 @@ (Identifier) { (Identifier) ->(Identifier) }) - ([])))))) + (Statements)))))) diff --git a/test/fixtures/go/corpus/struct-literals.parseA.txt b/test/fixtures/go/corpus/struct-literals.parseA.txt index f2df790f7..e8f5c9e73 100644 --- a/test/fixtures/go/corpus/struct-literals.parseA.txt +++ b/test/fixtures/go/corpus/struct-literals.parseA.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Composite (Identifier) - ( + (Statements (KeyValue (Identifier) (TextElement)) @@ -24,9 +24,9 @@ (Empty) (Field (Identifier) - ( + (Statements (Identifier)))) - ( + (Statements (KeyValue (Identifier) (Integer))))) @@ -36,4 +36,4 @@ (MemberAccess (Identifier) (Identifier)) - ([])))))) + (Statements)))))) diff --git a/test/fixtures/go/corpus/struct-literals.parseB.txt b/test/fixtures/go/corpus/struct-literals.parseB.txt index f2df790f7..e8f5c9e73 100644 --- a/test/fixtures/go/corpus/struct-literals.parseB.txt +++ b/test/fixtures/go/corpus/struct-literals.parseB.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Identifier) (Composite (Identifier) - ( + (Statements (KeyValue (Identifier) (TextElement)) @@ -24,9 +24,9 @@ (Empty) (Field (Identifier) - ( + (Statements (Identifier)))) - ( + (Statements (KeyValue (Identifier) (Integer))))) @@ -36,4 +36,4 @@ (MemberAccess (Identifier) (Identifier)) - ([])))))) + (Statements)))))) diff --git a/test/fixtures/go/corpus/struct-types.diffA-B.txt b/test/fixtures/go/corpus/struct-types.diffA-B.txt index 91dc8b9bf..1861a7c71 100644 --- a/test/fixtures/go/corpus/struct-types.diffA-B.txt +++ b/test/fixtures/go/corpus/struct-types.diffA-B.txt @@ -4,16 +4,16 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type { (Identifier) ->(Identifier) } (Constructor (Empty) - ([])))) - ( + (Statements)))) + (Statements (Type { (Identifier) ->(Identifier) } @@ -21,8 +21,8 @@ (Empty) (Field (Identifier) - ([]))))) - ( + (Statements))))) + (Statements (Type { (Identifier) ->(Identifier) } @@ -30,23 +30,23 @@ (Empty) (Field (Identifier) - ( + (Statements (Identifier) (Identifier)))))) - ( + (Statements (Type { (Identifier) ->(Identifier) } (Constructor (Empty) - ( + (Statements (Field - ( + (Statements (MemberAccess (Identifier) (Identifier)))) (Field (Identifier) (TextElement) - ( + (Statements (Identifier)))))))))) diff --git a/test/fixtures/go/corpus/struct-types.diffB-A.txt b/test/fixtures/go/corpus/struct-types.diffB-A.txt index 91dc8b9bf..1861a7c71 100644 --- a/test/fixtures/go/corpus/struct-types.diffB-A.txt +++ b/test/fixtures/go/corpus/struct-types.diffB-A.txt @@ -4,16 +4,16 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type { (Identifier) ->(Identifier) } (Constructor (Empty) - ([])))) - ( + (Statements)))) + (Statements (Type { (Identifier) ->(Identifier) } @@ -21,8 +21,8 @@ (Empty) (Field (Identifier) - ([]))))) - ( + (Statements))))) + (Statements (Type { (Identifier) ->(Identifier) } @@ -30,23 +30,23 @@ (Empty) (Field (Identifier) - ( + (Statements (Identifier) (Identifier)))))) - ( + (Statements (Type { (Identifier) ->(Identifier) } (Constructor (Empty) - ( + (Statements (Field - ( + (Statements (MemberAccess (Identifier) (Identifier)))) (Field (Identifier) (TextElement) - ( + (Statements (Identifier)))))))))) diff --git a/test/fixtures/go/corpus/struct-types.parseA.txt b/test/fixtures/go/corpus/struct-types.parseA.txt index 992beeb54..7abd634c1 100644 --- a/test/fixtures/go/corpus/struct-types.parseA.txt +++ b/test/fixtures/go/corpus/struct-types.parseA.txt @@ -4,45 +4,45 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Constructor (Empty) - ([])))) - ( + (Statements)))) + (Statements (Type (Identifier) (Constructor (Empty) (Field (Identifier) - ([]))))) - ( + (Statements))))) + (Statements (Type (Identifier) (Constructor (Empty) (Field (Identifier) - ( + (Statements (Identifier) (Identifier)))))) - ( + (Statements (Type (Identifier) (Constructor (Empty) - ( + (Statements (Field - ( + (Statements (MemberAccess (Identifier) (Identifier)))) (Field (Identifier) (TextElement) - ( + (Statements (Identifier)))))))))) diff --git a/test/fixtures/go/corpus/struct-types.parseB.txt b/test/fixtures/go/corpus/struct-types.parseB.txt index 992beeb54..7abd634c1 100644 --- a/test/fixtures/go/corpus/struct-types.parseB.txt +++ b/test/fixtures/go/corpus/struct-types.parseB.txt @@ -4,45 +4,45 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Constructor (Empty) - ([])))) - ( + (Statements)))) + (Statements (Type (Identifier) (Constructor (Empty) (Field (Identifier) - ([]))))) - ( + (Statements))))) + (Statements (Type (Identifier) (Constructor (Empty) (Field (Identifier) - ( + (Statements (Identifier) (Identifier)))))) - ( + (Statements (Type (Identifier) (Constructor (Empty) - ( + (Statements (Field - ( + (Statements (MemberAccess (Identifier) (Identifier)))) (Field (Identifier) (TextElement) - ( + (Statements (Identifier)))))))))) diff --git a/test/fixtures/go/corpus/switch-statements.diffA-B.txt b/test/fixtures/go/corpus/switch-statements.diffA-B.txt index f64cd3be8..599316453 100644 --- a/test/fixtures/go/corpus/switch-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/switch-statements.diffA-B.txt @@ -4,10 +4,10 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Match - ([]) - ( + (Statements) + (Statements (Pattern (LessThan { (Identifier) @@ -16,7 +16,7 @@ ->(Identifier) }) (Call (Identifier) - ([]) + (Statements) (Empty))) {+(Pattern {+(LessThan @@ -24,7 +24,7 @@ {+(Identifier)+})+} {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+})+} {+(Pattern {+(Equal @@ -32,7 +32,7 @@ {+(Integer)+})+} {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+})+} {-(Pattern {-(LessThan @@ -42,7 +42,7 @@ {-(Comment)-} {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-})-})-} {-(Context {-(Comment)-} @@ -52,5 +52,5 @@ {-(Integer)-})-} {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-})-})-})))) diff --git a/test/fixtures/go/corpus/switch-statements.diffB-A.txt b/test/fixtures/go/corpus/switch-statements.diffB-A.txt index bb02af14b..99347a9a8 100644 --- a/test/fixtures/go/corpus/switch-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/switch-statements.diffB-A.txt @@ -4,10 +4,10 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Match - ([]) - ( + (Statements) + (Statements (Pattern (LessThan { (Identifier) @@ -16,7 +16,7 @@ ->(Identifier) }) (Call (Identifier) - ([]) + (Statements) (Empty))) {+(Pattern {+(LessThan @@ -26,7 +26,7 @@ {+(Comment)+} {+(Call {+(Identifier)+} - {+([])+} + {+(Statements)+} {+(Empty)+})+})+})+} {+(Context {+(Comment)+} @@ -40,7 +40,7 @@ (Call { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty))))+} {-(Pattern {-(Equal @@ -48,5 +48,5 @@ {-(Integer)-})-} {-(Call {-(Identifier)-} - {-([])-} + {-(Statements)-} {-(Empty)-})-})-})))) diff --git a/test/fixtures/go/corpus/switch-statements.parseA.txt b/test/fixtures/go/corpus/switch-statements.parseA.txt index 987e3b538..ecd260c88 100644 --- a/test/fixtures/go/corpus/switch-statements.parseA.txt +++ b/test/fixtures/go/corpus/switch-statements.parseA.txt @@ -4,17 +4,17 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Match - ([]) - ( + (Statements) + (Statements (Pattern (LessThan (Identifier) (Identifier)) (Call (Identifier) - ([]) + (Statements) (Empty))) (Pattern (LessThan @@ -24,7 +24,7 @@ (Comment) (Call (Identifier) - ([]) + (Statements) (Empty)))) (Context (Comment) @@ -34,5 +34,5 @@ (Integer)) (Call (Identifier) - ([]) + (Statements) (Empty)))))))) diff --git a/test/fixtures/go/corpus/switch-statements.parseB.txt b/test/fixtures/go/corpus/switch-statements.parseB.txt index bc7b21c50..5b18abbb1 100644 --- a/test/fixtures/go/corpus/switch-statements.parseB.txt +++ b/test/fixtures/go/corpus/switch-statements.parseB.txt @@ -4,17 +4,17 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Match - ([]) - ( + (Statements) + (Statements (Pattern (LessThan (Identifier) (Identifier)) (Call (Identifier) - ([]) + (Statements) (Empty))) (Pattern (LessThan @@ -22,7 +22,7 @@ (Identifier)) (Call (Identifier) - ([]) + (Statements) (Empty))) (Pattern (Equal @@ -30,5 +30,5 @@ (Integer)) (Call (Identifier) - ([]) + (Statements) (Empty))))))) diff --git a/test/fixtures/go/corpus/type-aliases.diffA-B.txt b/test/fixtures/go/corpus/type-aliases.diffA-B.txt index 880222665..8e8ad3ef7 100644 --- a/test/fixtures/go/corpus/type-aliases.diffA-B.txt +++ b/test/fixtures/go/corpus/type-aliases.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (TypeAlias { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/type-aliases.diffB-A.txt b/test/fixtures/go/corpus/type-aliases.diffB-A.txt index 880222665..8e8ad3ef7 100644 --- a/test/fixtures/go/corpus/type-aliases.diffB-A.txt +++ b/test/fixtures/go/corpus/type-aliases.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (TypeAlias { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/type-aliases.parseA.txt b/test/fixtures/go/corpus/type-aliases.parseA.txt index 93e9fca3c..a8036faee 100644 --- a/test/fixtures/go/corpus/type-aliases.parseA.txt +++ b/test/fixtures/go/corpus/type-aliases.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (TypeAlias (Identifier) (Slice diff --git a/test/fixtures/go/corpus/type-aliases.parseB.txt b/test/fixtures/go/corpus/type-aliases.parseB.txt index 93e9fca3c..a8036faee 100644 --- a/test/fixtures/go/corpus/type-aliases.parseB.txt +++ b/test/fixtures/go/corpus/type-aliases.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (TypeAlias (Identifier) (Slice diff --git a/test/fixtures/go/corpus/type-assertion-expressions.diffA-B.txt b/test/fixtures/go/corpus/type-assertion-expressions.diffA-B.txt index 147c06c4d..55b905eb6 100644 --- a/test/fixtures/go/corpus/type-assertion-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/type-assertion-expressions.diffA-B.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (TypeAssertion { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/type-assertion-expressions.diffB-A.txt b/test/fixtures/go/corpus/type-assertion-expressions.diffB-A.txt index 147c06c4d..55b905eb6 100644 --- a/test/fixtures/go/corpus/type-assertion-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/type-assertion-expressions.diffB-A.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (TypeAssertion { (Identifier) ->(Identifier) } diff --git a/test/fixtures/go/corpus/type-assertion-expressions.parseA.txt b/test/fixtures/go/corpus/type-assertion-expressions.parseA.txt index 258a6ee23..2b9a80548 100644 --- a/test/fixtures/go/corpus/type-assertion-expressions.parseA.txt +++ b/test/fixtures/go/corpus/type-assertion-expressions.parseA.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (TypeAssertion (Identifier) (MemberAccess diff --git a/test/fixtures/go/corpus/type-assertion-expressions.parseB.txt b/test/fixtures/go/corpus/type-assertion-expressions.parseB.txt index 258a6ee23..2b9a80548 100644 --- a/test/fixtures/go/corpus/type-assertion-expressions.parseB.txt +++ b/test/fixtures/go/corpus/type-assertion-expressions.parseB.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (TypeAssertion (Identifier) (MemberAccess diff --git a/test/fixtures/go/corpus/type-conversion-expressions.diffA-B.txt b/test/fixtures/go/corpus/type-conversion-expressions.diffA-B.txt index 842fc63b1..bf3f4ef5a 100644 --- a/test/fixtures/go/corpus/type-conversion-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/type-conversion-expressions.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Pointer (Call (Identifier) @@ -31,27 +31,27 @@ ->(Identifier) }) (TypeConversion (Function - ([]) + (Statements) (Empty)) { (Identifier) ->(Identifier) }) (TypeConversion (Parenthesized (Function - ([]) + (Statements) (Empty))) { (Identifier) ->(Identifier) }) (TypeConversion (Parenthesized (Function - ([]) + (Statements) (Identifier))) { (Identifier) ->(Identifier) }) (TypeConversion (Function - ([]) + (Statements) (Identifier)) { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/go/corpus/type-conversion-expressions.diffB-A.txt b/test/fixtures/go/corpus/type-conversion-expressions.diffB-A.txt index 842fc63b1..bf3f4ef5a 100644 --- a/test/fixtures/go/corpus/type-conversion-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/type-conversion-expressions.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Pointer (Call (Identifier) @@ -31,27 +31,27 @@ ->(Identifier) }) (TypeConversion (Function - ([]) + (Statements) (Empty)) { (Identifier) ->(Identifier) }) (TypeConversion (Parenthesized (Function - ([]) + (Statements) (Empty))) { (Identifier) ->(Identifier) }) (TypeConversion (Parenthesized (Function - ([]) + (Statements) (Identifier))) { (Identifier) ->(Identifier) }) (TypeConversion (Function - ([]) + (Statements) (Identifier)) { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/go/corpus/type-conversion-expressions.parseA.txt b/test/fixtures/go/corpus/type-conversion-expressions.parseA.txt index 65591da46..5d85a36ae 100644 --- a/test/fixtures/go/corpus/type-conversion-expressions.parseA.txt +++ b/test/fixtures/go/corpus/type-conversion-expressions.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Pointer (Call (Identifier) @@ -27,24 +27,24 @@ (Identifier)) (TypeConversion (Function - ([]) + (Statements) (Empty)) (Identifier)) (TypeConversion (Parenthesized (Function - ([]) + (Statements) (Empty))) (Identifier)) (TypeConversion (Parenthesized (Function - ([]) + (Statements) (Identifier))) (Identifier)) (TypeConversion (Function - ([]) + (Statements) (Identifier)) (Identifier)) (TypeConversion diff --git a/test/fixtures/go/corpus/type-conversion-expressions.parseB.txt b/test/fixtures/go/corpus/type-conversion-expressions.parseB.txt index 65591da46..5d85a36ae 100644 --- a/test/fixtures/go/corpus/type-conversion-expressions.parseB.txt +++ b/test/fixtures/go/corpus/type-conversion-expressions.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Pointer (Call (Identifier) @@ -27,24 +27,24 @@ (Identifier)) (TypeConversion (Function - ([]) + (Statements) (Empty)) (Identifier)) (TypeConversion (Parenthesized (Function - ([]) + (Statements) (Empty))) (Identifier)) (TypeConversion (Parenthesized (Function - ([]) + (Statements) (Identifier))) (Identifier)) (TypeConversion (Function - ([]) + (Statements) (Identifier)) (Identifier)) (TypeConversion diff --git a/test/fixtures/go/corpus/type-declarations.diffA-B.txt b/test/fixtures/go/corpus/type-declarations.diffA-B.txt index 49febe748..5b29285f2 100644 --- a/test/fixtures/go/corpus/type-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/type-declarations.diffA-B.txt @@ -4,15 +4,15 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) })) - ( + (Statements (Type { (Identifier) ->(Identifier) } @@ -23,7 +23,7 @@ ->(Identifier) } { (Identifier) ->(Identifier) })) - ( + (Statements (Context (Comment) (Type @@ -31,24 +31,24 @@ ->(Identifier) } (Constructor (Empty) - ( + (Statements (Field (Identifier) - ( + (Statements (Identifier))) (Field (Identifier) - ( + (Statements (Identifier))) (Field (Identifier) - ( + (Statements (Identifier))))))) (Type { (Identifier) ->(Identifier) } (Interface - ([]))) + (Statements))) (Context (Comment) (Empty)))))) diff --git a/test/fixtures/go/corpus/type-declarations.diffB-A.txt b/test/fixtures/go/corpus/type-declarations.diffB-A.txt index 49febe748..5b29285f2 100644 --- a/test/fixtures/go/corpus/type-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/type-declarations.diffB-A.txt @@ -4,15 +4,15 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) })) - ( + (Statements (Type { (Identifier) ->(Identifier) } @@ -23,7 +23,7 @@ ->(Identifier) } { (Identifier) ->(Identifier) })) - ( + (Statements (Context (Comment) (Type @@ -31,24 +31,24 @@ ->(Identifier) } (Constructor (Empty) - ( + (Statements (Field (Identifier) - ( + (Statements (Identifier))) (Field (Identifier) - ( + (Statements (Identifier))) (Field (Identifier) - ( + (Statements (Identifier))))))) (Type { (Identifier) ->(Identifier) } (Interface - ([]))) + (Statements))) (Context (Comment) (Empty)))))) diff --git a/test/fixtures/go/corpus/type-declarations.parseA.txt b/test/fixtures/go/corpus/type-declarations.parseA.txt index e663d8172..48b9b35ed 100644 --- a/test/fixtures/go/corpus/type-declarations.parseA.txt +++ b/test/fixtures/go/corpus/type-declarations.parseA.txt @@ -4,43 +4,43 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Identifier))) - ( + (Statements (Type (Identifier) (Identifier)) (Type (Identifier) (Identifier))) - ( + (Statements (Context (Comment) (Type (Identifier) (Constructor (Empty) - ( + (Statements (Field (Identifier) - ( + (Statements (Identifier))) (Field (Identifier) - ( + (Statements (Identifier))) (Field (Identifier) - ( + (Statements (Identifier))))))) (Type (Identifier) (Interface - ([]))) + (Statements))) (Context (Comment) (Empty)))))) diff --git a/test/fixtures/go/corpus/type-declarations.parseB.txt b/test/fixtures/go/corpus/type-declarations.parseB.txt index e663d8172..48b9b35ed 100644 --- a/test/fixtures/go/corpus/type-declarations.parseB.txt +++ b/test/fixtures/go/corpus/type-declarations.parseB.txt @@ -4,43 +4,43 @@ (Function (Empty) (Identifier) - ([]) - ( - ( + (Statements) + (Statements + (Statements (Type (Identifier) (Identifier))) - ( + (Statements (Type (Identifier) (Identifier)) (Type (Identifier) (Identifier))) - ( + (Statements (Context (Comment) (Type (Identifier) (Constructor (Empty) - ( + (Statements (Field (Identifier) - ( + (Statements (Identifier))) (Field (Identifier) - ( + (Statements (Identifier))) (Field (Identifier) - ( + (Statements (Identifier))))))) (Type (Identifier) (Interface - ([]))) + (Statements))) (Context (Comment) (Empty)))))) diff --git a/test/fixtures/go/corpus/type-switch-statements.diffA-B.txt b/test/fixtures/go/corpus/type-switch-statements.diffA-B.txt index 4eb71a89b..f4e2d27ae 100644 --- a/test/fixtures/go/corpus/type-switch-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/type-switch-statements.diffA-B.txt @@ -4,10 +4,10 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (TypeSwitch - ( + (Statements (Assignment { (Identifier) ->(Identifier) } @@ -16,15 +16,15 @@ (TypeSwitchGuard { (Identifier) ->(Identifier) })) - ( + (Statements (Pattern - ( + (Statements (Identifier) (Pointer (MemberAccess (Identifier) (Identifier)))) - ([])) + (Statements)) (Context (Comment) (Pattern @@ -32,7 +32,7 @@ (Identifier)) (Call (Identifier) - ([]) + (Statements) (Empty)))) (Pattern (Pointer @@ -41,18 +41,18 @@ (Empty))) {+(Pattern {+(DefaultPattern - {+([])+})+} + {+(Statements)+})+} {+(Break {+(Empty)+})+})+})) (TypeSwitch - ( + (Statements (TypeSwitchGuard - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }))) - ( + (Statements (Pattern { (Identifier) ->(Identifier) } @@ -60,7 +60,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements { (TextElement) ->(TextElement) } { (Times @@ -77,7 +77,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements { (TextElement) ->(TextElement) } { (DividedBy @@ -89,7 +89,7 @@ (Empty))) (Pattern (Identifier) - ( + (Statements (Assignment { (Identifier) ->(Identifier) } @@ -104,7 +104,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements (TextElement) (Plus (Slice @@ -124,13 +124,13 @@ (Empty)))) (Pattern (DefaultPattern - ([])) - ([])))) + (Statements)) + (Statements)))) (TypeSwitch (Empty) - ( + (Statements (TypeSwitchGuard - ( + (Statements (Identifier) { (Identifier) ->(Identifier) })) diff --git a/test/fixtures/go/corpus/type-switch-statements.diffB-A.txt b/test/fixtures/go/corpus/type-switch-statements.diffB-A.txt index 5a6bda542..cfb3afcfd 100644 --- a/test/fixtures/go/corpus/type-switch-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/type-switch-statements.diffB-A.txt @@ -4,10 +4,10 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (TypeSwitch - ( + (Statements (Assignment { (Identifier) ->(Identifier) } @@ -16,15 +16,15 @@ (TypeSwitchGuard { (Identifier) ->(Identifier) })) - ( + (Statements (Pattern - ( + (Statements (Identifier) (Pointer (MemberAccess (Identifier) (Identifier)))) - ([])) + (Statements)) (Context (Comment) (Pattern @@ -32,7 +32,7 @@ (Identifier)) (Call (Identifier) - ([]) + (Statements) (Empty)))) (Pattern (Pointer @@ -41,18 +41,18 @@ (Empty))) {-(Pattern {-(DefaultPattern - {-([])-})-} + {-(Statements)-})-} {-(Break {-(Empty)-})-})-})) (TypeSwitch - ( + (Statements (TypeSwitchGuard - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }))) - ( + (Statements (Pattern { (Identifier) ->(Identifier) } @@ -60,7 +60,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements { (TextElement) ->(TextElement) } { (DividedBy @@ -77,7 +77,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements { (TextElement) ->(TextElement) } { (Times @@ -89,7 +89,7 @@ (Empty))) (Pattern (Identifier) - ( + (Statements (Assignment { (Identifier) ->(Identifier) } @@ -104,7 +104,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements (TextElement) (Plus (Slice @@ -124,13 +124,13 @@ (Empty)))) (Pattern (DefaultPattern - ([])) - ([])))) + (Statements)) + (Statements)))) (TypeSwitch (Empty) - ( + (Statements (TypeSwitchGuard - ( + (Statements (Identifier) { (Identifier) ->(Identifier) })) diff --git a/test/fixtures/go/corpus/type-switch-statements.parseA.txt b/test/fixtures/go/corpus/type-switch-statements.parseA.txt index 95bb86176..e3d29707a 100644 --- a/test/fixtures/go/corpus/type-switch-statements.parseA.txt +++ b/test/fixtures/go/corpus/type-switch-statements.parseA.txt @@ -4,24 +4,24 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (TypeSwitch - ( + (Statements (Assignment (Identifier) (Identifier)) (TypeSwitchGuard (Identifier))) - ( + (Statements (Pattern - ( + (Statements (Identifier) (Pointer (MemberAccess (Identifier) (Identifier)))) - ([])) + (Statements)) (Context (Comment) (Pattern @@ -29,7 +29,7 @@ (Identifier)) (Call (Identifier) - ([]) + (Statements) (Empty)))) (Pattern (Pointer @@ -37,19 +37,19 @@ (Break (Empty))))) (TypeSwitch - ( + (Statements (TypeSwitchGuard - ( + (Statements (Identifier) (Identifier)))) - ( + (Statements (Pattern (Identifier) (Call (MemberAccess (Identifier) (Identifier)) - ( + (Statements (TextElement) (Times (Identifier) @@ -61,7 +61,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements (TextElement) (DividedBy (Integer) @@ -69,7 +69,7 @@ (Empty))) (Pattern (Identifier) - ( + (Statements (Assignment (Identifier) (DividedBy @@ -82,7 +82,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements (TextElement) (Plus (Slice @@ -98,13 +98,13 @@ (Empty)))) (Pattern (DefaultPattern - ([])) - ([])))) + (Statements)) + (Statements)))) (TypeSwitch (Empty) - ( + (Statements (TypeSwitchGuard - ( + (Statements (Identifier) (Identifier))) (Context diff --git a/test/fixtures/go/corpus/type-switch-statements.parseB.txt b/test/fixtures/go/corpus/type-switch-statements.parseB.txt index 765e00fee..28ff0d9fa 100644 --- a/test/fixtures/go/corpus/type-switch-statements.parseB.txt +++ b/test/fixtures/go/corpus/type-switch-statements.parseB.txt @@ -4,24 +4,24 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (TypeSwitch - ( + (Statements (Assignment (Identifier) (Identifier)) (TypeSwitchGuard (Identifier))) - ( + (Statements (Pattern - ( + (Statements (Identifier) (Pointer (MemberAccess (Identifier) (Identifier)))) - ([])) + (Statements)) (Context (Comment) (Pattern @@ -29,7 +29,7 @@ (Identifier)) (Call (Identifier) - ([]) + (Statements) (Empty)))) (Pattern (Pointer @@ -38,23 +38,23 @@ (Empty))) (Pattern (DefaultPattern - ([])) + (Statements)) (Break (Empty))))) (TypeSwitch - ( + (Statements (TypeSwitchGuard - ( + (Statements (Identifier) (Identifier)))) - ( + (Statements (Pattern (Identifier) (Call (MemberAccess (Identifier) (Identifier)) - ( + (Statements (TextElement) (DividedBy (Integer) @@ -66,7 +66,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements (TextElement) (Times (Identifier) @@ -74,7 +74,7 @@ (Empty))) (Pattern (Identifier) - ( + (Statements (Assignment (Identifier) (DividedBy @@ -87,7 +87,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements (TextElement) (Plus (Slice @@ -103,13 +103,13 @@ (Empty)))) (Pattern (DefaultPattern - ([])) - ([])))) + (Statements)) + (Statements)))) (TypeSwitch (Empty) - ( + (Statements (TypeSwitchGuard - ( + (Statements (Identifier) (Identifier))) (Context diff --git a/test/fixtures/go/corpus/unary-expressions.diffA-B.txt b/test/fixtures/go/corpus/unary-expressions.diffA-B.txt index 755b66ffd..6aab2877a 100644 --- a/test/fixtures/go/corpus/unary-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/unary-expressions.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements { (Identifier) ->(Identifier) } (Negate @@ -19,7 +19,7 @@ (Call { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty))) (Complement { (Identifier) diff --git a/test/fixtures/go/corpus/unary-expressions.diffB-A.txt b/test/fixtures/go/corpus/unary-expressions.diffB-A.txt index 755b66ffd..6aab2877a 100644 --- a/test/fixtures/go/corpus/unary-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/unary-expressions.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements { (Identifier) ->(Identifier) } (Negate @@ -19,7 +19,7 @@ (Call { (Identifier) ->(Identifier) } - ([]) + (Statements) (Empty))) (Complement { (Identifier) diff --git a/test/fixtures/go/corpus/unary-expressions.parseA.txt b/test/fixtures/go/corpus/unary-expressions.parseA.txt index 9d88c4f54..a2e7539b7 100644 --- a/test/fixtures/go/corpus/unary-expressions.parseA.txt +++ b/test/fixtures/go/corpus/unary-expressions.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Identifier) (Negate (Identifier)) @@ -15,7 +15,7 @@ (Pointer (Call (Identifier) - ([]) + (Statements) (Empty))) (Complement (Identifier)) diff --git a/test/fixtures/go/corpus/unary-expressions.parseB.txt b/test/fixtures/go/corpus/unary-expressions.parseB.txt index 9d88c4f54..a2e7539b7 100644 --- a/test/fixtures/go/corpus/unary-expressions.parseB.txt +++ b/test/fixtures/go/corpus/unary-expressions.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Identifier) (Negate (Identifier)) @@ -15,7 +15,7 @@ (Pointer (Call (Identifier) - ([]) + (Statements) (Empty))) (Complement (Identifier)) diff --git a/test/fixtures/go/corpus/var-declarations-with-no-expressions.diffA-B.txt b/test/fixtures/go/corpus/var-declarations-with-no-expressions.diffA-B.txt index ea0b92855..be19067c9 100644 --- a/test/fixtures/go/corpus/var-declarations-with-no-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/var-declarations-with-no-expressions.diffA-B.txt @@ -4,21 +4,21 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Annotation - ( + (Statements { (Identifier) ->(Identifier) }) (Identifier)) - ([])) + (Statements)) (Assignment (Annotation - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) (Identifier)) - ([]))))) + (Statements))))) diff --git a/test/fixtures/go/corpus/var-declarations-with-no-expressions.diffB-A.txt b/test/fixtures/go/corpus/var-declarations-with-no-expressions.diffB-A.txt index ea0b92855..be19067c9 100644 --- a/test/fixtures/go/corpus/var-declarations-with-no-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/var-declarations-with-no-expressions.diffB-A.txt @@ -4,21 +4,21 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Annotation - ( + (Statements { (Identifier) ->(Identifier) }) (Identifier)) - ([])) + (Statements)) (Assignment (Annotation - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) (Identifier)) - ([]))))) + (Statements))))) diff --git a/test/fixtures/go/corpus/var-declarations-with-no-expressions.parseA.txt b/test/fixtures/go/corpus/var-declarations-with-no-expressions.parseA.txt index 7fa95fd6b..11418eaae 100644 --- a/test/fixtures/go/corpus/var-declarations-with-no-expressions.parseA.txt +++ b/test/fixtures/go/corpus/var-declarations-with-no-expressions.parseA.txt @@ -4,18 +4,18 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Annotation - ( + (Statements (Identifier)) (Identifier)) - ([])) + (Statements)) (Assignment (Annotation - ( + (Statements (Identifier) (Identifier)) (Identifier)) - ([]))))) + (Statements))))) diff --git a/test/fixtures/go/corpus/var-declarations-with-no-expressions.parseB.txt b/test/fixtures/go/corpus/var-declarations-with-no-expressions.parseB.txt index 7fa95fd6b..11418eaae 100644 --- a/test/fixtures/go/corpus/var-declarations-with-no-expressions.parseB.txt +++ b/test/fixtures/go/corpus/var-declarations-with-no-expressions.parseB.txt @@ -4,18 +4,18 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Annotation - ( + (Statements (Identifier)) (Identifier)) - ([])) + (Statements)) (Assignment (Annotation - ( + (Statements (Identifier) (Identifier)) (Identifier)) - ([]))))) + (Statements))))) diff --git a/test/fixtures/go/corpus/var-declarations-with-types.diffA-B.txt b/test/fixtures/go/corpus/var-declarations-with-types.diffA-B.txt index aee121c85..a54f8d86c 100644 --- a/test/fixtures/go/corpus/var-declarations-with-types.diffA-B.txt +++ b/test/fixtures/go/corpus/var-declarations-with-types.diffA-B.txt @@ -4,23 +4,23 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Annotation - ( + (Statements { (Identifier) ->(Identifier) }) (Identifier)) (Integer)) (Assignment (Annotation - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) (Identifier)) - ( + (Statements (Integer) (Integer)))))) diff --git a/test/fixtures/go/corpus/var-declarations-with-types.diffB-A.txt b/test/fixtures/go/corpus/var-declarations-with-types.diffB-A.txt index aee121c85..a54f8d86c 100644 --- a/test/fixtures/go/corpus/var-declarations-with-types.diffB-A.txt +++ b/test/fixtures/go/corpus/var-declarations-with-types.diffB-A.txt @@ -4,23 +4,23 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Annotation - ( + (Statements { (Identifier) ->(Identifier) }) (Identifier)) (Integer)) (Assignment (Annotation - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) }) (Identifier)) - ( + (Statements (Integer) (Integer)))))) diff --git a/test/fixtures/go/corpus/var-declarations-with-types.parseA.txt b/test/fixtures/go/corpus/var-declarations-with-types.parseA.txt index abf186d40..9118982be 100644 --- a/test/fixtures/go/corpus/var-declarations-with-types.parseA.txt +++ b/test/fixtures/go/corpus/var-declarations-with-types.parseA.txt @@ -4,20 +4,20 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Annotation - ( + (Statements (Identifier)) (Identifier)) (Integer)) (Assignment (Annotation - ( + (Statements (Identifier) (Identifier)) (Identifier)) - ( + (Statements (Integer) (Integer)))))) diff --git a/test/fixtures/go/corpus/var-declarations-with-types.parseB.txt b/test/fixtures/go/corpus/var-declarations-with-types.parseB.txt index abf186d40..9118982be 100644 --- a/test/fixtures/go/corpus/var-declarations-with-types.parseB.txt +++ b/test/fixtures/go/corpus/var-declarations-with-types.parseB.txt @@ -4,20 +4,20 @@ (Function (Empty) (Identifier) - ([]) - ( + (Statements) + (Statements (Assignment (Annotation - ( + (Statements (Identifier)) (Identifier)) (Integer)) (Assignment (Annotation - ( + (Statements (Identifier) (Identifier)) (Identifier)) - ( + (Statements (Integer) (Integer)))))) diff --git a/test/fixtures/go/corpus/var-declarations-without-types.diffA-B.txt b/test/fixtures/go/corpus/var-declarations-without-types.diffA-B.txt index e1320a947..2d984aebb 100644 --- a/test/fixtures/go/corpus/var-declarations-without-types.diffA-B.txt +++ b/test/fixtures/go/corpus/var-declarations-without-types.diffA-B.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment { (Identifier) - ->( + ->(Statements {+(Identifier)+} {+(Identifier)+}) } { (Integer) - ->( + ->(Statements {+(Integer)+} {+(Integer)+}) }))) diff --git a/test/fixtures/go/corpus/var-declarations-without-types.diffB-A.txt b/test/fixtures/go/corpus/var-declarations-without-types.diffB-A.txt index 6d0e73d9d..06f1fa789 100644 --- a/test/fixtures/go/corpus/var-declarations-without-types.diffB-A.txt +++ b/test/fixtures/go/corpus/var-declarations-without-types.diffB-A.txt @@ -4,13 +4,13 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment - { ( + { (Statements {-(Identifier)-} {-(Identifier)-}) ->(Identifier) } - { ( + { (Statements {-(Integer)-} {-(Integer)-}) ->(Integer) }))) diff --git a/test/fixtures/go/corpus/var-declarations-without-types.parseA.txt b/test/fixtures/go/corpus/var-declarations-without-types.parseA.txt index 9d343e9ba..d49580f45 100644 --- a/test/fixtures/go/corpus/var-declarations-without-types.parseA.txt +++ b/test/fixtures/go/corpus/var-declarations-without-types.parseA.txt @@ -4,7 +4,7 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment (Identifier) (Integer)))) diff --git a/test/fixtures/go/corpus/var-declarations-without-types.parseB.txt b/test/fixtures/go/corpus/var-declarations-without-types.parseB.txt index ac7eb7599..bbacb990a 100644 --- a/test/fixtures/go/corpus/var-declarations-without-types.parseB.txt +++ b/test/fixtures/go/corpus/var-declarations-without-types.parseB.txt @@ -4,11 +4,11 @@ (Function (Empty) (Identifier) - ([]) + (Statements) (Assignment - ( + (Statements (Identifier) (Identifier)) - ( + (Statements (Integer) (Integer))))) diff --git a/test/fixtures/go/corpus/variadic-function-declarations.diffA-B.txt b/test/fixtures/go/corpus/variadic-function-declarations.diffA-B.txt index 55d85d88f..06b29737e 100644 --- a/test/fixtures/go/corpus/variadic-function-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/variadic-function-declarations.diffA-B.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) { (Identifier) @@ -14,7 +14,7 @@ (Pointer (Identifier)) (Identifier)) - ([])) + (Statements)) (Function (Empty) { (Identifier) @@ -22,15 +22,15 @@ (Variadic (Identifier) (Empty)) - ([])) + (Statements)) (Function (Empty) { (Identifier) ->(Identifier) } - ( - ( + (Statements + (Statements (Identifier)) (Variadic (Identifier) (Empty))) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/variadic-function-declarations.diffB-A.txt b/test/fixtures/go/corpus/variadic-function-declarations.diffB-A.txt index 55d85d88f..06b29737e 100644 --- a/test/fixtures/go/corpus/variadic-function-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/variadic-function-declarations.diffB-A.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) { (Identifier) @@ -14,7 +14,7 @@ (Pointer (Identifier)) (Identifier)) - ([])) + (Statements)) (Function (Empty) { (Identifier) @@ -22,15 +22,15 @@ (Variadic (Identifier) (Empty)) - ([])) + (Statements)) (Function (Empty) { (Identifier) ->(Identifier) } - ( - ( + (Statements + (Statements (Identifier)) (Variadic (Identifier) (Empty))) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/variadic-function-declarations.parseA.txt b/test/fixtures/go/corpus/variadic-function-declarations.parseA.txt index a19e52973..0ab7e414e 100644 --- a/test/fixtures/go/corpus/variadic-function-declarations.parseA.txt +++ b/test/fixtures/go/corpus/variadic-function-declarations.parseA.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) (Identifier) @@ -13,21 +13,21 @@ (Pointer (Identifier)) (Identifier)) - ([])) + (Statements)) (Function (Empty) (Identifier) (Variadic (Identifier) (Empty)) - ([])) + (Statements)) (Function (Empty) (Identifier) - ( - ( + (Statements + (Statements (Identifier)) (Variadic (Identifier) (Empty))) - ([]))) + (Statements))) diff --git a/test/fixtures/go/corpus/variadic-function-declarations.parseB.txt b/test/fixtures/go/corpus/variadic-function-declarations.parseB.txt index a19e52973..0ab7e414e 100644 --- a/test/fixtures/go/corpus/variadic-function-declarations.parseB.txt +++ b/test/fixtures/go/corpus/variadic-function-declarations.parseB.txt @@ -4,8 +4,8 @@ (Function (Empty) (Identifier) - ([]) - ([])) + (Statements) + (Statements)) (Function (Empty) (Identifier) @@ -13,21 +13,21 @@ (Pointer (Identifier)) (Identifier)) - ([])) + (Statements)) (Function (Empty) (Identifier) (Variadic (Identifier) (Empty)) - ([])) + (Statements)) (Function (Empty) (Identifier) - ( - ( + (Statements + (Statements (Identifier)) (Variadic (Identifier) (Empty))) - ([]))) + (Statements))) diff --git a/test/fixtures/javascript/corpus/anonymous-function.diffA-B.txt b/test/fixtures/javascript/corpus/anonymous-function.diffA-B.txt index 7d647cf4c..a413f45aa 100644 --- a/test/fixtures/javascript/corpus/anonymous-function.diffA-B.txt +++ b/test/fixtures/javascript/corpus/anonymous-function.diffA-B.txt @@ -24,7 +24,7 @@ {+(Assignment {+(Identifier)+} {+(Empty)+})+})+} - ( + (Statements (Return { (Plus {-(Identifier)-} diff --git a/test/fixtures/javascript/corpus/anonymous-function.diffB-A.txt b/test/fixtures/javascript/corpus/anonymous-function.diffB-A.txt index 378fb36fa..14e2117e6 100644 --- a/test/fixtures/javascript/corpus/anonymous-function.diffB-A.txt +++ b/test/fixtures/javascript/corpus/anonymous-function.diffB-A.txt @@ -24,7 +24,7 @@ {-(Assignment {-(Identifier)-} {-(Empty)-})-})-} - ( + (Statements (Return { (Times {-(Identifier)-} diff --git a/test/fixtures/javascript/corpus/anonymous-function.parseA.txt b/test/fixtures/javascript/corpus/anonymous-function.parseA.txt index b16aad149..410fa0126 100644 --- a/test/fixtures/javascript/corpus/anonymous-function.parseA.txt +++ b/test/fixtures/javascript/corpus/anonymous-function.parseA.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Plus (Identifier) diff --git a/test/fixtures/javascript/corpus/anonymous-function.parseB.txt b/test/fixtures/javascript/corpus/anonymous-function.parseB.txt index a04c5cd22..f4cf6bbd8 100644 --- a/test/fixtures/javascript/corpus/anonymous-function.parseB.txt +++ b/test/fixtures/javascript/corpus/anonymous-function.parseB.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Times (Identifier) diff --git a/test/fixtures/javascript/corpus/anonymous-parameterless-function.diffA-B.txt b/test/fixtures/javascript/corpus/anonymous-parameterless-function.diffA-B.txt index b2b1fd3d9..33fc55d49 100644 --- a/test/fixtures/javascript/corpus/anonymous-parameterless-function.diffA-B.txt +++ b/test/fixtures/javascript/corpus/anonymous-parameterless-function.diffA-B.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Empty) - ( + (Statements (Return { (TextElement) ->(TextElement) })))) diff --git a/test/fixtures/javascript/corpus/anonymous-parameterless-function.diffB-A.txt b/test/fixtures/javascript/corpus/anonymous-parameterless-function.diffB-A.txt index b2b1fd3d9..33fc55d49 100644 --- a/test/fixtures/javascript/corpus/anonymous-parameterless-function.diffB-A.txt +++ b/test/fixtures/javascript/corpus/anonymous-parameterless-function.diffB-A.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Empty) - ( + (Statements (Return { (TextElement) ->(TextElement) })))) diff --git a/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseA.txt b/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseA.txt index 84537c07d..bb24b8ce4 100644 --- a/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseA.txt +++ b/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseA.txt @@ -3,6 +3,6 @@ (Empty) (Empty) (Empty) - ( + (Statements (Return (TextElement))))) diff --git a/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseB.txt b/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseB.txt index 84537c07d..bb24b8ce4 100644 --- a/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseB.txt +++ b/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseB.txt @@ -3,6 +3,6 @@ (Empty) (Empty) (Empty) - ( + (Statements (Return (TextElement))))) diff --git a/test/fixtures/javascript/corpus/arrow-function.diffA-B.txt b/test/fixtures/javascript/corpus/arrow-function.diffA-B.txt index 1edf8182d..600b385ff 100644 --- a/test/fixtures/javascript/corpus/arrow-function.diffA-B.txt +++ b/test/fixtures/javascript/corpus/arrow-function.diffA-B.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return { (Identifier) ->(Identifier) })))) diff --git a/test/fixtures/javascript/corpus/arrow-function.diffB-A.txt b/test/fixtures/javascript/corpus/arrow-function.diffB-A.txt index 1edf8182d..600b385ff 100644 --- a/test/fixtures/javascript/corpus/arrow-function.diffB-A.txt +++ b/test/fixtures/javascript/corpus/arrow-function.diffB-A.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return { (Identifier) ->(Identifier) })))) diff --git a/test/fixtures/javascript/corpus/arrow-function.parseA.txt b/test/fixtures/javascript/corpus/arrow-function.parseA.txt index 1bced8e40..e178c9e7c 100644 --- a/test/fixtures/javascript/corpus/arrow-function.parseA.txt +++ b/test/fixtures/javascript/corpus/arrow-function.parseA.txt @@ -17,6 +17,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier))))) diff --git a/test/fixtures/javascript/corpus/arrow-function.parseB.txt b/test/fixtures/javascript/corpus/arrow-function.parseB.txt index 1bced8e40..e178c9e7c 100644 --- a/test/fixtures/javascript/corpus/arrow-function.parseB.txt +++ b/test/fixtures/javascript/corpus/arrow-function.parseB.txt @@ -17,6 +17,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier))))) diff --git a/test/fixtures/javascript/corpus/break.diffA-B.txt b/test/fixtures/javascript/corpus/break.diffA-B.txt index eff385027..46eb71902 100644 --- a/test/fixtures/javascript/corpus/break.diffA-B.txt +++ b/test/fixtures/javascript/corpus/break.diffA-B.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements {+(Continue {+(Empty)+})+} {-(Break diff --git a/test/fixtures/javascript/corpus/break.diffB-A.txt b/test/fixtures/javascript/corpus/break.diffB-A.txt index 745ef1761..44e6c7bdc 100644 --- a/test/fixtures/javascript/corpus/break.diffB-A.txt +++ b/test/fixtures/javascript/corpus/break.diffB-A.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements {+(Break {+(Empty)+})+} {-(Continue diff --git a/test/fixtures/javascript/corpus/break.parseA.txt b/test/fixtures/javascript/corpus/break.parseA.txt index e927cd94c..c0af1c973 100644 --- a/test/fixtures/javascript/corpus/break.parseA.txt +++ b/test/fixtures/javascript/corpus/break.parseA.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements (Break (Empty))) (Empty)) diff --git a/test/fixtures/javascript/corpus/break.parseB.txt b/test/fixtures/javascript/corpus/break.parseB.txt index 9618a22b5..0c30ef033 100644 --- a/test/fixtures/javascript/corpus/break.parseB.txt +++ b/test/fixtures/javascript/corpus/break.parseB.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements (Continue (Empty))) (Empty)) diff --git a/test/fixtures/javascript/corpus/chained-callbacks.diffA-B.txt b/test/fixtures/javascript/corpus/chained-callbacks.diffA-B.txt index f88bc58c9..ba36adf30 100644 --- a/test/fixtures/javascript/corpus/chained-callbacks.diffA-B.txt +++ b/test/fixtures/javascript/corpus/chained-callbacks.diffA-B.txt @@ -15,7 +15,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (MemberAccess { (Identifier) diff --git a/test/fixtures/javascript/corpus/chained-callbacks.diffB-A.txt b/test/fixtures/javascript/corpus/chained-callbacks.diffB-A.txt index f88bc58c9..ba36adf30 100644 --- a/test/fixtures/javascript/corpus/chained-callbacks.diffB-A.txt +++ b/test/fixtures/javascript/corpus/chained-callbacks.diffB-A.txt @@ -15,7 +15,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (MemberAccess { (Identifier) diff --git a/test/fixtures/javascript/corpus/chained-callbacks.parseA.txt b/test/fixtures/javascript/corpus/chained-callbacks.parseA.txt index f54ff9ba2..a6043e559 100644 --- a/test/fixtures/javascript/corpus/chained-callbacks.parseA.txt +++ b/test/fixtures/javascript/corpus/chained-callbacks.parseA.txt @@ -14,7 +14,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/chained-callbacks.parseB.txt b/test/fixtures/javascript/corpus/chained-callbacks.parseB.txt index f54ff9ba2..a6043e559 100644 --- a/test/fixtures/javascript/corpus/chained-callbacks.parseB.txt +++ b/test/fixtures/javascript/corpus/chained-callbacks.parseB.txt @@ -14,7 +14,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/class.diffA-B.txt b/test/fixtures/javascript/corpus/class.diffA-B.txt index 4d6f8621d..c1fd07f93 100644 --- a/test/fixtures/javascript/corpus/class.diffA-B.txt +++ b/test/fixtures/javascript/corpus/class.diffA-B.txt @@ -1,7 +1,7 @@ (Program (Class (Identifier) - ( + (Statements {+(Method {+(Empty)+} {+(Empty)+} @@ -16,7 +16,7 @@ {+(Assignment {+(Identifier)+} {+(Empty)+})+})+} - {+( + {+(Statements {+(Return {+(Identifier)+})+})+})+} {+(Method @@ -33,7 +33,7 @@ {+(Assignment {+(Identifier)+} {+(Empty)+})+})+} - {+( + {+(Statements {+(Return {+(Identifier)+})+})+})+} {+(Method @@ -50,7 +50,7 @@ {+(Assignment {+(Identifier)+} {+(Empty)+})+})+} - {+( + {+(Statements {+(Return {+(Identifier)+})+})+})+} {-(PublicFieldDefinition @@ -73,7 +73,7 @@ {-(Assignment {-(Identifier)-} {-(Empty)-})-})-} - {-( + {-(Statements {-(Return {-(Identifier)-})-})-})-} {-(Method @@ -90,7 +90,7 @@ {-(Assignment {-(Identifier)-} {-(Empty)-})-})-} - {-( + {-(Statements {-(Return {-(Identifier)-})-})-})-} {-(Method @@ -107,6 +107,6 @@ {-(Assignment {-(Identifier)-} {-(Empty)-})-})-} - {-( + {-(Statements {-(Return {-(Identifier)-})-})-})-}))) diff --git a/test/fixtures/javascript/corpus/class.diffB-A.txt b/test/fixtures/javascript/corpus/class.diffB-A.txt index 0ecccd650..f4214b7cc 100644 --- a/test/fixtures/javascript/corpus/class.diffB-A.txt +++ b/test/fixtures/javascript/corpus/class.diffB-A.txt @@ -1,7 +1,7 @@ (Program (Class (Identifier) - ( + (Statements {+(PublicFieldDefinition {+(Empty)+} {+(Empty)+} @@ -23,7 +23,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier)))) (Method @@ -41,7 +41,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier)))) (Method @@ -59,6 +59,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier))))))) diff --git a/test/fixtures/javascript/corpus/class.parseA.txt b/test/fixtures/javascript/corpus/class.parseA.txt index 34abae5a2..1d34cdb49 100644 --- a/test/fixtures/javascript/corpus/class.parseA.txt +++ b/test/fixtures/javascript/corpus/class.parseA.txt @@ -1,7 +1,7 @@ (Program (Class (Identifier) - ( + (Statements (PublicFieldDefinition (Empty) (Empty) @@ -22,7 +22,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier)))) (Method @@ -39,7 +39,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier)))) (Method @@ -56,6 +56,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier))))))) diff --git a/test/fixtures/javascript/corpus/class.parseB.txt b/test/fixtures/javascript/corpus/class.parseB.txt index 7a85e6797..3bde6e0b0 100644 --- a/test/fixtures/javascript/corpus/class.parseB.txt +++ b/test/fixtures/javascript/corpus/class.parseB.txt @@ -1,7 +1,7 @@ (Program (Class (Identifier) - ( + (Statements (Method (Empty) (Empty) @@ -16,7 +16,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier)))) (Method @@ -33,7 +33,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier)))) (Method @@ -50,6 +50,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier))))))) diff --git a/test/fixtures/javascript/corpus/continue.diffA-B.txt b/test/fixtures/javascript/corpus/continue.diffA-B.txt index 745ef1761..44e6c7bdc 100644 --- a/test/fixtures/javascript/corpus/continue.diffA-B.txt +++ b/test/fixtures/javascript/corpus/continue.diffA-B.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements {+(Break {+(Empty)+})+} {-(Continue diff --git a/test/fixtures/javascript/corpus/continue.diffB-A.txt b/test/fixtures/javascript/corpus/continue.diffB-A.txt index eff385027..46eb71902 100644 --- a/test/fixtures/javascript/corpus/continue.diffB-A.txt +++ b/test/fixtures/javascript/corpus/continue.diffB-A.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements {+(Continue {+(Empty)+})+} {-(Break diff --git a/test/fixtures/javascript/corpus/continue.parseA.txt b/test/fixtures/javascript/corpus/continue.parseA.txt index 9618a22b5..0c30ef033 100644 --- a/test/fixtures/javascript/corpus/continue.parseA.txt +++ b/test/fixtures/javascript/corpus/continue.parseA.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements (Continue (Empty))) (Empty)) diff --git a/test/fixtures/javascript/corpus/continue.parseB.txt b/test/fixtures/javascript/corpus/continue.parseB.txt index e927cd94c..c0af1c973 100644 --- a/test/fixtures/javascript/corpus/continue.parseB.txt +++ b/test/fixtures/javascript/corpus/continue.parseB.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements (Break (Empty))) (Empty)) diff --git a/test/fixtures/javascript/corpus/do-while-statement.diffA-B.txt b/test/fixtures/javascript/corpus/do-while-statement.diffA-B.txt index 30c06d609..5935813f5 100644 --- a/test/fixtures/javascript/corpus/do-while-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/do-while-statement.diffA-B.txt @@ -2,7 +2,7 @@ (DoWhile { (Boolean) ->(Boolean) } - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/do-while-statement.diffB-A.txt b/test/fixtures/javascript/corpus/do-while-statement.diffB-A.txt index 30c06d609..5935813f5 100644 --- a/test/fixtures/javascript/corpus/do-while-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/do-while-statement.diffB-A.txt @@ -2,7 +2,7 @@ (DoWhile { (Boolean) ->(Boolean) } - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/do-while-statement.parseA.txt b/test/fixtures/javascript/corpus/do-while-statement.parseA.txt index 92c41b1a1..a75cc5e53 100644 --- a/test/fixtures/javascript/corpus/do-while-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/do-while-statement.parseA.txt @@ -1,7 +1,7 @@ (Program (DoWhile (Boolean) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/do-while-statement.parseB.txt b/test/fixtures/javascript/corpus/do-while-statement.parseB.txt index 92c41b1a1..a75cc5e53 100644 --- a/test/fixtures/javascript/corpus/do-while-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/do-while-statement.parseB.txt @@ -1,7 +1,7 @@ (Program (DoWhile (Boolean) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/export.diffA-B.txt b/test/fixtures/javascript/corpus/export.diffA-B.txt index 4e6aea904..d820a0e81 100644 --- a/test/fixtures/javascript/corpus/export.diffA-B.txt +++ b/test/fixtures/javascript/corpus/export.diffA-B.txt @@ -52,13 +52,13 @@ {+(Empty)+} {+(Empty)+} {+(Identifier)+} - {+([])+})+})+} + {+(Statements)+})+})+} (DefaultExport (Function (Empty) (Empty) (Empty) - ([]))) + (Statements))) {+(QualifiedExport)+} {+(DefaultExport {+(TextElement)+})+} @@ -69,7 +69,7 @@ {-(Empty)-} {-(Empty)-} {-(Identifier)-} - {-([])-})-})-} + {-(Statements)-})-})-} {-(QualifiedExport)-} {-(DefaultExport {-(TextElement)-})-} diff --git a/test/fixtures/javascript/corpus/export.diffB-A.txt b/test/fixtures/javascript/corpus/export.diffB-A.txt index c0d98eefd..fca2269b7 100644 --- a/test/fixtures/javascript/corpus/export.diffB-A.txt +++ b/test/fixtures/javascript/corpus/export.diffB-A.txt @@ -55,19 +55,19 @@ {-(Empty)-} {-(Empty)-} {-(Identifier)-} - {-([])-})-})-} + {-(Statements)-})-})-} (DefaultExport (Function (Empty) (Empty) (Empty) - ([]))) + (Statements))) {+(DefaultExport {+(Function {+(Empty)+} {+(Empty)+} {+(Identifier)+} - {+([])+})+})+} + {+(Statements)+})+})+} { (QualifiedExport) ->(QualifiedExport) } (DefaultExport diff --git a/test/fixtures/javascript/corpus/export.parseA.txt b/test/fixtures/javascript/corpus/export.parseA.txt index 5e293e404..c65411988 100644 --- a/test/fixtures/javascript/corpus/export.parseA.txt +++ b/test/fixtures/javascript/corpus/export.parseA.txt @@ -40,13 +40,13 @@ (Empty) (Empty) (Empty) - ([]))) + (Statements))) (DefaultExport (Function (Empty) (Empty) (Identifier) - ([]))) + (Statements))) (QualifiedExport) (DefaultExport (TextElement)) diff --git a/test/fixtures/javascript/corpus/export.parseB.txt b/test/fixtures/javascript/corpus/export.parseB.txt index 12ec54bef..a04091e87 100644 --- a/test/fixtures/javascript/corpus/export.parseB.txt +++ b/test/fixtures/javascript/corpus/export.parseB.txt @@ -40,13 +40,13 @@ (Empty) (Empty) (Identifier) - ([]))) + (Statements))) (DefaultExport (Function (Empty) (Empty) (Empty) - ([]))) + (Statements))) (QualifiedExport) (DefaultExport (TextElement)) diff --git a/test/fixtures/javascript/corpus/for-in-statement.diffA-B.txt b/test/fixtures/javascript/corpus/for-in-statement.diffA-B.txt index 4faf0ca9a..7f4c7fe4a 100644 --- a/test/fixtures/javascript/corpus/for-in-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/for-in-statement.diffA-B.txt @@ -4,7 +4,7 @@ ->(Identifier) } { (Identifier) ->(Identifier) } - ( + (Statements (Call { (Identifier) ->(Identifier) } diff --git a/test/fixtures/javascript/corpus/for-in-statement.diffB-A.txt b/test/fixtures/javascript/corpus/for-in-statement.diffB-A.txt index 4faf0ca9a..7f4c7fe4a 100644 --- a/test/fixtures/javascript/corpus/for-in-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/for-in-statement.diffB-A.txt @@ -4,7 +4,7 @@ ->(Identifier) } { (Identifier) ->(Identifier) } - ( + (Statements (Call { (Identifier) ->(Identifier) } diff --git a/test/fixtures/javascript/corpus/for-in-statement.parseA.txt b/test/fixtures/javascript/corpus/for-in-statement.parseA.txt index c41e5a7f1..79a82b79a 100644 --- a/test/fixtures/javascript/corpus/for-in-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/for-in-statement.parseA.txt @@ -2,7 +2,7 @@ (ForEach (Identifier) (Identifier) - ( + (Statements (Call (Identifier) (Empty))))) diff --git a/test/fixtures/javascript/corpus/for-in-statement.parseB.txt b/test/fixtures/javascript/corpus/for-in-statement.parseB.txt index c41e5a7f1..79a82b79a 100644 --- a/test/fixtures/javascript/corpus/for-in-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/for-in-statement.parseB.txt @@ -2,7 +2,7 @@ (ForEach (Identifier) (Identifier) - ( + (Statements (Call (Identifier) (Empty))))) diff --git a/test/fixtures/javascript/corpus/for-loop-with-in-statement.diffA-B.txt b/test/fixtures/javascript/corpus/for-loop-with-in-statement.diffA-B.txt index dcd085128..e3184832c 100644 --- a/test/fixtures/javascript/corpus/for-loop-with-in-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/for-loop-with-in-statement.diffA-B.txt @@ -13,7 +13,7 @@ (Identifier)) (Update (Identifier)) - ( + (Statements (Call { (Identifier) ->(Identifier) } diff --git a/test/fixtures/javascript/corpus/for-loop-with-in-statement.diffB-A.txt b/test/fixtures/javascript/corpus/for-loop-with-in-statement.diffB-A.txt index dcd085128..e3184832c 100644 --- a/test/fixtures/javascript/corpus/for-loop-with-in-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/for-loop-with-in-statement.diffB-A.txt @@ -13,7 +13,7 @@ (Identifier)) (Update (Identifier)) - ( + (Statements (Call { (Identifier) ->(Identifier) } diff --git a/test/fixtures/javascript/corpus/for-loop-with-in-statement.parseA.txt b/test/fixtures/javascript/corpus/for-loop-with-in-statement.parseA.txt index 09777939f..0c1d70fb4 100644 --- a/test/fixtures/javascript/corpus/for-loop-with-in-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/for-loop-with-in-statement.parseA.txt @@ -12,7 +12,7 @@ (Identifier)) (Update (Identifier)) - ( + (Statements (Call (Identifier) (Empty))))) diff --git a/test/fixtures/javascript/corpus/for-loop-with-in-statement.parseB.txt b/test/fixtures/javascript/corpus/for-loop-with-in-statement.parseB.txt index 09777939f..0c1d70fb4 100644 --- a/test/fixtures/javascript/corpus/for-loop-with-in-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/for-loop-with-in-statement.parseB.txt @@ -12,7 +12,7 @@ (Identifier)) (Update (Identifier)) - ( + (Statements (Call (Identifier) (Empty))))) diff --git a/test/fixtures/javascript/corpus/for-of-statement.diffA-B.txt b/test/fixtures/javascript/corpus/for-of-statement.diffA-B.txt index 9886795f9..f5e052f79 100644 --- a/test/fixtures/javascript/corpus/for-of-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/for-of-statement.diffA-B.txt @@ -4,7 +4,7 @@ ->(Identifier) } { (Identifier) ->(Identifier) } - ( + (Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/javascript/corpus/for-of-statement.diffB-A.txt b/test/fixtures/javascript/corpus/for-of-statement.diffB-A.txt index 9886795f9..f5e052f79 100644 --- a/test/fixtures/javascript/corpus/for-of-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/for-of-statement.diffB-A.txt @@ -4,7 +4,7 @@ ->(Identifier) } { (Identifier) ->(Identifier) } - ( + (Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/javascript/corpus/for-of-statement.parseA.txt b/test/fixtures/javascript/corpus/for-of-statement.parseA.txt index 025a1cf60..3c9704a36 100644 --- a/test/fixtures/javascript/corpus/for-of-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/for-of-statement.parseA.txt @@ -2,7 +2,7 @@ (ForOf (Identifier) (Identifier) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/for-of-statement.parseB.txt b/test/fixtures/javascript/corpus/for-of-statement.parseB.txt index 025a1cf60..3c9704a36 100644 --- a/test/fixtures/javascript/corpus/for-of-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/for-of-statement.parseB.txt @@ -2,7 +2,7 @@ (ForOf (Identifier) (Identifier) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/for-statement.diffA-B.txt b/test/fixtures/javascript/corpus/for-statement.diffA-B.txt index 42df10b93..1cf044616 100644 --- a/test/fixtures/javascript/corpus/for-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/for-statement.diffA-B.txt @@ -13,7 +13,7 @@ ->(Float) }) (Update (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/for-statement.diffB-A.txt b/test/fixtures/javascript/corpus/for-statement.diffB-A.txt index 42df10b93..1cf044616 100644 --- a/test/fixtures/javascript/corpus/for-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/for-statement.diffB-A.txt @@ -13,7 +13,7 @@ ->(Float) }) (Update (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/for-statement.parseA.txt b/test/fixtures/javascript/corpus/for-statement.parseA.txt index 4874a22fc..fe2179965 100644 --- a/test/fixtures/javascript/corpus/for-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/for-statement.parseA.txt @@ -12,7 +12,7 @@ (Float)) (Update (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/for-statement.parseB.txt b/test/fixtures/javascript/corpus/for-statement.parseB.txt index 4874a22fc..fe2179965 100644 --- a/test/fixtures/javascript/corpus/for-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/for-statement.parseB.txt @@ -12,7 +12,7 @@ (Float)) (Update (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/function-call-args.diffA-B.txt b/test/fixtures/javascript/corpus/function-call-args.diffA-B.txt index cb4b6e2d9..9ab5e70c0 100644 --- a/test/fixtures/javascript/corpus/function-call-args.diffA-B.txt +++ b/test/fixtures/javascript/corpus/function-call-args.diffA-B.txt @@ -29,7 +29,7 @@ {+(Assignment {+(Identifier)+} {+(Empty)+})+})+} - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/function-call-args.diffB-A.txt b/test/fixtures/javascript/corpus/function-call-args.diffB-A.txt index 194e964af..46e0b5c06 100644 --- a/test/fixtures/javascript/corpus/function-call-args.diffB-A.txt +++ b/test/fixtures/javascript/corpus/function-call-args.diffB-A.txt @@ -29,7 +29,7 @@ {-(Assignment {-(Identifier)-} {-(Empty)-})-})-} - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/function-call-args.parseA.txt b/test/fixtures/javascript/corpus/function-call-args.parseA.txt index 3f9ef783e..ed0d71201 100644 --- a/test/fixtures/javascript/corpus/function-call-args.parseA.txt +++ b/test/fixtures/javascript/corpus/function-call-args.parseA.txt @@ -21,7 +21,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/function-call-args.parseB.txt b/test/fixtures/javascript/corpus/function-call-args.parseB.txt index 3f9ef783e..ed0d71201 100644 --- a/test/fixtures/javascript/corpus/function-call-args.parseB.txt +++ b/test/fixtures/javascript/corpus/function-call-args.parseB.txt @@ -21,7 +21,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/function.diffA-B.txt b/test/fixtures/javascript/corpus/function.diffA-B.txt index 268dd2b35..ad894be7c 100644 --- a/test/fixtures/javascript/corpus/function.diffA-B.txt +++ b/test/fixtures/javascript/corpus/function.diffA-B.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements { (Identifier) ->(Identifier) })) (Empty)) diff --git a/test/fixtures/javascript/corpus/function.diffB-A.txt b/test/fixtures/javascript/corpus/function.diffB-A.txt index 268dd2b35..ad894be7c 100644 --- a/test/fixtures/javascript/corpus/function.diffB-A.txt +++ b/test/fixtures/javascript/corpus/function.diffB-A.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements { (Identifier) ->(Identifier) })) (Empty)) diff --git a/test/fixtures/javascript/corpus/function.parseA.txt b/test/fixtures/javascript/corpus/function.parseA.txt index 7b52e977a..4059c4550 100644 --- a/test/fixtures/javascript/corpus/function.parseA.txt +++ b/test/fixtures/javascript/corpus/function.parseA.txt @@ -17,6 +17,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Identifier))) (Empty)) diff --git a/test/fixtures/javascript/corpus/function.parseB.txt b/test/fixtures/javascript/corpus/function.parseB.txt index 7b52e977a..4059c4550 100644 --- a/test/fixtures/javascript/corpus/function.parseB.txt +++ b/test/fixtures/javascript/corpus/function.parseB.txt @@ -17,6 +17,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Identifier))) (Empty)) diff --git a/test/fixtures/javascript/corpus/generator-function.diffA-B.txt b/test/fixtures/javascript/corpus/generator-function.diffA-B.txt index 65f3d8507..2f4f58433 100644 --- a/test/fixtures/javascript/corpus/generator-function.diffA-B.txt +++ b/test/fixtures/javascript/corpus/generator-function.diffA-B.txt @@ -18,7 +18,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Yield (Empty)) (Yield diff --git a/test/fixtures/javascript/corpus/generator-function.diffB-A.txt b/test/fixtures/javascript/corpus/generator-function.diffB-A.txt index 65f3d8507..2f4f58433 100644 --- a/test/fixtures/javascript/corpus/generator-function.diffB-A.txt +++ b/test/fixtures/javascript/corpus/generator-function.diffB-A.txt @@ -18,7 +18,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Yield (Empty)) (Yield diff --git a/test/fixtures/javascript/corpus/generator-function.parseA.txt b/test/fixtures/javascript/corpus/generator-function.parseA.txt index d86eafa99..fd25c91b3 100644 --- a/test/fixtures/javascript/corpus/generator-function.parseA.txt +++ b/test/fixtures/javascript/corpus/generator-function.parseA.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Yield (Empty)) (Yield diff --git a/test/fixtures/javascript/corpus/generator-function.parseB.txt b/test/fixtures/javascript/corpus/generator-function.parseB.txt index d86eafa99..fd25c91b3 100644 --- a/test/fixtures/javascript/corpus/generator-function.parseB.txt +++ b/test/fixtures/javascript/corpus/generator-function.parseB.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Yield (Empty)) (Yield diff --git a/test/fixtures/javascript/corpus/if-else.diffA-B.txt b/test/fixtures/javascript/corpus/if-else.diffA-B.txt index 8d402c80e..41281f5e5 100644 --- a/test/fixtures/javascript/corpus/if-else.diffA-B.txt +++ b/test/fixtures/javascript/corpus/if-else.diffA-B.txt @@ -8,7 +8,7 @@ { (Identifier) ->(Identifier) } { (Identifier) - ->( + ->(Statements {+(Identifier)+}) } (If { (Identifier) @@ -19,7 +19,7 @@ { (Identifier) ->(Identifier) } { (Identifier) - ->( + ->(Statements {+(Identifier)+}) } { (Identifier) ->(Identifier) }))))) diff --git a/test/fixtures/javascript/corpus/if-else.diffB-A.txt b/test/fixtures/javascript/corpus/if-else.diffB-A.txt index 514f0cd36..a7e842460 100644 --- a/test/fixtures/javascript/corpus/if-else.diffB-A.txt +++ b/test/fixtures/javascript/corpus/if-else.diffB-A.txt @@ -7,7 +7,7 @@ (If { (Identifier) ->(Identifier) } - { ( + { (Statements {-(Identifier)-}) ->(Identifier) } (If @@ -18,7 +18,7 @@ (If { (Identifier) ->(Identifier) } - { ( + { (Statements {-(Identifier)-}) ->(Identifier) } { (Identifier) diff --git a/test/fixtures/javascript/corpus/if-else.parseB.txt b/test/fixtures/javascript/corpus/if-else.parseB.txt index 3a8f90cf1..2402f8fd0 100644 --- a/test/fixtures/javascript/corpus/if-else.parseB.txt +++ b/test/fixtures/javascript/corpus/if-else.parseB.txt @@ -4,13 +4,13 @@ (Identifier) (If (Identifier) - ( + (Statements (Identifier)) (If (Identifier) (Identifier) (If (Identifier) - ( + (Statements (Identifier)) (Identifier)))))) diff --git a/test/fixtures/javascript/corpus/if.diffA-B.txt b/test/fixtures/javascript/corpus/if.diffA-B.txt index 2a90eee30..329dbee61 100644 --- a/test/fixtures/javascript/corpus/if.diffA-B.txt +++ b/test/fixtures/javascript/corpus/if.diffA-B.txt @@ -4,7 +4,7 @@ ->(MemberAccess {+(Identifier)+} {+(Identifier)+}) } - ( + (Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/javascript/corpus/if.diffB-A.txt b/test/fixtures/javascript/corpus/if.diffB-A.txt index a6742d0e3..58379f889 100644 --- a/test/fixtures/javascript/corpus/if.diffB-A.txt +++ b/test/fixtures/javascript/corpus/if.diffB-A.txt @@ -4,7 +4,7 @@ {-(Identifier)-} {-(Identifier)-}) ->(Identifier) } - ( + (Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/javascript/corpus/if.parseA.txt b/test/fixtures/javascript/corpus/if.parseA.txt index 23bee3aca..c319b1eb0 100644 --- a/test/fixtures/javascript/corpus/if.parseA.txt +++ b/test/fixtures/javascript/corpus/if.parseA.txt @@ -1,7 +1,7 @@ (Program (If (Identifier) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/if.parseB.txt b/test/fixtures/javascript/corpus/if.parseB.txt index 82a81394a..4c23c44b9 100644 --- a/test/fixtures/javascript/corpus/if.parseB.txt +++ b/test/fixtures/javascript/corpus/if.parseB.txt @@ -3,7 +3,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/import.diffA-B.txt b/test/fixtures/javascript/corpus/import.diffA-B.txt index 9e5c75bdc..f817f812a 100644 --- a/test/fixtures/javascript/corpus/import.diffA-B.txt +++ b/test/fixtures/javascript/corpus/import.diffA-B.txt @@ -6,10 +6,10 @@ ->(Import) } {+(Import)+} {+(Import)+} -{+( +{+(Statements {+(Import)+} {+(Import)+})+} -{+( +{+(Statements {+(Import)+} {+(QualifiedAliasedImport {+(Identifier)+})+})+} @@ -19,10 +19,10 @@ {-(Import)-} {-(Import)-} {-(Import)-} -{-( +{-(Statements {-(Import)-} {-(Import)-})-} -{-( +{-(Statements {-(Import)-} {-(QualifiedAliasedImport {-(Identifier)-})-})-} diff --git a/test/fixtures/javascript/corpus/import.diffB-A.txt b/test/fixtures/javascript/corpus/import.diffB-A.txt index 7bcd92f6a..d9ef4348b 100644 --- a/test/fixtures/javascript/corpus/import.diffB-A.txt +++ b/test/fixtures/javascript/corpus/import.diffB-A.txt @@ -5,10 +5,10 @@ {+(Import)+} {+(Import)+} {+(Import)+} -{+( +{+(Statements {+(Import)+} {+(Import)+})+} -{+( +{+(Statements {+(Import)+} {+(QualifiedAliasedImport {+(Identifier)+})+})+} @@ -19,10 +19,10 @@ {-(Import)-} {-(Import)-} {-(Import)-} -{-( +{-(Statements {-(Import)-} {-(Import)-})-} -{-( +{-(Statements {-(Import)-} {-(QualifiedAliasedImport {-(Identifier)-})-})-} diff --git a/test/fixtures/javascript/corpus/import.parseA.txt b/test/fixtures/javascript/corpus/import.parseA.txt index 037e1c7c8..069afffe6 100644 --- a/test/fixtures/javascript/corpus/import.parseA.txt +++ b/test/fixtures/javascript/corpus/import.parseA.txt @@ -5,10 +5,10 @@ (Import) (Import) (Import) - ( + (Statements (Import) (Import)) - ( + (Statements (Import) (QualifiedAliasedImport (Identifier))) diff --git a/test/fixtures/javascript/corpus/import.parseB.txt b/test/fixtures/javascript/corpus/import.parseB.txt index 037e1c7c8..069afffe6 100644 --- a/test/fixtures/javascript/corpus/import.parseB.txt +++ b/test/fixtures/javascript/corpus/import.parseB.txt @@ -5,10 +5,10 @@ (Import) (Import) (Import) - ( + (Statements (Import) (Import)) - ( + (Statements (Import) (QualifiedAliasedImport (Identifier))) diff --git a/test/fixtures/javascript/corpus/named-function.diffA-B.txt b/test/fixtures/javascript/corpus/named-function.diffA-B.txt index 097c4555b..aec245b08 100644 --- a/test/fixtures/javascript/corpus/named-function.diffA-B.txt +++ b/test/fixtures/javascript/corpus/named-function.diffA-B.txt @@ -18,7 +18,7 @@ {-(Assignment {-(Identifier)-} {-(Empty)-})-})-} - ( + (Statements {+(Return {+(Boolean)+})+} {-(Identifier)-})) diff --git a/test/fixtures/javascript/corpus/named-function.diffB-A.txt b/test/fixtures/javascript/corpus/named-function.diffB-A.txt index 0b02b2e5a..8ac7047e0 100644 --- a/test/fixtures/javascript/corpus/named-function.diffB-A.txt +++ b/test/fixtures/javascript/corpus/named-function.diffB-A.txt @@ -18,7 +18,7 @@ {+(Assignment {+(Identifier)+} {+(Empty)+})+})+} - ( + (Statements {+(Identifier)+} {-(Return {-(Boolean)-})-})) diff --git a/test/fixtures/javascript/corpus/named-function.parseA.txt b/test/fixtures/javascript/corpus/named-function.parseA.txt index 6f4b7d301..a0596d5bd 100644 --- a/test/fixtures/javascript/corpus/named-function.parseA.txt +++ b/test/fixtures/javascript/corpus/named-function.parseA.txt @@ -17,6 +17,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Identifier))) (Empty)) diff --git a/test/fixtures/javascript/corpus/named-function.parseB.txt b/test/fixtures/javascript/corpus/named-function.parseB.txt index fbad167d9..96d3c4033 100644 --- a/test/fixtures/javascript/corpus/named-function.parseB.txt +++ b/test/fixtures/javascript/corpus/named-function.parseB.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Identifier) - ( + (Statements (Return (Boolean)))) (Empty)) diff --git a/test/fixtures/javascript/corpus/nested-do-while-in-function.diffA-B.txt b/test/fixtures/javascript/corpus/nested-do-while-in-function.diffA-B.txt index c7eea5548..00dd2f4a3 100644 --- a/test/fixtures/javascript/corpus/nested-do-while-in-function.diffA-B.txt +++ b/test/fixtures/javascript/corpus/nested-do-while-in-function.diffA-B.txt @@ -17,11 +17,11 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (DoWhile { (Identifier) ->(Identifier) } - ( + (Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/javascript/corpus/nested-do-while-in-function.diffB-A.txt b/test/fixtures/javascript/corpus/nested-do-while-in-function.diffB-A.txt index c7eea5548..00dd2f4a3 100644 --- a/test/fixtures/javascript/corpus/nested-do-while-in-function.diffB-A.txt +++ b/test/fixtures/javascript/corpus/nested-do-while-in-function.diffB-A.txt @@ -17,11 +17,11 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (DoWhile { (Identifier) ->(Identifier) } - ( + (Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/javascript/corpus/nested-do-while-in-function.parseA.txt b/test/fixtures/javascript/corpus/nested-do-while-in-function.parseA.txt index 440deb76f..618761627 100644 --- a/test/fixtures/javascript/corpus/nested-do-while-in-function.parseA.txt +++ b/test/fixtures/javascript/corpus/nested-do-while-in-function.parseA.txt @@ -17,10 +17,10 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (DoWhile (Identifier) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/nested-do-while-in-function.parseB.txt b/test/fixtures/javascript/corpus/nested-do-while-in-function.parseB.txt index 440deb76f..618761627 100644 --- a/test/fixtures/javascript/corpus/nested-do-while-in-function.parseB.txt +++ b/test/fixtures/javascript/corpus/nested-do-while-in-function.parseB.txt @@ -17,10 +17,10 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (DoWhile (Identifier) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/nested-functions.diffA-B.txt b/test/fixtures/javascript/corpus/nested-functions.diffA-B.txt index 0b3c286a9..2a221fcdd 100644 --- a/test/fixtures/javascript/corpus/nested-functions.diffA-B.txt +++ b/test/fixtures/javascript/corpus/nested-functions.diffA-B.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Function (Empty) (Empty) @@ -36,7 +36,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/nested-functions.diffB-A.txt b/test/fixtures/javascript/corpus/nested-functions.diffB-A.txt index 0b3c286a9..2a221fcdd 100644 --- a/test/fixtures/javascript/corpus/nested-functions.diffB-A.txt +++ b/test/fixtures/javascript/corpus/nested-functions.diffB-A.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Function (Empty) (Empty) @@ -36,7 +36,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/nested-functions.parseA.txt b/test/fixtures/javascript/corpus/nested-functions.parseA.txt index 0955c8914..bba0968bd 100644 --- a/test/fixtures/javascript/corpus/nested-functions.parseA.txt +++ b/test/fixtures/javascript/corpus/nested-functions.parseA.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Function (Empty) (Empty) @@ -36,7 +36,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/nested-functions.parseB.txt b/test/fixtures/javascript/corpus/nested-functions.parseB.txt index 0955c8914..bba0968bd 100644 --- a/test/fixtures/javascript/corpus/nested-functions.parseB.txt +++ b/test/fixtures/javascript/corpus/nested-functions.parseB.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Function (Empty) (Empty) @@ -36,7 +36,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/objects-with-methods.diffA-B.txt b/test/fixtures/javascript/corpus/objects-with-methods.diffA-B.txt index e7766878f..9c40be32f 100644 --- a/test/fixtures/javascript/corpus/objects-with-methods.diffA-B.txt +++ b/test/fixtures/javascript/corpus/objects-with-methods.diffA-B.txt @@ -22,7 +22,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return { (Plus {-(Identifier)-} diff --git a/test/fixtures/javascript/corpus/objects-with-methods.diffB-A.txt b/test/fixtures/javascript/corpus/objects-with-methods.diffB-A.txt index 6d87f8b53..914db2372 100644 --- a/test/fixtures/javascript/corpus/objects-with-methods.diffB-A.txt +++ b/test/fixtures/javascript/corpus/objects-with-methods.diffB-A.txt @@ -22,7 +22,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return { (Minus {-(Identifier)-} diff --git a/test/fixtures/javascript/corpus/objects-with-methods.parseA.txt b/test/fixtures/javascript/corpus/objects-with-methods.parseA.txt index d3d5e4345..618957d0f 100644 --- a/test/fixtures/javascript/corpus/objects-with-methods.parseA.txt +++ b/test/fixtures/javascript/corpus/objects-with-methods.parseA.txt @@ -21,7 +21,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Plus (Identifier) diff --git a/test/fixtures/javascript/corpus/objects-with-methods.parseB.txt b/test/fixtures/javascript/corpus/objects-with-methods.parseB.txt index b8747c6ea..8acf4faff 100644 --- a/test/fixtures/javascript/corpus/objects-with-methods.parseB.txt +++ b/test/fixtures/javascript/corpus/objects-with-methods.parseB.txt @@ -21,7 +21,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Minus (Identifier) diff --git a/test/fixtures/javascript/corpus/switch-statement.diffA-B.txt b/test/fixtures/javascript/corpus/switch-statement.diffA-B.txt index e72d89a5b..3883f69c5 100644 --- a/test/fixtures/javascript/corpus/switch-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/switch-statement.diffA-B.txt @@ -2,18 +2,18 @@ (Match { (Float) ->(Float) } - ( + (Statements (Pattern (Float) - ( + (Statements (Float))) (Pattern (Float) - ( + (Statements { (Float) ->(Float) })) (Pattern (Float) - ( + (Statements (Float))))) (Empty)) diff --git a/test/fixtures/javascript/corpus/switch-statement.diffB-A.txt b/test/fixtures/javascript/corpus/switch-statement.diffB-A.txt index e72d89a5b..3883f69c5 100644 --- a/test/fixtures/javascript/corpus/switch-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/switch-statement.diffB-A.txt @@ -2,18 +2,18 @@ (Match { (Float) ->(Float) } - ( + (Statements (Pattern (Float) - ( + (Statements (Float))) (Pattern (Float) - ( + (Statements { (Float) ->(Float) })) (Pattern (Float) - ( + (Statements (Float))))) (Empty)) diff --git a/test/fixtures/javascript/corpus/switch-statement.parseA.txt b/test/fixtures/javascript/corpus/switch-statement.parseA.txt index 7d77dcfad..3e597d106 100644 --- a/test/fixtures/javascript/corpus/switch-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/switch-statement.parseA.txt @@ -1,17 +1,17 @@ (Program (Match (Float) - ( + (Statements (Pattern (Float) - ( + (Statements (Float))) (Pattern (Float) - ( + (Statements (Float))) (Pattern (Float) - ( + (Statements (Float))))) (Empty)) diff --git a/test/fixtures/javascript/corpus/switch-statement.parseB.txt b/test/fixtures/javascript/corpus/switch-statement.parseB.txt index 7d77dcfad..3e597d106 100644 --- a/test/fixtures/javascript/corpus/switch-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/switch-statement.parseB.txt @@ -1,17 +1,17 @@ (Program (Match (Float) - ( + (Statements (Pattern (Float) - ( + (Statements (Float))) (Pattern (Float) - ( + (Statements (Float))) (Pattern (Float) - ( + (Statements (Float))))) (Empty)) diff --git a/test/fixtures/javascript/corpus/try-statement.diffA-B.txt b/test/fixtures/javascript/corpus/try-statement.diffA-B.txt index a1448e34d..a7241e603 100644 --- a/test/fixtures/javascript/corpus/try-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/try-statement.diffA-B.txt @@ -1,14 +1,14 @@ (Program (Try - ( + (Statements (Identifier)) (Catch (Empty) - ( + (Statements { (Identifier) ->(Identifier) })) (Finally - ( + (Statements { (Identifier) ->(Identifier) }))) (Empty)) diff --git a/test/fixtures/javascript/corpus/try-statement.diffB-A.txt b/test/fixtures/javascript/corpus/try-statement.diffB-A.txt index a1448e34d..a7241e603 100644 --- a/test/fixtures/javascript/corpus/try-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/try-statement.diffB-A.txt @@ -1,14 +1,14 @@ (Program (Try - ( + (Statements (Identifier)) (Catch (Empty) - ( + (Statements { (Identifier) ->(Identifier) })) (Finally - ( + (Statements { (Identifier) ->(Identifier) }))) (Empty)) diff --git a/test/fixtures/javascript/corpus/try-statement.parseA.txt b/test/fixtures/javascript/corpus/try-statement.parseA.txt index 7224cc157..22e10b492 100644 --- a/test/fixtures/javascript/corpus/try-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/try-statement.parseA.txt @@ -1,12 +1,12 @@ (Program (Try - ( + (Statements (Identifier)) (Catch (Empty) - ( + (Statements (Identifier))) (Finally - ( + (Statements (Identifier)))) (Empty)) diff --git a/test/fixtures/javascript/corpus/try-statement.parseB.txt b/test/fixtures/javascript/corpus/try-statement.parseB.txt index 7224cc157..22e10b492 100644 --- a/test/fixtures/javascript/corpus/try-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/try-statement.parseB.txt @@ -1,12 +1,12 @@ (Program (Try - ( + (Statements (Identifier)) (Catch (Empty) - ( + (Statements (Identifier))) (Finally - ( + (Statements (Identifier)))) (Empty)) diff --git a/test/fixtures/javascript/corpus/while-statement.diffA-B.txt b/test/fixtures/javascript/corpus/while-statement.diffA-B.txt index 7ecf81cea..6c6581fbe 100644 --- a/test/fixtures/javascript/corpus/while-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/while-statement.diffA-B.txt @@ -2,7 +2,7 @@ (While { (Identifier) ->(Identifier) } - ( + (Statements (Call { (Identifier) ->(Identifier) } diff --git a/test/fixtures/javascript/corpus/while-statement.diffB-A.txt b/test/fixtures/javascript/corpus/while-statement.diffB-A.txt index 7ecf81cea..6c6581fbe 100644 --- a/test/fixtures/javascript/corpus/while-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/while-statement.diffB-A.txt @@ -2,7 +2,7 @@ (While { (Identifier) ->(Identifier) } - ( + (Statements (Call { (Identifier) ->(Identifier) } diff --git a/test/fixtures/javascript/corpus/while-statement.parseA.txt b/test/fixtures/javascript/corpus/while-statement.parseA.txt index 384062c49..41960b042 100644 --- a/test/fixtures/javascript/corpus/while-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/while-statement.parseA.txt @@ -1,7 +1,7 @@ (Program (While (Identifier) - ( + (Statements (Call (Identifier) (Empty)))) diff --git a/test/fixtures/javascript/corpus/while-statement.parseB.txt b/test/fixtures/javascript/corpus/while-statement.parseB.txt index 384062c49..41960b042 100644 --- a/test/fixtures/javascript/corpus/while-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/while-statement.parseB.txt @@ -1,7 +1,7 @@ (Program (While (Identifier) - ( + (Statements (Call (Identifier) (Empty)))) diff --git a/test/fixtures/javascript/corpus/yield.diffA-B.txt b/test/fixtures/javascript/corpus/yield.diffA-B.txt index 1737c04ee..ccde7b2d7 100644 --- a/test/fixtures/javascript/corpus/yield.diffA-B.txt +++ b/test/fixtures/javascript/corpus/yield.diffA-B.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Identifier) - ( + (Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/javascript/corpus/yield.diffB-A.txt b/test/fixtures/javascript/corpus/yield.diffB-A.txt index 56edbe9a9..d7dd3fc20 100644 --- a/test/fixtures/javascript/corpus/yield.diffB-A.txt +++ b/test/fixtures/javascript/corpus/yield.diffB-A.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Identifier) - ( + (Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/javascript/corpus/yield.parseA.txt b/test/fixtures/javascript/corpus/yield.parseA.txt index 0a4c7dcc9..47d764d16 100644 --- a/test/fixtures/javascript/corpus/yield.parseA.txt +++ b/test/fixtures/javascript/corpus/yield.parseA.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Identifier) - ( + (Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/javascript/corpus/yield.parseB.txt b/test/fixtures/javascript/corpus/yield.parseB.txt index 85816f2b8..54eada74e 100644 --- a/test/fixtures/javascript/corpus/yield.parseB.txt +++ b/test/fixtures/javascript/corpus/yield.parseB.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Identifier) - ( + (Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/python/corpus/assignment.diffA-B.txt b/test/fixtures/python/corpus/assignment.diffA-B.txt index c1c74f5af..105306e81 100644 --- a/test/fixtures/python/corpus/assignment.diffA-B.txt +++ b/test/fixtures/python/corpus/assignment.diffA-B.txt @@ -1,9 +1,9 @@ (Program {+(Assignment - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} - {+( + {+(Statements {+(Integer)+} {+(Integer)+})+})+} (Assignment @@ -11,15 +11,15 @@ ->(Identifier) } (Integer)) (Assignment - { ( + { (Statements {-(Identifier)-} {-(Identifier)-}) ->(Identifier) } - ( + (Statements (Integer) (Integer))) {-(Assignment {-(Identifier)-} - {-( + {-(Statements {-(Integer)-} {-(Integer)-})-})-}) diff --git a/test/fixtures/python/corpus/assignment.diffB-A.txt b/test/fixtures/python/corpus/assignment.diffB-A.txt index bf818d4b1..3f7d8e47a 100644 --- a/test/fixtures/python/corpus/assignment.diffB-A.txt +++ b/test/fixtures/python/corpus/assignment.diffB-A.txt @@ -3,16 +3,16 @@ {+(Identifier)+} {+(Integer)+})+} (Assignment - ( + (Statements (Identifier) (Identifier)) - ( + (Statements {-(Integer)-} (Integer) {+(Integer)+})) {+(Assignment {+(Identifier)+} - {+( + {+(Statements {+(Integer)+} {+(Integer)+})+})+} {-(Assignment @@ -20,6 +20,6 @@ {-(Integer)-})-} {-(Assignment {-(Identifier)-} - {-( + {-(Statements {-(Integer)-} {-(Integer)-})-})-}) diff --git a/test/fixtures/python/corpus/assignment.parseA.txt b/test/fixtures/python/corpus/assignment.parseA.txt index d93fb0821..f0ffb8e02 100644 --- a/test/fixtures/python/corpus/assignment.parseA.txt +++ b/test/fixtures/python/corpus/assignment.parseA.txt @@ -3,14 +3,14 @@ (Identifier) (Integer)) (Assignment - ( + (Statements (Identifier) (Identifier)) - ( + (Statements (Integer) (Integer))) (Assignment (Identifier) - ( + (Statements (Integer) (Integer)))) diff --git a/test/fixtures/python/corpus/assignment.parseB.txt b/test/fixtures/python/corpus/assignment.parseB.txt index 38f765e34..bff44b92e 100644 --- a/test/fixtures/python/corpus/assignment.parseB.txt +++ b/test/fixtures/python/corpus/assignment.parseB.txt @@ -1,9 +1,9 @@ (Program (Assignment - ( + (Statements (Identifier) (Identifier)) - ( + (Statements (Integer) (Integer))) (Assignment @@ -11,6 +11,6 @@ (Integer)) (Assignment (Identifier) - ( + (Statements (Integer) (Integer)))) diff --git a/test/fixtures/python/corpus/concatenated-string.diffA-B.txt b/test/fixtures/python/corpus/concatenated-string.diffA-B.txt index d52ae0d35..e7430694b 100644 --- a/test/fixtures/python/corpus/concatenated-string.diffA-B.txt +++ b/test/fixtures/python/corpus/concatenated-string.diffA-B.txt @@ -1,5 +1,5 @@ (Program - ( + (Statements {-(TextElement)-} (TextElement) {+(TextElement)+} diff --git a/test/fixtures/python/corpus/concatenated-string.diffB-A.txt b/test/fixtures/python/corpus/concatenated-string.diffB-A.txt index 4387d6826..eccb0b1a1 100644 --- a/test/fixtures/python/corpus/concatenated-string.diffB-A.txt +++ b/test/fixtures/python/corpus/concatenated-string.diffB-A.txt @@ -1,5 +1,5 @@ (Program - ( + (Statements {-(TextElement)-} (TextElement) { (TextElement) diff --git a/test/fixtures/python/corpus/concatenated-string.parseA.txt b/test/fixtures/python/corpus/concatenated-string.parseA.txt index de9e080d5..acb17c616 100644 --- a/test/fixtures/python/corpus/concatenated-string.parseA.txt +++ b/test/fixtures/python/corpus/concatenated-string.parseA.txt @@ -1,5 +1,5 @@ (Program - ( + (Statements (TextElement) (TextElement) (TextElement))) diff --git a/test/fixtures/python/corpus/concatenated-string.parseB.txt b/test/fixtures/python/corpus/concatenated-string.parseB.txt index 64ca8c93b..fa4a37766 100644 --- a/test/fixtures/python/corpus/concatenated-string.parseB.txt +++ b/test/fixtures/python/corpus/concatenated-string.parseB.txt @@ -1,5 +1,5 @@ (Program - ( + (Statements (TextElement) (TextElement) (TextElement) diff --git a/test/fixtures/python/corpus/decorated-definition.diffA-B.txt b/test/fixtures/python/corpus/decorated-definition.diffA-B.txt index f0a6b4fb2..510db5649 100644 --- a/test/fixtures/python/corpus/decorated-definition.diffA-B.txt +++ b/test/fixtures/python/corpus/decorated-definition.diffA-B.txt @@ -6,7 +6,7 @@ ->(Identifier) } (Decorator (Identifier) - ([]) + (Statements) (Decorator { (Identifier) ->(Identifier) } @@ -16,12 +16,12 @@ { (Identifier) ->(Identifier) } {+(Identifier)+} - {-( + {-(Statements {-(Integer)-} {-(Integer)-})-} (Decorator (Identifier) - {+( + {+(Statements {+(Integer)+} {+(Assignment {+(Identifier)+} @@ -39,7 +39,7 @@ {-(Identifier)-} {-(Decorator {-(Identifier)-} - {-( + {-(Statements {-(Integer)-} {-(Assignment {-(Identifier)-} diff --git a/test/fixtures/python/corpus/decorated-definition.diffB-A.txt b/test/fixtures/python/corpus/decorated-definition.diffB-A.txt index 85a7a6104..bb3125542 100644 --- a/test/fixtures/python/corpus/decorated-definition.diffB-A.txt +++ b/test/fixtures/python/corpus/decorated-definition.diffB-A.txt @@ -6,7 +6,7 @@ ->(Identifier) } (Decorator (Identifier) - ([]) + (Statements) (Decorator { (Identifier) ->(Identifier) } @@ -15,7 +15,7 @@ (Decorator { (Identifier) ->(Identifier) } - {+( + {+(Statements {+(Integer)+} {+(Integer)+})+} {-(Identifier)-} @@ -24,7 +24,7 @@ {+(Assignment {+(Identifier)+} {+(Boolean)+})+} - {-( + {-(Statements {-(Integer)-} {-(Assignment {-(Identifier)-} @@ -44,7 +44,7 @@ {+(Identifier)+} {+(Decorator {+(Identifier)+} - {+( + {+(Statements {+(Integer)+} {+(Assignment {+(Identifier)+} diff --git a/test/fixtures/python/corpus/decorated-definition.parseA.txt b/test/fixtures/python/corpus/decorated-definition.parseA.txt index df00a660f..2250469bd 100644 --- a/test/fixtures/python/corpus/decorated-definition.parseA.txt +++ b/test/fixtures/python/corpus/decorated-definition.parseA.txt @@ -5,13 +5,13 @@ (Identifier) (Decorator (Identifier) - ([]) + (Statements) (Decorator (Identifier) (Integer) (Decorator (Identifier) - ( + (Statements (Integer) (Integer)) (Decorator @@ -27,7 +27,7 @@ (Identifier) (Decorator (Identifier) - ( + (Statements (Integer) (Assignment (Identifier) diff --git a/test/fixtures/python/corpus/decorated-definition.parseB.txt b/test/fixtures/python/corpus/decorated-definition.parseB.txt index d52f95e20..25ce8eb60 100644 --- a/test/fixtures/python/corpus/decorated-definition.parseB.txt +++ b/test/fixtures/python/corpus/decorated-definition.parseB.txt @@ -5,7 +5,7 @@ (Identifier) (Decorator (Identifier) - ([]) + (Statements) (Decorator (Identifier) (Identifier) @@ -14,7 +14,7 @@ (Identifier) (Decorator (Identifier) - ( + (Statements (Integer) (Assignment (Identifier) diff --git a/test/fixtures/python/corpus/dictionary-comprehension.diffA-B.txt b/test/fixtures/python/corpus/dictionary-comprehension.diffA-B.txt index 44b5c82b0..dc0803e7d 100644 --- a/test/fixtures/python/corpus/dictionary-comprehension.diffA-B.txt +++ b/test/fixtures/python/corpus/dictionary-comprehension.diffA-B.txt @@ -5,8 +5,8 @@ ->(Identifier) } { (Identifier) ->(Identifier) }) - ( - {+( + (Statements + {+(Statements {+(Identifier)+} {+(Identifier)+})+} { (Identifier) @@ -18,10 +18,10 @@ ->(Identifier) } { (Identifier) ->(Integer) }) - ( + (Statements {+(Identifier)+} {+(Identifier)+} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Identifier)-}))) diff --git a/test/fixtures/python/corpus/dictionary-comprehension.diffB-A.txt b/test/fixtures/python/corpus/dictionary-comprehension.diffB-A.txt index 932512545..80382a5a3 100644 --- a/test/fixtures/python/corpus/dictionary-comprehension.diffB-A.txt +++ b/test/fixtures/python/corpus/dictionary-comprehension.diffB-A.txt @@ -5,10 +5,10 @@ ->(Identifier) } { (Identifier) ->(Identifier) }) - ( + (Statements {+(Identifier)+} {+(Identifier)+} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Identifier)-})) @@ -18,8 +18,8 @@ ->(Identifier) } { (Integer) ->(Identifier) }) - ( - {+( + (Statements + {+(Statements {+(Identifier)+} {+(Identifier)+})+} { (Identifier) diff --git a/test/fixtures/python/corpus/dictionary-comprehension.parseA.txt b/test/fixtures/python/corpus/dictionary-comprehension.parseA.txt index 3cdfe0873..49a09e8d8 100644 --- a/test/fixtures/python/corpus/dictionary-comprehension.parseA.txt +++ b/test/fixtures/python/corpus/dictionary-comprehension.parseA.txt @@ -3,15 +3,15 @@ (KeyValue (Identifier) (Identifier)) - ( + (Statements (Identifier) (Identifier))) (Comprehension (KeyValue (Identifier) (Identifier)) - ( - ( + (Statements + (Statements (Identifier) (Identifier)) (Identifier)))) diff --git a/test/fixtures/python/corpus/dictionary-comprehension.parseB.txt b/test/fixtures/python/corpus/dictionary-comprehension.parseB.txt index a4da21d92..51e66945f 100644 --- a/test/fixtures/python/corpus/dictionary-comprehension.parseB.txt +++ b/test/fixtures/python/corpus/dictionary-comprehension.parseB.txt @@ -3,8 +3,8 @@ (KeyValue (Identifier) (Identifier)) - ( - ( + (Statements + (Statements (Identifier) (Identifier)) (Identifier))) @@ -12,6 +12,6 @@ (KeyValue (Identifier) (Integer)) - ( + (Statements (Identifier) (Identifier)))) diff --git a/test/fixtures/python/corpus/expression-statement.diffA-B.txt b/test/fixtures/python/corpus/expression-statement.diffA-B.txt index 260608ca3..ea55a1130 100644 --- a/test/fixtures/python/corpus/expression-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/expression-statement.diffA-B.txt @@ -3,12 +3,12 @@ {-(Plus {-(Identifier)-} {-(Identifier)-})-} - ( + (Statements (Integer) (Integer) (Integer)) {+(Identifier)+} - ( + (Statements {+(Integer)+} (Integer) (Integer) diff --git a/test/fixtures/python/corpus/expression-statement.diffB-A.txt b/test/fixtures/python/corpus/expression-statement.diffB-A.txt index 1bbccbc08..f4b01c082 100644 --- a/test/fixtures/python/corpus/expression-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/expression-statement.diffB-A.txt @@ -3,16 +3,16 @@ {+(Plus {+(Identifier)+} {+(Identifier)+})+} - ( + (Statements (Integer) (Integer) (Integer)) -{+( +{+(Statements {+(Integer)+} {+(Integer)+} {+(Integer)+})+} {-(Identifier)-} -{-( +{-(Statements {-(Integer)-} {-(Integer)-} {-(Integer)-})-} diff --git a/test/fixtures/python/corpus/expression-statement.parseA.txt b/test/fixtures/python/corpus/expression-statement.parseA.txt index 2a804df06..c0bc3ce18 100644 --- a/test/fixtures/python/corpus/expression-statement.parseA.txt +++ b/test/fixtures/python/corpus/expression-statement.parseA.txt @@ -3,11 +3,11 @@ (Plus (Identifier) (Identifier)) - ( + (Statements (Integer) (Integer) (Integer)) - ( + (Statements (Integer) (Integer) (Integer))) diff --git a/test/fixtures/python/corpus/expression-statement.parseB.txt b/test/fixtures/python/corpus/expression-statement.parseB.txt index 34dabf60b..e93d92934 100644 --- a/test/fixtures/python/corpus/expression-statement.parseB.txt +++ b/test/fixtures/python/corpus/expression-statement.parseB.txt @@ -1,10 +1,10 @@ (Program - ( + (Statements (Integer) (Integer) (Integer)) (Identifier) - ( + (Statements (Integer) (Integer) (Integer)) diff --git a/test/fixtures/python/corpus/for-statement.diffA-B.txt b/test/fixtures/python/corpus/for-statement.diffA-B.txt index b8d3a9af4..7513a42ec 100644 --- a/test/fixtures/python/corpus/for-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/for-statement.diffA-B.txt @@ -8,27 +8,27 @@ {+(Integer)+})+} {+(Tuple {+(Integer)+})+})+} - {+( + {+(Statements {+(Identifier)+})+})+} (Else (ForEach - ( + (Statements (Identifier) { (Identifier) ->(Identifier) }) (Identifier) - ( + (Statements (Call (Identifier) (Identifier) (Empty)) (ForEach - ( + (Statements (Identifier) { (Identifier) ->(Identifier) }) (Identifier) - ( + (Statements (Call (Identifier) (Identifier) @@ -47,5 +47,5 @@ {-(Integer)-})-} {-(Tuple {-(Integer)-})-})-} - {-( + {-(Statements {-(Identifier)-})-})-}) diff --git a/test/fixtures/python/corpus/for-statement.diffB-A.txt b/test/fixtures/python/corpus/for-statement.diffB-A.txt index b1a038936..19dd5c34f 100644 --- a/test/fixtures/python/corpus/for-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/for-statement.diffB-A.txt @@ -1,21 +1,21 @@ (Program {+(Else {+(ForEach - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Identifier)+} - {+( + {+(Statements {+(Call {+(Identifier)+} {+(Identifier)+} {+(Empty)+})+} {+(ForEach - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Identifier)+} - {+( + {+(Statements {+(Call {+(Identifier)+} {+(Identifier)+} @@ -34,26 +34,26 @@ (Integer)) (Tuple (Integer))) - ( + (Statements { (Identifier) ->(Identifier) })) {-(Else {-(ForEach - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Identifier)-} - {-( + {-(Statements {-(Call {-(Identifier)-} {-(Identifier)-} {-(Empty)-})-} {-(ForEach - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Identifier)-} - {-( + {-(Statements {-(Call {-(Identifier)-} {-(Identifier)-} diff --git a/test/fixtures/python/corpus/for-statement.parseA.txt b/test/fixtures/python/corpus/for-statement.parseA.txt index 6811bf720..59e599336 100644 --- a/test/fixtures/python/corpus/for-statement.parseA.txt +++ b/test/fixtures/python/corpus/for-statement.parseA.txt @@ -1,21 +1,21 @@ (Program (Else (ForEach - ( + (Statements (Identifier) (Identifier)) (Identifier) - ( + (Statements (Call (Identifier) (Identifier) (Empty)) (ForEach - ( + (Statements (Identifier) (Identifier)) (Identifier) - ( + (Statements (Call (Identifier) (Identifier) @@ -33,5 +33,5 @@ (Integer)) (Tuple (Integer))) - ( + (Statements (Identifier)))) diff --git a/test/fixtures/python/corpus/for-statement.parseB.txt b/test/fixtures/python/corpus/for-statement.parseB.txt index eb71bd86b..d48c01f77 100644 --- a/test/fixtures/python/corpus/for-statement.parseB.txt +++ b/test/fixtures/python/corpus/for-statement.parseB.txt @@ -8,25 +8,25 @@ (Integer)) (Tuple (Integer))) - ( + (Statements (Identifier))) (Else (ForEach - ( + (Statements (Identifier) (Identifier)) (Identifier) - ( + (Statements (Call (Identifier) (Identifier) (Empty)) (ForEach - ( + (Statements (Identifier) (Identifier)) (Identifier) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/generator-expression.diffA-B.txt b/test/fixtures/python/corpus/generator-expression.diffA-B.txt index 3484c5288..34837f585 100644 --- a/test/fixtures/python/corpus/generator-expression.diffA-B.txt +++ b/test/fixtures/python/corpus/generator-expression.diffA-B.txt @@ -2,7 +2,7 @@ (Comprehension { (Identifier) ->(Identifier) } - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) @@ -12,7 +12,7 @@ ->(Plus {+(Identifier)+} {+(Integer)+}) } - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) diff --git a/test/fixtures/python/corpus/generator-expression.diffB-A.txt b/test/fixtures/python/corpus/generator-expression.diffB-A.txt index d199e6c54..7cbbefea7 100644 --- a/test/fixtures/python/corpus/generator-expression.diffB-A.txt +++ b/test/fixtures/python/corpus/generator-expression.diffB-A.txt @@ -2,7 +2,7 @@ (Comprehension { (Identifier) ->(Identifier) } - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) @@ -12,7 +12,7 @@ {-(Identifier)-} {-(Integer)-}) ->(Identifier) } - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) diff --git a/test/fixtures/python/corpus/generator-expression.parseA.txt b/test/fixtures/python/corpus/generator-expression.parseA.txt index 5d0fe51fe..926348cdc 100644 --- a/test/fixtures/python/corpus/generator-expression.parseA.txt +++ b/test/fixtures/python/corpus/generator-expression.parseA.txt @@ -1,11 +1,11 @@ (Program (Comprehension (Identifier) - ( + (Statements (Identifier) (Identifier))) (Comprehension (Identifier) - ( + (Statements (Identifier) (Identifier)))) diff --git a/test/fixtures/python/corpus/generator-expression.parseB.txt b/test/fixtures/python/corpus/generator-expression.parseB.txt index 4d04bd87e..d5f7c1f64 100644 --- a/test/fixtures/python/corpus/generator-expression.parseB.txt +++ b/test/fixtures/python/corpus/generator-expression.parseB.txt @@ -1,13 +1,13 @@ (Program (Comprehension (Identifier) - ( + (Statements (Identifier) (Identifier))) (Comprehension (Plus (Identifier) (Integer)) - ( + (Statements (Identifier) (Identifier)))) diff --git a/test/fixtures/python/corpus/if-statement.diffA-B.txt b/test/fixtures/python/corpus/if-statement.diffA-B.txt index 4df75d39b..73708da79 100644 --- a/test/fixtures/python/corpus/if-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/if-statement.diffA-B.txt @@ -2,16 +2,16 @@ (If { (Identifier) ->(Identifier) } - ( + (Statements {+(Identifier)+} (Identifier) {-(Identifier)-}) { (If {-(Identifier)-} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-}) ->(Empty) })) diff --git a/test/fixtures/python/corpus/if-statement.diffB-A.txt b/test/fixtures/python/corpus/if-statement.diffB-A.txt index f054256a7..c604cad8a 100644 --- a/test/fixtures/python/corpus/if-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/if-statement.diffB-A.txt @@ -2,16 +2,16 @@ (If { (Identifier) ->(Identifier) } - ( + (Statements {-(Identifier)-} (Identifier) {+(Identifier)+}) { (Empty) ->(If {+(Identifier)+} - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+}) })) diff --git a/test/fixtures/python/corpus/if-statement.parseA.txt b/test/fixtures/python/corpus/if-statement.parseA.txt index fb5df2197..97223d23b 100644 --- a/test/fixtures/python/corpus/if-statement.parseA.txt +++ b/test/fixtures/python/corpus/if-statement.parseA.txt @@ -1,14 +1,14 @@ (Program (If (Identifier) - ( + (Statements (Identifier) (Identifier)) (If (Identifier) - ( + (Statements (Identifier) (Identifier)) - ( + (Statements (Identifier) (Identifier))))) diff --git a/test/fixtures/python/corpus/if-statement.parseB.txt b/test/fixtures/python/corpus/if-statement.parseB.txt index 7bde4e191..14179ed8a 100644 --- a/test/fixtures/python/corpus/if-statement.parseB.txt +++ b/test/fixtures/python/corpus/if-statement.parseB.txt @@ -1,7 +1,7 @@ (Program (If (Identifier) - ( + (Statements (Identifier) (Identifier)) (Empty))) diff --git a/test/fixtures/python/corpus/import-statement.diffA-B.txt b/test/fixtures/python/corpus/import-statement.diffA-B.txt index 5ded7d2a8..b6263e2ee 100644 --- a/test/fixtures/python/corpus/import-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/import-statement.diffA-B.txt @@ -1,5 +1,5 @@ (Program - ( + (Statements {+(QualifiedImport)+} (QualifiedImport) {-(QualifiedAliasedImport @@ -7,7 +7,7 @@ {+(QualifiedAliasedImport {+(Identifier)+})+} {+(QualifiedImport)+} -{-( +{-(Statements {-(QualifiedAliasedImport {-(Identifier)-})-} {-(QualifiedImport)-})-} diff --git a/test/fixtures/python/corpus/import-statement.diffB-A.txt b/test/fixtures/python/corpus/import-statement.diffB-A.txt index 0ee92833f..66546a122 100644 --- a/test/fixtures/python/corpus/import-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/import-statement.diffB-A.txt @@ -1,10 +1,10 @@ (Program - ( + (Statements {-(QualifiedImport)-} (QualifiedImport) {+(QualifiedAliasedImport {+(Identifier)+})+}) -{+( +{+(Statements {+(QualifiedAliasedImport {+(Identifier)+})+} {+(QualifiedImport)+})+} diff --git a/test/fixtures/python/corpus/import-statement.parseA.txt b/test/fixtures/python/corpus/import-statement.parseA.txt index e6a5033b1..cd5a2f551 100644 --- a/test/fixtures/python/corpus/import-statement.parseA.txt +++ b/test/fixtures/python/corpus/import-statement.parseA.txt @@ -1,9 +1,9 @@ (Program - ( + (Statements (QualifiedImport) (QualifiedAliasedImport (Identifier))) - ( + (Statements (QualifiedAliasedImport (Identifier)) (QualifiedImport)) diff --git a/test/fixtures/python/corpus/import-statement.parseB.txt b/test/fixtures/python/corpus/import-statement.parseB.txt index 39daaa1db..ff6acffe2 100644 --- a/test/fixtures/python/corpus/import-statement.parseB.txt +++ b/test/fixtures/python/corpus/import-statement.parseB.txt @@ -1,5 +1,5 @@ (Program - ( + (Statements (QualifiedImport) (QualifiedImport)) (QualifiedAliasedImport diff --git a/test/fixtures/python/corpus/list-comprehension.diffA-B.txt b/test/fixtures/python/corpus/list-comprehension.diffA-B.txt index a5801dc53..a47830074 100644 --- a/test/fixtures/python/corpus/list-comprehension.diffA-B.txt +++ b/test/fixtures/python/corpus/list-comprehension.diffA-B.txt @@ -2,14 +2,14 @@ (Comprehension { (Identifier) ->(Identifier) } - ( - {+( + (Statements + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Call {+(Identifier)+} {+(Empty)+})+} - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Call @@ -22,10 +22,10 @@ ->(Plus {+(Identifier)+} {+(Integer)+}) } - ( + (Statements {+(Identifier)+} {+(Identifier)+} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Identifier)-}))) diff --git a/test/fixtures/python/corpus/list-comprehension.diffB-A.txt b/test/fixtures/python/corpus/list-comprehension.diffB-A.txt index a3c181151..fc4c064af 100644 --- a/test/fixtures/python/corpus/list-comprehension.diffB-A.txt +++ b/test/fixtures/python/corpus/list-comprehension.diffB-A.txt @@ -2,16 +2,16 @@ (Comprehension { (Identifier) ->(Identifier) } - ( + (Statements {+(Identifier)+} {+(Identifier)+} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Call {-(Identifier)-} {-(Empty)-})-} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Call @@ -22,8 +22,8 @@ {-(Identifier)-} {-(Integer)-}) ->(Identifier) } - ( - {+( + (Statements + {+(Statements {+(Identifier)+} {+(Identifier)+})+} { (Identifier) diff --git a/test/fixtures/python/corpus/list-comprehension.parseA.txt b/test/fixtures/python/corpus/list-comprehension.parseA.txt index dd0a83238..927e76638 100644 --- a/test/fixtures/python/corpus/list-comprehension.parseA.txt +++ b/test/fixtures/python/corpus/list-comprehension.parseA.txt @@ -1,13 +1,13 @@ (Program (Comprehension (Identifier) - ( + (Statements (Identifier) (Identifier))) (Comprehension (Identifier) - ( - ( + (Statements + (Statements (Identifier) (Identifier)) (Identifier)))) diff --git a/test/fixtures/python/corpus/list-comprehension.parseB.txt b/test/fixtures/python/corpus/list-comprehension.parseB.txt index de2c92ee8..59256c488 100644 --- a/test/fixtures/python/corpus/list-comprehension.parseB.txt +++ b/test/fixtures/python/corpus/list-comprehension.parseB.txt @@ -1,14 +1,14 @@ (Program (Comprehension (Identifier) - ( - ( + (Statements + (Statements (Identifier) (Identifier)) (Call (Identifier) (Empty)) - ( + (Statements (Identifier) (Identifier)) (Call @@ -18,6 +18,6 @@ (Plus (Identifier) (Integer)) - ( + (Statements (Identifier) (Identifier)))) diff --git a/test/fixtures/python/corpus/raise-statement.diffA-B.txt b/test/fixtures/python/corpus/raise-statement.diffA-B.txt index 35e466cf8..a05bf8019 100644 --- a/test/fixtures/python/corpus/raise-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/raise-statement.diffA-B.txt @@ -5,21 +5,21 @@ {+(TextElement)+} {+(Empty)+})+})+} {+(Throw - {+( + {+(Statements {+(Call {+(Identifier)+} {+(TextElement)+} {+(Empty)+})+} {+(Identifier)+})+})+} (Throw - ([])) + (Statements)) {-(Throw {-(Call {-(Identifier)-} {-(TextElement)-} {-(Empty)-})-})-} {-(Throw - {-( + {-(Statements {-(Call {-(Identifier)-} {-(TextElement)-} diff --git a/test/fixtures/python/corpus/raise-statement.diffB-A.txt b/test/fixtures/python/corpus/raise-statement.diffB-A.txt index 48863f31f..2217380cb 100644 --- a/test/fixtures/python/corpus/raise-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/raise-statement.diffB-A.txt @@ -5,21 +5,21 @@ {-(TextElement)-} {-(Empty)-})-})-} {-(Throw - {-( + {-(Statements {-(Call {-(Identifier)-} {-(TextElement)-} {-(Empty)-})-} {-(Identifier)-})-})-} (Throw - ([])) + (Statements)) {+(Throw {+(Call {+(Identifier)+} {+(TextElement)+} {+(Empty)+})+})+} {+(Throw - {+( + {+(Statements {+(Call {+(Identifier)+} {+(TextElement)+} diff --git a/test/fixtures/python/corpus/raise-statement.parseA.txt b/test/fixtures/python/corpus/raise-statement.parseA.txt index b0ba84d68..c3f6865e0 100644 --- a/test/fixtures/python/corpus/raise-statement.parseA.txt +++ b/test/fixtures/python/corpus/raise-statement.parseA.txt @@ -1,13 +1,13 @@ (Program (Throw - ([])) + (Statements)) (Throw (Call (Identifier) (TextElement) (Empty))) (Throw - ( + (Statements (Call (Identifier) (TextElement) diff --git a/test/fixtures/python/corpus/raise-statement.parseB.txt b/test/fixtures/python/corpus/raise-statement.parseB.txt index 07853776a..2f21ece90 100644 --- a/test/fixtures/python/corpus/raise-statement.parseB.txt +++ b/test/fixtures/python/corpus/raise-statement.parseB.txt @@ -5,11 +5,11 @@ (TextElement) (Empty))) (Throw - ( + (Statements (Call (Identifier) (TextElement) (Empty)) (Identifier))) (Throw - ([]))) + (Statements))) diff --git a/test/fixtures/python/corpus/return-statement.diffA-B.txt b/test/fixtures/python/corpus/return-statement.diffA-B.txt index 0798a925c..b346595d2 100644 --- a/test/fixtures/python/corpus/return-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/return-statement.diffA-B.txt @@ -1,6 +1,6 @@ (Program {+(Return - {+( + {+(Statements {+(Plus {+(Identifier)+} {+(Identifier)+})+} @@ -8,7 +8,7 @@ (Return (Empty)) (Return - { ( + { (Statements {-(Plus {-(Identifier)-} {-(Identifier)-})-} diff --git a/test/fixtures/python/corpus/return-statement.diffB-A.txt b/test/fixtures/python/corpus/return-statement.diffB-A.txt index d9a15a3d4..44783eaaa 100644 --- a/test/fixtures/python/corpus/return-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/return-statement.diffB-A.txt @@ -1,6 +1,6 @@ (Program {-(Return - {-( + {-(Statements {-(Plus {-(Identifier)-} {-(Identifier)-})-} @@ -10,7 +10,7 @@ (Return { (Not {-(Identifier)-}) - ->( + ->(Statements {+(Plus {+(Identifier)+} {+(Identifier)+})+} diff --git a/test/fixtures/python/corpus/return-statement.parseA.txt b/test/fixtures/python/corpus/return-statement.parseA.txt index db83de41e..581590159 100644 --- a/test/fixtures/python/corpus/return-statement.parseA.txt +++ b/test/fixtures/python/corpus/return-statement.parseA.txt @@ -2,7 +2,7 @@ (Return (Empty)) (Return - ( + (Statements (Plus (Identifier) (Identifier)) diff --git a/test/fixtures/python/corpus/return-statement.parseB.txt b/test/fixtures/python/corpus/return-statement.parseB.txt index 10e570c6b..bf6bee6ed 100644 --- a/test/fixtures/python/corpus/return-statement.parseB.txt +++ b/test/fixtures/python/corpus/return-statement.parseB.txt @@ -1,6 +1,6 @@ (Program (Return - ( + (Statements (Plus (Identifier) (Identifier)) diff --git a/test/fixtures/python/corpus/set-comprehension.diffA-B.txt b/test/fixtures/python/corpus/set-comprehension.diffA-B.txt index 3484c5288..34837f585 100644 --- a/test/fixtures/python/corpus/set-comprehension.diffA-B.txt +++ b/test/fixtures/python/corpus/set-comprehension.diffA-B.txt @@ -2,7 +2,7 @@ (Comprehension { (Identifier) ->(Identifier) } - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) @@ -12,7 +12,7 @@ ->(Plus {+(Identifier)+} {+(Integer)+}) } - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) diff --git a/test/fixtures/python/corpus/set-comprehension.diffB-A.txt b/test/fixtures/python/corpus/set-comprehension.diffB-A.txt index d199e6c54..7cbbefea7 100644 --- a/test/fixtures/python/corpus/set-comprehension.diffB-A.txt +++ b/test/fixtures/python/corpus/set-comprehension.diffB-A.txt @@ -2,7 +2,7 @@ (Comprehension { (Identifier) ->(Identifier) } - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) @@ -12,7 +12,7 @@ {-(Identifier)-} {-(Integer)-}) ->(Identifier) } - ( + (Statements { (Identifier) ->(Identifier) } { (Identifier) diff --git a/test/fixtures/python/corpus/set-comprehension.parseA.txt b/test/fixtures/python/corpus/set-comprehension.parseA.txt index 5d0fe51fe..926348cdc 100644 --- a/test/fixtures/python/corpus/set-comprehension.parseA.txt +++ b/test/fixtures/python/corpus/set-comprehension.parseA.txt @@ -1,11 +1,11 @@ (Program (Comprehension (Identifier) - ( + (Statements (Identifier) (Identifier))) (Comprehension (Identifier) - ( + (Statements (Identifier) (Identifier)))) diff --git a/test/fixtures/python/corpus/set-comprehension.parseB.txt b/test/fixtures/python/corpus/set-comprehension.parseB.txt index 4d04bd87e..d5f7c1f64 100644 --- a/test/fixtures/python/corpus/set-comprehension.parseB.txt +++ b/test/fixtures/python/corpus/set-comprehension.parseB.txt @@ -1,13 +1,13 @@ (Program (Comprehension (Identifier) - ( + (Statements (Identifier) (Identifier))) (Comprehension (Plus (Identifier) (Integer)) - ( + (Statements (Identifier) (Identifier)))) diff --git a/test/fixtures/python/corpus/try-statement.diffA-B.txt b/test/fixtures/python/corpus/try-statement.diffA-B.txt index ab0d4b8a8..386b10bc4 100644 --- a/test/fixtures/python/corpus/try-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/try-statement.diffA-B.txt @@ -6,39 +6,39 @@ {+(Identifier)+})+} {-(Identifier)-} {-(Catch - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-} {-(Identifier)-})-} - {-([])-})-} + {-(Statements)-})-} {-(Catch {-(Let {-(Identifier)-} {-(Identifier)-} {-(Empty)-})-} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-})-} {-(Catch - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-} {-(Identifier)-} {-(Identifier)-})-} - {-([])-})-} + {-(Statements)-})-} {-(Catch - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} - {-([])-})-}) + {-(Statements)-})-}) (Try { (Identifier) ->(Identifier) } {+(Catch - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} - {+([])+})+} + {+(Statements)+})+} {+(Catch {+(Let {+(Identifier)+} @@ -46,16 +46,16 @@ {+(Empty)+})+} {+(Identifier)+})+} {+(Catch - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+} {+(Identifier)+})+} - {+([])+})+} + {+(Statements)+})+} {+(Catch {+(Identifier)+} - {+([])+})+} + {+(Statements)+})+} {-(Identifier)-} {-(Finally - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-})-})) diff --git a/test/fixtures/python/corpus/try-statement.diffB-A.txt b/test/fixtures/python/corpus/try-statement.diffB-A.txt index 50f6d6864..6505dab19 100644 --- a/test/fixtures/python/corpus/try-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/try-statement.diffB-A.txt @@ -4,31 +4,31 @@ ->(Identifier) } {+(Identifier)+} {+(Catch - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+} {+(Identifier)+})+} - {+([])+})+} + {+(Statements)+})+} {+(Catch {+(Let {+(Identifier)+} {+(Identifier)+} {+(Empty)+})+} - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+})+} {+(Catch - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+} {+(Identifier)+} {+(Identifier)+})+} - {+([])+})+} + {+(Statements)+})+} {+(Catch - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} - {+([])+})+} + {+(Statements)+})+} {-(Finally {-(Identifier)-})-}) (Try @@ -36,14 +36,14 @@ ->(Identifier) } {+(Identifier)+} {+(Finally - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+})+} {-(Catch - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} - {-([])-})-} + {-(Statements)-})-} {-(Catch {-(Let {-(Identifier)-} @@ -51,11 +51,11 @@ {-(Empty)-})-} {-(Identifier)-})-} {-(Catch - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-} {-(Identifier)-})-} - {-([])-})-} + {-(Statements)-})-} {-(Catch {-(Identifier)-} - {-([])-})-})) + {-(Statements)-})-})) diff --git a/test/fixtures/python/corpus/try-statement.parseA.txt b/test/fixtures/python/corpus/try-statement.parseA.txt index 027fdec43..57f428a7f 100644 --- a/test/fixtures/python/corpus/try-statement.parseA.txt +++ b/test/fixtures/python/corpus/try-statement.parseA.txt @@ -3,35 +3,35 @@ (Identifier) (Identifier) (Catch - ( + (Statements (Identifier) (Identifier) (Identifier)) - ([])) + (Statements)) (Catch (Let (Identifier) (Identifier) (Empty)) - ( + (Statements (Identifier) (Identifier))) (Catch - ( + (Statements (Identifier) (Identifier) (Identifier) (Identifier)) - ([])) + (Statements)) (Catch - ( + (Statements (Identifier) (Identifier)) - ([]))) + (Statements))) (Try (Identifier) (Identifier) (Finally - ( + (Statements (Identifier) (Identifier))))) diff --git a/test/fixtures/python/corpus/try-statement.parseB.txt b/test/fixtures/python/corpus/try-statement.parseB.txt index 77180043b..1eefadf9b 100644 --- a/test/fixtures/python/corpus/try-statement.parseB.txt +++ b/test/fixtures/python/corpus/try-statement.parseB.txt @@ -6,10 +6,10 @@ (Try (Identifier) (Catch - ( + (Statements (Identifier) (Identifier)) - ([])) + (Statements)) (Catch (Let (Identifier) @@ -17,11 +17,11 @@ (Empty)) (Identifier)) (Catch - ( + (Statements (Identifier) (Identifier) (Identifier)) - ([])) + (Statements)) (Catch (Identifier) - ([])))) + (Statements)))) diff --git a/test/fixtures/python/corpus/while-statement.diffA-B.txt b/test/fixtures/python/corpus/while-statement.diffA-B.txt index c49fe2352..29439f949 100644 --- a/test/fixtures/python/corpus/while-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/while-statement.diffA-B.txt @@ -2,7 +2,7 @@ (While { (Identifier) ->(Identifier) } - ( + (Statements {-(NoOp {-(Empty)-})-} (Break diff --git a/test/fixtures/python/corpus/while-statement.diffB-A.txt b/test/fixtures/python/corpus/while-statement.diffB-A.txt index bce43a580..8fde658c7 100644 --- a/test/fixtures/python/corpus/while-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/while-statement.diffB-A.txt @@ -2,7 +2,7 @@ (While { (Identifier) ->(Identifier) } - ( + (Statements {+(NoOp {+(Empty)+})+} (Break diff --git a/test/fixtures/python/corpus/while-statement.parseA.txt b/test/fixtures/python/corpus/while-statement.parseA.txt index 8fd702c80..bdfdc70cc 100644 --- a/test/fixtures/python/corpus/while-statement.parseA.txt +++ b/test/fixtures/python/corpus/while-statement.parseA.txt @@ -1,7 +1,7 @@ (Program (While (Identifier) - ( + (Statements (NoOp (Empty)) (Break diff --git a/test/fixtures/python/corpus/while-statement.parseB.txt b/test/fixtures/python/corpus/while-statement.parseB.txt index 7db912d69..05289b27e 100644 --- a/test/fixtures/python/corpus/while-statement.parseB.txt +++ b/test/fixtures/python/corpus/while-statement.parseB.txt @@ -1,7 +1,7 @@ (Program (While (Identifier) - ( + (Statements (Break (Empty)) (Continue diff --git a/test/fixtures/python/corpus/with-statement.diffA-B.txt b/test/fixtures/python/corpus/with-statement.diffA-B.txt index 7e25d1e9e..aad270979 100644 --- a/test/fixtures/python/corpus/with-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/with-statement.diffA-B.txt @@ -4,6 +4,6 @@ ->(Identifier) } { (Identifier) ->(Identifier) } - ( + (Statements { (Identifier) ->(Identifier) }))) diff --git a/test/fixtures/python/corpus/with-statement.diffB-A.txt b/test/fixtures/python/corpus/with-statement.diffB-A.txt index 7e25d1e9e..aad270979 100644 --- a/test/fixtures/python/corpus/with-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/with-statement.diffB-A.txt @@ -4,6 +4,6 @@ ->(Identifier) } { (Identifier) ->(Identifier) } - ( + (Statements { (Identifier) ->(Identifier) }))) diff --git a/test/fixtures/python/corpus/with-statement.parseA.txt b/test/fixtures/python/corpus/with-statement.parseA.txt index 9491e1fd5..bc2fe3e49 100644 --- a/test/fixtures/python/corpus/with-statement.parseA.txt +++ b/test/fixtures/python/corpus/with-statement.parseA.txt @@ -2,5 +2,5 @@ (Let (Identifier) (Identifier) - ( + (Statements (Identifier)))) diff --git a/test/fixtures/python/corpus/with-statement.parseB.txt b/test/fixtures/python/corpus/with-statement.parseB.txt index 9491e1fd5..bc2fe3e49 100644 --- a/test/fixtures/python/corpus/with-statement.parseB.txt +++ b/test/fixtures/python/corpus/with-statement.parseB.txt @@ -2,5 +2,5 @@ (Let (Identifier) (Identifier) - ( + (Statements (Identifier)))) diff --git a/test/fixtures/python/corpus/with.diffA-B.txt b/test/fixtures/python/corpus/with.diffA-B.txt index cbe67a91b..201cc0ac9 100644 --- a/test/fixtures/python/corpus/with.diffA-B.txt +++ b/test/fixtures/python/corpus/with.diffA-B.txt @@ -10,18 +10,18 @@ ->(MemberAccess {+(Identifier)+} {+(Identifier)+}) } - ( + (Statements (Assignment (Identifier) (Boolean)) {-(ForEach {-(Identifier)-} {-(Identifier)-} - {-( + {-(Statements {-(Assignment {-(Identifier)-} {-(Boolean)-})-})-})-})) -{+( +{+(Statements {+(Let {+(Empty)+} {+(Call @@ -32,7 +32,7 @@ {+(TextElement)+} {+(Identifier)+} {+(Empty)+})+} - {+([])+})+} + {+(Statements)+})+} {+(Let {+(Empty)+} {+(Call @@ -43,5 +43,5 @@ {+(TextElement)+} {+(Identifier)+} {+(Empty)+})+} - {+( + {+(Statements {+(Identifier)+})+})+})+}) diff --git a/test/fixtures/python/corpus/with.diffB-A.txt b/test/fixtures/python/corpus/with.diffB-A.txt index 66585dba9..0171c4924 100644 --- a/test/fixtures/python/corpus/with.diffB-A.txt +++ b/test/fixtures/python/corpus/with.diffB-A.txt @@ -10,18 +10,18 @@ {+(Identifier)+} {+(TextElement)+} {+(Empty)+}) } - ( + (Statements (Assignment (Identifier) (Boolean)) {+(ForEach {+(Identifier)+} {+(Identifier)+} - {+( + {+(Statements {+(Assignment {+(Identifier)+} {+(Boolean)+})+})+})+})) -{-( +{-(Statements {-(Let {-(Empty)-} {-(Call @@ -32,7 +32,7 @@ {-(TextElement)-} {-(Identifier)-} {-(Empty)-})-} - {-([])-})-} + {-(Statements)-})-} {-(Let {-(Empty)-} {-(Call @@ -43,5 +43,5 @@ {-(TextElement)-} {-(Identifier)-} {-(Empty)-})-} - {-( + {-(Statements {-(Identifier)-})-})-})-}) diff --git a/test/fixtures/python/corpus/with.parseA.txt b/test/fixtures/python/corpus/with.parseA.txt index b417c619c..edc854479 100644 --- a/test/fixtures/python/corpus/with.parseA.txt +++ b/test/fixtures/python/corpus/with.parseA.txt @@ -6,14 +6,14 @@ (Identifier) (TextElement) (Empty)) - ( + (Statements (Assignment (Identifier) (Boolean)) (ForEach (Identifier) (Identifier) - ( + (Statements (Assignment (Identifier) (Boolean))))))) diff --git a/test/fixtures/python/corpus/with.parseB.txt b/test/fixtures/python/corpus/with.parseB.txt index 44dbdfaee..23dcb54a1 100644 --- a/test/fixtures/python/corpus/with.parseB.txt +++ b/test/fixtures/python/corpus/with.parseB.txt @@ -4,11 +4,11 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements (Assignment (Identifier) (Boolean)))) - ( + (Statements (Let (Empty) (Call @@ -19,7 +19,7 @@ (TextElement) (Identifier) (Empty)) - ([])) + (Statements)) (Let (Empty) (Call @@ -30,5 +30,5 @@ (TextElement) (Identifier) (Empty)) - ( + (Statements (Identifier))))) diff --git a/test/fixtures/ruby/corpus/begin.diffA-B.txt b/test/fixtures/ruby/corpus/begin.diffA-B.txt index 1bec5bc39..4f983b578 100644 --- a/test/fixtures/ruby/corpus/begin.diffA-B.txt +++ b/test/fixtures/ruby/corpus/begin.diffA-B.txt @@ -2,9 +2,9 @@ (Method (Empty) (Identifier) - ( + (Statements (Try - { ([]) + { (Statements) ->(Send {+(Identifier)+} {+(TextElement)+}) })))) diff --git a/test/fixtures/ruby/corpus/begin.diffB-A.txt b/test/fixtures/ruby/corpus/begin.diffB-A.txt index 49fcd5397..623e25948 100644 --- a/test/fixtures/ruby/corpus/begin.diffB-A.txt +++ b/test/fixtures/ruby/corpus/begin.diffB-A.txt @@ -2,9 +2,9 @@ (Method (Empty) (Identifier) - ( + (Statements (Try { (Send {-(Identifier)-} {-(TextElement)-}) - ->([]) })))) + ->(Statements) })))) diff --git a/test/fixtures/ruby/corpus/begin.parseA.txt b/test/fixtures/ruby/corpus/begin.parseA.txt index 29c538f66..806a217d3 100644 --- a/test/fixtures/ruby/corpus/begin.parseA.txt +++ b/test/fixtures/ruby/corpus/begin.parseA.txt @@ -2,6 +2,6 @@ (Method (Empty) (Identifier) - ( + (Statements (Try - ([]))))) + (Statements))))) diff --git a/test/fixtures/ruby/corpus/begin.parseB.txt b/test/fixtures/ruby/corpus/begin.parseB.txt index b59119d4d..41a6a6fb2 100644 --- a/test/fixtures/ruby/corpus/begin.parseB.txt +++ b/test/fixtures/ruby/corpus/begin.parseB.txt @@ -2,7 +2,7 @@ (Method (Empty) (Identifier) - ( + (Statements (Try (Send (Identifier) diff --git a/test/fixtures/ruby/corpus/chained-string.parseA.txt b/test/fixtures/ruby/corpus/chained-string.parseA.txt index 13446218a..19e02b4a3 100644 --- a/test/fixtures/ruby/corpus/chained-string.parseA.txt +++ b/test/fixtures/ruby/corpus/chained-string.parseA.txt @@ -1,4 +1,4 @@ (Program - ( + (Statements (TextElement) (TextElement))) diff --git a/test/fixtures/ruby/corpus/class.diffA-B.txt b/test/fixtures/ruby/corpus/class.diffA-B.txt index 6a81deb4f..55399d0a4 100644 --- a/test/fixtures/ruby/corpus/class.diffA-B.txt +++ b/test/fixtures/ruby/corpus/class.diffA-B.txt @@ -5,9 +5,9 @@ (Method (Empty) (Identifier) - ([]))) + (Statements))) {-(Class {-(ScopeResolution {-(Identifier)-} {-(Identifier)-})-} - {-([])-})-}) + {-(Statements)-})-}) diff --git a/test/fixtures/ruby/corpus/class.diffB-A.txt b/test/fixtures/ruby/corpus/class.diffB-A.txt index 06b31c46d..ab35adee4 100644 --- a/test/fixtures/ruby/corpus/class.diffB-A.txt +++ b/test/fixtures/ruby/corpus/class.diffB-A.txt @@ -5,9 +5,9 @@ (Method (Empty) (Identifier) - ([]))) + (Statements))) {+(Class {+(ScopeResolution {+(Identifier)+} {+(Identifier)+})+} - {+([])+})+}) + {+(Statements)+})+}) diff --git a/test/fixtures/ruby/corpus/class.parseA.txt b/test/fixtures/ruby/corpus/class.parseA.txt index ad160990d..f6d5f0629 100644 --- a/test/fixtures/ruby/corpus/class.parseA.txt +++ b/test/fixtures/ruby/corpus/class.parseA.txt @@ -5,9 +5,9 @@ (Method (Empty) (Identifier) - ([]))) + (Statements))) (Class (ScopeResolution (Identifier) (Identifier)) - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/class.parseB.txt b/test/fixtures/ruby/corpus/class.parseB.txt index d50a18324..5b8137020 100644 --- a/test/fixtures/ruby/corpus/class.parseB.txt +++ b/test/fixtures/ruby/corpus/class.parseB.txt @@ -4,4 +4,4 @@ (Method (Empty) (Identifier) - ([])))) + (Statements)))) diff --git a/test/fixtures/ruby/corpus/else.diffA-B.txt b/test/fixtures/ruby/corpus/else.diffA-B.txt index 5749e4f84..d6cdeb537 100644 --- a/test/fixtures/ruby/corpus/else.diffA-B.txt +++ b/test/fixtures/ruby/corpus/else.diffA-B.txt @@ -1,10 +1,10 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Else (Empty) - { ([]) + { (Statements) ->(Send {+(Identifier)+}) })))) diff --git a/test/fixtures/ruby/corpus/else.diffB-A.txt b/test/fixtures/ruby/corpus/else.diffB-A.txt index 147cfbfbd..0b124ce02 100644 --- a/test/fixtures/ruby/corpus/else.diffB-A.txt +++ b/test/fixtures/ruby/corpus/else.diffB-A.txt @@ -1,10 +1,10 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Else (Empty) { (Send {-(Identifier)-}) - ->([]) })))) + ->(Statements) })))) diff --git a/test/fixtures/ruby/corpus/else.parseA.txt b/test/fixtures/ruby/corpus/else.parseA.txt index edf25207d..1db3bb723 100644 --- a/test/fixtures/ruby/corpus/else.parseA.txt +++ b/test/fixtures/ruby/corpus/else.parseA.txt @@ -1,8 +1,8 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Else (Empty) - ([]))))) + (Statements))))) diff --git a/test/fixtures/ruby/corpus/else.parseB.txt b/test/fixtures/ruby/corpus/else.parseB.txt index 28eaf190d..53227067f 100644 --- a/test/fixtures/ruby/corpus/else.parseB.txt +++ b/test/fixtures/ruby/corpus/else.parseB.txt @@ -1,6 +1,6 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Else diff --git a/test/fixtures/ruby/corpus/elsif.diffA-B.txt b/test/fixtures/ruby/corpus/elsif.diffA-B.txt index 7e659a08e..1b0d86d2d 100644 --- a/test/fixtures/ruby/corpus/elsif.diffA-B.txt +++ b/test/fixtures/ruby/corpus/elsif.diffA-B.txt @@ -2,13 +2,13 @@ (If (Send (Identifier)) - ( + (Statements (Send (Identifier))) (If (Send (Identifier)) - ( + (Statements {+(Send {+(Identifier)+})+}) (Empty)))) diff --git a/test/fixtures/ruby/corpus/elsif.diffB-A.txt b/test/fixtures/ruby/corpus/elsif.diffB-A.txt index d5e8d9b3f..46dc82c55 100644 --- a/test/fixtures/ruby/corpus/elsif.diffB-A.txt +++ b/test/fixtures/ruby/corpus/elsif.diffB-A.txt @@ -2,12 +2,13 @@ (If (Send (Identifier)) - ( + (Statements (Send (Identifier))) (If (Send (Identifier)) - ({-(Send + (Statements + {-(Send {-(Identifier)-})-}) (Empty)))) diff --git a/test/fixtures/ruby/corpus/elsif.parseA.txt b/test/fixtures/ruby/corpus/elsif.parseA.txt index 0dfc7558b..dcb8c47b7 100644 --- a/test/fixtures/ruby/corpus/elsif.parseA.txt +++ b/test/fixtures/ruby/corpus/elsif.parseA.txt @@ -2,11 +2,11 @@ (If (Send (Identifier)) - ( + (Statements (Send (Identifier))) (If (Send (Identifier)) - ([]) + (Statements) (Empty)))) diff --git a/test/fixtures/ruby/corpus/elsif.parseB.txt b/test/fixtures/ruby/corpus/elsif.parseB.txt index 88c665a03..2ef63a59e 100644 --- a/test/fixtures/ruby/corpus/elsif.parseB.txt +++ b/test/fixtures/ruby/corpus/elsif.parseB.txt @@ -2,13 +2,13 @@ (If (Send (Identifier)) - ( + (Statements (Send (Identifier))) (If (Send (Identifier)) - ( + (Statements (Send (Identifier))) (Empty)))) diff --git a/test/fixtures/ruby/corpus/ensure.diffA-B.txt b/test/fixtures/ruby/corpus/ensure.diffA-B.txt index f2eca4a32..c47d54df8 100644 --- a/test/fixtures/ruby/corpus/ensure.diffA-B.txt +++ b/test/fixtures/ruby/corpus/ensure.diffA-B.txt @@ -1,9 +1,9 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Finally - { ([]) + { (Statements) ->(Send {+(Identifier)+}) })))) diff --git a/test/fixtures/ruby/corpus/ensure.diffB-A.txt b/test/fixtures/ruby/corpus/ensure.diffB-A.txt index 9264966b3..5c8fe9c24 100644 --- a/test/fixtures/ruby/corpus/ensure.diffB-A.txt +++ b/test/fixtures/ruby/corpus/ensure.diffB-A.txt @@ -1,9 +1,9 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Finally { (Send {-(Identifier)-}) - ->([]) })))) + ->(Statements) })))) diff --git a/test/fixtures/ruby/corpus/ensure.parseA.txt b/test/fixtures/ruby/corpus/ensure.parseA.txt index 524c181ef..d9ac44bc3 100644 --- a/test/fixtures/ruby/corpus/ensure.parseA.txt +++ b/test/fixtures/ruby/corpus/ensure.parseA.txt @@ -1,7 +1,7 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Finally - ([]))))) + (Statements))))) diff --git a/test/fixtures/ruby/corpus/ensure.parseB.txt b/test/fixtures/ruby/corpus/ensure.parseB.txt index 3f3ef470b..2dbf9e402 100644 --- a/test/fixtures/ruby/corpus/ensure.parseB.txt +++ b/test/fixtures/ruby/corpus/ensure.parseB.txt @@ -1,6 +1,6 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Finally diff --git a/test/fixtures/ruby/corpus/for.diffA-B.txt b/test/fixtures/ruby/corpus/for.diffA-B.txt index d2865da18..0b93f83b4 100644 --- a/test/fixtures/ruby/corpus/for.diffA-B.txt +++ b/test/fixtures/ruby/corpus/for.diffA-B.txt @@ -1,6 +1,6 @@ (Program {+(ForEach - {+( + {+(Statements {+(Send {+(Identifier)+})+})+} {+(Array @@ -12,7 +12,7 @@ {+(Send {+(Identifier)+})+})+})+} {-(ForEach - {-( + {-(Statements {-(Send {-(Identifier)-})-})-} {-(Send @@ -20,7 +20,7 @@ {-(Send {-(Identifier)-})-})-} {-(ForEach - {-( + {-(Statements {-(Send {-(Identifier)-})-} {-(Send @@ -30,7 +30,7 @@ {-(Send {-(Identifier)-})-})-} {-(ForEach - {-( + {-(Statements {-(Send {-(Identifier)-})-})-} {-(Enumeration @@ -39,7 +39,7 @@ {-(Empty)-})-} {-(Boolean)-})-} {-(ForEach - {-( + {-(Statements {-(Send {-(Identifier)-})-} {-(Send diff --git a/test/fixtures/ruby/corpus/for.diffB-A.txt b/test/fixtures/ruby/corpus/for.diffB-A.txt index a0356bb13..330945146 100644 --- a/test/fixtures/ruby/corpus/for.diffB-A.txt +++ b/test/fixtures/ruby/corpus/for.diffB-A.txt @@ -1,6 +1,6 @@ (Program {+(ForEach - {+( + {+(Statements {+(Send {+(Identifier)+})+})+} {+(Send @@ -8,7 +8,7 @@ {+(Send {+(Identifier)+})+})+} (ForEach - ( + (Statements (Send { (Identifier) ->(Identifier) }) @@ -26,7 +26,7 @@ {-(Send {-(Identifier)-})-})) {+(ForEach - {+( + {+(Statements {+(Send {+(Identifier)+})+})+} {+(Enumeration @@ -35,7 +35,7 @@ {+(Empty)+})+} {+(Boolean)+})+} {+(ForEach - {+( + {+(Statements {+(Send {+(Identifier)+})+} {+(Send diff --git a/test/fixtures/ruby/corpus/for.parseA.txt b/test/fixtures/ruby/corpus/for.parseA.txt index 6f91ae369..5fdbf737a 100644 --- a/test/fixtures/ruby/corpus/for.parseA.txt +++ b/test/fixtures/ruby/corpus/for.parseA.txt @@ -1,6 +1,6 @@ (Program (ForEach - ( + (Statements (Send (Identifier))) (Send @@ -8,7 +8,7 @@ (Send (Identifier))) (ForEach - ( + (Statements (Send (Identifier)) (Send @@ -18,7 +18,7 @@ (Send (Identifier))) (ForEach - ( + (Statements (Send (Identifier))) (Enumeration @@ -27,7 +27,7 @@ (Empty)) (Boolean)) (ForEach - ( + (Statements (Send (Identifier)) (Send diff --git a/test/fixtures/ruby/corpus/for.parseB.txt b/test/fixtures/ruby/corpus/for.parseB.txt index 30ed78a02..cedbfe26c 100644 --- a/test/fixtures/ruby/corpus/for.parseB.txt +++ b/test/fixtures/ruby/corpus/for.parseB.txt @@ -1,6 +1,6 @@ (Program (ForEach - ( + (Statements (Send (Identifier))) (Array diff --git a/test/fixtures/ruby/corpus/if.diffA-B.txt b/test/fixtures/ruby/corpus/if.diffA-B.txt index dd8865faf..9ef5ed990 100644 --- a/test/fixtures/ruby/corpus/if.diffA-B.txt +++ b/test/fixtures/ruby/corpus/if.diffA-B.txt @@ -3,12 +3,13 @@ (Send { (Identifier) ->(Identifier) }) - ({-(Send + (Statements + {-(Send {-(Identifier)-})-}) { (If {-(Send {-(Identifier)-})-} - {-( + {-(Statements {-(Send {-(Identifier)-})-})-} {-(Send @@ -17,5 +18,5 @@ {+(If {+(Send {+(Identifier)+})+} - {+([])+} + {+(Statements)+} {+(Empty)+})+}) diff --git a/test/fixtures/ruby/corpus/if.diffB-A.txt b/test/fixtures/ruby/corpus/if.diffB-A.txt index f310c46c9..f16730bd8 100644 --- a/test/fixtures/ruby/corpus/if.diffB-A.txt +++ b/test/fixtures/ruby/corpus/if.diffB-A.txt @@ -3,14 +3,14 @@ (Send { (Identifier) ->(Identifier) }) - ( + (Statements {+(Send {+(Identifier)+})+}) { (Empty) ->(If {+(Send {+(Identifier)+})+} - {+( + {+(Statements {+(Send {+(Identifier)+})+})+} {+(Send @@ -18,5 +18,5 @@ {-(If {-(Send {-(Identifier)-})-} - {-([])-} + {-(Statements)-} {-(Empty)-})-}) diff --git a/test/fixtures/ruby/corpus/if.parseA.txt b/test/fixtures/ruby/corpus/if.parseA.txt index 1f437cf11..41430c07e 100644 --- a/test/fixtures/ruby/corpus/if.parseA.txt +++ b/test/fixtures/ruby/corpus/if.parseA.txt @@ -2,13 +2,13 @@ (If (Send (Identifier)) - ( + (Statements (Send (Identifier))) (If (Send (Identifier)) - ( + (Statements (Send (Identifier))) (Send diff --git a/test/fixtures/ruby/corpus/if.parseB.txt b/test/fixtures/ruby/corpus/if.parseB.txt index 1c33d88a2..c023a1d11 100644 --- a/test/fixtures/ruby/corpus/if.parseB.txt +++ b/test/fixtures/ruby/corpus/if.parseB.txt @@ -2,10 +2,10 @@ (If (Send (Identifier)) - ([]) + (Statements) (Empty)) (If (Send (Identifier)) - ([]) + (Statements) (Empty))) diff --git a/test/fixtures/ruby/corpus/lambda-dash-rocket.diffA-B.txt b/test/fixtures/ruby/corpus/lambda-dash-rocket.diffA-B.txt index 080b2d9a9..e6c297e5d 100644 --- a/test/fixtures/ruby/corpus/lambda-dash-rocket.diffA-B.txt +++ b/test/fixtures/ruby/corpus/lambda-dash-rocket.diffA-B.txt @@ -6,7 +6,7 @@ {-(Identifier)-} (Function (Empty) - { ( + { (Statements {-(Integer)-} {-(Integer)-}) ->(Send diff --git a/test/fixtures/ruby/corpus/lambda-dash-rocket.diffB-A.txt b/test/fixtures/ruby/corpus/lambda-dash-rocket.diffB-A.txt index 2476cec06..6abae706a 100644 --- a/test/fixtures/ruby/corpus/lambda-dash-rocket.diffB-A.txt +++ b/test/fixtures/ruby/corpus/lambda-dash-rocket.diffB-A.txt @@ -8,6 +8,6 @@ (Empty) { (Send {-(Identifier)-}) - ->( + ->(Statements {+(Integer)+} {+(Integer)+}) }))) diff --git a/test/fixtures/ruby/corpus/lambda-dash-rocket.parseA.txt b/test/fixtures/ruby/corpus/lambda-dash-rocket.parseA.txt index f927c0597..ff5b12b04 100644 --- a/test/fixtures/ruby/corpus/lambda-dash-rocket.parseA.txt +++ b/test/fixtures/ruby/corpus/lambda-dash-rocket.parseA.txt @@ -6,6 +6,6 @@ (Identifier) (Function (Empty) - ( + (Statements (Integer) (Integer))))) diff --git a/test/fixtures/ruby/corpus/lambda.diffA-B.txt b/test/fixtures/ruby/corpus/lambda.diffA-B.txt index 67d452c63..a432cec2e 100644 --- a/test/fixtures/ruby/corpus/lambda.diffA-B.txt +++ b/test/fixtures/ruby/corpus/lambda.diffA-B.txt @@ -4,7 +4,7 @@ (Function (Empty) {+(Identifier)+} - { ([]) + { (Statements) ->(Plus {+(Identifier)+} {+(Integer)+}) })) @@ -26,7 +26,7 @@ {-(Empty)-} {-(Function {-(Empty)-} - {-([])-})-})-} + {-(Statements)-})-})-} {-(Function {-(Empty)-} {-(Function @@ -43,9 +43,9 @@ {-(Empty)-} {-(Identifier)-} {-(Identifier)-} - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Function {-(Empty)-} - {-([])-})-})-}) + {-(Statements)-})-})-}) diff --git a/test/fixtures/ruby/corpus/lambda.diffB-A.txt b/test/fixtures/ruby/corpus/lambda.diffB-A.txt index 1f25ddb9c..df872e722 100644 --- a/test/fixtures/ruby/corpus/lambda.diffB-A.txt +++ b/test/fixtures/ruby/corpus/lambda.diffB-A.txt @@ -7,7 +7,7 @@ { (Plus {-(Identifier)-} {-(Integer)-}) - ->([]) })) + ->(Statements) })) {+(Send {+(Identifier)+} {+(Function @@ -26,7 +26,7 @@ {+(Empty)+} {+(Function {+(Empty)+} - {+([])+})+})+} + {+(Statements)+})+})+} {+(Function {+(Empty)+} {+(Function @@ -43,9 +43,9 @@ {+(Empty)+} {+(Identifier)+} {+(Identifier)+} - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Function {+(Empty)+} - {+([])+})+})+}) + {+(Statements)+})+})+}) diff --git a/test/fixtures/ruby/corpus/lambda.parseA.txt b/test/fixtures/ruby/corpus/lambda.parseA.txt index bbfaf8869..b88439a6a 100644 --- a/test/fixtures/ruby/corpus/lambda.parseA.txt +++ b/test/fixtures/ruby/corpus/lambda.parseA.txt @@ -3,7 +3,7 @@ (Identifier) (Function (Empty) - ([]))) + (Statements))) (Send (Identifier) (Function @@ -22,7 +22,7 @@ (Empty) (Function (Empty) - ([]))) + (Statements))) (Function (Empty) (Function @@ -39,9 +39,9 @@ (Empty) (Identifier) (Identifier) - ( + (Statements (Identifier) (Identifier)) (Function (Empty) - ([])))) + (Statements)))) diff --git a/test/fixtures/ruby/corpus/method-declaration-keyword-param.diffA-B.txt b/test/fixtures/ruby/corpus/method-declaration-keyword-param.diffA-B.txt index bebe36af5..53a62bc41 100644 --- a/test/fixtures/ruby/corpus/method-declaration-keyword-param.diffA-B.txt +++ b/test/fixtures/ruby/corpus/method-declaration-keyword-param.diffA-B.txt @@ -3,4 +3,4 @@ (Empty) (Identifier) {+(Identifier)+} - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-keyword-param.diffB-A.txt b/test/fixtures/ruby/corpus/method-declaration-keyword-param.diffB-A.txt index e37b12b67..94e20230e 100644 --- a/test/fixtures/ruby/corpus/method-declaration-keyword-param.diffB-A.txt +++ b/test/fixtures/ruby/corpus/method-declaration-keyword-param.diffB-A.txt @@ -3,4 +3,4 @@ (Empty) (Identifier) {-(Identifier)-} - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-keyword-param.parseA.txt b/test/fixtures/ruby/corpus/method-declaration-keyword-param.parseA.txt index 0db11f8a0..298d2bcd8 100644 --- a/test/fixtures/ruby/corpus/method-declaration-keyword-param.parseA.txt +++ b/test/fixtures/ruby/corpus/method-declaration-keyword-param.parseA.txt @@ -2,4 +2,4 @@ (Method (Empty) (Identifier) - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-keyword-param.parseB.txt b/test/fixtures/ruby/corpus/method-declaration-keyword-param.parseB.txt index e1d159a2f..d37ef9a8c 100644 --- a/test/fixtures/ruby/corpus/method-declaration-keyword-param.parseB.txt +++ b/test/fixtures/ruby/corpus/method-declaration-keyword-param.parseB.txt @@ -3,4 +3,4 @@ (Empty) (Identifier) (Identifier) - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-param-default.diffA-B.txt b/test/fixtures/ruby/corpus/method-declaration-param-default.diffA-B.txt index bebe36af5..53a62bc41 100644 --- a/test/fixtures/ruby/corpus/method-declaration-param-default.diffA-B.txt +++ b/test/fixtures/ruby/corpus/method-declaration-param-default.diffA-B.txt @@ -3,4 +3,4 @@ (Empty) (Identifier) {+(Identifier)+} - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-param-default.diffB-A.txt b/test/fixtures/ruby/corpus/method-declaration-param-default.diffB-A.txt index e37b12b67..94e20230e 100644 --- a/test/fixtures/ruby/corpus/method-declaration-param-default.diffB-A.txt +++ b/test/fixtures/ruby/corpus/method-declaration-param-default.diffB-A.txt @@ -3,4 +3,4 @@ (Empty) (Identifier) {-(Identifier)-} - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-param-default.parseA.txt b/test/fixtures/ruby/corpus/method-declaration-param-default.parseA.txt index 0db11f8a0..298d2bcd8 100644 --- a/test/fixtures/ruby/corpus/method-declaration-param-default.parseA.txt +++ b/test/fixtures/ruby/corpus/method-declaration-param-default.parseA.txt @@ -2,4 +2,4 @@ (Method (Empty) (Identifier) - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-param-default.parseB.txt b/test/fixtures/ruby/corpus/method-declaration-param-default.parseB.txt index e1d159a2f..d37ef9a8c 100644 --- a/test/fixtures/ruby/corpus/method-declaration-param-default.parseB.txt +++ b/test/fixtures/ruby/corpus/method-declaration-param-default.parseB.txt @@ -3,4 +3,4 @@ (Empty) (Identifier) (Identifier) - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-params.diffA-B.txt b/test/fixtures/ruby/corpus/method-declaration-params.diffA-B.txt index c8ecdbe0b..e54025850 100644 --- a/test/fixtures/ruby/corpus/method-declaration-params.diffA-B.txt +++ b/test/fixtures/ruby/corpus/method-declaration-params.diffA-B.txt @@ -5,4 +5,4 @@ (Identifier) {+(Identifier)+} {+(Identifier)+} - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-params.diffB-A.txt b/test/fixtures/ruby/corpus/method-declaration-params.diffB-A.txt index 8238f40c4..e2a20b25c 100644 --- a/test/fixtures/ruby/corpus/method-declaration-params.diffB-A.txt +++ b/test/fixtures/ruby/corpus/method-declaration-params.diffB-A.txt @@ -5,4 +5,4 @@ (Identifier) {-(Identifier)-} {-(Identifier)-} - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-params.parseA.txt b/test/fixtures/ruby/corpus/method-declaration-params.parseA.txt index e1d159a2f..d37ef9a8c 100644 --- a/test/fixtures/ruby/corpus/method-declaration-params.parseA.txt +++ b/test/fixtures/ruby/corpus/method-declaration-params.parseA.txt @@ -3,4 +3,4 @@ (Empty) (Identifier) (Identifier) - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-params.parseB.txt b/test/fixtures/ruby/corpus/method-declaration-params.parseB.txt index 8bc5e1951..3ba89843c 100644 --- a/test/fixtures/ruby/corpus/method-declaration-params.parseB.txt +++ b/test/fixtures/ruby/corpus/method-declaration-params.parseB.txt @@ -5,4 +5,4 @@ (Identifier) (Identifier) (Identifier) - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.diffA-B.txt b/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.diffA-B.txt index bebe36af5..53a62bc41 100644 --- a/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.diffA-B.txt +++ b/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.diffA-B.txt @@ -3,4 +3,4 @@ (Empty) (Identifier) {+(Identifier)+} - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.diffB-A.txt b/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.diffB-A.txt index e37b12b67..94e20230e 100644 --- a/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.diffB-A.txt +++ b/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.diffB-A.txt @@ -3,4 +3,4 @@ (Empty) (Identifier) {-(Identifier)-} - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.parseA.txt b/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.parseA.txt index 0db11f8a0..298d2bcd8 100644 --- a/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.parseA.txt +++ b/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.parseA.txt @@ -2,4 +2,4 @@ (Method (Empty) (Identifier) - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.parseB.txt b/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.parseB.txt index e1d159a2f..d37ef9a8c 100644 --- a/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.parseB.txt +++ b/test/fixtures/ruby/corpus/method-declaration-required-keyword-param.parseB.txt @@ -3,4 +3,4 @@ (Empty) (Identifier) (Identifier) - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-unnamed-param.diffA-B.txt b/test/fixtures/ruby/corpus/method-declaration-unnamed-param.diffA-B.txt index 72c9961f7..5518ef711 100644 --- a/test/fixtures/ruby/corpus/method-declaration-unnamed-param.diffA-B.txt +++ b/test/fixtures/ruby/corpus/method-declaration-unnamed-param.diffA-B.txt @@ -4,4 +4,4 @@ (Identifier) (Identifier) {+(Empty)+} - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-unnamed-param.diffB-A.txt b/test/fixtures/ruby/corpus/method-declaration-unnamed-param.diffB-A.txt index 50487c8b0..27239ae3f 100644 --- a/test/fixtures/ruby/corpus/method-declaration-unnamed-param.diffB-A.txt +++ b/test/fixtures/ruby/corpus/method-declaration-unnamed-param.diffB-A.txt @@ -4,4 +4,4 @@ (Identifier) (Identifier) {-(Empty)-} - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-unnamed-param.parseA.txt b/test/fixtures/ruby/corpus/method-declaration-unnamed-param.parseA.txt index e1d159a2f..d37ef9a8c 100644 --- a/test/fixtures/ruby/corpus/method-declaration-unnamed-param.parseA.txt +++ b/test/fixtures/ruby/corpus/method-declaration-unnamed-param.parseA.txt @@ -3,4 +3,4 @@ (Empty) (Identifier) (Identifier) - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration-unnamed-param.parseB.txt b/test/fixtures/ruby/corpus/method-declaration-unnamed-param.parseB.txt index 8d306c54e..9d41bda94 100644 --- a/test/fixtures/ruby/corpus/method-declaration-unnamed-param.parseB.txt +++ b/test/fixtures/ruby/corpus/method-declaration-unnamed-param.parseB.txt @@ -4,4 +4,4 @@ (Identifier) (Identifier) (Empty) - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration.diffA-B.txt b/test/fixtures/ruby/corpus/method-declaration.diffA-B.txt index 7592bf4e4..6dfccf172 100644 --- a/test/fixtures/ruby/corpus/method-declaration.diffA-B.txt +++ b/test/fixtures/ruby/corpus/method-declaration.diffA-B.txt @@ -4,6 +4,6 @@ { (Identifier) ->(Identifier) } {+(Identifier)+} - ( + (Statements {+(Send {+(Identifier)+})+}))) diff --git a/test/fixtures/ruby/corpus/method-declaration.diffB-A.txt b/test/fixtures/ruby/corpus/method-declaration.diffB-A.txt index ef50f5e7d..61ab57f96 100644 --- a/test/fixtures/ruby/corpus/method-declaration.diffB-A.txt +++ b/test/fixtures/ruby/corpus/method-declaration.diffB-A.txt @@ -4,5 +4,6 @@ { (Identifier) ->(Identifier) } {-(Identifier)-} - ({-(Send + (Statements + {-(Send {-(Identifier)-})-}))) diff --git a/test/fixtures/ruby/corpus/method-declaration.parseA.txt b/test/fixtures/ruby/corpus/method-declaration.parseA.txt index 0db11f8a0..298d2bcd8 100644 --- a/test/fixtures/ruby/corpus/method-declaration.parseA.txt +++ b/test/fixtures/ruby/corpus/method-declaration.parseA.txt @@ -2,4 +2,4 @@ (Method (Empty) (Identifier) - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/method-declaration.parseB.txt b/test/fixtures/ruby/corpus/method-declaration.parseB.txt index acf2aca5b..958ef8851 100644 --- a/test/fixtures/ruby/corpus/method-declaration.parseB.txt +++ b/test/fixtures/ruby/corpus/method-declaration.parseB.txt @@ -3,6 +3,6 @@ (Empty) (Identifier) (Identifier) - ( + (Statements (Send (Identifier))))) diff --git a/test/fixtures/ruby/corpus/methods.parseA.txt b/test/fixtures/ruby/corpus/methods.parseA.txt index 546f73f91..f9c8a1f04 100644 --- a/test/fixtures/ruby/corpus/methods.parseA.txt +++ b/test/fixtures/ruby/corpus/methods.parseA.txt @@ -2,16 +2,16 @@ (Method (Empty) (Identifier) - ([])) + (Statements)) (Method (Empty) (Identifier) - ([])) + (Statements)) (Method (Empty) (Identifier) (Identifier) - ([])) + (Statements)) (Method (Empty) (Identifier) @@ -19,24 +19,24 @@ (Identifier) (Identifier) (Empty) - ([])) + (Statements)) (Method (Empty) (Identifier) (Identifier) - ([])) + (Statements)) (Method (Empty) (Identifier) (Identifier) - ([])) + (Statements)) (Method (Identifier) (Identifier) - ([])) + (Statements)) (Method (Identifier) (Identifier) (Identifier) (Identifier) - ([]))) + (Statements))) diff --git a/test/fixtures/ruby/corpus/misc.parseA.txt b/test/fixtures/ruby/corpus/misc.parseA.txt index f494f4f8f..e51f4e761 100644 --- a/test/fixtures/ruby/corpus/misc.parseA.txt +++ b/test/fixtures/ruby/corpus/misc.parseA.txt @@ -5,7 +5,7 @@ (Identifier)) (Function (Empty) - ([]))) + (Statements))) (Send (Send (Identifier)) @@ -15,7 +15,7 @@ (Identifier) (Identifier) (Identifier) - ([]))) + (Statements))) (Send (Identifier) (Send @@ -23,5 +23,5 @@ (Function (Empty) (Identifier) - ([]))) + (Statements))) (Identifier)) diff --git a/test/fixtures/ruby/corpus/module.diffA-B.txt b/test/fixtures/ruby/corpus/module.diffA-B.txt index e93001b3e..8f0937a13 100644 --- a/test/fixtures/ruby/corpus/module.diffA-B.txt +++ b/test/fixtures/ruby/corpus/module.diffA-B.txt @@ -4,7 +4,7 @@ {+(Method {+(Empty)+} {+(Identifier)+} - {+([])+})+}) + {+(Statements)+})+}) {-(Module {-(ScopeResolution {-(Identifier)-} diff --git a/test/fixtures/ruby/corpus/module.diffB-A.txt b/test/fixtures/ruby/corpus/module.diffB-A.txt index 84fecbdc2..06b13c3c9 100644 --- a/test/fixtures/ruby/corpus/module.diffB-A.txt +++ b/test/fixtures/ruby/corpus/module.diffB-A.txt @@ -4,7 +4,7 @@ {-(Method {-(Empty)-} {-(Identifier)-} - {-([])-})-}) + {-(Statements)-})-}) {+(Module {+(ScopeResolution {+(Identifier)+} diff --git a/test/fixtures/ruby/corpus/module.parseB.txt b/test/fixtures/ruby/corpus/module.parseB.txt index cbd787a15..b73290959 100644 --- a/test/fixtures/ruby/corpus/module.parseB.txt +++ b/test/fixtures/ruby/corpus/module.parseB.txt @@ -4,4 +4,4 @@ (Method (Empty) (Identifier) - ([])))) + (Statements)))) diff --git a/test/fixtures/ruby/corpus/multiple-assignments.diffA-B.txt b/test/fixtures/ruby/corpus/multiple-assignments.diffA-B.txt index 7c735abdd..bbd4b921c 100644 --- a/test/fixtures/ruby/corpus/multiple-assignments.diffA-B.txt +++ b/test/fixtures/ruby/corpus/multiple-assignments.diffA-B.txt @@ -1,6 +1,6 @@ (Program (Assignment - ( + (Statements (Identifier) { (Identifier) ->(Identifier) } @@ -10,40 +10,40 @@ (Integer) (Integer))) {-(Assignment - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Array {-(Integer)-} {-(Integer)-})-})-} {-(Assignment - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Array {-(Integer)-} {-(Integer)-})-})-} {-(Assignment - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Array {-(Integer)-} {-(Integer)-})-})-} {-(Assignment - {-( + {-(Statements {-(Identifier)-} {-(Identifier)-})-} {-(Identifier)-})-} {-(Assignment - {-( + {-(Statements {-(Send {-(Identifier)-} {-(Identifier)-})-} {-(Send {-(Identifier)-} {-(Identifier)-})-})-} - {-( + {-(Statements {-(Send {-(Send {-(Identifier)-})-} @@ -53,8 +53,8 @@ {-(Identifier)-})-} {-(Identifier)-})-})-})-} {-(Assignment - {-( - {-( + {-(Statements + {-(Statements {-(Identifier)-} {-(Identifier)-})-})-} {-(Identifier)-})-}) diff --git a/test/fixtures/ruby/corpus/multiple-assignments.diffB-A.txt b/test/fixtures/ruby/corpus/multiple-assignments.diffB-A.txt index e6f8ba6d8..1eda9f932 100644 --- a/test/fixtures/ruby/corpus/multiple-assignments.diffB-A.txt +++ b/test/fixtures/ruby/corpus/multiple-assignments.diffB-A.txt @@ -1,6 +1,6 @@ (Program (Assignment - ( + (Statements (Identifier) { (Identifier) ->(Identifier) } @@ -10,40 +10,40 @@ (Integer) (Integer))) {+(Assignment - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Array {+(Integer)+} {+(Integer)+})+})+} {+(Assignment - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Array {+(Integer)+} {+(Integer)+})+})+} {+(Assignment - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Array {+(Integer)+} {+(Integer)+})+})+} {+(Assignment - {+( + {+(Statements {+(Identifier)+} {+(Identifier)+})+} {+(Identifier)+})+} {+(Assignment - {+( + {+(Statements {+(Send {+(Identifier)+} {+(Identifier)+})+} {+(Send {+(Identifier)+} {+(Identifier)+})+})+} - {+( + {+(Statements {+(Send {+(Send {+(Identifier)+})+} @@ -53,8 +53,8 @@ {+(Identifier)+})+} {+(Identifier)+})+})+})+} {+(Assignment - {+( - {+( + {+(Statements + {+(Statements {+(Identifier)+} {+(Identifier)+})+})+} {+(Identifier)+})+}) diff --git a/test/fixtures/ruby/corpus/multiple-assignments.parseA.txt b/test/fixtures/ruby/corpus/multiple-assignments.parseA.txt index 406650c2d..ea1fb4950 100644 --- a/test/fixtures/ruby/corpus/multiple-assignments.parseA.txt +++ b/test/fixtures/ruby/corpus/multiple-assignments.parseA.txt @@ -1,6 +1,6 @@ (Program (Assignment - ( + (Statements (Identifier) (Identifier) (Identifier)) @@ -9,40 +9,40 @@ (Integer) (Integer))) (Assignment - ( + (Statements (Identifier) (Identifier)) (Array (Integer) (Integer))) (Assignment - ( + (Statements (Identifier) (Identifier)) (Array (Integer) (Integer))) (Assignment - ( + (Statements (Identifier) (Identifier)) (Array (Integer) (Integer))) (Assignment - ( + (Statements (Identifier) (Identifier)) (Identifier)) (Assignment - ( + (Statements (Send (Identifier) (Identifier)) (Send (Identifier) (Identifier))) - ( + (Statements (Send (Send (Identifier)) @@ -52,8 +52,8 @@ (Identifier)) (Identifier)))) (Assignment - ( - ( + (Statements + (Statements (Identifier) (Identifier))) (Identifier))) diff --git a/test/fixtures/ruby/corpus/multiple-assignments.parseB.txt b/test/fixtures/ruby/corpus/multiple-assignments.parseB.txt index 1a12b19b5..166f46fdb 100644 --- a/test/fixtures/ruby/corpus/multiple-assignments.parseB.txt +++ b/test/fixtures/ruby/corpus/multiple-assignments.parseB.txt @@ -1,6 +1,6 @@ (Program (Assignment - ( + (Statements (Identifier) (Identifier)) (Array diff --git a/test/fixtures/ruby/corpus/next.parseA.txt b/test/fixtures/ruby/corpus/next.parseA.txt index 16cc87aba..c6a6b22b9 100644 --- a/test/fixtures/ruby/corpus/next.parseA.txt +++ b/test/fixtures/ruby/corpus/next.parseA.txt @@ -1,6 +1,6 @@ (Program (ForEach - ( + (Statements (Send (Identifier))) (Send diff --git a/test/fixtures/ruby/corpus/rescue-empty.diffA-B.txt b/test/fixtures/ruby/corpus/rescue-empty.diffA-B.txt index f0d3e467c..0c35e8b0e 100644 --- a/test/fixtures/ruby/corpus/rescue-empty.diffA-B.txt +++ b/test/fixtures/ruby/corpus/rescue-empty.diffA-B.txt @@ -1,10 +1,10 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Catch - ([]) - { ([]) + (Statements) + { (Statements) ->(Send {+(Identifier)+}) })))) diff --git a/test/fixtures/ruby/corpus/rescue-empty.diffB-A.txt b/test/fixtures/ruby/corpus/rescue-empty.diffB-A.txt index 73cad3bfc..9c21fe36d 100644 --- a/test/fixtures/ruby/corpus/rescue-empty.diffB-A.txt +++ b/test/fixtures/ruby/corpus/rescue-empty.diffB-A.txt @@ -1,10 +1,10 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Catch - ([]) + (Statements) { (Send {-(Identifier)-}) - ->([]) })))) + ->(Statements) })))) diff --git a/test/fixtures/ruby/corpus/rescue-empty.parseA.txt b/test/fixtures/ruby/corpus/rescue-empty.parseA.txt index 519796778..142f19085 100644 --- a/test/fixtures/ruby/corpus/rescue-empty.parseA.txt +++ b/test/fixtures/ruby/corpus/rescue-empty.parseA.txt @@ -1,8 +1,8 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Catch - ([]) - ([]))))) + (Statements) + (Statements))))) diff --git a/test/fixtures/ruby/corpus/rescue-empty.parseB.txt b/test/fixtures/ruby/corpus/rescue-empty.parseB.txt index c7bc8332d..5b9052323 100644 --- a/test/fixtures/ruby/corpus/rescue-empty.parseB.txt +++ b/test/fixtures/ruby/corpus/rescue-empty.parseB.txt @@ -1,9 +1,9 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Catch - ([]) + (Statements) (Send (Identifier)))))) diff --git a/test/fixtures/ruby/corpus/rescue-last-ex.diffA-B.txt b/test/fixtures/ruby/corpus/rescue-last-ex.diffA-B.txt index 8b0da7220..a1842467f 100644 --- a/test/fixtures/ruby/corpus/rescue-last-ex.diffA-B.txt +++ b/test/fixtures/ruby/corpus/rescue-last-ex.diffA-B.txt @@ -1,15 +1,15 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Catch - ( - ( + (Statements + (Statements (Identifier)) - ( + (Statements (Send (Identifier)))) - { ([]) + { (Statements) ->(Send {+(Identifier)+}) })))) diff --git a/test/fixtures/ruby/corpus/rescue-last-ex.diffB-A.txt b/test/fixtures/ruby/corpus/rescue-last-ex.diffB-A.txt index a639d31c5..25678b843 100644 --- a/test/fixtures/ruby/corpus/rescue-last-ex.diffB-A.txt +++ b/test/fixtures/ruby/corpus/rescue-last-ex.diffB-A.txt @@ -1,15 +1,15 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Catch - ( - ( + (Statements + (Statements (Identifier)) - ( + (Statements (Send (Identifier)))) { (Send {-(Identifier)-}) - ->([]) })))) + ->(Statements) })))) diff --git a/test/fixtures/ruby/corpus/rescue-last-ex.parseA.txt b/test/fixtures/ruby/corpus/rescue-last-ex.parseA.txt index 89713222d..a7585b32b 100644 --- a/test/fixtures/ruby/corpus/rescue-last-ex.parseA.txt +++ b/test/fixtures/ruby/corpus/rescue-last-ex.parseA.txt @@ -1,13 +1,13 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Catch - ( - ( + (Statements + (Statements (Identifier)) - ( + (Statements (Send (Identifier)))) - ([]))))) + (Statements))))) diff --git a/test/fixtures/ruby/corpus/rescue-last-ex.parseB.txt b/test/fixtures/ruby/corpus/rescue-last-ex.parseB.txt index eb5ee6c1c..2aa62b05c 100644 --- a/test/fixtures/ruby/corpus/rescue-last-ex.parseB.txt +++ b/test/fixtures/ruby/corpus/rescue-last-ex.parseB.txt @@ -1,13 +1,13 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Catch - ( - ( + (Statements + (Statements (Identifier)) - ( + (Statements (Send (Identifier)))) (Send diff --git a/test/fixtures/ruby/corpus/rescue.diffA-B.txt b/test/fixtures/ruby/corpus/rescue.diffA-B.txt index cd45faf3c..47e0ced9b 100644 --- a/test/fixtures/ruby/corpus/rescue.diffA-B.txt +++ b/test/fixtures/ruby/corpus/rescue.diffA-B.txt @@ -1,29 +1,29 @@ (Program {+(Try - {+( + {+(Statements {+(Send {+(Identifier)+})+} {+(Catch - {+( - {+( + {+(Statements + {+(Statements {+(Send {+(Identifier)+})+})+})+} {+(Send {+(Identifier)+})+})+})+})+} {-(Try - {-( + {-(Statements {-(Send {-(Identifier)-})-} {-(Catch - {-( - {-( + {-(Statements + {-(Statements {-(Identifier)-})-})-} {-(Catch - {-( - {-( + {-(Statements + {-(Statements {-(Identifier)-} {-(Identifier)-})-} - {-( + {-(Statements {-(Send {-(Identifier)-})-})-})-} {-(Send @@ -38,25 +38,25 @@ {-(Method {-(Empty)-} {-(Identifier)-} - {-( + {-(Statements {-(Catch - {-( - {-( + {-(Statements + {-(Statements {-(Identifier)-})-})-} {-(Catch - {-( - {-( + {-(Statements + {-(Statements {-(Identifier)-} {-(Identifier)-})-} - {-( + {-(Statements {-(Send {-(Identifier)-})-})-})-} - {-([])-})-})-} + {-(Statements)-})-})-} {-(Else {-(Empty)-} - {-([])-})-} + {-(Statements)-})-} {-(Finally - {-([])-})-})-})-} + {-(Statements)-})-})-})-} {-(Try {-(Send {-(Identifier)-})-} diff --git a/test/fixtures/ruby/corpus/rescue.diffB-A.txt b/test/fixtures/ruby/corpus/rescue.diffB-A.txt index 806ebf354..2dbe5f598 100644 --- a/test/fixtures/ruby/corpus/rescue.diffB-A.txt +++ b/test/fixtures/ruby/corpus/rescue.diffB-A.txt @@ -1,18 +1,18 @@ (Program {+(Try - {+( + {+(Statements {+(Send {+(Identifier)+})+} {+(Catch - {+( - {+( + {+(Statements + {+(Statements {+(Identifier)+})+})+} {+(Catch - {+( - {+( + {+(Statements + {+(Statements {+(Identifier)+} {+(Identifier)+})+} - {+( + {+(Statements {+(Send {+(Identifier)+})+})+})+} {+(Send @@ -27,32 +27,32 @@ {+(Method {+(Empty)+} {+(Identifier)+} - {+( + {+(Statements {+(Catch - {+( - {+( + {+(Statements + {+(Statements {+(Identifier)+})+})+} {+(Catch - {+( - {+( + {+(Statements + {+(Statements {+(Identifier)+} {+(Identifier)+})+} - {+( + {+(Statements {+(Send {+(Identifier)+})+})+})+} - {+([])+})+})+} + {+(Statements)+})+})+} {+(Else {+(Empty)+} - {+([])+})+} + {+(Statements)+})+} {+(Finally - {+([])+})+})+})+} + {+(Statements)+})+})+})+} (Try - { ( + { (Statements {-(Send {-(Identifier)-})-} {-(Catch - {-( - {-( + {-(Statements + {-(Statements {-(Send {-(Identifier)-})-})-})-} {-(Send diff --git a/test/fixtures/ruby/corpus/rescue.parseA.txt b/test/fixtures/ruby/corpus/rescue.parseA.txt index 9b906f35f..c3b90edec 100644 --- a/test/fixtures/ruby/corpus/rescue.parseA.txt +++ b/test/fixtures/ruby/corpus/rescue.parseA.txt @@ -1,18 +1,18 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Catch - ( - ( + (Statements + (Statements (Identifier))) (Catch - ( - ( + (Statements + (Statements (Identifier) (Identifier)) - ( + (Statements (Send (Identifier)))) (Send @@ -27,25 +27,25 @@ (Method (Empty) (Identifier) - ( + (Statements (Catch - ( - ( + (Statements + (Statements (Identifier))) (Catch - ( - ( + (Statements + (Statements (Identifier) (Identifier)) - ( + (Statements (Send (Identifier)))) - ([]))) + (Statements))) (Else (Empty) - ([])) + (Statements)) (Finally - ([])))) + (Statements)))) (Try (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/rescue.parseB.txt b/test/fixtures/ruby/corpus/rescue.parseB.txt index be7a76a73..d5a5ed658 100644 --- a/test/fixtures/ruby/corpus/rescue.parseB.txt +++ b/test/fixtures/ruby/corpus/rescue.parseB.txt @@ -1,11 +1,11 @@ (Program (Try - ( + (Statements (Send (Identifier)) (Catch - ( - ( + (Statements + (Statements (Send (Identifier)))) (Send diff --git a/test/fixtures/ruby/corpus/singleton-class.parseA.txt b/test/fixtures/ruby/corpus/singleton-class.parseA.txt index f80075b5a..2d718006d 100644 --- a/test/fixtures/ruby/corpus/singleton-class.parseA.txt +++ b/test/fixtures/ruby/corpus/singleton-class.parseA.txt @@ -1,7 +1,7 @@ (Program (Class (Identifier) - ([])) + (Statements)) (Class (ScopeResolution (Identifier) diff --git a/test/fixtures/ruby/corpus/unless.diffA-B.txt b/test/fixtures/ruby/corpus/unless.diffA-B.txt index e5b543018..ad44d6732 100644 --- a/test/fixtures/ruby/corpus/unless.diffA-B.txt +++ b/test/fixtures/ruby/corpus/unless.diffA-B.txt @@ -4,7 +4,8 @@ (Send { (Identifier) ->(Identifier) })) - ({-(Send + (Statements + {-(Send {-(Identifier)-})-}) { (Send {-(Identifier)-}) @@ -13,5 +14,5 @@ {+(Not {+(Send {+(Identifier)+})+})+} - {+([])+} + {+(Statements)+} {+(Empty)+})+}) diff --git a/test/fixtures/ruby/corpus/unless.diffB-A.txt b/test/fixtures/ruby/corpus/unless.diffB-A.txt index ccf5e5da4..4ee118f9d 100644 --- a/test/fixtures/ruby/corpus/unless.diffB-A.txt +++ b/test/fixtures/ruby/corpus/unless.diffB-A.txt @@ -4,7 +4,7 @@ (Send { (Identifier) ->(Identifier) })) - ( + (Statements {+(Send {+(Identifier)+})+}) { (Empty) @@ -14,5 +14,5 @@ {-(Not {-(Send {-(Identifier)-})-})-} - {-([])-} + {-(Statements)-} {-(Empty)-})-}) diff --git a/test/fixtures/ruby/corpus/unless.parseA.txt b/test/fixtures/ruby/corpus/unless.parseA.txt index e219ada22..81b87e968 100644 --- a/test/fixtures/ruby/corpus/unless.parseA.txt +++ b/test/fixtures/ruby/corpus/unless.parseA.txt @@ -3,7 +3,7 @@ (Not (Send (Identifier))) - ( + (Statements (Send (Identifier))) (Send diff --git a/test/fixtures/ruby/corpus/unless.parseB.txt b/test/fixtures/ruby/corpus/unless.parseB.txt index ac70e7130..0d627eb22 100644 --- a/test/fixtures/ruby/corpus/unless.parseB.txt +++ b/test/fixtures/ruby/corpus/unless.parseB.txt @@ -3,11 +3,11 @@ (Not (Send (Identifier))) - ([]) + (Statements) (Empty)) (If (Not (Send (Identifier))) - ([]) + (Statements) (Empty))) diff --git a/test/fixtures/ruby/corpus/until.diffA-B.txt b/test/fixtures/ruby/corpus/until.diffA-B.txt index 3e78b93db..fc6b6b977 100644 --- a/test/fixtures/ruby/corpus/until.diffA-B.txt +++ b/test/fixtures/ruby/corpus/until.diffA-B.txt @@ -3,7 +3,7 @@ (Not (Send (Identifier))) - { ([]) + { (Statements) ->(Send {+(Identifier)+}) }) {-(While diff --git a/test/fixtures/ruby/corpus/until.diffB-A.txt b/test/fixtures/ruby/corpus/until.diffB-A.txt index c9a208953..f6f7e3d00 100644 --- a/test/fixtures/ruby/corpus/until.diffB-A.txt +++ b/test/fixtures/ruby/corpus/until.diffB-A.txt @@ -5,7 +5,7 @@ (Identifier))) { (Send {-(Identifier)-}) - ->([]) }) + ->(Statements) }) {+(While {+(Not {+(Send diff --git a/test/fixtures/ruby/corpus/until.parseA.txt b/test/fixtures/ruby/corpus/until.parseA.txt index 42514e560..2c714334f 100644 --- a/test/fixtures/ruby/corpus/until.parseA.txt +++ b/test/fixtures/ruby/corpus/until.parseA.txt @@ -3,7 +3,7 @@ (Not (Send (Identifier))) - ([])) + (Statements)) (While (Not (Send diff --git a/test/fixtures/ruby/corpus/when-else.diffA-B.txt b/test/fixtures/ruby/corpus/when-else.diffA-B.txt index 67b5a3187..5fe140f15 100644 --- a/test/fixtures/ruby/corpus/when-else.diffA-B.txt +++ b/test/fixtures/ruby/corpus/when-else.diffA-B.txt @@ -2,24 +2,24 @@ (Match (Send (Identifier)) - ( + (Statements (Pattern - ( + (Statements (Send { (Identifier) ->(Identifier) })) - ( + (Statements {+(Send {+(Identifier)+})+} {+(Send {+(Identifier)+})+} {-(Pattern - {-( + {-(Statements {-(Send {-(Identifier)-})-} {-(Send {-(Identifier)-})-})-} - {-( + {-(Statements {-(Send {-(Identifier)-})-} - {-([])-})-})-}))))) + {-(Statements)-})-})-}))))) diff --git a/test/fixtures/ruby/corpus/when-else.diffB-A.txt b/test/fixtures/ruby/corpus/when-else.diffB-A.txt index 51de319d1..a663a07f4 100644 --- a/test/fixtures/ruby/corpus/when-else.diffB-A.txt +++ b/test/fixtures/ruby/corpus/when-else.diffB-A.txt @@ -2,23 +2,23 @@ (Match (Send (Identifier)) - ( + (Statements (Pattern - ( + (Statements (Send { (Identifier) ->(Identifier) })) - ( + (Statements {+(Pattern - {+( + {+(Statements {+(Send {+(Identifier)+})+} {+(Send {+(Identifier)+})+})+} - {+( + {+(Statements {+(Send {+(Identifier)+})+} - {+([])+})+})+} + {+(Statements)+})+})+} {-(Send {-(Identifier)-})-} {-(Send diff --git a/test/fixtures/ruby/corpus/when-else.parseA.txt b/test/fixtures/ruby/corpus/when-else.parseA.txt index 9eae0374a..9a0b2fe67 100644 --- a/test/fixtures/ruby/corpus/when-else.parseA.txt +++ b/test/fixtures/ruby/corpus/when-else.parseA.txt @@ -2,19 +2,19 @@ (Match (Send (Identifier)) - ( + (Statements (Pattern - ( + (Statements (Send (Identifier))) - ( + (Statements (Pattern - ( + (Statements (Send (Identifier)) (Send (Identifier))) - ( + (Statements (Send (Identifier)) - ([])))))))) + (Statements)))))))) diff --git a/test/fixtures/ruby/corpus/when-else.parseB.txt b/test/fixtures/ruby/corpus/when-else.parseB.txt index 4e0a1bc49..0bf7a8e0b 100644 --- a/test/fixtures/ruby/corpus/when-else.parseB.txt +++ b/test/fixtures/ruby/corpus/when-else.parseB.txt @@ -2,12 +2,12 @@ (Match (Send (Identifier)) - ( + (Statements (Pattern - ( + (Statements (Send (Identifier))) - ( + (Statements (Send (Identifier)) (Send diff --git a/test/fixtures/ruby/corpus/when.diffA-B.txt b/test/fixtures/ruby/corpus/when.diffA-B.txt index 431220686..424b74924 100644 --- a/test/fixtures/ruby/corpus/when.diffA-B.txt +++ b/test/fixtures/ruby/corpus/when.diffA-B.txt @@ -2,28 +2,28 @@ (Match (Send (Identifier)) - ( + (Statements (Pattern - ( + (Statements (Send (Identifier))) - ( + (Statements {+(Send {+(Identifier)+})+} {+(Pattern - {+( + {+(Statements {+(Send {+(Identifier)+})+} {+(Send {+(Identifier)+})+})+} - {+( + {+(Statements {+(Send {+(Identifier)+})+})+})+})))) {-(Match {-(Empty)-} - {-( + {-(Statements {-(Pattern - {-( + {-(Statements {-(Boolean)-})-} - {-( + {-(Statements {-(TextElement)-})-})-})-})-}) diff --git a/test/fixtures/ruby/corpus/when.diffB-A.txt b/test/fixtures/ruby/corpus/when.diffB-A.txt index 3f8fc05fe..85c2ab01e 100644 --- a/test/fixtures/ruby/corpus/when.diffB-A.txt +++ b/test/fixtures/ruby/corpus/when.diffB-A.txt @@ -2,27 +2,28 @@ (Match (Send (Identifier)) - ( + (Statements (Pattern - ( + (Statements (Send (Identifier))) - ({-(Send + (Statements + {-(Send {-(Identifier)-})-} {-(Pattern - {-( + {-(Statements {-(Send {-(Identifier)-})-} {-(Send {-(Identifier)-})-})-} - {-( + {-(Statements {-(Send {-(Identifier)-})-})-})-})))) {+(Match {+(Empty)+} - {+( + {+(Statements {+(Pattern - {+( + {+(Statements {+(Boolean)+})+} - {+( + {+(Statements {+(TextElement)+})+})+})+})+}) diff --git a/test/fixtures/ruby/corpus/when.parseA.txt b/test/fixtures/ruby/corpus/when.parseA.txt index 2533c0c85..d4fda449b 100644 --- a/test/fixtures/ruby/corpus/when.parseA.txt +++ b/test/fixtures/ruby/corpus/when.parseA.txt @@ -2,17 +2,17 @@ (Match (Send (Identifier)) - ( + (Statements (Pattern - ( + (Statements (Send (Identifier))) - ([])))) + (Statements)))) (Match (Empty) - ( + (Statements (Pattern - ( + (Statements (Boolean)) - ( + (Statements (TextElement)))))) diff --git a/test/fixtures/ruby/corpus/when.parseB.txt b/test/fixtures/ruby/corpus/when.parseB.txt index 3c10f0c37..9e2ad6051 100644 --- a/test/fixtures/ruby/corpus/when.parseB.txt +++ b/test/fixtures/ruby/corpus/when.parseB.txt @@ -2,20 +2,20 @@ (Match (Send (Identifier)) - ( + (Statements (Pattern - ( + (Statements (Send (Identifier))) - ( + (Statements (Send (Identifier)) (Pattern - ( + (Statements (Send (Identifier)) (Send (Identifier))) - ( + (Statements (Send (Identifier))))))))) diff --git a/test/fixtures/ruby/corpus/while.diffA-B.txt b/test/fixtures/ruby/corpus/while.diffA-B.txt index 5687ca0cc..6d36323a9 100644 --- a/test/fixtures/ruby/corpus/while.diffA-B.txt +++ b/test/fixtures/ruby/corpus/while.diffA-B.txt @@ -2,7 +2,7 @@ (While (Send (Identifier)) - { ([]) + { (Statements) ->(Send {+(Identifier)+}) }) {-(While diff --git a/test/fixtures/ruby/corpus/while.diffB-A.txt b/test/fixtures/ruby/corpus/while.diffB-A.txt index 969590f00..9ae46e79c 100644 --- a/test/fixtures/ruby/corpus/while.diffB-A.txt +++ b/test/fixtures/ruby/corpus/while.diffB-A.txt @@ -4,7 +4,7 @@ (Identifier)) { (Send {-(Identifier)-}) - ->([]) }) + ->(Statements) }) {+(While {+(Send {+(Identifier)+})+} diff --git a/test/fixtures/ruby/corpus/while.parseA.txt b/test/fixtures/ruby/corpus/while.parseA.txt index 6ae0c7011..4f8aa8649 100644 --- a/test/fixtures/ruby/corpus/while.parseA.txt +++ b/test/fixtures/ruby/corpus/while.parseA.txt @@ -2,7 +2,7 @@ (While (Send (Identifier)) - ([])) + (Statements)) (While (Send (Identifier)) diff --git a/test/fixtures/typescript/corpus/ambient-declarations.diffA-B.txt b/test/fixtures/typescript/corpus/ambient-declarations.diffA-B.txt index d3b4fd144..aa4d45b54 100644 --- a/test/fixtures/typescript/corpus/ambient-declarations.diffA-B.txt +++ b/test/fixtures/typescript/corpus/ambient-declarations.diffA-B.txt @@ -13,7 +13,7 @@ {-(TypeIdentifier)-})-} {-(Identifier)-} {-(Empty)-}) - ->([]) })) + ->(Statements) })) (AmbientDeclaration { (VariableDeclaration {-(Assignment @@ -99,7 +99,7 @@ (AmbientDeclaration (Class (Identifier) - ( + (Statements (MethodSignature (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/ambient-declarations.diffB-A.txt b/test/fixtures/typescript/corpus/ambient-declarations.diffB-A.txt index 496fe1411..2ec101943 100644 --- a/test/fixtures/typescript/corpus/ambient-declarations.diffB-A.txt +++ b/test/fixtures/typescript/corpus/ambient-declarations.diffB-A.txt @@ -92,7 +92,7 @@ {-(AmbientDeclaration {-(Class {-(Identifier)-} - {-([])-})-})-} + {-(Statements)-})-})-} {-(AmbientDeclaration {-(InterfaceDeclaration {-(Empty)-} @@ -102,7 +102,7 @@ (AmbientDeclaration (Class (Identifier) - ( + (Statements (MethodSignature (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/ambient-declarations.parseA.txt b/test/fixtures/typescript/corpus/ambient-declarations.parseA.txt index 751229398..f028e9b5b 100644 --- a/test/fixtures/typescript/corpus/ambient-declarations.parseA.txt +++ b/test/fixtures/typescript/corpus/ambient-declarations.parseA.txt @@ -89,7 +89,7 @@ (AmbientDeclaration (Class (Identifier) - ( + (Statements (MethodSignature (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/ambient-declarations.parseB.txt b/test/fixtures/typescript/corpus/ambient-declarations.parseB.txt index 769d3757c..0d0519272 100644 --- a/test/fixtures/typescript/corpus/ambient-declarations.parseB.txt +++ b/test/fixtures/typescript/corpus/ambient-declarations.parseB.txt @@ -5,7 +5,7 @@ (AmbientDeclaration (Class (Identifier) - ([]))) + (Statements))) (AmbientDeclaration (InterfaceDeclaration (Empty) @@ -15,7 +15,7 @@ (AmbientDeclaration (Class (Identifier) - ( + (Statements (MethodSignature (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/ambient-exports.diffA-B.txt b/test/fixtures/typescript/corpus/ambient-exports.diffA-B.txt index fda31a882..400442a30 100644 --- a/test/fixtures/typescript/corpus/ambient-exports.diffA-B.txt +++ b/test/fixtures/typescript/corpus/ambient-exports.diffA-B.txt @@ -2,7 +2,7 @@ (DefaultExport { (Class {-(Identifier)-} - {-([])-}) + {-(Statements)-}) ->(Function {+(Empty)+} {+(Empty)+} @@ -23,7 +23,7 @@ {+(Assignment {+(Identifier)+} {+(Empty)+})+})+} - {+( + {+(Statements {+(Return {+(Hash {+(ShorthandPropertyIdentifier)+} diff --git a/test/fixtures/typescript/corpus/ambient-exports.diffB-A.txt b/test/fixtures/typescript/corpus/ambient-exports.diffB-A.txt index afbaad04f..ac045fe1e 100644 --- a/test/fixtures/typescript/corpus/ambient-exports.diffB-A.txt +++ b/test/fixtures/typescript/corpus/ambient-exports.diffB-A.txt @@ -20,11 +20,11 @@ {-(Assignment {-(Identifier)-} {-(Empty)-})-})-} - {-( + {-(Statements {-(Return {-(Hash {-(ShorthandPropertyIdentifier)-} {-(ShorthandPropertyIdentifier)-})-})-})-}) ->(Class {+(Identifier)+} - {+([])+}) })) + {+(Statements)+}) })) diff --git a/test/fixtures/typescript/corpus/ambient-exports.parseA.txt b/test/fixtures/typescript/corpus/ambient-exports.parseA.txt index 3f6f3d427..29e69c225 100644 --- a/test/fixtures/typescript/corpus/ambient-exports.parseA.txt +++ b/test/fixtures/typescript/corpus/ambient-exports.parseA.txt @@ -2,4 +2,4 @@ (DefaultExport (Class (Identifier) - ([])))) + (Statements)))) diff --git a/test/fixtures/typescript/corpus/ambient-exports.parseB.txt b/test/fixtures/typescript/corpus/ambient-exports.parseB.txt index c95a6be19..daab22e4f 100644 --- a/test/fixtures/typescript/corpus/ambient-exports.parseB.txt +++ b/test/fixtures/typescript/corpus/ambient-exports.parseB.txt @@ -20,7 +20,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Hash (ShorthandPropertyIdentifier) diff --git a/test/fixtures/typescript/corpus/anonymous-function.diffA-B.txt b/test/fixtures/typescript/corpus/anonymous-function.diffA-B.txt index 7d647cf4c..a413f45aa 100644 --- a/test/fixtures/typescript/corpus/anonymous-function.diffA-B.txt +++ b/test/fixtures/typescript/corpus/anonymous-function.diffA-B.txt @@ -24,7 +24,7 @@ {+(Assignment {+(Identifier)+} {+(Empty)+})+})+} - ( + (Statements (Return { (Plus {-(Identifier)-} diff --git a/test/fixtures/typescript/corpus/anonymous-function.diffB-A.txt b/test/fixtures/typescript/corpus/anonymous-function.diffB-A.txt index 378fb36fa..14e2117e6 100644 --- a/test/fixtures/typescript/corpus/anonymous-function.diffB-A.txt +++ b/test/fixtures/typescript/corpus/anonymous-function.diffB-A.txt @@ -24,7 +24,7 @@ {-(Assignment {-(Identifier)-} {-(Empty)-})-})-} - ( + (Statements (Return { (Times {-(Identifier)-} diff --git a/test/fixtures/typescript/corpus/anonymous-function.parseA.txt b/test/fixtures/typescript/corpus/anonymous-function.parseA.txt index b16aad149..410fa0126 100644 --- a/test/fixtures/typescript/corpus/anonymous-function.parseA.txt +++ b/test/fixtures/typescript/corpus/anonymous-function.parseA.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Plus (Identifier) diff --git a/test/fixtures/typescript/corpus/anonymous-function.parseB.txt b/test/fixtures/typescript/corpus/anonymous-function.parseB.txt index a04c5cd22..f4cf6bbd8 100644 --- a/test/fixtures/typescript/corpus/anonymous-function.parseB.txt +++ b/test/fixtures/typescript/corpus/anonymous-function.parseB.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Times (Identifier) diff --git a/test/fixtures/typescript/corpus/anonymous-parameterless-function.diffA-B.txt b/test/fixtures/typescript/corpus/anonymous-parameterless-function.diffA-B.txt index b2b1fd3d9..33fc55d49 100644 --- a/test/fixtures/typescript/corpus/anonymous-parameterless-function.diffA-B.txt +++ b/test/fixtures/typescript/corpus/anonymous-parameterless-function.diffA-B.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Empty) - ( + (Statements (Return { (TextElement) ->(TextElement) })))) diff --git a/test/fixtures/typescript/corpus/anonymous-parameterless-function.diffB-A.txt b/test/fixtures/typescript/corpus/anonymous-parameterless-function.diffB-A.txt index b2b1fd3d9..33fc55d49 100644 --- a/test/fixtures/typescript/corpus/anonymous-parameterless-function.diffB-A.txt +++ b/test/fixtures/typescript/corpus/anonymous-parameterless-function.diffB-A.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Empty) - ( + (Statements (Return { (TextElement) ->(TextElement) })))) diff --git a/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseA.txt b/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseA.txt index 84537c07d..bb24b8ce4 100644 --- a/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseA.txt +++ b/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseA.txt @@ -3,6 +3,6 @@ (Empty) (Empty) (Empty) - ( + (Statements (Return (TextElement))))) diff --git a/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseB.txt b/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseB.txt index 84537c07d..bb24b8ce4 100644 --- a/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseB.txt +++ b/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseB.txt @@ -3,6 +3,6 @@ (Empty) (Empty) (Empty) - ( + (Statements (Return (TextElement))))) diff --git a/test/fixtures/typescript/corpus/arrow-function.diffA-B.txt b/test/fixtures/typescript/corpus/arrow-function.diffA-B.txt index 1edf8182d..600b385ff 100644 --- a/test/fixtures/typescript/corpus/arrow-function.diffA-B.txt +++ b/test/fixtures/typescript/corpus/arrow-function.diffA-B.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return { (Identifier) ->(Identifier) })))) diff --git a/test/fixtures/typescript/corpus/arrow-function.diffB-A.txt b/test/fixtures/typescript/corpus/arrow-function.diffB-A.txt index 1edf8182d..600b385ff 100644 --- a/test/fixtures/typescript/corpus/arrow-function.diffB-A.txt +++ b/test/fixtures/typescript/corpus/arrow-function.diffB-A.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return { (Identifier) ->(Identifier) })))) diff --git a/test/fixtures/typescript/corpus/arrow-function.parseA.txt b/test/fixtures/typescript/corpus/arrow-function.parseA.txt index 1bced8e40..e178c9e7c 100644 --- a/test/fixtures/typescript/corpus/arrow-function.parseA.txt +++ b/test/fixtures/typescript/corpus/arrow-function.parseA.txt @@ -17,6 +17,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier))))) diff --git a/test/fixtures/typescript/corpus/arrow-function.parseB.txt b/test/fixtures/typescript/corpus/arrow-function.parseB.txt index 1bced8e40..e178c9e7c 100644 --- a/test/fixtures/typescript/corpus/arrow-function.parseB.txt +++ b/test/fixtures/typescript/corpus/arrow-function.parseB.txt @@ -17,6 +17,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier))))) diff --git a/test/fixtures/typescript/corpus/break.diffA-B.txt b/test/fixtures/typescript/corpus/break.diffA-B.txt index eff385027..46eb71902 100644 --- a/test/fixtures/typescript/corpus/break.diffA-B.txt +++ b/test/fixtures/typescript/corpus/break.diffA-B.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements {+(Continue {+(Empty)+})+} {-(Break diff --git a/test/fixtures/typescript/corpus/break.diffB-A.txt b/test/fixtures/typescript/corpus/break.diffB-A.txt index 745ef1761..44e6c7bdc 100644 --- a/test/fixtures/typescript/corpus/break.diffB-A.txt +++ b/test/fixtures/typescript/corpus/break.diffB-A.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements {+(Break {+(Empty)+})+} {-(Continue diff --git a/test/fixtures/typescript/corpus/break.parseA.txt b/test/fixtures/typescript/corpus/break.parseA.txt index e927cd94c..c0af1c973 100644 --- a/test/fixtures/typescript/corpus/break.parseA.txt +++ b/test/fixtures/typescript/corpus/break.parseA.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements (Break (Empty))) (Empty)) diff --git a/test/fixtures/typescript/corpus/break.parseB.txt b/test/fixtures/typescript/corpus/break.parseB.txt index 9618a22b5..0c30ef033 100644 --- a/test/fixtures/typescript/corpus/break.parseB.txt +++ b/test/fixtures/typescript/corpus/break.parseB.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements (Continue (Empty))) (Empty)) diff --git a/test/fixtures/typescript/corpus/chained-callbacks.diffA-B.txt b/test/fixtures/typescript/corpus/chained-callbacks.diffA-B.txt index f88bc58c9..ba36adf30 100644 --- a/test/fixtures/typescript/corpus/chained-callbacks.diffA-B.txt +++ b/test/fixtures/typescript/corpus/chained-callbacks.diffA-B.txt @@ -15,7 +15,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (MemberAccess { (Identifier) diff --git a/test/fixtures/typescript/corpus/chained-callbacks.diffB-A.txt b/test/fixtures/typescript/corpus/chained-callbacks.diffB-A.txt index f88bc58c9..ba36adf30 100644 --- a/test/fixtures/typescript/corpus/chained-callbacks.diffB-A.txt +++ b/test/fixtures/typescript/corpus/chained-callbacks.diffB-A.txt @@ -15,7 +15,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (MemberAccess { (Identifier) diff --git a/test/fixtures/typescript/corpus/chained-callbacks.parseA.txt b/test/fixtures/typescript/corpus/chained-callbacks.parseA.txt index f54ff9ba2..a6043e559 100644 --- a/test/fixtures/typescript/corpus/chained-callbacks.parseA.txt +++ b/test/fixtures/typescript/corpus/chained-callbacks.parseA.txt @@ -14,7 +14,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/chained-callbacks.parseB.txt b/test/fixtures/typescript/corpus/chained-callbacks.parseB.txt index f54ff9ba2..a6043e559 100644 --- a/test/fixtures/typescript/corpus/chained-callbacks.parseB.txt +++ b/test/fixtures/typescript/corpus/chained-callbacks.parseB.txt @@ -14,7 +14,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/class.diffA-B.txt b/test/fixtures/typescript/corpus/class.diffA-B.txt index dab5d8cb8..e5098c83c 100644 --- a/test/fixtures/typescript/corpus/class.diffA-B.txt +++ b/test/fixtures/typescript/corpus/class.diffA-B.txt @@ -10,7 +10,7 @@ (ExtendsClause { (TypeIdentifier) ->(TypeIdentifier) }) - ( + (Statements {+(Method {+(Empty)+} {+(Empty)+} @@ -25,7 +25,7 @@ {+(Assignment {+(Identifier)+} {+(Empty)+})+})+} - {+( + {+(Statements {+(Return {+(Identifier)+})+})+})+} {+(Method @@ -42,7 +42,7 @@ {+(Assignment {+(Identifier)+} {+(Empty)+})+})+} - {+( + {+(Statements {+(Return {+(Identifier)+})+})+})+} {+(Method @@ -59,7 +59,7 @@ {+(Assignment {+(Identifier)+} {+(Empty)+})+})+} - {+( + {+(Statements {+(Return {+(Identifier)+})+})+})+} {-(PublicFieldDefinition @@ -82,7 +82,7 @@ {-(Assignment {-(Identifier)-} {-(Empty)-})-})-} - {-( + {-(Statements {-(Return {-(Identifier)-})-})-})-} {-(Method @@ -99,7 +99,7 @@ {-(Assignment {-(Identifier)-} {-(Empty)-})-})-} - {-( + {-(Statements {-(Return {-(Identifier)-})-})-})-} {-(Method @@ -116,6 +116,6 @@ {-(Assignment {-(Identifier)-} {-(Empty)-})-})-} - {-( + {-(Statements {-(Return {-(Identifier)-})-})-})-}))) diff --git a/test/fixtures/typescript/corpus/class.diffB-A.txt b/test/fixtures/typescript/corpus/class.diffB-A.txt index 85ae83908..25a835604 100644 --- a/test/fixtures/typescript/corpus/class.diffB-A.txt +++ b/test/fixtures/typescript/corpus/class.diffB-A.txt @@ -10,7 +10,7 @@ (ExtendsClause { (TypeIdentifier) ->(TypeIdentifier) }) - ( + (Statements {+(PublicFieldDefinition {+(Empty)+} {+(Empty)+} @@ -32,7 +32,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier)))) (Method @@ -50,7 +50,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier)))) (Method @@ -68,6 +68,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier))))))) diff --git a/test/fixtures/typescript/corpus/class.parseA.txt b/test/fixtures/typescript/corpus/class.parseA.txt index 2626ef337..0d3c5096e 100644 --- a/test/fixtures/typescript/corpus/class.parseA.txt +++ b/test/fixtures/typescript/corpus/class.parseA.txt @@ -7,7 +7,7 @@ (Identifier) (ExtendsClause (TypeIdentifier)) - ( + (Statements (PublicFieldDefinition (Empty) (Empty) @@ -28,7 +28,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier)))) (Method @@ -45,7 +45,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier)))) (Method @@ -62,6 +62,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier))))))) diff --git a/test/fixtures/typescript/corpus/class.parseB.txt b/test/fixtures/typescript/corpus/class.parseB.txt index ff695c7d8..79c19acf2 100644 --- a/test/fixtures/typescript/corpus/class.parseB.txt +++ b/test/fixtures/typescript/corpus/class.parseB.txt @@ -7,7 +7,7 @@ (Identifier) (ExtendsClause (TypeIdentifier)) - ( + (Statements (Method (Empty) (Empty) @@ -22,7 +22,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier)))) (Method @@ -39,7 +39,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier)))) (Method @@ -56,6 +56,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Identifier))))))) diff --git a/test/fixtures/typescript/corpus/continue.diffA-B.txt b/test/fixtures/typescript/corpus/continue.diffA-B.txt index 745ef1761..44e6c7bdc 100644 --- a/test/fixtures/typescript/corpus/continue.diffA-B.txt +++ b/test/fixtures/typescript/corpus/continue.diffA-B.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements {+(Break {+(Empty)+})+} {-(Continue diff --git a/test/fixtures/typescript/corpus/continue.diffB-A.txt b/test/fixtures/typescript/corpus/continue.diffB-A.txt index eff385027..46eb71902 100644 --- a/test/fixtures/typescript/corpus/continue.diffB-A.txt +++ b/test/fixtures/typescript/corpus/continue.diffB-A.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements {+(Continue {+(Empty)+})+} {-(Break diff --git a/test/fixtures/typescript/corpus/continue.parseA.txt b/test/fixtures/typescript/corpus/continue.parseA.txt index 9618a22b5..0c30ef033 100644 --- a/test/fixtures/typescript/corpus/continue.parseA.txt +++ b/test/fixtures/typescript/corpus/continue.parseA.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements (Continue (Empty))) (Empty)) diff --git a/test/fixtures/typescript/corpus/continue.parseB.txt b/test/fixtures/typescript/corpus/continue.parseB.txt index e927cd94c..c0af1c973 100644 --- a/test/fixtures/typescript/corpus/continue.parseB.txt +++ b/test/fixtures/typescript/corpus/continue.parseB.txt @@ -8,12 +8,12 @@ (Float)) (Update (Identifier)) - ( + (Statements (If (StrictEqual (Identifier) (Float)) - ( + (Statements (Break (Empty))) (Empty)) diff --git a/test/fixtures/typescript/corpus/do-while-statement.diffA-B.txt b/test/fixtures/typescript/corpus/do-while-statement.diffA-B.txt index 30c06d609..5935813f5 100644 --- a/test/fixtures/typescript/corpus/do-while-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/do-while-statement.diffA-B.txt @@ -2,7 +2,7 @@ (DoWhile { (Boolean) ->(Boolean) } - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/do-while-statement.diffB-A.txt b/test/fixtures/typescript/corpus/do-while-statement.diffB-A.txt index 30c06d609..5935813f5 100644 --- a/test/fixtures/typescript/corpus/do-while-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/do-while-statement.diffB-A.txt @@ -2,7 +2,7 @@ (DoWhile { (Boolean) ->(Boolean) } - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/do-while-statement.parseA.txt b/test/fixtures/typescript/corpus/do-while-statement.parseA.txt index 92c41b1a1..a75cc5e53 100644 --- a/test/fixtures/typescript/corpus/do-while-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/do-while-statement.parseA.txt @@ -1,7 +1,7 @@ (Program (DoWhile (Boolean) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/do-while-statement.parseB.txt b/test/fixtures/typescript/corpus/do-while-statement.parseB.txt index 92c41b1a1..a75cc5e53 100644 --- a/test/fixtures/typescript/corpus/do-while-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/do-while-statement.parseB.txt @@ -1,7 +1,7 @@ (Program (DoWhile (Boolean) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/export.diffA-B.txt b/test/fixtures/typescript/corpus/export.diffA-B.txt index 4e6aea904..d820a0e81 100644 --- a/test/fixtures/typescript/corpus/export.diffA-B.txt +++ b/test/fixtures/typescript/corpus/export.diffA-B.txt @@ -52,13 +52,13 @@ {+(Empty)+} {+(Empty)+} {+(Identifier)+} - {+([])+})+})+} + {+(Statements)+})+})+} (DefaultExport (Function (Empty) (Empty) (Empty) - ([]))) + (Statements))) {+(QualifiedExport)+} {+(DefaultExport {+(TextElement)+})+} @@ -69,7 +69,7 @@ {-(Empty)-} {-(Empty)-} {-(Identifier)-} - {-([])-})-})-} + {-(Statements)-})-})-} {-(QualifiedExport)-} {-(DefaultExport {-(TextElement)-})-} diff --git a/test/fixtures/typescript/corpus/export.diffB-A.txt b/test/fixtures/typescript/corpus/export.diffB-A.txt index c0d98eefd..fca2269b7 100644 --- a/test/fixtures/typescript/corpus/export.diffB-A.txt +++ b/test/fixtures/typescript/corpus/export.diffB-A.txt @@ -55,19 +55,19 @@ {-(Empty)-} {-(Empty)-} {-(Identifier)-} - {-([])-})-})-} + {-(Statements)-})-})-} (DefaultExport (Function (Empty) (Empty) (Empty) - ([]))) + (Statements))) {+(DefaultExport {+(Function {+(Empty)+} {+(Empty)+} {+(Identifier)+} - {+([])+})+})+} + {+(Statements)+})+})+} { (QualifiedExport) ->(QualifiedExport) } (DefaultExport diff --git a/test/fixtures/typescript/corpus/export.parseA.txt b/test/fixtures/typescript/corpus/export.parseA.txt index 5e293e404..c65411988 100644 --- a/test/fixtures/typescript/corpus/export.parseA.txt +++ b/test/fixtures/typescript/corpus/export.parseA.txt @@ -40,13 +40,13 @@ (Empty) (Empty) (Empty) - ([]))) + (Statements))) (DefaultExport (Function (Empty) (Empty) (Identifier) - ([]))) + (Statements))) (QualifiedExport) (DefaultExport (TextElement)) diff --git a/test/fixtures/typescript/corpus/export.parseB.txt b/test/fixtures/typescript/corpus/export.parseB.txt index 12ec54bef..a04091e87 100644 --- a/test/fixtures/typescript/corpus/export.parseB.txt +++ b/test/fixtures/typescript/corpus/export.parseB.txt @@ -40,13 +40,13 @@ (Empty) (Empty) (Identifier) - ([]))) + (Statements))) (DefaultExport (Function (Empty) (Empty) (Empty) - ([]))) + (Statements))) (QualifiedExport) (DefaultExport (TextElement)) diff --git a/test/fixtures/typescript/corpus/for-in-statement.diffA-B.txt b/test/fixtures/typescript/corpus/for-in-statement.diffA-B.txt index 4faf0ca9a..7f4c7fe4a 100644 --- a/test/fixtures/typescript/corpus/for-in-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/for-in-statement.diffA-B.txt @@ -4,7 +4,7 @@ ->(Identifier) } { (Identifier) ->(Identifier) } - ( + (Statements (Call { (Identifier) ->(Identifier) } diff --git a/test/fixtures/typescript/corpus/for-in-statement.diffB-A.txt b/test/fixtures/typescript/corpus/for-in-statement.diffB-A.txt index 4faf0ca9a..7f4c7fe4a 100644 --- a/test/fixtures/typescript/corpus/for-in-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/for-in-statement.diffB-A.txt @@ -4,7 +4,7 @@ ->(Identifier) } { (Identifier) ->(Identifier) } - ( + (Statements (Call { (Identifier) ->(Identifier) } diff --git a/test/fixtures/typescript/corpus/for-in-statement.parseA.txt b/test/fixtures/typescript/corpus/for-in-statement.parseA.txt index c41e5a7f1..79a82b79a 100644 --- a/test/fixtures/typescript/corpus/for-in-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/for-in-statement.parseA.txt @@ -2,7 +2,7 @@ (ForEach (Identifier) (Identifier) - ( + (Statements (Call (Identifier) (Empty))))) diff --git a/test/fixtures/typescript/corpus/for-in-statement.parseB.txt b/test/fixtures/typescript/corpus/for-in-statement.parseB.txt index c41e5a7f1..79a82b79a 100644 --- a/test/fixtures/typescript/corpus/for-in-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/for-in-statement.parseB.txt @@ -2,7 +2,7 @@ (ForEach (Identifier) (Identifier) - ( + (Statements (Call (Identifier) (Empty))))) diff --git a/test/fixtures/typescript/corpus/for-loop-with-in-statement.diffA-B.txt b/test/fixtures/typescript/corpus/for-loop-with-in-statement.diffA-B.txt index dcd085128..e3184832c 100644 --- a/test/fixtures/typescript/corpus/for-loop-with-in-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/for-loop-with-in-statement.diffA-B.txt @@ -13,7 +13,7 @@ (Identifier)) (Update (Identifier)) - ( + (Statements (Call { (Identifier) ->(Identifier) } diff --git a/test/fixtures/typescript/corpus/for-loop-with-in-statement.diffB-A.txt b/test/fixtures/typescript/corpus/for-loop-with-in-statement.diffB-A.txt index dcd085128..e3184832c 100644 --- a/test/fixtures/typescript/corpus/for-loop-with-in-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/for-loop-with-in-statement.diffB-A.txt @@ -13,7 +13,7 @@ (Identifier)) (Update (Identifier)) - ( + (Statements (Call { (Identifier) ->(Identifier) } diff --git a/test/fixtures/typescript/corpus/for-loop-with-in-statement.parseA.txt b/test/fixtures/typescript/corpus/for-loop-with-in-statement.parseA.txt index 09777939f..0c1d70fb4 100644 --- a/test/fixtures/typescript/corpus/for-loop-with-in-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/for-loop-with-in-statement.parseA.txt @@ -12,7 +12,7 @@ (Identifier)) (Update (Identifier)) - ( + (Statements (Call (Identifier) (Empty))))) diff --git a/test/fixtures/typescript/corpus/for-loop-with-in-statement.parseB.txt b/test/fixtures/typescript/corpus/for-loop-with-in-statement.parseB.txt index 09777939f..0c1d70fb4 100644 --- a/test/fixtures/typescript/corpus/for-loop-with-in-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/for-loop-with-in-statement.parseB.txt @@ -12,7 +12,7 @@ (Identifier)) (Update (Identifier)) - ( + (Statements (Call (Identifier) (Empty))))) diff --git a/test/fixtures/typescript/corpus/for-of-statement.diffA-B.txt b/test/fixtures/typescript/corpus/for-of-statement.diffA-B.txt index 9886795f9..f5e052f79 100644 --- a/test/fixtures/typescript/corpus/for-of-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/for-of-statement.diffA-B.txt @@ -4,7 +4,7 @@ ->(Identifier) } { (Identifier) ->(Identifier) } - ( + (Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/typescript/corpus/for-of-statement.diffB-A.txt b/test/fixtures/typescript/corpus/for-of-statement.diffB-A.txt index 9886795f9..f5e052f79 100644 --- a/test/fixtures/typescript/corpus/for-of-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/for-of-statement.diffB-A.txt @@ -4,7 +4,7 @@ ->(Identifier) } { (Identifier) ->(Identifier) } - ( + (Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/typescript/corpus/for-of-statement.parseA.txt b/test/fixtures/typescript/corpus/for-of-statement.parseA.txt index 025a1cf60..3c9704a36 100644 --- a/test/fixtures/typescript/corpus/for-of-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/for-of-statement.parseA.txt @@ -2,7 +2,7 @@ (ForOf (Identifier) (Identifier) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/for-of-statement.parseB.txt b/test/fixtures/typescript/corpus/for-of-statement.parseB.txt index 025a1cf60..3c9704a36 100644 --- a/test/fixtures/typescript/corpus/for-of-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/for-of-statement.parseB.txt @@ -2,7 +2,7 @@ (ForOf (Identifier) (Identifier) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/for-statement.diffA-B.txt b/test/fixtures/typescript/corpus/for-statement.diffA-B.txt index 42df10b93..1cf044616 100644 --- a/test/fixtures/typescript/corpus/for-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/for-statement.diffA-B.txt @@ -13,7 +13,7 @@ ->(Float) }) (Update (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/for-statement.diffB-A.txt b/test/fixtures/typescript/corpus/for-statement.diffB-A.txt index 42df10b93..1cf044616 100644 --- a/test/fixtures/typescript/corpus/for-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/for-statement.diffB-A.txt @@ -13,7 +13,7 @@ ->(Float) }) (Update (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/for-statement.parseA.txt b/test/fixtures/typescript/corpus/for-statement.parseA.txt index 4874a22fc..fe2179965 100644 --- a/test/fixtures/typescript/corpus/for-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/for-statement.parseA.txt @@ -12,7 +12,7 @@ (Float)) (Update (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/for-statement.parseB.txt b/test/fixtures/typescript/corpus/for-statement.parseB.txt index 4874a22fc..fe2179965 100644 --- a/test/fixtures/typescript/corpus/for-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/for-statement.parseB.txt @@ -12,7 +12,7 @@ (Float)) (Update (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/function-call-args.diffA-B.txt b/test/fixtures/typescript/corpus/function-call-args.diffA-B.txt index cb4b6e2d9..9ab5e70c0 100644 --- a/test/fixtures/typescript/corpus/function-call-args.diffA-B.txt +++ b/test/fixtures/typescript/corpus/function-call-args.diffA-B.txt @@ -29,7 +29,7 @@ {+(Assignment {+(Identifier)+} {+(Empty)+})+})+} - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/function-call-args.diffB-A.txt b/test/fixtures/typescript/corpus/function-call-args.diffB-A.txt index 194e964af..46e0b5c06 100644 --- a/test/fixtures/typescript/corpus/function-call-args.diffB-A.txt +++ b/test/fixtures/typescript/corpus/function-call-args.diffB-A.txt @@ -29,7 +29,7 @@ {-(Assignment {-(Identifier)-} {-(Empty)-})-})-} - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/function-call-args.parseA.txt b/test/fixtures/typescript/corpus/function-call-args.parseA.txt index 3f9ef783e..ed0d71201 100644 --- a/test/fixtures/typescript/corpus/function-call-args.parseA.txt +++ b/test/fixtures/typescript/corpus/function-call-args.parseA.txt @@ -21,7 +21,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/function-call-args.parseB.txt b/test/fixtures/typescript/corpus/function-call-args.parseB.txt index 3f9ef783e..ed0d71201 100644 --- a/test/fixtures/typescript/corpus/function-call-args.parseB.txt +++ b/test/fixtures/typescript/corpus/function-call-args.parseB.txt @@ -21,7 +21,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/function.diffA-B.txt b/test/fixtures/typescript/corpus/function.diffA-B.txt index a37e4e145..90c7297b0 100644 --- a/test/fixtures/typescript/corpus/function.diffA-B.txt +++ b/test/fixtures/typescript/corpus/function.diffA-B.txt @@ -25,7 +25,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements { (Identifier) ->(Identifier) })) (Empty)) diff --git a/test/fixtures/typescript/corpus/function.diffB-A.txt b/test/fixtures/typescript/corpus/function.diffB-A.txt index fa75d27e7..a3184822d 100644 --- a/test/fixtures/typescript/corpus/function.diffB-A.txt +++ b/test/fixtures/typescript/corpus/function.diffB-A.txt @@ -25,7 +25,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements { (Identifier) ->(Identifier) })) (Empty)) diff --git a/test/fixtures/typescript/corpus/function.parseA.txt b/test/fixtures/typescript/corpus/function.parseA.txt index 38ae68db9..b98eff32c 100644 --- a/test/fixtures/typescript/corpus/function.parseA.txt +++ b/test/fixtures/typescript/corpus/function.parseA.txt @@ -22,6 +22,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Identifier))) (Empty)) diff --git a/test/fixtures/typescript/corpus/function.parseB.txt b/test/fixtures/typescript/corpus/function.parseB.txt index 7db16df9e..493f1a5fc 100644 --- a/test/fixtures/typescript/corpus/function.parseB.txt +++ b/test/fixtures/typescript/corpus/function.parseB.txt @@ -18,6 +18,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Identifier))) (Empty)) diff --git a/test/fixtures/typescript/corpus/generator-function.diffA-B.txt b/test/fixtures/typescript/corpus/generator-function.diffA-B.txt index 65f3d8507..2f4f58433 100644 --- a/test/fixtures/typescript/corpus/generator-function.diffA-B.txt +++ b/test/fixtures/typescript/corpus/generator-function.diffA-B.txt @@ -18,7 +18,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Yield (Empty)) (Yield diff --git a/test/fixtures/typescript/corpus/generator-function.diffB-A.txt b/test/fixtures/typescript/corpus/generator-function.diffB-A.txt index 65f3d8507..2f4f58433 100644 --- a/test/fixtures/typescript/corpus/generator-function.diffB-A.txt +++ b/test/fixtures/typescript/corpus/generator-function.diffB-A.txt @@ -18,7 +18,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Yield (Empty)) (Yield diff --git a/test/fixtures/typescript/corpus/generator-function.parseA.txt b/test/fixtures/typescript/corpus/generator-function.parseA.txt index d86eafa99..fd25c91b3 100644 --- a/test/fixtures/typescript/corpus/generator-function.parseA.txt +++ b/test/fixtures/typescript/corpus/generator-function.parseA.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Yield (Empty)) (Yield diff --git a/test/fixtures/typescript/corpus/generator-function.parseB.txt b/test/fixtures/typescript/corpus/generator-function.parseB.txt index d86eafa99..fd25c91b3 100644 --- a/test/fixtures/typescript/corpus/generator-function.parseB.txt +++ b/test/fixtures/typescript/corpus/generator-function.parseB.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Yield (Empty)) (Yield diff --git a/test/fixtures/typescript/corpus/if-else.diffA-B.txt b/test/fixtures/typescript/corpus/if-else.diffA-B.txt index 8d402c80e..41281f5e5 100644 --- a/test/fixtures/typescript/corpus/if-else.diffA-B.txt +++ b/test/fixtures/typescript/corpus/if-else.diffA-B.txt @@ -8,7 +8,7 @@ { (Identifier) ->(Identifier) } { (Identifier) - ->( + ->(Statements {+(Identifier)+}) } (If { (Identifier) @@ -19,7 +19,7 @@ { (Identifier) ->(Identifier) } { (Identifier) - ->( + ->(Statements {+(Identifier)+}) } { (Identifier) ->(Identifier) }))))) diff --git a/test/fixtures/typescript/corpus/if-else.diffB-A.txt b/test/fixtures/typescript/corpus/if-else.diffB-A.txt index 514f0cd36..a7e842460 100644 --- a/test/fixtures/typescript/corpus/if-else.diffB-A.txt +++ b/test/fixtures/typescript/corpus/if-else.diffB-A.txt @@ -7,7 +7,7 @@ (If { (Identifier) ->(Identifier) } - { ( + { (Statements {-(Identifier)-}) ->(Identifier) } (If @@ -18,7 +18,7 @@ (If { (Identifier) ->(Identifier) } - { ( + { (Statements {-(Identifier)-}) ->(Identifier) } { (Identifier) diff --git a/test/fixtures/typescript/corpus/if-else.parseB.txt b/test/fixtures/typescript/corpus/if-else.parseB.txt index 3a8f90cf1..2402f8fd0 100644 --- a/test/fixtures/typescript/corpus/if-else.parseB.txt +++ b/test/fixtures/typescript/corpus/if-else.parseB.txt @@ -4,13 +4,13 @@ (Identifier) (If (Identifier) - ( + (Statements (Identifier)) (If (Identifier) (Identifier) (If (Identifier) - ( + (Statements (Identifier)) (Identifier)))))) diff --git a/test/fixtures/typescript/corpus/if.diffA-B.txt b/test/fixtures/typescript/corpus/if.diffA-B.txt index 2a90eee30..329dbee61 100644 --- a/test/fixtures/typescript/corpus/if.diffA-B.txt +++ b/test/fixtures/typescript/corpus/if.diffA-B.txt @@ -4,7 +4,7 @@ ->(MemberAccess {+(Identifier)+} {+(Identifier)+}) } - ( + (Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/typescript/corpus/if.diffB-A.txt b/test/fixtures/typescript/corpus/if.diffB-A.txt index a6742d0e3..58379f889 100644 --- a/test/fixtures/typescript/corpus/if.diffB-A.txt +++ b/test/fixtures/typescript/corpus/if.diffB-A.txt @@ -4,7 +4,7 @@ {-(Identifier)-} {-(Identifier)-}) ->(Identifier) } - ( + (Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/typescript/corpus/if.parseA.txt b/test/fixtures/typescript/corpus/if.parseA.txt index 23bee3aca..c319b1eb0 100644 --- a/test/fixtures/typescript/corpus/if.parseA.txt +++ b/test/fixtures/typescript/corpus/if.parseA.txt @@ -1,7 +1,7 @@ (Program (If (Identifier) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/if.parseB.txt b/test/fixtures/typescript/corpus/if.parseB.txt index 82a81394a..4c23c44b9 100644 --- a/test/fixtures/typescript/corpus/if.parseB.txt +++ b/test/fixtures/typescript/corpus/if.parseB.txt @@ -3,7 +3,7 @@ (MemberAccess (Identifier) (Identifier)) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/import.diffA-B.txt b/test/fixtures/typescript/corpus/import.diffA-B.txt index ae75bfbfd..d0fcad063 100644 --- a/test/fixtures/typescript/corpus/import.diffA-B.txt +++ b/test/fixtures/typescript/corpus/import.diffA-B.txt @@ -6,10 +6,10 @@ ->(Import) } {+(Import)+} {+(Import)+} -{+( +{+(Statements {+(Import)+} {+(Import)+})+} -{+( +{+(Statements {+(Import)+} {+(QualifiedAliasedImport {+(Identifier)+})+})+} @@ -19,10 +19,10 @@ {-(Import)-} {-(Import)-} {-(Import)-} -{-( +{-(Statements {-(Import)-} {-(Import)-})-} -{-( +{-(Statements {-(Import)-} {-(QualifiedAliasedImport {-(Identifier)-})-})-} diff --git a/test/fixtures/typescript/corpus/import.diffB-A.txt b/test/fixtures/typescript/corpus/import.diffB-A.txt index 475d4a5ee..cc1429eee 100644 --- a/test/fixtures/typescript/corpus/import.diffB-A.txt +++ b/test/fixtures/typescript/corpus/import.diffB-A.txt @@ -5,10 +5,10 @@ {+(Import)+} {+(Import)+} {+(Import)+} -{+( +{+(Statements {+(Import)+} {+(Import)+})+} -{+( +{+(Statements {+(Import)+} {+(QualifiedAliasedImport {+(Identifier)+})+})+} @@ -21,10 +21,10 @@ {-(Import)-} {-(Import)-} {-(Import)-} -{-( +{-(Statements {-(Import)-} {-(Import)-})-} -{-( +{-(Statements {-(Import)-} {-(QualifiedAliasedImport {-(Identifier)-})-})-} diff --git a/test/fixtures/typescript/corpus/import.parseA.txt b/test/fixtures/typescript/corpus/import.parseA.txt index 4301638e4..0441b60eb 100644 --- a/test/fixtures/typescript/corpus/import.parseA.txt +++ b/test/fixtures/typescript/corpus/import.parseA.txt @@ -5,10 +5,10 @@ (Import) (Import) (Import) - ( + (Statements (Import) (Import)) - ( + (Statements (Import) (QualifiedAliasedImport (Identifier))) diff --git a/test/fixtures/typescript/corpus/import.parseB.txt b/test/fixtures/typescript/corpus/import.parseB.txt index 037e1c7c8..069afffe6 100644 --- a/test/fixtures/typescript/corpus/import.parseB.txt +++ b/test/fixtures/typescript/corpus/import.parseB.txt @@ -5,10 +5,10 @@ (Import) (Import) (Import) - ( + (Statements (Import) (Import)) - ( + (Statements (Import) (QualifiedAliasedImport (Identifier))) diff --git a/test/fixtures/typescript/corpus/method-definition.diffA-B.txt b/test/fixtures/typescript/corpus/method-definition.diffA-B.txt index 558fc034e..8c1179c02 100644 --- a/test/fixtures/typescript/corpus/method-definition.diffA-B.txt +++ b/test/fixtures/typescript/corpus/method-definition.diffA-B.txt @@ -12,4 +12,4 @@ {-(TypeIdentifier)-})-} (Empty) (Identifier) - ([])))) + (Statements)))) diff --git a/test/fixtures/typescript/corpus/method-definition.diffB-A.txt b/test/fixtures/typescript/corpus/method-definition.diffB-A.txt index dcf092e33..de3d7407c 100644 --- a/test/fixtures/typescript/corpus/method-definition.diffB-A.txt +++ b/test/fixtures/typescript/corpus/method-definition.diffB-A.txt @@ -11,4 +11,4 @@ ->(TypeIdentifier) }) (Empty) (Identifier) - ([])))) + (Statements)))) diff --git a/test/fixtures/typescript/corpus/method-definition.parseA.txt b/test/fixtures/typescript/corpus/method-definition.parseA.txt index 0791b7882..be3406a4f 100644 --- a/test/fixtures/typescript/corpus/method-definition.parseA.txt +++ b/test/fixtures/typescript/corpus/method-definition.parseA.txt @@ -9,4 +9,4 @@ (TypeIdentifier)) (Empty) (Identifier) - ([])))) + (Statements)))) diff --git a/test/fixtures/typescript/corpus/method-definition.parseB.txt b/test/fixtures/typescript/corpus/method-definition.parseB.txt index 3ca2b792c..5f149585f 100644 --- a/test/fixtures/typescript/corpus/method-definition.parseB.txt +++ b/test/fixtures/typescript/corpus/method-definition.parseB.txt @@ -9,4 +9,4 @@ (PredefinedType)) (Empty) (Identifier) - ([])))) + (Statements)))) diff --git a/test/fixtures/typescript/corpus/named-function.diffA-B.txt b/test/fixtures/typescript/corpus/named-function.diffA-B.txt index 097c4555b..aec245b08 100644 --- a/test/fixtures/typescript/corpus/named-function.diffA-B.txt +++ b/test/fixtures/typescript/corpus/named-function.diffA-B.txt @@ -18,7 +18,7 @@ {-(Assignment {-(Identifier)-} {-(Empty)-})-})-} - ( + (Statements {+(Return {+(Boolean)+})+} {-(Identifier)-})) diff --git a/test/fixtures/typescript/corpus/named-function.diffB-A.txt b/test/fixtures/typescript/corpus/named-function.diffB-A.txt index 0b02b2e5a..8ac7047e0 100644 --- a/test/fixtures/typescript/corpus/named-function.diffB-A.txt +++ b/test/fixtures/typescript/corpus/named-function.diffB-A.txt @@ -18,7 +18,7 @@ {+(Assignment {+(Identifier)+} {+(Empty)+})+})+} - ( + (Statements {+(Identifier)+} {-(Return {-(Boolean)-})-})) diff --git a/test/fixtures/typescript/corpus/named-function.parseA.txt b/test/fixtures/typescript/corpus/named-function.parseA.txt index 6f4b7d301..a0596d5bd 100644 --- a/test/fixtures/typescript/corpus/named-function.parseA.txt +++ b/test/fixtures/typescript/corpus/named-function.parseA.txt @@ -17,6 +17,6 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Identifier))) (Empty)) diff --git a/test/fixtures/typescript/corpus/named-function.parseB.txt b/test/fixtures/typescript/corpus/named-function.parseB.txt index fbad167d9..96d3c4033 100644 --- a/test/fixtures/typescript/corpus/named-function.parseB.txt +++ b/test/fixtures/typescript/corpus/named-function.parseB.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Identifier) - ( + (Statements (Return (Boolean)))) (Empty)) diff --git a/test/fixtures/typescript/corpus/nested-do-while-in-function.diffA-B.txt b/test/fixtures/typescript/corpus/nested-do-while-in-function.diffA-B.txt index c7eea5548..00dd2f4a3 100644 --- a/test/fixtures/typescript/corpus/nested-do-while-in-function.diffA-B.txt +++ b/test/fixtures/typescript/corpus/nested-do-while-in-function.diffA-B.txt @@ -17,11 +17,11 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (DoWhile { (Identifier) ->(Identifier) } - ( + (Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/typescript/corpus/nested-do-while-in-function.diffB-A.txt b/test/fixtures/typescript/corpus/nested-do-while-in-function.diffB-A.txt index c7eea5548..00dd2f4a3 100644 --- a/test/fixtures/typescript/corpus/nested-do-while-in-function.diffB-A.txt +++ b/test/fixtures/typescript/corpus/nested-do-while-in-function.diffB-A.txt @@ -17,11 +17,11 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (DoWhile { (Identifier) ->(Identifier) } - ( + (Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/typescript/corpus/nested-do-while-in-function.parseA.txt b/test/fixtures/typescript/corpus/nested-do-while-in-function.parseA.txt index 440deb76f..618761627 100644 --- a/test/fixtures/typescript/corpus/nested-do-while-in-function.parseA.txt +++ b/test/fixtures/typescript/corpus/nested-do-while-in-function.parseA.txt @@ -17,10 +17,10 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (DoWhile (Identifier) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/nested-do-while-in-function.parseB.txt b/test/fixtures/typescript/corpus/nested-do-while-in-function.parseB.txt index 440deb76f..618761627 100644 --- a/test/fixtures/typescript/corpus/nested-do-while-in-function.parseB.txt +++ b/test/fixtures/typescript/corpus/nested-do-while-in-function.parseB.txt @@ -17,10 +17,10 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (DoWhile (Identifier) - ( + (Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/nested-functions.diffA-B.txt b/test/fixtures/typescript/corpus/nested-functions.diffA-B.txt index 0b3c286a9..2a221fcdd 100644 --- a/test/fixtures/typescript/corpus/nested-functions.diffA-B.txt +++ b/test/fixtures/typescript/corpus/nested-functions.diffA-B.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Function (Empty) (Empty) @@ -36,7 +36,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/nested-functions.diffB-A.txt b/test/fixtures/typescript/corpus/nested-functions.diffB-A.txt index 0b3c286a9..2a221fcdd 100644 --- a/test/fixtures/typescript/corpus/nested-functions.diffB-A.txt +++ b/test/fixtures/typescript/corpus/nested-functions.diffB-A.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Function (Empty) (Empty) @@ -36,7 +36,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/nested-functions.parseA.txt b/test/fixtures/typescript/corpus/nested-functions.parseA.txt index 0955c8914..bba0968bd 100644 --- a/test/fixtures/typescript/corpus/nested-functions.parseA.txt +++ b/test/fixtures/typescript/corpus/nested-functions.parseA.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Function (Empty) (Empty) @@ -36,7 +36,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/nested-functions.parseB.txt b/test/fixtures/typescript/corpus/nested-functions.parseB.txt index 0955c8914..bba0968bd 100644 --- a/test/fixtures/typescript/corpus/nested-functions.parseB.txt +++ b/test/fixtures/typescript/corpus/nested-functions.parseB.txt @@ -17,7 +17,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Function (Empty) (Empty) @@ -36,7 +36,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/objects-with-methods.diffA-B.txt b/test/fixtures/typescript/corpus/objects-with-methods.diffA-B.txt index e7766878f..9c40be32f 100644 --- a/test/fixtures/typescript/corpus/objects-with-methods.diffA-B.txt +++ b/test/fixtures/typescript/corpus/objects-with-methods.diffA-B.txt @@ -22,7 +22,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return { (Plus {-(Identifier)-} diff --git a/test/fixtures/typescript/corpus/objects-with-methods.diffB-A.txt b/test/fixtures/typescript/corpus/objects-with-methods.diffB-A.txt index 6d87f8b53..914db2372 100644 --- a/test/fixtures/typescript/corpus/objects-with-methods.diffB-A.txt +++ b/test/fixtures/typescript/corpus/objects-with-methods.diffB-A.txt @@ -22,7 +22,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return { (Minus {-(Identifier)-} diff --git a/test/fixtures/typescript/corpus/objects-with-methods.parseA.txt b/test/fixtures/typescript/corpus/objects-with-methods.parseA.txt index d3d5e4345..618957d0f 100644 --- a/test/fixtures/typescript/corpus/objects-with-methods.parseA.txt +++ b/test/fixtures/typescript/corpus/objects-with-methods.parseA.txt @@ -21,7 +21,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Plus (Identifier) diff --git a/test/fixtures/typescript/corpus/objects-with-methods.parseB.txt b/test/fixtures/typescript/corpus/objects-with-methods.parseB.txt index b8747c6ea..8acf4faff 100644 --- a/test/fixtures/typescript/corpus/objects-with-methods.parseB.txt +++ b/test/fixtures/typescript/corpus/objects-with-methods.parseB.txt @@ -21,7 +21,7 @@ (Assignment (Identifier) (Empty))) - ( + (Statements (Return (Minus (Identifier) diff --git a/test/fixtures/typescript/corpus/public-field-definition.diffA-B.txt b/test/fixtures/typescript/corpus/public-field-definition.diffA-B.txt index cfe226e03..155fe53f0 100644 --- a/test/fixtures/typescript/corpus/public-field-definition.diffA-B.txt +++ b/test/fixtures/typescript/corpus/public-field-definition.diffA-B.txt @@ -1,7 +1,7 @@ (Program (Class (Identifier) - ( + (Statements (PublicFieldDefinition (Empty) (Readonly) diff --git a/test/fixtures/typescript/corpus/public-field-definition.diffB-A.txt b/test/fixtures/typescript/corpus/public-field-definition.diffB-A.txt index 3286f2749..3fb59ca0b 100644 --- a/test/fixtures/typescript/corpus/public-field-definition.diffB-A.txt +++ b/test/fixtures/typescript/corpus/public-field-definition.diffB-A.txt @@ -1,7 +1,7 @@ (Program (Class (Identifier) - ( + (Statements (PublicFieldDefinition (Empty) (Readonly) diff --git a/test/fixtures/typescript/corpus/public-field-definition.parseA.txt b/test/fixtures/typescript/corpus/public-field-definition.parseA.txt index 0250fd3ec..2076494be 100644 --- a/test/fixtures/typescript/corpus/public-field-definition.parseA.txt +++ b/test/fixtures/typescript/corpus/public-field-definition.parseA.txt @@ -1,7 +1,7 @@ (Program (Class (Identifier) - ( + (Statements (PublicFieldDefinition (Empty) (Readonly) diff --git a/test/fixtures/typescript/corpus/public-field-definition.parseB.txt b/test/fixtures/typescript/corpus/public-field-definition.parseB.txt index 7651e2fc0..1bec273f5 100644 --- a/test/fixtures/typescript/corpus/public-field-definition.parseB.txt +++ b/test/fixtures/typescript/corpus/public-field-definition.parseB.txt @@ -1,7 +1,7 @@ (Program (Class (Identifier) - ( + (Statements (PublicFieldDefinition (Empty) (Readonly) diff --git a/test/fixtures/typescript/corpus/switch-statement.diffA-B.txt b/test/fixtures/typescript/corpus/switch-statement.diffA-B.txt index e72d89a5b..3883f69c5 100644 --- a/test/fixtures/typescript/corpus/switch-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/switch-statement.diffA-B.txt @@ -2,18 +2,18 @@ (Match { (Float) ->(Float) } - ( + (Statements (Pattern (Float) - ( + (Statements (Float))) (Pattern (Float) - ( + (Statements { (Float) ->(Float) })) (Pattern (Float) - ( + (Statements (Float))))) (Empty)) diff --git a/test/fixtures/typescript/corpus/switch-statement.diffB-A.txt b/test/fixtures/typescript/corpus/switch-statement.diffB-A.txt index e72d89a5b..3883f69c5 100644 --- a/test/fixtures/typescript/corpus/switch-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/switch-statement.diffB-A.txt @@ -2,18 +2,18 @@ (Match { (Float) ->(Float) } - ( + (Statements (Pattern (Float) - ( + (Statements (Float))) (Pattern (Float) - ( + (Statements { (Float) ->(Float) })) (Pattern (Float) - ( + (Statements (Float))))) (Empty)) diff --git a/test/fixtures/typescript/corpus/switch-statement.parseA.txt b/test/fixtures/typescript/corpus/switch-statement.parseA.txt index 7d77dcfad..3e597d106 100644 --- a/test/fixtures/typescript/corpus/switch-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/switch-statement.parseA.txt @@ -1,17 +1,17 @@ (Program (Match (Float) - ( + (Statements (Pattern (Float) - ( + (Statements (Float))) (Pattern (Float) - ( + (Statements (Float))) (Pattern (Float) - ( + (Statements (Float))))) (Empty)) diff --git a/test/fixtures/typescript/corpus/switch-statement.parseB.txt b/test/fixtures/typescript/corpus/switch-statement.parseB.txt index 7d77dcfad..3e597d106 100644 --- a/test/fixtures/typescript/corpus/switch-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/switch-statement.parseB.txt @@ -1,17 +1,17 @@ (Program (Match (Float) - ( + (Statements (Pattern (Float) - ( + (Statements (Float))) (Pattern (Float) - ( + (Statements (Float))) (Pattern (Float) - ( + (Statements (Float))))) (Empty)) diff --git a/test/fixtures/typescript/corpus/try-statement.diffA-B.txt b/test/fixtures/typescript/corpus/try-statement.diffA-B.txt index a1448e34d..a7241e603 100644 --- a/test/fixtures/typescript/corpus/try-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/try-statement.diffA-B.txt @@ -1,14 +1,14 @@ (Program (Try - ( + (Statements (Identifier)) (Catch (Empty) - ( + (Statements { (Identifier) ->(Identifier) })) (Finally - ( + (Statements { (Identifier) ->(Identifier) }))) (Empty)) diff --git a/test/fixtures/typescript/corpus/try-statement.diffB-A.txt b/test/fixtures/typescript/corpus/try-statement.diffB-A.txt index a1448e34d..a7241e603 100644 --- a/test/fixtures/typescript/corpus/try-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/try-statement.diffB-A.txt @@ -1,14 +1,14 @@ (Program (Try - ( + (Statements (Identifier)) (Catch (Empty) - ( + (Statements { (Identifier) ->(Identifier) })) (Finally - ( + (Statements { (Identifier) ->(Identifier) }))) (Empty)) diff --git a/test/fixtures/typescript/corpus/try-statement.parseA.txt b/test/fixtures/typescript/corpus/try-statement.parseA.txt index 7224cc157..22e10b492 100644 --- a/test/fixtures/typescript/corpus/try-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/try-statement.parseA.txt @@ -1,12 +1,12 @@ (Program (Try - ( + (Statements (Identifier)) (Catch (Empty) - ( + (Statements (Identifier))) (Finally - ( + (Statements (Identifier)))) (Empty)) diff --git a/test/fixtures/typescript/corpus/try-statement.parseB.txt b/test/fixtures/typescript/corpus/try-statement.parseB.txt index 7224cc157..22e10b492 100644 --- a/test/fixtures/typescript/corpus/try-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/try-statement.parseB.txt @@ -1,12 +1,12 @@ (Program (Try - ( + (Statements (Identifier)) (Catch (Empty) - ( + (Statements (Identifier))) (Finally - ( + (Statements (Identifier)))) (Empty)) diff --git a/test/fixtures/typescript/corpus/while-statement.diffA-B.txt b/test/fixtures/typescript/corpus/while-statement.diffA-B.txt index 7ecf81cea..6c6581fbe 100644 --- a/test/fixtures/typescript/corpus/while-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/while-statement.diffA-B.txt @@ -2,7 +2,7 @@ (While { (Identifier) ->(Identifier) } - ( + (Statements (Call { (Identifier) ->(Identifier) } diff --git a/test/fixtures/typescript/corpus/while-statement.diffB-A.txt b/test/fixtures/typescript/corpus/while-statement.diffB-A.txt index 7ecf81cea..6c6581fbe 100644 --- a/test/fixtures/typescript/corpus/while-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/while-statement.diffB-A.txt @@ -2,7 +2,7 @@ (While { (Identifier) ->(Identifier) } - ( + (Statements (Call { (Identifier) ->(Identifier) } diff --git a/test/fixtures/typescript/corpus/while-statement.parseA.txt b/test/fixtures/typescript/corpus/while-statement.parseA.txt index 384062c49..41960b042 100644 --- a/test/fixtures/typescript/corpus/while-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/while-statement.parseA.txt @@ -1,7 +1,7 @@ (Program (While (Identifier) - ( + (Statements (Call (Identifier) (Empty)))) diff --git a/test/fixtures/typescript/corpus/while-statement.parseB.txt b/test/fixtures/typescript/corpus/while-statement.parseB.txt index 384062c49..41960b042 100644 --- a/test/fixtures/typescript/corpus/while-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/while-statement.parseB.txt @@ -1,7 +1,7 @@ (Program (While (Identifier) - ( + (Statements (Call (Identifier) (Empty)))) diff --git a/test/fixtures/typescript/corpus/yield.diffA-B.txt b/test/fixtures/typescript/corpus/yield.diffA-B.txt index 1737c04ee..ccde7b2d7 100644 --- a/test/fixtures/typescript/corpus/yield.diffA-B.txt +++ b/test/fixtures/typescript/corpus/yield.diffA-B.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Identifier) - ( + (Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/yield.diffB-A.txt b/test/fixtures/typescript/corpus/yield.diffB-A.txt index 56edbe9a9..d7dd3fc20 100644 --- a/test/fixtures/typescript/corpus/yield.diffB-A.txt +++ b/test/fixtures/typescript/corpus/yield.diffB-A.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Identifier) - ( + (Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/yield.parseA.txt b/test/fixtures/typescript/corpus/yield.parseA.txt index 0a4c7dcc9..47d764d16 100644 --- a/test/fixtures/typescript/corpus/yield.parseA.txt +++ b/test/fixtures/typescript/corpus/yield.parseA.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Identifier) - ( + (Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/yield.parseB.txt b/test/fixtures/typescript/corpus/yield.parseB.txt index 85816f2b8..54eada74e 100644 --- a/test/fixtures/typescript/corpus/yield.parseB.txt +++ b/test/fixtures/typescript/corpus/yield.parseB.txt @@ -3,7 +3,7 @@ (Empty) (Empty) (Identifier) - ( + (Statements (VariableDeclaration (Assignment (Empty)