From 6ed988e4d6788f86fd59b6e55da4eba3a5c1b027 Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Wed, 30 May 2018 11:05:50 -0700 Subject: [PATCH 01/16] Doc fix --- src/Data/Abstract/Evaluatable.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/src/Data/Abstract/Evaluatable.hs b/src/Data/Abstract/Evaluatable.hs index ca2a5a611..13e277f33 100644 --- a/src/Data/Abstract/Evaluatable.hs +++ b/src/Data/Abstract/Evaluatable.hs @@ -217,11 +217,11 @@ instance Apply Evaluatable fs => Evaluatable (Sum fs) where instance Evaluatable s => Evaluatable (TermF s a) where eval = eval . termFOut ---- | '[]' is treated as an imperative sequence of statements/declarations s.t.: ---- ---- 1. Each statement’s effects on the store are accumulated; ---- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and ---- 3. Only the last statement’s return value is returned. +-- | '[]' is treated as an imperative sequence of statements/declarations s.t.: +-- +-- 1. Each statement’s effects on the store are accumulated; +-- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and +-- 3. Only the last statement’s return value is returned. instance Evaluatable [] where -- 'nonEmpty' and 'foldMap1' enable us to return the last statement’s result instead of 'unit' for non-empty lists. eval = maybe (pure (Rval unit)) (runApp . foldMap1 (App . subtermRef)) . nonEmpty From 85257f5622bc166410af305e29493c9741c3744c Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Wed, 30 May 2018 11:06:07 -0700 Subject: [PATCH 02/16] Introduce Statements syntax type and let program use it --- src/Data/Syntax.hs | 27 +++++++++++++++++++++++---- 1 file changed, 23 insertions(+), 4 deletions(-) diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index 17c707714..2d5ea2f22 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -1,19 +1,22 @@ -{-# LANGUAGE DeriveAnyClass, GADTs, TypeOperators, MultiParamTypeClasses, UndecidableInstances, ScopedTypeVariables #-} +{-# LANGUAGE DeriveAnyClass, GADTs, TypeOperators, MultiParamTypeClasses, UndecidableInstances, ScopedTypeVariables, TypeFamilies #-} {-# OPTIONS_GHC -Wno-redundant-constraints #-} -- For HasCallStack module Data.Syntax where import Data.Abstract.Evaluatable -import Data.Aeson (ToJSON(..), object) +import Data.Aeson (ToJSON(..), ToJSON1(..), object) import Data.AST import Data.JSON.Fields import Data.Range import Data.Record import Data.Span +import Data.Semigroup.App +import Data.Semigroup.Foldable import Data.Sum import Data.Term import Diffing.Algorithm hiding (Empty) import Prelude import Prologue +import qualified GHC.Exts as Exts import qualified Assigning.Assignment as Assignment import qualified Data.Error as Error @@ -118,7 +121,7 @@ instance Declarations1 Identifier where liftDeclaredName _ (Identifier x) = pure x -newtype Program a = Program [a] +newtype Program a = Program (Statements a) deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Program where liftEq = genericLiftEq @@ -126,8 +129,24 @@ instance Ord1 Program where liftCompare = genericLiftCompare instance Show1 Program where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Program where - eval (Program xs) = eval xs + eval (Program statements) = eval statements +-- | Imperative sequence of statements/declarations +newtype Statements a = Statements [a] + deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1) + +instance Eq1 Statements where liftEq = genericLiftEq +instance Ord1 Statements where liftCompare = genericLiftCompare +instance Show1 Statements where liftShowsPrec = genericLiftShowsPrec +instance ToJSON1 Statements + +instance Evaluatable Statements where + eval (Statements xs) = maybe (pure (Rval unit)) (runApp . foldMap1 (App . subtermRef)) (nonEmpty xs) + +instance Exts.IsList (Statements a) where + type Item (Statements a) = a + fromList = Statements + toList (Statements xs) = xs -- | An accessibility modifier, e.g. private, public, protected, etc. newtype AccessibilityModifier a = AccessibilityModifier ByteString From c0ca3df3d132aba445abb666070efd1f94d7ba99 Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Wed, 30 May 2018 11:07:09 -0700 Subject: [PATCH 03/16] Basic use of Statements in assignment and eval --- src/Language/Go/Assignment.hs | 4 +++- src/Language/Go/Syntax.hs | 3 ++- src/Language/PHP/Assignment.hs | 3 ++- src/Language/Python/Assignment.hs | 3 ++- src/Language/Ruby/Assignment.hs | 9 +++++++-- src/Language/Ruby/Syntax.hs | 3 ++- src/Language/TypeScript/Assignment.hs | 13 +++++++++---- src/Language/TypeScript/Syntax.hs | 5 +++-- 8 files changed, 30 insertions(+), 13 deletions(-) diff --git a/src/Language/Go/Assignment.hs b/src/Language/Go/Assignment.hs index a7e6cc44f..b7813b6e8 100644 --- a/src/Language/Go/Assignment.hs +++ b/src/Language/Go/Assignment.hs @@ -22,6 +22,7 @@ import qualified Data.Syntax.Literal as Literal import qualified Data.Syntax.Statement as Statement import qualified Data.Syntax.Type as Type import Data.Sum +import GHC.Exts (fromList) import qualified Data.Term as Term import Prologue @@ -91,6 +92,7 @@ type Syntax = , Syntax.Empty , Syntax.Identifier , Syntax.Program + , Syntax.Statements , Type.Annotation , Type.Array , Type.Function @@ -111,7 +113,7 @@ assignment :: Assignment assignment = handleError program <|> parseError program :: Assignment -program = makeTerm <$> symbol SourceFile <*> children (Syntax.Program <$> manyTerm expression) +program = makeTerm <$> symbol SourceFile <*> children (Syntax.Program . fromList <$> manyTerm expression) expression :: Assignment expression = term (handleError (choice expressionChoices)) diff --git a/src/Language/Go/Syntax.hs b/src/Language/Go/Syntax.hs index 9b47e4894..404dcb2e5 100644 --- a/src/Language/Go/Syntax.hs +++ b/src/Language/Go/Syntax.hs @@ -9,6 +9,7 @@ import Data.Aeson import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as BC import Data.JSON.Fields +import Data.Syntax (Statements) import Diffing.Algorithm import Prologue import System.FilePath.Posix @@ -299,7 +300,7 @@ instance ToJSONFields1 Field instance Evaluatable Field -data Package a = Package { packageName :: !a, packageContents :: ![a] } +data Package a = Package { packageName :: !a, packageContents :: Statements a } deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) instance Eq1 Package where liftEq = genericLiftEq diff --git a/src/Language/PHP/Assignment.hs b/src/Language/PHP/Assignment.hs index 256f11948..7092fadfc 100644 --- a/src/Language/PHP/Assignment.hs +++ b/src/Language/PHP/Assignment.hs @@ -23,6 +23,7 @@ import qualified Data.Syntax.Statement as Statement import qualified Data.Syntax.Type as Type import qualified Data.Term as Term import qualified Language.PHP.Syntax as Syntax +import GHC.Exts (fromList) import Prologue type Syntax = '[ @@ -140,7 +141,7 @@ bookend head list last = head : append last list -- | Assignment from AST in PHP's grammar onto a program in PHP's syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program <$> (bookend <$> (text <|> emptyTerm) <*> manyTerm statement <*> (text <|> emptyTerm))) <|> parseError +assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . fromList <$> (bookend <$> (text <|> emptyTerm) <*> manyTerm statement <*> (text <|> emptyTerm))) <|> parseError term :: Assignment -> Assignment term term = contextualize (comment <|> textInterpolation) (postContextualize (comment <|> textInterpolation) term) diff --git a/src/Language/Python/Assignment.hs b/src/Language/Python/Assignment.hs index ddbcca6d8..b4b2514f8 100644 --- a/src/Language/Python/Assignment.hs +++ b/src/Language/Python/Assignment.hs @@ -25,6 +25,7 @@ import qualified Data.Syntax.Statement as Statement import qualified Data.Syntax.Type as Type import qualified Data.Term as Term import qualified Data.List.NonEmpty as NonEmpty +import GHC.Exts (fromList) import Prologue @@ -90,7 +91,7 @@ type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term -- | Assignment from AST in Python's grammar onto a program in Python's syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Module <*> children (Syntax.Program <$> manyTerm expression) <|> parseError +assignment = handleError $ makeTerm <$> symbol Module <*> children (Syntax.Program . fromList <$> manyTerm expression) <|> parseError -- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present. manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] diff --git a/src/Language/Ruby/Assignment.hs b/src/Language/Ruby/Assignment.hs index be2683e5d..061dc2423 100644 --- a/src/Language/Ruby/Assignment.hs +++ b/src/Language/Ruby/Assignment.hs @@ -23,6 +23,7 @@ import qualified Data.Syntax.Literal as Literal import qualified Data.Syntax.Statement as Statement import qualified Data.Term as Term import qualified Language.Ruby.Syntax as Ruby.Syntax +import GHC.Exts (fromList) import Prologue hiding (for) -- | The type of Ruby syntax. @@ -77,6 +78,7 @@ type Syntax = '[ , Syntax.Error , Syntax.Identifier , Syntax.Program + , Syntax.Statements , Ruby.Syntax.Class , Ruby.Syntax.Load , Ruby.Syntax.LowPrecedenceBoolean @@ -92,7 +94,7 @@ type Assignment = Assignment' Term -- | Assignment from AST in Ruby’s grammar onto a program in Ruby’s syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program <$> many expression) <|> parseError +assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . fromList <$> many expression) <|> parseError expression :: Assignment expression = term (handleError (choice expressionChoices)) @@ -230,7 +232,7 @@ singletonClass :: Assignment singletonClass = makeTerm <$> symbol SingletonClass <*> (withNewScope . children) (Ruby.Syntax.Class <$> expression <*> pure Nothing <*> expressions) module' :: Assignment -module' = makeTerm <$> symbol Module <*> (withNewScope . children) (Ruby.Syntax.Module <$> expression <*> many expression) +module' = makeTerm <$> symbol Module <*> (withNewScope . children) (Ruby.Syntax.Module <$> expression <*> manyStatements expression) scopeResolution :: Assignment scopeResolution = makeTerm <$> symbol ScopeResolution <*> children (Expression.ScopeResolution <$> many expression) @@ -494,6 +496,9 @@ term term = contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> som manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term] manyTermsTill step end = manyTill (step <|> comment) end +manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) +manyStatements expr = fromList <$> (many expr) + -- | Match infix terms separated by any of a list of operators, assigning any comments following each operand. infixTerm :: HasCallStack => Assignment diff --git a/src/Language/Ruby/Syntax.hs b/src/Language/Ruby/Syntax.hs index 862d41eb7..8375f86e8 100644 --- a/src/Language/Ruby/Syntax.hs +++ b/src/Language/Ruby/Syntax.hs @@ -8,6 +8,7 @@ import Data.Abstract.Path import qualified Data.ByteString.Char8 as BC import Data.JSON.Fields import qualified Data.Language as Language +import Data.Syntax (Statements) import Diffing.Algorithm import Prelude hiding (fail) import Prologue @@ -146,7 +147,7 @@ instance Evaluatable Class where Rval <$> letrec' name (\addr -> subtermValue classBody <* makeNamespace name addr super) -data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] } +data Module a = Module { moduleIdentifier :: !a, moduleStatements :: Statements a } deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Module where liftEq = genericLiftEq diff --git a/src/Language/TypeScript/Assignment.hs b/src/Language/TypeScript/Assignment.hs index 5f2599129..914ba6380 100644 --- a/src/Language/TypeScript/Assignment.hs +++ b/src/Language/TypeScript/Assignment.hs @@ -22,6 +22,7 @@ import qualified Data.Syntax.Type as Type import qualified Data.Term as Term import Language.TypeScript.Grammar as Grammar import qualified Language.TypeScript.Syntax as TypeScript.Syntax +import GHC.Exts (fromList) import Prologue -- | The type of TypeScript syntax. @@ -89,6 +90,7 @@ type Syntax = '[ , Syntax.Error , Syntax.Identifier , Syntax.Program + , Syntax.Statements , Syntax.Context , Type.Readonly , Type.TypeParameters @@ -175,12 +177,15 @@ type Assignment = Assignment.Assignment [] Grammar Term -- | Assignment from AST in TypeScript’s grammar onto a program in TypeScript’s syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program <$> manyTerm statement) <|> parseError +assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . fromList <$> manyTerm statement) <|> parseError -- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present. manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) +manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) +manyStatements expr = fromList <$> (manyTerm expr) + term :: Assignment -> Assignment term term = contextualize comment (postContextualize comment term) @@ -763,11 +768,11 @@ internalModule :: Assignment internalModule = makeTerm <$> symbol Grammar.InternalModule <*> children (TypeScript.Syntax.InternalModule <$> term (string <|> identifier <|> nestedIdentifier) <*> statements) module' :: Assignment -module' = makeTerm <$> symbol Module <*> children (TypeScript.Syntax.Module <$> term (string <|> identifier <|> nestedIdentifier) <*> (statements <|> pure [])) +module' = makeTerm <$> symbol Module <*> children (TypeScript.Syntax.Module <$> term (string <|> identifier <|> nestedIdentifier) <*> (statements <|> pure (fromList []))) -statements :: Assignment.Assignment [] Grammar [Term] -statements = symbol StatementBlock *> children (manyTerm statement) +statements :: Assignment.Assignment [] Grammar (Syntax.Statements Term) +statements = symbol StatementBlock *> children (manyStatements statement) arrowFunction :: Assignment arrowFunction = makeArrowFun <$> symbol ArrowFunction <*> children ((,,) <$> emptyTerm <*> (((\a b c -> (a, [b], c)) <$> emptyTerm <*> term identifier <*> emptyTerm) <|> callSignatureParts) <*> term (expression <|> statementBlock)) diff --git a/src/Language/TypeScript/Syntax.hs b/src/Language/TypeScript/Syntax.hs index b05d22bd1..8be450a50 100644 --- a/src/Language/TypeScript/Syntax.hs +++ b/src/Language/TypeScript/Syntax.hs @@ -13,6 +13,7 @@ import Data.JSON.Fields import qualified Data.Language as Language import qualified Data.Map as Map import Data.Semigroup.Reducer (Reducer) +import Data.Syntax (Statements) import Diffing.Algorithm import Prelude import Prologue @@ -758,7 +759,7 @@ instance Ord1 Update where liftCompare = genericLiftCompare instance Show1 Update where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Update -data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] } +data Module a = Module { moduleIdentifier :: !a, moduleStatements :: Statements a } deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Module where liftEq = genericLiftEq @@ -775,7 +776,7 @@ instance Evaluatable Module where -data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: ![a] } +data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: Statements a } deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 InternalModule where liftEq = genericLiftEq From f7b6ba3734b1d754ac9ab26df4600caba21156b0 Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Wed, 30 May 2018 11:09:56 -0700 Subject: [PATCH 04/16] Fix for emptyStatements --- src/Language/Go/Assignment.hs | 5 ++++- src/Language/Ruby/Assignment.hs | 2 +- src/Language/TypeScript/Assignment.hs | 5 ++++- 3 files changed, 9 insertions(+), 3 deletions(-) diff --git a/src/Language/Go/Assignment.hs b/src/Language/Go/Assignment.hs index b7813b6e8..0c51a34a0 100644 --- a/src/Language/Go/Assignment.hs +++ b/src/Language/Go/Assignment.hs @@ -422,7 +422,7 @@ methodSpecList :: Assignment methodSpecList = symbol MethodSpecList *> children expressions packageClause :: Assignment -packageClause = makeTerm <$> symbol PackageClause <*> children (Go.Syntax.Package <$> expression <*> pure []) +packageClause = makeTerm <$> symbol PackageClause <*> children (Go.Syntax.Package <$> expression <*> emptyStatements) parameters :: Assignment parameters = symbol ParameterList *> children expressions @@ -610,4 +610,7 @@ manyTerm = many . term term :: Assignment -> Assignment term term' = contextualize comment term' <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm) +emptyStatements :: Assignment.Assignment [] Grammar (Syntax.Statements Term) +emptyStatements = pure (fromList []) + {-# ANN module ("HLint: ignore Eta reduce" :: String) #-} diff --git a/src/Language/Ruby/Assignment.hs b/src/Language/Ruby/Assignment.hs index 061dc2423..121d155f6 100644 --- a/src/Language/Ruby/Assignment.hs +++ b/src/Language/Ruby/Assignment.hs @@ -94,7 +94,7 @@ type Assignment = Assignment' Term -- | Assignment from AST in Ruby’s grammar onto a program in Ruby’s syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . fromList <$> many expression) <|> parseError +assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program <$> manyStatements expression) <|> parseError expression :: Assignment expression = term (handleError (choice expressionChoices)) diff --git a/src/Language/TypeScript/Assignment.hs b/src/Language/TypeScript/Assignment.hs index 914ba6380..d7222d3ac 100644 --- a/src/Language/TypeScript/Assignment.hs +++ b/src/Language/TypeScript/Assignment.hs @@ -186,6 +186,9 @@ manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Conte manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) manyStatements expr = fromList <$> (manyTerm expr) +emptyStatements :: Assignment.Assignment [] Grammar (Syntax.Statements Term) +emptyStatements = pure (fromList []) + term :: Assignment -> Assignment term term = contextualize comment (postContextualize comment term) @@ -768,7 +771,7 @@ internalModule :: Assignment internalModule = makeTerm <$> symbol Grammar.InternalModule <*> children (TypeScript.Syntax.InternalModule <$> term (string <|> identifier <|> nestedIdentifier) <*> statements) module' :: Assignment -module' = makeTerm <$> symbol Module <*> children (TypeScript.Syntax.Module <$> term (string <|> identifier <|> nestedIdentifier) <*> (statements <|> pure (fromList []))) +module' = makeTerm <$> symbol Module <*> children (TypeScript.Syntax.Module <$> term (string <|> identifier <|> nestedIdentifier) <*> (statements <|> emptyStatements)) statements :: Assignment.Assignment [] Grammar (Syntax.Statements Term) From 40ea6d0767585684e47a895fd7a57df26b54f37a Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Wed, 30 May 2018 12:54:22 -0700 Subject: [PATCH 05/16] Helpers at the bottom of assignment file, use emptyStatements and manyStatements --- src/Language/Go/Assignment.hs | 13 ++++--- src/Language/PHP/Assignment.hs | 50 +++++++++++++++------------ src/Language/Python/Assignment.hs | 28 +++++++++------ src/Language/Ruby/Assignment.hs | 2 +- src/Language/TypeScript/Assignment.hs | 31 +++++++++-------- 5 files changed, 70 insertions(+), 54 deletions(-) diff --git a/src/Language/Go/Assignment.hs b/src/Language/Go/Assignment.hs index 0c51a34a0..cfcbc7795 100644 --- a/src/Language/Go/Assignment.hs +++ b/src/Language/Go/Assignment.hs @@ -113,7 +113,7 @@ assignment :: Assignment assignment = handleError program <|> parseError program :: Assignment -program = makeTerm <$> symbol SourceFile <*> children (Syntax.Program . fromList <$> manyTerm expression) +program = makeTerm <$> symbol SourceFile <*> children (Syntax.Program <$> manyStatements expression) expression :: Assignment expression = term (handleError (choice expressionChoices)) @@ -360,7 +360,7 @@ defaultExpressionCase :: Assignment defaultExpressionCase = makeTerm <$> symbol DefaultCase <*> (Go.Syntax.DefaultPattern <$ source <*> (expressions <|> emptyTerm)) callExpression :: Assignment -callExpression = makeTerm <$> symbol CallExpression <*> children (Expression.Call <$> pure [] <*> expression <*> manyTerm expression <*> emptyTerm) +callExpression = makeTerm <$> symbol CallExpression <*> children (Expression.Call [] <$> expression <*> manyTerm expression <*> emptyTerm) expressionCase :: Assignment expressionCase = makeTerm <$> symbol ExpressionCase <*> (Statement.Pattern <$> children expressions <*> expressions) @@ -606,11 +606,14 @@ manyTermsTill step end = manyTill (step <|> comment) end manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] manyTerm = many . term --- | Match a term and contextualize any comments preceeding or proceeding the term. -term :: Assignment -> Assignment -term term' = contextualize comment term' <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm) +manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) +manyStatements expr = fromList <$> (manyTerm expr) emptyStatements :: Assignment.Assignment [] Grammar (Syntax.Statements Term) emptyStatements = pure (fromList []) +-- | Match a term and contextualize any comments preceeding or proceeding the term. +term :: Assignment -> Assignment +term term' = contextualize comment term' <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm) + {-# ANN module ("HLint: ignore Eta reduce" :: String) #-} diff --git a/src/Language/PHP/Assignment.hs b/src/Language/PHP/Assignment.hs index 7092fadfc..273503d64 100644 --- a/src/Language/PHP/Assignment.hs +++ b/src/Language/PHP/Assignment.hs @@ -128,37 +128,16 @@ type Syntax = '[ , Syntax.UseClause , Syntax.VariableName , Type.Annotation - , [] ] + , [] + ] type Term = Term.Term (Sum Syntax) (Record Location) type Assignment = Assignment.Assignment [] Grammar Term -append :: a -> [a] -> [a] -append x xs = xs ++ [x] - -bookend :: a -> [a] -> a -> [a] -bookend head list last = head : append last list - -- | Assignment from AST in PHP's grammar onto a program in PHP's syntax. assignment :: Assignment assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . fromList <$> (bookend <$> (text <|> emptyTerm) <*> manyTerm statement <*> (text <|> emptyTerm))) <|> parseError -term :: Assignment -> Assignment -term term = contextualize (comment <|> textInterpolation) (postContextualize (comment <|> textInterpolation) term) - -commentedTerm :: Assignment -> Assignment -commentedTerm term = contextualize (comment <|> textInterpolation) term <|> makeTerm1 <$> (Syntax.Context <$> some1 (comment <|> textInterpolation) <*> emptyTerm) - --- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present. -manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] -manyTerm = many . commentedTerm - -someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] -someTerm = fmap NonEmpty.toList . someTerm' - -someTerm' :: Assignment -> Assignment.Assignment [] Grammar (NonEmpty Term) -someTerm' = NonEmpty.some1 . commentedTerm - text :: Assignment text = makeTerm <$> symbol Text <*> (Syntax.Text <$> source) @@ -763,6 +742,31 @@ comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) string :: Assignment string = makeTerm <$> (symbol Grammar.String <|> symbol Heredoc) <*> (Literal.TextElement <$> source) + +-- Helpers + +append :: a -> [a] -> [a] +append x xs = xs ++ [x] + +bookend :: a -> [a] -> a -> [a] +bookend head list last = head : append last list + +term :: Assignment -> Assignment +term term = contextualize (comment <|> textInterpolation) (postContextualize (comment <|> textInterpolation) term) + +commentedTerm :: Assignment -> Assignment +commentedTerm term = contextualize (comment <|> textInterpolation) term <|> makeTerm1 <$> (Syntax.Context <$> some1 (comment <|> textInterpolation) <*> emptyTerm) + +-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present. +manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] +manyTerm = many . commentedTerm + +someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] +someTerm = fmap NonEmpty.toList . someTerm' + +someTerm' :: Assignment -> Assignment.Assignment [] Grammar (NonEmpty Term) +someTerm' = NonEmpty.some1 . commentedTerm + -- | Match infix terms separated by any of a list of operators, assigning any comments following each operand. infixTerm :: Assignment -> Assignment diff --git a/src/Language/Python/Assignment.hs b/src/Language/Python/Assignment.hs index b4b2514f8..4ad69e75a 100644 --- a/src/Language/Python/Assignment.hs +++ b/src/Language/Python/Assignment.hs @@ -91,17 +91,7 @@ type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term -- | Assignment from AST in Python's grammar onto a program in Python's syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Module <*> children (Syntax.Program . fromList <$> manyTerm expression) <|> parseError - --- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present. -manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] -manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) - -someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] -someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) - -term :: Assignment -> Assignment -term term = contextualize comment (postContextualize comment term) +assignment = handleError $ makeTerm <$> symbol Module <*> children (Syntax.Program <$> manyStatements expression) <|> parseError expression :: Assignment expression = handleError (choice expressionChoices) @@ -484,6 +474,19 @@ ifClause = symbol IfClause *> children expressions conditionalExpression :: Assignment conditionalExpression = makeTerm <$> symbol ConditionalExpression <*> children (flip Statement.If <$> term expression <*> term expression <*> expressions) + +-- Helpers +-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present. +manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] +manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) + +someTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] +someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) + +term :: Assignment -> Assignment +term term = contextualize comment (postContextualize comment term) + + -- | Match a left-associated infix chain of terms, optionally followed by comments. Like 'chainl1' but assigning comment nodes automatically. chainl1Term :: Assignment -> Assignment.Assignment [] Grammar (Term -> Term -> Term) -> Assignment chainl1Term expr op = postContextualize (comment <|> symbol AnonLambda *> empty) expr `chainl1` op @@ -492,6 +495,9 @@ chainl1Term expr op = postContextualize (comment <|> symbol AnonLambda *> empty) manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term] manyTermsTill step end = manyTill (step <|> comment) end +manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) +manyStatements expr = fromList <$> (manyTerm expr) + -- | Match infix terms separated by any of a list of operators, assigning any comments following each operand. infixTerm :: HasCallStack => Assignment diff --git a/src/Language/Ruby/Assignment.hs b/src/Language/Ruby/Assignment.hs index 121d155f6..6eaf4fcdf 100644 --- a/src/Language/Ruby/Assignment.hs +++ b/src/Language/Ruby/Assignment.hs @@ -482,7 +482,7 @@ emptyStatement :: Assignment emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ source <|> pure Syntax.Empty) --- Helper functions +-- Helpers invert :: Assignment -> Assignment invert term = makeTerm <$> location <*> fmap Expression.Not term diff --git a/src/Language/TypeScript/Assignment.hs b/src/Language/TypeScript/Assignment.hs index d7222d3ac..be5911e8f 100644 --- a/src/Language/TypeScript/Assignment.hs +++ b/src/Language/TypeScript/Assignment.hs @@ -177,20 +177,7 @@ type Assignment = Assignment.Assignment [] Grammar Term -- | Assignment from AST in TypeScript’s grammar onto a program in TypeScript’s syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . fromList <$> manyTerm statement) <|> parseError - --- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present. -manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] -manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) - -manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) -manyStatements expr = fromList <$> (manyTerm expr) - -emptyStatements :: Assignment.Assignment [] Grammar (Syntax.Statements Term) -emptyStatements = pure (fromList []) - -term :: Assignment -> Assignment -term term = contextualize comment (postContextualize comment term) +assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program <$> manyStatements statement) <|> parseError expression :: Assignment expression = handleError everything @@ -866,6 +853,22 @@ binaryExpression = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm ]) where invert cons a b = Expression.Not (makeTerm1 (cons a b)) + +-- Helpers + +-- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present. +manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] +manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) + +manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) +manyStatements expr = fromList <$> (manyTerm expr) + +emptyStatements :: Assignment.Assignment [] Grammar (Syntax.Statements Term) +emptyStatements = pure (fromList []) + +term :: Assignment -> Assignment +term term = contextualize comment (postContextualize comment term) + emptyStatement :: Assignment emptyStatement = makeTerm <$> symbol EmptyStatement <*> (Syntax.Empty <$ source <|> pure Syntax.Empty) From 7e2c8eed3a9902baa2e524e14c2212488faaf94e Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Wed, 30 May 2018 17:06:32 -0700 Subject: [PATCH 06/16] Use Statement exclusively for imperative semantics --- src/Data/Abstract/Evaluatable.hs | 11 ++------- src/Data/Syntax.hs | 31 +++++++++++++++++++----- src/Language/Go/Assignment.hs | 13 ++++------ src/Language/Haskell/Assignment.hs | 4 +-- src/Language/PHP/Assignment.hs | 12 ++++++--- src/Language/Python/Assignment.hs | 35 +++++++++++++-------------- src/Language/Ruby/Assignment.hs | 28 +++++++++++++-------- src/Language/TypeScript/Assignment.hs | 9 +++---- 8 files changed, 80 insertions(+), 63 deletions(-) diff --git a/src/Data/Abstract/Evaluatable.hs b/src/Data/Abstract/Evaluatable.hs index 13e277f33..bb6034fc8 100644 --- a/src/Data/Abstract/Evaluatable.hs +++ b/src/Data/Abstract/Evaluatable.hs @@ -34,8 +34,6 @@ import Data.Abstract.Name as X import Data.Abstract.Package as Package import Data.Abstract.Ref as X import Data.Scientific (Scientific) -import Data.Semigroup.App -import Data.Semigroup.Foldable import Data.Semigroup.Reducer hiding (unit) import Data.Semilattice.Lower import Data.Sum @@ -217,11 +215,6 @@ instance Apply Evaluatable fs => Evaluatable (Sum fs) where instance Evaluatable s => Evaluatable (TermF s a) where eval = eval . termFOut --- | '[]' is treated as an imperative sequence of statements/declarations s.t.: --- --- 1. Each statement’s effects on the store are accumulated; --- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and --- 3. Only the last statement’s return value is returned. +-- | '[]' uses the default eval. Use Data.Syntax.Statements if you need an imperative sequence. instance Evaluatable [] where - -- 'nonEmpty' and 'foldMap1' enable us to return the last statement’s result instead of 'unit' for non-empty lists. - eval = maybe (pure (Rval unit)) (runApp . foldMap1 (App . subtermRef)) . nonEmpty + eval _ = throwResumable (Unspecialized ("Eval unspecialized for []")) diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index 2d5ea2f22..b5faf715d 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -30,12 +30,6 @@ makeTerm a = makeTerm' a . inject makeTerm' :: (HasCallStack, Semigroup a, Foldable f) => a -> f (Term f a) -> Term f a makeTerm' a f = termIn (sconcat (a :| (termAnnotation <$> toList f))) f --- | Lift syntax and an annotation into a term, injecting the syntax into a union & ensuring the annotation encompasses all children. Removes extra structure if term is a list of a single item. -makeTerm'' :: (HasCallStack, f :< fs, Semigroup a, Apply Foldable fs, Foldable f) => a -> f (Term (Sum fs) a) -> Term (Sum fs) a -makeTerm'' a children = case toList children of - [x] -> x - _ -> makeTerm' a (inject children) - -- | Lift non-empty syntax into a term, injecting the syntax into a union & appending all subterms’.annotations to make the new term’s annotation. makeTerm1 :: (HasCallStack, f :< fs, Semigroup a, Apply Foldable fs) => f (Term (Sum fs) a) -> Term (Sum fs) a makeTerm1 = makeTerm1' . inject @@ -46,11 +40,26 @@ makeTerm1' f = case toList f of a : _ -> makeTerm' (termAnnotation a) f _ -> error "makeTerm1': empty structure" +-- FIXME: I think this might be an anti-pattern. +-- | Lift syntax and an annotation into a term, injecting the syntax into a union & ensuring the annotation encompasses all children. Removes extra structure if term is a list of a single item. +makeStatementTerm :: (HasCallStack, f :< fs, Statements :< fs, Semigroup a, Apply Foldable fs, Foldable f) => a -> f (Term (Sum fs) a) -> Term (Sum fs) a +makeStatementTerm a children = case toList children of + [x] -> x + xs -> makeTerm' a (inject (Statements xs)) + -- | Construct an empty term at the current position. emptyTerm :: (HasCallStack, Empty :< fs, Apply Foldable fs) => Assignment.Assignment ast grammar (Term (Sum fs) (Record Location)) emptyTerm = makeTerm . startLocation <$> Assignment.location <*> pure Empty where startLocation ann = Range (start (getField ann)) (start (getField ann)) :. Span (spanStart (getField ann)) (spanStart (getField ann)) :. Nil +-- | Construct zero or more Statements. +manyStatements :: (Enum grammar, Eq1 ast, Ix grammar, Show grammar) => Assignment.Assignment ast grammar (Term f a) -> Assignment.Assignment ast grammar (Statements (Term f a)) +manyStatements expr = Exts.fromList <$> (many expr) + +-- | Construct an empty list of Statements. +emptyStatements :: Assignment.Assignment ast grammar (Statements (Term f a)) +emptyStatements = pure (Exts.fromList []) + -- | Catch assignment errors into an error term. handleError :: (HasCallStack, Error :< fs, Enum grammar, Eq1 ast, Ix grammar, Show grammar, Apply Foldable fs) => Assignment.Assignment ast grammar (Term (Sum fs) (Record Location)) -> Assignment.Assignment ast grammar (Term (Sum fs) (Record Location)) handleError = flip catchError (\ err -> makeTerm <$> Assignment.location <*> pure (errorSyntax (either id show <$> err) []) <* Assignment.source) @@ -132,6 +141,10 @@ instance Evaluatable Program where eval (Program statements) = eval statements -- | Imperative sequence of statements/declarations +-- +-- 1. Each statement’s effects on the store are accumulated; +-- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and +-- 3. Only the last statement’s return value is returned. newtype Statements a = Statements [a] deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1) @@ -140,6 +153,11 @@ instance Ord1 Statements where liftCompare = genericLiftCompare instance Show1 Statements where liftShowsPrec = genericLiftShowsPrec instance ToJSON1 Statements +-- | Imperative sequence of statements is evaluated s.t: +-- +-- 1. Each statement’s effects on the store are accumulated; +-- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and +-- 3. Only the last statement’s return value is returned. instance Evaluatable Statements where eval (Statements xs) = maybe (pure (Rval unit)) (runApp . foldMap1 (App . subtermRef)) (nonEmpty xs) @@ -148,6 +166,7 @@ instance Exts.IsList (Statements a) where fromList = Statements toList (Statements xs) = 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, ToJSONFields1) diff --git a/src/Language/Go/Assignment.hs b/src/Language/Go/Assignment.hs index cfcbc7795..778a7bb90 100644 --- a/src/Language/Go/Assignment.hs +++ b/src/Language/Go/Assignment.hs @@ -9,7 +9,7 @@ module Language.Go.Assignment import Assigning.Assignment hiding (Assignment, Error) import Data.Abstract.Name (name) import Data.Record -import Data.Syntax (contextualize, emptyTerm, parseError, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1) +import Data.Syntax (contextualize, emptyStatements, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeStatementTerm, makeTerm1, parseError) import Language.Go.Grammar as Grammar import Language.Go.Syntax as Go.Syntax import Language.Go.Type as Go.Type @@ -209,10 +209,10 @@ types = ] identifiers :: Assignment -identifiers = makeTerm'' <$> location <*> manyTerm identifier +identifiers = makeStatementTerm <$> location <*> manyTerm identifier expressions :: Assignment -expressions = makeTerm'' <$> location <*> manyTerm expression +expressions = makeStatementTerm <$> location <*> manyTerm expression -- Literals @@ -384,7 +384,7 @@ functionDeclaration = makeTerm <$> (symbol FunctionDeclaration <|> symbol FuncL returnParameters = makeTerm <$> symbol ParameterList <*> children (manyTerm expression) importDeclaration :: Assignment -importDeclaration = makeTerm'' <$> symbol ImportDeclaration <*> children (manyTerm (importSpec <|> importSpecList)) +importDeclaration = makeStatementTerm <$> symbol ImportDeclaration <*> children (manyTerm (importSpec <|> importSpecList)) where -- `import . "lib/Math"` dotImport = inject <$> (flip Go.Syntax.Import <$> dot <*> importFromPath) @@ -401,7 +401,7 @@ importDeclaration = makeTerm'' <$> symbol ImportDeclaration <*> children (manyTe dot = makeTerm <$> symbol Dot <*> (Literal.TextElement <$> source) underscore = makeTerm <$> symbol BlankIdentifier <*> (Literal.TextElement <$> source) importSpec = makeTerm' <$> symbol ImportSpec <*> children (sideEffectImport <|> dotImport <|> namedImport <|> plainImport) - importSpecList = makeTerm <$> symbol ImportSpecList <*> children (manyTerm (importSpec <|> comment)) + importSpecList = makeTerm <$> symbol ImportSpecList <*> children (manyStatements (importSpec <|> comment)) importFromPath = symbol InterpretedStringLiteral *> (importPath <$> source) indexExpression :: Assignment @@ -609,9 +609,6 @@ manyTerm = many . term manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) manyStatements expr = fromList <$> (manyTerm expr) -emptyStatements :: Assignment.Assignment [] Grammar (Syntax.Statements Term) -emptyStatements = pure (fromList []) - -- | Match a term and contextualize any comments preceeding or proceeding the term. term :: Assignment -> Assignment term term' = contextualize comment term' <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm) diff --git a/src/Language/Haskell/Assignment.hs b/src/Language/Haskell/Assignment.hs index 0da96796c..5cd81ed5a 100644 --- a/src/Language/Haskell/Assignment.hs +++ b/src/Language/Haskell/Assignment.hs @@ -9,7 +9,7 @@ module Language.Haskell.Assignment import Assigning.Assignment hiding (Assignment, Error) import Data.Record import Data.Sum -import Data.Syntax (emptyTerm, handleError, parseError, makeTerm, makeTerm'', contextualize, postContextualize) +import Data.Syntax (emptyTerm, handleError, parseError, makeTerm, contextualize, postContextualize) import Language.Haskell.Grammar as Grammar import qualified Assigning.Assignment as Assignment import qualified Data.Abstract.Name as Name @@ -48,7 +48,7 @@ module' = makeTerm expressions :: Assignment -expressions = makeTerm'' <$> location <*> many expression +expressions = makeTerm <$> location <*> many expression expression :: Assignment expression = term (handleError (choice expressionChoices)) diff --git a/src/Language/PHP/Assignment.hs b/src/Language/PHP/Assignment.hs index 273503d64..83b68db38 100644 --- a/src/Language/PHP/Assignment.hs +++ b/src/Language/PHP/Assignment.hs @@ -117,6 +117,7 @@ type Syntax = '[ , Syntax.ScalarType , Syntax.ShellCommand , Syntax.SimpleVariable + , Syntax.Statements , Syntax.Static , Syntax.Text , Syntax.TraitDeclaration @@ -390,12 +391,12 @@ scalarType :: Assignment scalarType = makeTerm <$> symbol ScalarType <*> (Syntax.ScalarType <$> source) compoundStatement :: Assignment -compoundStatement = makeTerm <$> symbol CompoundStatement <*> children (manyTerm statement) +compoundStatement = makeTerm <$> symbol CompoundStatement <*> children (manyStatements statement) objectCreationExpression :: Assignment objectCreationExpression = (makeTerm <$> symbol ObjectCreationExpression <*> children (Expression.New <$> ((:) <$> term classTypeDesignator <*> (arguments <|> pure [])))) - <|> (makeTerm <$> symbol ObjectCreationExpression <*> children (makeAnonClass <$ token AnonNew <* token AnonClass <*> emptyTerm <*> (arguments <|> pure []) <*> (term classBaseClause <|> emptyTerm) <*> (term classInterfaceClause <|> emptyTerm) <*> (makeTerm <$> location <*> manyTerm classMemberDeclaration))) + <|> (makeTerm <$> symbol ObjectCreationExpression <*> children (makeAnonClass <$ token AnonNew <* token AnonClass <*> emptyTerm <*> (arguments <|> pure []) <*> (term classBaseClause <|> emptyTerm) <*> (term classInterfaceClause <|> emptyTerm) <*> (makeTerm <$> location <*> manyStatements classMemberDeclaration))) where makeAnonClass identifier args baseClause interfaceClause declarations = Declaration.Class [] identifier (args <> [baseClause, interfaceClause]) declarations classMemberDeclaration :: Assignment @@ -602,7 +603,7 @@ functionDefinition = makeTerm <$> symbol FunctionDefinition <*> children (makeFu makeFunction identifier parameters returnType statement = Declaration.Function [returnType] identifier parameters statement classDeclaration :: Assignment -classDeclaration = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> (term classModifier <|> emptyTerm) <*> term name <*> (term classBaseClause <|> emptyTerm) <*> (term classInterfaceClause <|> emptyTerm) <*> (makeTerm <$> location <*> manyTerm classMemberDeclaration)) +classDeclaration = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> (term classModifier <|> emptyTerm) <*> term name <*> (term classBaseClause <|> emptyTerm) <*> (term classInterfaceClause <|> emptyTerm) <*> (makeTerm <$> location <*> manyStatements classMemberDeclaration)) where makeClass modifier name baseClause interfaceClause declarations = Declaration.Class [modifier] name [baseClause, interfaceClause] declarations @@ -734,7 +735,7 @@ functionStaticDeclaration :: Assignment functionStaticDeclaration = makeTerm <$> symbol FunctionStaticDeclaration <*> children (Declaration.VariableDeclaration <$> manyTerm staticVariableDeclaration) staticVariableDeclaration :: Assignment -staticVariableDeclaration = makeTerm <$> symbol StaticVariableDeclaration <*> children (Statement.Assignment <$> pure [] <*> term variableName <*> (term expression <|> emptyTerm)) +staticVariableDeclaration = makeTerm <$> symbol StaticVariableDeclaration <*> children (Statement.Assignment [] <$> term variableName <*> (term expression <|> emptyTerm)) comment :: Assignment comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) @@ -767,6 +768,9 @@ someTerm = fmap NonEmpty.toList . someTerm' someTerm' :: Assignment -> Assignment.Assignment [] Grammar (NonEmpty Term) someTerm' = NonEmpty.some1 . commentedTerm +manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) +manyStatements expr = fromList <$> (manyTerm expr) + -- | Match infix terms separated by any of a list of operators, assigning any comments following each operand. infixTerm :: Assignment -> Assignment diff --git a/src/Language/Python/Assignment.hs b/src/Language/Python/Assignment.hs index 4ad69e75a..8fbfd5e84 100644 --- a/src/Language/Python/Assignment.hs +++ b/src/Language/Python/Assignment.hs @@ -10,7 +10,7 @@ module Language.Python.Assignment import Assigning.Assignment hiding (Assignment, Error) import Data.Abstract.Name (name) import Data.Record -import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, parseError, postContextualize) +import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeStatementTerm, makeTerm1, parseError, postContextualize) import GHC.Stack import Language.Python.Grammar as Grammar import Language.Python.Syntax as Python.Syntax @@ -82,6 +82,7 @@ type Syntax = , Syntax.Error , Syntax.Identifier , Syntax.Program + , Syntax.Statements , Type.Annotation , [] ] @@ -91,7 +92,7 @@ type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term -- | Assignment from AST in Python's grammar onto a program in Python's syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Module <*> children (Syntax.Program <$> manyStatements expression) <|> parseError +assignment = handleError $ makeTerm <$> symbol Module <*> children (Syntax.Program . fromList <$> manyTerm expression) <|> parseError expression :: Assignment expression = handleError (choice expressionChoices) @@ -163,14 +164,15 @@ expressionChoices = , yield ] + expressions :: Assignment -expressions = makeTerm'' <$> location <*> manyTerm expression +expressions = makeStatementTerm <$> location <*> manyTerm expression expressionStatement :: Assignment -expressionStatement = makeTerm'' <$> symbol ExpressionStatement <*> children (someTerm expression) +expressionStatement = makeStatementTerm <$> symbol ExpressionStatement <*> children (someTerm expression) expressionList :: Assignment -expressionList = makeTerm'' <$> symbol ExpressionList <*> children (someTerm expression) +expressionList = makeStatementTerm <$> symbol ExpressionList <*> children (someTerm expression) listSplat :: Assignment listSplat = makeTerm <$> symbol ListSplat <*> (Syntax.Identifier . name <$> source) @@ -241,7 +243,7 @@ functionDefinition = makeFunctionDeclaration loc (functionName', functionParameters, ty, functionBody) = makeTerm loc $ Type.Annotation (makeTerm loc $ Declaration.Function [] functionName' functionParameters functionBody) (fromMaybe (makeTerm loc Syntax.Empty) ty) classDefinition :: Assignment -classDefinition = makeTerm <$> symbol ClassDefinition <*> children (Declaration.Class <$> pure [] <*> term expression <*> argumentList <*> expressions) +classDefinition = makeTerm <$> symbol ClassDefinition <*> children (Declaration.Class [] <$> term expression <*> argumentList <*> expressions) where argumentList = symbol ArgumentList *> children (manyTerm expression) <|> pure [] @@ -360,7 +362,7 @@ comment :: Assignment comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) import' :: Assignment -import' = makeTerm'' <$> symbol ImportStatement <*> children (manyTerm (aliasedImport <|> plainImport)) +import' = makeStatementTerm <$> symbol ImportStatement <*> children (manyTerm (aliasedImport <|> plainImport)) <|> makeTerm <$> symbol ImportFromStatement <*> children (Python.Syntax.Import <$> importPath <*> (wildcard <|> some (aliasImportSymbol <|> importSymbol))) where -- `import a as b` @@ -385,7 +387,7 @@ import' = makeTerm'' <$> symbol ImportStatement <*> children (manyTerm (aliase makeNameAliasPair from Nothing = (from, from) assertStatement :: Assignment -assertStatement = makeTerm <$> symbol AssertStatement <*> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm) +assertStatement = makeTerm <$> symbol AssertStatement <*> children (Expression.Call [] <$> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm) printStatement :: Assignment printStatement = do @@ -399,19 +401,19 @@ printStatement = do printCallTerm location identifier = makeTerm location <$> (Expression.Call [] identifier <$> manyTerm expression <*> emptyTerm) nonlocalStatement :: Assignment -nonlocalStatement = makeTerm <$> symbol NonlocalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonNonlocal <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm) +nonlocalStatement = makeTerm <$> symbol NonlocalStatement <*> children (Expression.Call [] <$> term (makeTerm <$> symbol AnonNonlocal <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm) globalStatement :: Assignment -globalStatement = makeTerm <$> symbol GlobalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonGlobal <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm) +globalStatement = makeTerm <$> symbol GlobalStatement <*> children (Expression.Call [] <$> term (makeTerm <$> symbol AnonGlobal <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm) await :: Assignment -await = makeTerm <$> symbol Await <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm) +await = makeTerm <$> symbol Await <*> children (Expression.Call [] <$> term (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm) returnStatement :: Assignment returnStatement = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> term (expressionList <|> emptyTerm)) deleteStatement :: Assignment -deleteStatement = makeTerm <$> symbol DeleteStatement <*> children (Expression.Call <$> pure [] <*> term deleteIdentifier <* symbol ExpressionList <*> children (manyTerm expression) <*> emptyTerm) +deleteStatement = makeTerm <$> symbol DeleteStatement <*> children (Expression.Call [] <$> term deleteIdentifier <* symbol ExpressionList <*> children (manyTerm expression) <*> emptyTerm) where deleteIdentifier = makeTerm <$> symbol AnonDel <*> (Syntax.Identifier . name <$> source) raiseStatement :: Assignment @@ -423,7 +425,7 @@ ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> ter makeElif (loc, makeIf) rest = makeTerm loc (makeIf rest) execStatement :: Assignment -execStatement = makeTerm <$> symbol ExecStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> location <*> (Syntax.Identifier . name <$> source)) <*> manyTerm (string <|> expression) <*> emptyTerm) +execStatement = makeTerm <$> symbol ExecStatement <*> children (Expression.Call [] <$> term (makeTerm <$> location <*> (Syntax.Identifier . name <$> source)) <*> manyTerm (string <|> expression) <*> emptyTerm) passStatement :: Assignment passStatement = makeTerm <$> symbol PassStatement <*> (Statement.NoOp <$> emptyTerm <* advance) @@ -447,7 +449,7 @@ slice = makeTerm <$> symbol Slice <*> children <*> (term expression <|> emptyTerm)) call :: Assignment -call = makeTerm <$> symbol Call <*> children (Expression.Call <$> pure [] <*> term (identifier <|> expression) <*> (symbol ArgumentList *> children (manyTerm expression) <|> someTerm comprehension) <*> emptyTerm) +call = makeTerm <$> symbol Call <*> children (Expression.Call [] <$> term (identifier <|> expression) <*> (symbol ArgumentList *> children (manyTerm expression) <|> someTerm comprehension) <*> emptyTerm) boolean :: Assignment boolean = makeTerm <$> token Grammar.True <*> pure Literal.true @@ -476,6 +478,7 @@ conditionalExpression = makeTerm <$> symbol ConditionalExpression <*> children ( -- Helpers + -- | Match a term optionally preceded by comment(s), or a sequence of comments if the term is not present. manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) @@ -486,7 +489,6 @@ someTerm term = some (contextualize comment term <|> makeTerm1 <$> (Syntax.Conte term :: Assignment -> Assignment term term = contextualize comment (postContextualize comment term) - -- | Match a left-associated infix chain of terms, optionally followed by comments. Like 'chainl1' but assigning comment nodes automatically. chainl1Term :: Assignment -> Assignment.Assignment [] Grammar (Term -> Term -> Term) -> Assignment chainl1Term expr op = postContextualize (comment <|> symbol AnonLambda *> empty) expr `chainl1` op @@ -495,9 +497,6 @@ chainl1Term expr op = postContextualize (comment <|> symbol AnonLambda *> empty) manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term] manyTermsTill step end = manyTill (step <|> comment) end -manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) -manyStatements expr = fromList <$> (manyTerm expr) - -- | Match infix terms separated by any of a list of operators, assigning any comments following each operand. infixTerm :: HasCallStack => Assignment diff --git a/src/Language/Ruby/Assignment.hs b/src/Language/Ruby/Assignment.hs index 6eaf4fcdf..92c710d5b 100644 --- a/src/Language/Ruby/Assignment.hs +++ b/src/Language/Ruby/Assignment.hs @@ -10,7 +10,19 @@ import Assigning.Assignment hiding (Assignment, Error) import Data.Abstract.Name (name) import Data.List (elem) import Data.Record -import Data.Syntax (contextualize, postContextualize, emptyTerm, parseError, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1) +import Data.Syntax + ( contextualize + , emptyTerm + , handleError + , infixContext + , makeTerm + , makeTerm' + , makeTerm1 + , makeStatementTerm + , manyStatements + , parseError + , postContextualize + ) import Language.Ruby.Grammar as Grammar import qualified Assigning.Assignment as Assignment import Data.Sum @@ -146,10 +158,10 @@ expressionChoices = mk s construct = makeTerm <$> symbol s <*> children ((construct .) . fromMaybe <$> emptyTerm <*> optional (symbol ArgumentList *> children expressions)) expressions :: Assignment -expressions = makeTerm'' <$> location <*> many expression +expressions = makeStatementTerm <$> location <*> many expression parenthesizedExpressions :: Assignment -parenthesizedExpressions = makeTerm'' <$> symbol ParenthesizedStatements <*> children (many expression) +parenthesizedExpressions = makeTerm <$> symbol ParenthesizedStatements <*> children (manyStatements expression) withExtendedScope :: Assignment' a -> Assignment' a withExtendedScope inner = do @@ -262,9 +274,8 @@ parameter = postContextualize comment (term uncontextualizedParameter) optionalParameter = symbol OptionalParameter *> children (lhsIdent <* expression) method :: Assignment -method = makeTerm <$> symbol Method <*> (withNewScope . children) (Declaration.Method <$> pure [] <*> emptyTerm <*> methodSelector <*> params <*> expressions') +method = makeTerm <$> symbol Method <*> (withNewScope . children) (Declaration.Method <$> pure [] <*> emptyTerm <*> methodSelector <*> params <*> expressions) where params = symbol MethodParameters *> children (many parameter) <|> pure [] - expressions' = makeTerm <$> location <*> many expression singletonMethod :: Assignment singletonMethod = makeTerm <$> symbol SingletonMethod <*> (withNewScope . children) (Declaration.Method <$> pure [] <*> expression <*> methodSelector <*> params <*> expressions) @@ -493,11 +504,8 @@ term term = contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> som where heredocEnd = makeTerm <$> symbol HeredocEnd <*> (Literal.TextElement <$> source) -- | Match a series of terms or comments until a delimiter is matched. -manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term] -manyTermsTill step end = manyTill (step <|> comment) end - -manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) -manyStatements expr = fromList <$> (many expr) +manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar (Syntax.Statements Term) +manyTermsTill step end = fromList <$> manyTill (step <|> comment) end -- | Match infix terms separated by any of a list of operators, assigning any comments following each operand. infixTerm :: HasCallStack diff --git a/src/Language/TypeScript/Assignment.hs b/src/Language/TypeScript/Assignment.hs index be5911e8f..b3e2f2784 100644 --- a/src/Language/TypeScript/Assignment.hs +++ b/src/Language/TypeScript/Assignment.hs @@ -11,7 +11,7 @@ import Data.Abstract.Name (name) import qualified Assigning.Assignment as Assignment import Data.Record import Data.Sum -import Data.Syntax (emptyTerm, handleError, parseError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1, contextualize, postContextualize) +import Data.Syntax (emptyTerm, emptyStatements, handleError, parseError, infixContext, makeTerm, makeTerm', makeStatementTerm, makeTerm1, contextualize, postContextualize) import qualified Data.Syntax as Syntax import qualified Data.Syntax.Comment as Comment import qualified Data.Syntax.Declaration as Declaration @@ -558,10 +558,10 @@ constructorTy :: Assignment constructorTy = makeTerm <$> symbol ConstructorType <*> children (TypeScript.Syntax.Constructor <$> (fromMaybe <$> emptyTerm <*> optional (term typeParameters)) <*> formalParameters <*> term ty) statementBlock :: Assignment -statementBlock = makeTerm <$> symbol StatementBlock <*> children (manyTerm statement) +statementBlock = makeTerm <$> symbol StatementBlock <*> children (manyStatements statement) classBodyStatements :: Assignment -classBodyStatements = makeTerm'' <$> symbol ClassBody <*> children (contextualize' <$> Assignment.manyThrough comment (postContextualize' <$> (concat <$> many ((\as b -> as ++ [b]) <$> manyTerm decorator <*> term (methodDefinition <|> publicFieldDefinition <|> methodSignature <|> indexSignature <|> abstractMethodSignature))) <*> many comment)) +classBodyStatements = makeStatementTerm <$> symbol ClassBody <*> children (contextualize' <$> Assignment.manyThrough comment (postContextualize' <$> (concat <$> many ((\as b -> as ++ [b]) <$> manyTerm decorator <*> term (methodDefinition <|> publicFieldDefinition <|> methodSignature <|> indexSignature <|> abstractMethodSignature))) <*> many comment)) where contextualize' (cs, formalParams) = case nonEmpty cs of Just cs -> toList cs ++ formalParams @@ -863,9 +863,6 @@ manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Conte manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) manyStatements expr = fromList <$> (manyTerm expr) -emptyStatements :: Assignment.Assignment [] Grammar (Syntax.Statements Term) -emptyStatements = pure (fromList []) - term :: Assignment -> Assignment term term = contextualize comment (postContextualize comment term) From 327bbf4ca0c713de4cc0ff7a618ee980daa19280 Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Thu, 31 May 2018 08:09:06 -0700 Subject: [PATCH 07/16] Revert back to carefully introducing Statements --- src/Data/Abstract/Evaluatable.hs | 11 ++++++-- src/Data/Syntax.hs | 40 ++++++--------------------- src/Language/Go/Assignment.hs | 20 ++++++-------- src/Language/Go/Syntax.hs | 3 +- src/Language/Haskell/Assignment.hs | 4 +-- src/Language/PHP/Assignment.hs | 24 ++++++++++------ src/Language/Python/Assignment.hs | 24 +++++++++++----- src/Language/Ruby/Assignment.hs | 19 ++++++------- src/Language/Ruby/Syntax.hs | 3 +- src/Language/TypeScript/Assignment.hs | 29 +++++++++++-------- src/Language/TypeScript/Syntax.hs | 5 ++-- 11 files changed, 90 insertions(+), 92 deletions(-) diff --git a/src/Data/Abstract/Evaluatable.hs b/src/Data/Abstract/Evaluatable.hs index bb6034fc8..ca2a5a611 100644 --- a/src/Data/Abstract/Evaluatable.hs +++ b/src/Data/Abstract/Evaluatable.hs @@ -34,6 +34,8 @@ import Data.Abstract.Name as X import Data.Abstract.Package as Package import Data.Abstract.Ref as X import Data.Scientific (Scientific) +import Data.Semigroup.App +import Data.Semigroup.Foldable import Data.Semigroup.Reducer hiding (unit) import Data.Semilattice.Lower import Data.Sum @@ -215,6 +217,11 @@ instance Apply Evaluatable fs => Evaluatable (Sum fs) where instance Evaluatable s => Evaluatable (TermF s a) where eval = eval . termFOut --- | '[]' uses the default eval. Use Data.Syntax.Statements if you need an imperative sequence. +--- | '[]' is treated as an imperative sequence of statements/declarations s.t.: +--- +--- 1. Each statement’s effects on the store are accumulated; +--- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and +--- 3. Only the last statement’s return value is returned. instance Evaluatable [] where - eval _ = throwResumable (Unspecialized ("Eval unspecialized for []")) + -- 'nonEmpty' and 'foldMap1' enable us to return the last statement’s result instead of 'unit' for non-empty lists. + eval = maybe (pure (Rval unit)) (runApp . foldMap1 (App . subtermRef)) . nonEmpty diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index b5faf715d..0a9b16c7d 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -16,7 +16,6 @@ import Data.Term import Diffing.Algorithm hiding (Empty) import Prelude import Prologue -import qualified GHC.Exts as Exts import qualified Assigning.Assignment as Assignment import qualified Data.Error as Error @@ -30,6 +29,12 @@ makeTerm a = makeTerm' a . inject makeTerm' :: (HasCallStack, Semigroup a, Foldable f) => a -> f (Term f a) -> Term f a makeTerm' a f = termIn (sconcat (a :| (termAnnotation <$> toList f))) f +-- | Lift syntax and an annotation into a term, injecting the syntax into a union & ensuring the annotation encompasses all children. Removes extra structure if term is a list of a single item. +makeTerm'' :: (HasCallStack, f :< fs, Semigroup a, Apply Foldable fs, Foldable f) => a -> f (Term (Sum fs) a) -> Term (Sum fs) a +makeTerm'' a children = case toList children of + [x] -> x + _ -> makeTerm' a (inject children) + -- | Lift non-empty syntax into a term, injecting the syntax into a union & appending all subterms’.annotations to make the new term’s annotation. makeTerm1 :: (HasCallStack, f :< fs, Semigroup a, Apply Foldable fs) => f (Term (Sum fs) a) -> Term (Sum fs) a makeTerm1 = makeTerm1' . inject @@ -40,26 +45,11 @@ makeTerm1' f = case toList f of a : _ -> makeTerm' (termAnnotation a) f _ -> error "makeTerm1': empty structure" --- FIXME: I think this might be an anti-pattern. --- | Lift syntax and an annotation into a term, injecting the syntax into a union & ensuring the annotation encompasses all children. Removes extra structure if term is a list of a single item. -makeStatementTerm :: (HasCallStack, f :< fs, Statements :< fs, Semigroup a, Apply Foldable fs, Foldable f) => a -> f (Term (Sum fs) a) -> Term (Sum fs) a -makeStatementTerm a children = case toList children of - [x] -> x - xs -> makeTerm' a (inject (Statements xs)) - -- | Construct an empty term at the current position. emptyTerm :: (HasCallStack, Empty :< fs, Apply Foldable fs) => Assignment.Assignment ast grammar (Term (Sum fs) (Record Location)) emptyTerm = makeTerm . startLocation <$> Assignment.location <*> pure Empty where startLocation ann = Range (start (getField ann)) (start (getField ann)) :. Span (spanStart (getField ann)) (spanStart (getField ann)) :. Nil --- | Construct zero or more Statements. -manyStatements :: (Enum grammar, Eq1 ast, Ix grammar, Show grammar) => Assignment.Assignment ast grammar (Term f a) -> Assignment.Assignment ast grammar (Statements (Term f a)) -manyStatements expr = Exts.fromList <$> (many expr) - --- | Construct an empty list of Statements. -emptyStatements :: Assignment.Assignment ast grammar (Statements (Term f a)) -emptyStatements = pure (Exts.fromList []) - -- | Catch assignment errors into an error term. handleError :: (HasCallStack, Error :< fs, Enum grammar, Eq1 ast, Ix grammar, Show grammar, Apply Foldable fs) => Assignment.Assignment ast grammar (Term (Sum fs) (Record Location)) -> Assignment.Assignment ast grammar (Term (Sum fs) (Record Location)) handleError = flip catchError (\ err -> makeTerm <$> Assignment.location <*> pure (errorSyntax (either id show <$> err) []) <* Assignment.source) @@ -153,19 +143,9 @@ instance Ord1 Statements where liftCompare = genericLiftCompare instance Show1 Statements where liftShowsPrec = genericLiftShowsPrec instance ToJSON1 Statements --- | Imperative sequence of statements is evaluated s.t: --- --- 1. Each statement’s effects on the store are accumulated; --- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and --- 3. Only the last statement’s return value is returned. instance Evaluatable Statements where eval (Statements xs) = maybe (pure (Rval unit)) (runApp . foldMap1 (App . subtermRef)) (nonEmpty xs) -instance Exts.IsList (Statements a) where - type Item (Statements a) = a - fromList = Statements - toList (Statements xs) = xs - -- | An accessibility modifier, e.g. private, public, protected, etc. newtype AccessibilityModifier a = AccessibilityModifier ByteString @@ -182,9 +162,7 @@ instance Evaluatable AccessibilityModifier -- -- This can be used to represent an implicit no-op, e.g. the alternative in an 'if' statement without an 'else'. data Empty a = Empty - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Empty + deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Empty where liftEq _ _ _ = True instance Ord1 Empty where liftCompare _ _ _ = EQ @@ -249,9 +227,7 @@ instance Ord ErrorStack where data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a } - deriving (Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Context + deriving (Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1) instance Diffable Context where subalgorithmFor blur focus (Context n s) = Context <$> traverse blur n <*> focus s diff --git a/src/Language/Go/Assignment.hs b/src/Language/Go/Assignment.hs index 778a7bb90..c471462f3 100644 --- a/src/Language/Go/Assignment.hs +++ b/src/Language/Go/Assignment.hs @@ -9,7 +9,7 @@ module Language.Go.Assignment import Assigning.Assignment hiding (Assignment, Error) import Data.Abstract.Name (name) import Data.Record -import Data.Syntax (contextualize, emptyStatements, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeStatementTerm, makeTerm1, parseError) +import Data.Syntax (contextualize, emptyTerm, parseError, handleError, infixContext, makeTerm, makeTerm', makeTerm'', makeTerm1) import Language.Go.Grammar as Grammar import Language.Go.Syntax as Go.Syntax import Language.Go.Type as Go.Type @@ -22,7 +22,6 @@ import qualified Data.Syntax.Literal as Literal import qualified Data.Syntax.Statement as Statement import qualified Data.Syntax.Type as Type import Data.Sum -import GHC.Exts (fromList) import qualified Data.Term as Term import Prologue @@ -113,7 +112,7 @@ assignment :: Assignment assignment = handleError program <|> parseError program :: Assignment -program = makeTerm <$> symbol SourceFile <*> children (Syntax.Program <$> manyStatements expression) +program = makeTerm <$> symbol SourceFile <*> children (Syntax.Program. Syntax.Statements <$> manyTerm expression) expression :: Assignment expression = term (handleError (choice expressionChoices)) @@ -209,10 +208,10 @@ types = ] identifiers :: Assignment -identifiers = makeStatementTerm <$> location <*> manyTerm identifier +identifiers = makeTerm'' <$> location <*> manyTerm identifier expressions :: Assignment -expressions = makeStatementTerm <$> location <*> manyTerm expression +expressions = makeTerm'' <$> location <*> manyTerm expression -- Literals @@ -360,7 +359,7 @@ defaultExpressionCase :: Assignment defaultExpressionCase = makeTerm <$> symbol DefaultCase <*> (Go.Syntax.DefaultPattern <$ source <*> (expressions <|> emptyTerm)) callExpression :: Assignment -callExpression = makeTerm <$> symbol CallExpression <*> children (Expression.Call [] <$> expression <*> manyTerm expression <*> emptyTerm) +callExpression = makeTerm <$> symbol CallExpression <*> children (Expression.Call <$> pure [] <*> expression <*> manyTerm expression <*> emptyTerm) expressionCase :: Assignment expressionCase = makeTerm <$> symbol ExpressionCase <*> (Statement.Pattern <$> children expressions <*> expressions) @@ -384,7 +383,7 @@ functionDeclaration = makeTerm <$> (symbol FunctionDeclaration <|> symbol FuncL returnParameters = makeTerm <$> symbol ParameterList <*> children (manyTerm expression) importDeclaration :: Assignment -importDeclaration = makeStatementTerm <$> symbol ImportDeclaration <*> children (manyTerm (importSpec <|> importSpecList)) +importDeclaration = makeTerm'' <$> symbol ImportDeclaration <*> children (manyTerm (importSpec <|> importSpecList)) where -- `import . "lib/Math"` dotImport = inject <$> (flip Go.Syntax.Import <$> dot <*> importFromPath) @@ -401,7 +400,7 @@ importDeclaration = makeStatementTerm <$> symbol ImportDeclaration <*> children dot = makeTerm <$> symbol Dot <*> (Literal.TextElement <$> source) underscore = makeTerm <$> symbol BlankIdentifier <*> (Literal.TextElement <$> source) importSpec = makeTerm' <$> symbol ImportSpec <*> children (sideEffectImport <|> dotImport <|> namedImport <|> plainImport) - importSpecList = makeTerm <$> symbol ImportSpecList <*> children (manyStatements (importSpec <|> comment)) + importSpecList = makeTerm <$> symbol ImportSpecList <*> children (manyTerm (importSpec <|> comment)) importFromPath = symbol InterpretedStringLiteral *> (importPath <$> source) indexExpression :: Assignment @@ -422,7 +421,7 @@ methodSpecList :: Assignment methodSpecList = symbol MethodSpecList *> children expressions packageClause :: Assignment -packageClause = makeTerm <$> symbol PackageClause <*> children (Go.Syntax.Package <$> expression <*> emptyStatements) +packageClause = makeTerm <$> symbol PackageClause <*> children (Go.Syntax.Package <$> expression <*> pure []) parameters :: Assignment parameters = symbol ParameterList *> children expressions @@ -606,9 +605,6 @@ manyTermsTill step end = manyTill (step <|> comment) end manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] manyTerm = many . term -manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) -manyStatements expr = fromList <$> (manyTerm expr) - -- | Match a term and contextualize any comments preceeding or proceeding the term. term :: Assignment -> Assignment term term' = contextualize comment term' <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm) diff --git a/src/Language/Go/Syntax.hs b/src/Language/Go/Syntax.hs index 404dcb2e5..9b47e4894 100644 --- a/src/Language/Go/Syntax.hs +++ b/src/Language/Go/Syntax.hs @@ -9,7 +9,6 @@ import Data.Aeson import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as BC import Data.JSON.Fields -import Data.Syntax (Statements) import Diffing.Algorithm import Prologue import System.FilePath.Posix @@ -300,7 +299,7 @@ instance ToJSONFields1 Field instance Evaluatable Field -data Package a = Package { packageName :: !a, packageContents :: Statements a } +data Package a = Package { packageName :: !a, packageContents :: ![a] } deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) instance Eq1 Package where liftEq = genericLiftEq diff --git a/src/Language/Haskell/Assignment.hs b/src/Language/Haskell/Assignment.hs index 5cd81ed5a..0da96796c 100644 --- a/src/Language/Haskell/Assignment.hs +++ b/src/Language/Haskell/Assignment.hs @@ -9,7 +9,7 @@ module Language.Haskell.Assignment import Assigning.Assignment hiding (Assignment, Error) import Data.Record import Data.Sum -import Data.Syntax (emptyTerm, handleError, parseError, makeTerm, contextualize, postContextualize) +import Data.Syntax (emptyTerm, handleError, parseError, makeTerm, makeTerm'', contextualize, postContextualize) import Language.Haskell.Grammar as Grammar import qualified Assigning.Assignment as Assignment import qualified Data.Abstract.Name as Name @@ -48,7 +48,7 @@ module' = makeTerm expressions :: Assignment -expressions = makeTerm <$> location <*> many expression +expressions = makeTerm'' <$> location <*> many expression expression :: Assignment expression = term (handleError (choice expressionChoices)) diff --git a/src/Language/PHP/Assignment.hs b/src/Language/PHP/Assignment.hs index 83b68db38..70171daac 100644 --- a/src/Language/PHP/Assignment.hs +++ b/src/Language/PHP/Assignment.hs @@ -9,7 +9,17 @@ module Language.PHP.Assignment import Assigning.Assignment hiding (Assignment, Error) import Data.Record import Data.Sum -import Data.Syntax (emptyTerm, handleError, parseError, infixContext, makeTerm, makeTerm', makeTerm1, contextualize, postContextualize) +import Data.Syntax + ( contextualize + , emptyTerm + , handleError + , infixContext + , makeTerm + , makeTerm' + , makeTerm1 + , parseError + , postContextualize + ) import Language.PHP.Grammar as Grammar import qualified Assigning.Assignment as Assignment import qualified Data.Abstract.Name as Name @@ -23,7 +33,6 @@ import qualified Data.Syntax.Statement as Statement import qualified Data.Syntax.Type as Type import qualified Data.Term as Term import qualified Language.PHP.Syntax as Syntax -import GHC.Exts (fromList) import Prologue type Syntax = '[ @@ -137,7 +146,7 @@ type Assignment = Assignment.Assignment [] Grammar Term -- | Assignment from AST in PHP's grammar onto a program in PHP's syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . fromList <$> (bookend <$> (text <|> emptyTerm) <*> manyTerm statement <*> (text <|> emptyTerm))) <|> parseError +assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . Syntax.Statements <$> (bookend <$> (text <|> emptyTerm) <*> manyTerm statement <*> (text <|> emptyTerm))) <|> parseError text :: Assignment text = makeTerm <$> symbol Text <*> (Syntax.Text <$> source) @@ -391,12 +400,12 @@ scalarType :: Assignment scalarType = makeTerm <$> symbol ScalarType <*> (Syntax.ScalarType <$> source) compoundStatement :: Assignment -compoundStatement = makeTerm <$> symbol CompoundStatement <*> children (manyStatements statement) +compoundStatement = makeTerm <$> symbol CompoundStatement <*> children (manyTerm statement) objectCreationExpression :: Assignment objectCreationExpression = (makeTerm <$> symbol ObjectCreationExpression <*> children (Expression.New <$> ((:) <$> term classTypeDesignator <*> (arguments <|> pure [])))) - <|> (makeTerm <$> symbol ObjectCreationExpression <*> children (makeAnonClass <$ token AnonNew <* token AnonClass <*> emptyTerm <*> (arguments <|> pure []) <*> (term classBaseClause <|> emptyTerm) <*> (term classInterfaceClause <|> emptyTerm) <*> (makeTerm <$> location <*> manyStatements classMemberDeclaration))) + <|> (makeTerm <$> symbol ObjectCreationExpression <*> children (makeAnonClass <$ token AnonNew <* token AnonClass <*> emptyTerm <*> (arguments <|> pure []) <*> (term classBaseClause <|> emptyTerm) <*> (term classInterfaceClause <|> emptyTerm) <*> (makeTerm <$> location <*> manyTerm classMemberDeclaration))) where makeAnonClass identifier args baseClause interfaceClause declarations = Declaration.Class [] identifier (args <> [baseClause, interfaceClause]) declarations classMemberDeclaration :: Assignment @@ -603,7 +612,7 @@ functionDefinition = makeTerm <$> symbol FunctionDefinition <*> children (makeFu makeFunction identifier parameters returnType statement = Declaration.Function [returnType] identifier parameters statement classDeclaration :: Assignment -classDeclaration = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> (term classModifier <|> emptyTerm) <*> term name <*> (term classBaseClause <|> emptyTerm) <*> (term classInterfaceClause <|> emptyTerm) <*> (makeTerm <$> location <*> manyStatements classMemberDeclaration)) +classDeclaration = makeTerm <$> symbol ClassDeclaration <*> children (makeClass <$> (term classModifier <|> emptyTerm) <*> term name <*> (term classBaseClause <|> emptyTerm) <*> (term classInterfaceClause <|> emptyTerm) <*> (makeTerm <$> location <*> manyTerm classMemberDeclaration)) where makeClass modifier name baseClause interfaceClause declarations = Declaration.Class [modifier] name [baseClause, interfaceClause] declarations @@ -768,9 +777,6 @@ someTerm = fmap NonEmpty.toList . someTerm' someTerm' :: Assignment -> Assignment.Assignment [] Grammar (NonEmpty Term) someTerm' = NonEmpty.some1 . commentedTerm -manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) -manyStatements expr = fromList <$> (manyTerm expr) - -- | Match infix terms separated by any of a list of operators, assigning any comments following each operand. infixTerm :: Assignment -> Assignment diff --git a/src/Language/Python/Assignment.hs b/src/Language/Python/Assignment.hs index 8fbfd5e84..5f4a4c64e 100644 --- a/src/Language/Python/Assignment.hs +++ b/src/Language/Python/Assignment.hs @@ -10,7 +10,18 @@ module Language.Python.Assignment import Assigning.Assignment hiding (Assignment, Error) import Data.Abstract.Name (name) import Data.Record -import Data.Syntax (contextualize, emptyTerm, handleError, infixContext, makeTerm, makeTerm', makeStatementTerm, makeTerm1, parseError, postContextualize) +import Data.Syntax + ( contextualize + , emptyTerm + , handleError + , infixContext + , makeTerm + , makeTerm' + , makeTerm'' + , makeTerm1 + , parseError + , postContextualize + ) import GHC.Stack import Language.Python.Grammar as Grammar import Language.Python.Syntax as Python.Syntax @@ -25,7 +36,6 @@ import qualified Data.Syntax.Statement as Statement import qualified Data.Syntax.Type as Type import qualified Data.Term as Term import qualified Data.List.NonEmpty as NonEmpty -import GHC.Exts (fromList) import Prologue @@ -92,7 +102,7 @@ type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term -- | Assignment from AST in Python's grammar onto a program in Python's syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Module <*> children (Syntax.Program . fromList <$> manyTerm expression) <|> parseError +assignment = handleError $ makeTerm <$> symbol Module <*> children (Syntax.Program . Syntax.Statements <$> manyTerm expression) <|> parseError expression :: Assignment expression = handleError (choice expressionChoices) @@ -166,13 +176,13 @@ expressionChoices = expressions :: Assignment -expressions = makeStatementTerm <$> location <*> manyTerm expression +expressions = makeTerm'' <$> location <*> manyTerm expression expressionStatement :: Assignment -expressionStatement = makeStatementTerm <$> symbol ExpressionStatement <*> children (someTerm expression) +expressionStatement = makeTerm'' <$> symbol ExpressionStatement <*> children (someTerm expression) expressionList :: Assignment -expressionList = makeStatementTerm <$> symbol ExpressionList <*> children (someTerm expression) +expressionList = makeTerm'' <$> symbol ExpressionList <*> children (someTerm expression) listSplat :: Assignment listSplat = makeTerm <$> symbol ListSplat <*> (Syntax.Identifier . name <$> source) @@ -362,7 +372,7 @@ comment :: Assignment comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source) import' :: Assignment -import' = makeStatementTerm <$> symbol ImportStatement <*> children (manyTerm (aliasedImport <|> plainImport)) +import' = makeTerm'' <$> symbol ImportStatement <*> children (manyTerm (aliasedImport <|> plainImport)) <|> makeTerm <$> symbol ImportFromStatement <*> children (Python.Syntax.Import <$> importPath <*> (wildcard <|> some (aliasImportSymbol <|> importSymbol))) where -- `import a as b` diff --git a/src/Language/Ruby/Assignment.hs b/src/Language/Ruby/Assignment.hs index 92c710d5b..eef043837 100644 --- a/src/Language/Ruby/Assignment.hs +++ b/src/Language/Ruby/Assignment.hs @@ -17,9 +17,8 @@ import Data.Syntax , infixContext , makeTerm , makeTerm' + , makeTerm'' , makeTerm1 - , makeStatementTerm - , manyStatements , parseError , postContextualize ) @@ -35,7 +34,6 @@ import qualified Data.Syntax.Literal as Literal import qualified Data.Syntax.Statement as Statement import qualified Data.Term as Term import qualified Language.Ruby.Syntax as Ruby.Syntax -import GHC.Exts (fromList) import Prologue hiding (for) -- | The type of Ruby syntax. @@ -106,7 +104,7 @@ type Assignment = Assignment' Term -- | Assignment from AST in Ruby’s grammar onto a program in Ruby’s syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program <$> manyStatements expression) <|> parseError +assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . Syntax.Statements <$> many expression) <|> parseError expression :: Assignment expression = term (handleError (choice expressionChoices)) @@ -158,10 +156,10 @@ expressionChoices = mk s construct = makeTerm <$> symbol s <*> children ((construct .) . fromMaybe <$> emptyTerm <*> optional (symbol ArgumentList *> children expressions)) expressions :: Assignment -expressions = makeStatementTerm <$> location <*> many expression +expressions = makeTerm'' <$> location <*> many expression parenthesizedExpressions :: Assignment -parenthesizedExpressions = makeTerm <$> symbol ParenthesizedStatements <*> children (manyStatements expression) +parenthesizedExpressions = makeTerm'' <$> symbol ParenthesizedStatements <*> children (many expression) withExtendedScope :: Assignment' a -> Assignment' a withExtendedScope inner = do @@ -244,7 +242,7 @@ singletonClass :: Assignment singletonClass = makeTerm <$> symbol SingletonClass <*> (withNewScope . children) (Ruby.Syntax.Class <$> expression <*> pure Nothing <*> expressions) module' :: Assignment -module' = makeTerm <$> symbol Module <*> (withNewScope . children) (Ruby.Syntax.Module <$> expression <*> manyStatements expression) +module' = makeTerm <$> symbol Module <*> (withNewScope . children) (Ruby.Syntax.Module <$> expression <*> many expression) scopeResolution :: Assignment scopeResolution = makeTerm <$> symbol ScopeResolution <*> children (Expression.ScopeResolution <$> many expression) @@ -274,8 +272,9 @@ parameter = postContextualize comment (term uncontextualizedParameter) optionalParameter = symbol OptionalParameter *> children (lhsIdent <* expression) method :: Assignment -method = makeTerm <$> symbol Method <*> (withNewScope . children) (Declaration.Method <$> pure [] <*> emptyTerm <*> methodSelector <*> params <*> expressions) +method = makeTerm <$> symbol Method <*> (withNewScope . children) (Declaration.Method <$> pure [] <*> emptyTerm <*> methodSelector <*> params <*> expressions') where params = symbol MethodParameters *> children (many parameter) <|> pure [] + expressions' = makeTerm <$> location <*> many expression singletonMethod :: Assignment singletonMethod = makeTerm <$> symbol SingletonMethod <*> (withNewScope . children) (Declaration.Method <$> pure [] <*> expression <*> methodSelector <*> params <*> expressions) @@ -504,8 +503,8 @@ term term = contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> som where heredocEnd = makeTerm <$> symbol HeredocEnd <*> (Literal.TextElement <$> source) -- | Match a series of terms or comments until a delimiter is matched. -manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar (Syntax.Statements Term) -manyTermsTill step end = fromList <$> manyTill (step <|> comment) end +manyTermsTill :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar b -> Assignment.Assignment [] Grammar [Term] +manyTermsTill step end = manyTill (step <|> comment) end -- | Match infix terms separated by any of a list of operators, assigning any comments following each operand. infixTerm :: HasCallStack diff --git a/src/Language/Ruby/Syntax.hs b/src/Language/Ruby/Syntax.hs index 8375f86e8..862d41eb7 100644 --- a/src/Language/Ruby/Syntax.hs +++ b/src/Language/Ruby/Syntax.hs @@ -8,7 +8,6 @@ import Data.Abstract.Path import qualified Data.ByteString.Char8 as BC import Data.JSON.Fields import qualified Data.Language as Language -import Data.Syntax (Statements) import Diffing.Algorithm import Prelude hiding (fail) import Prologue @@ -147,7 +146,7 @@ instance Evaluatable Class where Rval <$> letrec' name (\addr -> subtermValue classBody <* makeNamespace name addr super) -data Module a = Module { moduleIdentifier :: !a, moduleStatements :: Statements a } +data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] } deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Module where liftEq = genericLiftEq diff --git a/src/Language/TypeScript/Assignment.hs b/src/Language/TypeScript/Assignment.hs index b3e2f2784..a01e30515 100644 --- a/src/Language/TypeScript/Assignment.hs +++ b/src/Language/TypeScript/Assignment.hs @@ -11,7 +11,18 @@ import Data.Abstract.Name (name) import qualified Assigning.Assignment as Assignment import Data.Record import Data.Sum -import Data.Syntax (emptyTerm, emptyStatements, handleError, parseError, infixContext, makeTerm, makeTerm', makeStatementTerm, makeTerm1, contextualize, postContextualize) +import Data.Syntax + ( contextualize + , emptyTerm + , handleError + , infixContext + , makeTerm + , makeTerm' + , makeTerm'' + , makeTerm1 + , parseError + , postContextualize + ) import qualified Data.Syntax as Syntax import qualified Data.Syntax.Comment as Comment import qualified Data.Syntax.Declaration as Declaration @@ -22,7 +33,6 @@ import qualified Data.Syntax.Type as Type import qualified Data.Term as Term import Language.TypeScript.Grammar as Grammar import qualified Language.TypeScript.Syntax as TypeScript.Syntax -import GHC.Exts (fromList) import Prologue -- | The type of TypeScript syntax. @@ -177,7 +187,7 @@ type Assignment = Assignment.Assignment [] Grammar Term -- | Assignment from AST in TypeScript’s grammar onto a program in TypeScript’s syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program <$> manyStatements statement) <|> parseError +assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . Syntax.Statements <$> manyTerm statement) <|> parseError expression :: Assignment expression = handleError everything @@ -558,10 +568,10 @@ constructorTy :: Assignment constructorTy = makeTerm <$> symbol ConstructorType <*> children (TypeScript.Syntax.Constructor <$> (fromMaybe <$> emptyTerm <*> optional (term typeParameters)) <*> formalParameters <*> term ty) statementBlock :: Assignment -statementBlock = makeTerm <$> symbol StatementBlock <*> children (manyStatements statement) +statementBlock = makeTerm <$> symbol StatementBlock <*> children (manyTerm statement) classBodyStatements :: Assignment -classBodyStatements = makeStatementTerm <$> symbol ClassBody <*> children (contextualize' <$> Assignment.manyThrough comment (postContextualize' <$> (concat <$> many ((\as b -> as ++ [b]) <$> manyTerm decorator <*> term (methodDefinition <|> publicFieldDefinition <|> methodSignature <|> indexSignature <|> abstractMethodSignature))) <*> many comment)) +classBodyStatements = makeTerm'' <$> symbol ClassBody <*> children (contextualize' <$> Assignment.manyThrough comment (postContextualize' <$> (concat <$> many ((\as b -> as ++ [b]) <$> manyTerm decorator <*> term (methodDefinition <|> publicFieldDefinition <|> methodSignature <|> indexSignature <|> abstractMethodSignature))) <*> many comment)) where contextualize' (cs, formalParams) = case nonEmpty cs of Just cs -> toList cs ++ formalParams @@ -758,11 +768,11 @@ internalModule :: Assignment internalModule = makeTerm <$> symbol Grammar.InternalModule <*> children (TypeScript.Syntax.InternalModule <$> term (string <|> identifier <|> nestedIdentifier) <*> statements) module' :: Assignment -module' = makeTerm <$> symbol Module <*> children (TypeScript.Syntax.Module <$> term (string <|> identifier <|> nestedIdentifier) <*> (statements <|> emptyStatements)) +module' = makeTerm <$> symbol Module <*> children (TypeScript.Syntax.Module <$> term (string <|> identifier <|> nestedIdentifier) <*> (statements <|> pure [])) -statements :: Assignment.Assignment [] Grammar (Syntax.Statements Term) -statements = symbol StatementBlock *> children (manyStatements statement) +statements :: Assignment.Assignment [] Grammar [Term] +statements = symbol StatementBlock *> children (manyTerm statement) arrowFunction :: Assignment arrowFunction = makeArrowFun <$> symbol ArrowFunction <*> children ((,,) <$> emptyTerm <*> (((\a b c -> (a, [b], c)) <$> emptyTerm <*> term identifier <*> emptyTerm) <|> callSignatureParts) <*> term (expression <|> statementBlock)) @@ -860,9 +870,6 @@ binaryExpression = makeTerm' <$> symbol BinaryExpression <*> children (infixTerm manyTerm :: Assignment -> Assignment.Assignment [] Grammar [Term] manyTerm term = many (contextualize comment term <|> makeTerm1 <$> (Syntax.Context <$> some1 comment <*> emptyTerm)) -manyStatements :: Assignment.Assignment [] Grammar Term -> Assignment.Assignment [] Grammar (Syntax.Statements Term) -manyStatements expr = fromList <$> (manyTerm expr) - term :: Assignment -> Assignment term term = contextualize comment (postContextualize comment term) diff --git a/src/Language/TypeScript/Syntax.hs b/src/Language/TypeScript/Syntax.hs index 8be450a50..b05d22bd1 100644 --- a/src/Language/TypeScript/Syntax.hs +++ b/src/Language/TypeScript/Syntax.hs @@ -13,7 +13,6 @@ import Data.JSON.Fields import qualified Data.Language as Language import qualified Data.Map as Map import Data.Semigroup.Reducer (Reducer) -import Data.Syntax (Statements) import Diffing.Algorithm import Prelude import Prologue @@ -759,7 +758,7 @@ instance Ord1 Update where liftCompare = genericLiftCompare instance Show1 Update where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Update -data Module a = Module { moduleIdentifier :: !a, moduleStatements :: Statements a } +data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] } deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 Module where liftEq = genericLiftEq @@ -776,7 +775,7 @@ instance Evaluatable Module where -data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: Statements a } +data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: ![a] } deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) instance Eq1 InternalModule where liftEq = genericLiftEq From fe0f9460a72bd41fae0e0501304936aadb1cf3d6 Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Thu, 31 May 2018 08:10:20 -0700 Subject: [PATCH 08/16] Add a note about usage of [] --- src/Data/Abstract/Evaluatable.hs | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/src/Data/Abstract/Evaluatable.hs b/src/Data/Abstract/Evaluatable.hs index ca2a5a611..f9742d2e5 100644 --- a/src/Data/Abstract/Evaluatable.hs +++ b/src/Data/Abstract/Evaluatable.hs @@ -217,11 +217,14 @@ instance Apply Evaluatable fs => Evaluatable (Sum fs) where instance Evaluatable s => Evaluatable (TermF s a) where eval = eval . termFOut ---- | '[]' is treated as an imperative sequence of statements/declarations s.t.: ---- ---- 1. Each statement’s effects on the store are accumulated; ---- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and ---- 3. Only the last statement’s return value is returned. + +-- NOTE: Use 'Data.Syntax.Statements' instead of '[]' if you need imperative eval semantics. +-- +-- | '[]' is treated as an imperative sequence of statements/declarations s.t.: +-- +-- 1. Each statement’s effects on the store are accumulated; +-- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and +-- 3. Only the last statement’s return value is returned. instance Evaluatable [] where -- 'nonEmpty' and 'foldMap1' enable us to return the last statement’s result instead of 'unit' for non-empty lists. eval = maybe (pure (Rval unit)) (runApp . foldMap1 (App . subtermRef)) . nonEmpty From 5f676278a60180cd55773c42d1b1e61dead634bc Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Thu, 31 May 2018 08:29:33 -0700 Subject: [PATCH 09/16] Small cleanups --- src/Data/Syntax.hs | 2 +- src/Language/PHP/Assignment.hs | 3 +-- src/Language/Python/Assignment.hs | 1 - 3 files changed, 2 insertions(+), 4 deletions(-) diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index 0a9b16c7d..0ef8db25e 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -130,7 +130,7 @@ instance Show1 Program where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Program where eval (Program statements) = eval statements --- | Imperative sequence of statements/declarations +-- | Imperative sequence of statements/declarations s.t.: -- -- 1. Each statement’s effects on the store are accumulated; -- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and diff --git a/src/Language/PHP/Assignment.hs b/src/Language/PHP/Assignment.hs index 70171daac..94c4412ae 100644 --- a/src/Language/PHP/Assignment.hs +++ b/src/Language/PHP/Assignment.hs @@ -138,8 +138,7 @@ type Syntax = '[ , Syntax.UseClause , Syntax.VariableName , Type.Annotation - , [] - ] + , [] ] type Term = Term.Term (Sum Syntax) (Record Location) type Assignment = Assignment.Assignment [] Grammar Term diff --git a/src/Language/Python/Assignment.hs b/src/Language/Python/Assignment.hs index 5f4a4c64e..2f03af218 100644 --- a/src/Language/Python/Assignment.hs +++ b/src/Language/Python/Assignment.hs @@ -174,7 +174,6 @@ expressionChoices = , yield ] - expressions :: Assignment expressions = makeTerm'' <$> location <*> manyTerm expression From d05225fe615b96f639cb4b0f6f2fa1cc59eaecc5 Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Thu, 31 May 2018 08:44:44 -0700 Subject: [PATCH 10/16] Test fixes --- test/fixtures/javascript/corpus/export.diffA-B.txt | 8 ++++---- test/fixtures/javascript/corpus/export.diffB-A.txt | 7 ++++--- test/fixtures/javascript/corpus/import.diffA-B.txt | 4 ++-- test/fixtures/javascript/corpus/import.diffB-A.txt | 4 ++-- test/fixtures/typescript/corpus/export.diffA-B.txt | 8 ++++---- test/fixtures/typescript/corpus/export.diffB-A.txt | 7 ++++--- test/fixtures/typescript/corpus/import.diffA-B.txt | 4 ++-- test/fixtures/typescript/corpus/import.diffB-A.txt | 4 ++-- 8 files changed, 24 insertions(+), 22 deletions(-) diff --git a/test/fixtures/javascript/corpus/export.diffA-B.txt b/test/fixtures/javascript/corpus/export.diffA-B.txt index d820a0e81..c4fcacf9d 100644 --- a/test/fixtures/javascript/corpus/export.diffA-B.txt +++ b/test/fixtures/javascript/corpus/export.diffA-B.txt @@ -44,15 +44,15 @@ { (Identifier) ->(Identifier) } (Empty)))) +{+(DefaultExport + {+(Identifier)+})+} (DefaultExport { (Identifier) - ->(Identifier) }) -{+(DefaultExport - {+(Function + ->(Function {+(Empty)+} {+(Empty)+} {+(Identifier)+} - {+(Statements)+})+})+} + {+(Statements)+}) }) (DefaultExport (Function (Empty) diff --git a/test/fixtures/javascript/corpus/export.diffB-A.txt b/test/fixtures/javascript/corpus/export.diffB-A.txt index fca2269b7..0f430d3a8 100644 --- a/test/fixtures/javascript/corpus/export.diffB-A.txt +++ b/test/fixtures/javascript/corpus/export.diffB-A.txt @@ -47,9 +47,10 @@ {-(Empty)-} {-(Identifier)-} {-(Empty)-})-})) - (DefaultExport - { (Identifier) - ->(Identifier) }) +{+(DefaultExport + {+(Identifier)+})+} +{-(DefaultExport + {-(Identifier)-})-} {-(DefaultExport {-(Function {-(Empty)-} diff --git a/test/fixtures/javascript/corpus/import.diffA-B.txt b/test/fixtures/javascript/corpus/import.diffA-B.txt index f817f812a..d9ef4348b 100644 --- a/test/fixtures/javascript/corpus/import.diffA-B.txt +++ b/test/fixtures/javascript/corpus/import.diffA-B.txt @@ -2,8 +2,7 @@ {+(Import)+} {+(QualifiedAliasedImport {+(Identifier)+})+} -{ (Import) -->(Import) } +{+(Import)+} {+(Import)+} {+(Import)+} {+(Statements @@ -14,6 +13,7 @@ {+(QualifiedAliasedImport {+(Identifier)+})+})+} {+(SideEffectImport)+} +{-(Import)-} {-(QualifiedAliasedImport {-(Identifier)-})-} {-(Import)-} diff --git a/test/fixtures/javascript/corpus/import.diffB-A.txt b/test/fixtures/javascript/corpus/import.diffB-A.txt index d9ef4348b..f817f812a 100644 --- a/test/fixtures/javascript/corpus/import.diffB-A.txt +++ b/test/fixtures/javascript/corpus/import.diffB-A.txt @@ -2,7 +2,8 @@ {+(Import)+} {+(QualifiedAliasedImport {+(Identifier)+})+} -{+(Import)+} +{ (Import) +->(Import) } {+(Import)+} {+(Import)+} {+(Statements @@ -13,7 +14,6 @@ {+(QualifiedAliasedImport {+(Identifier)+})+})+} {+(SideEffectImport)+} -{-(Import)-} {-(QualifiedAliasedImport {-(Identifier)-})-} {-(Import)-} diff --git a/test/fixtures/typescript/corpus/export.diffA-B.txt b/test/fixtures/typescript/corpus/export.diffA-B.txt index d820a0e81..c4fcacf9d 100644 --- a/test/fixtures/typescript/corpus/export.diffA-B.txt +++ b/test/fixtures/typescript/corpus/export.diffA-B.txt @@ -44,15 +44,15 @@ { (Identifier) ->(Identifier) } (Empty)))) +{+(DefaultExport + {+(Identifier)+})+} (DefaultExport { (Identifier) - ->(Identifier) }) -{+(DefaultExport - {+(Function + ->(Function {+(Empty)+} {+(Empty)+} {+(Identifier)+} - {+(Statements)+})+})+} + {+(Statements)+}) }) (DefaultExport (Function (Empty) diff --git a/test/fixtures/typescript/corpus/export.diffB-A.txt b/test/fixtures/typescript/corpus/export.diffB-A.txt index fca2269b7..0f430d3a8 100644 --- a/test/fixtures/typescript/corpus/export.diffB-A.txt +++ b/test/fixtures/typescript/corpus/export.diffB-A.txt @@ -47,9 +47,10 @@ {-(Empty)-} {-(Identifier)-} {-(Empty)-})-})) - (DefaultExport - { (Identifier) - ->(Identifier) }) +{+(DefaultExport + {+(Identifier)+})+} +{-(DefaultExport + {-(Identifier)-})-} {-(DefaultExport {-(Function {-(Empty)-} diff --git a/test/fixtures/typescript/corpus/import.diffA-B.txt b/test/fixtures/typescript/corpus/import.diffA-B.txt index d0fcad063..b7e287342 100644 --- a/test/fixtures/typescript/corpus/import.diffA-B.txt +++ b/test/fixtures/typescript/corpus/import.diffA-B.txt @@ -2,8 +2,7 @@ {+(Import)+} {+(QualifiedAliasedImport {+(Identifier)+})+} -{ (Import) -->(Import) } +{+(Import)+} {+(Import)+} {+(Import)+} {+(Statements @@ -14,6 +13,7 @@ {+(QualifiedAliasedImport {+(Identifier)+})+})+} {+(SideEffectImport)+} +{-(Import)-} {-(QualifiedAliasedImport {-(Identifier)-})-} {-(Import)-} diff --git a/test/fixtures/typescript/corpus/import.diffB-A.txt b/test/fixtures/typescript/corpus/import.diffB-A.txt index cc1429eee..ed443bef3 100644 --- a/test/fixtures/typescript/corpus/import.diffB-A.txt +++ b/test/fixtures/typescript/corpus/import.diffB-A.txt @@ -2,7 +2,8 @@ {+(Import)+} {+(QualifiedAliasedImport {+(Identifier)+})+} -{+(Import)+} +{ (Import) +->(Import) } {+(Import)+} {+(Import)+} {+(Statements @@ -15,7 +16,6 @@ {+(SideEffectImport)+} {+(QualifiedAliasedImport {+(Identifier)+})+} -{-(Import)-} {-(QualifiedAliasedImport {-(Identifier)-})-} {-(Import)-} From 9baea34f5dcd8a0e9c33ceda3c8fb8b4fc873922 Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Thu, 31 May 2018 10:56:04 -0700 Subject: [PATCH 11/16] Generically derive ToJSONFields1 for basically everything --- src/Data/JSON/Fields.hs | 39 +--- src/Data/Syntax.hs | 20 +- src/Data/Syntax/Comment.hs | 6 +- src/Data/Syntax/Declaration.hs | 64 ++----- src/Data/Syntax/Directive.hs | 8 +- src/Data/Syntax/Expression.hs | 76 ++------ src/Data/Syntax/Literal.hs | 81 ++------ src/Data/Syntax/Statement.hs | 106 +++-------- src/Data/Syntax/Type.hs | 44 ++--- src/Language/Go/Syntax.hs | 84 +++------ src/Language/Go/Type.hs | 12 +- src/Language/Haskell/Syntax.hs | 4 +- src/Language/Markdown/Syntax.hs | 82 ++------- src/Language/PHP/Syntax.hs | 221 ++++++---------------- src/Language/Python/Syntax.hs | 20 +- src/Language/Ruby/Syntax.hs | 24 +-- src/Language/TypeScript/Syntax.hs | 296 ++++++++---------------------- test/Semantic/CLI/Spec.hs | 6 +- 18 files changed, 293 insertions(+), 900 deletions(-) diff --git a/src/Data/JSON/Fields.hs b/src/Data/JSON/Fields.hs index 99690b9cf..140fb8df5 100644 --- a/src/Data/JSON/Fields.hs +++ b/src/Data/JSON/Fields.hs @@ -6,8 +6,6 @@ module Data.JSON.Fields , ToJSONFields (..) , ToJSONFields1 (..) , (.=) - , noChildren - , withChildren ) where import Data.Aeson @@ -25,12 +23,6 @@ class ToJSONFields1 f where 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 - -noChildren :: KeyValue kv => [kv] -> [kv] -noChildren ks = ("children" .= ([] :: [Int])) : ks - instance ToJSONFields a => ToJSONFields (Join (,) a) where toJSONFields (Join (a, b)) = [ "before" .= object (toJSONFields a), "after" .= object (toJSONFields b) ] @@ -105,10 +97,10 @@ 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) + gtoJSONFields1 m1 = gselectorJSONValue1 keyName (unM1 m1) + where keyName = case selName m1 of + "" -> Nothing + n -> Just (Text.pack n) instance (GToJSONFields1 f, GToJSONFields1 g) => GToJSONFields1 (f :+: g) where gtoJSONFields1 (L1 l) = gtoJSONFields1 l @@ -119,34 +111,19 @@ instance (GToJSONFields1 f, GToJSONFields1 g) => GToJSONFields1 (f :*: g) where -- | A typeclass to retrieve the JSON 'Value' of a record selector. class GSelectorJSONValue1 f where - gselectorJSONValue1 :: ToJSON a => f a -> SomeJSON + gselectorJSONValue1 :: (KeyValue kv, ToJSON a) => Maybe Text -> f a -> [kv] instance GSelectorJSONValue1 Par1 where - gselectorJSONValue1 = SomeJSON . unPar1 + gselectorJSONValue1 k x = [ fromMaybe "children" k .= unPar1 x] instance ToJSON1 f => GSelectorJSONValue1 (Rec1 f) where - gselectorJSONValue1 = SomeJSON . SomeJSON1 . unRec1 + gselectorJSONValue1 k x = [ fromMaybe "children" k .= toJSON1 (unRec1 x)] instance ToJSON k => GSelectorJSONValue1 (K1 r k) where - gselectorJSONValue1 = SomeJSON . unK1 + gselectorJSONValue1 k x = [ fromMaybe "value" k .= unK1 x ] -- 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 17c707714..541d9f1bb 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -119,7 +119,7 @@ instance Declarations1 Identifier where newtype Program a = Program [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Program where liftEq = genericLiftEq instance Ord1 Program where liftCompare = genericLiftCompare @@ -131,7 +131,7 @@ instance Evaluatable Program where -- | 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, ToJSONFields1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 AccessibilityModifier where liftEq = genericLiftEq instance Ord1 AccessibilityModifier where liftCompare = genericLiftCompare @@ -144,9 +144,7 @@ instance Evaluatable AccessibilityModifier -- -- This can be used to represent an implicit no-op, e.g. the alternative in an 'if' statement without an 'else'. data Empty a = Empty - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Empty + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Empty where liftEq _ _ _ = True instance Ord1 Empty where liftCompare _ _ _ = EQ @@ -158,7 +156,7 @@ instance Evaluatable Empty where -- | Syntax representing a parsing or assignment error. data Error a = Error { errorCallStack :: ErrorStack, errorExpected :: [String], errorActual :: Maybe String, errorChildren :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Error where liftEq = genericLiftEq instance Ord1 Error where liftCompare = genericLiftCompare @@ -166,12 +164,6 @@ instance Show1 Error where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Error -instance ToJSONFields1 Error where - toJSONFields1 f@Error{..} = withChildren f [ "stack" .= errorCallStack - , "expected" .= errorExpected - , "actual" .= errorActual - ] - errorSyntax :: Error.Error String -> [a] -> Error a errorSyntax Error.Error{..} = Error (ErrorStack (getCallStack callStack)) errorExpected errorActual @@ -211,9 +203,7 @@ instance Ord ErrorStack where data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a } - deriving (Eq, Foldable, Functor, Generic1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Context + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Diffable Context where subalgorithmFor blur focus (Context n s) = Context <$> traverse blur n <*> focus s diff --git a/src/Data/Syntax/Comment.hs b/src/Data/Syntax/Comment.hs index e00f4ce58..b47a7d161 100644 --- a/src/Data/Syntax/Comment.hs +++ b/src/Data/Syntax/Comment.hs @@ -3,21 +3,17 @@ module Data.Syntax.Comment where import Prologue import Data.Abstract.Evaluatable -import Data.ByteString (unpack) import Data.JSON.Fields import Diffing.Algorithm -- | An unnested comment (line or block). newtype Comment a = Comment { commentContent :: 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 Comment where liftEq = genericLiftEq instance Ord1 Comment where liftCompare = genericLiftCompare instance Show1 Comment where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Comment where - toJSONFields1 f@Comment{..} = withChildren f ["contents" .= unpack commentContent ] - instance Evaluatable Comment where eval _ = pure (Rval unit) diff --git a/src/Data/Syntax/Declaration.hs b/src/Data/Syntax/Declaration.hs index 34f5f0ce2..b7aa4f9fb 100644 --- a/src/Data/Syntax/Declaration.hs +++ b/src/Data/Syntax/Declaration.hs @@ -9,7 +9,7 @@ import Diffing.Algorithm import Prologue data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a } - deriving (Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Diffable Function where equivalentBySubterm = Just . functionName @@ -18,8 +18,6 @@ instance Eq1 Function where liftEq = genericLiftEq instance Ord1 Function where liftCompare = genericLiftCompare instance Show1 Function where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Function - -- TODO: Filter the closed-over environment by the free variables in the term. -- TODO: How should we represent function types, where applicable? @@ -36,7 +34,7 @@ instance Declarations a => Declarations (Function a) where data Method a = Method { methodContext :: ![a], methodReceiver :: !a, methodName :: !a, methodParameters :: ![a], methodBody :: !a } - deriving (Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Method where liftEq = genericLiftEq instance Ord1 Method where liftCompare = genericLiftCompare @@ -45,8 +43,6 @@ instance Show1 Method where liftShowsPrec = genericLiftShowsPrec instance Diffable Method where equivalentBySubterm = Just . methodName -instance ToJSONFields1 Method - -- Evaluating a Method creates a closure and makes that value available in the -- local environment. instance Evaluatable Method where @@ -60,40 +56,34 @@ instance Evaluatable Method where -- | A method signature in TypeScript or a method spec in Go. data MethodSignature a = MethodSignature { _methodSignatureContext :: ![a], _methodSignatureName :: !a, _methodSignatureParameters :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 MethodSignature where liftEq = genericLiftEq instance Ord1 MethodSignature where liftCompare = genericLiftCompare instance Show1 MethodSignature where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 MethodSignature - -- TODO: Implement Eval instance for MethodSignature instance Evaluatable MethodSignature newtype RequiredParameter a = RequiredParameter { requiredParameter :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 RequiredParameter where liftEq = genericLiftEq instance Ord1 RequiredParameter where liftCompare = genericLiftCompare instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 RequiredParameter - -- TODO: Implement Eval instance for RequiredParameter instance Evaluatable RequiredParameter newtype OptionalParameter a = OptionalParameter { optionalParameter :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 OptionalParameter where liftEq = genericLiftEq instance Ord1 OptionalParameter where liftCompare = genericLiftCompare instance Show1 OptionalParameter where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 OptionalParameter - -- TODO: Implement Eval instance for OptionalParameter instance Evaluatable OptionalParameter @@ -103,14 +93,12 @@ instance Evaluatable OptionalParameter -- TODO: It would be really nice to have a more meaningful type contained in here than [a] -- | A declaration of possibly many variables such as var foo = 5, bar = 6 in JavaScript. newtype VariableDeclaration a = VariableDeclaration { variableDeclarations :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 VariableDeclaration where liftEq = genericLiftEq instance Ord1 VariableDeclaration where liftCompare = genericLiftCompare instance Show1 VariableDeclaration where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 VariableDeclaration - instance Evaluatable VariableDeclaration where eval (VariableDeclaration []) = pure (Rval unit) eval (VariableDeclaration decs) = Rval . multiple <$> traverse subtermValue decs @@ -123,14 +111,12 @@ instance Declarations a => Declarations (VariableDeclaration a) where -- | A TypeScript/Java style interface declaration to implement. data InterfaceDeclaration a = InterfaceDeclaration { interfaceDeclarationContext :: ![a], interfaceDeclarationIdentifier :: !a, interfaceDeclarationBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare instance Show1 InterfaceDeclaration where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 InterfaceDeclaration - -- TODO: Implement Eval instance for InterfaceDeclaration instance Evaluatable InterfaceDeclaration @@ -140,38 +126,32 @@ instance Declarations a => Declarations (InterfaceDeclaration a) where -- | A public field definition such as a field definition in a JavaScript class. data PublicFieldDefinition a = PublicFieldDefinition { publicFieldContext :: ![a], publicFieldPropertyName :: !a, publicFieldValue :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 PublicFieldDefinition where liftEq = genericLiftEq instance Ord1 PublicFieldDefinition where liftCompare = genericLiftCompare instance Show1 PublicFieldDefinition where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 PublicFieldDefinition - -- TODO: Implement Eval instance for PublicFieldDefinition instance Evaluatable PublicFieldDefinition data Variable a = Variable { variableName :: !a, variableType :: !a, variableValue :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Variable where liftEq = genericLiftEq instance Ord1 Variable where liftCompare = genericLiftCompare instance Show1 Variable where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Variable - -- TODO: Implement Eval instance for Variable instance Evaluatable Variable data Class a = Class { classContext :: ![a], classIdentifier :: !a, classSuperclasses :: ![a], classBody :: !a } - deriving (Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Declarations a => Declarations (Class a) where declaredName (Class _ name _ _) = declaredName name -instance ToJSONFields1 Class - instance Diffable Class where equivalentBySubterm = Just . classIdentifier @@ -191,14 +171,12 @@ instance Evaluatable Class where -- | A decorator in Python data Decorator a = Decorator { decoratorIdentifier :: !a, decoratorParamaters :: ![a], decoratorBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Decorator where liftEq = genericLiftEq instance Ord1 Decorator where liftCompare = genericLiftCompare instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Decorator - -- TODO: Implement Eval instance for Decorator instance Evaluatable Decorator @@ -207,70 +185,60 @@ instance Evaluatable Decorator -- | An ADT, i.e. a disjoint sum of products, like 'data' in Haskell, or 'enum' in Rust or Swift. data Datatype a = Datatype { datatypeName :: !a, datatypeConstructors :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Data.Syntax.Declaration.Datatype where liftEq = genericLiftEq instance Ord1 Data.Syntax.Declaration.Datatype where liftCompare = genericLiftCompare instance Show1 Data.Syntax.Declaration.Datatype where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Data.Syntax.Declaration.Datatype - -- TODO: Implement Eval instance for Datatype instance Evaluatable Data.Syntax.Declaration.Datatype -- | A single constructor in a datatype, or equally a 'struct' in C, Rust, or Swift. data Constructor a = Constructor { constructorName :: !a, constructorFields :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Data.Syntax.Declaration.Constructor where liftEq = genericLiftEq instance Ord1 Data.Syntax.Declaration.Constructor where liftCompare = genericLiftCompare instance Show1 Data.Syntax.Declaration.Constructor where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Data.Syntax.Declaration.Constructor - -- TODO: Implement Eval instance for Constructor instance Evaluatable Data.Syntax.Declaration.Constructor -- | Comprehension (e.g. ((a for b in c if a()) in Python) data Comprehension a = Comprehension { comprehensionValue :: !a, comprehensionBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Comprehension where liftEq = genericLiftEq instance Ord1 Comprehension where liftCompare = genericLiftCompare instance Show1 Comprehension where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Comprehension - -- TODO: Implement Eval instance for Comprehension instance Evaluatable Comprehension -- | A declared type (e.g. `a []int` in Go). data Type a = Type { typeName :: !a, typeKind :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Type where liftEq = genericLiftEq instance Ord1 Type where liftCompare = genericLiftCompare instance Show1 Type where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Type - -- TODO: Implement Eval instance for Type instance Evaluatable Type -- | Type alias declarations in Javascript/Haskell, etc. data TypeAlias a = TypeAlias { typeAliasContext :: ![a], typeAliasIdentifier :: !a, typeAliasKind :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TypeAlias where liftEq = genericLiftEq instance Ord1 TypeAlias where liftCompare = genericLiftCompare instance Show1 TypeAlias where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 TypeAlias - -- TODO: Implement Eval instance for TypeAlias instance Evaluatable TypeAlias where eval TypeAlias{..} = do diff --git a/src/Data/Syntax/Directive.hs b/src/Data/Syntax/Directive.hs index 34589291d..ce7bfa4dc 100644 --- a/src/Data/Syntax/Directive.hs +++ b/src/Data/Syntax/Directive.hs @@ -11,27 +11,23 @@ import Prologue -- A file directive like the Ruby constant `__FILE__`. data File a = File - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 File where liftEq = genericLiftEq instance Ord1 File where liftCompare = genericLiftCompare instance Show1 File where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 File - instance Evaluatable File where eval File = Rval . string . BC.pack . modulePath <$> currentModule -- A line directive like the Ruby constant `__LINE__`. data Line a = Line - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Line where liftEq = genericLiftEq instance Ord1 Line where liftCompare = genericLiftCompare instance Show1 Line where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Line - instance Evaluatable Line where eval Line = Rval . integer . fromIntegral . posLine . spanStart <$> currentSpan diff --git a/src/Data/Syntax/Expression.hs b/src/Data/Syntax/Expression.hs index 7315bc412..ddf03371e 100644 --- a/src/Data/Syntax/Expression.hs +++ b/src/Data/Syntax/Expression.hs @@ -10,14 +10,12 @@ import Prologue hiding (index) -- | Typical prefix function application, like `f(x)` in many languages, or `f x` in Haskell. data Call a = Call { callContext :: ![a], callFunction :: !a, callParams :: ![a], callBlock :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Call where liftEq = genericLiftEq instance Ord1 Call where liftCompare = genericLiftCompare instance Show1 Call where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Call - instance Evaluatable Call where eval Call{..} = do op <- subtermValue callFunction @@ -31,14 +29,12 @@ data Comparison a | Equal !a !a | StrictEqual !a !a | Comparison !a !a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Comparison where liftEq = genericLiftEq instance Ord1 Comparison where liftCompare = genericLiftCompare instance Show1 Comparison where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Comparison - instance Evaluatable Comparison where eval t = Rval <$> (traverse subtermValue t >>= go) where go x = case x of @@ -62,14 +58,12 @@ data Arithmetic a | Modulo !a !a | Power !a !a | Negate !a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Arithmetic where liftEq = genericLiftEq instance Ord1 Arithmetic where liftCompare = genericLiftCompare instance Show1 Arithmetic where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Arithmetic - instance Evaluatable Arithmetic where eval t = Rval <$> (traverse subtermValue t >>= go) where go (Plus a b) = liftNumeric2 add a b where add = liftReal (+) @@ -85,14 +79,12 @@ instance Evaluatable Arithmetic where data Match a = Matches !a !a | NotMatches !a !a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Match where liftEq = genericLiftEq instance Ord1 Match where liftCompare = genericLiftCompare instance Show1 Match where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Match - -- TODO: Implement Eval instance for Match instance Evaluatable Match @@ -102,14 +94,12 @@ data Boolean a | And !a !a | Not !a | XOr !a !a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Boolean where liftEq = genericLiftEq instance Ord1 Boolean where liftCompare = genericLiftCompare instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Boolean - instance Evaluatable Boolean where -- N.B. we have to use Monad rather than Applicative/Traversable on 'And' and 'Or' so that we don't evaluate both operands eval t = Rval <$> go (fmap subtermValue t) where @@ -124,56 +114,48 @@ instance Evaluatable Boolean where -- | Javascript delete operator newtype Delete a = Delete a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Delete where liftEq = genericLiftEq instance Ord1 Delete where liftCompare = genericLiftCompare instance Show1 Delete where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Delete - -- TODO: Implement Eval instance for Delete instance Evaluatable Delete -- | A sequence expression such as Javascript or C's comma operator. data SequenceExpression a = SequenceExpression { _firstExpression :: !a, _secondExpression :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 SequenceExpression where liftEq = genericLiftEq instance Ord1 SequenceExpression where liftCompare = genericLiftCompare instance Show1 SequenceExpression where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 SequenceExpression - -- TODO: Implement Eval instance for SequenceExpression instance Evaluatable SequenceExpression -- | Javascript void operator newtype Void a = Void a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Void where liftEq = genericLiftEq instance Ord1 Void where liftCompare = genericLiftCompare instance Show1 Void where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Void - -- TODO: Implement Eval instance for Void instance Evaluatable Void -- | Javascript typeof operator newtype Typeof a = Typeof a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Typeof where liftEq = genericLiftEq instance Ord1 Typeof where liftCompare = genericLiftCompare instance Show1 Typeof where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Typeof - -- TODO: Implement Eval instance for Typeof instance Evaluatable Typeof @@ -187,14 +169,12 @@ data Bitwise a | RShift !a !a | UnsignedRShift !a !a | Complement a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Bitwise where liftEq = genericLiftEq instance Ord1 Bitwise where liftCompare = genericLiftCompare instance Show1 Bitwise where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Bitwise - instance Evaluatable Bitwise where eval t = Rval <$> (traverse subtermValue t >>= go) where genLShift x y = shiftL x (fromIntegral y) @@ -211,14 +191,12 @@ instance Evaluatable Bitwise where -- | Member Access (e.g. a.b) data MemberAccess a = MemberAccess !a !a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 MemberAccess where liftEq = genericLiftEq instance Ord1 MemberAccess where liftCompare = genericLiftCompare instance Show1 MemberAccess where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 MemberAccess - instance Evaluatable MemberAccess where eval (MemberAccess obj prop) = do obj <- subtermValue obj @@ -231,14 +209,12 @@ instance Evaluatable MemberAccess where data Subscript a = Subscript !a ![a] | Member !a !a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Subscript where liftEq = genericLiftEq instance Ord1 Subscript where liftCompare = genericLiftCompare instance Show1 Subscript where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Subscript - -- TODO: Finish Eval instance for Subscript -- TODO return a special LvalSubscript instance here instance Evaluatable Subscript where @@ -249,97 +225,83 @@ instance Evaluatable Subscript where -- | Enumeration (e.g. a[1:10:1] in Python (start at index 1, stop at index 10, step 1 element from start to stop)) data Enumeration a = Enumeration { enumerationStart :: !a, enumerationEnd :: !a, enumerationStep :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Enumeration where liftEq = genericLiftEq instance Ord1 Enumeration where liftCompare = genericLiftCompare instance Show1 Enumeration where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Enumeration - -- TODO: Implement Eval instance for Enumeration instance Evaluatable Enumeration -- | InstanceOf (e.g. a instanceof b in JavaScript data InstanceOf a = InstanceOf { instanceOfSubject :: !a, instanceOfObject :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 InstanceOf where liftEq = genericLiftEq instance Ord1 InstanceOf where liftCompare = genericLiftCompare instance Show1 InstanceOf where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 InstanceOf - -- TODO: Implement Eval instance for InstanceOf instance Evaluatable InstanceOf -- | ScopeResolution (e.g. import a.b in Python or a::b in C++) newtype ScopeResolution a = ScopeResolution [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ScopeResolution where liftEq = genericLiftEq instance Ord1 ScopeResolution where liftCompare = genericLiftCompare instance Show1 ScopeResolution where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 ScopeResolution - -- TODO: Implement Eval instance for ScopeResolution instance Evaluatable ScopeResolution -- | A non-null expression such as Typescript or Swift's ! expression. newtype NonNullExpression a = NonNullExpression { nonNullExpression :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 NonNullExpression where liftEq = genericLiftEq instance Ord1 NonNullExpression where liftCompare = genericLiftCompare instance Show1 NonNullExpression where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 NonNullExpression - -- TODO: Implement Eval instance for NonNullExpression instance Evaluatable NonNullExpression -- | An await expression in Javascript or C#. newtype Await a = Await { awaitSubject :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Await where liftEq = genericLiftEq instance Ord1 Await where liftCompare = genericLiftCompare instance Show1 Await where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Await - -- TODO: Implement Eval instance for Await instance Evaluatable Await -- | An object constructor call in Javascript, Java, etc. newtype New a = New { newSubject :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 New where liftEq = genericLiftEq instance Ord1 New where liftCompare = genericLiftCompare instance Show1 New where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 New - -- TODO: Implement Eval instance for New instance Evaluatable New -- | A cast expression to a specified type. data Cast a = Cast { castSubject :: !a, castType :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Cast where liftEq = genericLiftEq instance Ord1 Cast where liftCompare = genericLiftCompare instance Show1 Cast where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Cast - -- TODO: Implement Eval instance for Cast instance Evaluatable Cast diff --git a/src/Data/Syntax/Literal.hs b/src/Data/Syntax/Literal.hs index 924052d56..0401873b3 100644 --- a/src/Data/Syntax/Literal.hs +++ b/src/Data/Syntax/Literal.hs @@ -14,7 +14,7 @@ import Text.Read (readMaybe) -- Boolean newtype Boolean a = Boolean Bool - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) true :: Boolean a true = Boolean True @@ -29,14 +29,11 @@ instance Show1 Boolean where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Boolean where eval (Boolean x) = pure (Rval (boolean x)) -instance ToJSONFields1 Boolean where - toJSONFields1 (Boolean b) = noChildren [ "value" .= b ] - -- Numeric -- | A literal integer of unspecified width. No particular base is implied. newtype Integer a = Integer { integerContent :: ByteString } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Data.Syntax.Literal.Integer where liftEq = genericLiftEq instance Ord1 Data.Syntax.Literal.Integer where liftCompare = genericLiftCompare @@ -47,17 +44,13 @@ instance Evaluatable Data.Syntax.Literal.Integer where eval (Data.Syntax.Literal.Integer x) = Rval . integer <$> maybeM (throwEvalError (IntegerFormatError x)) (fst <$> readInteger x) -instance ToJSONFields1 Data.Syntax.Literal.Integer where - toJSONFields1 (Integer i) = noChildren ["asString" .= unpack i] - - -- TODO: Should IntegerLiteral hold an Integer instead of a ByteString? -- TODO: Do we care about differentiating between hex/octal/decimal/binary integer literals? -- TODO: Consider a Numeric datatype with FloatingPoint/Integral/etc constructors. -- | A literal float of unspecified width. newtype Float a = Float { floatContent :: ByteString } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Data.Syntax.Literal.Float where liftEq = genericLiftEq instance Ord1 Data.Syntax.Literal.Float where liftCompare = genericLiftCompare @@ -67,12 +60,9 @@ instance Evaluatable Data.Syntax.Literal.Float where eval (Float s) = Rval . float <$> either (const (throwEvalError (FloatFormatError s))) pure (parseScientific s) -instance ToJSONFields1 Float where - toJSONFields1 (Float f) = noChildren ["asString" .= unpack f] - -- Rational literals e.g. `2/3r` newtype Rational a = Rational ByteString - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Data.Syntax.Literal.Rational where liftEq = genericLiftEq instance Ord1 Data.Syntax.Literal.Rational where liftCompare = genericLiftCompare @@ -85,12 +75,9 @@ instance Evaluatable Data.Syntax.Literal.Rational where parsed = readMaybe @Prelude.Integer (unpack trimmed) in Rval . rational <$> maybe (throwEvalError (RationalFormatError r)) (pure . toRational) parsed -instance ToJSONFields1 Data.Syntax.Literal.Rational where - toJSONFields1 (Rational r) = noChildren ["asString" .= unpack r] - -- Complex literals e.g. `3 + 2i` newtype Complex a = Complex 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 Data.Syntax.Literal.Complex where liftEq = genericLiftEq instance Ord1 Data.Syntax.Literal.Complex where liftCompare = genericLiftCompare @@ -99,13 +86,10 @@ instance Show1 Data.Syntax.Literal.Complex where liftShowsPrec = genericLiftShow -- TODO: Implement Eval instance for Complex instance Evaluatable Complex -instance ToJSONFields1 Complex where - toJSONFields1 (Complex c) = noChildren ["asString" .= unpack c] - -- Strings, symbols newtype String a = String { stringElements :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Data.Syntax.Literal.String where liftEq = genericLiftEq instance Ord1 Data.Syntax.Literal.String where liftCompare = genericLiftCompare @@ -116,11 +100,9 @@ instance Show1 Data.Syntax.Literal.String where liftShowsPrec = genericLiftShows -- TODO: Implement Eval instance for String instance Evaluatable Data.Syntax.Literal.String -instance ToJSONFields1 Data.Syntax.Literal.String - -- | An interpolation element within a string literal. newtype InterpolationElement a = InterpolationElement { interpolationBody :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 InterpolationElement where liftEq = genericLiftEq instance Ord1 InterpolationElement where liftCompare = genericLiftCompare @@ -129,24 +111,19 @@ instance Show1 InterpolationElement where liftShowsPrec = genericLiftShowsPrec -- TODO: Implement Eval instance for InterpolationElement instance Evaluatable InterpolationElement -instance ToJSONFields1 InterpolationElement - -- | A sequence of textual contents within a string literal. newtype TextElement a = TextElement { textElementContent :: 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 TextElement where liftEq = genericLiftEq instance Ord1 TextElement where liftCompare = genericLiftCompare instance Show1 TextElement where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 TextElement where - toJSONFields1 (TextElement c) = noChildren ["asString" .= unpack c] - instance Evaluatable TextElement where eval (TextElement x) = pure (Rval (string x)) data Null a = Null - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Null where liftEq = genericLiftEq instance Ord1 Null where liftCompare = genericLiftCompare @@ -154,22 +131,18 @@ instance Show1 Null where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Null where eval _ = pure (Rval null) -instance ToJSONFields1 Null - newtype Symbol a = Symbol { symbolContent :: ByteString } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Symbol where liftEq = genericLiftEq instance Ord1 Symbol where liftCompare = genericLiftCompare instance Show1 Symbol where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Symbol - instance Evaluatable Symbol where eval (Symbol s) = pure (Rval (symbol s)) newtype Regex a = Regex { regexContent :: 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 Regex where liftEq = genericLiftEq instance Ord1 Regex where liftCompare = genericLiftCompare @@ -178,10 +151,6 @@ instance Show1 Regex where liftShowsPrec = genericLiftShowsPrec -- TODO: Heredoc-style string literals? -- TODO: Character literals. -instance ToJSONFields1 Regex where - toJSONFields1 (Regex r) = noChildren ["asString" .= unpack r] - - -- TODO: Implement Eval instance for Regex instance Evaluatable Regex @@ -189,46 +158,38 @@ instance Evaluatable Regex -- Collections newtype Array a = Array { arrayElements :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Array where liftEq = genericLiftEq instance Ord1 Array where liftCompare = genericLiftCompare instance Show1 Array where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Array - instance Evaluatable Array where eval (Array a) = Rval <$> (array =<< traverse subtermValue a) newtype Hash a = Hash { hashElements :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Hash where liftEq = genericLiftEq instance Ord1 Hash where liftCompare = genericLiftCompare instance Show1 Hash where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Hash - instance Evaluatable Hash where eval t = Rval . hash <$> traverse (subtermValue >=> asPair) (hashElements t) data KeyValue a = KeyValue { key :: !a, value :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 KeyValue where liftEq = genericLiftEq instance Ord1 KeyValue where liftCompare = genericLiftCompare instance Show1 KeyValue where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 KeyValue - instance Evaluatable KeyValue where eval (fmap subtermValue -> KeyValue{..}) = Rval <$> (kvPair <$> key <*> value) -instance ToJSONFields1 Tuple - newtype Tuple a = Tuple { tupleContents :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Tuple where liftEq = genericLiftEq instance Ord1 Tuple where liftCompare = genericLiftCompare @@ -238,14 +199,12 @@ instance Evaluatable Tuple where eval (Tuple cs) = Rval . multiple <$> traverse subtermValue cs newtype Set a = Set { setElements :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Set where liftEq = genericLiftEq instance Ord1 Set where liftCompare = genericLiftCompare instance Show1 Set where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Set - -- TODO: Implement Eval instance for Set instance Evaluatable Set @@ -254,28 +213,24 @@ instance Evaluatable Set -- | A declared pointer (e.g. var pointer *int in Go) newtype Pointer a = Pointer a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Pointer where liftEq = genericLiftEq instance Ord1 Pointer where liftCompare = genericLiftCompare instance Show1 Pointer where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Pointer - -- TODO: Implement Eval instance for Pointer instance Evaluatable Pointer -- | A reference to a pointer's address (e.g. &pointer in Go) newtype Reference a = Reference a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Reference where liftEq = genericLiftEq instance Ord1 Reference where liftCompare = genericLiftCompare instance Show1 Reference where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Reference - -- TODO: Implement Eval instance for Reference instance Evaluatable Reference diff --git a/src/Data/Syntax/Statement.hs b/src/Data/Syntax/Statement.hs index cea29f2f1..8983bd18d 100644 --- a/src/Data/Syntax/Statement.hs +++ b/src/Data/Syntax/Statement.hs @@ -2,7 +2,6 @@ module Data.Syntax.Statement where import Data.Abstract.Evaluatable -import Data.ByteString.Char8 (unpack) import Data.JSON.Fields import Diffing.Algorithm import Prelude @@ -10,14 +9,12 @@ import Prologue -- | Conditional. This must have an else block, which can be filled with some default value when omitted in the source, e.g. 'pure ()' for C-style if-without-else or 'pure Nothing' for Ruby-style, in both cases assuming some appropriate Applicative context into which the If will be lifted. data If a = If { ifCondition :: !a, ifThenBody :: !a, ifElseBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 If where liftEq = genericLiftEq instance Ord1 If where liftCompare = genericLiftCompare instance Show1 If where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 If - instance Evaluatable If where eval (If cond if' else') = do bool <- subtermValue cond @@ -25,14 +22,12 @@ instance Evaluatable If where -- | Else statement. The else condition is any term, that upon successful completion, continues evaluation to the elseBody, e.g. `for ... else` in Python. data Else a = Else { elseCondition :: !a, elseBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Else where liftEq = genericLiftEq instance Ord1 Else where liftCompare = genericLiftCompare instance Show1 Else where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Else - -- TODO: Implement Eval instance for Else instance Evaluatable Else @@ -40,56 +35,48 @@ instance Evaluatable Else -- | Goto statement (e.g. `goto a` in Go). newtype Goto a = Goto { gotoLocation :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Goto where liftEq = genericLiftEq instance Ord1 Goto where liftCompare = genericLiftCompare instance Show1 Goto where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Goto - -- TODO: Implement Eval instance for Goto instance Evaluatable Goto -- | A pattern-matching or computed jump control-flow statement, like 'switch' in C or JavaScript, or 'case' in Ruby or Haskell. data Match a = Match { matchSubject :: !a, matchPatterns :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Match where liftEq = genericLiftEq instance Ord1 Match where liftCompare = genericLiftCompare instance Show1 Match where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Match - -- TODO: Implement Eval instance for Match instance Evaluatable Match -- | A pattern in a pattern-matching or computed jump control-flow statement, like 'case' in C or JavaScript, 'when' in Ruby, or the left-hand side of '->' in the body of Haskell 'case' expressions. data Pattern a = Pattern { _pattern :: !a, patternBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Pattern where liftEq = genericLiftEq instance Ord1 Pattern where liftCompare = genericLiftCompare instance Show1 Pattern where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Pattern - -- TODO: Implement Eval instance for Pattern instance Evaluatable Pattern -- | A let statement or local binding, like 'a as b' or 'let a = b'. data Let a = Let { letVariable :: !a, letValue :: !a, letBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Let where liftEq = genericLiftEq instance Ord1 Let where liftCompare = genericLiftCompare instance Show1 Let where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Let - instance Evaluatable Let where eval Let{..} = do name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm letVariable) @@ -101,14 +88,12 @@ instance Evaluatable Let where -- | Assignment to a variable or other lvalue. data Assignment a = Assignment { assignmentContext :: ![a], assignmentTarget :: !a, assignmentValue :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Assignment where liftEq = genericLiftEq instance Ord1 Assignment where liftCompare = genericLiftCompare instance Show1 Assignment where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Assignment - instance Evaluatable Assignment where eval Assignment{..} = do lhs <- subtermRef assignmentTarget @@ -130,28 +115,24 @@ instance Evaluatable Assignment where -- | Post increment operator (e.g. 1++ in Go, or i++ in C). newtype PostIncrement a = PostIncrement a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 PostIncrement where liftEq = genericLiftEq instance Ord1 PostIncrement where liftCompare = genericLiftCompare instance Show1 PostIncrement where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 PostIncrement - -- TODO: Implement Eval instance for PostIncrement instance Evaluatable PostIncrement -- | Post decrement operator (e.g. 1-- in Go, or i-- in C). newtype PostDecrement a = PostDecrement a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 PostDecrement where liftEq = genericLiftEq instance Ord1 PostDecrement where liftCompare = genericLiftCompare instance Show1 PostDecrement where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 PostDecrement - -- TODO: Implement Eval instance for PostDecrement instance Evaluatable PostDecrement @@ -159,181 +140,153 @@ instance Evaluatable PostDecrement -- Returns newtype Return a = Return a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Return where liftEq = genericLiftEq instance Ord1 Return where liftCompare = genericLiftCompare instance Show1 Return where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Return - instance Evaluatable Return where eval (Return x) = Rval <$> (subtermValue x >>= earlyReturn) newtype Yield a = Yield a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Yield where liftEq = genericLiftEq instance Ord1 Yield where liftCompare = genericLiftCompare instance Show1 Yield where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Yield - -- TODO: Implement Eval instance for Yield instance Evaluatable Yield newtype Break a = Break a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Break where liftEq = genericLiftEq instance Ord1 Break where liftCompare = genericLiftCompare instance Show1 Break where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Break - instance Evaluatable Break where eval (Break x) = Rval <$> (subtermValue x >>= throwBreak) newtype Continue a = Continue a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Continue where liftEq = genericLiftEq instance Ord1 Continue where liftCompare = genericLiftCompare instance Show1 Continue where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Continue - instance Evaluatable Continue where eval (Continue a) = Rval <$> (subtermValue a >>= throwContinue) newtype Retry a = Retry a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Retry where liftEq = genericLiftEq instance Ord1 Retry where liftCompare = genericLiftCompare instance Show1 Retry where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Retry - -- TODO: Implement Eval instance for Retry instance Evaluatable Retry newtype NoOp a = NoOp a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 NoOp where liftEq = genericLiftEq instance Ord1 NoOp where liftCompare = genericLiftCompare instance Show1 NoOp where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 NoOp - instance Evaluatable NoOp where eval _ = pure (Rval unit) -- Loops data For a = For { forBefore :: !a, forCondition :: !a, forStep :: !a, forBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 For where liftEq = genericLiftEq instance Ord1 For where liftCompare = genericLiftCompare instance Show1 For where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 For - instance Evaluatable For where eval (fmap subtermValue -> For before cond step body) = Rval <$> forLoop before cond step body data ForEach a = ForEach { forEachBinding :: !a, forEachSubject :: !a, forEachBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ForEach where liftEq = genericLiftEq instance Ord1 ForEach where liftCompare = genericLiftCompare instance Show1 ForEach where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 ForEach - -- TODO: Implement Eval instance for ForEach instance Evaluatable ForEach data While a = While { whileCondition :: !a, whileBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 While where liftEq = genericLiftEq instance Ord1 While where liftCompare = genericLiftCompare instance Show1 While where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 While - instance Evaluatable While where eval While{..} = Rval <$> while (subtermValue whileCondition) (subtermValue whileBody) data DoWhile a = DoWhile { doWhileCondition :: !a, doWhileBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 DoWhile where liftEq = genericLiftEq instance Ord1 DoWhile where liftCompare = genericLiftCompare instance Show1 DoWhile where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 DoWhile - instance Evaluatable DoWhile where eval DoWhile{..} = Rval <$> doWhile (subtermValue doWhileBody) (subtermValue doWhileCondition) -- Exception handling newtype Throw a = Throw a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Throw where liftEq = genericLiftEq instance Ord1 Throw where liftCompare = genericLiftCompare instance Show1 Throw where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Throw - -- TODO: Implement Eval instance for Throw instance Evaluatable Throw data Try a = Try { tryBody :: !a, tryCatch :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Try where liftEq = genericLiftEq instance Ord1 Try where liftCompare = genericLiftCompare instance Show1 Try where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Try - -- TODO: Implement Eval instance for Try instance Evaluatable Try data Catch a = Catch { catchException :: !a, catchBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Catch where liftEq = genericLiftEq instance Ord1 Catch where liftCompare = genericLiftCompare instance Show1 Catch where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Catch - -- TODO: Implement Eval instance for Catch instance Evaluatable Catch newtype Finally a = Finally a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Finally where liftEq = genericLiftEq instance Ord1 Finally where liftCompare = genericLiftCompare instance Show1 Finally where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Finally - -- TODO: Implement Eval instance for Finally instance Evaluatable Finally @@ -342,41 +295,34 @@ instance Evaluatable Finally -- | ScopeEntry (e.g. `BEGIN {}` block in Ruby or Perl). newtype ScopeEntry a = ScopeEntry [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ScopeEntry where liftEq = genericLiftEq instance Ord1 ScopeEntry where liftCompare = genericLiftCompare instance Show1 ScopeEntry where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 ScopeEntry - -- TODO: Implement Eval instance for ScopeEntry instance Evaluatable ScopeEntry -- | ScopeExit (e.g. `END {}` block in Ruby or Perl). newtype ScopeExit a = ScopeExit [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ScopeExit where liftEq = genericLiftEq instance Ord1 ScopeExit where liftCompare = genericLiftCompare instance Show1 ScopeExit where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 ScopeExit - -- TODO: Implement Eval instance for ScopeExit instance Evaluatable ScopeExit -- | HashBang line (e.g. `#!/usr/bin/env node`) newtype HashBang a = HashBang 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 HashBang where liftEq = genericLiftEq instance Ord1 HashBang where liftCompare = genericLiftCompare instance Show1 HashBang where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 HashBang where - toJSONFields1 (HashBang f) = noChildren [ "contents" .= unpack f ] - -- TODO: Implement Eval instance for HashBang instance Evaluatable HashBang diff --git a/src/Data/Syntax/Type.hs b/src/Data/Syntax/Type.hs index 02f269eaf..9ba9ca940 100644 --- a/src/Data/Syntax/Type.hs +++ b/src/Data/Syntax/Type.hs @@ -7,145 +7,123 @@ import Diffing.Algorithm import Prologue hiding (Map) data Array a = Array { arraySize :: Maybe a, arrayElementType :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Array where liftEq = genericLiftEq instance Ord1 Array where liftCompare = genericLiftCompare instance Show1 Array where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Array - -- TODO: Implement Eval instance for Array instance Evaluatable Array -- TODO: What about type variables? re: FreeVariables1 data Annotation a = Annotation { annotationSubject :: !a, annotationType :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Annotation where liftEq = genericLiftEq instance Ord1 Annotation where liftCompare = genericLiftCompare instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Annotation where - -- TODO: Specialize Evaluatable for Type to unify the inferred type of the subject with the specified type instance Evaluatable Annotation where eval Annotation{annotationSubject = Subterm _ action} = action data Function a = Function { functionParameters :: [a], functionReturn :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Function where liftEq = genericLiftEq instance Ord1 Function where liftCompare = genericLiftCompare instance Show1 Function where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Function - -- TODO: Implement Eval instance for Function instance Evaluatable Function newtype Interface a = Interface [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Interface where liftEq = genericLiftEq instance Ord1 Interface where liftCompare = genericLiftCompare instance Show1 Interface where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Interface - -- TODO: Implement Eval instance for Interface instance Evaluatable Interface data Map a = Map { mapKeyType :: a, mapElementType :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Map where liftEq = genericLiftEq instance Ord1 Map where liftCompare = genericLiftCompare instance Show1 Map where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Map - -- TODO: Implement Eval instance for Map instance Evaluatable Map newtype Parenthesized a = Parenthesized a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Parenthesized where liftEq = genericLiftEq instance Ord1 Parenthesized where liftCompare = genericLiftCompare instance Show1 Parenthesized where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Parenthesized - -- TODO: Implement Eval instance for Parenthesized instance Evaluatable Parenthesized newtype Pointer a = Pointer a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Pointer where liftEq = genericLiftEq instance Ord1 Pointer where liftCompare = genericLiftCompare instance Show1 Pointer where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Pointer - -- TODO: Implement Eval instance for Pointer instance Evaluatable Pointer newtype Product a = Product [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Product where liftEq = genericLiftEq instance Ord1 Product where liftCompare = genericLiftCompare instance Show1 Product where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Product - -- TODO: Implement Eval instance for Product instance Evaluatable Product data Readonly a = Readonly - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Readonly where liftEq = genericLiftEq instance Ord1 Readonly where liftCompare = genericLiftCompare instance Show1 Readonly where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Readonly - -- TODO: Implement Eval instance for Readonly instance Evaluatable Readonly newtype Slice a = Slice a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Slice where liftEq = genericLiftEq instance Ord1 Slice where liftCompare = genericLiftCompare instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Slice - -- TODO: Implement Eval instance for Slice instance Evaluatable Slice newtype TypeParameters a = TypeParameters [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TypeParameters where liftEq = genericLiftEq instance Ord1 TypeParameters where liftCompare = genericLiftCompare instance Show1 TypeParameters where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 TypeParameters - -- TODO: Implement Eval instance for TypeParameters instance Evaluatable TypeParameters diff --git a/src/Language/Go/Syntax.hs b/src/Language/Go/Syntax.hs index 9b47e4894..eb38f92f3 100644 --- a/src/Language/Go/Syntax.hs +++ b/src/Language/Go/Syntax.hs @@ -57,14 +57,12 @@ resolveGoImport (ImportPath path NonRelative) = do -- -- If the list of symbols is empty copy everything to the calling environment. data Import a = Import { importFrom :: ImportPath, importWildcardToken :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Import where liftEq = genericLiftEq instance Ord1 Import where liftCompare = genericLiftCompare instance Show1 Import where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Import - instance Evaluatable Import where eval (Import importPath _) = do paths <- resolveGoImport importPath @@ -79,14 +77,12 @@ instance Evaluatable Import where -- -- If the list of symbols is empty copy and qualify everything to the calling environment. data QualifiedImport a = QualifiedImport { qualifiedImportFrom :: !ImportPath, qualifiedImportAlias :: !a} - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 QualifiedImport where liftEq = genericLiftEq instance Ord1 QualifiedImport where liftCompare = genericLiftCompare instance Show1 QualifiedImport where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 QualifiedImport - instance Evaluatable QualifiedImport where eval (QualifiedImport importPath aliasTerm) = do paths <- resolveGoImport importPath @@ -101,14 +97,12 @@ instance Evaluatable QualifiedImport where -- | Side effect only imports (no symbols made available to the calling environment). data SideEffectImport a = SideEffectImport { sideEffectImportFrom :: !ImportPath, sideEffectImportToken :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 SideEffectImport where liftEq = genericLiftEq instance Ord1 SideEffectImport where liftCompare = genericLiftCompare instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 SideEffectImport - instance Evaluatable SideEffectImport where eval (SideEffectImport importPath _) = do paths <- resolveGoImport importPath @@ -118,74 +112,62 @@ instance Evaluatable SideEffectImport where -- A composite literal in Go data Composite a = Composite { compositeType :: !a, compositeElement :: !a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Composite where liftEq = genericLiftEq instance Ord1 Composite where liftCompare = genericLiftCompare instance Show1 Composite where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Composite - -- TODO: Implement Eval instance for Composite instance Evaluatable Composite -- | A default pattern in a Go select or switch statement (e.g. `switch { default: s() }`). newtype DefaultPattern a = DefaultPattern { defaultPatternBody :: a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 DefaultPattern where liftEq = genericLiftEq instance Ord1 DefaultPattern where liftCompare = genericLiftCompare instance Show1 DefaultPattern where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 DefaultPattern - -- TODO: Implement Eval instance for DefaultPattern instance Evaluatable DefaultPattern -- | A defer statement in Go (e.g. `defer x()`). newtype Defer a = Defer { deferBody :: a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Defer where liftEq = genericLiftEq instance Ord1 Defer where liftCompare = genericLiftCompare instance Show1 Defer where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Defer - -- TODO: Implement Eval instance for Defer instance Evaluatable Defer -- | A go statement (i.e. go routine) in Go (e.g. `go x()`). newtype Go a = Go { goBody :: a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Go where liftEq = genericLiftEq instance Ord1 Go where liftCompare = genericLiftCompare instance Show1 Go where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Go - -- TODO: Implement Eval instance for Go instance Evaluatable Go -- | A label statement in Go (e.g. `label:continue`). data Label a = Label { _labelName :: !a, labelStatement :: !a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Label where liftEq = genericLiftEq instance Ord1 Label where liftCompare = genericLiftCompare instance Show1 Label where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Label - -- TODO: Implement Eval instance for Label instance Evaluatable Label -- | A rune literal in Go (e.g. `'⌘'`). newtype Rune a = Rune { _runeLiteral :: ByteString } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Rune + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) -- TODO: Implement Eval instance for Rune instance Evaluatable Rune @@ -196,9 +178,7 @@ instance Show1 Rune where liftShowsPrec = genericLiftShowsPrec -- | A select statement in Go (e.g. `select { case x := <-c: x() }` where each case is a send or receive operation on channels). newtype Select a = Select { selectCases :: a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Select + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) -- TODO: Implement Eval instance for Select instance Evaluatable Select @@ -209,144 +189,122 @@ instance Show1 Select where liftShowsPrec = genericLiftShowsPrec -- | A send statement in Go (e.g. `channel <- value`). data Send a = Send { sendReceiver :: !a, sendValue :: !a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Send where liftEq = genericLiftEq instance Ord1 Send where liftCompare = genericLiftCompare instance Show1 Send where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Send - -- TODO: Implement Eval instance for Send instance Evaluatable Send -- | A slice expression in Go (e.g. `a[1:4:3]` where a is a list, 1 is the low bound, 4 is the high bound, and 3 is the max capacity). data Slice a = Slice { sliceName :: !a, sliceLow :: !a, sliceHigh :: !a, sliceCapacity :: !a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Slice where liftEq = genericLiftEq instance Ord1 Slice where liftCompare = genericLiftCompare instance Show1 Slice where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Slice - -- TODO: Implement Eval instance for Slice instance Evaluatable Slice -- | A type switch statement in Go (e.g. `switch x.(type) { // cases }`). data TypeSwitch a = TypeSwitch { typeSwitchSubject :: !a, typeSwitchCases :: !a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TypeSwitch where liftEq = genericLiftEq instance Ord1 TypeSwitch where liftCompare = genericLiftCompare instance Show1 TypeSwitch where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 TypeSwitch - -- TODO: Implement Eval instance for TypeSwitch instance Evaluatable TypeSwitch -- | A type switch guard statement in a Go type switch statement (e.g. `switch i := x.(type) { // cases}`). newtype TypeSwitchGuard a = TypeSwitchGuard { typeSwitchGuardSubject :: a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TypeSwitchGuard where liftEq = genericLiftEq instance Ord1 TypeSwitchGuard where liftCompare = genericLiftCompare instance Show1 TypeSwitchGuard where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 TypeSwitchGuard - -- TODO: Implement Eval instance for TypeSwitchGuard instance Evaluatable TypeSwitchGuard -- | A receive statement in a Go select statement (e.g. `case value := <-channel` ) data Receive a = Receive { receiveSubject :: !a, receiveExpression :: !a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Receive where liftEq = genericLiftEq instance Ord1 Receive where liftCompare = genericLiftCompare instance Show1 Receive where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Receive - -- TODO: Implement Eval instance for Receive instance Evaluatable Receive -- | A receive operator unary expression in Go (e.g. `<-channel` ) newtype ReceiveOperator a = ReceiveOperator a - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ReceiveOperator where liftEq = genericLiftEq instance Ord1 ReceiveOperator where liftCompare = genericLiftCompare instance Show1 ReceiveOperator where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 ReceiveOperator - -- TODO: Implement Eval instance for ReceiveOperator instance Evaluatable ReceiveOperator -- | A field declaration in a Go struct type declaration. data Field a = Field { fieldContext :: ![a], fieldName :: !a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Field where liftEq = genericLiftEq instance Ord1 Field where liftCompare = genericLiftCompare instance Show1 Field where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Field - -- TODO: Implement Eval instance for Field instance Evaluatable Field data Package a = Package { packageName :: !a, packageContents :: ![a] } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Package where liftEq = genericLiftEq instance Ord1 Package where liftCompare = genericLiftCompare instance Show1 Package where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Package - instance Evaluatable Package where eval (Package _ xs) = eval xs -- | A type assertion in Go (e.g. `x.(T)` where the value of `x` is not nil and is of type `T`). data TypeAssertion a = TypeAssertion { typeAssertionSubject :: !a, typeAssertionType :: !a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TypeAssertion where liftEq = genericLiftEq instance Ord1 TypeAssertion where liftCompare = genericLiftCompare instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 TypeAssertion - -- TODO: Implement Eval instance for TypeAssertion instance Evaluatable TypeAssertion -- | A type conversion expression in Go (e.g. `T(x)` where `T` is a type and `x` is an expression that can be converted to type `T`). data TypeConversion a = TypeConversion { typeConversionType :: !a, typeConversionSubject :: !a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TypeConversion where liftEq = genericLiftEq instance Ord1 TypeConversion where liftCompare = genericLiftCompare instance Show1 TypeConversion where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 TypeConversion - -- TODO: Implement Eval instance for TypeConversion instance Evaluatable TypeConversion -- | Variadic arguments and parameters in Go (e.g. parameter: `param ...Type`, argument: `Type...`). data Variadic a = Variadic { variadicContext :: [a], variadicIdentifier :: a } - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Variadic where liftEq = genericLiftEq instance Ord1 Variadic where liftCompare = genericLiftCompare instance Show1 Variadic where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Variadic - -- TODO: Implement Eval instance for Variadic instance Evaluatable Variadic diff --git a/src/Language/Go/Type.hs b/src/Language/Go/Type.hs index c78a2b6bd..40f4acaeb 100644 --- a/src/Language/Go/Type.hs +++ b/src/Language/Go/Type.hs @@ -8,39 +8,33 @@ import Diffing.Algorithm -- | A Bidirectional channel in Go (e.g. `chan`). newtype BidirectionalChannel a = BidirectionalChannel a - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 BidirectionalChannel where liftEq = genericLiftEq instance Ord1 BidirectionalChannel where liftCompare = genericLiftCompare instance Show1 BidirectionalChannel where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 BidirectionalChannel - -- TODO: Implement Eval instance for BidirectionalChannel instance Evaluatable BidirectionalChannel -- | A Receive channel in Go (e.g. `<-chan`). newtype ReceiveChannel a = ReceiveChannel a - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ReceiveChannel where liftEq = genericLiftEq instance Ord1 ReceiveChannel where liftCompare = genericLiftCompare instance Show1 ReceiveChannel where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 ReceiveChannel - -- TODO: Implement Eval instance for ReceiveChannel instance Evaluatable ReceiveChannel -- | A Send channel in Go (e.g. `chan<-`). newtype SendChannel a = SendChannel a - deriving (Diffable, Eq, FreeVariables1, Declarations1, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 SendChannel where liftEq = genericLiftEq instance Ord1 SendChannel where liftCompare = genericLiftCompare instance Show1 SendChannel where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 SendChannel - -- TODO: Implement Eval instance for SendChannel instance Evaluatable SendChannel diff --git a/src/Language/Haskell/Syntax.hs b/src/Language/Haskell/Syntax.hs index 45ee637d5..87f260d5e 100644 --- a/src/Language/Haskell/Syntax.hs +++ b/src/Language/Haskell/Syntax.hs @@ -11,12 +11,10 @@ data Module a = Module { moduleIdentifier :: !a , moduleExports :: ![a] , moduleStatements :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Module where liftEq = genericLiftEq instance Ord1 Module where liftCompare = genericLiftCompare instance Show1 Module where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Module - instance Evaluatable Module where diff --git a/src/Language/Markdown/Syntax.hs b/src/Language/Markdown/Syntax.hs index a4937751b..59a4b4b2a 100644 --- a/src/Language/Markdown/Syntax.hs +++ b/src/Language/Markdown/Syntax.hs @@ -2,14 +2,11 @@ module Language.Markdown.Syntax where import Prologue hiding (Text) -import Data.ByteString.Char8 (unpack) import Data.JSON.Fields import Diffing.Algorithm newtype Document a = Document [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Document + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 Document where liftEq = genericLiftEq instance Ord1 Document where liftCompare = genericLiftCompare @@ -19,91 +16,70 @@ instance Show1 Document where liftShowsPrec = genericLiftShowsPrec -- Block elements newtype Paragraph a = Paragraph [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Paragraph + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 Paragraph where liftEq = genericLiftEq instance Ord1 Paragraph where liftCompare = genericLiftCompare instance Show1 Paragraph where liftShowsPrec = genericLiftShowsPrec data Heading a = Heading { headingLevel :: Int, headingContent :: [a], sectionContent :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Heading + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 Heading where liftEq = genericLiftEq instance Ord1 Heading where liftCompare = genericLiftCompare instance Show1 Heading where liftShowsPrec = genericLiftShowsPrec newtype UnorderedList a = UnorderedList [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 UnorderedList + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 UnorderedList where liftEq = genericLiftEq instance Ord1 UnorderedList where liftCompare = genericLiftCompare instance Show1 UnorderedList where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 OrderedList - newtype OrderedList a = OrderedList [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 OrderedList where liftEq = genericLiftEq instance Ord1 OrderedList where liftCompare = genericLiftCompare instance Show1 OrderedList where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 BlockQuote - newtype BlockQuote a = BlockQuote [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 BlockQuote where liftEq = genericLiftEq instance Ord1 BlockQuote where liftCompare = genericLiftCompare instance Show1 BlockQuote where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 ThematicBreak - data ThematicBreak a = ThematicBreak - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 ThematicBreak where liftEq = genericLiftEq instance Ord1 ThematicBreak where liftCompare = genericLiftCompare instance Show1 ThematicBreak where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 HTMLBlock where - toJSONFields1 (HTMLBlock b) = noChildren [ "asString" .= unpack b ] - newtype HTMLBlock a = HTMLBlock ByteString - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 HTMLBlock where liftEq = genericLiftEq instance Ord1 HTMLBlock where liftCompare = genericLiftCompare instance Show1 HTMLBlock where liftShowsPrec = genericLiftShowsPrec newtype Table a = Table [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Table + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 Table where liftEq = genericLiftEq instance Ord1 Table where liftCompare = genericLiftCompare instance Show1 Table where liftShowsPrec = genericLiftShowsPrec newtype TableRow a = TableRow [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 TableRow + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 TableRow where liftEq = genericLiftEq instance Ord1 TableRow where liftCompare = genericLiftCompare instance Show1 TableRow where liftShowsPrec = genericLiftShowsPrec newtype TableCell a = TableCell [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 TableCell + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 TableCell where liftEq = genericLiftEq instance Ord1 TableCell where liftCompare = genericLiftCompare @@ -113,76 +89,56 @@ instance Show1 TableCell where liftShowsPrec = genericLiftShowsPrec -- Inline elements newtype Strong a = Strong [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Strong + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 Strong where liftEq = genericLiftEq instance Ord1 Strong where liftCompare = genericLiftCompare instance Show1 Strong where liftShowsPrec = genericLiftShowsPrec newtype Emphasis a = Emphasis [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Emphasis + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 Emphasis where liftEq = genericLiftEq instance Ord1 Emphasis where liftCompare = genericLiftCompare instance Show1 Emphasis where liftShowsPrec = genericLiftShowsPrec newtype Text a = Text ByteString - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Text where - toJSONFields1 (Text s) = noChildren ["asString" .= unpack s ] + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 Text where liftEq = genericLiftEq instance Ord1 Text where liftCompare = genericLiftCompare instance Show1 Text where liftShowsPrec = genericLiftShowsPrec data Link a = Link { linkURL :: ByteString, linkTitle :: Maybe ByteString } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - --- TODO: Better ToJSONFields1 instance -instance ToJSONFields1 Link + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 Link where liftEq = genericLiftEq instance Ord1 Link where liftCompare = genericLiftCompare instance Show1 Link where liftShowsPrec = genericLiftShowsPrec data Image a = Image { imageURL :: ByteString, imageTitle :: Maybe ByteString } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - --- TODO: Better ToJSONFields1 instance -instance ToJSONFields1 Image + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 Image where liftEq = genericLiftEq instance Ord1 Image where liftCompare = genericLiftCompare instance Show1 Image where liftShowsPrec = genericLiftShowsPrec data Code a = Code { codeLanguage :: Maybe ByteString, codeContent :: ByteString } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - --- TODO: Better ToJSONFields1 instance -instance ToJSONFields1 Code + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 Code where liftEq = genericLiftEq instance Ord1 Code where liftCompare = genericLiftCompare instance Show1 Code where liftShowsPrec = genericLiftShowsPrec data LineBreak a = LineBreak - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 LineBreak + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 LineBreak where liftEq = genericLiftEq instance Ord1 LineBreak where liftCompare = genericLiftCompare instance Show1 LineBreak where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Strikethrough - newtype Strikethrough a = Strikethrough [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, ToJSONFields1) instance Eq1 Strikethrough where liftEq = genericLiftEq instance Ord1 Strikethrough where liftCompare = genericLiftCompare diff --git a/src/Language/PHP/Syntax.hs b/src/Language/PHP/Syntax.hs index 66d023d6e..ecfa90d76 100644 --- a/src/Language/PHP/Syntax.hs +++ b/src/Language/PHP/Syntax.hs @@ -12,10 +12,7 @@ import Prelude hiding (fail) import Prologue hiding (Text) newtype Text a = Text ByteString - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Text where - toJSONFields1 (Text t) = noChildren ["asString" .= BC.unpack t] + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Text where liftEq = genericLiftEq instance Ord1 Text where liftCompare = genericLiftCompare @@ -24,9 +21,7 @@ instance Evaluatable Text newtype VariableName a = VariableName a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 VariableName + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 VariableName where liftEq = genericLiftEq instance Ord1 VariableName where liftCompare = genericLiftCompare @@ -74,61 +69,51 @@ include pathTerm f = do pure (Rval v) newtype Require a = Require a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Require where liftEq = genericLiftEq instance Ord1 Require where liftCompare = genericLiftCompare instance Show1 Require where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Require - instance Evaluatable Require where eval (Require path) = include path load newtype RequireOnce a = RequireOnce a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 RequireOnce where liftEq = genericLiftEq instance Ord1 RequireOnce where liftCompare = genericLiftCompare instance Show1 RequireOnce where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 RequireOnce - instance Evaluatable RequireOnce where eval (RequireOnce path) = include path require newtype Include a = Include a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Include where liftEq = genericLiftEq instance Ord1 Include where liftCompare = genericLiftCompare instance Show1 Include where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Include - instance Evaluatable Include where eval (Include path) = include path load newtype IncludeOnce a = IncludeOnce a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 IncludeOnce where liftEq = genericLiftEq instance Ord1 IncludeOnce where liftCompare = genericLiftCompare instance Show1 IncludeOnce where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 IncludeOnce - instance Evaluatable IncludeOnce where eval (IncludeOnce path) = include path require newtype ArrayElement a = ArrayElement a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 ArrayElement + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ArrayElement where liftEq = genericLiftEq instance Ord1 ArrayElement where liftCompare = genericLiftCompare @@ -136,9 +121,7 @@ instance Show1 ArrayElement where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ArrayElement newtype GlobalDeclaration a = GlobalDeclaration [a] - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 GlobalDeclaration + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 GlobalDeclaration where liftEq = genericLiftEq instance Ord1 GlobalDeclaration where liftCompare = genericLiftCompare @@ -146,9 +129,7 @@ instance Show1 GlobalDeclaration where liftShowsPrec = genericLiftShowsPrec instance Evaluatable GlobalDeclaration newtype SimpleVariable a = SimpleVariable a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 SimpleVariable + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 SimpleVariable where liftEq = genericLiftEq instance Ord1 SimpleVariable where liftCompare = genericLiftCompare @@ -158,9 +139,7 @@ instance Evaluatable SimpleVariable -- | TODO: Unify with TypeScript's PredefinedType newtype CastType a = CastType { _castType :: ByteString } - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 CastType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 CastType where liftEq = genericLiftEq instance Ord1 CastType where liftCompare = genericLiftCompare @@ -168,9 +147,7 @@ instance Show1 CastType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable CastType newtype ErrorControl a = ErrorControl a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 ErrorControl + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ErrorControl where liftEq = genericLiftEq instance Ord1 ErrorControl where liftCompare = genericLiftCompare @@ -178,9 +155,7 @@ instance Show1 ErrorControl where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ErrorControl newtype Clone a = Clone a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Clone + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Clone where liftEq = genericLiftEq instance Ord1 Clone where liftCompare = genericLiftCompare @@ -188,9 +163,7 @@ instance Show1 Clone where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Clone newtype ShellCommand a = ShellCommand ByteString - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 ShellCommand + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ShellCommand where liftEq = genericLiftEq instance Ord1 ShellCommand where liftCompare = genericLiftCompare @@ -199,9 +172,7 @@ instance Evaluatable ShellCommand -- | TODO: Combine with TypeScript update expression. newtype Update a = Update { _updateSubject :: a } - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Update + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Update where liftEq = genericLiftEq instance Ord1 Update where liftCompare = genericLiftCompare @@ -209,9 +180,7 @@ instance Show1 Update where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Update newtype NewVariable a = NewVariable [a] - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 NewVariable + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 NewVariable where liftEq = genericLiftEq instance Ord1 NewVariable where liftCompare = genericLiftCompare @@ -219,9 +188,7 @@ instance Show1 NewVariable where liftShowsPrec = genericLiftShowsPrec instance Evaluatable NewVariable newtype RelativeScope a = RelativeScope ByteString - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 RelativeScope + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 RelativeScope where liftEq = genericLiftEq instance Ord1 RelativeScope where liftCompare = genericLiftCompare @@ -229,9 +196,7 @@ instance Show1 RelativeScope where liftShowsPrec = genericLiftShowsPrec instance Evaluatable RelativeScope data QualifiedName a = QualifiedName !a !a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 QualifiedName + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 QualifiedName where liftEq = genericLiftEq instance Ord1 QualifiedName where liftCompare = genericLiftCompare @@ -241,9 +206,7 @@ instance Evaluatable QualifiedName where eval (fmap subtermValue -> QualifiedName name iden) = Rval <$> evaluateInScopedEnv name iden newtype NamespaceName a = NamespaceName (NonEmpty a) - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 NamespaceName + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Hashable1 NamespaceName where liftHashWithSalt = foldl instance Eq1 NamespaceName where liftEq = genericLiftEq @@ -254,9 +217,7 @@ instance Evaluatable NamespaceName where eval (NamespaceName xs) = Rval <$> foldl1 evaluateInScopedEnv (fmap subtermValue xs) newtype ConstDeclaration a = ConstDeclaration [a] - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 ConstDeclaration + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ConstDeclaration where liftEq = genericLiftEq instance Ord1 ConstDeclaration where liftCompare = genericLiftCompare @@ -264,9 +225,7 @@ instance Show1 ConstDeclaration where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ConstDeclaration data ClassConstDeclaration a = ClassConstDeclaration a [a] - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 ClassConstDeclaration + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ClassConstDeclaration where liftEq = genericLiftEq instance Ord1 ClassConstDeclaration where liftCompare = genericLiftCompare @@ -274,9 +233,7 @@ instance Show1 ClassConstDeclaration where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ClassConstDeclaration newtype ClassInterfaceClause a = ClassInterfaceClause [a] - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 ClassInterfaceClause + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ClassInterfaceClause where liftEq = genericLiftEq instance Ord1 ClassInterfaceClause where liftCompare = genericLiftCompare @@ -284,9 +241,7 @@ instance Show1 ClassInterfaceClause where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ClassInterfaceClause newtype ClassBaseClause a = ClassBaseClause a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 ClassBaseClause + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ClassBaseClause where liftEq = genericLiftEq instance Ord1 ClassBaseClause where liftCompare = genericLiftCompare @@ -295,9 +250,7 @@ instance Evaluatable ClassBaseClause newtype UseClause a = UseClause [a] - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 UseClause + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 UseClause where liftEq = genericLiftEq instance Ord1 UseClause where liftCompare = genericLiftCompare @@ -305,9 +258,7 @@ instance Show1 UseClause where liftShowsPrec = genericLiftShowsPrec instance Evaluatable UseClause newtype ReturnType a = ReturnType a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 ReturnType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ReturnType where liftEq = genericLiftEq instance Ord1 ReturnType where liftCompare = genericLiftCompare @@ -315,9 +266,7 @@ instance Show1 ReturnType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ReturnType newtype TypeDeclaration a = TypeDeclaration a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 TypeDeclaration + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TypeDeclaration where liftEq = genericLiftEq instance Ord1 TypeDeclaration where liftCompare = genericLiftCompare @@ -325,9 +274,7 @@ instance Show1 TypeDeclaration where liftShowsPrec = genericLiftShowsPrec instance Evaluatable TypeDeclaration newtype BaseTypeDeclaration a = BaseTypeDeclaration a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 BaseTypeDeclaration + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 BaseTypeDeclaration where liftEq = genericLiftEq instance Ord1 BaseTypeDeclaration where liftCompare = genericLiftCompare @@ -335,9 +282,7 @@ instance Show1 BaseTypeDeclaration where liftShowsPrec = genericLiftShowsPrec instance Evaluatable BaseTypeDeclaration newtype ScalarType a = ScalarType ByteString - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 ScalarType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ScalarType where liftEq = genericLiftEq instance Ord1 ScalarType where liftCompare = genericLiftCompare @@ -345,9 +290,7 @@ instance Show1 ScalarType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ScalarType newtype EmptyIntrinsic a = EmptyIntrinsic a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 EmptyIntrinsic + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 EmptyIntrinsic where liftEq = genericLiftEq instance Ord1 EmptyIntrinsic where liftCompare = genericLiftCompare @@ -355,9 +298,7 @@ instance Show1 EmptyIntrinsic where liftShowsPrec = genericLiftShowsPrec instance Evaluatable EmptyIntrinsic newtype ExitIntrinsic a = ExitIntrinsic a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 ExitIntrinsic + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ExitIntrinsic where liftEq = genericLiftEq instance Ord1 ExitIntrinsic where liftCompare = genericLiftCompare @@ -365,9 +306,7 @@ instance Show1 ExitIntrinsic where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ExitIntrinsic newtype IssetIntrinsic a = IssetIntrinsic a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 IssetIntrinsic + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 IssetIntrinsic where liftEq = genericLiftEq instance Ord1 IssetIntrinsic where liftCompare = genericLiftCompare @@ -375,9 +314,7 @@ instance Show1 IssetIntrinsic where liftShowsPrec = genericLiftShowsPrec instance Evaluatable IssetIntrinsic newtype EvalIntrinsic a = EvalIntrinsic a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 EvalIntrinsic + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 EvalIntrinsic where liftEq = genericLiftEq instance Ord1 EvalIntrinsic where liftCompare = genericLiftCompare @@ -385,9 +322,7 @@ instance Show1 EvalIntrinsic where liftShowsPrec = genericLiftShowsPrec instance Evaluatable EvalIntrinsic newtype PrintIntrinsic a = PrintIntrinsic a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 PrintIntrinsic + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 PrintIntrinsic where liftEq = genericLiftEq instance Ord1 PrintIntrinsic where liftCompare = genericLiftCompare @@ -395,9 +330,7 @@ instance Show1 PrintIntrinsic where liftShowsPrec = genericLiftShowsPrec instance Evaluatable PrintIntrinsic newtype NamespaceAliasingClause a = NamespaceAliasingClause a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 NamespaceAliasingClause + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 NamespaceAliasingClause where liftEq = genericLiftEq instance Ord1 NamespaceAliasingClause where liftCompare = genericLiftCompare @@ -405,9 +338,7 @@ instance Show1 NamespaceAliasingClause where liftShowsPrec = genericLiftShowsPre instance Evaluatable NamespaceAliasingClause newtype NamespaceUseDeclaration a = NamespaceUseDeclaration [a] - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 NamespaceUseDeclaration + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 NamespaceUseDeclaration where liftEq = genericLiftEq instance Ord1 NamespaceUseDeclaration where liftCompare = genericLiftCompare @@ -415,9 +346,7 @@ instance Show1 NamespaceUseDeclaration where liftShowsPrec = genericLiftShowsPre instance Evaluatable NamespaceUseDeclaration newtype NamespaceUseClause a = NamespaceUseClause [a] - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 NamespaceUseClause + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 NamespaceUseClause where liftEq = genericLiftEq instance Ord1 NamespaceUseClause where liftCompare = genericLiftCompare @@ -425,9 +354,7 @@ instance Show1 NamespaceUseClause where liftShowsPrec = genericLiftShowsPrec instance Evaluatable NamespaceUseClause newtype NamespaceUseGroupClause a = NamespaceUseGroupClause [a] - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 NamespaceUseGroupClause + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 NamespaceUseGroupClause where liftEq = genericLiftEq instance Ord1 NamespaceUseGroupClause where liftCompare = genericLiftCompare @@ -435,14 +362,12 @@ instance Show1 NamespaceUseGroupClause where liftShowsPrec = genericLiftShowsPre instance Evaluatable NamespaceUseGroupClause data Namespace a = Namespace { namespaceName :: a, namespaceBody :: a } - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Namespace where liftEq = genericLiftEq instance Ord1 Namespace where liftCompare = genericLiftCompare instance Show1 Namespace where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Namespace - instance Evaluatable Namespace where eval Namespace{..} = Rval <$> go names where @@ -456,9 +381,7 @@ instance Evaluatable Namespace where go xs <* makeNamespace name addr Nothing data TraitDeclaration a = TraitDeclaration { traitName :: a, traitStatements :: [a] } - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 TraitDeclaration + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TraitDeclaration where liftEq = genericLiftEq instance Ord1 TraitDeclaration where liftCompare = genericLiftCompare @@ -466,9 +389,7 @@ instance Show1 TraitDeclaration where liftShowsPrec = genericLiftShowsPrec instance Evaluatable TraitDeclaration data AliasAs a = AliasAs { aliasAsName :: a, aliasAsModifier :: a, aliasAsClause :: a } - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 AliasAs + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 AliasAs where liftEq = genericLiftEq instance Ord1 AliasAs where liftCompare = genericLiftCompare @@ -476,9 +397,7 @@ instance Show1 AliasAs where liftShowsPrec = genericLiftShowsPrec instance Evaluatable AliasAs data InsteadOf a = InsteadOf a a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 InsteadOf + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 InsteadOf where liftEq = genericLiftEq instance Ord1 InsteadOf where liftCompare = genericLiftCompare @@ -486,9 +405,7 @@ instance Show1 InsteadOf where liftShowsPrec = genericLiftShowsPrec instance Evaluatable InsteadOf newtype TraitUseSpecification a = TraitUseSpecification [a] - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 TraitUseSpecification + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TraitUseSpecification where liftEq = genericLiftEq instance Ord1 TraitUseSpecification where liftCompare = genericLiftCompare @@ -496,9 +413,7 @@ instance Show1 TraitUseSpecification where liftShowsPrec = genericLiftShowsPrec instance Evaluatable TraitUseSpecification data TraitUseClause a = TraitUseClause [a] a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 TraitUseClause + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TraitUseClause where liftEq = genericLiftEq instance Ord1 TraitUseClause where liftCompare = genericLiftCompare @@ -506,9 +421,7 @@ instance Show1 TraitUseClause where liftShowsPrec = genericLiftShowsPrec instance Evaluatable TraitUseClause data DestructorDeclaration a = DestructorDeclaration [a] a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 DestructorDeclaration + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 DestructorDeclaration where liftEq = genericLiftEq instance Ord1 DestructorDeclaration where liftCompare = genericLiftCompare @@ -516,9 +429,7 @@ instance Show1 DestructorDeclaration where liftShowsPrec = genericLiftShowsPrec instance Evaluatable DestructorDeclaration newtype Static a = Static ByteString - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Static + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Static where liftEq = genericLiftEq instance Ord1 Static where liftCompare = genericLiftCompare @@ -526,9 +437,7 @@ instance Show1 Static where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Static newtype ClassModifier a = ClassModifier ByteString - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 ClassModifier + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ClassModifier where liftEq = genericLiftEq instance Ord1 ClassModifier where liftCompare = genericLiftCompare @@ -536,9 +445,7 @@ instance Show1 ClassModifier where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ClassModifier data ConstructorDeclaration a = ConstructorDeclaration [a] [a] a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 ConstructorDeclaration + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ConstructorDeclaration where liftEq = genericLiftEq instance Ord1 ConstructorDeclaration where liftCompare = genericLiftCompare @@ -546,9 +453,7 @@ instance Show1 ConstructorDeclaration where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ConstructorDeclaration data PropertyDeclaration a = PropertyDeclaration a [a] - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 PropertyDeclaration + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 PropertyDeclaration where liftEq = genericLiftEq instance Ord1 PropertyDeclaration where liftCompare = genericLiftCompare @@ -556,9 +461,7 @@ instance Show1 PropertyDeclaration where liftShowsPrec = genericLiftShowsPrec instance Evaluatable PropertyDeclaration data PropertyModifier a = PropertyModifier a a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 PropertyModifier + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 PropertyModifier where liftEq = genericLiftEq instance Ord1 PropertyModifier where liftCompare = genericLiftCompare @@ -566,9 +469,7 @@ instance Show1 PropertyModifier where liftShowsPrec = genericLiftShowsPrec instance Evaluatable PropertyModifier data InterfaceDeclaration a = InterfaceDeclaration a a [a] - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 InterfaceDeclaration + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 InterfaceDeclaration where liftEq = genericLiftEq instance Ord1 InterfaceDeclaration where liftCompare = genericLiftCompare @@ -576,9 +477,7 @@ instance Show1 InterfaceDeclaration where liftShowsPrec = genericLiftShowsPrec instance Evaluatable InterfaceDeclaration newtype InterfaceBaseClause a = InterfaceBaseClause [a] - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 InterfaceBaseClause + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 InterfaceBaseClause where liftEq = genericLiftEq instance Ord1 InterfaceBaseClause where liftCompare = genericLiftCompare @@ -586,9 +485,7 @@ instance Show1 InterfaceBaseClause where liftShowsPrec = genericLiftShowsPrec instance Evaluatable InterfaceBaseClause newtype Echo a = Echo a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Echo + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Echo where liftEq = genericLiftEq instance Ord1 Echo where liftCompare = genericLiftCompare @@ -596,9 +493,7 @@ instance Show1 Echo where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Echo newtype Unset a = Unset a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Unset + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Unset where liftEq = genericLiftEq instance Ord1 Unset where liftCompare = genericLiftCompare @@ -606,9 +501,7 @@ instance Show1 Unset where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Unset data Declare a = Declare a a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 Declare + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Declare where liftEq = genericLiftEq instance Ord1 Declare where liftCompare = genericLiftCompare @@ -616,9 +509,7 @@ instance Show1 Declare where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Declare newtype DeclareDirective a = DeclareDirective a - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 DeclareDirective + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 DeclareDirective where liftEq = genericLiftEq instance Ord1 DeclareDirective where liftCompare = genericLiftCompare @@ -626,9 +517,7 @@ instance Show1 DeclareDirective where liftShowsPrec = genericLiftShowsPrec instance Evaluatable DeclareDirective newtype LabeledStatement a = LabeledStatement { _labeledStatementIdentifier :: a } - deriving (Diffable, Eq, Foldable, Functor, FreeVariables1, Declarations1, Generic1, Hashable1, Mergeable, Ord, Show, Traversable) - -instance ToJSONFields1 LabeledStatement + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 LabeledStatement where liftEq = genericLiftEq instance Ord1 LabeledStatement where liftCompare = genericLiftCompare diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index 310f79e6d..cd1e93ef4 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -89,9 +89,7 @@ resolvePythonModules q = do -- -- If the list of symbols is empty copy everything to the calling environment. data Import a = Import { importFrom :: QualifiedName, importSymbols :: ![(Name, Name)] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Import + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Import where liftEq = genericLiftEq instance Ord1 Import where liftCompare = genericLiftCompare @@ -144,9 +142,7 @@ evalQualifiedImport name path = letrec' name $ \addr -> do unit <$ makeNamespace name addr Nothing newtype QualifiedImport a = QualifiedImport { qualifiedImportFrom :: QualifiedName } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 QualifiedImport + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 QualifiedImport where liftEq = genericLiftEq instance Ord1 QualifiedImport where liftCompare = genericLiftCompare @@ -168,9 +164,7 @@ instance Evaluatable QualifiedImport where makeNamespace name addr Nothing data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportFrom :: QualifiedName, qualifiedAliasedImportAlias :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 QualifiedAliasedImport + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare @@ -194,26 +188,22 @@ instance Evaluatable QualifiedAliasedImport where -- | Ellipsis (used in splice expressions and alternatively can be used as a fill in expression, like `undefined` in Haskell) data Ellipsis a = Ellipsis - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Ellipsis where liftEq = genericLiftEq instance Ord1 Ellipsis where liftCompare = genericLiftCompare instance Show1 Ellipsis where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Ellipsis - -- TODO: Implement Eval instance for Ellipsis instance Evaluatable Ellipsis data Redirect a = Redirect !a !a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Redirect where liftEq = genericLiftEq instance Ord1 Redirect where liftCompare = genericLiftCompare instance Show1 Redirect where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Redirect - -- TODO: Implement Eval instance for Redirect instance Evaluatable Redirect diff --git a/src/Language/Ruby/Syntax.hs b/src/Language/Ruby/Syntax.hs index 862d41eb7..7524819c2 100644 --- a/src/Language/Ruby/Syntax.hs +++ b/src/Language/Ruby/Syntax.hs @@ -43,14 +43,12 @@ cleanNameOrPath :: ByteString -> String cleanNameOrPath = BC.unpack . dropRelativePrefix . stripQuotes data Send a = Send { sendReceiver :: Maybe a, sendSelector :: Maybe a, sendArgs :: [a], sendBlock :: Maybe a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Send where liftEq = genericLiftEq instance Ord1 Send where liftCompare = genericLiftCompare instance Show1 Send where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Send - instance Evaluatable Send where eval Send{..} = do let sel = case sendSelector of @@ -60,14 +58,12 @@ instance Evaluatable Send where Rval <$> call func (map subtermValue sendArgs) -- TODO pass through sendBlock data Require a = Require { requireRelative :: Bool, requirePath :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Require where liftEq = genericLiftEq instance Ord1 Require where liftCompare = genericLiftCompare instance Show1 Require where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Require - instance Evaluatable Require where eval (Require _ x) = do name <- subtermValue x >>= asString @@ -90,14 +86,12 @@ doRequire path = do newtype Load a = Load { loadArgs :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Load where liftEq = genericLiftEq instance Ord1 Load where liftCompare = genericLiftCompare instance Show1 Load where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Load - instance Evaluatable Load where eval (Load [x]) = do path <- subtermValue x >>= asString @@ -128,9 +122,7 @@ doLoad path shouldWrap = do -- TODO: autoload data Class a = Class { classIdentifier :: !a, classSuperClass :: !(Maybe a), classBody :: !a } - deriving (Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Class + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Diffable Class where equivalentBySubterm = Just . classIdentifier @@ -147,14 +139,12 @@ instance Evaluatable Class where subtermValue classBody <* makeNamespace name addr super) data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Module where liftEq = genericLiftEq instance Ord1 Module where liftCompare = genericLiftCompare instance Show1 Module where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Module - instance Evaluatable Module where eval (Module iden xs) = do name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden) @@ -164,9 +154,7 @@ instance Evaluatable Module where data LowPrecedenceBoolean a = LowAnd !a !a | LowOr !a !a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 LowPrecedenceBoolean + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Evaluatable LowPrecedenceBoolean where -- N.B. we have to use Monad rather than Applicative/Traversable on 'And' and 'Or' so that we don't evaluate both operands diff --git a/src/Language/TypeScript/Syntax.hs b/src/Language/TypeScript/Syntax.hs index b05d22bd1..16e92c1f3 100644 --- a/src/Language/TypeScript/Syntax.hs +++ b/src/Language/TypeScript/Syntax.hs @@ -152,9 +152,7 @@ evalRequire modulePath alias = letrec' alias $ \addr -> do unit <$ makeNamespace alias addr Nothing data Import a = Import { importSymbols :: ![(Name, Name)], importFrom :: ImportPath } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Import + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Import where liftEq = genericLiftEq instance Ord1 Import where liftCompare = genericLiftCompare @@ -172,14 +170,12 @@ instance Evaluatable Import where | otherwise = Env.overwrite symbols importedEnv data JavaScriptRequire a = JavaScriptRequire { javascriptRequireIden :: !a, javascriptRequireFrom :: ImportPath } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 JavaScriptRequire where liftEq = genericLiftEq instance Ord1 JavaScriptRequire where liftCompare = genericLiftCompare instance Show1 JavaScriptRequire where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 JavaScriptRequire - instance Evaluatable JavaScriptRequire where eval (JavaScriptRequire aliasTerm importPath) = do modulePath <- resolveWithNodejsStrategy importPath javascriptExtensions @@ -188,14 +184,12 @@ instance Evaluatable JavaScriptRequire where data QualifiedAliasedImport a = QualifiedAliasedImport { qualifiedAliasedImportAlias :: !a, qualifiedAliasedImportFrom :: ImportPath } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 QualifiedAliasedImport where liftEq = genericLiftEq instance Ord1 QualifiedAliasedImport where liftCompare = genericLiftCompare instance Show1 QualifiedAliasedImport where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 QualifiedAliasedImport - instance Evaluatable QualifiedAliasedImport where eval (QualifiedAliasedImport aliasTerm importPath) = do modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions @@ -203,14 +197,12 @@ instance Evaluatable QualifiedAliasedImport where Rval <$> evalRequire modulePath alias newtype SideEffectImport a = SideEffectImport { sideEffectImportFrom :: ImportPath } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 SideEffectImport where liftEq = genericLiftEq instance Ord1 SideEffectImport where liftCompare = genericLiftCompare instance Show1 SideEffectImport where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 SideEffectImport - instance Evaluatable SideEffectImport where eval (SideEffectImport importPath) = do modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions @@ -220,14 +212,12 @@ instance Evaluatable SideEffectImport where -- | Qualified Export declarations newtype QualifiedExport a = QualifiedExport { qualifiedExportSymbols :: [(Name, Name)] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 QualifiedExport where liftEq = genericLiftEq instance Ord1 QualifiedExport where liftCompare = genericLiftCompare instance Show1 QualifiedExport where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 QualifiedExport - instance Evaluatable QualifiedExport where eval (QualifiedExport exportSymbols) = do -- Insert the aliases with no addresses. @@ -238,14 +228,12 @@ instance Evaluatable QualifiedExport where -- | Qualified Export declarations that export from another module. data QualifiedExportFrom a = QualifiedExportFrom { qualifiedExportFrom :: ImportPath, qualifiedExportFromSymbols :: ![(Name, Name)]} - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 QualifiedExportFrom where liftEq = genericLiftEq instance Ord1 QualifiedExportFrom where liftCompare = genericLiftCompare instance Show1 QualifiedExportFrom where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 QualifiedExportFrom - instance Evaluatable QualifiedExportFrom where eval (QualifiedExportFrom importPath exportSymbols) = do modulePath <- resolveWithNodejsStrategy importPath typescriptExtensions @@ -257,9 +245,7 @@ instance Evaluatable QualifiedExportFrom where pure (Rval unit) newtype DefaultExport a = DefaultExport { defaultExport :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 DefaultExport + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 DefaultExport where liftEq = genericLiftEq instance Ord1 DefaultExport where liftCompare = genericLiftCompare @@ -280,9 +266,7 @@ instance Evaluatable DefaultExport where -- | Lookup type for a type-level key in a typescript map. data LookupType a = LookupType { lookupTypeIdentifier :: a, lookupTypeKey :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 LookupType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 LookupType where liftEq = genericLiftEq instance Ord1 LookupType where liftCompare = genericLiftCompare @@ -291,9 +275,7 @@ instance Evaluatable LookupType -- | ShorthandPropertyIdentifier used in object patterns such as var baz = { foo } to mean var baz = { foo: foo } newtype ShorthandPropertyIdentifier a = ShorthandPropertyIdentifier ByteString - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ShorthandPropertyIdentifier + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ShorthandPropertyIdentifier where liftEq = genericLiftEq instance Ord1 ShorthandPropertyIdentifier where liftCompare = genericLiftCompare @@ -301,9 +283,7 @@ instance Show1 ShorthandPropertyIdentifier where liftShowsPrec = genericLiftShow instance Evaluatable ShorthandPropertyIdentifier data Union a = Union { _unionLeft :: !a, _unionRight :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Language.TypeScript.Syntax.Union + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Language.TypeScript.Syntax.Union where liftEq = genericLiftEq instance Ord1 Language.TypeScript.Syntax.Union where liftCompare = genericLiftCompare @@ -311,9 +291,7 @@ instance Show1 Language.TypeScript.Syntax.Union where liftShowsPrec = genericLif instance Evaluatable Language.TypeScript.Syntax.Union data Intersection a = Intersection { _intersectionLeft :: !a, _intersectionRight :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Intersection + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Intersection where liftEq = genericLiftEq instance Ord1 Intersection where liftCompare = genericLiftCompare @@ -321,9 +299,7 @@ instance Show1 Intersection where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Intersection data FunctionType a = FunctionType { _functionTypeParameters :: !a, _functionFormalParameters :: ![a], _functionType :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 FunctionType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 FunctionType where liftEq = genericLiftEq instance Ord1 FunctionType where liftCompare = genericLiftCompare @@ -331,9 +307,7 @@ instance Show1 FunctionType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable FunctionType data AmbientFunction a = AmbientFunction { _ambientFunctionContext :: ![a], _ambientFunctionIdentifier :: !a, _ambientFunctionParameters :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 AmbientFunction + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 AmbientFunction where liftEq = genericLiftEq instance Ord1 AmbientFunction where liftCompare = genericLiftCompare @@ -341,9 +315,7 @@ instance Show1 AmbientFunction where liftShowsPrec = genericLiftShowsPrec instance Evaluatable AmbientFunction data ImportRequireClause a = ImportRequireClause { _importRequireIdentifier :: !a, _importRequireSubject :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ImportRequireClause + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ImportRequireClause where liftEq = genericLiftEq instance Ord1 ImportRequireClause where liftCompare = genericLiftCompare @@ -351,9 +323,7 @@ instance Show1 ImportRequireClause where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ImportRequireClause newtype ImportClause a = ImportClause { _importClauseElements :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ImportClause + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ImportClause where liftEq = genericLiftEq instance Ord1 ImportClause where liftCompare = genericLiftCompare @@ -361,9 +331,7 @@ instance Show1 ImportClause where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ImportClause newtype Tuple a = Tuple { _tupleElements :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Tuple + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Tuple where liftEq = genericLiftEq instance Ord1 Tuple where liftCompare = genericLiftCompare @@ -373,9 +341,7 @@ instance Show1 Tuple where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Tuple data Constructor a = Constructor { _constructorTypeParameters :: !a, _constructorFormalParameters :: ![a], _constructorType :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Language.TypeScript.Syntax.Constructor + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Language.TypeScript.Syntax.Constructor where liftEq = genericLiftEq instance Ord1 Language.TypeScript.Syntax.Constructor where liftCompare = genericLiftCompare @@ -383,9 +349,7 @@ instance Show1 Language.TypeScript.Syntax.Constructor where liftShowsPrec = gene instance Evaluatable Language.TypeScript.Syntax.Constructor data TypeParameter a = TypeParameter { _typeParameter :: !a, _typeParameterConstraint :: !a, _typeParameterDefaultType :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 TypeParameter + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TypeParameter where liftEq = genericLiftEq instance Ord1 TypeParameter where liftCompare = genericLiftCompare @@ -393,9 +357,7 @@ instance Show1 TypeParameter where liftShowsPrec = genericLiftShowsPrec instance Evaluatable TypeParameter data TypeAssertion a = TypeAssertion { _typeAssertionParameters :: !a, _typeAssertionExpression :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 TypeAssertion + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TypeAssertion where liftEq = genericLiftEq instance Ord1 TypeAssertion where liftCompare = genericLiftCompare @@ -403,9 +365,7 @@ instance Show1 TypeAssertion where liftShowsPrec = genericLiftShowsPrec instance Evaluatable TypeAssertion newtype Annotation a = Annotation { _annotationType :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Annotation + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Annotation where liftEq = genericLiftEq instance Ord1 Annotation where liftCompare = genericLiftCompare @@ -413,9 +373,7 @@ instance Show1 Annotation where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Annotation newtype Decorator a = Decorator { _decoratorTerm :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Decorator + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Decorator where liftEq = genericLiftEq instance Ord1 Decorator where liftCompare = genericLiftCompare @@ -423,9 +381,7 @@ instance Show1 Decorator where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Decorator newtype ComputedPropertyName a = ComputedPropertyName a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ComputedPropertyName + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ComputedPropertyName where liftEq = genericLiftEq instance Ord1 ComputedPropertyName where liftCompare = genericLiftCompare @@ -433,9 +389,7 @@ instance Show1 ComputedPropertyName where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ComputedPropertyName newtype Constraint a = Constraint { _constraintType :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Constraint + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Constraint where liftEq = genericLiftEq instance Ord1 Constraint where liftCompare = genericLiftCompare @@ -443,9 +397,7 @@ instance Show1 Constraint where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Constraint newtype DefaultType a = DefaultType { _defaultType :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 DefaultType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 DefaultType where liftEq = genericLiftEq instance Ord1 DefaultType where liftCompare = genericLiftCompare @@ -453,9 +405,7 @@ instance Show1 DefaultType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable DefaultType newtype ParenthesizedType a = ParenthesizedType { _parenthesizedType :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ParenthesizedType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ParenthesizedType where liftEq = genericLiftEq instance Ord1 ParenthesizedType where liftCompare = genericLiftCompare @@ -463,9 +413,7 @@ instance Show1 ParenthesizedType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ParenthesizedType newtype PredefinedType a = PredefinedType { _predefinedType :: ByteString } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 PredefinedType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 PredefinedType where liftEq = genericLiftEq instance Ord1 PredefinedType where liftCompare = genericLiftCompare @@ -473,9 +421,7 @@ instance Show1 PredefinedType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable PredefinedType newtype TypeIdentifier a = TypeIdentifier ByteString - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 TypeIdentifier + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TypeIdentifier where liftEq = genericLiftEq instance Ord1 TypeIdentifier where liftCompare = genericLiftCompare @@ -483,9 +429,7 @@ instance Show1 TypeIdentifier where liftShowsPrec = genericLiftShowsPrec instance Evaluatable TypeIdentifier data NestedIdentifier a = NestedIdentifier !a !a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 NestedIdentifier + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 NestedIdentifier where liftEq = genericLiftEq instance Ord1 NestedIdentifier where liftCompare = genericLiftCompare @@ -493,9 +437,7 @@ instance Show1 NestedIdentifier where liftShowsPrec = genericLiftShowsPrec instance Evaluatable NestedIdentifier data NestedTypeIdentifier a = NestedTypeIdentifier !a !a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 NestedTypeIdentifier + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 NestedTypeIdentifier where liftEq = genericLiftEq instance Ord1 NestedTypeIdentifier where liftCompare = genericLiftCompare @@ -503,9 +445,7 @@ instance Show1 NestedTypeIdentifier where liftShowsPrec = genericLiftShowsPrec instance Evaluatable NestedTypeIdentifier data GenericType a = GenericType { _genericTypeIdentifier :: !a, _genericTypeArguments :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 GenericType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 GenericType where liftEq = genericLiftEq instance Ord1 GenericType where liftCompare = genericLiftCompare @@ -513,9 +453,7 @@ instance Show1 GenericType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable GenericType data TypePredicate a = TypePredicate { _typePredicateIdentifier :: !a, _typePredicateType :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 TypePredicate + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TypePredicate where liftEq = genericLiftEq instance Ord1 TypePredicate where liftCompare = genericLiftCompare @@ -523,9 +461,7 @@ instance Show1 TypePredicate where liftShowsPrec = genericLiftShowsPrec instance Evaluatable TypePredicate newtype ObjectType a = ObjectType { _objectTypeElements :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ObjectType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ObjectType where liftEq = genericLiftEq instance Ord1 ObjectType where liftCompare = genericLiftCompare @@ -533,9 +469,7 @@ instance Show1 ObjectType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ObjectType data With a = With { _withExpression :: !a, _withBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 With + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 With where liftEq = genericLiftEq instance Ord1 With where liftCompare = genericLiftCompare @@ -543,9 +477,7 @@ instance Show1 With where liftShowsPrec = genericLiftShowsPrec instance Evaluatable With newtype AmbientDeclaration a = AmbientDeclaration { _ambientDeclarationBody :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 AmbientDeclaration + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 AmbientDeclaration where liftEq = genericLiftEq instance Ord1 AmbientDeclaration where liftCompare = genericLiftCompare @@ -555,9 +487,7 @@ instance Evaluatable AmbientDeclaration where eval (AmbientDeclaration body) = subtermRef body data EnumDeclaration a = EnumDeclaration { enumDeclarationIdentifier :: !a, _enumDeclarationBody :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 EnumDeclaration + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 EnumDeclaration where liftEq = genericLiftEq instance Ord1 EnumDeclaration where liftCompare = genericLiftCompare @@ -568,9 +498,7 @@ instance Declarations a => Declarations (EnumDeclaration a) where declaredName EnumDeclaration{..} = declaredName enumDeclarationIdentifier newtype ExtendsClause a = ExtendsClause { _extendsClauses :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ExtendsClause + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ExtendsClause where liftEq = genericLiftEq instance Ord1 ExtendsClause where liftCompare = genericLiftCompare @@ -578,9 +506,7 @@ instance Show1 ExtendsClause where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ExtendsClause newtype ArrayType a = ArrayType { _arrayType :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ArrayType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ArrayType where liftEq = genericLiftEq instance Ord1 ArrayType where liftCompare = genericLiftCompare @@ -588,9 +514,7 @@ instance Show1 ArrayType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ArrayType newtype FlowMaybeType a = FlowMaybeType { _flowMaybeType :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 FlowMaybeType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 FlowMaybeType where liftEq = genericLiftEq instance Ord1 FlowMaybeType where liftCompare = genericLiftCompare @@ -598,9 +522,7 @@ instance Show1 FlowMaybeType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable FlowMaybeType newtype TypeQuery a = TypeQuery { _typeQuerySubject :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 TypeQuery + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TypeQuery where liftEq = genericLiftEq instance Ord1 TypeQuery where liftCompare = genericLiftCompare @@ -608,9 +530,7 @@ instance Show1 TypeQuery where liftShowsPrec = genericLiftShowsPrec instance Evaluatable TypeQuery newtype IndexTypeQuery a = IndexTypeQuery { _indexTypeQuerySubject :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 IndexTypeQuery + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 IndexTypeQuery where liftEq = genericLiftEq instance Ord1 IndexTypeQuery where liftCompare = genericLiftCompare @@ -618,9 +538,7 @@ instance Show1 IndexTypeQuery where liftShowsPrec = genericLiftShowsPrec instance Evaluatable IndexTypeQuery newtype TypeArguments a = TypeArguments { _typeArguments :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 TypeArguments + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 TypeArguments where liftEq = genericLiftEq instance Ord1 TypeArguments where liftCompare = genericLiftCompare @@ -628,9 +546,7 @@ instance Show1 TypeArguments where liftShowsPrec = genericLiftShowsPrec instance Evaluatable TypeArguments newtype ThisType a = ThisType ByteString - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ThisType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ThisType where liftEq = genericLiftEq instance Ord1 ThisType where liftCompare = genericLiftCompare @@ -638,9 +554,7 @@ instance Show1 ThisType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ThisType newtype ExistentialType a = ExistentialType ByteString - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ExistentialType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ExistentialType where liftEq = genericLiftEq instance Ord1 ExistentialType where liftCompare = genericLiftCompare @@ -648,9 +562,7 @@ instance Show1 ExistentialType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ExistentialType newtype LiteralType a = LiteralType { _literalTypeSubject :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 LiteralType + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 LiteralType where liftEq = genericLiftEq instance Ord1 LiteralType where liftCompare = genericLiftCompare @@ -658,9 +570,7 @@ instance Show1 LiteralType where liftShowsPrec = genericLiftShowsPrec instance Evaluatable LiteralType data PropertySignature a = PropertySignature { _modifiers :: ![a], _propertySignaturePropertyName :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 PropertySignature + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 PropertySignature where liftEq = genericLiftEq instance Ord1 PropertySignature where liftCompare = genericLiftCompare @@ -668,9 +578,7 @@ instance Show1 PropertySignature where liftShowsPrec = genericLiftShowsPrec instance Evaluatable PropertySignature data CallSignature a = CallSignature { _callSignatureTypeParameters :: !a, _callSignatureParameters :: ![a], _callSignatureType :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 CallSignature + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 CallSignature where liftEq = genericLiftEq instance Ord1 CallSignature where liftCompare = genericLiftCompare @@ -679,9 +587,7 @@ instance Evaluatable CallSignature -- | Todo: Move type params and type to context data ConstructSignature a = ConstructSignature { _constructSignatureTypeParameters :: !a, _constructSignatureParameters :: ![a], _constructSignatureType :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ConstructSignature + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ConstructSignature where liftEq = genericLiftEq instance Ord1 ConstructSignature where liftCompare = genericLiftCompare @@ -689,9 +595,7 @@ instance Show1 ConstructSignature where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ConstructSignature data IndexSignature a = IndexSignature { _indexSignatureSubject :: a, _indexSignatureType :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 IndexSignature + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 IndexSignature where liftEq = genericLiftEq instance Ord1 IndexSignature where liftCompare = genericLiftCompare @@ -699,9 +603,7 @@ instance Show1 IndexSignature where liftShowsPrec = genericLiftShowsPrec instance Evaluatable IndexSignature data AbstractMethodSignature a = AbstractMethodSignature { _abstractMethodSignatureContext :: ![a], _abstractMethodSignatureName :: !a, _abstractMethodSignatureParameters :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 AbstractMethodSignature + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 AbstractMethodSignature where liftEq = genericLiftEq instance Ord1 AbstractMethodSignature where liftCompare = genericLiftCompare @@ -709,9 +611,7 @@ instance Show1 AbstractMethodSignature where liftShowsPrec = genericLiftShowsPre instance Evaluatable AbstractMethodSignature data Debugger a = Debugger - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Debugger + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Debugger where liftEq = genericLiftEq instance Ord1 Debugger where liftCompare = genericLiftCompare @@ -719,9 +619,7 @@ instance Show1 Debugger where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Debugger data ForOf a = ForOf { _forOfBinding :: !a, _forOfSubject :: !a, _forOfBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ForOf + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ForOf where liftEq = genericLiftEq instance Ord1 ForOf where liftCompare = genericLiftCompare @@ -729,9 +627,7 @@ instance Show1 ForOf where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ForOf data This a = This - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 This + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 This where liftEq = genericLiftEq instance Ord1 This where liftCompare = genericLiftCompare @@ -739,9 +635,7 @@ instance Show1 This where liftShowsPrec = genericLiftShowsPrec instance Evaluatable This data LabeledStatement a = LabeledStatement { _labeledStatementIdentifier :: !a, _labeledStatementSubject :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 LabeledStatement + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 LabeledStatement where liftEq = genericLiftEq instance Ord1 LabeledStatement where liftCompare = genericLiftCompare @@ -749,9 +643,7 @@ instance Show1 LabeledStatement where liftShowsPrec = genericLiftShowsPrec instance Evaluatable LabeledStatement newtype Update a = Update { _updateSubject :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Update + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Update where liftEq = genericLiftEq instance Ord1 Update where liftCompare = genericLiftCompare @@ -759,14 +651,12 @@ instance Show1 Update where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Update data Module a = Module { moduleIdentifier :: !a, moduleStatements :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Module where liftEq = genericLiftEq instance Ord1 Module where liftCompare = genericLiftCompare instance Show1 Module where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 Module - instance Evaluatable Module where eval (Module iden xs) = do name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden) @@ -776,14 +666,12 @@ instance Evaluatable Module where data InternalModule a = InternalModule { internalModuleIdentifier :: !a, internalModuleStatements :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 InternalModule where liftEq = genericLiftEq instance Ord1 InternalModule where liftCompare = genericLiftCompare instance Show1 InternalModule where liftShowsPrec = genericLiftShowsPrec -instance ToJSONFields1 InternalModule - instance Evaluatable InternalModule where eval (InternalModule iden xs) = do name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm iden) @@ -795,9 +683,7 @@ instance Declarations a => Declarations (InternalModule a) where data ImportAlias a = ImportAlias { _importAliasSubject :: !a, _importAlias :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ImportAlias + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ImportAlias where liftEq = genericLiftEq instance Ord1 ImportAlias where liftCompare = genericLiftCompare @@ -805,9 +691,7 @@ instance Show1 ImportAlias where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ImportAlias data Super a = Super - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Super + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Super where liftEq = genericLiftEq instance Ord1 Super where liftCompare = genericLiftCompare @@ -815,9 +699,7 @@ instance Show1 Super where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Super data Undefined a = Undefined - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 Undefined + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 Undefined where liftEq = genericLiftEq instance Ord1 Undefined where liftCompare = genericLiftCompare @@ -825,9 +707,7 @@ instance Show1 Undefined where liftShowsPrec = genericLiftShowsPrec instance Evaluatable Undefined data ClassHeritage a = ClassHeritage { _classHeritageExtendsClause :: !a, _implementsClause :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ClassHeritage + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ClassHeritage where liftEq = genericLiftEq instance Ord1 ClassHeritage where liftCompare = genericLiftCompare @@ -835,7 +715,7 @@ instance Show1 ClassHeritage where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ClassHeritage data AbstractClass a = AbstractClass { abstractClassIdentifier :: !a, _abstractClassTypeParameters :: !a, classHeritage :: ![a], classBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 AbstractClass where liftEq = genericLiftEq instance Ord1 AbstractClass where liftCompare = genericLiftCompare @@ -843,8 +723,6 @@ instance Show1 AbstractClass where liftShowsPrec = genericLiftShowsPrec instance Declarations a => Declarations (AbstractClass a) where declaredName AbstractClass{..} = declaredName abstractClassIdentifier -instance ToJSONFields1 AbstractClass - instance Evaluatable AbstractClass where eval AbstractClass{..} = do name <- either (throwEvalError . FreeVariablesError) pure (freeVariable $ subterm abstractClassIdentifier) @@ -857,9 +735,7 @@ instance Evaluatable AbstractClass where data JsxElement a = JsxElement { _jsxOpeningElement :: !a, _jsxElements :: ![a], _jsxClosingElement :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 JsxElement + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 JsxElement where liftEq = genericLiftEq instance Ord1 JsxElement where liftCompare = genericLiftCompare @@ -867,9 +743,7 @@ instance Show1 JsxElement where liftShowsPrec = genericLiftShowsPrec instance Evaluatable JsxElement newtype JsxText a = JsxText ByteString - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 JsxText + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 JsxText where liftEq = genericLiftEq instance Ord1 JsxText where liftCompare = genericLiftCompare @@ -877,9 +751,7 @@ instance Show1 JsxText where liftShowsPrec = genericLiftShowsPrec instance Evaluatable JsxText newtype JsxExpression a = JsxExpression { _jsxExpression :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 JsxExpression + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 JsxExpression where liftEq = genericLiftEq instance Ord1 JsxExpression where liftCompare = genericLiftCompare @@ -887,9 +759,7 @@ instance Show1 JsxExpression where liftShowsPrec = genericLiftShowsPrec instance Evaluatable JsxExpression data JsxOpeningElement a = JsxOpeningElement { _jsxOpeningElementIdentifier :: !a, _jsxAttributes :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 JsxOpeningElement + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 JsxOpeningElement where liftEq = genericLiftEq instance Ord1 JsxOpeningElement where liftCompare = genericLiftCompare @@ -897,9 +767,7 @@ instance Show1 JsxOpeningElement where liftShowsPrec = genericLiftShowsPrec instance Evaluatable JsxOpeningElement newtype JsxClosingElement a = JsxClosingElement { _jsxClosingElementIdentifier :: a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 JsxClosingElement + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 JsxClosingElement where liftEq = genericLiftEq instance Ord1 JsxClosingElement where liftCompare = genericLiftCompare @@ -907,9 +775,7 @@ instance Show1 JsxClosingElement where liftShowsPrec = genericLiftShowsPrec instance Evaluatable JsxClosingElement data JsxSelfClosingElement a = JsxSelfClosingElement { _jsxSelfClosingElementIdentifier :: !a, _jsxSelfClosingElementAttributes :: ![a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 JsxSelfClosingElement + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 JsxSelfClosingElement where liftEq = genericLiftEq instance Ord1 JsxSelfClosingElement where liftCompare = genericLiftCompare @@ -917,9 +783,7 @@ instance Show1 JsxSelfClosingElement where liftShowsPrec = genericLiftShowsPrec instance Evaluatable JsxSelfClosingElement data JsxAttribute a = JsxAttribute { _jsxAttributeTarget :: !a, _jsxAttributeValue :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 JsxAttribute + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 JsxAttribute where liftEq = genericLiftEq instance Ord1 JsxAttribute where liftCompare = genericLiftCompare @@ -927,9 +791,7 @@ instance Show1 JsxAttribute where liftShowsPrec = genericLiftShowsPrec instance Evaluatable JsxAttribute newtype ImplementsClause a = ImplementsClause { _implementsClauseTypes :: [a] } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 ImplementsClause + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 ImplementsClause where liftEq = genericLiftEq instance Ord1 ImplementsClause where liftCompare = genericLiftCompare @@ -937,9 +799,7 @@ instance Show1 ImplementsClause where liftShowsPrec = genericLiftShowsPrec instance Evaluatable ImplementsClause data OptionalParameter a = OptionalParameter { _optionalParameterContext :: ![a], _optionalParameterSubject :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 OptionalParameter + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 OptionalParameter where liftEq = genericLiftEq instance Ord1 OptionalParameter where liftCompare = genericLiftCompare @@ -947,9 +807,7 @@ instance Show1 OptionalParameter where liftShowsPrec = genericLiftShowsPrec instance Evaluatable OptionalParameter data RequiredParameter a = RequiredParameter { _requiredParameterContext :: ![a], _requiredParameterSubject :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 RequiredParameter + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 RequiredParameter where liftEq = genericLiftEq instance Ord1 RequiredParameter where liftCompare = genericLiftCompare @@ -957,9 +815,7 @@ instance Show1 RequiredParameter where liftShowsPrec = genericLiftShowsPrec instance Evaluatable RequiredParameter data RestParameter a = RestParameter { _restParameterContext :: ![a], _restParameterSubject :: !a } - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 RestParameter + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 RestParameter where liftEq = genericLiftEq instance Ord1 RestParameter where liftCompare = genericLiftCompare @@ -967,9 +823,7 @@ instance Show1 RestParameter where liftShowsPrec = genericLiftShowsPrec instance Evaluatable RestParameter newtype JsxFragment a = JsxFragment [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 JsxFragment + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 JsxFragment where liftEq = genericLiftEq instance Ord1 JsxFragment where liftCompare = genericLiftCompare @@ -977,9 +831,7 @@ instance Show1 JsxFragment where liftShowsPrec = genericLiftShowsPrec instance Evaluatable JsxFragment data JsxNamespaceName a = JsxNamespaceName a a - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) - -instance ToJSONFields1 JsxNamespaceName + deriving (Eq, Ord, Show, Foldable, Traversable, Functor, Generic1, Hashable1, Diffable, Mergeable, FreeVariables1, Declarations1, ToJSONFields1) instance Eq1 JsxNamespaceName where liftEq = genericLiftEq instance Ord1 JsxNamespaceName where liftCompare = genericLiftCompare diff --git a/test/Semantic/CLI/Spec.hs b/test/Semantic/CLI/Spec.hs index f0799501e..e063c309c 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\":[{\"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" + jsonParseTreeOutput = "{\"trees\":[{\"tree\":{\"term\":\"Program\",\"children\":[{\"children\":{\"term\":\"Send\",\"sourceRange\":[8,11],\"sendReceiver\":null,\"sendBlock\":null,\"sendArgs\":[],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]},\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}}},\"term\":\"LowAnd\",\"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\":[{\"children\":{\"term\":\"Send\",\"sourceRange\":[8,11],\"sendReceiver\":null,\"sendBlock\":null,\"sendArgs\":[],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]},\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}}},\"term\":\"LowAnd\",\"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\":[{\"children\":{\"term\":\"Send\",\"sourceRange\":[7,10],\"sendReceiver\":null,\"sendBlock\":null,\"sendArgs\":[],\"sourceSpan\":{\"start\":[1,8],\"end\":[1,11]},\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[7,10],\"sourceSpan\":{\"start\":[1,8],\"end\":[1,11]}}},\"term\":\"LowOr\",\"sourceRange\":[0,10],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,11]}},{\"children\":{\"term\":\"Send\",\"sourceRange\":[22,23],\"sendReceiver\":null,\"sendBlock\":null,\"sendArgs\":[],\"sourceSpan\":{\"start\":[2,12],\"end\":[2,13]},\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"c\",\"sourceRange\":[22,23],\"sourceSpan\":{\"start\":[2,12],\"end\":[2,13]}}},\"term\":\"LowAnd\",\"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\":{\"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" + jsonOutput = "{\"diffs\":[{\"diff\":{\"merge\":{\"term\":\"Program\",\"children\":[{\"merge\":{\"after\":{\"sourceRange\":[0,20],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,4]}},\"methodParameters\":[{\"patch\":{\"insert\":{\"term\":\"Identifier\",\"name\":\"a\",\"sourceRange\":[8,9],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,10]}}}}],\"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]}}]}},\"methodContext\":[],\"methodReceiver\":{\"merge\":{\"after\":{\"sourceRange\":[0,0],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,1]}},\"term\":\"Empty\",\"before\":{\"sourceRange\":[0,0],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,1]}}}},\"term\":\"Method\",\"methodBody\":{\"merge\":{\"after\":{\"sourceRange\":[13,16],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,6]}},\"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]}}}},\"before\":{\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,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" From 53e1ebf86e5ee644ae45d90d6af02562784ca2ff Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Thu, 31 May 2018 17:20:37 -0700 Subject: [PATCH 12/16] Don't duplicate or drop fields --- src/Data/JSON/Fields.hs | 38 +++++++++++++++++++++++++++++--------- 1 file changed, 29 insertions(+), 9 deletions(-) diff --git a/src/Data/JSON/Fields.hs b/src/Data/JSON/Fields.hs index 140fb8df5..602e1ba8c 100644 --- a/src/Data/JSON/Fields.hs +++ b/src/Data/JSON/Fields.hs @@ -9,6 +9,7 @@ module Data.JSON.Fields ) where import Data.Aeson +import qualified Data.Map as Map import Data.Sum (Apply (..), Sum) import qualified Data.Text as Text import qualified Data.Text.Encoding as Text @@ -21,7 +22,11 @@ class ToJSONFields1 f where toJSONFields1 :: (KeyValue kv, ToJSON a) => f a -> [kv] 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 + "term" .= gconstructorName1 r : Map.foldrWithKey m [] (gtoJSONFields1 r) + where + m _ [] acc = acc + m k [v] acc = (k .= v) : acc + m k vs acc = (k .= vs) : acc instance ToJSONFields a => ToJSONFields (Join (,) a) where toJSONFields (Join (a, b)) = [ "before" .= object (toJSONFields a), "after" .= object (toJSONFields b) ] @@ -85,7 +90,7 @@ instance (GConstructorName1 f, GConstructorName1 g) => GConstructorName1 (f :+: -- | 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] + gtoJSONFields1 :: (ToJSON a) => f a -> Map.Map Text [SomeJSON] instance GToJSONFields1 f => GToJSONFields1 (M1 D c f) where gtoJSONFields1 = gtoJSONFields1 . unM1 @@ -94,10 +99,10 @@ instance GToJSONFields1 f => GToJSONFields1 (M1 C c f) where gtoJSONFields1 = gtoJSONFields1 . unM1 instance GToJSONFields1 U1 where - gtoJSONFields1 _ = [] + gtoJSONFields1 _ = mempty instance (Selector c, GSelectorJSONValue1 f) => GToJSONFields1 (M1 S c f) where - gtoJSONFields1 m1 = gselectorJSONValue1 keyName (unM1 m1) + gtoJSONFields1 m1 = Map.fromList [gselectorJSONValue1 keyName (unM1 m1)] where keyName = case selName m1 of "" -> Nothing n -> Just (Text.pack n) @@ -107,23 +112,38 @@ instance (GToJSONFields1 f, GToJSONFields1 g) => GToJSONFields1 (f :+: g) where gtoJSONFields1 (R1 r) = gtoJSONFields1 r instance (GToJSONFields1 f, GToJSONFields1 g) => GToJSONFields1 (f :*: g) where - gtoJSONFields1 (x :*: y) = gtoJSONFields1 x <> gtoJSONFields1 y + gtoJSONFields1 (x :*: y) = Map.unionWith (<>) (gtoJSONFields1 x) (gtoJSONFields1 y) -- | A typeclass to retrieve the JSON 'Value' of a record selector. class GSelectorJSONValue1 f where - gselectorJSONValue1 :: (KeyValue kv, ToJSON a) => Maybe Text -> f a -> [kv] + gselectorJSONValue1 :: (ToJSON a) => Maybe Text -> f a -> (Text, [SomeJSON]) instance GSelectorJSONValue1 Par1 where - gselectorJSONValue1 k x = [ fromMaybe "children" k .= unPar1 x] + gselectorJSONValue1 k x = (fromMaybe "children" k, [SomeJSON (unPar1 x)]) instance ToJSON1 f => GSelectorJSONValue1 (Rec1 f) where - gselectorJSONValue1 k x = [ fromMaybe "children" k .= toJSON1 (unRec1 x)] + gselectorJSONValue1 k x = (fromMaybe "children" k, [SomeJSON (SomeJSON1 (unRec1 x))]) instance ToJSON k => GSelectorJSONValue1 (K1 r k) where - gselectorJSONValue1 k x = [ fromMaybe "value" k .= unK1 x ] + gselectorJSONValue1 k x = (fromMaybe "value" k, [SomeJSON (unK1 x)]) -- 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 From a4e0ca668652a8ec22c443c10ed86f64b30f4bf2 Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Thu, 31 May 2018 17:20:51 -0700 Subject: [PATCH 13/16] Fix tests and use fixtures that are easier to maintain --- test/Semantic/CLI/Spec.hs | 59 +++--- test/fixtures/cli/diff-tree.json | 198 ++++++++++++++++++ test/fixtures/cli/diff-tree.toc.json | 18 ++ test/fixtures/cli/parse-tree-empty.json | 3 + test/fixtures/cli/parse-tree.json | 74 +++++++ test/fixtures/cli/parse-tree.symbols.json | 17 ++ test/fixtures/cli/parse-tree.tags.json | 13 ++ test/fixtures/cli/parse-trees.json | 234 ++++++++++++++++++++++ 8 files changed, 583 insertions(+), 33 deletions(-) create mode 100644 test/fixtures/cli/diff-tree.json create mode 100644 test/fixtures/cli/diff-tree.toc.json create mode 100644 test/fixtures/cli/parse-tree-empty.json create mode 100644 test/fixtures/cli/parse-tree.json create mode 100644 test/fixtures/cli/parse-tree.symbols.json create mode 100644 test/fixtures/cli/parse-tree.tags.json create mode 100644 test/fixtures/cli/parse-trees.json diff --git a/test/Semantic/CLI/Spec.hs b/test/Semantic/CLI/Spec.hs index e063c309c..1c474875b 100644 --- a/test/Semantic/CLI/Spec.hs +++ b/test/Semantic/CLI/Spec.hs @@ -1,11 +1,12 @@ module Semantic.CLI.Spec (spec) where -import Control.Monad (when) -import Data.ByteString.Builder -import Data.Foldable (for_) -import Semantic.CLI -import Semantic.IO -import Semantic.Task +import Control.Monad (when) +import qualified Data.ByteString as B +import Data.ByteString.Builder +import Data.Foldable (for_) +import Semantic.CLI +import Semantic.IO +import Semantic.Task import SpecHelpers @@ -24,38 +25,30 @@ spec = parallel $ do output <- runTask $ readBlobs (Right files) >>= runParse runBuilder output `shouldBe'` expected where - shouldBe' actual expected = do - when (actual /= expected) $ print actual + shouldBe' actual' expectedFile = do + let actual = verbatim actual' + expected <- verbatim <$> B.readFile expectedFile actual `shouldBe` expected -parseFixtures :: [(String, [Blob] -> TaskEff Builder, [File], ByteString)] +parseFixtures :: [(String, [Blob] -> TaskEff Builder, [File], FilePath)] parseFixtures = - [ (show SExpressionTermRenderer, runParse SExpressionTermRenderer, pathMode, sExpressionParseTreeOutput) - , (show JSONTermRenderer, runParse JSONTermRenderer, pathMode, jsonParseTreeOutput) - , (show JSONTermRenderer, runParse JSONTermRenderer, pathMode', jsonParseTreeOutput') - , (show JSONTermRenderer, runParse JSONTermRenderer, [], emptyJsonParseTreeOutput) - , (show (SymbolsTermRenderer defaultSymbolFields), runParse (SymbolsTermRenderer defaultSymbolFields), [File "test/fixtures/ruby/corpus/method-declaration.A.rb" (Just Ruby)], symbolsOutput) - , (show TagsTermRenderer, runParse TagsTermRenderer, [File "test/fixtures/ruby/corpus/method-declaration.A.rb" (Just Ruby)], tagsOutput) + [ (show SExpressionTermRenderer, runParse SExpressionTermRenderer, path, "test/fixtures/ruby/corpus/and-or.parseA.txt") + , (show JSONTermRenderer, runParse JSONTermRenderer, path, prefix "parse-tree.json") + , (show JSONTermRenderer, runParse JSONTermRenderer, path', prefix "parse-trees.json") + , (show JSONTermRenderer, runParse JSONTermRenderer, [], prefix "parse-tree-empty.json") + , (show (SymbolsTermRenderer defaultSymbolFields), runParse (SymbolsTermRenderer defaultSymbolFields), path'', prefix "parse-tree.symbols.json") + , (show TagsTermRenderer, runParse TagsTermRenderer, path'', prefix "parse-tree.tags.json") ] - where pathMode = [File "test/fixtures/ruby/corpus/and-or.A.rb" (Just Ruby)] - pathMode' = [File "test/fixtures/ruby/corpus/and-or.A.rb" (Just Ruby), File "test/fixtures/ruby/corpus/and-or.B.rb" (Just Ruby)] + where path = [File "test/fixtures/ruby/corpus/and-or.A.rb" (Just Ruby)] + path' = [File "test/fixtures/ruby/corpus/and-or.A.rb" (Just Ruby), File "test/fixtures/ruby/corpus/and-or.B.rb" (Just Ruby)] + path'' = [File "test/fixtures/ruby/corpus/method-declaration.A.rb" (Just Ruby)] + prefix = "test/fixtures/cli" - sExpressionParseTreeOutput = "(Program\n (LowAnd\n (Send\n (Identifier))\n (Send\n (Identifier))))\n" - jsonParseTreeOutput = "{\"trees\":[{\"tree\":{\"term\":\"Program\",\"children\":[{\"children\":{\"term\":\"Send\",\"sourceRange\":[8,11],\"sendReceiver\":null,\"sendBlock\":null,\"sendArgs\":[],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]},\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}}},\"term\":\"LowAnd\",\"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\":[{\"children\":{\"term\":\"Send\",\"sourceRange\":[8,11],\"sendReceiver\":null,\"sendBlock\":null,\"sendArgs\":[],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]},\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}}},\"term\":\"LowAnd\",\"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\":[{\"children\":{\"term\":\"Send\",\"sourceRange\":[7,10],\"sendReceiver\":null,\"sendBlock\":null,\"sendArgs\":[],\"sourceSpan\":{\"start\":[1,8],\"end\":[1,11]},\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"bar\",\"sourceRange\":[7,10],\"sourceSpan\":{\"start\":[1,8],\"end\":[1,11]}}},\"term\":\"LowOr\",\"sourceRange\":[0,10],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,11]}},{\"children\":{\"term\":\"Send\",\"sourceRange\":[22,23],\"sendReceiver\":null,\"sendBlock\":null,\"sendArgs\":[],\"sourceSpan\":{\"start\":[2,12],\"end\":[2,13]},\"sendSelector\":{\"term\":\"Identifier\",\"name\":\"c\",\"sourceRange\":[22,23],\"sourceSpan\":{\"start\":[2,12],\"end\":[2,13]}}},\"term\":\"LowAnd\",\"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" - - -diffFixtures :: [(String, [BlobPair] -> TaskEff Builder, [Both File], ByteString)] +diffFixtures :: [(String, [BlobPair] -> TaskEff Builder, [Both File], FilePath)] diffFixtures = - [ (show JSONDiffRenderer, runDiff JSONDiffRenderer, pathMode, jsonOutput) - , (show SExpressionDiffRenderer, runDiff SExpressionDiffRenderer, pathMode, sExpressionOutput) - , (show ToCDiffRenderer, runDiff ToCDiffRenderer, pathMode, tocOutput) + [ (show JSONDiffRenderer, runDiff JSONDiffRenderer, pathMode, prefix "diff-tree.json") + , (show SExpressionDiffRenderer, runDiff SExpressionDiffRenderer, pathMode, "test/fixtures/ruby/corpus/method-declaration.diffA-B.txt") + , (show ToCDiffRenderer, runDiff ToCDiffRenderer, pathMode, prefix "diff-tree.toc.json") ] 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\":{\"term\":\"Program\",\"children\":[{\"merge\":{\"after\":{\"sourceRange\":[0,20],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,4]}},\"methodParameters\":[{\"patch\":{\"insert\":{\"term\":\"Identifier\",\"name\":\"a\",\"sourceRange\":[8,9],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,10]}}}}],\"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]}}]}},\"methodContext\":[],\"methodReceiver\":{\"merge\":{\"after\":{\"sourceRange\":[0,0],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,1]}},\"term\":\"Empty\",\"before\":{\"sourceRange\":[0,0],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,1]}}}},\"term\":\"Method\",\"methodBody\":{\"merge\":{\"after\":{\"sourceRange\":[13,16],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,6]}},\"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]}}}},\"before\":{\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,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" + prefix = "test/fixtures/cli" diff --git a/test/fixtures/cli/diff-tree.json b/test/fixtures/cli/diff-tree.json new file mode 100644 index 000000000..63786e67a --- /dev/null +++ b/test/fixtures/cli/diff-tree.json @@ -0,0 +1,198 @@ +{ + "diffs": [ + { + "diff": + { + "merge": + { + "term": "Program", + "children": [ + { + "merge": + { + "term": "Method", + "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] + } + } + } + }, + "methodContext": [], + "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] + } + } + } + }], + "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] + } + } + } + }, + "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" + }] + } + }] +} diff --git a/test/fixtures/cli/diff-tree.toc.json b/test/fixtures/cli/diff-tree.toc.json new file mode 100644 index 000000000..01b42fe92 --- /dev/null +++ b/test/fixtures/cli/diff-tree.toc.json @@ -0,0 +1,18 @@ +{ + "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": + {} +} diff --git a/test/fixtures/cli/parse-tree-empty.json b/test/fixtures/cli/parse-tree-empty.json new file mode 100644 index 000000000..ec8e3347d --- /dev/null +++ b/test/fixtures/cli/parse-tree-empty.json @@ -0,0 +1,3 @@ +{ + "trees": [] +} diff --git a/test/fixtures/cli/parse-tree.json b/test/fixtures/cli/parse-tree.json new file mode 100644 index 000000000..67c21e302 --- /dev/null +++ b/test/fixtures/cli/parse-tree.json @@ -0,0 +1,74 @@ +{ + "trees": [ + { + "tree": + { + "term": "Program", + "children": [ + { + "term": "LowAnd", + "children": [ + { + "term": "Send", + "sendArgs": [], + "sendBlock": null, + "sendReceiver": null, + "sendSelector": + { + "term": "Identifier", + "name": "foo", + "sourceRange": [0, 3], + "sourceSpan": + { + "start": [1, 1], + "end": [1, 4] + } + }, + "sourceRange": [0, 3], + "sourceSpan": + { + "start": [1, 1], + "end": [1, 4] + } + }, + { + "term": "Send", + "sendArgs": [], + "sendBlock": null, + "sendReceiver": null, + "sendSelector": + { + "term": "Identifier", + "name": "bar", + "sourceRange": [8, 11], + "sourceSpan": + { + "start": [1, 9], + "end": [1, 12] + } + }, + "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" + }] +} diff --git a/test/fixtures/cli/parse-tree.symbols.json b/test/fixtures/cli/parse-tree.symbols.json new file mode 100644 index 000000000..a02f04676 --- /dev/null +++ b/test/fixtures/cli/parse-tree.symbols.json @@ -0,0 +1,17 @@ +{ + "files": [ + { + "path": "test/fixtures/ruby/corpus/method-declaration.A.rb", + "symbols": [ + { + "span": + { + "start": [1, 1], + "end": [2, 4] + }, + "kind": "Method", + "symbol": "foo" + }], + "language": "Ruby" + }] +} diff --git a/test/fixtures/cli/parse-tree.tags.json b/test/fixtures/cli/parse-tree.tags.json new file mode 100644 index 000000000..dd1281eaa --- /dev/null +++ b/test/fixtures/cli/parse-tree.tags.json @@ -0,0 +1,13 @@ +[ +{ + "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" +}] diff --git a/test/fixtures/cli/parse-trees.json b/test/fixtures/cli/parse-trees.json new file mode 100644 index 000000000..0bd86671c --- /dev/null +++ b/test/fixtures/cli/parse-trees.json @@ -0,0 +1,234 @@ +{ + "trees": [ + { + "tree": + { + "term": "Program", + "children": [ + { + "term": "LowAnd", + "children": [ + { + "term": "Send", + "sendArgs": [], + "sendBlock": null, + "sendReceiver": null, + "sendSelector": + { + "term": "Identifier", + "name": "foo", + "sourceRange": [0, 3], + "sourceSpan": + { + "start": [1, 1], + "end": [1, 4] + } + }, + "sourceRange": [0, 3], + "sourceSpan": + { + "start": [1, 1], + "end": [1, 4] + } + }, + { + "term": "Send", + "sendArgs": [], + "sendBlock": null, + "sendReceiver": null, + "sendSelector": + { + "term": "Identifier", + "name": "bar", + "sourceRange": [8, 11], + "sourceSpan": + { + "start": [1, 9], + "end": [1, 12] + } + }, + "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", + "sendArgs": [], + "sendBlock": null, + "sendReceiver": null, + "sendSelector": + { + "term": "Identifier", + "name": "foo", + "sourceRange": [0, 3], + "sourceSpan": + { + "start": [1, 1], + "end": [1, 4] + } + }, + "sourceRange": [0, 3], + "sourceSpan": + { + "start": [1, 1], + "end": [1, 4] + } + }, + { + "term": "Send", + "sendArgs": [], + "sendBlock": null, + "sendReceiver": null, + "sendSelector": + { + "term": "Identifier", + "name": "bar", + "sourceRange": [7, 10], + "sourceSpan": + { + "start": [1, 8], + "end": [1, 11] + } + }, + "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", + "sendArgs": [], + "sendBlock": null, + "sendReceiver": null, + "sendSelector": + { + "term": "Identifier", + "name": "a", + "sourceRange": [11, 12], + "sourceSpan": + { + "start": [2, 1], + "end": [2, 2] + } + }, + "sourceRange": [11, 12], + "sourceSpan": + { + "start": [2, 1], + "end": [2, 2] + } + }, + { + "term": "Send", + "sendArgs": [], + "sendBlock": null, + "sendReceiver": null, + "sendSelector": + { + "term": "Identifier", + "name": "b", + "sourceRange": [16, 17], + "sourceSpan": + { + "start": [2, 6], + "end": [2, 7] + } + }, + "sourceRange": [16, 17], + "sourceSpan": + { + "start": [2, 6], + "end": [2, 7] + } + }], + "sourceRange": [11, 17], + "sourceSpan": + { + "start": [2, 1], + "end": [2, 7] + } + }, + { + "term": "Send", + "sendArgs": [], + "sendBlock": null, + "sendReceiver": null, + "sendSelector": + { + "term": "Identifier", + "name": "c", + "sourceRange": [22, 23], + "sourceSpan": + { + "start": [2, 12], + "end": [2, 13] + } + }, + "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" + }] +} From 5f135f84fc05edf5b5f9fef358ed5789957e8d36 Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Fri, 1 Jun 2018 11:20:46 -0700 Subject: [PATCH 14/16] No more Program, only Statements --- src/Data/Syntax.hs | 32 +-------------------------- src/Data/Syntax/Statement.hs | 19 ++++++++++++++++ src/Language/Go/Assignment.hs | 5 ++--- src/Language/PHP/Assignment.hs | 5 ++--- src/Language/Python/Assignment.hs | 5 ++--- src/Language/Ruby/Assignment.hs | 5 ++--- src/Language/TypeScript/Assignment.hs | 5 ++--- 7 files changed, 30 insertions(+), 46 deletions(-) diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index 22dc053b2..cbc36e01f 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -3,14 +3,12 @@ module Data.Syntax where import Data.Abstract.Evaluatable -import Data.Aeson (ToJSON(..), ToJSON1(..), object) +import Data.Aeson (ToJSON(..), object) import Data.AST import Data.JSON.Fields import Data.Range import Data.Record import Data.Span -import Data.Semigroup.App -import Data.Semigroup.Foldable import Data.Sum import Data.Term import Diffing.Algorithm hiding (Empty) @@ -150,34 +148,6 @@ instance FreeVariables1 Identifier where instance Declarations1 Identifier where liftDeclaredName _ (Identifier x) = pure x - -newtype Program a = Program (Statements a) - 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 Evaluatable Program where - eval (Program statements) = eval statements - --- | Imperative sequence of statements/declarations s.t.: --- --- 1. Each statement’s effects on the store are accumulated; --- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and --- 3. Only the last statement’s return value is returned. -newtype Statements a = Statements [a] - deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1) - -instance Eq1 Statements where liftEq = genericLiftEq -instance Ord1 Statements where liftCompare = genericLiftCompare -instance Show1 Statements where liftShowsPrec = genericLiftShowsPrec -instance ToJSON1 Statements - -instance Evaluatable Statements where - eval (Statements xs) = maybe (pure (Rval unit)) (runApp . foldMap1 (App . subtermRef)) (nonEmpty 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, ToJSONFields1) diff --git a/src/Data/Syntax/Statement.hs b/src/Data/Syntax/Statement.hs index cea29f2f1..07db118f1 100644 --- a/src/Data/Syntax/Statement.hs +++ b/src/Data/Syntax/Statement.hs @@ -2,12 +2,31 @@ module Data.Syntax.Statement where import Data.Abstract.Evaluatable +import Data.Aeson (ToJSON1 (..)) import Data.ByteString.Char8 (unpack) import Data.JSON.Fields +import Data.Semigroup.App +import Data.Semigroup.Foldable import Diffing.Algorithm import Prelude import Prologue +-- | Imperative sequence of statements/declarations s.t.: +-- +-- 1. Each statement’s effects on the store are accumulated; +-- 2. Each statement can affect the environment of later statements (e.g. by 'modify'-ing the environment); and +-- 3. Only the last statement’s return value is returned. +newtype Statements a = Statements [a] + deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1, ToJSONFields1) + +instance Eq1 Statements where liftEq = genericLiftEq +instance Ord1 Statements where liftCompare = genericLiftCompare +instance Show1 Statements where liftShowsPrec = genericLiftShowsPrec +instance ToJSON1 Statements + +instance Evaluatable Statements where + eval (Statements xs) = maybe (pure (Rval unit)) (runApp . foldMap1 (App . subtermRef)) (nonEmpty xs) + -- | Conditional. This must have an else block, which can be filled with some default value when omitted in the source, e.g. 'pure ()' for C-style if-without-else or 'pure Nothing' for Ruby-style, in both cases assuming some appropriate Applicative context into which the If will be lifted. data If a = If { ifCondition :: !a, ifThenBody :: !a, ifElseBody :: !a } deriving (Diffable, Eq, Foldable, Functor, Generic1, Hashable1, Mergeable, Ord, Show, Traversable, FreeVariables1, Declarations1) diff --git a/src/Language/Go/Assignment.hs b/src/Language/Go/Assignment.hs index c471462f3..7a1547e5b 100644 --- a/src/Language/Go/Assignment.hs +++ b/src/Language/Go/Assignment.hs @@ -86,12 +86,11 @@ type Syntax = , Statement.NoOp , Statement.Pattern , Statement.Return + , Statement.Statements , Syntax.Context , Syntax.Error , Syntax.Empty , Syntax.Identifier - , Syntax.Program - , Syntax.Statements , Type.Annotation , Type.Array , Type.Function @@ -112,7 +111,7 @@ assignment :: Assignment assignment = handleError program <|> parseError program :: Assignment -program = makeTerm <$> symbol SourceFile <*> children (Syntax.Program. Syntax.Statements <$> manyTerm expression) +program = makeTerm <$> symbol SourceFile <*> children (Statement.Statements <$> manyTerm expression) expression :: Assignment expression = term (handleError (choice expressionChoices)) diff --git a/src/Language/PHP/Assignment.hs b/src/Language/PHP/Assignment.hs index 94c4412ae..3c6782d33 100644 --- a/src/Language/PHP/Assignment.hs +++ b/src/Language/PHP/Assignment.hs @@ -72,6 +72,7 @@ type Syntax = '[ , Statement.Match , Statement.Pattern , Statement.Return + , Statement.Statements , Statement.Throw , Statement.Try , Statement.While @@ -115,7 +116,6 @@ type Syntax = '[ , Syntax.NamespaceUseGroupClause , Syntax.NewVariable , Syntax.PrintIntrinsic - , Syntax.Program , Syntax.PropertyDeclaration , Syntax.PropertyModifier , Syntax.QualifiedName @@ -126,7 +126,6 @@ type Syntax = '[ , Syntax.ScalarType , Syntax.ShellCommand , Syntax.SimpleVariable - , Syntax.Statements , Syntax.Static , Syntax.Text , Syntax.TraitDeclaration @@ -145,7 +144,7 @@ type Assignment = Assignment.Assignment [] Grammar Term -- | Assignment from AST in PHP's grammar onto a program in PHP's syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . Syntax.Statements <$> (bookend <$> (text <|> emptyTerm) <*> manyTerm statement <*> (text <|> emptyTerm))) <|> parseError +assignment = handleError $ makeTerm <$> symbol Program <*> children (Statement.Statements <$> (bookend <$> (text <|> emptyTerm) <*> manyTerm statement <*> (text <|> emptyTerm))) <|> parseError text :: Assignment text = makeTerm <$> symbol Text <*> (Syntax.Text <$> source) diff --git a/src/Language/Python/Assignment.hs b/src/Language/Python/Assignment.hs index 2f03af218..66fc051d7 100644 --- a/src/Language/Python/Assignment.hs +++ b/src/Language/Python/Assignment.hs @@ -79,6 +79,7 @@ type Syntax = , Statement.Let , Statement.NoOp , Statement.Return + , Statement.Statements , Statement.Throw , Statement.Try , Statement.While @@ -91,8 +92,6 @@ type Syntax = , Syntax.Empty , Syntax.Error , Syntax.Identifier - , Syntax.Program - , Syntax.Statements , Type.Annotation , [] ] @@ -102,7 +101,7 @@ type Assignment = HasCallStack => Assignment.Assignment [] Grammar Term -- | Assignment from AST in Python's grammar onto a program in Python's syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Module <*> children (Syntax.Program . Syntax.Statements <$> manyTerm expression) <|> parseError +assignment = handleError $ makeTerm <$> symbol Module <*> children (Statement.Statements <$> manyTerm expression) <|> parseError expression :: Assignment expression = handleError (choice expressionChoices) diff --git a/src/Language/Ruby/Assignment.hs b/src/Language/Ruby/Assignment.hs index eef043837..a897de320 100644 --- a/src/Language/Ruby/Assignment.hs +++ b/src/Language/Ruby/Assignment.hs @@ -80,6 +80,7 @@ type Syntax = '[ , Statement.Return , Statement.ScopeEntry , Statement.ScopeExit + , Statement.Statements , Statement.Try , Statement.While , Statement.Yield @@ -87,8 +88,6 @@ type Syntax = '[ , Syntax.Empty , Syntax.Error , Syntax.Identifier - , Syntax.Program - , Syntax.Statements , Ruby.Syntax.Class , Ruby.Syntax.Load , Ruby.Syntax.LowPrecedenceBoolean @@ -104,7 +103,7 @@ type Assignment = Assignment' Term -- | Assignment from AST in Ruby’s grammar onto a program in Ruby’s syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . Syntax.Statements <$> many expression) <|> parseError +assignment = handleError $ makeTerm <$> symbol Program <*> children (Statement.Statements <$> many expression) <|> parseError expression :: Assignment expression = term (handleError (choice expressionChoices)) diff --git a/src/Language/TypeScript/Assignment.hs b/src/Language/TypeScript/Assignment.hs index a01e30515..7a6e5915e 100644 --- a/src/Language/TypeScript/Assignment.hs +++ b/src/Language/TypeScript/Assignment.hs @@ -91,6 +91,7 @@ type Syntax = '[ , Statement.Return , Statement.ScopeEntry , Statement.ScopeExit + , Statement.Statements , Statement.Throw , Statement.Try , Statement.While @@ -99,8 +100,6 @@ type Syntax = '[ , Syntax.Empty , Syntax.Error , Syntax.Identifier - , Syntax.Program - , Syntax.Statements , Syntax.Context , Type.Readonly , Type.TypeParameters @@ -187,7 +186,7 @@ type Assignment = Assignment.Assignment [] Grammar Term -- | Assignment from AST in TypeScript’s grammar onto a program in TypeScript’s syntax. assignment :: Assignment -assignment = handleError $ makeTerm <$> symbol Program <*> children (Syntax.Program . Syntax.Statements <$> manyTerm statement) <|> parseError +assignment = handleError $ makeTerm <$> symbol Program <*> children (Statement.Statements <$> manyTerm statement) <|> parseError expression :: Assignment expression = handleError everything From 359031d7774e4a0bedcd198174c1951cb12f967a Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Fri, 1 Jun 2018 11:44:03 -0700 Subject: [PATCH 15/16] s/Program/Statements in all of the tests --- test/Semantic/Spec.hs | 2 +- test/fixtures/cli/diff-tree.json | 2 +- test/fixtures/cli/parse-tree.json | 2 +- test/fixtures/cli/parse-trees.json | 4 +- .../go/corpus/array-types.diffA-B.txt | 62 ++++++++------ .../go/corpus/array-types.diffB-A.txt | 62 ++++++++------ .../fixtures/go/corpus/array-types.parseA.txt | 2 +- .../fixtures/go/corpus/array-types.parseB.txt | 2 +- .../array-with-implicit-length.diffA-B.txt | 2 +- .../array-with-implicit-length.diffB-A.txt | 2 +- .../array-with-implicit-length.parseA.txt | 2 +- .../array-with-implicit-length.parseB.txt | 2 +- .../corpus/assignment-statements.diffA-B.txt | 19 ++--- .../corpus/assignment-statements.diffB-A.txt | 2 +- .../corpus/assignment-statements.parseA.txt | 2 +- .../corpus/assignment-statements.parseB.txt | 2 +- .../go/corpus/binary-expressions.diffA-B.txt | 27 +++--- .../go/corpus/binary-expressions.diffB-A.txt | 27 +++--- .../go/corpus/binary-expressions.parseA.txt | 2 +- .../go/corpus/binary-expressions.parseB.txt | 2 +- .../go/corpus/call-expressions.diffA-B.txt | 24 ++---- .../go/corpus/call-expressions.diffB-A.txt | 22 ++--- .../go/corpus/call-expressions.parseA.txt | 2 +- .../go/corpus/call-expressions.parseB.txt | 2 +- .../go/corpus/case-statements.diffA-B.txt | 2 +- .../go/corpus/case-statements.diffB-A.txt | 2 +- .../go/corpus/case-statements.parseA.txt | 2 +- .../go/corpus/case-statements.parseB.txt | 2 +- .../go/corpus/channel-types.diffA-B.txt | 19 +++-- .../go/corpus/channel-types.diffB-A.txt | 2 +- .../go/corpus/channel-types.parseA.txt | 2 +- .../go/corpus/channel-types.parseB.txt | 2 +- test/fixtures/go/corpus/comment.diffA-B.txt | 2 +- test/fixtures/go/corpus/comment.diffB-A.txt | 2 +- test/fixtures/go/corpus/comment.parseA.txt | 2 +- test/fixtures/go/corpus/comment.parseB.txt | 2 +- .../const-declarations-with-types.diffA-B.txt | 2 +- .../const-declarations-with-types.diffB-A.txt | 2 +- .../const-declarations-with-types.parseA.txt | 2 +- .../const-declarations-with-types.parseB.txt | 2 +- ...nst-declarations-without-types.diffA-B.txt | 2 +- ...nst-declarations-without-types.diffB-A.txt | 2 +- ...onst-declarations-without-types.parseA.txt | 2 +- ...onst-declarations-without-types.parseB.txt | 2 +- .../const-with-implicit-values.diffA-B.txt | 23 ++--- .../const-with-implicit-values.diffB-A.txt | 23 ++--- .../const-with-implicit-values.parseA.txt | 2 +- .../const-with-implicit-values.parseB.txt | 2 +- .../go/corpus/constructors.diffA-B.txt | 2 +- .../go/corpus/constructors.diffB-A.txt | 2 +- .../go/corpus/constructors.parseA.txt | 2 +- .../go/corpus/constructors.parseB.txt | 2 +- .../go/corpus/float-literals.diffA-B.txt | 2 +- .../go/corpus/float-literals.diffB-A.txt | 2 +- .../go/corpus/float-literals.parseA.txt | 2 +- .../go/corpus/float-literals.parseB.txt | 2 +- .../go/corpus/for-statements.diffA-B.txt | 2 +- .../go/corpus/for-statements.diffB-A.txt | 2 +- .../go/corpus/for-statements.parseA.txt | 2 +- .../go/corpus/for-statements.parseB.txt | 2 +- .../corpus/function-declarations.diffA-B.txt | 2 +- .../corpus/function-declarations.diffB-A.txt | 2 +- .../corpus/function-declarations.parseA.txt | 2 +- .../corpus/function-declarations.parseB.txt | 2 +- .../go/corpus/function-literals.diffA-B.txt | 2 +- .../go/corpus/function-literals.diffB-A.txt | 2 +- .../go/corpus/function-literals.parseA.txt | 2 +- .../go/corpus/function-literals.parseB.txt | 2 +- .../go/corpus/function-types.diffA-B.txt | 2 +- .../go/corpus/function-types.diffB-A.txt | 2 +- .../go/corpus/function-types.parseA.txt | 2 +- .../go/corpus/function-types.parseB.txt | 2 +- .../go-and-defer-statements.diffA-B.txt | 2 +- .../go-and-defer-statements.diffB-A.txt | 2 +- .../corpus/go-and-defer-statements.parseA.txt | 2 +- .../corpus/go-and-defer-statements.parseB.txt | 2 +- .../grouped-import-declarations.diffA-B.txt | 26 +++--- .../grouped-import-declarations.diffB-A.txt | 26 +++--- .../grouped-import-declarations.parseA.txt | 2 +- .../grouped-import-declarations.parseB.txt | 2 +- .../grouped-var-declarations.diffA-B.txt | 2 +- .../grouped-var-declarations.diffB-A.txt | 2 +- .../grouped-var-declarations.parseA.txt | 2 +- .../grouped-var-declarations.parseB.txt | 2 +- .../go/corpus/if-statements.diffA-B.txt | 2 +- .../go/corpus/if-statements.diffB-A.txt | 2 +- .../go/corpus/if-statements.parseA.txt | 2 +- .../go/corpus/if-statements.parseB.txt | 2 +- .../go/corpus/imaginary-literals.diffA-B.txt | 2 +- .../go/corpus/imaginary-literals.diffB-A.txt | 2 +- .../go/corpus/imaginary-literals.parseA.txt | 2 +- .../go/corpus/imaginary-literals.parseB.txt | 2 +- .../go/corpus/import-statements.diffA-B.txt | 2 +- .../go/corpus/import-statements.diffB-A.txt | 2 +- .../go/corpus/import-statements.parseA.txt | 2 +- .../go/corpus/import-statements.parseB.txt | 2 +- ...increment-decrement-statements.diffA-B.txt | 2 +- ...increment-decrement-statements.diffB-A.txt | 2 +- .../increment-decrement-statements.parseA.txt | 2 +- .../increment-decrement-statements.parseB.txt | 2 +- .../go/corpus/int-literals.diffA-B.txt | 2 +- .../go/corpus/int-literals.diffB-A.txt | 2 +- .../go/corpus/int-literals.parseA.txt | 2 +- .../go/corpus/int-literals.parseB.txt | 2 +- .../go/corpus/interface-types.diffA-B.txt | 2 +- .../go/corpus/interface-types.diffB-A.txt | 2 +- .../go/corpus/interface-types.parseA.txt | 2 +- .../go/corpus/interface-types.parseB.txt | 2 +- .../go/corpus/label-statements.diffA-B.txt | 2 +- .../go/corpus/label-statements.diffB-A.txt | 2 +- .../go/corpus/label-statements.parseA.txt | 2 +- .../go/corpus/label-statements.parseB.txt | 2 +- .../go/corpus/map-literals.diffA-B.txt | 2 +- .../go/corpus/map-literals.diffB-A.txt | 2 +- .../go/corpus/map-literals.parseA.txt | 2 +- .../go/corpus/map-literals.parseB.txt | 2 +- test/fixtures/go/corpus/map-types.diffA-B.txt | 2 +- test/fixtures/go/corpus/map-types.diffB-A.txt | 2 +- test/fixtures/go/corpus/map-types.parseA.txt | 2 +- test/fixtures/go/corpus/map-types.parseB.txt | 2 +- .../go/corpus/method-declarations.diffA-B.txt | 2 +- .../go/corpus/method-declarations.diffB-A.txt | 2 +- .../go/corpus/method-declarations.parseA.txt | 2 +- .../go/corpus/method-declarations.parseB.txt | 2 +- .../modifying-struct-fields.diffA-B.txt | 2 +- .../modifying-struct-fields.diffB-A.txt | 2 +- .../corpus/modifying-struct-fields.parseA.txt | 2 +- .../corpus/modifying-struct-fields.parseB.txt | 2 +- ...ameter-declarations-with-types.diffA-B.txt | 2 +- ...ameter-declarations-with-types.diffB-A.txt | 2 +- ...rameter-declarations-with-types.parseA.txt | 2 +- ...rameter-declarations-with-types.parseB.txt | 2 +- .../go/corpus/pointer-types.diffA-B.txt | 2 +- .../go/corpus/pointer-types.diffB-A.txt | 2 +- .../go/corpus/pointer-types.parseA.txt | 2 +- .../go/corpus/pointer-types.parseB.txt | 2 +- .../go/corpus/qualified-types.diffA-B.txt | 2 +- .../go/corpus/qualified-types.diffB-A.txt | 2 +- .../go/corpus/qualified-types.parseA.txt | 2 +- .../go/corpus/qualified-types.parseB.txt | 2 +- .../go/corpus/rune-literals.diffA-B.txt | 2 +- .../go/corpus/rune-literals.diffB-A.txt | 2 +- .../go/corpus/rune-literals.parseA.txt | 2 +- .../go/corpus/rune-literals.parseB.txt | 2 +- .../go/corpus/select-statements.diffA-B.txt | 2 +- .../go/corpus/select-statements.diffB-A.txt | 2 +- .../go/corpus/select-statements.parseA.txt | 2 +- .../go/corpus/select-statements.parseB.txt | 2 +- .../corpus/selector-expressions.diffA-B.txt | 2 +- .../corpus/selector-expressions.diffB-A.txt | 2 +- .../go/corpus/selector-expressions.parseA.txt | 2 +- .../go/corpus/selector-expressions.parseB.txt | 2 +- .../go/corpus/send-statements.diffA-B.txt | 2 +- .../go/corpus/send-statements.diffB-A.txt | 2 +- .../go/corpus/send-statements.parseA.txt | 2 +- .../go/corpus/send-statements.parseB.txt | 2 +- .../corpus/short-var-declarations.diffA-B.txt | 2 +- .../corpus/short-var-declarations.diffB-A.txt | 2 +- .../corpus/short-var-declarations.parseA.txt | 2 +- .../corpus/short-var-declarations.parseB.txt | 2 +- .../single-import-declarations.diffA-B.txt | 2 +- .../single-import-declarations.diffB-A.txt | 2 +- .../single-import-declarations.parseA.txt | 2 +- .../single-import-declarations.parseB.txt | 2 +- ...gle-line-function-declarations.diffA-B.txt | 2 +- ...gle-line-function-declarations.diffB-A.txt | 2 +- ...ngle-line-function-declarations.parseA.txt | 2 +- ...ngle-line-function-declarations.parseB.txt | 2 +- .../go/corpus/slice-expressions.diffA-B.txt | 53 +++++++----- .../go/corpus/slice-expressions.diffB-A.txt | 40 +++++---- .../go/corpus/slice-expressions.parseA.txt | 2 +- .../go/corpus/slice-expressions.parseB.txt | 2 +- .../go/corpus/slice-literals.diffA-B.txt | 2 +- .../go/corpus/slice-literals.diffB-A.txt | 2 +- .../go/corpus/slice-literals.parseA.txt | 2 +- .../go/corpus/slice-literals.parseB.txt | 2 +- .../go/corpus/slice-types.diffA-B.txt | 2 +- .../go/corpus/slice-types.diffB-A.txt | 2 +- .../fixtures/go/corpus/slice-types.parseA.txt | 2 +- .../fixtures/go/corpus/slice-types.parseB.txt | 2 +- .../go/corpus/string-literals.diffA-B.txt | 2 +- .../go/corpus/string-literals.diffB-A.txt | 2 +- .../go/corpus/string-literals.parseA.txt | 2 +- .../go/corpus/string-literals.parseB.txt | 2 +- .../struct-field-declarations.diffA-B.txt | 2 +- .../struct-field-declarations.diffB-A.txt | 2 +- .../struct-field-declarations.parseA.txt | 2 +- .../struct-field-declarations.parseB.txt | 2 +- .../go/corpus/struct-literals.diffA-B.txt | 2 +- .../go/corpus/struct-literals.diffB-A.txt | 2 +- .../go/corpus/struct-literals.parseA.txt | 2 +- .../go/corpus/struct-literals.parseB.txt | 2 +- .../go/corpus/struct-types.diffA-B.txt | 2 +- .../go/corpus/struct-types.diffB-A.txt | 2 +- .../go/corpus/struct-types.parseA.txt | 2 +- .../go/corpus/struct-types.parseB.txt | 2 +- .../go/corpus/switch-statements.diffA-B.txt | 54 +++++------- .../go/corpus/switch-statements.diffB-A.txt | 40 ++++----- .../go/corpus/switch-statements.parseA.txt | 2 +- .../go/corpus/switch-statements.parseB.txt | 2 +- .../go/corpus/type-aliases.diffA-B.txt | 2 +- .../go/corpus/type-aliases.diffB-A.txt | 2 +- .../go/corpus/type-aliases.parseA.txt | 2 +- .../go/corpus/type-aliases.parseB.txt | 2 +- .../type-assertion-expressions.diffA-B.txt | 2 +- .../type-assertion-expressions.diffB-A.txt | 2 +- .../type-assertion-expressions.parseA.txt | 2 +- .../type-assertion-expressions.parseB.txt | 2 +- .../type-conversion-expressions.diffA-B.txt | 2 +- .../type-conversion-expressions.diffB-A.txt | 2 +- .../type-conversion-expressions.parseA.txt | 2 +- .../type-conversion-expressions.parseB.txt | 2 +- .../go/corpus/type-declarations.diffA-B.txt | 2 +- .../go/corpus/type-declarations.diffB-A.txt | 2 +- .../go/corpus/type-declarations.parseA.txt | 2 +- .../go/corpus/type-declarations.parseB.txt | 2 +- .../corpus/type-switch-statements.diffA-B.txt | 2 +- .../corpus/type-switch-statements.diffB-A.txt | 2 +- .../corpus/type-switch-statements.parseA.txt | 2 +- .../corpus/type-switch-statements.parseB.txt | 2 +- .../go/corpus/unary-expressions.diffA-B.txt | 56 ++++++++----- .../go/corpus/unary-expressions.diffB-A.txt | 56 ++++++++----- .../go/corpus/unary-expressions.parseA.txt | 2 +- .../go/corpus/unary-expressions.parseB.txt | 2 +- ...clarations-with-no-expressions.diffA-B.txt | 2 +- ...clarations-with-no-expressions.diffB-A.txt | 2 +- ...eclarations-with-no-expressions.parseA.txt | 2 +- ...eclarations-with-no-expressions.parseB.txt | 2 +- .../var-declarations-with-types.diffA-B.txt | 2 +- .../var-declarations-with-types.diffB-A.txt | 2 +- .../var-declarations-with-types.parseA.txt | 2 +- .../var-declarations-with-types.parseB.txt | 2 +- ...var-declarations-without-types.diffA-B.txt | 2 +- ...var-declarations-without-types.diffB-A.txt | 2 +- .../var-declarations-without-types.parseA.txt | 2 +- .../var-declarations-without-types.parseB.txt | 2 +- ...variadic-function-declarations.diffA-B.txt | 2 +- ...variadic-function-declarations.diffB-A.txt | 2 +- .../variadic-function-declarations.parseA.txt | 2 +- .../variadic-function-declarations.parseB.txt | 2 +- .../corpus/anonymous-function.diffA-B.txt | 2 +- .../corpus/anonymous-function.diffB-A.txt | 2 +- .../corpus/anonymous-function.parseA.txt | 2 +- .../corpus/anonymous-function.parseB.txt | 2 +- ...onymous-parameterless-function.diffA-B.txt | 2 +- ...onymous-parameterless-function.diffB-A.txt | 2 +- ...nonymous-parameterless-function.parseA.txt | 2 +- ...nonymous-parameterless-function.parseB.txt | 2 +- .../javascript/corpus/array.diffA-B.txt | 2 +- .../javascript/corpus/array.diffB-A.txt | 2 +- .../javascript/corpus/array.parseA.txt | 2 +- .../javascript/corpus/array.parseB.txt | 2 +- .../corpus/arrow-function.diffA-B.txt | 2 +- .../corpus/arrow-function.diffB-A.txt | 2 +- .../corpus/arrow-function.parseA.txt | 2 +- .../corpus/arrow-function.parseB.txt | 2 +- .../corpus/assignment-pattern.diffA-B.txt | 2 +- .../corpus/assignment-pattern.diffB-A.txt | 2 +- .../corpus/assignment-pattern.parseA.txt | 2 +- .../corpus/assignment-pattern.parseB.txt | 2 +- .../javascript/corpus/assignment.diffA-B.txt | 2 +- .../javascript/corpus/assignment.diffB-A.txt | 2 +- .../javascript/corpus/assignment.parseA.txt | 2 +- .../javascript/corpus/assignment.parseB.txt | 2 +- .../corpus/bitwise-operator.diffA-B.txt | 2 +- .../corpus/bitwise-operator.diffB-A.txt | 2 +- .../corpus/bitwise-operator.parseA.txt | 2 +- .../corpus/bitwise-operator.parseB.txt | 2 +- .../corpus/boolean-operator.diffA-B.txt | 2 +- .../corpus/boolean-operator.diffB-A.txt | 2 +- .../corpus/boolean-operator.parseA.txt | 2 +- .../corpus/boolean-operator.parseB.txt | 2 +- .../javascript/corpus/break.diffA-B.txt | 2 +- .../javascript/corpus/break.diffB-A.txt | 2 +- .../javascript/corpus/break.parseA.txt | 2 +- .../javascript/corpus/break.parseB.txt | 2 +- .../corpus/chained-callbacks.diffA-B.txt | 2 +- .../corpus/chained-callbacks.diffB-A.txt | 2 +- .../corpus/chained-callbacks.parseA.txt | 2 +- .../corpus/chained-callbacks.parseB.txt | 2 +- .../chained-property-access.diffA-B.txt | 2 +- .../chained-property-access.diffB-A.txt | 2 +- .../corpus/chained-property-access.parseA.txt | 2 +- .../corpus/chained-property-access.parseB.txt | 2 +- .../javascript/corpus/class.diffA-B.txt | 2 +- .../javascript/corpus/class.diffB-A.txt | 2 +- .../javascript/corpus/class.parseA.txt | 2 +- .../javascript/corpus/class.parseB.txt | 2 +- .../corpus/comma-operator.diffA-B.txt | 2 +- .../corpus/comma-operator.diffB-A.txt | 2 +- .../corpus/comma-operator.parseA.txt | 2 +- .../corpus/comma-operator.parseB.txt | 2 +- .../javascript/corpus/comment.diffA-B.txt | 2 +- .../javascript/corpus/comment.diffB-A.txt | 2 +- .../javascript/corpus/comment.parseA.txt | 2 +- .../javascript/corpus/comment.parseB.txt | 2 +- .../corpus/constructor-call.diffA-B.txt | 2 +- .../corpus/constructor-call.diffB-A.txt | 2 +- .../corpus/constructor-call.parseA.txt | 2 +- .../corpus/constructor-call.parseB.txt | 2 +- .../javascript/corpus/continue.diffA-B.txt | 2 +- .../javascript/corpus/continue.diffB-A.txt | 2 +- .../javascript/corpus/continue.parseA.txt | 2 +- .../javascript/corpus/continue.parseB.txt | 2 +- .../corpus/delete-operator.diffA-B.txt | 2 +- .../corpus/delete-operator.diffB-A.txt | 2 +- .../corpus/delete-operator.parseA.txt | 2 +- .../corpus/delete-operator.parseB.txt | 2 +- .../corpus/do-while-statement.diffA-B.txt | 2 +- .../corpus/do-while-statement.diffB-A.txt | 2 +- .../corpus/do-while-statement.parseA.txt | 2 +- .../corpus/do-while-statement.parseB.txt | 2 +- .../javascript/corpus/export.diffA-B.txt | 20 ++--- .../javascript/corpus/export.diffB-A.txt | 22 ++--- .../javascript/corpus/export.parseA.txt | 2 +- .../javascript/corpus/export.parseB.txt | 2 +- .../javascript/corpus/false.diffA-B.txt | 2 +- .../javascript/corpus/false.diffB-A.txt | 2 +- .../javascript/corpus/false.parseA.txt | 2 +- .../javascript/corpus/false.parseB.txt | 2 +- .../corpus/for-in-statement.diffA-B.txt | 2 +- .../corpus/for-in-statement.diffB-A.txt | 2 +- .../corpus/for-in-statement.parseA.txt | 2 +- .../corpus/for-in-statement.parseB.txt | 2 +- .../for-loop-with-in-statement.diffA-B.txt | 2 +- .../for-loop-with-in-statement.diffB-A.txt | 2 +- .../for-loop-with-in-statement.parseA.txt | 2 +- .../for-loop-with-in-statement.parseB.txt | 2 +- .../corpus/for-of-statement.diffA-B.txt | 2 +- .../corpus/for-of-statement.diffB-A.txt | 2 +- .../corpus/for-of-statement.parseA.txt | 2 +- .../corpus/for-of-statement.parseB.txt | 2 +- .../corpus/for-statement.diffA-B.txt | 2 +- .../corpus/for-statement.diffB-A.txt | 2 +- .../corpus/for-statement.parseA.txt | 2 +- .../corpus/for-statement.parseB.txt | 2 +- .../corpus/function-call-args.diffA-B.txt | 2 +- .../corpus/function-call-args.diffB-A.txt | 2 +- .../corpus/function-call-args.parseA.txt | 2 +- .../corpus/function-call-args.parseB.txt | 2 +- .../corpus/function-call.diffA-B.txt | 2 +- .../corpus/function-call.diffB-A.txt | 2 +- .../corpus/function-call.parseA.txt | 2 +- .../corpus/function-call.parseB.txt | 2 +- .../javascript/corpus/function.diffA-B.txt | 2 +- .../javascript/corpus/function.diffB-A.txt | 2 +- .../javascript/corpus/function.parseA.txt | 2 +- .../javascript/corpus/function.parseB.txt | 2 +- .../corpus/generator-function.diffA-B.txt | 2 +- .../corpus/generator-function.diffB-A.txt | 2 +- .../corpus/generator-function.parseA.txt | 2 +- .../corpus/generator-function.parseB.txt | 2 +- .../javascript/corpus/identifier.diffA-B.txt | 2 +- .../javascript/corpus/identifier.diffB-A.txt | 2 +- .../javascript/corpus/identifier.parseA.txt | 2 +- .../javascript/corpus/identifier.parseB.txt | 2 +- .../javascript/corpus/if-else.diffA-B.txt | 2 +- .../javascript/corpus/if-else.diffB-A.txt | 2 +- .../javascript/corpus/if-else.parseA.txt | 2 +- .../javascript/corpus/if-else.parseB.txt | 2 +- .../fixtures/javascript/corpus/if.diffA-B.txt | 2 +- .../fixtures/javascript/corpus/if.diffB-A.txt | 2 +- test/fixtures/javascript/corpus/if.parseA.txt | 2 +- test/fixtures/javascript/corpus/if.parseB.txt | 2 +- .../javascript/corpus/import.diffA-B.txt | 6 +- .../javascript/corpus/import.diffB-A.txt | 6 +- .../javascript/corpus/import.parseA.txt | 2 +- .../javascript/corpus/import.parseB.txt | 2 +- .../math-assignment-operator.diffA-B.txt | 2 +- .../math-assignment-operator.diffB-A.txt | 2 +- .../math-assignment-operator.parseA.txt | 2 +- .../math-assignment-operator.parseB.txt | 2 +- .../corpus/math-operator.diffA-B.txt | 2 +- .../corpus/math-operator.diffB-A.txt | 2 +- .../corpus/math-operator.parseA.txt | 2 +- .../corpus/math-operator.parseB.txt | 2 +- .../member-access-assignment.diffA-B.txt | 2 +- .../member-access-assignment.diffB-A.txt | 2 +- .../member-access-assignment.parseA.txt | 2 +- .../member-access-assignment.parseB.txt | 2 +- .../corpus/member-access.diffA-B.txt | 2 +- .../corpus/member-access.diffB-A.txt | 2 +- .../corpus/member-access.parseA.txt | 2 +- .../corpus/member-access.parseB.txt | 2 +- .../javascript/corpus/method-call.diffA-B.txt | 2 +- .../javascript/corpus/method-call.diffB-A.txt | 2 +- .../javascript/corpus/method-call.parseA.txt | 2 +- .../javascript/corpus/method-call.parseB.txt | 2 +- .../corpus/named-function.diffA-B.txt | 2 +- .../corpus/named-function.diffB-A.txt | 2 +- .../corpus/named-function.parseA.txt | 2 +- .../corpus/named-function.parseB.txt | 2 +- .../nested-do-while-in-function.diffA-B.txt | 2 +- .../nested-do-while-in-function.diffB-A.txt | 2 +- .../nested-do-while-in-function.parseA.txt | 2 +- .../nested-do-while-in-function.parseB.txt | 2 +- .../corpus/nested-functions.diffA-B.txt | 2 +- .../corpus/nested-functions.diffB-A.txt | 2 +- .../corpus/nested-functions.parseA.txt | 2 +- .../corpus/nested-functions.parseB.txt | 2 +- .../javascript/corpus/null.diffA-B.txt | 2 +- .../javascript/corpus/null.diffB-A.txt | 2 +- .../javascript/corpus/null.parseA.txt | 2 +- .../javascript/corpus/null.parseB.txt | 2 +- .../javascript/corpus/number.diffA-B.txt | 2 +- .../javascript/corpus/number.diffB-A.txt | 2 +- .../javascript/corpus/number.parseA.txt | 2 +- .../javascript/corpus/number.parseB.txt | 2 +- .../javascript/corpus/object.diffA-B.txt | 2 +- .../javascript/corpus/object.diffB-A.txt | 2 +- .../javascript/corpus/object.parseA.txt | 2 +- .../javascript/corpus/object.parseB.txt | 2 +- .../corpus/objects-with-methods.diffA-B.txt | 2 +- .../corpus/objects-with-methods.diffB-A.txt | 2 +- .../corpus/objects-with-methods.parseA.txt | 2 +- .../corpus/objects-with-methods.parseB.txt | 2 +- .../javascript/corpus/regex.diffA-B.txt | 2 +- .../javascript/corpus/regex.diffB-A.txt | 2 +- .../javascript/corpus/regex.parseA.txt | 2 +- .../javascript/corpus/regex.parseB.txt | 2 +- .../corpus/relational-operator.diffA-B.txt | 2 +- .../corpus/relational-operator.diffB-A.txt | 2 +- .../corpus/relational-operator.parseA.txt | 2 +- .../corpus/relational-operator.parseB.txt | 2 +- .../corpus/return-statement.diffA-B.txt | 2 +- .../corpus/return-statement.diffB-A.txt | 2 +- .../corpus/return-statement.parseA.txt | 2 +- .../corpus/return-statement.parseB.txt | 2 +- .../javascript/corpus/string.diffA-B.txt | 2 +- .../javascript/corpus/string.diffB-A.txt | 2 +- .../javascript/corpus/string.parseA.txt | 2 +- .../javascript/corpus/string.parseB.txt | 2 +- .../subscript-access-assignment.diffA-B.txt | 2 +- .../subscript-access-assignment.diffB-A.txt | 2 +- .../subscript-access-assignment.parseA.txt | 2 +- .../subscript-access-assignment.parseB.txt | 2 +- .../subscript-access-string.diffA-B.txt | 2 +- .../subscript-access-string.diffB-A.txt | 2 +- .../corpus/subscript-access-string.parseA.txt | 2 +- .../corpus/subscript-access-string.parseB.txt | 2 +- .../subscript-access-variable.diffA-B.txt | 2 +- .../subscript-access-variable.diffB-A.txt | 2 +- .../subscript-access-variable.parseA.txt | 2 +- .../subscript-access-variable.parseB.txt | 2 +- .../corpus/switch-statement.diffA-B.txt | 2 +- .../corpus/switch-statement.diffB-A.txt | 2 +- .../corpus/switch-statement.parseA.txt | 2 +- .../corpus/switch-statement.parseB.txt | 2 +- .../corpus/template-string.diffA-B.txt | 2 +- .../corpus/template-string.diffB-A.txt | 2 +- .../corpus/template-string.parseA.txt | 2 +- .../corpus/template-string.parseB.txt | 2 +- .../javascript/corpus/ternary.diffA-B.txt | 2 +- .../javascript/corpus/ternary.diffB-A.txt | 2 +- .../javascript/corpus/ternary.parseA.txt | 2 +- .../javascript/corpus/ternary.parseB.txt | 2 +- .../corpus/this-expression.diffA-B.txt | 2 +- .../corpus/this-expression.diffB-A.txt | 2 +- .../corpus/this-expression.parseA.txt | 2 +- .../corpus/this-expression.parseB.txt | 2 +- .../corpus/throw-statement.diffA-B.txt | 2 +- .../corpus/throw-statement.diffB-A.txt | 2 +- .../corpus/throw-statement.parseA.txt | 2 +- .../corpus/throw-statement.parseB.txt | 2 +- .../javascript/corpus/true.diffA-B.txt | 2 +- .../javascript/corpus/true.diffB-A.txt | 2 +- .../javascript/corpus/true.parseA.txt | 2 +- .../javascript/corpus/true.parseB.txt | 2 +- .../corpus/try-statement.diffA-B.txt | 2 +- .../corpus/try-statement.diffB-A.txt | 2 +- .../corpus/try-statement.parseA.txt | 2 +- .../corpus/try-statement.parseB.txt | 2 +- .../corpus/type-operator.diffA-B.txt | 2 +- .../corpus/type-operator.diffB-A.txt | 2 +- .../corpus/type-operator.parseA.txt | 2 +- .../corpus/type-operator.parseB.txt | 2 +- .../javascript/corpus/undefined.diffA-B.txt | 2 +- .../javascript/corpus/undefined.diffB-A.txt | 2 +- .../javascript/corpus/undefined.parseA.txt | 2 +- .../javascript/corpus/undefined.parseB.txt | 2 +- .../corpus/var-declaration.diffA-B.txt | 2 +- .../corpus/var-declaration.diffB-A.txt | 2 +- .../corpus/var-declaration.parseA.txt | 2 +- .../corpus/var-declaration.parseB.txt | 2 +- .../javascript/corpus/variable.diffA-B.txt | 2 +- .../javascript/corpus/variable.diffB-A.txt | 2 +- .../javascript/corpus/variable.parseA.txt | 2 +- .../javascript/corpus/variable.parseB.txt | 2 +- .../corpus/void-operator.diffA-B.txt | 2 +- .../corpus/void-operator.diffB-A.txt | 2 +- .../corpus/void-operator.parseA.txt | 2 +- .../corpus/void-operator.parseB.txt | 2 +- .../corpus/while-statement.diffA-B.txt | 2 +- .../corpus/while-statement.diffB-A.txt | 2 +- .../corpus/while-statement.parseA.txt | 2 +- .../corpus/while-statement.parseB.txt | 2 +- .../javascript/corpus/yield.diffA-B.txt | 2 +- .../javascript/corpus/yield.diffB-A.txt | 2 +- .../javascript/corpus/yield.parseA.txt | 2 +- .../javascript/corpus/yield.parseB.txt | 2 +- .../corpus/assert-statement.diffA-B.txt | 2 +- .../corpus/assert-statement.diffB-A.txt | 2 +- .../python/corpus/assert-statement.parseA.txt | 2 +- .../python/corpus/assert-statement.parseB.txt | 2 +- .../python/corpus/assignment.diffA-B.txt | 20 +++-- .../python/corpus/assignment.diffB-A.txt | 15 ++-- .../python/corpus/assignment.parseA.txt | 2 +- .../python/corpus/assignment.parseB.txt | 2 +- .../async-function-definition.diffA-B.txt | 2 +- .../async-function-definition.diffB-A.txt | 2 +- .../async-function-definition.parseA.txt | 2 +- .../async-function-definition.parseB.txt | 2 +- .../python/corpus/attribute.diffA-B.txt | 2 +- .../python/corpus/attribute.diffB-A.txt | 2 +- .../python/corpus/attribute.parseA.txt | 2 +- .../python/corpus/attribute.parseB.txt | 2 +- .../corpus/augmented-assignment.diffA-B.txt | 2 +- .../corpus/augmented-assignment.diffB-A.txt | 19 +++-- .../corpus/augmented-assignment.parseA.txt | 2 +- .../corpus/augmented-assignment.parseB.txt | 2 +- test/fixtures/python/corpus/await.diffA-B.txt | 2 +- test/fixtures/python/corpus/await.diffB-A.txt | 2 +- test/fixtures/python/corpus/await.parseA.txt | 2 +- test/fixtures/python/corpus/await.parseB.txt | 2 +- .../python/corpus/binary-operator.diffA-B.txt | 2 +- .../python/corpus/binary-operator.diffB-A.txt | 2 +- .../python/corpus/binary-operator.parseA.txt | 2 +- .../python/corpus/binary-operator.parseB.txt | 2 +- .../corpus/boolean-operator.diffA-B.txt | 2 +- .../corpus/boolean-operator.diffB-A.txt | 2 +- .../python/corpus/boolean-operator.parseA.txt | 2 +- .../python/corpus/boolean-operator.parseB.txt | 2 +- .../python/corpus/boolean.diffA-B.txt | 2 +- .../python/corpus/boolean.diffB-A.txt | 2 +- .../fixtures/python/corpus/boolean.parseA.txt | 2 +- .../fixtures/python/corpus/boolean.parseB.txt | 2 +- .../python/corpus/break-statement.diffA-B.txt | 2 +- .../python/corpus/break-statement.diffB-A.txt | 2 +- .../python/corpus/break-statement.parseA.txt | 2 +- .../python/corpus/break-statement.parseB.txt | 2 +- test/fixtures/python/corpus/call.diffA-B.txt | 2 +- test/fixtures/python/corpus/call.diffB-A.txt | 2 +- test/fixtures/python/corpus/call.parseA.txt | 2 +- test/fixtures/python/corpus/call.parseB.txt | 2 +- .../corpus/class-definition.diffA-B.txt | 2 +- .../corpus/class-definition.diffB-A.txt | 2 +- .../python/corpus/class-definition.parseA.txt | 2 +- .../python/corpus/class-definition.parseB.txt | 2 +- .../python/corpus/comment.diffA-B.txt | 2 +- .../python/corpus/comment.diffB-A.txt | 2 +- .../fixtures/python/corpus/comment.parseA.txt | 2 +- .../fixtures/python/corpus/comment.parseB.txt | 2 +- .../corpus/comparison-operator.diffA-B.txt | 23 +++-- .../corpus/comparison-operator.diffB-A.txt | 36 ++++---- .../corpus/comparison-operator.parseA.txt | 2 +- .../corpus/comparison-operator.parseB.txt | 2 +- .../corpus/concatenated-string.diffA-B.txt | 2 +- .../corpus/concatenated-string.diffB-A.txt | 2 +- .../corpus/concatenated-string.parseA.txt | 2 +- .../corpus/concatenated-string.parseB.txt | 2 +- .../corpus/conditional-expression.diffA-B.txt | 2 +- .../corpus/conditional-expression.diffB-A.txt | 2 +- .../corpus/conditional-expression.parseA.txt | 2 +- .../corpus/conditional-expression.parseB.txt | 2 +- .../corpus/continue-statement.diffA-B.txt | 2 +- .../corpus/continue-statement.diffB-A.txt | 2 +- .../corpus/continue-statement.parseA.txt | 2 +- .../corpus/continue-statement.parseB.txt | 2 +- .../corpus/decorated-definition.diffA-B.txt | 2 +- .../corpus/decorated-definition.diffB-A.txt | 2 +- .../corpus/decorated-definition.parseA.txt | 2 +- .../corpus/decorated-definition.parseB.txt | 2 +- .../corpus/delete-statement.diffA-B.txt | 2 +- .../corpus/delete-statement.diffB-A.txt | 2 +- .../python/corpus/delete-statement.parseA.txt | 2 +- .../python/corpus/delete-statement.parseB.txt | 2 +- .../dictionary-comprehension.diffA-B.txt | 2 +- .../dictionary-comprehension.diffB-A.txt | 2 +- .../dictionary-comprehension.parseA.txt | 2 +- .../dictionary-comprehension.parseB.txt | 2 +- .../python/corpus/dictionary.diffA-B.txt | 2 +- .../python/corpus/dictionary.diffB-A.txt | 2 +- .../python/corpus/dictionary.parseA.txt | 2 +- .../python/corpus/dictionary.parseB.txt | 2 +- .../python/corpus/dotted-name.diffA-B.txt | 2 +- .../python/corpus/dotted-name.diffB-A.txt | 2 +- .../python/corpus/dotted-name.parseA.txt | 2 +- .../python/corpus/dotted-name.parseB.txt | 2 +- .../python/corpus/ellipsis.diffA-B.txt | 2 +- .../python/corpus/ellipsis.diffB-A.txt | 2 +- .../python/corpus/ellipsis.parseA.txt | 2 +- .../python/corpus/ellipsis.parseB.txt | 2 +- .../python/corpus/exec-statement.diffA-B.txt | 2 +- .../python/corpus/exec-statement.diffB-A.txt | 2 +- .../python/corpus/exec-statement.parseA.txt | 2 +- .../python/corpus/exec-statement.parseB.txt | 2 +- .../corpus/expression-statement.diffA-B.txt | 2 +- .../corpus/expression-statement.diffB-A.txt | 2 +- .../corpus/expression-statement.parseA.txt | 2 +- .../corpus/expression-statement.parseB.txt | 2 +- test/fixtures/python/corpus/float.diffA-B.txt | 2 +- test/fixtures/python/corpus/float.diffB-A.txt | 2 +- test/fixtures/python/corpus/float.parseA.txt | 2 +- test/fixtures/python/corpus/float.parseB.txt | 2 +- .../python/corpus/for-statement.diffA-B.txt | 2 +- .../python/corpus/for-statement.diffB-A.txt | 2 +- .../python/corpus/for-statement.parseA.txt | 2 +- .../python/corpus/for-statement.parseB.txt | 2 +- .../corpus/function-definition.diffA-B.txt | 2 +- .../corpus/function-definition.diffB-A.txt | 2 +- .../corpus/function-definition.parseA.txt | 2 +- .../corpus/function-definition.parseB.txt | 2 +- .../corpus/generator-expression.diffA-B.txt | 2 +- .../corpus/generator-expression.diffB-A.txt | 2 +- .../corpus/generator-expression.parseA.txt | 2 +- .../corpus/generator-expression.parseB.txt | 2 +- .../corpus/global-statement.diffA-B.txt | 2 +- .../corpus/global-statement.diffB-A.txt | 2 +- .../python/corpus/global-statement.parseA.txt | 2 +- .../python/corpus/global-statement.parseB.txt | 2 +- .../python/corpus/identifier.diffA-B.txt | 2 +- .../python/corpus/identifier.diffB-A.txt | 2 +- .../python/corpus/identifier.parseA.txt | 2 +- .../python/corpus/identifier.parseB.txt | 2 +- .../python/corpus/if-statement.diffA-B.txt | 2 +- .../python/corpus/if-statement.diffB-A.txt | 2 +- .../python/corpus/if-statement.parseA.txt | 2 +- .../python/corpus/if-statement.parseB.txt | 2 +- .../corpus/import-from-statement.diffA-B.txt | 6 +- .../corpus/import-from-statement.diffB-A.txt | 8 +- .../corpus/import-from-statement.parseA.txt | 2 +- .../corpus/import-from-statement.parseB.txt | 2 +- .../corpus/import-statement.diffA-B.txt | 2 +- .../corpus/import-statement.diffB-A.txt | 2 +- .../python/corpus/import-statement.parseA.txt | 2 +- .../python/corpus/import-statement.parseB.txt | 2 +- .../python/corpus/integer.diffA-B.txt | 2 +- .../python/corpus/integer.diffB-A.txt | 2 +- .../fixtures/python/corpus/integer.parseA.txt | 2 +- .../fixtures/python/corpus/integer.parseB.txt | 2 +- .../corpus/keyword-identifier.diffA-B.txt | 2 +- .../corpus/keyword-identifier.diffB-A.txt | 2 +- .../corpus/keyword-identifier.parseA.txt | 2 +- .../corpus/keyword-identifier.parseB.txt | 2 +- .../fixtures/python/corpus/lambda.diffA-B.txt | 2 +- .../fixtures/python/corpus/lambda.diffB-A.txt | 2 +- test/fixtures/python/corpus/lambda.parseA.txt | 2 +- test/fixtures/python/corpus/lambda.parseB.txt | 2 +- .../corpus/list-comprehension.diffA-B.txt | 2 +- .../corpus/list-comprehension.diffB-A.txt | 2 +- .../corpus/list-comprehension.parseA.txt | 2 +- .../corpus/list-comprehension.parseB.txt | 2 +- test/fixtures/python/corpus/list.diffA-B.txt | 2 +- test/fixtures/python/corpus/list.diffB-A.txt | 2 +- test/fixtures/python/corpus/list.parseA.txt | 2 +- test/fixtures/python/corpus/list.parseB.txt | 2 +- .../corpus/non-local-statement.diffA-B.txt | 2 +- .../corpus/non-local-statement.diffB-A.txt | 2 +- .../corpus/non-local-statement.parseA.txt | 2 +- .../corpus/non-local-statement.parseB.txt | 2 +- test/fixtures/python/corpus/none.diffA-B.txt | 2 +- test/fixtures/python/corpus/none.diffB-A.txt | 2 +- test/fixtures/python/corpus/none.parseA.txt | 2 +- test/fixtures/python/corpus/none.parseB.txt | 2 +- test/fixtures/python/corpus/not.diffA-B.txt | 2 +- test/fixtures/python/corpus/not.diffB-A.txt | 2 +- test/fixtures/python/corpus/not.parseA.txt | 2 +- test/fixtures/python/corpus/not.parseB.txt | 2 +- .../python/corpus/pass-statement.diffA-B.txt | 2 +- .../python/corpus/pass-statement.diffB-A.txt | 2 +- .../python/corpus/pass-statement.parseA.txt | 2 +- .../python/corpus/pass-statement.parseB.txt | 2 +- .../python/corpus/print-statement.diffA-B.txt | 2 +- .../python/corpus/print-statement.diffB-A.txt | 2 +- .../python/corpus/print-statement.parseA.txt | 2 +- .../python/corpus/print-statement.parseB.txt | 2 +- .../python/corpus/raise-statement.diffA-B.txt | 2 +- .../python/corpus/raise-statement.diffB-A.txt | 2 +- .../python/corpus/raise-statement.parseA.txt | 2 +- .../python/corpus/raise-statement.parseB.txt | 2 +- .../corpus/return-statement.diffA-B.txt | 2 +- .../corpus/return-statement.diffB-A.txt | 2 +- .../python/corpus/return-statement.parseA.txt | 2 +- .../python/corpus/return-statement.parseB.txt | 2 +- .../corpus/set-comprehension.diffA-B.txt | 2 +- .../corpus/set-comprehension.diffB-A.txt | 2 +- .../corpus/set-comprehension.parseA.txt | 2 +- .../corpus/set-comprehension.parseB.txt | 2 +- test/fixtures/python/corpus/set.diffA-B.txt | 2 +- test/fixtures/python/corpus/set.diffB-A.txt | 2 +- test/fixtures/python/corpus/set.parseA.txt | 2 +- test/fixtures/python/corpus/set.parseB.txt | 2 +- test/fixtures/python/corpus/slice.diffA-B.txt | 2 +- test/fixtures/python/corpus/slice.diffB-A.txt | 2 +- test/fixtures/python/corpus/slice.parseA.txt | 2 +- test/fixtures/python/corpus/slice.parseB.txt | 2 +- .../fixtures/python/corpus/string.diffA-B.txt | 2 +- .../fixtures/python/corpus/string.diffB-A.txt | 2 +- test/fixtures/python/corpus/string.parseA.txt | 2 +- test/fixtures/python/corpus/string.parseB.txt | 2 +- .../python/corpus/subscript.diffA-B.txt | 2 +- .../python/corpus/subscript.diffB-A.txt | 2 +- .../python/corpus/subscript.parseA.txt | 2 +- .../python/corpus/subscript.parseB.txt | 2 +- .../python/corpus/try-statement.diffA-B.txt | 2 +- .../python/corpus/try-statement.diffB-A.txt | 2 +- .../python/corpus/try-statement.parseA.txt | 2 +- .../python/corpus/try-statement.parseB.txt | 2 +- test/fixtures/python/corpus/tuple.diffA-B.txt | 2 +- test/fixtures/python/corpus/tuple.diffB-A.txt | 2 +- test/fixtures/python/corpus/tuple.parseA.txt | 2 +- test/fixtures/python/corpus/tuple.parseB.txt | 2 +- .../python/corpus/unary-operator.diffA-B.txt | 2 +- .../python/corpus/unary-operator.diffB-A.txt | 2 +- .../python/corpus/unary-operator.parseA.txt | 2 +- .../python/corpus/unary-operator.parseB.txt | 2 +- .../python/corpus/while-statement.diffA-B.txt | 2 +- .../python/corpus/while-statement.diffB-A.txt | 2 +- .../python/corpus/while-statement.parseA.txt | 2 +- .../python/corpus/while-statement.parseB.txt | 2 +- .../python/corpus/with-statement.diffA-B.txt | 2 +- .../python/corpus/with-statement.diffB-A.txt | 2 +- .../python/corpus/with-statement.parseA.txt | 2 +- .../python/corpus/with-statement.parseB.txt | 2 +- test/fixtures/python/corpus/with.diffA-B.txt | 2 +- test/fixtures/python/corpus/with.diffB-A.txt | 2 +- test/fixtures/python/corpus/with.parseA.txt | 2 +- test/fixtures/python/corpus/with.parseB.txt | 2 +- test/fixtures/python/corpus/yield.diffA-B.txt | 2 +- test/fixtures/python/corpus/yield.diffB-A.txt | 2 +- test/fixtures/python/corpus/yield.parseA.txt | 2 +- test/fixtures/python/corpus/yield.parseB.txt | 2 +- test/fixtures/ruby/corpus/alias.parseA.txt | 2 +- test/fixtures/ruby/corpus/and-or.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/and-or.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/and-or.parseA.txt | 2 +- test/fixtures/ruby/corpus/and-or.parseB.txt | 2 +- test/fixtures/ruby/corpus/array.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/array.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/array.parseA.txt | 2 +- test/fixtures/ruby/corpus/array.parseB.txt | 2 +- .../ruby/corpus/assignment.diffA-B.txt | 2 +- .../ruby/corpus/assignment.diffB-A.txt | 2 +- .../ruby/corpus/assignment.parseA.txt | 2 +- .../ruby/corpus/assignment.parseB.txt | 2 +- .../ruby/corpus/begin-block.diffA-B.txt | 2 +- .../ruby/corpus/begin-block.diffB-A.txt | 2 +- .../ruby/corpus/begin-block.parseA.txt | 2 +- .../ruby/corpus/begin-block.parseB.txt | 2 +- test/fixtures/ruby/corpus/begin.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/begin.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/begin.parseA.txt | 2 +- test/fixtures/ruby/corpus/begin.parseB.txt | 2 +- test/fixtures/ruby/corpus/binary.parseA.txt | 2 +- .../ruby/corpus/bitwise-operator.diffA-B.txt | 2 +- .../ruby/corpus/bitwise-operator.diffB-A.txt | 2 +- .../ruby/corpus/bitwise-operator.parseA.txt | 2 +- .../ruby/corpus/bitwise-operator.parseB.txt | 2 +- .../ruby/corpus/boolean-operator.diffA-B.txt | 2 +- .../ruby/corpus/boolean-operator.diffB-A.txt | 2 +- .../ruby/corpus/boolean-operator.parseA.txt | 2 +- .../ruby/corpus/boolean-operator.parseB.txt | 2 +- test/fixtures/ruby/corpus/break.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/break.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/break.parseA.txt | 2 +- test/fixtures/ruby/corpus/break.parseB.txt | 2 +- test/fixtures/ruby/corpus/calls.parseA.txt | 2 +- .../ruby/corpus/chained-string.parseA.txt | 2 +- test/fixtures/ruby/corpus/class.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/class.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/class.parseA.txt | 2 +- test/fixtures/ruby/corpus/class.parseB.txt | 2 +- test/fixtures/ruby/corpus/comment.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/comment.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/comment.parseA.txt | 2 +- test/fixtures/ruby/corpus/comment.parseB.txt | 2 +- .../corpus/comparision-operator.diffA-B.txt | 2 +- .../corpus/comparision-operator.diffB-A.txt | 2 +- .../corpus/comparision-operator.parseA.txt | 2 +- .../corpus/comparision-operator.parseB.txt | 2 +- .../corpus/conditional-assignment.diffA-B.txt | 2 +- .../corpus/conditional-assignment.diffB-A.txt | 2 +- .../corpus/conditional-assignment.parseA.txt | 2 +- .../corpus/conditional-assignment.parseB.txt | 2 +- .../ruby/corpus/delimiter.diffA-B.txt | 2 +- .../ruby/corpus/delimiter.diffB-A.txt | 2 +- .../fixtures/ruby/corpus/delimiter.parseA.txt | 2 +- .../fixtures/ruby/corpus/delimiter.parseB.txt | 2 +- .../ruby/corpus/element-reference.diffA-B.txt | 2 +- .../ruby/corpus/element-reference.diffB-A.txt | 2 +- .../ruby/corpus/element-reference.parseA.txt | 2 +- .../ruby/corpus/element-reference.parseB.txt | 2 +- test/fixtures/ruby/corpus/else.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/else.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/else.parseA.txt | 2 +- test/fixtures/ruby/corpus/else.parseB.txt | 2 +- test/fixtures/ruby/corpus/elsif.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/elsif.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/elsif.parseA.txt | 2 +- test/fixtures/ruby/corpus/elsif.parseB.txt | 2 +- .../ruby/corpus/empty-statement.parseA.txt | 2 +- .../ruby/corpus/end-block.diffA-B.txt | 2 +- .../ruby/corpus/end-block.diffB-A.txt | 2 +- .../fixtures/ruby/corpus/end-block.parseA.txt | 2 +- .../fixtures/ruby/corpus/end-block.parseB.txt | 2 +- test/fixtures/ruby/corpus/ensure.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/ensure.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/ensure.parseA.txt | 2 +- test/fixtures/ruby/corpus/ensure.parseB.txt | 2 +- test/fixtures/ruby/corpus/for.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/for.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/for.parseA.txt | 2 +- test/fixtures/ruby/corpus/for.parseB.txt | 2 +- test/fixtures/ruby/corpus/hash.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/hash.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/hash.parseA.txt | 2 +- test/fixtures/ruby/corpus/hash.parseB.txt | 2 +- test/fixtures/ruby/corpus/heredoc.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/heredoc.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/heredoc.parseA.txt | 2 +- test/fixtures/ruby/corpus/heredoc.parseB.txt | 2 +- .../corpus/if-unless-modifiers.diffA-B.txt | 2 +- .../corpus/if-unless-modifiers.diffB-A.txt | 2 +- .../corpus/if-unless-modifiers.parseA.txt | 2 +- .../corpus/if-unless-modifiers.parseB.txt | 2 +- test/fixtures/ruby/corpus/if.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/if.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/if.parseA.txt | 2 +- test/fixtures/ruby/corpus/if.parseB.txt | 2 +- .../ruby/corpus/interpolation.diffA-B.txt | 2 +- .../ruby/corpus/interpolation.diffB-A.txt | 2 +- .../ruby/corpus/interpolation.parseA.txt | 2 +- .../ruby/corpus/interpolation.parseB.txt | 2 +- test/fixtures/ruby/corpus/keywords.parseA.txt | 2 +- .../corpus/lambda-dash-rocket.diffA-B.txt | 2 +- .../corpus/lambda-dash-rocket.diffB-A.txt | 2 +- .../ruby/corpus/lambda-dash-rocket.parseA.txt | 2 +- .../ruby/corpus/lambda-dash-rocket.parseB.txt | 2 +- test/fixtures/ruby/corpus/lambda.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/lambda.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/lambda.parseA.txt | 2 +- test/fixtures/ruby/corpus/lambda.parseB.txt | 2 +- test/fixtures/ruby/corpus/literals.parseA.txt | 2 +- .../ruby/corpus/math-assignment.diffA-B.txt | 2 +- .../ruby/corpus/math-assignment.diffB-A.txt | 2 +- .../ruby/corpus/math-assignment.parseA.txt | 2 +- .../ruby/corpus/math-assignment.parseB.txt | 2 +- .../corpus/method-calls-hash-args.diffA-B.txt | 2 +- .../corpus/method-calls-hash-args.diffB-A.txt | 2 +- .../corpus/method-calls-hash-args.parseA.txt | 2 +- .../corpus/method-calls-hash-args.parseB.txt | 2 +- .../method-calls-keyword-args.diffA-B.txt | 2 +- .../method-calls-keyword-args.diffB-A.txt | 2 +- .../method-calls-keyword-args.parseA.txt | 2 +- .../method-calls-keyword-args.parseB.txt | 2 +- .../ruby/corpus/method-calls.diffA-B.txt | 2 +- .../ruby/corpus/method-calls.diffB-A.txt | 2 +- .../ruby/corpus/method-calls.parseA.txt | 2 +- .../ruby/corpus/method-calls.parseB.txt | 2 +- ...thod-declaration-keyword-param.diffA-B.txt | 2 +- ...thod-declaration-keyword-param.diffB-A.txt | 2 +- ...ethod-declaration-keyword-param.parseA.txt | 2 +- ...ethod-declaration-keyword-param.parseB.txt | 2 +- ...thod-declaration-param-default.diffA-B.txt | 2 +- ...thod-declaration-param-default.diffB-A.txt | 2 +- ...ethod-declaration-param-default.parseA.txt | 2 +- ...ethod-declaration-param-default.parseB.txt | 2 +- .../method-declaration-params.diffA-B.txt | 2 +- .../method-declaration-params.diffB-A.txt | 2 +- .../method-declaration-params.parseA.txt | 2 +- .../method-declaration-params.parseB.txt | 2 +- ...aration-required-keyword-param.diffA-B.txt | 2 +- ...aration-required-keyword-param.diffB-A.txt | 2 +- ...laration-required-keyword-param.parseA.txt | 2 +- ...laration-required-keyword-param.parseB.txt | 2 +- ...thod-declaration-unnamed-param.diffA-B.txt | 2 +- ...thod-declaration-unnamed-param.diffB-A.txt | 2 +- ...ethod-declaration-unnamed-param.parseA.txt | 2 +- ...ethod-declaration-unnamed-param.parseB.txt | 2 +- .../corpus/method-declaration.diffA-B.txt | 2 +- .../corpus/method-declaration.diffB-A.txt | 2 +- .../ruby/corpus/method-declaration.parseA.txt | 2 +- .../ruby/corpus/method-declaration.parseB.txt | 2 +- .../ruby/corpus/method-invocation.diffA-B.txt | 2 +- .../ruby/corpus/method-invocation.diffB-A.txt | 2 +- .../ruby/corpus/method-invocation.parseA.txt | 2 +- .../ruby/corpus/method-invocation.parseB.txt | 2 +- test/fixtures/ruby/corpus/methods.parseA.txt | 2 +- test/fixtures/ruby/corpus/misc.parseA.txt | 2 +- test/fixtures/ruby/corpus/module.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/module.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/module.parseA.txt | 2 +- test/fixtures/ruby/corpus/module.parseB.txt | 2 +- .../corpus/multiple-assignments.diffA-B.txt | 2 +- .../corpus/multiple-assignments.diffB-A.txt | 2 +- .../corpus/multiple-assignments.parseA.txt | 2 +- .../corpus/multiple-assignments.parseB.txt | 2 +- test/fixtures/ruby/corpus/next.parseA.txt | 2 +- test/fixtures/ruby/corpus/number.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/number.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/number.parseA.txt | 2 +- test/fixtures/ruby/corpus/number.parseB.txt | 2 +- .../ruby/corpus/percent-array.diffA-B.txt | 2 +- .../ruby/corpus/percent-array.diffB-A.txt | 2 +- .../ruby/corpus/percent-array.parseA.txt | 2 +- .../ruby/corpus/percent-array.parseB.txt | 2 +- .../ruby/corpus/pseudo-variables.diffA-B.txt | 2 +- .../ruby/corpus/pseudo-variables.diffB-A.txt | 2 +- .../ruby/corpus/pseudo-variables.parseA.txt | 2 +- .../ruby/corpus/pseudo-variables.parseB.txt | 2 +- test/fixtures/ruby/corpus/regex.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/regex.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/regex.parseA.txt | 2 +- test/fixtures/ruby/corpus/regex.parseB.txt | 2 +- .../corpus/relational-operator.diffA-B.txt | 2 +- .../corpus/relational-operator.diffB-A.txt | 2 +- .../corpus/relational-operator.parseA.txt | 2 +- .../corpus/relational-operator.parseB.txt | 2 +- test/fixtures/ruby/corpus/require.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/require.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/require.parseA.txt | 2 +- test/fixtures/ruby/corpus/require.parseB.txt | 2 +- .../ruby/corpus/rescue-empty.diffA-B.txt | 2 +- .../ruby/corpus/rescue-empty.diffB-A.txt | 2 +- .../ruby/corpus/rescue-empty.parseA.txt | 2 +- .../ruby/corpus/rescue-empty.parseB.txt | 2 +- .../ruby/corpus/rescue-last-ex.diffA-B.txt | 2 +- .../ruby/corpus/rescue-last-ex.diffB-A.txt | 2 +- .../ruby/corpus/rescue-last-ex.parseA.txt | 2 +- .../ruby/corpus/rescue-last-ex.parseB.txt | 2 +- .../ruby/corpus/rescue-modifier.diffA-B.txt | 2 +- .../ruby/corpus/rescue-modifier.diffB-A.txt | 2 +- .../ruby/corpus/rescue-modifier.parseA.txt | 2 +- .../ruby/corpus/rescue-modifier.parseB.txt | 2 +- .../ruby/corpus/rescue-modifier2.diffA-B.txt | 2 +- .../ruby/corpus/rescue-modifier2.diffB-A.txt | 2 +- .../ruby/corpus/rescue-modifier2.parseA.txt | 2 +- .../ruby/corpus/rescue-modifier2.parseB.txt | 2 +- test/fixtures/ruby/corpus/rescue.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/rescue.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/rescue.parseA.txt | 2 +- test/fixtures/ruby/corpus/rescue.parseB.txt | 2 +- test/fixtures/ruby/corpus/return.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/return.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/return.parseA.txt | 2 +- test/fixtures/ruby/corpus/return.parseB.txt | 2 +- .../ruby/corpus/singleton-class.parseA.txt | 2 +- test/fixtures/ruby/corpus/string.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/string.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/string.parseA.txt | 2 +- test/fixtures/ruby/corpus/string.parseB.txt | 2 +- .../fixtures/ruby/corpus/subshell.diffA-B.txt | 2 +- .../fixtures/ruby/corpus/subshell.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/subshell.parseA.txt | 2 +- test/fixtures/ruby/corpus/subshell.parseB.txt | 2 +- test/fixtures/ruby/corpus/symbol.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/symbol.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/symbol.parseA.txt | 2 +- test/fixtures/ruby/corpus/symbol.parseB.txt | 2 +- test/fixtures/ruby/corpus/ternary.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/ternary.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/ternary.parseA.txt | 2 +- test/fixtures/ruby/corpus/ternary.parseB.txt | 2 +- test/fixtures/ruby/corpus/unary.parseA.txt | 2 +- test/fixtures/ruby/corpus/undef.parseA.txt | 2 +- test/fixtures/ruby/corpus/unless.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/unless.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/unless.parseA.txt | 2 +- test/fixtures/ruby/corpus/unless.parseB.txt | 2 +- test/fixtures/ruby/corpus/until.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/until.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/until.parseA.txt | 2 +- test/fixtures/ruby/corpus/until.parseB.txt | 2 +- .../ruby/corpus/when-else.diffA-B.txt | 2 +- .../ruby/corpus/when-else.diffB-A.txt | 2 +- .../fixtures/ruby/corpus/when-else.parseA.txt | 2 +- .../fixtures/ruby/corpus/when-else.parseB.txt | 2 +- test/fixtures/ruby/corpus/when.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/when.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/when.parseA.txt | 2 +- test/fixtures/ruby/corpus/when.parseB.txt | 2 +- test/fixtures/ruby/corpus/while.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/while.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/while.parseA.txt | 2 +- test/fixtures/ruby/corpus/while.parseB.txt | 2 +- test/fixtures/ruby/corpus/yield.diffA-B.txt | 2 +- test/fixtures/ruby/corpus/yield.diffB-A.txt | 2 +- test/fixtures/ruby/corpus/yield.parseA.txt | 2 +- test/fixtures/ruby/corpus/yield.parseB.txt | 2 +- .../corpus/ambient-declarations.diffA-B.txt | 2 +- .../corpus/ambient-declarations.diffB-A.txt | 2 +- .../corpus/ambient-declarations.parseA.txt | 2 +- .../corpus/ambient-declarations.parseB.txt | 2 +- .../corpus/ambient-exports.diffA-B.txt | 2 +- .../corpus/ambient-exports.diffB-A.txt | 2 +- .../corpus/ambient-exports.parseA.txt | 2 +- .../corpus/ambient-exports.parseB.txt | 2 +- .../ambient-type-declarations.diffA-B.txt | 2 +- .../ambient-type-declarations.diffB-A.txt | 2 +- .../ambient-type-declarations.parseA.txt | 2 +- .../ambient-type-declarations.parseB.txt | 2 +- .../corpus/anonymous-function.diffA-B.txt | 2 +- .../corpus/anonymous-function.diffB-A.txt | 2 +- .../corpus/anonymous-function.parseA.txt | 2 +- .../corpus/anonymous-function.parseB.txt | 2 +- ...onymous-parameterless-function.diffA-B.txt | 2 +- ...onymous-parameterless-function.diffB-A.txt | 2 +- ...nonymous-parameterless-function.parseA.txt | 2 +- ...nonymous-parameterless-function.parseB.txt | 2 +- .../typescript/corpus/array-type.diffA-B.txt | 2 +- .../typescript/corpus/array-type.diffB-A.txt | 2 +- .../typescript/corpus/array-type.parseA.txt | 2 +- .../typescript/corpus/array-type.parseB.txt | 2 +- .../typescript/corpus/array.diffA-B.txt | 2 +- .../typescript/corpus/array.diffB-A.txt | 2 +- .../typescript/corpus/array.parseA.txt | 2 +- .../typescript/corpus/array.parseB.txt | 2 +- .../corpus/arrow-function.diffA-B.txt | 2 +- .../corpus/arrow-function.diffB-A.txt | 2 +- .../corpus/arrow-function.parseA.txt | 2 +- .../corpus/arrow-function.parseB.txt | 2 +- .../corpus/assignment-pattern.diffA-B.txt | 2 +- .../corpus/assignment-pattern.diffB-A.txt | 2 +- .../corpus/assignment-pattern.parseA.txt | 2 +- .../corpus/assignment-pattern.parseB.txt | 2 +- .../typescript/corpus/assignment.diffA-B.txt | 2 +- .../typescript/corpus/assignment.diffB-A.txt | 2 +- .../typescript/corpus/assignment.parseA.txt | 2 +- .../typescript/corpus/assignment.parseB.txt | 2 +- .../corpus/bitwise-operator.diffA-B.txt | 2 +- .../corpus/bitwise-operator.diffB-A.txt | 2 +- .../corpus/bitwise-operator.parseA.txt | 2 +- .../corpus/bitwise-operator.parseB.txt | 2 +- .../corpus/boolean-operator.diffA-B.txt | 2 +- .../corpus/boolean-operator.diffB-A.txt | 2 +- .../corpus/boolean-operator.parseA.txt | 2 +- .../corpus/boolean-operator.parseB.txt | 2 +- .../typescript/corpus/break.diffA-B.txt | 2 +- .../typescript/corpus/break.diffB-A.txt | 2 +- .../typescript/corpus/break.parseA.txt | 2 +- .../typescript/corpus/break.parseB.txt | 2 +- .../corpus/chained-callbacks.diffA-B.txt | 2 +- .../corpus/chained-callbacks.diffB-A.txt | 2 +- .../corpus/chained-callbacks.parseA.txt | 2 +- .../corpus/chained-callbacks.parseB.txt | 2 +- .../chained-property-access.diffA-B.txt | 2 +- .../chained-property-access.diffB-A.txt | 2 +- .../corpus/chained-property-access.parseA.txt | 2 +- .../corpus/chained-property-access.parseB.txt | 2 +- .../typescript/corpus/class.diffA-B.txt | 2 +- .../typescript/corpus/class.diffB-A.txt | 2 +- .../typescript/corpus/class.parseA.txt | 2 +- .../typescript/corpus/class.parseB.txt | 2 +- .../corpus/comma-operator.diffA-B.txt | 2 +- .../corpus/comma-operator.diffB-A.txt | 2 +- .../corpus/comma-operator.parseA.txt | 2 +- .../corpus/comma-operator.parseB.txt | 2 +- .../typescript/corpus/comment.diffA-B.txt | 2 +- .../typescript/corpus/comment.diffB-A.txt | 2 +- .../typescript/corpus/comment.parseA.txt | 2 +- .../typescript/corpus/comment.parseB.txt | 2 +- .../corpus/constructor-call.diffA-B.txt | 2 +- .../corpus/constructor-call.diffB-A.txt | 2 +- .../corpus/constructor-call.parseA.txt | 2 +- .../corpus/constructor-call.parseB.txt | 2 +- .../typescript/corpus/continue.diffA-B.txt | 2 +- .../typescript/corpus/continue.diffB-A.txt | 2 +- .../typescript/corpus/continue.parseA.txt | 2 +- .../typescript/corpus/continue.parseB.txt | 2 +- .../corpus/delete-operator.diffA-B.txt | 2 +- .../corpus/delete-operator.diffB-A.txt | 2 +- .../corpus/delete-operator.parseA.txt | 2 +- .../corpus/delete-operator.parseB.txt | 2 +- .../corpus/do-while-statement.diffA-B.txt | 2 +- .../corpus/do-while-statement.diffB-A.txt | 2 +- .../corpus/do-while-statement.parseA.txt | 2 +- .../corpus/do-while-statement.parseB.txt | 2 +- .../corpus/export-assignments.diffA-B.txt | 2 +- .../corpus/export-assignments.diffB-A.txt | 2 +- .../corpus/export-assignments.parseA.txt | 2 +- .../corpus/export-assignments.parseB.txt | 2 +- .../typescript/corpus/export.diffA-B.txt | 20 ++--- .../typescript/corpus/export.diffB-A.txt | 22 ++--- .../typescript/corpus/export.parseA.txt | 2 +- .../typescript/corpus/export.parseB.txt | 2 +- .../typescript/corpus/false.diffA-B.txt | 2 +- .../typescript/corpus/false.diffB-A.txt | 2 +- .../typescript/corpus/false.parseA.txt | 2 +- .../typescript/corpus/false.parseB.txt | 2 +- .../corpus/for-in-statement.diffA-B.txt | 2 +- .../corpus/for-in-statement.diffB-A.txt | 2 +- .../corpus/for-in-statement.parseA.txt | 2 +- .../corpus/for-in-statement.parseB.txt | 2 +- .../for-loop-with-in-statement.diffA-B.txt | 2 +- .../for-loop-with-in-statement.diffB-A.txt | 2 +- .../for-loop-with-in-statement.parseA.txt | 2 +- .../for-loop-with-in-statement.parseB.txt | 2 +- .../corpus/for-of-statement.diffA-B.txt | 2 +- .../corpus/for-of-statement.diffB-A.txt | 2 +- .../corpus/for-of-statement.parseA.txt | 2 +- .../corpus/for-of-statement.parseB.txt | 2 +- .../corpus/for-statement.diffA-B.txt | 2 +- .../corpus/for-statement.diffB-A.txt | 2 +- .../corpus/for-statement.parseA.txt | 2 +- .../corpus/for-statement.parseB.txt | 2 +- .../corpus/function-call-args.diffA-B.txt | 2 +- .../corpus/function-call-args.diffB-A.txt | 2 +- .../corpus/function-call-args.parseA.txt | 2 +- .../corpus/function-call-args.parseB.txt | 2 +- .../corpus/function-call.diffA-B.txt | 2 +- .../corpus/function-call.diffB-A.txt | 2 +- .../corpus/function-call.parseA.txt | 2 +- .../corpus/function-call.parseB.txt | 2 +- .../corpus/function-type.diffA-B.txt | 2 +- .../corpus/function-type.diffB-A.txt | 2 +- .../corpus/function-type.parseA.txt | 2 +- .../corpus/function-type.parseB.txt | 2 +- .../typescript/corpus/function.diffA-B.txt | 2 +- .../typescript/corpus/function.diffB-A.txt | 2 +- .../typescript/corpus/function.parseA.txt | 2 +- .../typescript/corpus/function.parseB.txt | 2 +- .../corpus/generator-function.diffA-B.txt | 2 +- .../corpus/generator-function.diffB-A.txt | 2 +- .../corpus/generator-function.parseA.txt | 2 +- .../corpus/generator-function.parseB.txt | 2 +- .../typescript/corpus/identifier.diffA-B.txt | 2 +- .../typescript/corpus/identifier.diffB-A.txt | 2 +- .../typescript/corpus/identifier.parseA.txt | 2 +- .../typescript/corpus/identifier.parseB.txt | 2 +- .../typescript/corpus/if-else.diffA-B.txt | 2 +- .../typescript/corpus/if-else.diffB-A.txt | 2 +- .../typescript/corpus/if-else.parseA.txt | 2 +- .../typescript/corpus/if-else.parseB.txt | 2 +- .../fixtures/typescript/corpus/if.diffA-B.txt | 2 +- .../fixtures/typescript/corpus/if.diffB-A.txt | 2 +- test/fixtures/typescript/corpus/if.parseA.txt | 2 +- test/fixtures/typescript/corpus/if.parseB.txt | 2 +- .../typescript/corpus/import.diffA-B.txt | 6 +- .../typescript/corpus/import.diffB-A.txt | 6 +- .../typescript/corpus/import.parseA.txt | 2 +- .../typescript/corpus/import.parseB.txt | 2 +- .../typescript/corpus/interface.diffA-B.txt | 2 +- .../typescript/corpus/interface.diffB-A.txt | 2 +- .../typescript/corpus/interface.parseA.txt | 2 +- .../typescript/corpus/interface.parseB.txt | 2 +- .../corpus/intersection-type.diffA-B.txt | 2 +- .../corpus/intersection-type.diffB-A.txt | 2 +- .../corpus/intersection-type.parseA.txt | 2 +- .../corpus/intersection-type.parseB.txt | 2 +- .../corpus/jsx-elements.diffA-B.txt | 2 +- .../corpus/jsx-elements.diffB-A.txt | 2 +- .../typescript/corpus/jsx-elements.parseA.txt | 2 +- .../typescript/corpus/jsx-elements.parseB.txt | 2 +- .../math-assignment-operator.diffA-B.txt | 2 +- .../math-assignment-operator.diffB-A.txt | 2 +- .../math-assignment-operator.parseA.txt | 2 +- .../math-assignment-operator.parseB.txt | 2 +- .../corpus/math-operator.diffA-B.txt | 2 +- .../corpus/math-operator.diffB-A.txt | 2 +- .../corpus/math-operator.parseA.txt | 2 +- .../corpus/math-operator.parseB.txt | 2 +- .../member-access-assignment.diffA-B.txt | 2 +- .../member-access-assignment.diffB-A.txt | 2 +- .../member-access-assignment.parseA.txt | 2 +- .../member-access-assignment.parseB.txt | 2 +- .../corpus/member-access.diffA-B.txt | 2 +- .../corpus/member-access.diffB-A.txt | 2 +- .../corpus/member-access.parseA.txt | 2 +- .../corpus/member-access.parseB.txt | 2 +- .../typescript/corpus/method-call.diffA-B.txt | 2 +- .../typescript/corpus/method-call.diffB-A.txt | 2 +- .../typescript/corpus/method-call.parseA.txt | 2 +- .../typescript/corpus/method-call.parseB.txt | 2 +- .../corpus/method-definition.diffA-B.txt | 2 +- .../corpus/method-definition.diffB-A.txt | 2 +- .../corpus/method-definition.parseA.txt | 2 +- .../corpus/method-definition.parseB.txt | 2 +- .../corpus/module-declarations.diffA-B.txt | 2 +- .../corpus/module-declarations.diffB-A.txt | 2 +- .../corpus/module-declarations.parseA.txt | 2 +- .../corpus/module-declarations.parseB.txt | 2 +- .../corpus/named-function.diffA-B.txt | 2 +- .../corpus/named-function.diffB-A.txt | 2 +- .../corpus/named-function.parseA.txt | 2 +- .../corpus/named-function.parseB.txt | 2 +- .../nested-do-while-in-function.diffA-B.txt | 2 +- .../nested-do-while-in-function.diffB-A.txt | 2 +- .../nested-do-while-in-function.parseA.txt | 2 +- .../nested-do-while-in-function.parseB.txt | 2 +- .../corpus/nested-functions.diffA-B.txt | 2 +- .../corpus/nested-functions.diffB-A.txt | 2 +- .../corpus/nested-functions.parseA.txt | 2 +- .../corpus/nested-functions.parseB.txt | 2 +- .../typescript/corpus/null.diffA-B.txt | 2 +- .../typescript/corpus/null.diffB-A.txt | 2 +- .../typescript/corpus/null.parseA.txt | 2 +- .../typescript/corpus/null.parseB.txt | 2 +- .../typescript/corpus/number.diffA-B.txt | 2 +- .../typescript/corpus/number.diffB-A.txt | 2 +- .../typescript/corpus/number.parseA.txt | 2 +- .../typescript/corpus/number.parseB.txt | 2 +- .../typescript/corpus/object.diffA-B.txt | 2 +- .../typescript/corpus/object.diffB-A.txt | 2 +- .../typescript/corpus/object.parseA.txt | 2 +- .../typescript/corpus/object.parseB.txt | 2 +- .../corpus/objects-with-methods.diffA-B.txt | 2 +- .../corpus/objects-with-methods.diffB-A.txt | 2 +- .../corpus/objects-with-methods.parseA.txt | 2 +- .../corpus/objects-with-methods.parseB.txt | 2 +- .../public-field-definition.diffA-B.txt | 83 ++++++++++++------- .../public-field-definition.diffB-A.txt | 68 +++++++++------ .../corpus/public-field-definition.parseA.txt | 2 +- .../corpus/public-field-definition.parseB.txt | 2 +- .../typescript/corpus/regex.diffA-B.txt | 2 +- .../typescript/corpus/regex.diffB-A.txt | 2 +- .../typescript/corpus/regex.parseA.txt | 2 +- .../typescript/corpus/regex.parseB.txt | 2 +- .../corpus/relational-operator.diffA-B.txt | 2 +- .../corpus/relational-operator.diffB-A.txt | 2 +- .../corpus/relational-operator.parseA.txt | 2 +- .../corpus/relational-operator.parseB.txt | 2 +- .../corpus/return-statement.diffA-B.txt | 2 +- .../corpus/return-statement.diffB-A.txt | 2 +- .../corpus/return-statement.parseA.txt | 2 +- .../corpus/return-statement.parseB.txt | 2 +- .../typescript/corpus/string.diffA-B.txt | 2 +- .../typescript/corpus/string.diffB-A.txt | 2 +- .../typescript/corpus/string.parseA.txt | 2 +- .../typescript/corpus/string.parseB.txt | 2 +- .../subscript-access-assignment.diffA-B.txt | 2 +- .../subscript-access-assignment.diffB-A.txt | 2 +- .../subscript-access-assignment.parseA.txt | 2 +- .../subscript-access-assignment.parseB.txt | 2 +- .../subscript-access-string.diffA-B.txt | 2 +- .../subscript-access-string.diffB-A.txt | 2 +- .../corpus/subscript-access-string.parseA.txt | 2 +- .../corpus/subscript-access-string.parseB.txt | 2 +- .../subscript-access-variable.diffA-B.txt | 2 +- .../subscript-access-variable.diffB-A.txt | 2 +- .../subscript-access-variable.parseA.txt | 2 +- .../subscript-access-variable.parseB.txt | 2 +- .../corpus/switch-statement.diffA-B.txt | 2 +- .../corpus/switch-statement.diffB-A.txt | 2 +- .../corpus/switch-statement.parseA.txt | 2 +- .../corpus/switch-statement.parseB.txt | 2 +- .../corpus/template-string.diffA-B.txt | 2 +- .../corpus/template-string.diffB-A.txt | 2 +- .../corpus/template-string.parseA.txt | 2 +- .../corpus/template-string.parseB.txt | 2 +- .../typescript/corpus/ternary.diffA-B.txt | 2 +- .../typescript/corpus/ternary.diffB-A.txt | 2 +- .../typescript/corpus/ternary.parseA.txt | 2 +- .../typescript/corpus/ternary.parseB.txt | 2 +- .../corpus/this-expression.diffA-B.txt | 2 +- .../corpus/this-expression.diffB-A.txt | 2 +- .../corpus/this-expression.parseA.txt | 2 +- .../corpus/this-expression.parseB.txt | 2 +- .../corpus/throw-statement.diffA-B.txt | 2 +- .../corpus/throw-statement.diffB-A.txt | 2 +- .../corpus/throw-statement.parseA.txt | 2 +- .../corpus/throw-statement.parseB.txt | 2 +- .../typescript/corpus/true.diffA-B.txt | 2 +- .../typescript/corpus/true.diffB-A.txt | 2 +- .../typescript/corpus/true.parseA.txt | 2 +- .../typescript/corpus/true.parseB.txt | 2 +- .../corpus/try-statement.diffA-B.txt | 2 +- .../corpus/try-statement.diffB-A.txt | 2 +- .../corpus/try-statement.parseA.txt | 2 +- .../corpus/try-statement.parseB.txt | 2 +- .../typescript/corpus/tuple-type.diffA-B.txt | 2 +- .../typescript/corpus/tuple-type.diffB-A.txt | 2 +- .../typescript/corpus/tuple-type.parseA.txt | 2 +- .../typescript/corpus/tuple-type.parseB.txt | 2 +- .../corpus/type-assertions.diffA-B.txt | 2 +- .../corpus/type-assertions.diffB-A.txt | 2 +- .../corpus/type-assertions.parseA.txt | 2 +- .../corpus/type-assertions.parseB.txt | 2 +- .../corpus/type-operator.diffA-B.txt | 2 +- .../corpus/type-operator.diffB-A.txt | 2 +- .../corpus/type-operator.parseA.txt | 2 +- .../corpus/type-operator.parseB.txt | 2 +- .../corpus/typeof-types.diffA-B.txt | 2 +- .../corpus/typeof-types.diffB-A.txt | 2 +- .../typescript/corpus/typeof-types.parseA.txt | 2 +- .../typescript/corpus/typeof-types.parseB.txt | 2 +- .../typescript/corpus/undefined.diffA-B.txt | 2 +- .../typescript/corpus/undefined.diffB-A.txt | 2 +- .../typescript/corpus/undefined.parseA.txt | 2 +- .../typescript/corpus/undefined.parseB.txt | 2 +- .../typescript/corpus/union-type.diffA-B.txt | 2 +- .../typescript/corpus/union-type.diffB-A.txt | 2 +- .../typescript/corpus/union-type.parseA.txt | 2 +- .../typescript/corpus/union-type.parseB.txt | 2 +- .../corpus/var-declaration.diffA-B.txt | 2 +- .../corpus/var-declaration.diffB-A.txt | 2 +- .../corpus/var-declaration.parseA.txt | 2 +- .../corpus/var-declaration.parseB.txt | 2 +- .../typescript/corpus/variable.diffA-B.txt | 2 +- .../typescript/corpus/variable.diffB-A.txt | 2 +- .../typescript/corpus/variable.parseA.txt | 2 +- .../typescript/corpus/variable.parseB.txt | 2 +- .../corpus/void-operator.diffA-B.txt | 2 +- .../corpus/void-operator.diffB-A.txt | 2 +- .../corpus/void-operator.parseA.txt | 2 +- .../corpus/void-operator.parseB.txt | 2 +- .../corpus/while-statement.diffA-B.txt | 2 +- .../corpus/while-statement.diffB-A.txt | 2 +- .../corpus/while-statement.parseA.txt | 2 +- .../corpus/while-statement.parseB.txt | 2 +- .../typescript/corpus/yield.diffA-B.txt | 2 +- .../typescript/corpus/yield.diffB-A.txt | 2 +- .../typescript/corpus/yield.parseA.txt | 2 +- .../typescript/corpus/yield.parseB.txt | 2 +- 1313 files changed, 1830 insertions(+), 1773 deletions(-) diff --git a/test/Semantic/Spec.hs b/test/Semantic/Spec.hs index b620a92a6..442eec578 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 (Statements)))\n" + output `shouldBe` "(Statements\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/cli/diff-tree.json b/test/fixtures/cli/diff-tree.json index 63786e67a..683fdf539 100644 --- a/test/fixtures/cli/diff-tree.json +++ b/test/fixtures/cli/diff-tree.json @@ -5,7 +5,7 @@ { "merge": { - "term": "Program", + "term": "Statements", "children": [ { "merge": diff --git a/test/fixtures/cli/parse-tree.json b/test/fixtures/cli/parse-tree.json index 67c21e302..43e07d9b4 100644 --- a/test/fixtures/cli/parse-tree.json +++ b/test/fixtures/cli/parse-tree.json @@ -3,7 +3,7 @@ { "tree": { - "term": "Program", + "term": "Statements", "children": [ { "term": "LowAnd", diff --git a/test/fixtures/cli/parse-trees.json b/test/fixtures/cli/parse-trees.json index 0bd86671c..7beb46a0c 100644 --- a/test/fixtures/cli/parse-trees.json +++ b/test/fixtures/cli/parse-trees.json @@ -3,7 +3,7 @@ { "tree": { - "term": "Program", + "term": "Statements", "children": [ { "term": "LowAnd", @@ -74,7 +74,7 @@ { "tree": { - "term": "Program", + "term": "Statements", "children": [ { "term": "LowOr", diff --git a/test/fixtures/go/corpus/array-types.diffA-B.txt b/test/fixtures/go/corpus/array-types.diffA-B.txt index 56be1c980..44375d74d 100644 --- a/test/fixtures/go/corpus/array-types.diffA-B.txt +++ b/test/fixtures/go/corpus/array-types.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -17,27 +17,39 @@ ->(Integer) }) { (Identifier) ->(Identifier) }))) - (Statements - (Type - { (Identifier) - ->(Identifier) } - (Array - { (Integer) - ->(Integer) } - (Array - { (Integer) - ->(Integer) } - (Identifier))))) - (Statements - (Type - { (Identifier) - ->(Identifier) } - (Array - { (Integer) - ->(Integer) } - (Array - (Integer) - (Array - { (Integer) - ->(Integer) } - (Identifier))))))))) + {+(Statements + {+(Type + {+(Identifier)+} + {+(Array + {+(Integer)+} + {+(Array + {+(Integer)+} + {+(Identifier)+})+})+})+})+} + {+(Statements + {+(Type + {+(Identifier)+} + {+(Array + {+(Integer)+} + {+(Array + {+(Integer)+} + {+(Array + {+(Integer)+} + {+(Identifier)+})+})+})+})+})+} + {-(Statements + {-(Type + {-(Identifier)-} + {-(Array + {-(Integer)-} + {-(Array + {-(Integer)-} + {-(Identifier)-})-})-})-})-} + {-(Statements + {-(Type + {-(Identifier)-} + {-(Array + {-(Integer)-} + {-(Array + {-(Integer)-} + {-(Array + {-(Integer)-} + {-(Identifier)-})-})-})-})-})-}))) diff --git a/test/fixtures/go/corpus/array-types.diffB-A.txt b/test/fixtures/go/corpus/array-types.diffB-A.txt index 56be1c980..44375d74d 100644 --- a/test/fixtures/go/corpus/array-types.diffB-A.txt +++ b/test/fixtures/go/corpus/array-types.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -17,27 +17,39 @@ ->(Integer) }) { (Identifier) ->(Identifier) }))) - (Statements - (Type - { (Identifier) - ->(Identifier) } - (Array - { (Integer) - ->(Integer) } - (Array - { (Integer) - ->(Integer) } - (Identifier))))) - (Statements - (Type - { (Identifier) - ->(Identifier) } - (Array - { (Integer) - ->(Integer) } - (Array - (Integer) - (Array - { (Integer) - ->(Integer) } - (Identifier))))))))) + {+(Statements + {+(Type + {+(Identifier)+} + {+(Array + {+(Integer)+} + {+(Array + {+(Integer)+} + {+(Identifier)+})+})+})+})+} + {+(Statements + {+(Type + {+(Identifier)+} + {+(Array + {+(Integer)+} + {+(Array + {+(Integer)+} + {+(Array + {+(Integer)+} + {+(Identifier)+})+})+})+})+})+} + {-(Statements + {-(Type + {-(Identifier)-} + {-(Array + {-(Integer)-} + {-(Array + {-(Integer)-} + {-(Identifier)-})-})-})-})-} + {-(Statements + {-(Type + {-(Identifier)-} + {-(Array + {-(Integer)-} + {-(Array + {-(Integer)-} + {-(Array + {-(Integer)-} + {-(Identifier)-})-})-})-})-})-}))) diff --git a/test/fixtures/go/corpus/array-types.parseA.txt b/test/fixtures/go/corpus/array-types.parseA.txt index 84a768d0e..61ccd80a0 100644 --- a/test/fixtures/go/corpus/array-types.parseA.txt +++ b/test/fixtures/go/corpus/array-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/array-types.parseB.txt b/test/fixtures/go/corpus/array-types.parseB.txt index 84a768d0e..61ccd80a0 100644 --- a/test/fixtures/go/corpus/array-types.parseB.txt +++ b/test/fixtures/go/corpus/array-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 c7bcedee0..0517541a8 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 cc7f5639b..9d43c214e 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 d6cb95c51..3acc2cffa 100644 --- a/test/fixtures/go/corpus/array-with-implicit-length.parseA.txt +++ b/test/fixtures/go/corpus/array-with-implicit-length.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 d6cb95c51..3acc2cffa 100644 --- a/test/fixtures/go/corpus/array-with-implicit-length.parseB.txt +++ b/test/fixtures/go/corpus/array-with-implicit-length.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/assignment-statements.diffA-B.txt b/test/fixtures/go/corpus/assignment-statements.diffA-B.txt index 124828615..214111c43 100644 --- a/test/fixtures/go/corpus/assignment-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/assignment-statements.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -35,11 +35,15 @@ {+(Plus {+(Identifier)+} {+(Integer)+})+})+} - {+(Assignment - {+(Identifier)+} - {+(LShift + (Assignment + { (Identifier) + ->(Identifier) } + { (Times + {-(Identifier)-} + {-(Integer)-}) + ->(LShift {+(Identifier)+} - {+(Integer)+})+})+} + {+(Integer)+}) }) {+(Assignment {+(Identifier)+} {+(RShift @@ -78,11 +82,6 @@ {+(KeyValue {+(Identifier)+} {+(Integer)+})+})+})+})+})+})+} - {-(Assignment - {-(Identifier)-} - {-(Times - {-(Identifier)-} - {-(Integer)-})-})-} {-(Assignment {-(Identifier)-} {-(Plus diff --git a/test/fixtures/go/corpus/assignment-statements.diffB-A.txt b/test/fixtures/go/corpus/assignment-statements.diffB-A.txt index 124828615..dfe0c7afa 100644 --- a/test/fixtures/go/corpus/assignment-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/assignment-statements.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/assignment-statements.parseA.txt b/test/fixtures/go/corpus/assignment-statements.parseA.txt index b791f8bea..79423d196 100644 --- a/test/fixtures/go/corpus/assignment-statements.parseA.txt +++ b/test/fixtures/go/corpus/assignment-statements.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/assignment-statements.parseB.txt b/test/fixtures/go/corpus/assignment-statements.parseB.txt index b791f8bea..79423d196 100644 --- a/test/fixtures/go/corpus/assignment-statements.parseB.txt +++ b/test/fixtures/go/corpus/assignment-statements.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/binary-expressions.diffA-B.txt b/test/fixtures/go/corpus/binary-expressions.diffA-B.txt index b917e06f7..d8b289d28 100644 --- a/test/fixtures/go/corpus/binary-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/binary-expressions.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -22,17 +22,13 @@ ->(Identifier) } { (Identifier) ->(Identifier) })) - (Equal - { (Identifier) - ->(Identifier) } - { (Identifier) - ->(Identifier) }) - (Not - (Equal - { (Identifier) - ->(Identifier) } - { (Identifier) - ->(Identifier) })) + {+(Equal + {+(Identifier)+} + {+(Identifier)+})+} + {+(Not + {+(Equal + {+(Identifier)+} + {+(Identifier)+})+})+} {+(LessThan {+(Identifier)+} {+(Identifier)+})+} @@ -78,6 +74,13 @@ {+(BAnd {+(Identifier)+} {+(Identifier)+})+} + {-(Equal + {-(Identifier)-} + {-(Identifier)-})-} + {-(Not + {-(Equal + {-(Identifier)-} + {-(Identifier)-})-})-} {-(LessThan {-(Identifier)-} {-(Identifier)-})-} diff --git a/test/fixtures/go/corpus/binary-expressions.diffB-A.txt b/test/fixtures/go/corpus/binary-expressions.diffB-A.txt index b917e06f7..d8b289d28 100644 --- a/test/fixtures/go/corpus/binary-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/binary-expressions.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -22,17 +22,13 @@ ->(Identifier) } { (Identifier) ->(Identifier) })) - (Equal - { (Identifier) - ->(Identifier) } - { (Identifier) - ->(Identifier) }) - (Not - (Equal - { (Identifier) - ->(Identifier) } - { (Identifier) - ->(Identifier) })) + {+(Equal + {+(Identifier)+} + {+(Identifier)+})+} + {+(Not + {+(Equal + {+(Identifier)+} + {+(Identifier)+})+})+} {+(LessThan {+(Identifier)+} {+(Identifier)+})+} @@ -78,6 +74,13 @@ {+(BAnd {+(Identifier)+} {+(Identifier)+})+} + {-(Equal + {-(Identifier)-} + {-(Identifier)-})-} + {-(Not + {-(Equal + {-(Identifier)-} + {-(Identifier)-})-})-} {-(LessThan {-(Identifier)-} {-(Identifier)-})-} diff --git a/test/fixtures/go/corpus/binary-expressions.parseA.txt b/test/fixtures/go/corpus/binary-expressions.parseA.txt index 44e685fd0..87953095e 100644 --- a/test/fixtures/go/corpus/binary-expressions.parseA.txt +++ b/test/fixtures/go/corpus/binary-expressions.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/binary-expressions.parseB.txt b/test/fixtures/go/corpus/binary-expressions.parseB.txt index 44e685fd0..87953095e 100644 --- a/test/fixtures/go/corpus/binary-expressions.parseB.txt +++ b/test/fixtures/go/corpus/binary-expressions.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/call-expressions.diffA-B.txt b/test/fixtures/go/corpus/call-expressions.diffA-B.txt index 3c48543b6..90b706eb5 100644 --- a/test/fixtures/go/corpus/call-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/call-expressions.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -21,20 +21,14 @@ (Identifier) (Identifier)) (Empty)) - {+(Call - {+(Identifier)+} - {+(Statements - {+(Identifier)+} - {+(Variadic - {+(Identifier)+})+})+} - {+(Empty)+})+} - {-(Call - {-(Identifier)-} - {-(Statements - {-(Identifier)-} - {-(Variadic - {-(Identifier)-})-})-} - {-(Empty)-})-} + (Call + { (Identifier) + ->(Identifier) } + (Statements + (Identifier) + (Variadic + (Identifier))) + (Empty)) {-(Call {-(Identifier)-} {-(Statements)-} diff --git a/test/fixtures/go/corpus/call-expressions.diffB-A.txt b/test/fixtures/go/corpus/call-expressions.diffB-A.txt index 2c96f544d..d89396030 100644 --- a/test/fixtures/go/corpus/call-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/call-expressions.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -21,19 +21,15 @@ (Identifier) (Identifier)) (Empty)) - {+(Call - {+(Identifier)+} - {+(Statements - {+(Identifier)+} - {+(Variadic - {+(Identifier)+})+})+} - {+(Empty)+})+} (Call { (Identifier) ->(Identifier) } + (Statements + (Identifier) + (Variadic + (Identifier))) + (Empty)) + {+(Call + {+(Identifier)+} {+(Statements)+} - {-(Statements - {-(Identifier)-} - {-(Variadic - {-(Identifier)-})-})-} - (Empty))))) + {+(Empty)+})+}))) diff --git a/test/fixtures/go/corpus/call-expressions.parseA.txt b/test/fixtures/go/corpus/call-expressions.parseA.txt index d3a17acc0..07af90f42 100644 --- a/test/fixtures/go/corpus/call-expressions.parseA.txt +++ b/test/fixtures/go/corpus/call-expressions.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/call-expressions.parseB.txt b/test/fixtures/go/corpus/call-expressions.parseB.txt index 405ccd9f8..a0061678c 100644 --- a/test/fixtures/go/corpus/call-expressions.parseB.txt +++ b/test/fixtures/go/corpus/call-expressions.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/case-statements.diffA-B.txt b/test/fixtures/go/corpus/case-statements.diffA-B.txt index fff31dbb0..a314f8a8f 100644 --- a/test/fixtures/go/corpus/case-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/case-statements.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/case-statements.diffB-A.txt b/test/fixtures/go/corpus/case-statements.diffB-A.txt index 58e3ab7f4..a8fe47aec 100644 --- a/test/fixtures/go/corpus/case-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/case-statements.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/case-statements.parseA.txt b/test/fixtures/go/corpus/case-statements.parseA.txt index b5290544a..5328937b5 100644 --- a/test/fixtures/go/corpus/case-statements.parseA.txt +++ b/test/fixtures/go/corpus/case-statements.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/case-statements.parseB.txt b/test/fixtures/go/corpus/case-statements.parseB.txt index 30ac23d2c..d93e3d640 100644 --- a/test/fixtures/go/corpus/case-statements.parseB.txt +++ b/test/fixtures/go/corpus/case-statements.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/channel-types.diffA-B.txt b/test/fixtures/go/corpus/channel-types.diffA-B.txt index d5317887d..efabef389 100644 --- a/test/fixtures/go/corpus/channel-types.diffA-B.txt +++ b/test/fixtures/go/corpus/channel-types.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -18,15 +18,11 @@ {+(Constructor {+(Empty)+} {+(Statements)+})+})+})+})+} - (Type - { (Identifier) - ->(Identifier) } - { (BidirectionalChannel - {-(ReceiveChannel - {-(Identifier)-})-}) - ->(SendChannel + {+(Type + {+(Identifier)+} + {+(SendChannel {+(ReceiveChannel - {+(Identifier)+})+}) }) + {+(Identifier)+})+})+})+} {+(Type {+(Identifier)+} {+(ReceiveChannel @@ -38,6 +34,11 @@ {+(Parenthesized {+(ReceiveChannel {+(Identifier)+})+})+})+})+} + {-(Type + {-(Identifier)-} + {-(BidirectionalChannel + {-(ReceiveChannel + {-(Identifier)-})-})-})-} {-(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 51a49dc4b..efabef389 100644 --- a/test/fixtures/go/corpus/channel-types.diffB-A.txt +++ b/test/fixtures/go/corpus/channel-types.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/channel-types.parseA.txt b/test/fixtures/go/corpus/channel-types.parseA.txt index 1396ee35f..1fac3aefe 100644 --- a/test/fixtures/go/corpus/channel-types.parseA.txt +++ b/test/fixtures/go/corpus/channel-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/channel-types.parseB.txt b/test/fixtures/go/corpus/channel-types.parseB.txt index 1396ee35f..1fac3aefe 100644 --- a/test/fixtures/go/corpus/channel-types.parseB.txt +++ b/test/fixtures/go/corpus/channel-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/comment.diffA-B.txt b/test/fixtures/go/corpus/comment.diffA-B.txt index 58437db7e..2d08d1942 100644 --- a/test/fixtures/go/corpus/comment.diffA-B.txt +++ b/test/fixtures/go/corpus/comment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/comment.diffB-A.txt b/test/fixtures/go/corpus/comment.diffB-A.txt index 58437db7e..2d08d1942 100644 --- a/test/fixtures/go/corpus/comment.diffB-A.txt +++ b/test/fixtures/go/corpus/comment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/comment.parseA.txt b/test/fixtures/go/corpus/comment.parseA.txt index 5972880e0..b1beb038f 100644 --- a/test/fixtures/go/corpus/comment.parseA.txt +++ b/test/fixtures/go/corpus/comment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/comment.parseB.txt b/test/fixtures/go/corpus/comment.parseB.txt index 5972880e0..b1beb038f 100644 --- a/test/fixtures/go/corpus/comment.parseB.txt +++ b/test/fixtures/go/corpus/comment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 25059d86c..d5c8ba3ce 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 409f37825..8440f2b8b 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 83a22058d..adb372883 100644 --- a/test/fixtures/go/corpus/const-declarations-with-types.parseA.txt +++ b/test/fixtures/go/corpus/const-declarations-with-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 23d0ec50b..0b9b3fdb9 100644 --- a/test/fixtures/go/corpus/const-declarations-with-types.parseB.txt +++ b/test/fixtures/go/corpus/const-declarations-with-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 2d984aebb..8f6103b96 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 06f1fa789..6ef1f0819 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 d49580f45..0e1ac2501 100644 --- a/test/fixtures/go/corpus/const-declarations-without-types.parseA.txt +++ b/test/fixtures/go/corpus/const-declarations-without-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 bbacb990a..8e483ac19 100644 --- a/test/fixtures/go/corpus/const-declarations-without-types.parseB.txt +++ b/test/fixtures/go/corpus/const-declarations-without-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 a9e14b08e..10cf87c5b 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -6,20 +6,15 @@ (Identifier) (Statements) (Statements - {+(Assignment - {+(Identifier)+} - {+(Identifier)+})+} (Assignment { (Identifier) ->(Identifier) } + (Identifier)) + (Assignment { (Identifier) - ->(Statements) }) - {+(Assignment - {+(Identifier)+} - {+(Statements)+})+} - {-(Assignment - {-(Identifier)-} - {-(Statements)-})-} - {-(Assignment - {-(Identifier)-} - {-(Statements)-})-}))) + ->(Identifier) } + (Statements)) + (Assignment + { (Identifier) + ->(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 a9e14b08e..10cf87c5b 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -6,20 +6,15 @@ (Identifier) (Statements) (Statements - {+(Assignment - {+(Identifier)+} - {+(Identifier)+})+} (Assignment { (Identifier) ->(Identifier) } + (Identifier)) + (Assignment { (Identifier) - ->(Statements) }) - {+(Assignment - {+(Identifier)+} - {+(Statements)+})+} - {-(Assignment - {-(Identifier)-} - {-(Statements)-})-} - {-(Assignment - {-(Identifier)-} - {-(Statements)-})-}))) + ->(Identifier) } + (Statements)) + (Assignment + { (Identifier) + ->(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 d74622291..cf8bed22f 100644 --- a/test/fixtures/go/corpus/const-with-implicit-values.parseA.txt +++ b/test/fixtures/go/corpus/const-with-implicit-values.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 d74622291..cf8bed22f 100644 --- a/test/fixtures/go/corpus/const-with-implicit-values.parseB.txt +++ b/test/fixtures/go/corpus/const-with-implicit-values.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/constructors.diffA-B.txt b/test/fixtures/go/corpus/constructors.diffA-B.txt index 7ff5225d7..412da579a 100644 --- a/test/fixtures/go/corpus/constructors.diffA-B.txt +++ b/test/fixtures/go/corpus/constructors.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/constructors.diffB-A.txt b/test/fixtures/go/corpus/constructors.diffB-A.txt index 7ff5225d7..412da579a 100644 --- a/test/fixtures/go/corpus/constructors.diffB-A.txt +++ b/test/fixtures/go/corpus/constructors.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/constructors.parseA.txt b/test/fixtures/go/corpus/constructors.parseA.txt index 67a463345..55e1653d6 100644 --- a/test/fixtures/go/corpus/constructors.parseA.txt +++ b/test/fixtures/go/corpus/constructors.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/constructors.parseB.txt b/test/fixtures/go/corpus/constructors.parseB.txt index 67a463345..55e1653d6 100644 --- a/test/fixtures/go/corpus/constructors.parseB.txt +++ b/test/fixtures/go/corpus/constructors.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/float-literals.diffA-B.txt b/test/fixtures/go/corpus/float-literals.diffA-B.txt index 07225a1f4..6ed86435c 100644 --- a/test/fixtures/go/corpus/float-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/float-literals.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/float-literals.diffB-A.txt b/test/fixtures/go/corpus/float-literals.diffB-A.txt index 07225a1f4..6ed86435c 100644 --- a/test/fixtures/go/corpus/float-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/float-literals.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/float-literals.parseA.txt b/test/fixtures/go/corpus/float-literals.parseA.txt index 1bb8f4561..604d9283e 100644 --- a/test/fixtures/go/corpus/float-literals.parseA.txt +++ b/test/fixtures/go/corpus/float-literals.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/float-literals.parseB.txt b/test/fixtures/go/corpus/float-literals.parseB.txt index 1bb8f4561..604d9283e 100644 --- a/test/fixtures/go/corpus/float-literals.parseB.txt +++ b/test/fixtures/go/corpus/float-literals.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/for-statements.diffA-B.txt b/test/fixtures/go/corpus/for-statements.diffA-B.txt index 34a068f3f..d92eb40be 100644 --- a/test/fixtures/go/corpus/for-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/for-statements.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/for-statements.diffB-A.txt b/test/fixtures/go/corpus/for-statements.diffB-A.txt index 702a21acd..883185c00 100644 --- a/test/fixtures/go/corpus/for-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/for-statements.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/for-statements.parseA.txt b/test/fixtures/go/corpus/for-statements.parseA.txt index 5f6668119..bc1e52d41 100644 --- a/test/fixtures/go/corpus/for-statements.parseA.txt +++ b/test/fixtures/go/corpus/for-statements.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/for-statements.parseB.txt b/test/fixtures/go/corpus/for-statements.parseB.txt index 93ce681f2..d2429a999 100644 --- a/test/fixtures/go/corpus/for-statements.parseB.txt +++ b/test/fixtures/go/corpus/for-statements.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/function-declarations.diffA-B.txt b/test/fixtures/go/corpus/function-declarations.diffA-B.txt index f65f31e62..27ecfe94a 100644 --- a/test/fixtures/go/corpus/function-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/function-declarations.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/function-declarations.diffB-A.txt b/test/fixtures/go/corpus/function-declarations.diffB-A.txt index 1056ed0be..d59d93a6b 100644 --- a/test/fixtures/go/corpus/function-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/function-declarations.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/function-declarations.parseA.txt b/test/fixtures/go/corpus/function-declarations.parseA.txt index 452629f0e..039ffd14a 100644 --- a/test/fixtures/go/corpus/function-declarations.parseA.txt +++ b/test/fixtures/go/corpus/function-declarations.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/function-declarations.parseB.txt b/test/fixtures/go/corpus/function-declarations.parseB.txt index 8c9ffbe9a..1171706f8 100644 --- a/test/fixtures/go/corpus/function-declarations.parseB.txt +++ b/test/fixtures/go/corpus/function-declarations.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/function-literals.diffA-B.txt b/test/fixtures/go/corpus/function-literals.diffA-B.txt index 92470cd71..567e66d7c 100644 --- a/test/fixtures/go/corpus/function-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/function-literals.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/function-literals.diffB-A.txt b/test/fixtures/go/corpus/function-literals.diffB-A.txt index 92470cd71..567e66d7c 100644 --- a/test/fixtures/go/corpus/function-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/function-literals.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/function-literals.parseA.txt b/test/fixtures/go/corpus/function-literals.parseA.txt index 978efb513..fb85c202d 100644 --- a/test/fixtures/go/corpus/function-literals.parseA.txt +++ b/test/fixtures/go/corpus/function-literals.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/function-literals.parseB.txt b/test/fixtures/go/corpus/function-literals.parseB.txt index 978efb513..fb85c202d 100644 --- a/test/fixtures/go/corpus/function-literals.parseB.txt +++ b/test/fixtures/go/corpus/function-literals.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/function-types.diffA-B.txt b/test/fixtures/go/corpus/function-types.diffA-B.txt index 8a7463671..a0448276b 100644 --- a/test/fixtures/go/corpus/function-types.diffA-B.txt +++ b/test/fixtures/go/corpus/function-types.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/function-types.diffB-A.txt b/test/fixtures/go/corpus/function-types.diffB-A.txt index 27129ae93..36d6a5b2f 100644 --- a/test/fixtures/go/corpus/function-types.diffB-A.txt +++ b/test/fixtures/go/corpus/function-types.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/function-types.parseA.txt b/test/fixtures/go/corpus/function-types.parseA.txt index 71ca93ab6..a1f15a359 100644 --- a/test/fixtures/go/corpus/function-types.parseA.txt +++ b/test/fixtures/go/corpus/function-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/function-types.parseB.txt b/test/fixtures/go/corpus/function-types.parseB.txt index 2221de55b..d8dbb1623 100644 --- a/test/fixtures/go/corpus/function-types.parseB.txt +++ b/test/fixtures/go/corpus/function-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 6e514bb12..3407d1fe4 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 6e514bb12..3407d1fe4 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 328d1ff21..4c5a5ae00 100644 --- a/test/fixtures/go/corpus/go-and-defer-statements.parseA.txt +++ b/test/fixtures/go/corpus/go-and-defer-statements.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 328d1ff21..4c5a5ae00 100644 --- a/test/fixtures/go/corpus/go-and-defer-statements.parseB.txt +++ b/test/fixtures/go/corpus/go-and-defer-statements.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 1a203ec98..06941ad63 100644 --- a/test/fixtures/go/corpus/grouped-import-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/grouped-import-declarations.diffA-B.txt @@ -1,19 +1,19 @@ -(Program +(Statements (Package (Identifier)) (Statements - {+(QualifiedImport - {+(Identifier)+})+} - {+(Import - {+(TextElement)+})+} - {+(QualifiedImport - {+(Identifier)+})+} - {-(QualifiedImport - {-(Identifier)-})-} - {-(Import - {-(TextElement)-})-} - {-(QualifiedImport - {-(Identifier)-})-}) + { (QualifiedImport + {-(Identifier)-}) + ->(QualifiedImport + {+(Identifier)+}) } + { (Import + {-(TextElement)-}) + ->(Import + {+(TextElement)+}) } + { (QualifiedImport + {-(Identifier)-}) + ->(QualifiedImport + {+(Identifier)+}) }) (Function (Empty) (Identifier) 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 1a203ec98..06941ad63 100644 --- a/test/fixtures/go/corpus/grouped-import-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/grouped-import-declarations.diffB-A.txt @@ -1,19 +1,19 @@ -(Program +(Statements (Package (Identifier)) (Statements - {+(QualifiedImport - {+(Identifier)+})+} - {+(Import - {+(TextElement)+})+} - {+(QualifiedImport - {+(Identifier)+})+} - {-(QualifiedImport - {-(Identifier)-})-} - {-(Import - {-(TextElement)-})-} - {-(QualifiedImport - {-(Identifier)-})-}) + { (QualifiedImport + {-(Identifier)-}) + ->(QualifiedImport + {+(Identifier)+}) } + { (Import + {-(TextElement)-}) + ->(Import + {+(TextElement)+}) } + { (QualifiedImport + {-(Identifier)-}) + ->(QualifiedImport + {+(Identifier)+}) }) (Function (Empty) (Identifier) diff --git a/test/fixtures/go/corpus/grouped-import-declarations.parseA.txt b/test/fixtures/go/corpus/grouped-import-declarations.parseA.txt index 3056c74a1..ec86195ad 100644 --- a/test/fixtures/go/corpus/grouped-import-declarations.parseA.txt +++ b/test/fixtures/go/corpus/grouped-import-declarations.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Statements diff --git a/test/fixtures/go/corpus/grouped-import-declarations.parseB.txt b/test/fixtures/go/corpus/grouped-import-declarations.parseB.txt index 3056c74a1..ec86195ad 100644 --- a/test/fixtures/go/corpus/grouped-import-declarations.parseB.txt +++ b/test/fixtures/go/corpus/grouped-import-declarations.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (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 34b5a2048..5c49e56ea 100644 --- a/test/fixtures/go/corpus/grouped-var-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/grouped-var-declarations.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 34b5a2048..5c49e56ea 100644 --- a/test/fixtures/go/corpus/grouped-var-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/grouped-var-declarations.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/grouped-var-declarations.parseA.txt b/test/fixtures/go/corpus/grouped-var-declarations.parseA.txt index e2b812db4..9030e56aa 100644 --- a/test/fixtures/go/corpus/grouped-var-declarations.parseA.txt +++ b/test/fixtures/go/corpus/grouped-var-declarations.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/grouped-var-declarations.parseB.txt b/test/fixtures/go/corpus/grouped-var-declarations.parseB.txt index e2b812db4..9030e56aa 100644 --- a/test/fixtures/go/corpus/grouped-var-declarations.parseB.txt +++ b/test/fixtures/go/corpus/grouped-var-declarations.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/if-statements.diffA-B.txt b/test/fixtures/go/corpus/if-statements.diffA-B.txt index 85aa397a7..1c3b20551 100644 --- a/test/fixtures/go/corpus/if-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/if-statements.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/if-statements.diffB-A.txt b/test/fixtures/go/corpus/if-statements.diffB-A.txt index 5dfcda691..99716b9c2 100644 --- a/test/fixtures/go/corpus/if-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/if-statements.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/if-statements.parseA.txt b/test/fixtures/go/corpus/if-statements.parseA.txt index 1736450cf..6c80cd2f2 100644 --- a/test/fixtures/go/corpus/if-statements.parseA.txt +++ b/test/fixtures/go/corpus/if-statements.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/if-statements.parseB.txt b/test/fixtures/go/corpus/if-statements.parseB.txt index 57ddb0dc8..8b7c9a44f 100644 --- a/test/fixtures/go/corpus/if-statements.parseB.txt +++ b/test/fixtures/go/corpus/if-statements.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/imaginary-literals.diffA-B.txt b/test/fixtures/go/corpus/imaginary-literals.diffA-B.txt index 5effba7cf..fbaa3b93c 100644 --- a/test/fixtures/go/corpus/imaginary-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/imaginary-literals.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/imaginary-literals.diffB-A.txt b/test/fixtures/go/corpus/imaginary-literals.diffB-A.txt index 5effba7cf..fbaa3b93c 100644 --- a/test/fixtures/go/corpus/imaginary-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/imaginary-literals.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/imaginary-literals.parseA.txt b/test/fixtures/go/corpus/imaginary-literals.parseA.txt index f7a8584b2..c16a997a3 100644 --- a/test/fixtures/go/corpus/imaginary-literals.parseA.txt +++ b/test/fixtures/go/corpus/imaginary-literals.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/imaginary-literals.parseB.txt b/test/fixtures/go/corpus/imaginary-literals.parseB.txt index f7a8584b2..c16a997a3 100644 --- a/test/fixtures/go/corpus/imaginary-literals.parseB.txt +++ b/test/fixtures/go/corpus/imaginary-literals.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/import-statements.diffA-B.txt b/test/fixtures/go/corpus/import-statements.diffA-B.txt index 7a7da2e36..713d34676 100644 --- a/test/fixtures/go/corpus/import-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/import-statements.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Statements diff --git a/test/fixtures/go/corpus/import-statements.diffB-A.txt b/test/fixtures/go/corpus/import-statements.diffB-A.txt index 7a7da2e36..713d34676 100644 --- a/test/fixtures/go/corpus/import-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/import-statements.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Statements diff --git a/test/fixtures/go/corpus/import-statements.parseA.txt b/test/fixtures/go/corpus/import-statements.parseA.txt index 3dee6a1dc..2565893f2 100644 --- a/test/fixtures/go/corpus/import-statements.parseA.txt +++ b/test/fixtures/go/corpus/import-statements.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Statements diff --git a/test/fixtures/go/corpus/import-statements.parseB.txt b/test/fixtures/go/corpus/import-statements.parseB.txt index 3dee6a1dc..2565893f2 100644 --- a/test/fixtures/go/corpus/import-statements.parseB.txt +++ b/test/fixtures/go/corpus/import-statements.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (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 45abdcf05..cf99b205c 100644 --- a/test/fixtures/go/corpus/increment-decrement-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/increment-decrement-statements.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 3235fddb4..abcf2963e 100644 --- a/test/fixtures/go/corpus/increment-decrement-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/increment-decrement-statements.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/increment-decrement-statements.parseA.txt b/test/fixtures/go/corpus/increment-decrement-statements.parseA.txt index 31efb99ab..178f4ba45 100644 --- a/test/fixtures/go/corpus/increment-decrement-statements.parseA.txt +++ b/test/fixtures/go/corpus/increment-decrement-statements.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/increment-decrement-statements.parseB.txt b/test/fixtures/go/corpus/increment-decrement-statements.parseB.txt index 3a5c0c90e..af789a301 100644 --- a/test/fixtures/go/corpus/increment-decrement-statements.parseB.txt +++ b/test/fixtures/go/corpus/increment-decrement-statements.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/int-literals.diffA-B.txt b/test/fixtures/go/corpus/int-literals.diffA-B.txt index 0509a4b55..4a75d07e5 100644 --- a/test/fixtures/go/corpus/int-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/int-literals.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/int-literals.diffB-A.txt b/test/fixtures/go/corpus/int-literals.diffB-A.txt index 0509a4b55..4a75d07e5 100644 --- a/test/fixtures/go/corpus/int-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/int-literals.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/int-literals.parseA.txt b/test/fixtures/go/corpus/int-literals.parseA.txt index 866d153dd..148e2cf77 100644 --- a/test/fixtures/go/corpus/int-literals.parseA.txt +++ b/test/fixtures/go/corpus/int-literals.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/int-literals.parseB.txt b/test/fixtures/go/corpus/int-literals.parseB.txt index 866d153dd..148e2cf77 100644 --- a/test/fixtures/go/corpus/int-literals.parseB.txt +++ b/test/fixtures/go/corpus/int-literals.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/interface-types.diffA-B.txt b/test/fixtures/go/corpus/interface-types.diffA-B.txt index 7dd0e89fb..edae4db17 100644 --- a/test/fixtures/go/corpus/interface-types.diffA-B.txt +++ b/test/fixtures/go/corpus/interface-types.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/interface-types.diffB-A.txt b/test/fixtures/go/corpus/interface-types.diffB-A.txt index 7dd0e89fb..edae4db17 100644 --- a/test/fixtures/go/corpus/interface-types.diffB-A.txt +++ b/test/fixtures/go/corpus/interface-types.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/interface-types.parseA.txt b/test/fixtures/go/corpus/interface-types.parseA.txt index 4c29cbcbc..dc46d6ef8 100644 --- a/test/fixtures/go/corpus/interface-types.parseA.txt +++ b/test/fixtures/go/corpus/interface-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/interface-types.parseB.txt b/test/fixtures/go/corpus/interface-types.parseB.txt index 4c29cbcbc..dc46d6ef8 100644 --- a/test/fixtures/go/corpus/interface-types.parseB.txt +++ b/test/fixtures/go/corpus/interface-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/label-statements.diffA-B.txt b/test/fixtures/go/corpus/label-statements.diffA-B.txt index 2b1b97ef6..ffd763e9e 100644 --- a/test/fixtures/go/corpus/label-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/label-statements.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/label-statements.diffB-A.txt b/test/fixtures/go/corpus/label-statements.diffB-A.txt index 2b1b97ef6..ffd763e9e 100644 --- a/test/fixtures/go/corpus/label-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/label-statements.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/label-statements.parseA.txt b/test/fixtures/go/corpus/label-statements.parseA.txt index c99e5541c..d88033fdc 100644 --- a/test/fixtures/go/corpus/label-statements.parseA.txt +++ b/test/fixtures/go/corpus/label-statements.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/label-statements.parseB.txt b/test/fixtures/go/corpus/label-statements.parseB.txt index c99e5541c..d88033fdc 100644 --- a/test/fixtures/go/corpus/label-statements.parseB.txt +++ b/test/fixtures/go/corpus/label-statements.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/map-literals.diffA-B.txt b/test/fixtures/go/corpus/map-literals.diffA-B.txt index bb2ce33a2..1f30850dc 100644 --- a/test/fixtures/go/corpus/map-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/map-literals.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/map-literals.diffB-A.txt b/test/fixtures/go/corpus/map-literals.diffB-A.txt index bb2ce33a2..1f30850dc 100644 --- a/test/fixtures/go/corpus/map-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/map-literals.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/map-literals.parseA.txt b/test/fixtures/go/corpus/map-literals.parseA.txt index f3f8dcb3c..f4d0cc528 100644 --- a/test/fixtures/go/corpus/map-literals.parseA.txt +++ b/test/fixtures/go/corpus/map-literals.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/map-literals.parseB.txt b/test/fixtures/go/corpus/map-literals.parseB.txt index f3f8dcb3c..f4d0cc528 100644 --- a/test/fixtures/go/corpus/map-literals.parseB.txt +++ b/test/fixtures/go/corpus/map-literals.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/map-types.diffA-B.txt b/test/fixtures/go/corpus/map-types.diffA-B.txt index 11c405f5e..32c2675cb 100644 --- a/test/fixtures/go/corpus/map-types.diffA-B.txt +++ b/test/fixtures/go/corpus/map-types.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/map-types.diffB-A.txt b/test/fixtures/go/corpus/map-types.diffB-A.txt index 11c405f5e..32c2675cb 100644 --- a/test/fixtures/go/corpus/map-types.diffB-A.txt +++ b/test/fixtures/go/corpus/map-types.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/map-types.parseA.txt b/test/fixtures/go/corpus/map-types.parseA.txt index 6128e1b82..83a980d60 100644 --- a/test/fixtures/go/corpus/map-types.parseA.txt +++ b/test/fixtures/go/corpus/map-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/map-types.parseB.txt b/test/fixtures/go/corpus/map-types.parseB.txt index 6128e1b82..83a980d60 100644 --- a/test/fixtures/go/corpus/map-types.parseB.txt +++ b/test/fixtures/go/corpus/map-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/method-declarations.diffA-B.txt b/test/fixtures/go/corpus/method-declarations.diffA-B.txt index 847454e0e..5eb057583 100644 --- a/test/fixtures/go/corpus/method-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/method-declarations.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/method-declarations.diffB-A.txt b/test/fixtures/go/corpus/method-declarations.diffB-A.txt index 6329377d8..f6437a30a 100644 --- a/test/fixtures/go/corpus/method-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/method-declarations.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/method-declarations.parseA.txt b/test/fixtures/go/corpus/method-declarations.parseA.txt index 9fced1d8c..c6adc792d 100644 --- a/test/fixtures/go/corpus/method-declarations.parseA.txt +++ b/test/fixtures/go/corpus/method-declarations.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/method-declarations.parseB.txt b/test/fixtures/go/corpus/method-declarations.parseB.txt index 1185a4db2..11b4b6f20 100644 --- a/test/fixtures/go/corpus/method-declarations.parseB.txt +++ b/test/fixtures/go/corpus/method-declarations.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 8f06d89dd..1d42e7ea2 100644 --- a/test/fixtures/go/corpus/modifying-struct-fields.diffA-B.txt +++ b/test/fixtures/go/corpus/modifying-struct-fields.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 239eeee8e..33594c4f6 100644 --- a/test/fixtures/go/corpus/modifying-struct-fields.diffB-A.txt +++ b/test/fixtures/go/corpus/modifying-struct-fields.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/modifying-struct-fields.parseA.txt b/test/fixtures/go/corpus/modifying-struct-fields.parseA.txt index 9a8d9a7e4..b9254b59f 100644 --- a/test/fixtures/go/corpus/modifying-struct-fields.parseA.txt +++ b/test/fixtures/go/corpus/modifying-struct-fields.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/modifying-struct-fields.parseB.txt b/test/fixtures/go/corpus/modifying-struct-fields.parseB.txt index 79a74af4a..50a7ce391 100644 --- a/test/fixtures/go/corpus/modifying-struct-fields.parseB.txt +++ b/test/fixtures/go/corpus/modifying-struct-fields.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 43e79de42..76cab465a 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 43e79de42..76cab465a 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 dcbdb5c2b..220123a5f 100644 --- a/test/fixtures/go/corpus/parameter-declarations-with-types.parseA.txt +++ b/test/fixtures/go/corpus/parameter-declarations-with-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 dcbdb5c2b..220123a5f 100644 --- a/test/fixtures/go/corpus/parameter-declarations-with-types.parseB.txt +++ b/test/fixtures/go/corpus/parameter-declarations-with-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/pointer-types.diffA-B.txt b/test/fixtures/go/corpus/pointer-types.diffA-B.txt index 15cb6604f..17e2b4cae 100644 --- a/test/fixtures/go/corpus/pointer-types.diffA-B.txt +++ b/test/fixtures/go/corpus/pointer-types.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/pointer-types.diffB-A.txt b/test/fixtures/go/corpus/pointer-types.diffB-A.txt index 15cb6604f..17e2b4cae 100644 --- a/test/fixtures/go/corpus/pointer-types.diffB-A.txt +++ b/test/fixtures/go/corpus/pointer-types.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/pointer-types.parseA.txt b/test/fixtures/go/corpus/pointer-types.parseA.txt index cd4e58bbf..e8c3d5719 100644 --- a/test/fixtures/go/corpus/pointer-types.parseA.txt +++ b/test/fixtures/go/corpus/pointer-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/pointer-types.parseB.txt b/test/fixtures/go/corpus/pointer-types.parseB.txt index cd4e58bbf..e8c3d5719 100644 --- a/test/fixtures/go/corpus/pointer-types.parseB.txt +++ b/test/fixtures/go/corpus/pointer-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/qualified-types.diffA-B.txt b/test/fixtures/go/corpus/qualified-types.diffA-B.txt index 8ad11b154..d3ed706f0 100644 --- a/test/fixtures/go/corpus/qualified-types.diffA-B.txt +++ b/test/fixtures/go/corpus/qualified-types.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/qualified-types.diffB-A.txt b/test/fixtures/go/corpus/qualified-types.diffB-A.txt index 8ad11b154..d3ed706f0 100644 --- a/test/fixtures/go/corpus/qualified-types.diffB-A.txt +++ b/test/fixtures/go/corpus/qualified-types.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/qualified-types.parseA.txt b/test/fixtures/go/corpus/qualified-types.parseA.txt index 2659648a1..f380eedce 100644 --- a/test/fixtures/go/corpus/qualified-types.parseA.txt +++ b/test/fixtures/go/corpus/qualified-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/qualified-types.parseB.txt b/test/fixtures/go/corpus/qualified-types.parseB.txt index 2659648a1..f380eedce 100644 --- a/test/fixtures/go/corpus/qualified-types.parseB.txt +++ b/test/fixtures/go/corpus/qualified-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/rune-literals.diffA-B.txt b/test/fixtures/go/corpus/rune-literals.diffA-B.txt index bf009a8d1..48cd0f753 100644 --- a/test/fixtures/go/corpus/rune-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/rune-literals.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Statements diff --git a/test/fixtures/go/corpus/rune-literals.diffB-A.txt b/test/fixtures/go/corpus/rune-literals.diffB-A.txt index bf009a8d1..48cd0f753 100644 --- a/test/fixtures/go/corpus/rune-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/rune-literals.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Statements diff --git a/test/fixtures/go/corpus/rune-literals.parseA.txt b/test/fixtures/go/corpus/rune-literals.parseA.txt index 90ad8d2dd..3e0b36dc3 100644 --- a/test/fixtures/go/corpus/rune-literals.parseA.txt +++ b/test/fixtures/go/corpus/rune-literals.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Statements diff --git a/test/fixtures/go/corpus/rune-literals.parseB.txt b/test/fixtures/go/corpus/rune-literals.parseB.txt index 90ad8d2dd..3e0b36dc3 100644 --- a/test/fixtures/go/corpus/rune-literals.parseB.txt +++ b/test/fixtures/go/corpus/rune-literals.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Statements diff --git a/test/fixtures/go/corpus/select-statements.diffA-B.txt b/test/fixtures/go/corpus/select-statements.diffA-B.txt index 12ebaa2dd..681781ff1 100644 --- a/test/fixtures/go/corpus/select-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/select-statements.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/select-statements.diffB-A.txt b/test/fixtures/go/corpus/select-statements.diffB-A.txt index e1fdedccb..68e10a88b 100644 --- a/test/fixtures/go/corpus/select-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/select-statements.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/select-statements.parseA.txt b/test/fixtures/go/corpus/select-statements.parseA.txt index 7674928c7..8d27e574b 100644 --- a/test/fixtures/go/corpus/select-statements.parseA.txt +++ b/test/fixtures/go/corpus/select-statements.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/select-statements.parseB.txt b/test/fixtures/go/corpus/select-statements.parseB.txt index e5ed101b4..f6829953a 100644 --- a/test/fixtures/go/corpus/select-statements.parseB.txt +++ b/test/fixtures/go/corpus/select-statements.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/selector-expressions.diffA-B.txt b/test/fixtures/go/corpus/selector-expressions.diffA-B.txt index 7930ef495..589674ad0 100644 --- a/test/fixtures/go/corpus/selector-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/selector-expressions.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/selector-expressions.diffB-A.txt b/test/fixtures/go/corpus/selector-expressions.diffB-A.txt index 7930ef495..589674ad0 100644 --- a/test/fixtures/go/corpus/selector-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/selector-expressions.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/selector-expressions.parseA.txt b/test/fixtures/go/corpus/selector-expressions.parseA.txt index 6635631f2..3a9be8caf 100644 --- a/test/fixtures/go/corpus/selector-expressions.parseA.txt +++ b/test/fixtures/go/corpus/selector-expressions.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/selector-expressions.parseB.txt b/test/fixtures/go/corpus/selector-expressions.parseB.txt index 6635631f2..3a9be8caf 100644 --- a/test/fixtures/go/corpus/selector-expressions.parseB.txt +++ b/test/fixtures/go/corpus/selector-expressions.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/send-statements.diffA-B.txt b/test/fixtures/go/corpus/send-statements.diffA-B.txt index 41e14f0e0..491a0998d 100644 --- a/test/fixtures/go/corpus/send-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/send-statements.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/send-statements.diffB-A.txt b/test/fixtures/go/corpus/send-statements.diffB-A.txt index 41e14f0e0..491a0998d 100644 --- a/test/fixtures/go/corpus/send-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/send-statements.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/send-statements.parseA.txt b/test/fixtures/go/corpus/send-statements.parseA.txt index 82d99394b..87d06fc46 100644 --- a/test/fixtures/go/corpus/send-statements.parseA.txt +++ b/test/fixtures/go/corpus/send-statements.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/send-statements.parseB.txt b/test/fixtures/go/corpus/send-statements.parseB.txt index 82d99394b..87d06fc46 100644 --- a/test/fixtures/go/corpus/send-statements.parseB.txt +++ b/test/fixtures/go/corpus/send-statements.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 b7a258c18..e87c67689 100644 --- a/test/fixtures/go/corpus/short-var-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/short-var-declarations.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 b7a258c18..e87c67689 100644 --- a/test/fixtures/go/corpus/short-var-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/short-var-declarations.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/short-var-declarations.parseA.txt b/test/fixtures/go/corpus/short-var-declarations.parseA.txt index bbacb990a..8e483ac19 100644 --- a/test/fixtures/go/corpus/short-var-declarations.parseA.txt +++ b/test/fixtures/go/corpus/short-var-declarations.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/short-var-declarations.parseB.txt b/test/fixtures/go/corpus/short-var-declarations.parseB.txt index bbacb990a..8e483ac19 100644 --- a/test/fixtures/go/corpus/short-var-declarations.parseB.txt +++ b/test/fixtures/go/corpus/short-var-declarations.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 838735730..efc4ca634 100644 --- a/test/fixtures/go/corpus/single-import-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/single-import-declarations.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) { (QualifiedImport 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 838735730..efc4ca634 100644 --- a/test/fixtures/go/corpus/single-import-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/single-import-declarations.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) { (QualifiedImport diff --git a/test/fixtures/go/corpus/single-import-declarations.parseA.txt b/test/fixtures/go/corpus/single-import-declarations.parseA.txt index dc96d2e05..17640e932 100644 --- a/test/fixtures/go/corpus/single-import-declarations.parseA.txt +++ b/test/fixtures/go/corpus/single-import-declarations.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (QualifiedImport diff --git a/test/fixtures/go/corpus/single-import-declarations.parseB.txt b/test/fixtures/go/corpus/single-import-declarations.parseB.txt index dc96d2e05..17640e932 100644 --- a/test/fixtures/go/corpus/single-import-declarations.parseB.txt +++ b/test/fixtures/go/corpus/single-import-declarations.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (QualifiedImport 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 f18abdfa2..d91203eb6 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 f18abdfa2..d91203eb6 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 d7e7e69ec..84afeae8a 100644 --- a/test/fixtures/go/corpus/single-line-function-declarations.parseA.txt +++ b/test/fixtures/go/corpus/single-line-function-declarations.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 d7e7e69ec..84afeae8a 100644 --- a/test/fixtures/go/corpus/single-line-function-declarations.parseB.txt +++ b/test/fixtures/go/corpus/single-line-function-declarations.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/slice-expressions.diffA-B.txt b/test/fixtures/go/corpus/slice-expressions.diffA-B.txt index afdd3980e..fec4aed20 100644 --- a/test/fixtures/go/corpus/slice-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/slice-expressions.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -18,24 +18,33 @@ { (Integer) ->(Integer) } (Empty)) - (Slice - (Identifier) - { (Empty) - ->(Integer) } - { (Empty) - ->(Integer) } - (Empty)) - (Slice - (Identifier) - { (Integer) - ->(Integer) } - { (Integer) - ->(Integer) } - { (Integer) - ->(Integer) }) - (Slice - { (Identifier) - ->(Identifier) } - (Integer) - (Integer) - (Empty))))) + {+(Slice + {+(Identifier)+} + {+(Integer)+} + {+(Integer)+} + {+(Empty)+})+} + {+(Slice + {+(Identifier)+} + {+(Integer)+} + {+(Integer)+} + {+(Integer)+})+} + {+(Slice + {+(Identifier)+} + {+(Integer)+} + {+(Integer)+} + {+(Empty)+})+} + {-(Slice + {-(Identifier)-} + {-(Empty)-} + {-(Empty)-} + {-(Empty)-})-} + {-(Slice + {-(Identifier)-} + {-(Integer)-} + {-(Integer)-} + {-(Integer)-})-} + {-(Slice + {-(Identifier)-} + {-(Integer)-} + {-(Integer)-} + {-(Empty)-})-}))) diff --git a/test/fixtures/go/corpus/slice-expressions.diffB-A.txt b/test/fixtures/go/corpus/slice-expressions.diffB-A.txt index 0f1c22f17..75d305554 100644 --- a/test/fixtures/go/corpus/slice-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/slice-expressions.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -18,24 +18,30 @@ { (Integer) ->(Integer) } (Empty)) - (Slice - (Identifier) - { (Integer) - ->(Empty) } - { (Integer) - ->(Empty) } - (Empty)) - (Slice - (Identifier) - { (Integer) - ->(Integer) } - { (Integer) - ->(Integer) } - { (Integer) - ->(Integer) }) + {+(Slice + {+(Identifier)+} + {+(Empty)+} + {+(Empty)+} + {+(Empty)+})+} (Slice { (Identifier) ->(Identifier) } (Integer) (Integer) - (Empty))))) + { (Empty) + ->(Integer) }) + {+(Slice + {+(Identifier)+} + {+(Integer)+} + {+(Integer)+} + {+(Empty)+})+} + {-(Slice + {-(Identifier)-} + {-(Integer)-} + {-(Integer)-} + {-(Integer)-})-} + {-(Slice + {-(Identifier)-} + {-(Integer)-} + {-(Integer)-} + {-(Empty)-})-}))) diff --git a/test/fixtures/go/corpus/slice-expressions.parseA.txt b/test/fixtures/go/corpus/slice-expressions.parseA.txt index b7271293b..c3d64892a 100644 --- a/test/fixtures/go/corpus/slice-expressions.parseA.txt +++ b/test/fixtures/go/corpus/slice-expressions.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/slice-expressions.parseB.txt b/test/fixtures/go/corpus/slice-expressions.parseB.txt index 5b69a0f3c..cac34d174 100644 --- a/test/fixtures/go/corpus/slice-expressions.parseB.txt +++ b/test/fixtures/go/corpus/slice-expressions.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/slice-literals.diffA-B.txt b/test/fixtures/go/corpus/slice-literals.diffA-B.txt index f0dd4b87f..aaab1bac6 100644 --- a/test/fixtures/go/corpus/slice-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/slice-literals.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/slice-literals.diffB-A.txt b/test/fixtures/go/corpus/slice-literals.diffB-A.txt index 221351ea1..4a75ef1f1 100644 --- a/test/fixtures/go/corpus/slice-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/slice-literals.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/slice-literals.parseA.txt b/test/fixtures/go/corpus/slice-literals.parseA.txt index 9434a9460..8e13f9ee0 100644 --- a/test/fixtures/go/corpus/slice-literals.parseA.txt +++ b/test/fixtures/go/corpus/slice-literals.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/slice-literals.parseB.txt b/test/fixtures/go/corpus/slice-literals.parseB.txt index c9e74f4fc..686203d38 100644 --- a/test/fixtures/go/corpus/slice-literals.parseB.txt +++ b/test/fixtures/go/corpus/slice-literals.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/slice-types.diffA-B.txt b/test/fixtures/go/corpus/slice-types.diffA-B.txt index f546172ad..6db40989c 100644 --- a/test/fixtures/go/corpus/slice-types.diffA-B.txt +++ b/test/fixtures/go/corpus/slice-types.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/slice-types.diffB-A.txt b/test/fixtures/go/corpus/slice-types.diffB-A.txt index 2686dc34a..df53f7c7c 100644 --- a/test/fixtures/go/corpus/slice-types.diffB-A.txt +++ b/test/fixtures/go/corpus/slice-types.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/slice-types.parseA.txt b/test/fixtures/go/corpus/slice-types.parseA.txt index bbed0bb87..5ab10b4c3 100644 --- a/test/fixtures/go/corpus/slice-types.parseA.txt +++ b/test/fixtures/go/corpus/slice-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/slice-types.parseB.txt b/test/fixtures/go/corpus/slice-types.parseB.txt index 5573c3321..0cfdc462e 100644 --- a/test/fixtures/go/corpus/slice-types.parseB.txt +++ b/test/fixtures/go/corpus/slice-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/string-literals.diffA-B.txt b/test/fixtures/go/corpus/string-literals.diffA-B.txt index 1046acf29..c5d545073 100644 --- a/test/fixtures/go/corpus/string-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/string-literals.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/string-literals.diffB-A.txt b/test/fixtures/go/corpus/string-literals.diffB-A.txt index 1046acf29..c5d545073 100644 --- a/test/fixtures/go/corpus/string-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/string-literals.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/string-literals.parseA.txt b/test/fixtures/go/corpus/string-literals.parseA.txt index 9f0a2a1b2..cc4ef77dd 100644 --- a/test/fixtures/go/corpus/string-literals.parseA.txt +++ b/test/fixtures/go/corpus/string-literals.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/string-literals.parseB.txt b/test/fixtures/go/corpus/string-literals.parseB.txt index 9f0a2a1b2..cc4ef77dd 100644 --- a/test/fixtures/go/corpus/string-literals.parseB.txt +++ b/test/fixtures/go/corpus/string-literals.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 cbc6a9a3b..1d0b7c811 100644 --- a/test/fixtures/go/corpus/struct-field-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/struct-field-declarations.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 94db2fd9f..b7a5a2f01 100644 --- a/test/fixtures/go/corpus/struct-field-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/struct-field-declarations.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/struct-field-declarations.parseA.txt b/test/fixtures/go/corpus/struct-field-declarations.parseA.txt index 405ca456d..a177758b5 100644 --- a/test/fixtures/go/corpus/struct-field-declarations.parseA.txt +++ b/test/fixtures/go/corpus/struct-field-declarations.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/struct-field-declarations.parseB.txt b/test/fixtures/go/corpus/struct-field-declarations.parseB.txt index 42235b5b4..a35c7eba2 100644 --- a/test/fixtures/go/corpus/struct-field-declarations.parseB.txt +++ b/test/fixtures/go/corpus/struct-field-declarations.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/struct-literals.diffA-B.txt b/test/fixtures/go/corpus/struct-literals.diffA-B.txt index 7b90f5a0e..fa62a4845 100644 --- a/test/fixtures/go/corpus/struct-literals.diffA-B.txt +++ b/test/fixtures/go/corpus/struct-literals.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/struct-literals.diffB-A.txt b/test/fixtures/go/corpus/struct-literals.diffB-A.txt index 7b90f5a0e..fa62a4845 100644 --- a/test/fixtures/go/corpus/struct-literals.diffB-A.txt +++ b/test/fixtures/go/corpus/struct-literals.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/struct-literals.parseA.txt b/test/fixtures/go/corpus/struct-literals.parseA.txt index e8f5c9e73..52dcb474d 100644 --- a/test/fixtures/go/corpus/struct-literals.parseA.txt +++ b/test/fixtures/go/corpus/struct-literals.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/struct-literals.parseB.txt b/test/fixtures/go/corpus/struct-literals.parseB.txt index e8f5c9e73..52dcb474d 100644 --- a/test/fixtures/go/corpus/struct-literals.parseB.txt +++ b/test/fixtures/go/corpus/struct-literals.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/struct-types.diffA-B.txt b/test/fixtures/go/corpus/struct-types.diffA-B.txt index 1861a7c71..00224e093 100644 --- a/test/fixtures/go/corpus/struct-types.diffA-B.txt +++ b/test/fixtures/go/corpus/struct-types.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/struct-types.diffB-A.txt b/test/fixtures/go/corpus/struct-types.diffB-A.txt index 1861a7c71..00224e093 100644 --- a/test/fixtures/go/corpus/struct-types.diffB-A.txt +++ b/test/fixtures/go/corpus/struct-types.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/struct-types.parseA.txt b/test/fixtures/go/corpus/struct-types.parseA.txt index 7abd634c1..bd6e6cb4d 100644 --- a/test/fixtures/go/corpus/struct-types.parseA.txt +++ b/test/fixtures/go/corpus/struct-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/struct-types.parseB.txt b/test/fixtures/go/corpus/struct-types.parseB.txt index 7abd634c1..bd6e6cb4d 100644 --- a/test/fixtures/go/corpus/struct-types.parseB.txt +++ b/test/fixtures/go/corpus/struct-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/switch-statements.diffA-B.txt b/test/fixtures/go/corpus/switch-statements.diffA-B.txt index 599316453..d7ea3f556 100644 --- a/test/fixtures/go/corpus/switch-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/switch-statements.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -18,39 +18,27 @@ (Identifier) (Statements) (Empty))) - {+(Pattern - {+(LessThan - {+(Identifier)+} - {+(Identifier)+})+} - {+(Call - {+(Identifier)+} - {+(Statements)+} - {+(Empty)+})+})+} - {+(Pattern - {+(Equal - {+(Identifier)+} - {+(Integer)+})+} - {+(Call - {+(Identifier)+} - {+(Statements)+} - {+(Empty)+})+})+} - {-(Pattern - {-(LessThan - {-(Identifier)-} - {-(Identifier)-})-} + (Pattern + (LessThan + { (Identifier) + ->(Identifier) } + { (Identifier) + ->(Identifier) }) {-(Context {-(Comment)-} - {-(Call - {-(Identifier)-} - {-(Statements)-} - {-(Empty)-})-})-})-} + (Call + (Identifier) + (Statements) + (Empty)))-}) {-(Context {-(Comment)-} - {-(Pattern - {-(Equal - {-(Identifier)-} - {-(Integer)-})-} - {-(Call - {-(Identifier)-} - {-(Statements)-} - {-(Empty)-})-})-})-})))) + (Pattern + (Equal + { (Identifier) + ->(Identifier) } + (Integer)) + (Call + { (Identifier) + ->(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 99347a9a8..98a9f7aab 100644 --- a/test/fixtures/go/corpus/switch-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/switch-statements.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -18,35 +18,27 @@ (Identifier) (Statements) (Empty))) - {+(Pattern - {+(LessThan - {+(Identifier)+} - {+(Identifier)+})+} + (Pattern + (LessThan + { (Identifier) + ->(Identifier) } + { (Identifier) + ->(Identifier) }) {+(Context {+(Comment)+} - {+(Call - {+(Identifier)+} - {+(Statements)+} - {+(Empty)+})+})+})+} + (Call + (Identifier) + (Statements) + (Empty)))+}) {+(Context {+(Comment)+} (Pattern - { (LessThan - {-(Identifier)-} - {-(Identifier)-}) - ->(Equal - {+(Identifier)+} - {+(Integer)+}) } + (Equal + { (Identifier) + ->(Identifier) } + (Integer)) (Call { (Identifier) ->(Identifier) } (Statements) - (Empty))))+} - {-(Pattern - {-(Equal - {-(Identifier)-} - {-(Integer)-})-} - {-(Call - {-(Identifier)-} - {-(Statements)-} - {-(Empty)-})-})-})))) + (Empty))))+})))) diff --git a/test/fixtures/go/corpus/switch-statements.parseA.txt b/test/fixtures/go/corpus/switch-statements.parseA.txt index ecd260c88..90eb64110 100644 --- a/test/fixtures/go/corpus/switch-statements.parseA.txt +++ b/test/fixtures/go/corpus/switch-statements.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/switch-statements.parseB.txt b/test/fixtures/go/corpus/switch-statements.parseB.txt index 5b18abbb1..bb5e3707c 100644 --- a/test/fixtures/go/corpus/switch-statements.parseB.txt +++ b/test/fixtures/go/corpus/switch-statements.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-aliases.diffA-B.txt b/test/fixtures/go/corpus/type-aliases.diffA-B.txt index 8e8ad3ef7..f202aa157 100644 --- a/test/fixtures/go/corpus/type-aliases.diffA-B.txt +++ b/test/fixtures/go/corpus/type-aliases.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-aliases.diffB-A.txt b/test/fixtures/go/corpus/type-aliases.diffB-A.txt index 8e8ad3ef7..f202aa157 100644 --- a/test/fixtures/go/corpus/type-aliases.diffB-A.txt +++ b/test/fixtures/go/corpus/type-aliases.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-aliases.parseA.txt b/test/fixtures/go/corpus/type-aliases.parseA.txt index a8036faee..48ee05723 100644 --- a/test/fixtures/go/corpus/type-aliases.parseA.txt +++ b/test/fixtures/go/corpus/type-aliases.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-aliases.parseB.txt b/test/fixtures/go/corpus/type-aliases.parseB.txt index a8036faee..48ee05723 100644 --- a/test/fixtures/go/corpus/type-aliases.parseB.txt +++ b/test/fixtures/go/corpus/type-aliases.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 55b905eb6..cec0cdbb4 100644 --- a/test/fixtures/go/corpus/type-assertion-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/type-assertion-expressions.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 55b905eb6..cec0cdbb4 100644 --- a/test/fixtures/go/corpus/type-assertion-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/type-assertion-expressions.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-assertion-expressions.parseA.txt b/test/fixtures/go/corpus/type-assertion-expressions.parseA.txt index 2b9a80548..64a2128a2 100644 --- a/test/fixtures/go/corpus/type-assertion-expressions.parseA.txt +++ b/test/fixtures/go/corpus/type-assertion-expressions.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-assertion-expressions.parseB.txt b/test/fixtures/go/corpus/type-assertion-expressions.parseB.txt index 2b9a80548..64a2128a2 100644 --- a/test/fixtures/go/corpus/type-assertion-expressions.parseB.txt +++ b/test/fixtures/go/corpus/type-assertion-expressions.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 bf3f4ef5a..bcd28b7c2 100644 --- a/test/fixtures/go/corpus/type-conversion-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/type-conversion-expressions.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 bf3f4ef5a..bcd28b7c2 100644 --- a/test/fixtures/go/corpus/type-conversion-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/type-conversion-expressions.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-conversion-expressions.parseA.txt b/test/fixtures/go/corpus/type-conversion-expressions.parseA.txt index 5d85a36ae..dd2ed84d1 100644 --- a/test/fixtures/go/corpus/type-conversion-expressions.parseA.txt +++ b/test/fixtures/go/corpus/type-conversion-expressions.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-conversion-expressions.parseB.txt b/test/fixtures/go/corpus/type-conversion-expressions.parseB.txt index 5d85a36ae..dd2ed84d1 100644 --- a/test/fixtures/go/corpus/type-conversion-expressions.parseB.txt +++ b/test/fixtures/go/corpus/type-conversion-expressions.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-declarations.diffA-B.txt b/test/fixtures/go/corpus/type-declarations.diffA-B.txt index 5b29285f2..07b5f067b 100644 --- a/test/fixtures/go/corpus/type-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/type-declarations.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-declarations.diffB-A.txt b/test/fixtures/go/corpus/type-declarations.diffB-A.txt index 5b29285f2..07b5f067b 100644 --- a/test/fixtures/go/corpus/type-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/type-declarations.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-declarations.parseA.txt b/test/fixtures/go/corpus/type-declarations.parseA.txt index 48b9b35ed..0833c568a 100644 --- a/test/fixtures/go/corpus/type-declarations.parseA.txt +++ b/test/fixtures/go/corpus/type-declarations.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-declarations.parseB.txt b/test/fixtures/go/corpus/type-declarations.parseB.txt index 48b9b35ed..0833c568a 100644 --- a/test/fixtures/go/corpus/type-declarations.parseB.txt +++ b/test/fixtures/go/corpus/type-declarations.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 f4e2d27ae..87c7a94e9 100644 --- a/test/fixtures/go/corpus/type-switch-statements.diffA-B.txt +++ b/test/fixtures/go/corpus/type-switch-statements.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 cfb3afcfd..798b15b33 100644 --- a/test/fixtures/go/corpus/type-switch-statements.diffB-A.txt +++ b/test/fixtures/go/corpus/type-switch-statements.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-switch-statements.parseA.txt b/test/fixtures/go/corpus/type-switch-statements.parseA.txt index e3d29707a..72d1acba5 100644 --- a/test/fixtures/go/corpus/type-switch-statements.parseA.txt +++ b/test/fixtures/go/corpus/type-switch-statements.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/type-switch-statements.parseB.txt b/test/fixtures/go/corpus/type-switch-statements.parseB.txt index 28ff0d9fa..629abdf99 100644 --- a/test/fixtures/go/corpus/type-switch-statements.parseB.txt +++ b/test/fixtures/go/corpus/type-switch-statements.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/unary-expressions.diffA-B.txt b/test/fixtures/go/corpus/unary-expressions.diffA-B.txt index 6aab2877a..45d6fc72f 100644 --- a/test/fixtures/go/corpus/unary-expressions.diffA-B.txt +++ b/test/fixtures/go/corpus/unary-expressions.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -8,25 +8,35 @@ (Statements { (Identifier) ->(Identifier) } - (Negate - { (Identifier) - ->(Identifier) }) - (Not - (ReceiveOperator - { (Identifier) - ->(Identifier) })) - (Pointer - (Call - { (Identifier) - ->(Identifier) } - (Statements) - (Empty))) - (Complement - { (Identifier) - ->(Identifier) }) - (Reference - { (Identifier) - ->(Identifier) }) - (ReceiveOperator - { (Identifier) - ->(Identifier) })))) + {+(Negate + {+(Identifier)+})+} + {+(Not + {+(ReceiveOperator + {+(Identifier)+})+})+} + {+(Pointer + {+(Call + {+(Identifier)+} + {+(Statements)+} + {+(Empty)+})+})+} + {+(Complement + {+(Identifier)+})+} + {+(Reference + {+(Identifier)+})+} + {+(ReceiveOperator + {+(Identifier)+})+} + {-(Negate + {-(Identifier)-})-} + {-(Not + {-(ReceiveOperator + {-(Identifier)-})-})-} + {-(Pointer + {-(Call + {-(Identifier)-} + {-(Statements)-} + {-(Empty)-})-})-} + {-(Complement + {-(Identifier)-})-} + {-(Reference + {-(Identifier)-})-} + {-(ReceiveOperator + {-(Identifier)-})-}))) diff --git a/test/fixtures/go/corpus/unary-expressions.diffB-A.txt b/test/fixtures/go/corpus/unary-expressions.diffB-A.txt index 6aab2877a..45d6fc72f 100644 --- a/test/fixtures/go/corpus/unary-expressions.diffB-A.txt +++ b/test/fixtures/go/corpus/unary-expressions.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function @@ -8,25 +8,35 @@ (Statements { (Identifier) ->(Identifier) } - (Negate - { (Identifier) - ->(Identifier) }) - (Not - (ReceiveOperator - { (Identifier) - ->(Identifier) })) - (Pointer - (Call - { (Identifier) - ->(Identifier) } - (Statements) - (Empty))) - (Complement - { (Identifier) - ->(Identifier) }) - (Reference - { (Identifier) - ->(Identifier) }) - (ReceiveOperator - { (Identifier) - ->(Identifier) })))) + {+(Negate + {+(Identifier)+})+} + {+(Not + {+(ReceiveOperator + {+(Identifier)+})+})+} + {+(Pointer + {+(Call + {+(Identifier)+} + {+(Statements)+} + {+(Empty)+})+})+} + {+(Complement + {+(Identifier)+})+} + {+(Reference + {+(Identifier)+})+} + {+(ReceiveOperator + {+(Identifier)+})+} + {-(Negate + {-(Identifier)-})-} + {-(Not + {-(ReceiveOperator + {-(Identifier)-})-})-} + {-(Pointer + {-(Call + {-(Identifier)-} + {-(Statements)-} + {-(Empty)-})-})-} + {-(Complement + {-(Identifier)-})-} + {-(Reference + {-(Identifier)-})-} + {-(ReceiveOperator + {-(Identifier)-})-}))) diff --git a/test/fixtures/go/corpus/unary-expressions.parseA.txt b/test/fixtures/go/corpus/unary-expressions.parseA.txt index a2e7539b7..21a33c2bd 100644 --- a/test/fixtures/go/corpus/unary-expressions.parseA.txt +++ b/test/fixtures/go/corpus/unary-expressions.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/unary-expressions.parseB.txt b/test/fixtures/go/corpus/unary-expressions.parseB.txt index a2e7539b7..21a33c2bd 100644 --- a/test/fixtures/go/corpus/unary-expressions.parseB.txt +++ b/test/fixtures/go/corpus/unary-expressions.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 be19067c9..aad23c540 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 be19067c9..aad23c540 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 11418eaae..c673fd0f0 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 11418eaae..c673fd0f0 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 a54f8d86c..fdd894f29 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 a54f8d86c..fdd894f29 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 9118982be..e5d91f369 100644 --- a/test/fixtures/go/corpus/var-declarations-with-types.parseA.txt +++ b/test/fixtures/go/corpus/var-declarations-with-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 9118982be..e5d91f369 100644 --- a/test/fixtures/go/corpus/var-declarations-with-types.parseB.txt +++ b/test/fixtures/go/corpus/var-declarations-with-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 2d984aebb..8f6103b96 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 06f1fa789..6ef1f0819 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 d49580f45..0e1ac2501 100644 --- a/test/fixtures/go/corpus/var-declarations-without-types.parseA.txt +++ b/test/fixtures/go/corpus/var-declarations-without-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 bbacb990a..8e483ac19 100644 --- a/test/fixtures/go/corpus/var-declarations-without-types.parseB.txt +++ b/test/fixtures/go/corpus/var-declarations-without-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 06b29737e..51a60a3f1 100644 --- a/test/fixtures/go/corpus/variadic-function-declarations.diffA-B.txt +++ b/test/fixtures/go/corpus/variadic-function-declarations.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function 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 06b29737e..51a60a3f1 100644 --- a/test/fixtures/go/corpus/variadic-function-declarations.diffB-A.txt +++ b/test/fixtures/go/corpus/variadic-function-declarations.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/variadic-function-declarations.parseA.txt b/test/fixtures/go/corpus/variadic-function-declarations.parseA.txt index 0ab7e414e..84ac041f8 100644 --- a/test/fixtures/go/corpus/variadic-function-declarations.parseA.txt +++ b/test/fixtures/go/corpus/variadic-function-declarations.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/go/corpus/variadic-function-declarations.parseB.txt b/test/fixtures/go/corpus/variadic-function-declarations.parseB.txt index 0ab7e414e..84ac041f8 100644 --- a/test/fixtures/go/corpus/variadic-function-declarations.parseB.txt +++ b/test/fixtures/go/corpus/variadic-function-declarations.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Package (Identifier)) (Function diff --git a/test/fixtures/javascript/corpus/anonymous-function.diffA-B.txt b/test/fixtures/javascript/corpus/anonymous-function.diffA-B.txt index a413f45aa..d526868af 100644 --- a/test/fixtures/javascript/corpus/anonymous-function.diffA-B.txt +++ b/test/fixtures/javascript/corpus/anonymous-function.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/anonymous-function.diffB-A.txt b/test/fixtures/javascript/corpus/anonymous-function.diffB-A.txt index 14e2117e6..963fa9460 100644 --- a/test/fixtures/javascript/corpus/anonymous-function.diffB-A.txt +++ b/test/fixtures/javascript/corpus/anonymous-function.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/anonymous-function.parseA.txt b/test/fixtures/javascript/corpus/anonymous-function.parseA.txt index 410fa0126..0984eea18 100644 --- a/test/fixtures/javascript/corpus/anonymous-function.parseA.txt +++ b/test/fixtures/javascript/corpus/anonymous-function.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/anonymous-function.parseB.txt b/test/fixtures/javascript/corpus/anonymous-function.parseB.txt index f4cf6bbd8..270de0665 100644 --- a/test/fixtures/javascript/corpus/anonymous-function.parseB.txt +++ b/test/fixtures/javascript/corpus/anonymous-function.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) 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 33fc55d49..ddb22e178 100644 --- a/test/fixtures/javascript/corpus/anonymous-parameterless-function.diffA-B.txt +++ b/test/fixtures/javascript/corpus/anonymous-parameterless-function.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) 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 33fc55d49..ddb22e178 100644 --- a/test/fixtures/javascript/corpus/anonymous-parameterless-function.diffB-A.txt +++ b/test/fixtures/javascript/corpus/anonymous-parameterless-function.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseA.txt b/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseA.txt index bb24b8ce4..58a9e2102 100644 --- a/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseA.txt +++ b/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseB.txt b/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseB.txt index bb24b8ce4..58a9e2102 100644 --- a/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseB.txt +++ b/test/fixtures/javascript/corpus/anonymous-parameterless-function.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/array.diffA-B.txt b/test/fixtures/javascript/corpus/array.diffA-B.txt index 991e26a26..d91bf8637 100644 --- a/test/fixtures/javascript/corpus/array.diffA-B.txt +++ b/test/fixtures/javascript/corpus/array.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array (TextElement) {+(TextElement)+})) diff --git a/test/fixtures/javascript/corpus/array.diffB-A.txt b/test/fixtures/javascript/corpus/array.diffB-A.txt index c5bd3b828..4acede0f6 100644 --- a/test/fixtures/javascript/corpus/array.diffB-A.txt +++ b/test/fixtures/javascript/corpus/array.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array (TextElement) {-(TextElement)-})) diff --git a/test/fixtures/javascript/corpus/array.parseA.txt b/test/fixtures/javascript/corpus/array.parseA.txt index 0965f1f9f..d5891f355 100644 --- a/test/fixtures/javascript/corpus/array.parseA.txt +++ b/test/fixtures/javascript/corpus/array.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Array (TextElement))) diff --git a/test/fixtures/javascript/corpus/array.parseB.txt b/test/fixtures/javascript/corpus/array.parseB.txt index 69ab394db..4de5832a5 100644 --- a/test/fixtures/javascript/corpus/array.parseB.txt +++ b/test/fixtures/javascript/corpus/array.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array (TextElement) (TextElement))) diff --git a/test/fixtures/javascript/corpus/arrow-function.diffA-B.txt b/test/fixtures/javascript/corpus/arrow-function.diffA-B.txt index 600b385ff..182077320 100644 --- a/test/fixtures/javascript/corpus/arrow-function.diffA-B.txt +++ b/test/fixtures/javascript/corpus/arrow-function.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/arrow-function.diffB-A.txt b/test/fixtures/javascript/corpus/arrow-function.diffB-A.txt index 600b385ff..182077320 100644 --- a/test/fixtures/javascript/corpus/arrow-function.diffB-A.txt +++ b/test/fixtures/javascript/corpus/arrow-function.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/arrow-function.parseA.txt b/test/fixtures/javascript/corpus/arrow-function.parseA.txt index e178c9e7c..66bcd0037 100644 --- a/test/fixtures/javascript/corpus/arrow-function.parseA.txt +++ b/test/fixtures/javascript/corpus/arrow-function.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/arrow-function.parseB.txt b/test/fixtures/javascript/corpus/arrow-function.parseB.txt index e178c9e7c..66bcd0037 100644 --- a/test/fixtures/javascript/corpus/arrow-function.parseB.txt +++ b/test/fixtures/javascript/corpus/arrow-function.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/assignment-pattern.diffA-B.txt b/test/fixtures/javascript/corpus/assignment-pattern.diffA-B.txt index e2d3e4509..18cea23ed 100644 --- a/test/fixtures/javascript/corpus/assignment-pattern.diffA-B.txt +++ b/test/fixtures/javascript/corpus/assignment-pattern.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/javascript/corpus/assignment-pattern.diffB-A.txt b/test/fixtures/javascript/corpus/assignment-pattern.diffB-A.txt index e2d3e4509..18cea23ed 100644 --- a/test/fixtures/javascript/corpus/assignment-pattern.diffB-A.txt +++ b/test/fixtures/javascript/corpus/assignment-pattern.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/javascript/corpus/assignment-pattern.parseA.txt b/test/fixtures/javascript/corpus/assignment-pattern.parseA.txt index 668ff126f..2db3947ee 100644 --- a/test/fixtures/javascript/corpus/assignment-pattern.parseA.txt +++ b/test/fixtures/javascript/corpus/assignment-pattern.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/javascript/corpus/assignment-pattern.parseB.txt b/test/fixtures/javascript/corpus/assignment-pattern.parseB.txt index 668ff126f..2db3947ee 100644 --- a/test/fixtures/javascript/corpus/assignment-pattern.parseB.txt +++ b/test/fixtures/javascript/corpus/assignment-pattern.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/javascript/corpus/assignment.diffA-B.txt b/test/fixtures/javascript/corpus/assignment.diffA-B.txt index 9572881a4..3f9ac8708 100644 --- a/test/fixtures/javascript/corpus/assignment.diffA-B.txt +++ b/test/fixtures/javascript/corpus/assignment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) { (Float) diff --git a/test/fixtures/javascript/corpus/assignment.diffB-A.txt b/test/fixtures/javascript/corpus/assignment.diffB-A.txt index 9572881a4..3f9ac8708 100644 --- a/test/fixtures/javascript/corpus/assignment.diffB-A.txt +++ b/test/fixtures/javascript/corpus/assignment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) { (Float) diff --git a/test/fixtures/javascript/corpus/assignment.parseA.txt b/test/fixtures/javascript/corpus/assignment.parseA.txt index 7631b5f93..e68803f14 100644 --- a/test/fixtures/javascript/corpus/assignment.parseA.txt +++ b/test/fixtures/javascript/corpus/assignment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Float))) diff --git a/test/fixtures/javascript/corpus/assignment.parseB.txt b/test/fixtures/javascript/corpus/assignment.parseB.txt index 7631b5f93..e68803f14 100644 --- a/test/fixtures/javascript/corpus/assignment.parseB.txt +++ b/test/fixtures/javascript/corpus/assignment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Float))) diff --git a/test/fixtures/javascript/corpus/bitwise-operator.diffA-B.txt b/test/fixtures/javascript/corpus/bitwise-operator.diffA-B.txt index b039bc977..643068d8f 100644 --- a/test/fixtures/javascript/corpus/bitwise-operator.diffA-B.txt +++ b/test/fixtures/javascript/corpus/bitwise-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (RShift (Identifier) { (Identifier) diff --git a/test/fixtures/javascript/corpus/bitwise-operator.diffB-A.txt b/test/fixtures/javascript/corpus/bitwise-operator.diffB-A.txt index b039bc977..643068d8f 100644 --- a/test/fixtures/javascript/corpus/bitwise-operator.diffB-A.txt +++ b/test/fixtures/javascript/corpus/bitwise-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (RShift (Identifier) { (Identifier) diff --git a/test/fixtures/javascript/corpus/bitwise-operator.parseA.txt b/test/fixtures/javascript/corpus/bitwise-operator.parseA.txt index 4f83e3ae5..3be6465cf 100644 --- a/test/fixtures/javascript/corpus/bitwise-operator.parseA.txt +++ b/test/fixtures/javascript/corpus/bitwise-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (RShift (Identifier) (Identifier))) diff --git a/test/fixtures/javascript/corpus/bitwise-operator.parseB.txt b/test/fixtures/javascript/corpus/bitwise-operator.parseB.txt index 4f83e3ae5..3be6465cf 100644 --- a/test/fixtures/javascript/corpus/bitwise-operator.parseB.txt +++ b/test/fixtures/javascript/corpus/bitwise-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (RShift (Identifier) (Identifier))) diff --git a/test/fixtures/javascript/corpus/boolean-operator.diffA-B.txt b/test/fixtures/javascript/corpus/boolean-operator.diffA-B.txt index 365405c5c..a257366e8 100644 --- a/test/fixtures/javascript/corpus/boolean-operator.diffA-B.txt +++ b/test/fixtures/javascript/corpus/boolean-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Or {-(Identifier)-} {-(Identifier)-}) diff --git a/test/fixtures/javascript/corpus/boolean-operator.diffB-A.txt b/test/fixtures/javascript/corpus/boolean-operator.diffB-A.txt index bab8a9ceb..ef610ad5c 100644 --- a/test/fixtures/javascript/corpus/boolean-operator.diffB-A.txt +++ b/test/fixtures/javascript/corpus/boolean-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (And {-(Identifier)-} {-(Identifier)-}) diff --git a/test/fixtures/javascript/corpus/boolean-operator.parseA.txt b/test/fixtures/javascript/corpus/boolean-operator.parseA.txt index ac8cbd824..90cabac73 100644 --- a/test/fixtures/javascript/corpus/boolean-operator.parseA.txt +++ b/test/fixtures/javascript/corpus/boolean-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Or (Identifier) (Identifier))) diff --git a/test/fixtures/javascript/corpus/boolean-operator.parseB.txt b/test/fixtures/javascript/corpus/boolean-operator.parseB.txt index c45251d63..8fa994bf7 100644 --- a/test/fixtures/javascript/corpus/boolean-operator.parseB.txt +++ b/test/fixtures/javascript/corpus/boolean-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (And (Identifier) (Identifier))) diff --git a/test/fixtures/javascript/corpus/break.diffA-B.txt b/test/fixtures/javascript/corpus/break.diffA-B.txt index 46eb71902..7a6ade058 100644 --- a/test/fixtures/javascript/corpus/break.diffA-B.txt +++ b/test/fixtures/javascript/corpus/break.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/javascript/corpus/break.diffB-A.txt b/test/fixtures/javascript/corpus/break.diffB-A.txt index 44e6c7bdc..e57de03a9 100644 --- a/test/fixtures/javascript/corpus/break.diffB-A.txt +++ b/test/fixtures/javascript/corpus/break.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/javascript/corpus/break.parseA.txt b/test/fixtures/javascript/corpus/break.parseA.txt index c0af1c973..7e374ef00 100644 --- a/test/fixtures/javascript/corpus/break.parseA.txt +++ b/test/fixtures/javascript/corpus/break.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/javascript/corpus/break.parseB.txt b/test/fixtures/javascript/corpus/break.parseB.txt index 0c30ef033..33b8ce898 100644 --- a/test/fixtures/javascript/corpus/break.parseB.txt +++ b/test/fixtures/javascript/corpus/break.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/javascript/corpus/chained-callbacks.diffA-B.txt b/test/fixtures/javascript/corpus/chained-callbacks.diffA-B.txt index ba36adf30..33edbf7a2 100644 --- a/test/fixtures/javascript/corpus/chained-callbacks.diffA-B.txt +++ b/test/fixtures/javascript/corpus/chained-callbacks.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (This) diff --git a/test/fixtures/javascript/corpus/chained-callbacks.diffB-A.txt b/test/fixtures/javascript/corpus/chained-callbacks.diffB-A.txt index ba36adf30..33edbf7a2 100644 --- a/test/fixtures/javascript/corpus/chained-callbacks.diffB-A.txt +++ b/test/fixtures/javascript/corpus/chained-callbacks.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (This) diff --git a/test/fixtures/javascript/corpus/chained-callbacks.parseA.txt b/test/fixtures/javascript/corpus/chained-callbacks.parseA.txt index a6043e559..545dc8174 100644 --- a/test/fixtures/javascript/corpus/chained-callbacks.parseA.txt +++ b/test/fixtures/javascript/corpus/chained-callbacks.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (This) diff --git a/test/fixtures/javascript/corpus/chained-callbacks.parseB.txt b/test/fixtures/javascript/corpus/chained-callbacks.parseB.txt index a6043e559..545dc8174 100644 --- a/test/fixtures/javascript/corpus/chained-callbacks.parseB.txt +++ b/test/fixtures/javascript/corpus/chained-callbacks.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (This) diff --git a/test/fixtures/javascript/corpus/chained-property-access.diffA-B.txt b/test/fixtures/javascript/corpus/chained-property-access.diffA-B.txt index 1c4c5c60f..4cbf4df13 100644 --- a/test/fixtures/javascript/corpus/chained-property-access.diffA-B.txt +++ b/test/fixtures/javascript/corpus/chained-property-access.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return (Call (MemberAccess diff --git a/test/fixtures/javascript/corpus/chained-property-access.diffB-A.txt b/test/fixtures/javascript/corpus/chained-property-access.diffB-A.txt index 1c4c5c60f..4cbf4df13 100644 --- a/test/fixtures/javascript/corpus/chained-property-access.diffB-A.txt +++ b/test/fixtures/javascript/corpus/chained-property-access.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return (Call (MemberAccess diff --git a/test/fixtures/javascript/corpus/chained-property-access.parseA.txt b/test/fixtures/javascript/corpus/chained-property-access.parseA.txt index c45050ddf..52d369111 100644 --- a/test/fixtures/javascript/corpus/chained-property-access.parseA.txt +++ b/test/fixtures/javascript/corpus/chained-property-access.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return (Call (MemberAccess diff --git a/test/fixtures/javascript/corpus/chained-property-access.parseB.txt b/test/fixtures/javascript/corpus/chained-property-access.parseB.txt index c45050ddf..52d369111 100644 --- a/test/fixtures/javascript/corpus/chained-property-access.parseB.txt +++ b/test/fixtures/javascript/corpus/chained-property-access.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return (Call (MemberAccess diff --git a/test/fixtures/javascript/corpus/class.diffA-B.txt b/test/fixtures/javascript/corpus/class.diffA-B.txt index c1fd07f93..6896309ab 100644 --- a/test/fixtures/javascript/corpus/class.diffA-B.txt +++ b/test/fixtures/javascript/corpus/class.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Statements diff --git a/test/fixtures/javascript/corpus/class.diffB-A.txt b/test/fixtures/javascript/corpus/class.diffB-A.txt index f4214b7cc..48206cf61 100644 --- a/test/fixtures/javascript/corpus/class.diffB-A.txt +++ b/test/fixtures/javascript/corpus/class.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Statements diff --git a/test/fixtures/javascript/corpus/class.parseA.txt b/test/fixtures/javascript/corpus/class.parseA.txt index 1d34cdb49..d7efa27f8 100644 --- a/test/fixtures/javascript/corpus/class.parseA.txt +++ b/test/fixtures/javascript/corpus/class.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Statements diff --git a/test/fixtures/javascript/corpus/class.parseB.txt b/test/fixtures/javascript/corpus/class.parseB.txt index 3bde6e0b0..57e40f4f1 100644 --- a/test/fixtures/javascript/corpus/class.parseB.txt +++ b/test/fixtures/javascript/corpus/class.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Statements diff --git a/test/fixtures/javascript/corpus/comma-operator.diffA-B.txt b/test/fixtures/javascript/corpus/comma-operator.diffA-B.txt index 1d77d4600..15fc0c2b3 100644 --- a/test/fixtures/javascript/corpus/comma-operator.diffA-B.txt +++ b/test/fixtures/javascript/corpus/comma-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Assignment {+(Identifier)+} {+(Hash diff --git a/test/fixtures/javascript/corpus/comma-operator.diffB-A.txt b/test/fixtures/javascript/corpus/comma-operator.diffB-A.txt index 3baaed40f..8a6943ae5 100644 --- a/test/fixtures/javascript/corpus/comma-operator.diffB-A.txt +++ b/test/fixtures/javascript/corpus/comma-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(SequenceExpression {+(Assignment {+(Identifier)+} diff --git a/test/fixtures/javascript/corpus/comma-operator.parseA.txt b/test/fixtures/javascript/corpus/comma-operator.parseA.txt index 73999dc0d..06fbde18f 100644 --- a/test/fixtures/javascript/corpus/comma-operator.parseA.txt +++ b/test/fixtures/javascript/corpus/comma-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (SequenceExpression (Assignment (Identifier) diff --git a/test/fixtures/javascript/corpus/comma-operator.parseB.txt b/test/fixtures/javascript/corpus/comma-operator.parseB.txt index 071db7345..acf60ac42 100644 --- a/test/fixtures/javascript/corpus/comma-operator.parseB.txt +++ b/test/fixtures/javascript/corpus/comma-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Hash diff --git a/test/fixtures/javascript/corpus/comment.diffA-B.txt b/test/fixtures/javascript/corpus/comment.diffA-B.txt index ab0622e59..5229a390d 100644 --- a/test/fixtures/javascript/corpus/comment.diffA-B.txt +++ b/test/fixtures/javascript/corpus/comment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context { (Comment) ->(Comment) } diff --git a/test/fixtures/javascript/corpus/comment.diffB-A.txt b/test/fixtures/javascript/corpus/comment.diffB-A.txt index ab0622e59..5229a390d 100644 --- a/test/fixtures/javascript/corpus/comment.diffB-A.txt +++ b/test/fixtures/javascript/corpus/comment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context { (Comment) ->(Comment) } diff --git a/test/fixtures/javascript/corpus/comment.parseA.txt b/test/fixtures/javascript/corpus/comment.parseA.txt index a4f06fd8c..4568b6b78 100644 --- a/test/fixtures/javascript/corpus/comment.parseA.txt +++ b/test/fixtures/javascript/corpus/comment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context (Comment) (Empty))) diff --git a/test/fixtures/javascript/corpus/comment.parseB.txt b/test/fixtures/javascript/corpus/comment.parseB.txt index a4f06fd8c..4568b6b78 100644 --- a/test/fixtures/javascript/corpus/comment.parseB.txt +++ b/test/fixtures/javascript/corpus/comment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context (Comment) (Empty))) diff --git a/test/fixtures/javascript/corpus/constructor-call.diffA-B.txt b/test/fixtures/javascript/corpus/constructor-call.diffA-B.txt index 4cd5b5e65..029bd21e8 100644 --- a/test/fixtures/javascript/corpus/constructor-call.diffA-B.txt +++ b/test/fixtures/javascript/corpus/constructor-call.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (New (Call (MemberAccess diff --git a/test/fixtures/javascript/corpus/constructor-call.diffB-A.txt b/test/fixtures/javascript/corpus/constructor-call.diffB-A.txt index 4cd5b5e65..029bd21e8 100644 --- a/test/fixtures/javascript/corpus/constructor-call.diffB-A.txt +++ b/test/fixtures/javascript/corpus/constructor-call.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (New (Call (MemberAccess diff --git a/test/fixtures/javascript/corpus/constructor-call.parseA.txt b/test/fixtures/javascript/corpus/constructor-call.parseA.txt index 14fd6d198..2618e8ed8 100644 --- a/test/fixtures/javascript/corpus/constructor-call.parseA.txt +++ b/test/fixtures/javascript/corpus/constructor-call.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (New (Call (MemberAccess diff --git a/test/fixtures/javascript/corpus/constructor-call.parseB.txt b/test/fixtures/javascript/corpus/constructor-call.parseB.txt index 14fd6d198..2618e8ed8 100644 --- a/test/fixtures/javascript/corpus/constructor-call.parseB.txt +++ b/test/fixtures/javascript/corpus/constructor-call.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (New (Call (MemberAccess diff --git a/test/fixtures/javascript/corpus/continue.diffA-B.txt b/test/fixtures/javascript/corpus/continue.diffA-B.txt index 44e6c7bdc..e57de03a9 100644 --- a/test/fixtures/javascript/corpus/continue.diffA-B.txt +++ b/test/fixtures/javascript/corpus/continue.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/javascript/corpus/continue.diffB-A.txt b/test/fixtures/javascript/corpus/continue.diffB-A.txt index 46eb71902..7a6ade058 100644 --- a/test/fixtures/javascript/corpus/continue.diffB-A.txt +++ b/test/fixtures/javascript/corpus/continue.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/javascript/corpus/continue.parseA.txt b/test/fixtures/javascript/corpus/continue.parseA.txt index 0c30ef033..33b8ce898 100644 --- a/test/fixtures/javascript/corpus/continue.parseA.txt +++ b/test/fixtures/javascript/corpus/continue.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/javascript/corpus/continue.parseB.txt b/test/fixtures/javascript/corpus/continue.parseB.txt index c0af1c973..7e374ef00 100644 --- a/test/fixtures/javascript/corpus/continue.parseB.txt +++ b/test/fixtures/javascript/corpus/continue.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/javascript/corpus/delete-operator.diffA-B.txt b/test/fixtures/javascript/corpus/delete-operator.diffA-B.txt index 2208aa02b..7405cd40e 100644 --- a/test/fixtures/javascript/corpus/delete-operator.diffA-B.txt +++ b/test/fixtures/javascript/corpus/delete-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Delete { (Subscript {-(Identifier)-} diff --git a/test/fixtures/javascript/corpus/delete-operator.diffB-A.txt b/test/fixtures/javascript/corpus/delete-operator.diffB-A.txt index b278868d6..f27ec8412 100644 --- a/test/fixtures/javascript/corpus/delete-operator.diffB-A.txt +++ b/test/fixtures/javascript/corpus/delete-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Delete { (MemberAccess {-(Identifier)-} diff --git a/test/fixtures/javascript/corpus/delete-operator.parseA.txt b/test/fixtures/javascript/corpus/delete-operator.parseA.txt index 19f110f27..1f1a1d58f 100644 --- a/test/fixtures/javascript/corpus/delete-operator.parseA.txt +++ b/test/fixtures/javascript/corpus/delete-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Delete (Subscript (Identifier) diff --git a/test/fixtures/javascript/corpus/delete-operator.parseB.txt b/test/fixtures/javascript/corpus/delete-operator.parseB.txt index 36e4bfbaa..310b7babe 100644 --- a/test/fixtures/javascript/corpus/delete-operator.parseB.txt +++ b/test/fixtures/javascript/corpus/delete-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Delete (MemberAccess (Identifier) 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 5935813f5..b2248e3d0 100644 --- a/test/fixtures/javascript/corpus/do-while-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/do-while-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (DoWhile { (Boolean) ->(Boolean) } 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 5935813f5..b2248e3d0 100644 --- a/test/fixtures/javascript/corpus/do-while-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/do-while-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (DoWhile { (Boolean) ->(Boolean) } diff --git a/test/fixtures/javascript/corpus/do-while-statement.parseA.txt b/test/fixtures/javascript/corpus/do-while-statement.parseA.txt index a75cc5e53..d518e0b65 100644 --- a/test/fixtures/javascript/corpus/do-while-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/do-while-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (DoWhile (Boolean) (Statements diff --git a/test/fixtures/javascript/corpus/do-while-statement.parseB.txt b/test/fixtures/javascript/corpus/do-while-statement.parseB.txt index a75cc5e53..d518e0b65 100644 --- a/test/fixtures/javascript/corpus/do-while-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/do-while-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (DoWhile (Boolean) (Statements diff --git a/test/fixtures/javascript/corpus/export.diffA-B.txt b/test/fixtures/javascript/corpus/export.diffA-B.txt index c4fcacf9d..2d05a4ca2 100644 --- a/test/fixtures/javascript/corpus/export.diffA-B.txt +++ b/test/fixtures/javascript/corpus/export.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (QualifiedExport) ->(QualifiedExport) } { (QualifiedExport) @@ -35,24 +35,24 @@ (Identifier) { (Empty) ->(Identifier) }) - {+(Assignment - {+(Empty)+} - {+(Identifier)+} - {+(Empty)+})+} (Assignment (Empty) { (Identifier) ->(Identifier) } - (Empty)))) -{+(DefaultExport - {+(Identifier)+})+} + (Empty)) + {+(Assignment + {+(Empty)+} + {+(Identifier)+} + {+(Empty)+})+})) (DefaultExport { (Identifier) - ->(Function + ->(Identifier) }) +{+(DefaultExport + {+(Function {+(Empty)+} {+(Empty)+} {+(Identifier)+} - {+(Statements)+}) }) + {+(Statements)+})+})+} (DefaultExport (Function (Empty) diff --git a/test/fixtures/javascript/corpus/export.diffB-A.txt b/test/fixtures/javascript/corpus/export.diffB-A.txt index 0f430d3a8..25c78e485 100644 --- a/test/fixtures/javascript/corpus/export.diffB-A.txt +++ b/test/fixtures/javascript/corpus/export.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (QualifiedExport) ->(QualifiedExport) } { (QualifiedExport) @@ -35,22 +35,18 @@ (Identifier) { (Identifier) ->(Empty) }) - {+(Assignment - {+(Empty)+} - {+(Identifier)+} - {+(Empty)+})+} - {-(Assignment - {-(Empty)-} - {-(Identifier)-} - {-(Empty)-})-} + (Assignment + (Empty) + { (Identifier) + ->(Identifier) } + (Empty)) {-(Assignment {-(Empty)-} {-(Identifier)-} {-(Empty)-})-})) -{+(DefaultExport - {+(Identifier)+})+} -{-(DefaultExport - {-(Identifier)-})-} + (DefaultExport + { (Identifier) + ->(Identifier) }) {-(DefaultExport {-(Function {-(Empty)-} diff --git a/test/fixtures/javascript/corpus/export.parseA.txt b/test/fixtures/javascript/corpus/export.parseA.txt index c65411988..269ace8d0 100644 --- a/test/fixtures/javascript/corpus/export.parseA.txt +++ b/test/fixtures/javascript/corpus/export.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (QualifiedExport) (QualifiedExport) (DefaultExport diff --git a/test/fixtures/javascript/corpus/export.parseB.txt b/test/fixtures/javascript/corpus/export.parseB.txt index a04091e87..3d01a836a 100644 --- a/test/fixtures/javascript/corpus/export.parseB.txt +++ b/test/fixtures/javascript/corpus/export.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (QualifiedExport) (QualifiedExport) (DefaultExport diff --git a/test/fixtures/javascript/corpus/false.diffA-B.txt b/test/fixtures/javascript/corpus/false.diffA-B.txt index ac2ca170c..62f7e4e3e 100644 --- a/test/fixtures/javascript/corpus/false.diffA-B.txt +++ b/test/fixtures/javascript/corpus/false.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Return {+(Boolean)+})+} {-(Boolean)-}) diff --git a/test/fixtures/javascript/corpus/false.diffB-A.txt b/test/fixtures/javascript/corpus/false.diffB-A.txt index 846a9c224..57c1b8c70 100644 --- a/test/fixtures/javascript/corpus/false.diffB-A.txt +++ b/test/fixtures/javascript/corpus/false.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Boolean)+} {-(Return {-(Boolean)-})-}) diff --git a/test/fixtures/javascript/corpus/false.parseA.txt b/test/fixtures/javascript/corpus/false.parseA.txt index 1fdad7cac..25d98872e 100644 --- a/test/fixtures/javascript/corpus/false.parseA.txt +++ b/test/fixtures/javascript/corpus/false.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Boolean)) diff --git a/test/fixtures/javascript/corpus/false.parseB.txt b/test/fixtures/javascript/corpus/false.parseB.txt index a37bdc4ee..02e3c2a13 100644 --- a/test/fixtures/javascript/corpus/false.parseB.txt +++ b/test/fixtures/javascript/corpus/false.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Boolean))) 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 7f4c7fe4a..d311b808b 100644 --- a/test/fixtures/javascript/corpus/for-in-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/for-in-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForEach { (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 7f4c7fe4a..d311b808b 100644 --- a/test/fixtures/javascript/corpus/for-in-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/for-in-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForEach { (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 79a82b79a..6becb7a8d 100644 --- a/test/fixtures/javascript/corpus/for-in-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/for-in-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForEach (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/for-in-statement.parseB.txt b/test/fixtures/javascript/corpus/for-in-statement.parseB.txt index 79a82b79a..6becb7a8d 100644 --- a/test/fixtures/javascript/corpus/for-in-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/for-in-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForEach (Identifier) (Identifier) 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 e3184832c..bf4e69b44 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 @@ -1,4 +1,4 @@ -(Program +(Statements (For (And (Member 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 e3184832c..bf4e69b44 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 @@ -1,4 +1,4 @@ -(Program +(Statements (For (And (Member 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 0c1d70fb4..a83600b05 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 @@ -1,4 +1,4 @@ -(Program +(Statements (For (And (Member 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 0c1d70fb4..a83600b05 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 @@ -1,4 +1,4 @@ -(Program +(Statements (For (And (Member 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 f5e052f79..a17ddbf18 100644 --- a/test/fixtures/javascript/corpus/for-of-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/for-of-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForOf { (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 f5e052f79..a17ddbf18 100644 --- a/test/fixtures/javascript/corpus/for-of-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/for-of-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForOf { (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 3c9704a36..f7defa7f3 100644 --- a/test/fixtures/javascript/corpus/for-of-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/for-of-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForOf (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 3c9704a36..f7defa7f3 100644 --- a/test/fixtures/javascript/corpus/for-of-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/for-of-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForOf (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 1cf044616..5437569a4 100644 --- a/test/fixtures/javascript/corpus/for-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/for-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (SequenceExpression (Assignment diff --git a/test/fixtures/javascript/corpus/for-statement.diffB-A.txt b/test/fixtures/javascript/corpus/for-statement.diffB-A.txt index 1cf044616..5437569a4 100644 --- a/test/fixtures/javascript/corpus/for-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/for-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (SequenceExpression (Assignment diff --git a/test/fixtures/javascript/corpus/for-statement.parseA.txt b/test/fixtures/javascript/corpus/for-statement.parseA.txt index fe2179965..883d1fd1a 100644 --- a/test/fixtures/javascript/corpus/for-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/for-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (SequenceExpression (Assignment diff --git a/test/fixtures/javascript/corpus/for-statement.parseB.txt b/test/fixtures/javascript/corpus/for-statement.parseB.txt index fe2179965..883d1fd1a 100644 --- a/test/fixtures/javascript/corpus/for-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/for-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (SequenceExpression (Assignment 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 9ab5e70c0..303706eac 100644 --- a/test/fixtures/javascript/corpus/function-call-args.diffA-B.txt +++ b/test/fixtures/javascript/corpus/function-call-args.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Float) 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 46e0b5c06..8eda0d972 100644 --- a/test/fixtures/javascript/corpus/function-call-args.diffB-A.txt +++ b/test/fixtures/javascript/corpus/function-call-args.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Float) diff --git a/test/fixtures/javascript/corpus/function-call-args.parseA.txt b/test/fixtures/javascript/corpus/function-call-args.parseA.txt index ed0d71201..62f704351 100644 --- a/test/fixtures/javascript/corpus/function-call-args.parseA.txt +++ b/test/fixtures/javascript/corpus/function-call-args.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Float) diff --git a/test/fixtures/javascript/corpus/function-call-args.parseB.txt b/test/fixtures/javascript/corpus/function-call-args.parseB.txt index ed0d71201..62f704351 100644 --- a/test/fixtures/javascript/corpus/function-call-args.parseB.txt +++ b/test/fixtures/javascript/corpus/function-call-args.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Float) diff --git a/test/fixtures/javascript/corpus/function-call.diffA-B.txt b/test/fixtures/javascript/corpus/function-call.diffA-B.txt index 9ff4cf165..c247ef4df 100644 --- a/test/fixtures/javascript/corpus/function-call.diffA-B.txt +++ b/test/fixtures/javascript/corpus/function-call.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/function-call.diffB-A.txt b/test/fixtures/javascript/corpus/function-call.diffB-A.txt index 9ff4cf165..c247ef4df 100644 --- a/test/fixtures/javascript/corpus/function-call.diffB-A.txt +++ b/test/fixtures/javascript/corpus/function-call.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/function-call.parseA.txt b/test/fixtures/javascript/corpus/function-call.parseA.txt index 992897b06..0a2778613 100644 --- a/test/fixtures/javascript/corpus/function-call.parseA.txt +++ b/test/fixtures/javascript/corpus/function-call.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/function-call.parseB.txt b/test/fixtures/javascript/corpus/function-call.parseB.txt index 992897b06..0a2778613 100644 --- a/test/fixtures/javascript/corpus/function-call.parseB.txt +++ b/test/fixtures/javascript/corpus/function-call.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/function.diffA-B.txt b/test/fixtures/javascript/corpus/function.diffA-B.txt index ad894be7c..269e74ff2 100644 --- a/test/fixtures/javascript/corpus/function.diffA-B.txt +++ b/test/fixtures/javascript/corpus/function.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/function.diffB-A.txt b/test/fixtures/javascript/corpus/function.diffB-A.txt index ad894be7c..269e74ff2 100644 --- a/test/fixtures/javascript/corpus/function.diffB-A.txt +++ b/test/fixtures/javascript/corpus/function.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/function.parseA.txt b/test/fixtures/javascript/corpus/function.parseA.txt index 4059c4550..4fb5ae44d 100644 --- a/test/fixtures/javascript/corpus/function.parseA.txt +++ b/test/fixtures/javascript/corpus/function.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/function.parseB.txt b/test/fixtures/javascript/corpus/function.parseB.txt index 4059c4550..4fb5ae44d 100644 --- a/test/fixtures/javascript/corpus/function.parseB.txt +++ b/test/fixtures/javascript/corpus/function.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/generator-function.diffA-B.txt b/test/fixtures/javascript/corpus/generator-function.diffA-B.txt index 2f4f58433..bcc4a72fd 100644 --- a/test/fixtures/javascript/corpus/generator-function.diffA-B.txt +++ b/test/fixtures/javascript/corpus/generator-function.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/generator-function.diffB-A.txt b/test/fixtures/javascript/corpus/generator-function.diffB-A.txt index 2f4f58433..bcc4a72fd 100644 --- a/test/fixtures/javascript/corpus/generator-function.diffB-A.txt +++ b/test/fixtures/javascript/corpus/generator-function.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/generator-function.parseA.txt b/test/fixtures/javascript/corpus/generator-function.parseA.txt index fd25c91b3..d621cd07d 100644 --- a/test/fixtures/javascript/corpus/generator-function.parseA.txt +++ b/test/fixtures/javascript/corpus/generator-function.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/generator-function.parseB.txt b/test/fixtures/javascript/corpus/generator-function.parseB.txt index fd25c91b3..d621cd07d 100644 --- a/test/fixtures/javascript/corpus/generator-function.parseB.txt +++ b/test/fixtures/javascript/corpus/generator-function.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/identifier.diffA-B.txt b/test/fixtures/javascript/corpus/identifier.diffA-B.txt index 6ac9cd896..d2449f436 100644 --- a/test/fixtures/javascript/corpus/identifier.diffA-B.txt +++ b/test/fixtures/javascript/corpus/identifier.diffA-B.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/javascript/corpus/identifier.diffB-A.txt b/test/fixtures/javascript/corpus/identifier.diffB-A.txt index 6ac9cd896..d2449f436 100644 --- a/test/fixtures/javascript/corpus/identifier.diffB-A.txt +++ b/test/fixtures/javascript/corpus/identifier.diffB-A.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/javascript/corpus/identifier.parseA.txt b/test/fixtures/javascript/corpus/identifier.parseA.txt index 67b75f388..5f0ab64c1 100644 --- a/test/fixtures/javascript/corpus/identifier.parseA.txt +++ b/test/fixtures/javascript/corpus/identifier.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Identifier)) diff --git a/test/fixtures/javascript/corpus/identifier.parseB.txt b/test/fixtures/javascript/corpus/identifier.parseB.txt index 67b75f388..5f0ab64c1 100644 --- a/test/fixtures/javascript/corpus/identifier.parseB.txt +++ b/test/fixtures/javascript/corpus/identifier.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Identifier)) diff --git a/test/fixtures/javascript/corpus/if-else.diffA-B.txt b/test/fixtures/javascript/corpus/if-else.diffA-B.txt index 41281f5e5..c11bb2001 100644 --- a/test/fixtures/javascript/corpus/if-else.diffA-B.txt +++ b/test/fixtures/javascript/corpus/if-else.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If { (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 a7e842460..8c5267811 100644 --- a/test/fixtures/javascript/corpus/if-else.diffB-A.txt +++ b/test/fixtures/javascript/corpus/if-else.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If { (Identifier) ->(Identifier) } diff --git a/test/fixtures/javascript/corpus/if-else.parseA.txt b/test/fixtures/javascript/corpus/if-else.parseA.txt index f3737b63e..09d678134 100644 --- a/test/fixtures/javascript/corpus/if-else.parseA.txt +++ b/test/fixtures/javascript/corpus/if-else.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/if-else.parseB.txt b/test/fixtures/javascript/corpus/if-else.parseB.txt index 2402f8fd0..49c8b8af1 100644 --- a/test/fixtures/javascript/corpus/if-else.parseB.txt +++ b/test/fixtures/javascript/corpus/if-else.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/if.diffA-B.txt b/test/fixtures/javascript/corpus/if.diffA-B.txt index 329dbee61..dc1da1028 100644 --- a/test/fixtures/javascript/corpus/if.diffA-B.txt +++ b/test/fixtures/javascript/corpus/if.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If { (Identifier) ->(MemberAccess diff --git a/test/fixtures/javascript/corpus/if.diffB-A.txt b/test/fixtures/javascript/corpus/if.diffB-A.txt index 58379f889..1f5a16737 100644 --- a/test/fixtures/javascript/corpus/if.diffB-A.txt +++ b/test/fixtures/javascript/corpus/if.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If { (MemberAccess {-(Identifier)-} diff --git a/test/fixtures/javascript/corpus/if.parseA.txt b/test/fixtures/javascript/corpus/if.parseA.txt index c319b1eb0..63f3ac321 100644 --- a/test/fixtures/javascript/corpus/if.parseA.txt +++ b/test/fixtures/javascript/corpus/if.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Identifier) (Statements diff --git a/test/fixtures/javascript/corpus/if.parseB.txt b/test/fixtures/javascript/corpus/if.parseB.txt index 4c23c44b9..0b58858fd 100644 --- a/test/fixtures/javascript/corpus/if.parseB.txt +++ b/test/fixtures/javascript/corpus/if.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/import.diffA-B.txt b/test/fixtures/javascript/corpus/import.diffA-B.txt index d9ef4348b..dd663bae3 100644 --- a/test/fixtures/javascript/corpus/import.diffA-B.txt +++ b/test/fixtures/javascript/corpus/import.diffA-B.txt @@ -1,8 +1,9 @@ -(Program +(Statements {+(Import)+} {+(QualifiedAliasedImport {+(Identifier)+})+} -{+(Import)+} +{ (Import) +->(Import) } {+(Import)+} {+(Import)+} {+(Statements @@ -13,7 +14,6 @@ {+(QualifiedAliasedImport {+(Identifier)+})+})+} {+(SideEffectImport)+} -{-(Import)-} {-(QualifiedAliasedImport {-(Identifier)-})-} {-(Import)-} diff --git a/test/fixtures/javascript/corpus/import.diffB-A.txt b/test/fixtures/javascript/corpus/import.diffB-A.txt index f817f812a..ae06e60a3 100644 --- a/test/fixtures/javascript/corpus/import.diffB-A.txt +++ b/test/fixtures/javascript/corpus/import.diffB-A.txt @@ -1,9 +1,8 @@ -(Program +(Statements {+(Import)+} {+(QualifiedAliasedImport {+(Identifier)+})+} -{ (Import) -->(Import) } +{+(Import)+} {+(Import)+} {+(Import)+} {+(Statements @@ -14,6 +13,7 @@ {+(QualifiedAliasedImport {+(Identifier)+})+})+} {+(SideEffectImport)+} +{-(Import)-} {-(QualifiedAliasedImport {-(Identifier)-})-} {-(Import)-} diff --git a/test/fixtures/javascript/corpus/import.parseA.txt b/test/fixtures/javascript/corpus/import.parseA.txt index 069afffe6..828eb6ea7 100644 --- a/test/fixtures/javascript/corpus/import.parseA.txt +++ b/test/fixtures/javascript/corpus/import.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Import) (QualifiedAliasedImport (Identifier)) diff --git a/test/fixtures/javascript/corpus/import.parseB.txt b/test/fixtures/javascript/corpus/import.parseB.txt index 069afffe6..828eb6ea7 100644 --- a/test/fixtures/javascript/corpus/import.parseB.txt +++ b/test/fixtures/javascript/corpus/import.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Import) (QualifiedAliasedImport (Identifier)) diff --git a/test/fixtures/javascript/corpus/math-assignment-operator.diffA-B.txt b/test/fixtures/javascript/corpus/math-assignment-operator.diffA-B.txt index 467bac8dc..b1aa79ef3 100644 --- a/test/fixtures/javascript/corpus/math-assignment-operator.diffA-B.txt +++ b/test/fixtures/javascript/corpus/math-assignment-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Plus diff --git a/test/fixtures/javascript/corpus/math-assignment-operator.diffB-A.txt b/test/fixtures/javascript/corpus/math-assignment-operator.diffB-A.txt index 467bac8dc..b1aa79ef3 100644 --- a/test/fixtures/javascript/corpus/math-assignment-operator.diffB-A.txt +++ b/test/fixtures/javascript/corpus/math-assignment-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Plus diff --git a/test/fixtures/javascript/corpus/math-assignment-operator.parseA.txt b/test/fixtures/javascript/corpus/math-assignment-operator.parseA.txt index f6247a719..5403b2a5e 100644 --- a/test/fixtures/javascript/corpus/math-assignment-operator.parseA.txt +++ b/test/fixtures/javascript/corpus/math-assignment-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Plus diff --git a/test/fixtures/javascript/corpus/math-assignment-operator.parseB.txt b/test/fixtures/javascript/corpus/math-assignment-operator.parseB.txt index f6247a719..5403b2a5e 100644 --- a/test/fixtures/javascript/corpus/math-assignment-operator.parseB.txt +++ b/test/fixtures/javascript/corpus/math-assignment-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Plus diff --git a/test/fixtures/javascript/corpus/math-operator.diffA-B.txt b/test/fixtures/javascript/corpus/math-operator.diffA-B.txt index 48df33060..a7c867465 100644 --- a/test/fixtures/javascript/corpus/math-operator.diffA-B.txt +++ b/test/fixtures/javascript/corpus/math-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Minus (Plus (Identifier) diff --git a/test/fixtures/javascript/corpus/math-operator.diffB-A.txt b/test/fixtures/javascript/corpus/math-operator.diffB-A.txt index 48df33060..a7c867465 100644 --- a/test/fixtures/javascript/corpus/math-operator.diffB-A.txt +++ b/test/fixtures/javascript/corpus/math-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Minus (Plus (Identifier) diff --git a/test/fixtures/javascript/corpus/math-operator.parseA.txt b/test/fixtures/javascript/corpus/math-operator.parseA.txt index f18864aac..023fa5c6a 100644 --- a/test/fixtures/javascript/corpus/math-operator.parseA.txt +++ b/test/fixtures/javascript/corpus/math-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Minus (Plus (Identifier) diff --git a/test/fixtures/javascript/corpus/math-operator.parseB.txt b/test/fixtures/javascript/corpus/math-operator.parseB.txt index f18864aac..023fa5c6a 100644 --- a/test/fixtures/javascript/corpus/math-operator.parseB.txt +++ b/test/fixtures/javascript/corpus/math-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Minus (Plus (Identifier) diff --git a/test/fixtures/javascript/corpus/member-access-assignment.diffA-B.txt b/test/fixtures/javascript/corpus/member-access-assignment.diffA-B.txt index 971eac6e7..6ddc09680 100644 --- a/test/fixtures/javascript/corpus/member-access-assignment.diffA-B.txt +++ b/test/fixtures/javascript/corpus/member-access-assignment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/member-access-assignment.diffB-A.txt b/test/fixtures/javascript/corpus/member-access-assignment.diffB-A.txt index 971eac6e7..6ddc09680 100644 --- a/test/fixtures/javascript/corpus/member-access-assignment.diffB-A.txt +++ b/test/fixtures/javascript/corpus/member-access-assignment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/member-access-assignment.parseA.txt b/test/fixtures/javascript/corpus/member-access-assignment.parseA.txt index 7d15e4ab4..a4d274369 100644 --- a/test/fixtures/javascript/corpus/member-access-assignment.parseA.txt +++ b/test/fixtures/javascript/corpus/member-access-assignment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/member-access-assignment.parseB.txt b/test/fixtures/javascript/corpus/member-access-assignment.parseB.txt index 7d15e4ab4..a4d274369 100644 --- a/test/fixtures/javascript/corpus/member-access-assignment.parseB.txt +++ b/test/fixtures/javascript/corpus/member-access-assignment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/member-access.diffA-B.txt b/test/fixtures/javascript/corpus/member-access.diffA-B.txt index 032d939dd..e09883b07 100644 --- a/test/fixtures/javascript/corpus/member-access.diffA-B.txt +++ b/test/fixtures/javascript/corpus/member-access.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess (Identifier) { (Identifier) diff --git a/test/fixtures/javascript/corpus/member-access.diffB-A.txt b/test/fixtures/javascript/corpus/member-access.diffB-A.txt index 032d939dd..e09883b07 100644 --- a/test/fixtures/javascript/corpus/member-access.diffB-A.txt +++ b/test/fixtures/javascript/corpus/member-access.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess (Identifier) { (Identifier) diff --git a/test/fixtures/javascript/corpus/member-access.parseA.txt b/test/fixtures/javascript/corpus/member-access.parseA.txt index 3a5c9e565..70674960a 100644 --- a/test/fixtures/javascript/corpus/member-access.parseA.txt +++ b/test/fixtures/javascript/corpus/member-access.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess (Identifier) (Identifier))) diff --git a/test/fixtures/javascript/corpus/member-access.parseB.txt b/test/fixtures/javascript/corpus/member-access.parseB.txt index 3a5c9e565..70674960a 100644 --- a/test/fixtures/javascript/corpus/member-access.parseB.txt +++ b/test/fixtures/javascript/corpus/member-access.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess (Identifier) (Identifier))) diff --git a/test/fixtures/javascript/corpus/method-call.diffA-B.txt b/test/fixtures/javascript/corpus/method-call.diffA-B.txt index 04b6484e5..6eafae55c 100644 --- a/test/fixtures/javascript/corpus/method-call.diffA-B.txt +++ b/test/fixtures/javascript/corpus/method-call.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/method-call.diffB-A.txt b/test/fixtures/javascript/corpus/method-call.diffB-A.txt index 04b6484e5..6eafae55c 100644 --- a/test/fixtures/javascript/corpus/method-call.diffB-A.txt +++ b/test/fixtures/javascript/corpus/method-call.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/method-call.parseA.txt b/test/fixtures/javascript/corpus/method-call.parseA.txt index 1bc561706..447b0ae78 100644 --- a/test/fixtures/javascript/corpus/method-call.parseA.txt +++ b/test/fixtures/javascript/corpus/method-call.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/method-call.parseB.txt b/test/fixtures/javascript/corpus/method-call.parseB.txt index 1bc561706..447b0ae78 100644 --- a/test/fixtures/javascript/corpus/method-call.parseB.txt +++ b/test/fixtures/javascript/corpus/method-call.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/named-function.diffA-B.txt b/test/fixtures/javascript/corpus/named-function.diffA-B.txt index aec245b08..e78597819 100644 --- a/test/fixtures/javascript/corpus/named-function.diffA-B.txt +++ b/test/fixtures/javascript/corpus/named-function.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/named-function.diffB-A.txt b/test/fixtures/javascript/corpus/named-function.diffB-A.txt index 8ac7047e0..e88fc69f9 100644 --- a/test/fixtures/javascript/corpus/named-function.diffB-A.txt +++ b/test/fixtures/javascript/corpus/named-function.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/named-function.parseA.txt b/test/fixtures/javascript/corpus/named-function.parseA.txt index a0596d5bd..d03c49b95 100644 --- a/test/fixtures/javascript/corpus/named-function.parseA.txt +++ b/test/fixtures/javascript/corpus/named-function.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/named-function.parseB.txt b/test/fixtures/javascript/corpus/named-function.parseB.txt index 96d3c4033..791208cdc 100644 --- a/test/fixtures/javascript/corpus/named-function.parseB.txt +++ b/test/fixtures/javascript/corpus/named-function.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (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 00dd2f4a3..016ca6847 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) 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 00dd2f4a3..016ca6847 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) 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 618761627..fec2a038f 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) 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 618761627..fec2a038f 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/nested-functions.diffA-B.txt b/test/fixtures/javascript/corpus/nested-functions.diffA-B.txt index 2a221fcdd..3882a7fe2 100644 --- a/test/fixtures/javascript/corpus/nested-functions.diffA-B.txt +++ b/test/fixtures/javascript/corpus/nested-functions.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/nested-functions.diffB-A.txt b/test/fixtures/javascript/corpus/nested-functions.diffB-A.txt index 2a221fcdd..3882a7fe2 100644 --- a/test/fixtures/javascript/corpus/nested-functions.diffB-A.txt +++ b/test/fixtures/javascript/corpus/nested-functions.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/nested-functions.parseA.txt b/test/fixtures/javascript/corpus/nested-functions.parseA.txt index bba0968bd..3d8dd1f13 100644 --- a/test/fixtures/javascript/corpus/nested-functions.parseA.txt +++ b/test/fixtures/javascript/corpus/nested-functions.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/nested-functions.parseB.txt b/test/fixtures/javascript/corpus/nested-functions.parseB.txt index bba0968bd..3d8dd1f13 100644 --- a/test/fixtures/javascript/corpus/nested-functions.parseB.txt +++ b/test/fixtures/javascript/corpus/nested-functions.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/null.diffA-B.txt b/test/fixtures/javascript/corpus/null.diffA-B.txt index 4d48f1e43..8b3d414fd 100644 --- a/test/fixtures/javascript/corpus/null.diffA-B.txt +++ b/test/fixtures/javascript/corpus/null.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Return {+(Null)+})+} {-(Null)-}) diff --git a/test/fixtures/javascript/corpus/null.diffB-A.txt b/test/fixtures/javascript/corpus/null.diffB-A.txt index 08550b95d..b56dab77f 100644 --- a/test/fixtures/javascript/corpus/null.diffB-A.txt +++ b/test/fixtures/javascript/corpus/null.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Null)+} {-(Return {-(Null)-})-}) diff --git a/test/fixtures/javascript/corpus/null.parseA.txt b/test/fixtures/javascript/corpus/null.parseA.txt index d6499ddef..5c722556e 100644 --- a/test/fixtures/javascript/corpus/null.parseA.txt +++ b/test/fixtures/javascript/corpus/null.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Null)) diff --git a/test/fixtures/javascript/corpus/null.parseB.txt b/test/fixtures/javascript/corpus/null.parseB.txt index 1572f3d32..24f16825d 100644 --- a/test/fixtures/javascript/corpus/null.parseB.txt +++ b/test/fixtures/javascript/corpus/null.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Null))) diff --git a/test/fixtures/javascript/corpus/number.diffA-B.txt b/test/fixtures/javascript/corpus/number.diffA-B.txt index 9c7b7f65e..dedbdd592 100644 --- a/test/fixtures/javascript/corpus/number.diffA-B.txt +++ b/test/fixtures/javascript/corpus/number.diffA-B.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Float) ->(Float) }) diff --git a/test/fixtures/javascript/corpus/number.diffB-A.txt b/test/fixtures/javascript/corpus/number.diffB-A.txt index 9c7b7f65e..dedbdd592 100644 --- a/test/fixtures/javascript/corpus/number.diffB-A.txt +++ b/test/fixtures/javascript/corpus/number.diffB-A.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Float) ->(Float) }) diff --git a/test/fixtures/javascript/corpus/number.parseA.txt b/test/fixtures/javascript/corpus/number.parseA.txt index ef448a3ab..ca689125a 100644 --- a/test/fixtures/javascript/corpus/number.parseA.txt +++ b/test/fixtures/javascript/corpus/number.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Float)) diff --git a/test/fixtures/javascript/corpus/number.parseB.txt b/test/fixtures/javascript/corpus/number.parseB.txt index ef448a3ab..ca689125a 100644 --- a/test/fixtures/javascript/corpus/number.parseB.txt +++ b/test/fixtures/javascript/corpus/number.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Float)) diff --git a/test/fixtures/javascript/corpus/object.diffA-B.txt b/test/fixtures/javascript/corpus/object.diffA-B.txt index f6f828919..98d338876 100644 --- a/test/fixtures/javascript/corpus/object.diffA-B.txt +++ b/test/fixtures/javascript/corpus/object.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (KeyValue (TextElement) diff --git a/test/fixtures/javascript/corpus/object.diffB-A.txt b/test/fixtures/javascript/corpus/object.diffB-A.txt index 941bef337..647a9c7eb 100644 --- a/test/fixtures/javascript/corpus/object.diffB-A.txt +++ b/test/fixtures/javascript/corpus/object.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (KeyValue (TextElement) diff --git a/test/fixtures/javascript/corpus/object.parseA.txt b/test/fixtures/javascript/corpus/object.parseA.txt index 29f6b615c..7a96e8f9f 100644 --- a/test/fixtures/javascript/corpus/object.parseA.txt +++ b/test/fixtures/javascript/corpus/object.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (KeyValue (TextElement) diff --git a/test/fixtures/javascript/corpus/object.parseB.txt b/test/fixtures/javascript/corpus/object.parseB.txt index 54fac815b..a99262911 100644 --- a/test/fixtures/javascript/corpus/object.parseB.txt +++ b/test/fixtures/javascript/corpus/object.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (KeyValue (TextElement) 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 9c40be32f..55487ab44 100644 --- a/test/fixtures/javascript/corpus/objects-with-methods.diffA-B.txt +++ b/test/fixtures/javascript/corpus/objects-with-methods.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (Method (Empty) 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 914db2372..069f3780f 100644 --- a/test/fixtures/javascript/corpus/objects-with-methods.diffB-A.txt +++ b/test/fixtures/javascript/corpus/objects-with-methods.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (Method (Empty) diff --git a/test/fixtures/javascript/corpus/objects-with-methods.parseA.txt b/test/fixtures/javascript/corpus/objects-with-methods.parseA.txt index 618957d0f..6f7f53d13 100644 --- a/test/fixtures/javascript/corpus/objects-with-methods.parseA.txt +++ b/test/fixtures/javascript/corpus/objects-with-methods.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (Method (Empty) diff --git a/test/fixtures/javascript/corpus/objects-with-methods.parseB.txt b/test/fixtures/javascript/corpus/objects-with-methods.parseB.txt index 8acf4faff..423132fb8 100644 --- a/test/fixtures/javascript/corpus/objects-with-methods.parseB.txt +++ b/test/fixtures/javascript/corpus/objects-with-methods.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (Method (Empty) diff --git a/test/fixtures/javascript/corpus/regex.diffA-B.txt b/test/fixtures/javascript/corpus/regex.diffA-B.txt index 9c5e630f5..adc40c12d 100644 --- a/test/fixtures/javascript/corpus/regex.diffA-B.txt +++ b/test/fixtures/javascript/corpus/regex.diffA-B.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Regex) ->(Regex) }) diff --git a/test/fixtures/javascript/corpus/regex.diffB-A.txt b/test/fixtures/javascript/corpus/regex.diffB-A.txt index 9c5e630f5..adc40c12d 100644 --- a/test/fixtures/javascript/corpus/regex.diffB-A.txt +++ b/test/fixtures/javascript/corpus/regex.diffB-A.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Regex) ->(Regex) }) diff --git a/test/fixtures/javascript/corpus/regex.parseA.txt b/test/fixtures/javascript/corpus/regex.parseA.txt index a72f52076..b154d3ebe 100644 --- a/test/fixtures/javascript/corpus/regex.parseA.txt +++ b/test/fixtures/javascript/corpus/regex.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Regex)) diff --git a/test/fixtures/javascript/corpus/regex.parseB.txt b/test/fixtures/javascript/corpus/regex.parseB.txt index a72f52076..b154d3ebe 100644 --- a/test/fixtures/javascript/corpus/regex.parseB.txt +++ b/test/fixtures/javascript/corpus/regex.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Regex)) diff --git a/test/fixtures/javascript/corpus/relational-operator.diffA-B.txt b/test/fixtures/javascript/corpus/relational-operator.diffA-B.txt index b10fba844..d98198807 100644 --- a/test/fixtures/javascript/corpus/relational-operator.diffA-B.txt +++ b/test/fixtures/javascript/corpus/relational-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (LessThan {-(Identifier)-} {-(Identifier)-}) diff --git a/test/fixtures/javascript/corpus/relational-operator.diffB-A.txt b/test/fixtures/javascript/corpus/relational-operator.diffB-A.txt index 811022c76..17bca315b 100644 --- a/test/fixtures/javascript/corpus/relational-operator.diffB-A.txt +++ b/test/fixtures/javascript/corpus/relational-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (LessThanEqual {-(Identifier)-} {-(Identifier)-}) diff --git a/test/fixtures/javascript/corpus/relational-operator.parseA.txt b/test/fixtures/javascript/corpus/relational-operator.parseA.txt index 5e1d59256..4bacd5c81 100644 --- a/test/fixtures/javascript/corpus/relational-operator.parseA.txt +++ b/test/fixtures/javascript/corpus/relational-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (LessThan (Identifier) (Identifier))) diff --git a/test/fixtures/javascript/corpus/relational-operator.parseB.txt b/test/fixtures/javascript/corpus/relational-operator.parseB.txt index 31b057eaf..eb9125c71 100644 --- a/test/fixtures/javascript/corpus/relational-operator.parseB.txt +++ b/test/fixtures/javascript/corpus/relational-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (LessThanEqual (Identifier) (Identifier))) diff --git a/test/fixtures/javascript/corpus/return-statement.diffA-B.txt b/test/fixtures/javascript/corpus/return-statement.diffA-B.txt index fc7cd4365..f18860ea0 100644 --- a/test/fixtures/javascript/corpus/return-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/return-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return { (Float) ->(Empty) })) diff --git a/test/fixtures/javascript/corpus/return-statement.diffB-A.txt b/test/fixtures/javascript/corpus/return-statement.diffB-A.txt index b7288ed17..883b736a6 100644 --- a/test/fixtures/javascript/corpus/return-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/return-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return { (Empty) ->(Float) })) diff --git a/test/fixtures/javascript/corpus/return-statement.parseA.txt b/test/fixtures/javascript/corpus/return-statement.parseA.txt index c116bee18..fd629221e 100644 --- a/test/fixtures/javascript/corpus/return-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/return-statement.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Float))) diff --git a/test/fixtures/javascript/corpus/return-statement.parseB.txt b/test/fixtures/javascript/corpus/return-statement.parseB.txt index 7d27dcae1..878ee5e75 100644 --- a/test/fixtures/javascript/corpus/return-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/return-statement.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Empty))) diff --git a/test/fixtures/javascript/corpus/string.diffA-B.txt b/test/fixtures/javascript/corpus/string.diffA-B.txt index c368003ca..93e83c046 100644 --- a/test/fixtures/javascript/corpus/string.diffA-B.txt +++ b/test/fixtures/javascript/corpus/string.diffA-B.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (TextElement) ->(TextElement) }) diff --git a/test/fixtures/javascript/corpus/string.diffB-A.txt b/test/fixtures/javascript/corpus/string.diffB-A.txt index c368003ca..93e83c046 100644 --- a/test/fixtures/javascript/corpus/string.diffB-A.txt +++ b/test/fixtures/javascript/corpus/string.diffB-A.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (TextElement) ->(TextElement) }) diff --git a/test/fixtures/javascript/corpus/string.parseA.txt b/test/fixtures/javascript/corpus/string.parseA.txt index 7eb233a5b..244724dcd 100644 --- a/test/fixtures/javascript/corpus/string.parseA.txt +++ b/test/fixtures/javascript/corpus/string.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (TextElement)) diff --git a/test/fixtures/javascript/corpus/string.parseB.txt b/test/fixtures/javascript/corpus/string.parseB.txt index 7eb233a5b..244724dcd 100644 --- a/test/fixtures/javascript/corpus/string.parseB.txt +++ b/test/fixtures/javascript/corpus/string.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (TextElement)) diff --git a/test/fixtures/javascript/corpus/subscript-access-assignment.diffA-B.txt b/test/fixtures/javascript/corpus/subscript-access-assignment.diffA-B.txt index 364b1a226..b87f35fd6 100644 --- a/test/fixtures/javascript/corpus/subscript-access-assignment.diffA-B.txt +++ b/test/fixtures/javascript/corpus/subscript-access-assignment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Subscript (Identifier) diff --git a/test/fixtures/javascript/corpus/subscript-access-assignment.diffB-A.txt b/test/fixtures/javascript/corpus/subscript-access-assignment.diffB-A.txt index 364b1a226..b87f35fd6 100644 --- a/test/fixtures/javascript/corpus/subscript-access-assignment.diffB-A.txt +++ b/test/fixtures/javascript/corpus/subscript-access-assignment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Subscript (Identifier) diff --git a/test/fixtures/javascript/corpus/subscript-access-assignment.parseA.txt b/test/fixtures/javascript/corpus/subscript-access-assignment.parseA.txt index 23430e8b8..065c52c81 100644 --- a/test/fixtures/javascript/corpus/subscript-access-assignment.parseA.txt +++ b/test/fixtures/javascript/corpus/subscript-access-assignment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Subscript (Identifier) diff --git a/test/fixtures/javascript/corpus/subscript-access-assignment.parseB.txt b/test/fixtures/javascript/corpus/subscript-access-assignment.parseB.txt index 23430e8b8..065c52c81 100644 --- a/test/fixtures/javascript/corpus/subscript-access-assignment.parseB.txt +++ b/test/fixtures/javascript/corpus/subscript-access-assignment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Subscript (Identifier) diff --git a/test/fixtures/javascript/corpus/subscript-access-string.diffA-B.txt b/test/fixtures/javascript/corpus/subscript-access-string.diffA-B.txt index e89be8ff9..e95863ee0 100644 --- a/test/fixtures/javascript/corpus/subscript-access-string.diffA-B.txt +++ b/test/fixtures/javascript/corpus/subscript-access-string.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) { (TextElement) diff --git a/test/fixtures/javascript/corpus/subscript-access-string.diffB-A.txt b/test/fixtures/javascript/corpus/subscript-access-string.diffB-A.txt index e89be8ff9..e95863ee0 100644 --- a/test/fixtures/javascript/corpus/subscript-access-string.diffB-A.txt +++ b/test/fixtures/javascript/corpus/subscript-access-string.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) { (TextElement) diff --git a/test/fixtures/javascript/corpus/subscript-access-string.parseA.txt b/test/fixtures/javascript/corpus/subscript-access-string.parseA.txt index 1005056be..5d5853ad7 100644 --- a/test/fixtures/javascript/corpus/subscript-access-string.parseA.txt +++ b/test/fixtures/javascript/corpus/subscript-access-string.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) (TextElement))) diff --git a/test/fixtures/javascript/corpus/subscript-access-string.parseB.txt b/test/fixtures/javascript/corpus/subscript-access-string.parseB.txt index 1005056be..5d5853ad7 100644 --- a/test/fixtures/javascript/corpus/subscript-access-string.parseB.txt +++ b/test/fixtures/javascript/corpus/subscript-access-string.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) (TextElement))) diff --git a/test/fixtures/javascript/corpus/subscript-access-variable.diffA-B.txt b/test/fixtures/javascript/corpus/subscript-access-variable.diffA-B.txt index 428bf4bf1..0a3963195 100644 --- a/test/fixtures/javascript/corpus/subscript-access-variable.diffA-B.txt +++ b/test/fixtures/javascript/corpus/subscript-access-variable.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) { (Identifier) diff --git a/test/fixtures/javascript/corpus/subscript-access-variable.diffB-A.txt b/test/fixtures/javascript/corpus/subscript-access-variable.diffB-A.txt index 428bf4bf1..0a3963195 100644 --- a/test/fixtures/javascript/corpus/subscript-access-variable.diffB-A.txt +++ b/test/fixtures/javascript/corpus/subscript-access-variable.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) { (Identifier) diff --git a/test/fixtures/javascript/corpus/subscript-access-variable.parseA.txt b/test/fixtures/javascript/corpus/subscript-access-variable.parseA.txt index d51465cb0..e2c7fbd55 100644 --- a/test/fixtures/javascript/corpus/subscript-access-variable.parseA.txt +++ b/test/fixtures/javascript/corpus/subscript-access-variable.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) (Identifier))) diff --git a/test/fixtures/javascript/corpus/subscript-access-variable.parseB.txt b/test/fixtures/javascript/corpus/subscript-access-variable.parseB.txt index d51465cb0..e2c7fbd55 100644 --- a/test/fixtures/javascript/corpus/subscript-access-variable.parseB.txt +++ b/test/fixtures/javascript/corpus/subscript-access-variable.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) (Identifier))) diff --git a/test/fixtures/javascript/corpus/switch-statement.diffA-B.txt b/test/fixtures/javascript/corpus/switch-statement.diffA-B.txt index 3883f69c5..b150ce8fc 100644 --- a/test/fixtures/javascript/corpus/switch-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/switch-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match { (Float) ->(Float) } diff --git a/test/fixtures/javascript/corpus/switch-statement.diffB-A.txt b/test/fixtures/javascript/corpus/switch-statement.diffB-A.txt index 3883f69c5..b150ce8fc 100644 --- a/test/fixtures/javascript/corpus/switch-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/switch-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match { (Float) ->(Float) } diff --git a/test/fixtures/javascript/corpus/switch-statement.parseA.txt b/test/fixtures/javascript/corpus/switch-statement.parseA.txt index 3e597d106..50a633ec5 100644 --- a/test/fixtures/javascript/corpus/switch-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/switch-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match (Float) (Statements diff --git a/test/fixtures/javascript/corpus/switch-statement.parseB.txt b/test/fixtures/javascript/corpus/switch-statement.parseB.txt index 3e597d106..50a633ec5 100644 --- a/test/fixtures/javascript/corpus/switch-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/switch-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match (Float) (Statements diff --git a/test/fixtures/javascript/corpus/template-string.diffA-B.txt b/test/fixtures/javascript/corpus/template-string.diffA-B.txt index d1f43f5d8..d6d776fad 100644 --- a/test/fixtures/javascript/corpus/template-string.diffA-B.txt +++ b/test/fixtures/javascript/corpus/template-string.diffA-B.txt @@ -1,2 +1,2 @@ -(Program +(Statements (String)) diff --git a/test/fixtures/javascript/corpus/template-string.diffB-A.txt b/test/fixtures/javascript/corpus/template-string.diffB-A.txt index d1f43f5d8..d6d776fad 100644 --- a/test/fixtures/javascript/corpus/template-string.diffB-A.txt +++ b/test/fixtures/javascript/corpus/template-string.diffB-A.txt @@ -1,2 +1,2 @@ -(Program +(Statements (String)) diff --git a/test/fixtures/javascript/corpus/template-string.parseA.txt b/test/fixtures/javascript/corpus/template-string.parseA.txt index d1f43f5d8..d6d776fad 100644 --- a/test/fixtures/javascript/corpus/template-string.parseA.txt +++ b/test/fixtures/javascript/corpus/template-string.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (String)) diff --git a/test/fixtures/javascript/corpus/template-string.parseB.txt b/test/fixtures/javascript/corpus/template-string.parseB.txt index d1f43f5d8..d6d776fad 100644 --- a/test/fixtures/javascript/corpus/template-string.parseB.txt +++ b/test/fixtures/javascript/corpus/template-string.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (String)) diff --git a/test/fixtures/javascript/corpus/ternary.diffA-B.txt b/test/fixtures/javascript/corpus/ternary.diffA-B.txt index 500a7b34a..62d5ee7dc 100644 --- a/test/fixtures/javascript/corpus/ternary.diffA-B.txt +++ b/test/fixtures/javascript/corpus/ternary.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Assignment {+(MemberAccess {+(Identifier)+} diff --git a/test/fixtures/javascript/corpus/ternary.diffB-A.txt b/test/fixtures/javascript/corpus/ternary.diffB-A.txt index 4696a13d8..651fe0c1f 100644 --- a/test/fixtures/javascript/corpus/ternary.diffB-A.txt +++ b/test/fixtures/javascript/corpus/ternary.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(If {+(Identifier)+} {+(Identifier)+} diff --git a/test/fixtures/javascript/corpus/ternary.parseA.txt b/test/fixtures/javascript/corpus/ternary.parseA.txt index 76d8615b5..ff5f03d89 100644 --- a/test/fixtures/javascript/corpus/ternary.parseA.txt +++ b/test/fixtures/javascript/corpus/ternary.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Identifier) (Identifier) diff --git a/test/fixtures/javascript/corpus/ternary.parseB.txt b/test/fixtures/javascript/corpus/ternary.parseB.txt index 988c986b7..93db1d9d2 100644 --- a/test/fixtures/javascript/corpus/ternary.parseB.txt +++ b/test/fixtures/javascript/corpus/ternary.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (MemberAccess (Identifier) diff --git a/test/fixtures/javascript/corpus/this-expression.diffA-B.txt b/test/fixtures/javascript/corpus/this-expression.diffA-B.txt index f5bd377a6..d02578fcf 100644 --- a/test/fixtures/javascript/corpus/this-expression.diffA-B.txt +++ b/test/fixtures/javascript/corpus/this-expression.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Return {+(This)+})+} {-(This)-}) diff --git a/test/fixtures/javascript/corpus/this-expression.diffB-A.txt b/test/fixtures/javascript/corpus/this-expression.diffB-A.txt index ca392b2b4..47b93e9e0 100644 --- a/test/fixtures/javascript/corpus/this-expression.diffB-A.txt +++ b/test/fixtures/javascript/corpus/this-expression.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(This)+} {-(Return {-(This)-})-}) diff --git a/test/fixtures/javascript/corpus/this-expression.parseA.txt b/test/fixtures/javascript/corpus/this-expression.parseA.txt index 276aa4584..2fce35ed5 100644 --- a/test/fixtures/javascript/corpus/this-expression.parseA.txt +++ b/test/fixtures/javascript/corpus/this-expression.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (This)) diff --git a/test/fixtures/javascript/corpus/this-expression.parseB.txt b/test/fixtures/javascript/corpus/this-expression.parseB.txt index 0872d6ab5..2ebca766a 100644 --- a/test/fixtures/javascript/corpus/this-expression.parseB.txt +++ b/test/fixtures/javascript/corpus/this-expression.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (This))) diff --git a/test/fixtures/javascript/corpus/throw-statement.diffA-B.txt b/test/fixtures/javascript/corpus/throw-statement.diffA-B.txt index a442e1a04..5b8fd0cab 100644 --- a/test/fixtures/javascript/corpus/throw-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/throw-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Throw (New (Call diff --git a/test/fixtures/javascript/corpus/throw-statement.diffB-A.txt b/test/fixtures/javascript/corpus/throw-statement.diffB-A.txt index a442e1a04..5b8fd0cab 100644 --- a/test/fixtures/javascript/corpus/throw-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/throw-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Throw (New (Call diff --git a/test/fixtures/javascript/corpus/throw-statement.parseA.txt b/test/fixtures/javascript/corpus/throw-statement.parseA.txt index d6347b923..f19d27175 100644 --- a/test/fixtures/javascript/corpus/throw-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/throw-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Throw (New (Call diff --git a/test/fixtures/javascript/corpus/throw-statement.parseB.txt b/test/fixtures/javascript/corpus/throw-statement.parseB.txt index d6347b923..f19d27175 100644 --- a/test/fixtures/javascript/corpus/throw-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/throw-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Throw (New (Call diff --git a/test/fixtures/javascript/corpus/true.diffA-B.txt b/test/fixtures/javascript/corpus/true.diffA-B.txt index ac2ca170c..62f7e4e3e 100644 --- a/test/fixtures/javascript/corpus/true.diffA-B.txt +++ b/test/fixtures/javascript/corpus/true.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Return {+(Boolean)+})+} {-(Boolean)-}) diff --git a/test/fixtures/javascript/corpus/true.diffB-A.txt b/test/fixtures/javascript/corpus/true.diffB-A.txt index 846a9c224..57c1b8c70 100644 --- a/test/fixtures/javascript/corpus/true.diffB-A.txt +++ b/test/fixtures/javascript/corpus/true.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Boolean)+} {-(Return {-(Boolean)-})-}) diff --git a/test/fixtures/javascript/corpus/true.parseA.txt b/test/fixtures/javascript/corpus/true.parseA.txt index 1fdad7cac..25d98872e 100644 --- a/test/fixtures/javascript/corpus/true.parseA.txt +++ b/test/fixtures/javascript/corpus/true.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Boolean)) diff --git a/test/fixtures/javascript/corpus/true.parseB.txt b/test/fixtures/javascript/corpus/true.parseB.txt index a37bdc4ee..02e3c2a13 100644 --- a/test/fixtures/javascript/corpus/true.parseB.txt +++ b/test/fixtures/javascript/corpus/true.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Boolean))) diff --git a/test/fixtures/javascript/corpus/try-statement.diffA-B.txt b/test/fixtures/javascript/corpus/try-statement.diffA-B.txt index a7241e603..e5ea1fab8 100644 --- a/test/fixtures/javascript/corpus/try-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/try-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Identifier)) diff --git a/test/fixtures/javascript/corpus/try-statement.diffB-A.txt b/test/fixtures/javascript/corpus/try-statement.diffB-A.txt index a7241e603..e5ea1fab8 100644 --- a/test/fixtures/javascript/corpus/try-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/try-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Identifier)) diff --git a/test/fixtures/javascript/corpus/try-statement.parseA.txt b/test/fixtures/javascript/corpus/try-statement.parseA.txt index 22e10b492..00902f275 100644 --- a/test/fixtures/javascript/corpus/try-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/try-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Identifier)) diff --git a/test/fixtures/javascript/corpus/try-statement.parseB.txt b/test/fixtures/javascript/corpus/try-statement.parseB.txt index 22e10b492..00902f275 100644 --- a/test/fixtures/javascript/corpus/try-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/try-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Identifier)) diff --git a/test/fixtures/javascript/corpus/type-operator.diffA-B.txt b/test/fixtures/javascript/corpus/type-operator.diffA-B.txt index fe1dba975..41ac6e1cb 100644 --- a/test/fixtures/javascript/corpus/type-operator.diffA-B.txt +++ b/test/fixtures/javascript/corpus/type-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(InstanceOf {+(Identifier)+} {+(Identifier)+})+} diff --git a/test/fixtures/javascript/corpus/type-operator.diffB-A.txt b/test/fixtures/javascript/corpus/type-operator.diffB-A.txt index f45173af0..7ad244a67 100644 --- a/test/fixtures/javascript/corpus/type-operator.diffB-A.txt +++ b/test/fixtures/javascript/corpus/type-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Typeof {+(Identifier)+})+} {-(InstanceOf diff --git a/test/fixtures/javascript/corpus/type-operator.parseA.txt b/test/fixtures/javascript/corpus/type-operator.parseA.txt index 7953fe31a..f20b03753 100644 --- a/test/fixtures/javascript/corpus/type-operator.parseA.txt +++ b/test/fixtures/javascript/corpus/type-operator.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Typeof (Identifier))) diff --git a/test/fixtures/javascript/corpus/type-operator.parseB.txt b/test/fixtures/javascript/corpus/type-operator.parseB.txt index 79142c960..6087bffac 100644 --- a/test/fixtures/javascript/corpus/type-operator.parseB.txt +++ b/test/fixtures/javascript/corpus/type-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (InstanceOf (Identifier) (Identifier))) diff --git a/test/fixtures/javascript/corpus/undefined.diffA-B.txt b/test/fixtures/javascript/corpus/undefined.diffA-B.txt index 8edd91ab0..e0aaaa117 100644 --- a/test/fixtures/javascript/corpus/undefined.diffA-B.txt +++ b/test/fixtures/javascript/corpus/undefined.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Return {+(Undefined)+})+} {-(Undefined)-}) diff --git a/test/fixtures/javascript/corpus/undefined.diffB-A.txt b/test/fixtures/javascript/corpus/undefined.diffB-A.txt index a74390230..6736d273a 100644 --- a/test/fixtures/javascript/corpus/undefined.diffB-A.txt +++ b/test/fixtures/javascript/corpus/undefined.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Undefined)+} {-(Return {-(Undefined)-})-}) diff --git a/test/fixtures/javascript/corpus/undefined.parseA.txt b/test/fixtures/javascript/corpus/undefined.parseA.txt index 87378cd50..ea5e6fca6 100644 --- a/test/fixtures/javascript/corpus/undefined.parseA.txt +++ b/test/fixtures/javascript/corpus/undefined.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Undefined)) diff --git a/test/fixtures/javascript/corpus/undefined.parseB.txt b/test/fixtures/javascript/corpus/undefined.parseB.txt index 0afc44c9e..58c1a9eaf 100644 --- a/test/fixtures/javascript/corpus/undefined.parseB.txt +++ b/test/fixtures/javascript/corpus/undefined.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Undefined))) diff --git a/test/fixtures/javascript/corpus/var-declaration.diffA-B.txt b/test/fixtures/javascript/corpus/var-declaration.diffA-B.txt index f7607a355..125c37429 100644 --- a/test/fixtures/javascript/corpus/var-declaration.diffA-B.txt +++ b/test/fixtures/javascript/corpus/var-declaration.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/javascript/corpus/var-declaration.diffB-A.txt b/test/fixtures/javascript/corpus/var-declaration.diffB-A.txt index 57e89c6ec..190ddb8ff 100644 --- a/test/fixtures/javascript/corpus/var-declaration.diffB-A.txt +++ b/test/fixtures/javascript/corpus/var-declaration.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/javascript/corpus/var-declaration.parseA.txt b/test/fixtures/javascript/corpus/var-declaration.parseA.txt index f6cc57179..1634cc36e 100644 --- a/test/fixtures/javascript/corpus/var-declaration.parseA.txt +++ b/test/fixtures/javascript/corpus/var-declaration.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/javascript/corpus/var-declaration.parseB.txt b/test/fixtures/javascript/corpus/var-declaration.parseB.txt index 66abdae58..2ffadbf28 100644 --- a/test/fixtures/javascript/corpus/var-declaration.parseB.txt +++ b/test/fixtures/javascript/corpus/var-declaration.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/javascript/corpus/variable.diffA-B.txt b/test/fixtures/javascript/corpus/variable.diffA-B.txt index 6ac9cd896..d2449f436 100644 --- a/test/fixtures/javascript/corpus/variable.diffA-B.txt +++ b/test/fixtures/javascript/corpus/variable.diffA-B.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/javascript/corpus/variable.diffB-A.txt b/test/fixtures/javascript/corpus/variable.diffB-A.txt index 6ac9cd896..d2449f436 100644 --- a/test/fixtures/javascript/corpus/variable.diffB-A.txt +++ b/test/fixtures/javascript/corpus/variable.diffB-A.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/javascript/corpus/variable.parseA.txt b/test/fixtures/javascript/corpus/variable.parseA.txt index 67b75f388..5f0ab64c1 100644 --- a/test/fixtures/javascript/corpus/variable.parseA.txt +++ b/test/fixtures/javascript/corpus/variable.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Identifier)) diff --git a/test/fixtures/javascript/corpus/variable.parseB.txt b/test/fixtures/javascript/corpus/variable.parseB.txt index 67b75f388..5f0ab64c1 100644 --- a/test/fixtures/javascript/corpus/variable.parseB.txt +++ b/test/fixtures/javascript/corpus/variable.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Identifier)) diff --git a/test/fixtures/javascript/corpus/void-operator.diffA-B.txt b/test/fixtures/javascript/corpus/void-operator.diffA-B.txt index 1478a4241..8b8801ab7 100644 --- a/test/fixtures/javascript/corpus/void-operator.diffA-B.txt +++ b/test/fixtures/javascript/corpus/void-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Void (Call { (Identifier) diff --git a/test/fixtures/javascript/corpus/void-operator.diffB-A.txt b/test/fixtures/javascript/corpus/void-operator.diffB-A.txt index 1478a4241..8b8801ab7 100644 --- a/test/fixtures/javascript/corpus/void-operator.diffB-A.txt +++ b/test/fixtures/javascript/corpus/void-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Void (Call { (Identifier) diff --git a/test/fixtures/javascript/corpus/void-operator.parseA.txt b/test/fixtures/javascript/corpus/void-operator.parseA.txt index 71c1d3bd3..71bb37891 100644 --- a/test/fixtures/javascript/corpus/void-operator.parseA.txt +++ b/test/fixtures/javascript/corpus/void-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Void (Call (Identifier) diff --git a/test/fixtures/javascript/corpus/void-operator.parseB.txt b/test/fixtures/javascript/corpus/void-operator.parseB.txt index 71c1d3bd3..71bb37891 100644 --- a/test/fixtures/javascript/corpus/void-operator.parseB.txt +++ b/test/fixtures/javascript/corpus/void-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Void (Call (Identifier) diff --git a/test/fixtures/javascript/corpus/while-statement.diffA-B.txt b/test/fixtures/javascript/corpus/while-statement.diffA-B.txt index 6c6581fbe..123a81df0 100644 --- a/test/fixtures/javascript/corpus/while-statement.diffA-B.txt +++ b/test/fixtures/javascript/corpus/while-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While { (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 6c6581fbe..123a81df0 100644 --- a/test/fixtures/javascript/corpus/while-statement.diffB-A.txt +++ b/test/fixtures/javascript/corpus/while-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While { (Identifier) ->(Identifier) } diff --git a/test/fixtures/javascript/corpus/while-statement.parseA.txt b/test/fixtures/javascript/corpus/while-statement.parseA.txt index 41960b042..9d2e8f0d8 100644 --- a/test/fixtures/javascript/corpus/while-statement.parseA.txt +++ b/test/fixtures/javascript/corpus/while-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Identifier) (Statements diff --git a/test/fixtures/javascript/corpus/while-statement.parseB.txt b/test/fixtures/javascript/corpus/while-statement.parseB.txt index 41960b042..9d2e8f0d8 100644 --- a/test/fixtures/javascript/corpus/while-statement.parseB.txt +++ b/test/fixtures/javascript/corpus/while-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Identifier) (Statements diff --git a/test/fixtures/javascript/corpus/yield.diffA-B.txt b/test/fixtures/javascript/corpus/yield.diffA-B.txt index ccde7b2d7..7d14f5b38 100644 --- a/test/fixtures/javascript/corpus/yield.diffA-B.txt +++ b/test/fixtures/javascript/corpus/yield.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/yield.diffB-A.txt b/test/fixtures/javascript/corpus/yield.diffB-A.txt index d7dd3fc20..28d99fdcc 100644 --- a/test/fixtures/javascript/corpus/yield.diffB-A.txt +++ b/test/fixtures/javascript/corpus/yield.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/yield.parseA.txt b/test/fixtures/javascript/corpus/yield.parseA.txt index 47d764d16..ead5d4445 100644 --- a/test/fixtures/javascript/corpus/yield.parseA.txt +++ b/test/fixtures/javascript/corpus/yield.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/javascript/corpus/yield.parseB.txt b/test/fixtures/javascript/corpus/yield.parseB.txt index 54eada74e..ba8875d78 100644 --- a/test/fixtures/javascript/corpus/yield.parseB.txt +++ b/test/fixtures/javascript/corpus/yield.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/python/corpus/assert-statement.diffA-B.txt b/test/fixtures/python/corpus/assert-statement.diffA-B.txt index f94c584be..6eec42d8b 100644 --- a/test/fixtures/python/corpus/assert-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/assert-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) {+(Identifier)+} diff --git a/test/fixtures/python/corpus/assert-statement.diffB-A.txt b/test/fixtures/python/corpus/assert-statement.diffB-A.txt index 3e06b4659..454fce91a 100644 --- a/test/fixtures/python/corpus/assert-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/assert-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) {-(Identifier)-} diff --git a/test/fixtures/python/corpus/assert-statement.parseA.txt b/test/fixtures/python/corpus/assert-statement.parseA.txt index 21c3139eb..ad22b5d53 100644 --- a/test/fixtures/python/corpus/assert-statement.parseA.txt +++ b/test/fixtures/python/corpus/assert-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/assert-statement.parseB.txt b/test/fixtures/python/corpus/assert-statement.parseB.txt index 5faf916ff..eaeb4c216 100644 --- a/test/fixtures/python/corpus/assert-statement.parseB.txt +++ b/test/fixtures/python/corpus/assert-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/assignment.diffA-B.txt b/test/fixtures/python/corpus/assignment.diffA-B.txt index 105306e81..936a92db5 100644 --- a/test/fixtures/python/corpus/assignment.diffA-B.txt +++ b/test/fixtures/python/corpus/assignment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Assignment {+(Statements {+(Identifier)+} @@ -10,14 +10,18 @@ { (Identifier) ->(Identifier) } (Integer)) - (Assignment - { (Statements +{+(Assignment + {+(Identifier)+} + {+(Statements + {+(Integer)+} + {+(Integer)+})+})+} +{-(Assignment + {-(Statements {-(Identifier)-} - {-(Identifier)-}) - ->(Identifier) } - (Statements - (Integer) - (Integer))) + {-(Identifier)-})-} + {-(Statements + {-(Integer)-} + {-(Integer)-})-})-} {-(Assignment {-(Identifier)-} {-(Statements diff --git a/test/fixtures/python/corpus/assignment.diffB-A.txt b/test/fixtures/python/corpus/assignment.diffB-A.txt index 3f7d8e47a..eedd8e486 100644 --- a/test/fixtures/python/corpus/assignment.diffB-A.txt +++ b/test/fixtures/python/corpus/assignment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Assignment {+(Identifier)+} {+(Integer)+})+} @@ -10,14 +10,13 @@ {-(Integer)-} (Integer) {+(Integer)+})) -{+(Assignment - {+(Identifier)+} - {+(Statements + (Assignment + { (Identifier) + ->(Identifier) } + { (Integer) + ->(Statements {+(Integer)+} - {+(Integer)+})+})+} -{-(Assignment - {-(Identifier)-} - {-(Integer)-})-} + {+(Integer)+}) }) {-(Assignment {-(Identifier)-} {-(Statements diff --git a/test/fixtures/python/corpus/assignment.parseA.txt b/test/fixtures/python/corpus/assignment.parseA.txt index f0ffb8e02..f012ce5dd 100644 --- a/test/fixtures/python/corpus/assignment.parseA.txt +++ b/test/fixtures/python/corpus/assignment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Integer)) diff --git a/test/fixtures/python/corpus/assignment.parseB.txt b/test/fixtures/python/corpus/assignment.parseB.txt index bff44b92e..c22a7c109 100644 --- a/test/fixtures/python/corpus/assignment.parseB.txt +++ b/test/fixtures/python/corpus/assignment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Statements (Identifier) diff --git a/test/fixtures/python/corpus/async-function-definition.diffA-B.txt b/test/fixtures/python/corpus/async-function-definition.diffA-B.txt index 38aaf812b..e70e50188 100644 --- a/test/fixtures/python/corpus/async-function-definition.diffA-B.txt +++ b/test/fixtures/python/corpus/async-function-definition.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Annotation {+(Function {+(Identifier)+} diff --git a/test/fixtures/python/corpus/async-function-definition.diffB-A.txt b/test/fixtures/python/corpus/async-function-definition.diffB-A.txt index b2c67dbd4..a695e240e 100644 --- a/test/fixtures/python/corpus/async-function-definition.diffB-A.txt +++ b/test/fixtures/python/corpus/async-function-definition.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(Annotation {-(Function {-(Identifier)-} diff --git a/test/fixtures/python/corpus/async-function-definition.parseA.txt b/test/fixtures/python/corpus/async-function-definition.parseA.txt index 5e5cbe380..5662245d1 100644 --- a/test/fixtures/python/corpus/async-function-definition.parseA.txt +++ b/test/fixtures/python/corpus/async-function-definition.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Annotation (Function (Identifier) diff --git a/test/fixtures/python/corpus/async-function-definition.parseB.txt b/test/fixtures/python/corpus/async-function-definition.parseB.txt index 359dbd827..fcfd4cfbb 100644 --- a/test/fixtures/python/corpus/async-function-definition.parseB.txt +++ b/test/fixtures/python/corpus/async-function-definition.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Annotation (Function (Identifier) diff --git a/test/fixtures/python/corpus/attribute.diffA-B.txt b/test/fixtures/python/corpus/attribute.diffA-B.txt index 2b777d817..564dd494f 100644 --- a/test/fixtures/python/corpus/attribute.diffA-B.txt +++ b/test/fixtures/python/corpus/attribute.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess { (Identifier) ->(MemberAccess diff --git a/test/fixtures/python/corpus/attribute.diffB-A.txt b/test/fixtures/python/corpus/attribute.diffB-A.txt index 6c5c1123d..7b3f25d67 100644 --- a/test/fixtures/python/corpus/attribute.diffB-A.txt +++ b/test/fixtures/python/corpus/attribute.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess { (MemberAccess {-(Identifier)-} diff --git a/test/fixtures/python/corpus/attribute.parseA.txt b/test/fixtures/python/corpus/attribute.parseA.txt index 3a5c9e565..70674960a 100644 --- a/test/fixtures/python/corpus/attribute.parseA.txt +++ b/test/fixtures/python/corpus/attribute.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess (Identifier) (Identifier))) diff --git a/test/fixtures/python/corpus/attribute.parseB.txt b/test/fixtures/python/corpus/attribute.parseB.txt index 4a53ec17f..9d14d98a7 100644 --- a/test/fixtures/python/corpus/attribute.parseB.txt +++ b/test/fixtures/python/corpus/attribute.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess (MemberAccess (Identifier) diff --git a/test/fixtures/python/corpus/augmented-assignment.diffA-B.txt b/test/fixtures/python/corpus/augmented-assignment.diffA-B.txt index 795ae8f24..33a88e419 100644 --- a/test/fixtures/python/corpus/augmented-assignment.diffA-B.txt +++ b/test/fixtures/python/corpus/augmented-assignment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) { (Plus diff --git a/test/fixtures/python/corpus/augmented-assignment.diffB-A.txt b/test/fixtures/python/corpus/augmented-assignment.diffB-A.txt index 21e96d951..ea3c92602 100644 --- a/test/fixtures/python/corpus/augmented-assignment.diffB-A.txt +++ b/test/fixtures/python/corpus/augmented-assignment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) { (RShift @@ -12,13 +12,16 @@ {+(RShift {+(Identifier)+} {+(Integer)+})+})+} - (Assignment - { (Identifier) - ->(Identifier) } - (DividedBy - { (Identifier) - ->(Identifier) } - (Integer))) +{+(Assignment + {+(Identifier)+} + {+(DividedBy + {+(Identifier)+} + {+(Integer)+})+})+} +{-(Assignment + {-(Identifier)-} + {-(DividedBy + {-(Identifier)-} + {-(Integer)-})-})-} {-(Assignment {-(Identifier)-} {-(Plus diff --git a/test/fixtures/python/corpus/augmented-assignment.parseA.txt b/test/fixtures/python/corpus/augmented-assignment.parseA.txt index 190b55103..9abfe9a16 100644 --- a/test/fixtures/python/corpus/augmented-assignment.parseA.txt +++ b/test/fixtures/python/corpus/augmented-assignment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Plus diff --git a/test/fixtures/python/corpus/augmented-assignment.parseB.txt b/test/fixtures/python/corpus/augmented-assignment.parseB.txt index aa2045ee3..c8e6d106c 100644 --- a/test/fixtures/python/corpus/augmented-assignment.parseB.txt +++ b/test/fixtures/python/corpus/augmented-assignment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (RShift diff --git a/test/fixtures/python/corpus/await.diffA-B.txt b/test/fixtures/python/corpus/await.diffA-B.txt index 08efc600b..cb5cda07d 100644 --- a/test/fixtures/python/corpus/await.diffA-B.txt +++ b/test/fixtures/python/corpus/await.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Plus diff --git a/test/fixtures/python/corpus/await.diffB-A.txt b/test/fixtures/python/corpus/await.diffB-A.txt index 08efc600b..cb5cda07d 100644 --- a/test/fixtures/python/corpus/await.diffB-A.txt +++ b/test/fixtures/python/corpus/await.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Plus diff --git a/test/fixtures/python/corpus/await.parseA.txt b/test/fixtures/python/corpus/await.parseA.txt index cce6f47b0..0cdfe52de 100644 --- a/test/fixtures/python/corpus/await.parseA.txt +++ b/test/fixtures/python/corpus/await.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Plus diff --git a/test/fixtures/python/corpus/await.parseB.txt b/test/fixtures/python/corpus/await.parseB.txt index cce6f47b0..0cdfe52de 100644 --- a/test/fixtures/python/corpus/await.parseB.txt +++ b/test/fixtures/python/corpus/await.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Plus diff --git a/test/fixtures/python/corpus/binary-operator.diffA-B.txt b/test/fixtures/python/corpus/binary-operator.diffA-B.txt index 13320b6a2..4019d9609 100644 --- a/test/fixtures/python/corpus/binary-operator.diffA-B.txt +++ b/test/fixtures/python/corpus/binary-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(RShift {+(Identifier)+} {+(Identifier)+})+} diff --git a/test/fixtures/python/corpus/binary-operator.diffB-A.txt b/test/fixtures/python/corpus/binary-operator.diffB-A.txt index f2072e075..8c510ef80 100644 --- a/test/fixtures/python/corpus/binary-operator.diffB-A.txt +++ b/test/fixtures/python/corpus/binary-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Plus {+(Identifier)+} {+(Identifier)+})+} diff --git a/test/fixtures/python/corpus/binary-operator.parseA.txt b/test/fixtures/python/corpus/binary-operator.parseA.txt index e9b517350..f4df7c95b 100644 --- a/test/fixtures/python/corpus/binary-operator.parseA.txt +++ b/test/fixtures/python/corpus/binary-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Plus (Identifier) (Identifier)) diff --git a/test/fixtures/python/corpus/binary-operator.parseB.txt b/test/fixtures/python/corpus/binary-operator.parseB.txt index e56504619..c98dc7627 100644 --- a/test/fixtures/python/corpus/binary-operator.parseB.txt +++ b/test/fixtures/python/corpus/binary-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (RShift (Identifier) (Identifier)) diff --git a/test/fixtures/python/corpus/boolean-operator.diffA-B.txt b/test/fixtures/python/corpus/boolean-operator.diffA-B.txt index e50d82a2c..859f4bb46 100644 --- a/test/fixtures/python/corpus/boolean-operator.diffA-B.txt +++ b/test/fixtures/python/corpus/boolean-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (And {-(Identifier)-} {-(Identifier)-}) diff --git a/test/fixtures/python/corpus/boolean-operator.diffB-A.txt b/test/fixtures/python/corpus/boolean-operator.diffB-A.txt index 59ab6347c..1176814b9 100644 --- a/test/fixtures/python/corpus/boolean-operator.diffB-A.txt +++ b/test/fixtures/python/corpus/boolean-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Or {-(Identifier)-} {-(Identifier)-}) diff --git a/test/fixtures/python/corpus/boolean-operator.parseA.txt b/test/fixtures/python/corpus/boolean-operator.parseA.txt index 06de296df..c7052e778 100644 --- a/test/fixtures/python/corpus/boolean-operator.parseA.txt +++ b/test/fixtures/python/corpus/boolean-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (And (Identifier) (Identifier)) diff --git a/test/fixtures/python/corpus/boolean-operator.parseB.txt b/test/fixtures/python/corpus/boolean-operator.parseB.txt index 9cc2bc079..1180fe094 100644 --- a/test/fixtures/python/corpus/boolean-operator.parseB.txt +++ b/test/fixtures/python/corpus/boolean-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Or (Identifier) (Identifier)) diff --git a/test/fixtures/python/corpus/boolean.diffA-B.txt b/test/fixtures/python/corpus/boolean.diffA-B.txt index 79f1741d7..832d11e3c 100644 --- a/test/fixtures/python/corpus/boolean.diffA-B.txt +++ b/test/fixtures/python/corpus/boolean.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(Boolean)-} (Boolean) { (Boolean) diff --git a/test/fixtures/python/corpus/boolean.diffB-A.txt b/test/fixtures/python/corpus/boolean.diffB-A.txt index 79f1741d7..832d11e3c 100644 --- a/test/fixtures/python/corpus/boolean.diffB-A.txt +++ b/test/fixtures/python/corpus/boolean.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(Boolean)-} (Boolean) { (Boolean) diff --git a/test/fixtures/python/corpus/boolean.parseA.txt b/test/fixtures/python/corpus/boolean.parseA.txt index 3a37d9b6c..e5b167fee 100644 --- a/test/fixtures/python/corpus/boolean.parseA.txt +++ b/test/fixtures/python/corpus/boolean.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Boolean) (Boolean) (Boolean)) diff --git a/test/fixtures/python/corpus/boolean.parseB.txt b/test/fixtures/python/corpus/boolean.parseB.txt index 3a37d9b6c..e5b167fee 100644 --- a/test/fixtures/python/corpus/boolean.parseB.txt +++ b/test/fixtures/python/corpus/boolean.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Boolean) (Boolean) (Boolean)) diff --git a/test/fixtures/python/corpus/break-statement.diffA-B.txt b/test/fixtures/python/corpus/break-statement.diffA-B.txt index 1367eecb8..621a59632 100644 --- a/test/fixtures/python/corpus/break-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/break-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Break (Empty)) {+(Break diff --git a/test/fixtures/python/corpus/break-statement.diffB-A.txt b/test/fixtures/python/corpus/break-statement.diffB-A.txt index ecd9cee0f..15c731313 100644 --- a/test/fixtures/python/corpus/break-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/break-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Break (Empty)) {-(Break diff --git a/test/fixtures/python/corpus/break-statement.parseA.txt b/test/fixtures/python/corpus/break-statement.parseA.txt index 4e0806ff8..58c1a6e14 100644 --- a/test/fixtures/python/corpus/break-statement.parseA.txt +++ b/test/fixtures/python/corpus/break-statement.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Break (Empty))) diff --git a/test/fixtures/python/corpus/break-statement.parseB.txt b/test/fixtures/python/corpus/break-statement.parseB.txt index 60a88a85d..fb40ca7bd 100644 --- a/test/fixtures/python/corpus/break-statement.parseB.txt +++ b/test/fixtures/python/corpus/break-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Break (Empty)) (Break diff --git a/test/fixtures/python/corpus/call.diffA-B.txt b/test/fixtures/python/corpus/call.diffA-B.txt index b75a5a434..247adc52d 100644 --- a/test/fixtures/python/corpus/call.diffA-B.txt +++ b/test/fixtures/python/corpus/call.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) {-(Identifier)-} diff --git a/test/fixtures/python/corpus/call.diffB-A.txt b/test/fixtures/python/corpus/call.diffB-A.txt index c86cb65b9..cea75ec1a 100644 --- a/test/fixtures/python/corpus/call.diffB-A.txt +++ b/test/fixtures/python/corpus/call.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) {+(Identifier)+} diff --git a/test/fixtures/python/corpus/call.parseA.txt b/test/fixtures/python/corpus/call.parseA.txt index 16a4376db..523c4a825 100644 --- a/test/fixtures/python/corpus/call.parseA.txt +++ b/test/fixtures/python/corpus/call.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/call.parseB.txt b/test/fixtures/python/corpus/call.parseB.txt index 64a3a2d9f..a6ac94e1d 100644 --- a/test/fixtures/python/corpus/call.parseB.txt +++ b/test/fixtures/python/corpus/call.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Empty)) diff --git a/test/fixtures/python/corpus/class-definition.diffA-B.txt b/test/fixtures/python/corpus/class-definition.diffA-B.txt index 6f620d618..385e87b9f 100644 --- a/test/fixtures/python/corpus/class-definition.diffA-B.txt +++ b/test/fixtures/python/corpus/class-definition.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class { (Identifier) ->(Identifier) } diff --git a/test/fixtures/python/corpus/class-definition.diffB-A.txt b/test/fixtures/python/corpus/class-definition.diffB-A.txt index cb63f4546..ccf23098f 100644 --- a/test/fixtures/python/corpus/class-definition.diffB-A.txt +++ b/test/fixtures/python/corpus/class-definition.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class { (Identifier) ->(Identifier) } diff --git a/test/fixtures/python/corpus/class-definition.parseA.txt b/test/fixtures/python/corpus/class-definition.parseA.txt index 70b121f0e..0296ade4b 100644 --- a/test/fixtures/python/corpus/class-definition.parseA.txt +++ b/test/fixtures/python/corpus/class-definition.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Annotation diff --git a/test/fixtures/python/corpus/class-definition.parseB.txt b/test/fixtures/python/corpus/class-definition.parseB.txt index 02580b0c4..fff246a1e 100644 --- a/test/fixtures/python/corpus/class-definition.parseB.txt +++ b/test/fixtures/python/corpus/class-definition.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/comment.diffA-B.txt b/test/fixtures/python/corpus/comment.diffA-B.txt index caee9eca6..5f7b28f2a 100644 --- a/test/fixtures/python/corpus/comment.diffA-B.txt +++ b/test/fixtures/python/corpus/comment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context {-(Comment)-} (Comment) diff --git a/test/fixtures/python/corpus/comment.diffB-A.txt b/test/fixtures/python/corpus/comment.diffB-A.txt index 57d15fc24..041623af4 100644 --- a/test/fixtures/python/corpus/comment.diffB-A.txt +++ b/test/fixtures/python/corpus/comment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context {-(Comment)-} (Comment) diff --git a/test/fixtures/python/corpus/comment.parseA.txt b/test/fixtures/python/corpus/comment.parseA.txt index e1ae13e92..c5a20a732 100644 --- a/test/fixtures/python/corpus/comment.parseA.txt +++ b/test/fixtures/python/corpus/comment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context (Comment) (Comment) diff --git a/test/fixtures/python/corpus/comment.parseB.txt b/test/fixtures/python/corpus/comment.parseB.txt index 58f034df3..64b336a63 100644 --- a/test/fixtures/python/corpus/comment.parseB.txt +++ b/test/fixtures/python/corpus/comment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context (Comment) (Comment) diff --git a/test/fixtures/python/corpus/comparison-operator.diffA-B.txt b/test/fixtures/python/corpus/comparison-operator.diffA-B.txt index 9bbe5ce35..783c0cb0f 100644 --- a/test/fixtures/python/corpus/comparison-operator.diffA-B.txt +++ b/test/fixtures/python/corpus/comparison-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Not {+(Equal {+(Identifier)+} @@ -17,9 +17,12 @@ {+(Equal {+(Identifier)+} {+(Identifier)+})+})+} -{+(GreaterThan +{ (LessThan + {-(Identifier)-} + {-(Identifier)-}) +->(GreaterThan {+(Identifier)+} - {+(Identifier)+})+} + {+(Identifier)+}) } {+(GreaterThanEqual {+(Identifier)+} {+(Identifier)+})+} @@ -27,18 +30,14 @@ {+(Equal {+(Identifier)+} {+(Identifier)+})+})+} -{+(LessThanEqual - {+(Identifier)+} - {+(Identifier)+})+} + (LessThanEqual + { (Identifier) + ->(Identifier) } + { (Identifier) + ->(Identifier) }) {+(LessThan {+(Identifier)+} {+(Identifier)+})+} -{-(LessThan - {-(Identifier)-} - {-(Identifier)-})-} -{-(LessThanEqual - {-(Identifier)-} - {-(Identifier)-})-} {-(Not {-(Equal {-(Identifier)-} diff --git a/test/fixtures/python/corpus/comparison-operator.diffB-A.txt b/test/fixtures/python/corpus/comparison-operator.diffB-A.txt index 56d83b338..a3d117412 100644 --- a/test/fixtures/python/corpus/comparison-operator.diffB-A.txt +++ b/test/fixtures/python/corpus/comparison-operator.diffB-A.txt @@ -1,44 +1,42 @@ -(Program +(Statements {+(LessThan {+(Identifier)+} {+(Identifier)+})+} {+(LessThanEqual {+(Identifier)+} {+(Identifier)+})+} +{+(Not + {+(Equal + {+(Identifier)+} + {+(Identifier)+})+})+} +{+(GreaterThanEqual + {+(Identifier)+} + {+(Identifier)+})+} +{+(GreaterThan + {+(Identifier)+} + {+(Identifier)+})+} (Not (Equal { (Identifier) ->(Identifier) } { (Identifier) ->(Identifier) })) -{+(GreaterThanEqual - {+(Identifier)+} - {+(Identifier)+})+} -{+(GreaterThan - {+(Identifier)+} - {+(Identifier)+})+} -{+(Not - {+(Equal - {+(Identifier)+} - {+(Identifier)+})+})+} {+(Member {+(Identifier)+} {+(Identifier)+})+} {+(Equal {+(Identifier)+} {+(Identifier)+})+} -{+(Not - {+(Member - {+(Identifier)+} - {+(Identifier)+})+})+} + (Not + (Member + { (Identifier) + ->(Identifier) } + { (Identifier) + ->(Identifier) })) {+(Not {+(Equal {+(Identifier)+} {+(Identifier)+})+})+} -{-(Not - {-(Member - {-(Identifier)-} - {-(Identifier)-})-})-} {-(Equal {-(Identifier)-} {-(Identifier)-})-} diff --git a/test/fixtures/python/corpus/comparison-operator.parseA.txt b/test/fixtures/python/corpus/comparison-operator.parseA.txt index ad62cb1e6..82030142d 100644 --- a/test/fixtures/python/corpus/comparison-operator.parseA.txt +++ b/test/fixtures/python/corpus/comparison-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (LessThan (Identifier) (Identifier)) diff --git a/test/fixtures/python/corpus/comparison-operator.parseB.txt b/test/fixtures/python/corpus/comparison-operator.parseB.txt index 598f86007..a9647fe00 100644 --- a/test/fixtures/python/corpus/comparison-operator.parseB.txt +++ b/test/fixtures/python/corpus/comparison-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Not (Equal (Identifier) diff --git a/test/fixtures/python/corpus/concatenated-string.diffA-B.txt b/test/fixtures/python/corpus/concatenated-string.diffA-B.txt index e7430694b..62aa64606 100644 --- a/test/fixtures/python/corpus/concatenated-string.diffA-B.txt +++ b/test/fixtures/python/corpus/concatenated-string.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Statements {-(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 eccb0b1a1..e75259571 100644 --- a/test/fixtures/python/corpus/concatenated-string.diffB-A.txt +++ b/test/fixtures/python/corpus/concatenated-string.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Statements {-(TextElement)-} (TextElement) diff --git a/test/fixtures/python/corpus/concatenated-string.parseA.txt b/test/fixtures/python/corpus/concatenated-string.parseA.txt index acb17c616..db1371402 100644 --- a/test/fixtures/python/corpus/concatenated-string.parseA.txt +++ b/test/fixtures/python/corpus/concatenated-string.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Statements (TextElement) (TextElement) diff --git a/test/fixtures/python/corpus/concatenated-string.parseB.txt b/test/fixtures/python/corpus/concatenated-string.parseB.txt index fa4a37766..b7376182f 100644 --- a/test/fixtures/python/corpus/concatenated-string.parseB.txt +++ b/test/fixtures/python/corpus/concatenated-string.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Statements (TextElement) (TextElement) diff --git a/test/fixtures/python/corpus/conditional-expression.diffA-B.txt b/test/fixtures/python/corpus/conditional-expression.diffA-B.txt index c6e760a8d..20228627b 100644 --- a/test/fixtures/python/corpus/conditional-expression.diffA-B.txt +++ b/test/fixtures/python/corpus/conditional-expression.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Assignment {+(Identifier)+} {+(If diff --git a/test/fixtures/python/corpus/conditional-expression.diffB-A.txt b/test/fixtures/python/corpus/conditional-expression.diffB-A.txt index d5c9ed657..b3d6319ae 100644 --- a/test/fixtures/python/corpus/conditional-expression.diffB-A.txt +++ b/test/fixtures/python/corpus/conditional-expression.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(If {+(Identifier)+} {+(Call diff --git a/test/fixtures/python/corpus/conditional-expression.parseA.txt b/test/fixtures/python/corpus/conditional-expression.parseA.txt index 18a13549c..67d8d9b07 100644 --- a/test/fixtures/python/corpus/conditional-expression.parseA.txt +++ b/test/fixtures/python/corpus/conditional-expression.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Identifier) (Call diff --git a/test/fixtures/python/corpus/conditional-expression.parseB.txt b/test/fixtures/python/corpus/conditional-expression.parseB.txt index 3e2bdc87c..0f588f6e6 100644 --- a/test/fixtures/python/corpus/conditional-expression.parseB.txt +++ b/test/fixtures/python/corpus/conditional-expression.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (If diff --git a/test/fixtures/python/corpus/continue-statement.diffA-B.txt b/test/fixtures/python/corpus/continue-statement.diffA-B.txt index 16ad0b4d3..174f7ecc9 100644 --- a/test/fixtures/python/corpus/continue-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/continue-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Continue (Empty)) {+(Continue diff --git a/test/fixtures/python/corpus/continue-statement.diffB-A.txt b/test/fixtures/python/corpus/continue-statement.diffB-A.txt index 34f74f20b..544ee454e 100644 --- a/test/fixtures/python/corpus/continue-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/continue-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Continue (Empty)) {-(Continue diff --git a/test/fixtures/python/corpus/continue-statement.parseA.txt b/test/fixtures/python/corpus/continue-statement.parseA.txt index 562d29d73..00420c427 100644 --- a/test/fixtures/python/corpus/continue-statement.parseA.txt +++ b/test/fixtures/python/corpus/continue-statement.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Continue (Empty))) diff --git a/test/fixtures/python/corpus/continue-statement.parseB.txt b/test/fixtures/python/corpus/continue-statement.parseB.txt index 41422eaa0..5f95ddf98 100644 --- a/test/fixtures/python/corpus/continue-statement.parseB.txt +++ b/test/fixtures/python/corpus/continue-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Continue (Empty)) (Continue diff --git a/test/fixtures/python/corpus/decorated-definition.diffA-B.txt b/test/fixtures/python/corpus/decorated-definition.diffA-B.txt index 510db5649..0857a89a8 100644 --- a/test/fixtures/python/corpus/decorated-definition.diffA-B.txt +++ b/test/fixtures/python/corpus/decorated-definition.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Decorator (Identifier) (Class diff --git a/test/fixtures/python/corpus/decorated-definition.diffB-A.txt b/test/fixtures/python/corpus/decorated-definition.diffB-A.txt index bb3125542..d0796adde 100644 --- a/test/fixtures/python/corpus/decorated-definition.diffB-A.txt +++ b/test/fixtures/python/corpus/decorated-definition.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Decorator (Identifier) (Class diff --git a/test/fixtures/python/corpus/decorated-definition.parseA.txt b/test/fixtures/python/corpus/decorated-definition.parseA.txt index 2250469bd..72897a9af 100644 --- a/test/fixtures/python/corpus/decorated-definition.parseA.txt +++ b/test/fixtures/python/corpus/decorated-definition.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Decorator (Identifier) (Class diff --git a/test/fixtures/python/corpus/decorated-definition.parseB.txt b/test/fixtures/python/corpus/decorated-definition.parseB.txt index 25ce8eb60..a86bb7639 100644 --- a/test/fixtures/python/corpus/decorated-definition.parseB.txt +++ b/test/fixtures/python/corpus/decorated-definition.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Decorator (Identifier) (Class diff --git a/test/fixtures/python/corpus/delete-statement.diffA-B.txt b/test/fixtures/python/corpus/delete-statement.diffA-B.txt index 7b3240632..ff40df387 100644 --- a/test/fixtures/python/corpus/delete-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/delete-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Subscript diff --git a/test/fixtures/python/corpus/delete-statement.diffB-A.txt b/test/fixtures/python/corpus/delete-statement.diffB-A.txt index 7b3240632..ff40df387 100644 --- a/test/fixtures/python/corpus/delete-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/delete-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Subscript diff --git a/test/fixtures/python/corpus/delete-statement.parseA.txt b/test/fixtures/python/corpus/delete-statement.parseA.txt index 9f3c646c7..1a9774e50 100644 --- a/test/fixtures/python/corpus/delete-statement.parseA.txt +++ b/test/fixtures/python/corpus/delete-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Subscript diff --git a/test/fixtures/python/corpus/delete-statement.parseB.txt b/test/fixtures/python/corpus/delete-statement.parseB.txt index 9f3c646c7..1a9774e50 100644 --- a/test/fixtures/python/corpus/delete-statement.parseB.txt +++ b/test/fixtures/python/corpus/delete-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Subscript diff --git a/test/fixtures/python/corpus/dictionary-comprehension.diffA-B.txt b/test/fixtures/python/corpus/dictionary-comprehension.diffA-B.txt index dc0803e7d..0a995c14d 100644 --- a/test/fixtures/python/corpus/dictionary-comprehension.diffA-B.txt +++ b/test/fixtures/python/corpus/dictionary-comprehension.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension (KeyValue { (Identifier) diff --git a/test/fixtures/python/corpus/dictionary-comprehension.diffB-A.txt b/test/fixtures/python/corpus/dictionary-comprehension.diffB-A.txt index 80382a5a3..f0fcdda96 100644 --- a/test/fixtures/python/corpus/dictionary-comprehension.diffB-A.txt +++ b/test/fixtures/python/corpus/dictionary-comprehension.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension (KeyValue { (Identifier) diff --git a/test/fixtures/python/corpus/dictionary-comprehension.parseA.txt b/test/fixtures/python/corpus/dictionary-comprehension.parseA.txt index 49a09e8d8..112c24249 100644 --- a/test/fixtures/python/corpus/dictionary-comprehension.parseA.txt +++ b/test/fixtures/python/corpus/dictionary-comprehension.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension (KeyValue (Identifier) diff --git a/test/fixtures/python/corpus/dictionary-comprehension.parseB.txt b/test/fixtures/python/corpus/dictionary-comprehension.parseB.txt index 51e66945f..9d95fa0cb 100644 --- a/test/fixtures/python/corpus/dictionary-comprehension.parseB.txt +++ b/test/fixtures/python/corpus/dictionary-comprehension.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension (KeyValue (Identifier) diff --git a/test/fixtures/python/corpus/dictionary.diffA-B.txt b/test/fixtures/python/corpus/dictionary.diffA-B.txt index 1f63215b0..ed5106aa5 100644 --- a/test/fixtures/python/corpus/dictionary.diffA-B.txt +++ b/test/fixtures/python/corpus/dictionary.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Hash {+(KeyValue {+(Identifier)+} diff --git a/test/fixtures/python/corpus/dictionary.diffB-A.txt b/test/fixtures/python/corpus/dictionary.diffB-A.txt index 219d99ad5..fb5924954 100644 --- a/test/fixtures/python/corpus/dictionary.diffB-A.txt +++ b/test/fixtures/python/corpus/dictionary.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(Hash {-(KeyValue {-(Identifier)-} diff --git a/test/fixtures/python/corpus/dictionary.parseA.txt b/test/fixtures/python/corpus/dictionary.parseA.txt index 7735051c2..bb9afdff0 100644 --- a/test/fixtures/python/corpus/dictionary.parseA.txt +++ b/test/fixtures/python/corpus/dictionary.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash) (Hash (KeyValue diff --git a/test/fixtures/python/corpus/dictionary.parseB.txt b/test/fixtures/python/corpus/dictionary.parseB.txt index 2ffcd29da..ab1a5246e 100644 --- a/test/fixtures/python/corpus/dictionary.parseB.txt +++ b/test/fixtures/python/corpus/dictionary.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (KeyValue (Identifier) diff --git a/test/fixtures/python/corpus/dotted-name.diffA-B.txt b/test/fixtures/python/corpus/dotted-name.diffA-B.txt index 6612c182f..585a9894a 100644 --- a/test/fixtures/python/corpus/dotted-name.diffA-B.txt +++ b/test/fixtures/python/corpus/dotted-name.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess { (Identifier) ->(MemberAccess diff --git a/test/fixtures/python/corpus/dotted-name.diffB-A.txt b/test/fixtures/python/corpus/dotted-name.diffB-A.txt index 1ad85b8aa..f79f5ff53 100644 --- a/test/fixtures/python/corpus/dotted-name.diffB-A.txt +++ b/test/fixtures/python/corpus/dotted-name.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess { (MemberAccess {-(Identifier)-} diff --git a/test/fixtures/python/corpus/dotted-name.parseA.txt b/test/fixtures/python/corpus/dotted-name.parseA.txt index faab106f1..96ac53b2b 100644 --- a/test/fixtures/python/corpus/dotted-name.parseA.txt +++ b/test/fixtures/python/corpus/dotted-name.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess (Identifier) (Identifier)) diff --git a/test/fixtures/python/corpus/dotted-name.parseB.txt b/test/fixtures/python/corpus/dotted-name.parseB.txt index 0bcbcc68d..8e6cef600 100644 --- a/test/fixtures/python/corpus/dotted-name.parseB.txt +++ b/test/fixtures/python/corpus/dotted-name.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess (MemberAccess (Identifier) diff --git a/test/fixtures/python/corpus/ellipsis.diffA-B.txt b/test/fixtures/python/corpus/ellipsis.diffA-B.txt index 8f748760a..e84ce3e4e 100644 --- a/test/fixtures/python/corpus/ellipsis.diffA-B.txt +++ b/test/fixtures/python/corpus/ellipsis.diffA-B.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Ellipsis) {-(Ellipsis)-}) diff --git a/test/fixtures/python/corpus/ellipsis.diffB-A.txt b/test/fixtures/python/corpus/ellipsis.diffB-A.txt index 522926cc7..1e9d9ae4a 100644 --- a/test/fixtures/python/corpus/ellipsis.diffB-A.txt +++ b/test/fixtures/python/corpus/ellipsis.diffB-A.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Ellipsis) {+(Ellipsis)+}) diff --git a/test/fixtures/python/corpus/ellipsis.parseA.txt b/test/fixtures/python/corpus/ellipsis.parseA.txt index 3f9d9ebac..76b3ebba6 100644 --- a/test/fixtures/python/corpus/ellipsis.parseA.txt +++ b/test/fixtures/python/corpus/ellipsis.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Ellipsis) (Ellipsis)) diff --git a/test/fixtures/python/corpus/ellipsis.parseB.txt b/test/fixtures/python/corpus/ellipsis.parseB.txt index d17f8d8fa..e7209aaaa 100644 --- a/test/fixtures/python/corpus/ellipsis.parseB.txt +++ b/test/fixtures/python/corpus/ellipsis.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Ellipsis)) diff --git a/test/fixtures/python/corpus/exec-statement.diffA-B.txt b/test/fixtures/python/corpus/exec-statement.diffA-B.txt index 70f51f3a8..f51260a9b 100644 --- a/test/fixtures/python/corpus/exec-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/exec-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Call {+(Identifier)+} {+(TextElement)+} diff --git a/test/fixtures/python/corpus/exec-statement.diffB-A.txt b/test/fixtures/python/corpus/exec-statement.diffB-A.txt index 25cb30a7c..278c9efaf 100644 --- a/test/fixtures/python/corpus/exec-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/exec-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Call {+(Identifier)+} {+(TextElement)+} diff --git a/test/fixtures/python/corpus/exec-statement.parseA.txt b/test/fixtures/python/corpus/exec-statement.parseA.txt index d305b08ab..f4c14c4d1 100644 --- a/test/fixtures/python/corpus/exec-statement.parseA.txt +++ b/test/fixtures/python/corpus/exec-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (TextElement) diff --git a/test/fixtures/python/corpus/exec-statement.parseB.txt b/test/fixtures/python/corpus/exec-statement.parseB.txt index df384a38e..588cb9ec0 100644 --- a/test/fixtures/python/corpus/exec-statement.parseB.txt +++ b/test/fixtures/python/corpus/exec-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (TextElement) diff --git a/test/fixtures/python/corpus/expression-statement.diffA-B.txt b/test/fixtures/python/corpus/expression-statement.diffA-B.txt index ea55a1130..e5a55f1d7 100644 --- a/test/fixtures/python/corpus/expression-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/expression-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(Identifier)-} {-(Plus {-(Identifier)-} diff --git a/test/fixtures/python/corpus/expression-statement.diffB-A.txt b/test/fixtures/python/corpus/expression-statement.diffB-A.txt index f4b01c082..e8f9aabd9 100644 --- a/test/fixtures/python/corpus/expression-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/expression-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Identifier)+} {+(Plus {+(Identifier)+} diff --git a/test/fixtures/python/corpus/expression-statement.parseA.txt b/test/fixtures/python/corpus/expression-statement.parseA.txt index c0bc3ce18..847b5a074 100644 --- a/test/fixtures/python/corpus/expression-statement.parseA.txt +++ b/test/fixtures/python/corpus/expression-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Identifier) (Plus (Identifier) diff --git a/test/fixtures/python/corpus/expression-statement.parseB.txt b/test/fixtures/python/corpus/expression-statement.parseB.txt index e93d92934..61e8ba8f1 100644 --- a/test/fixtures/python/corpus/expression-statement.parseB.txt +++ b/test/fixtures/python/corpus/expression-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Statements (Integer) (Integer) diff --git a/test/fixtures/python/corpus/float.diffA-B.txt b/test/fixtures/python/corpus/float.diffA-B.txt index db81ffe15..b45efb022 100644 --- a/test/fixtures/python/corpus/float.diffA-B.txt +++ b/test/fixtures/python/corpus/float.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Negate { (Float) ->(Float) }) diff --git a/test/fixtures/python/corpus/float.diffB-A.txt b/test/fixtures/python/corpus/float.diffB-A.txt index 304dfddef..cec2e6d1b 100644 --- a/test/fixtures/python/corpus/float.diffB-A.txt +++ b/test/fixtures/python/corpus/float.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Negate { (Float) ->(Float) }) diff --git a/test/fixtures/python/corpus/float.parseA.txt b/test/fixtures/python/corpus/float.parseA.txt index ffe9ae0e3..c3cd2858d 100644 --- a/test/fixtures/python/corpus/float.parseA.txt +++ b/test/fixtures/python/corpus/float.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Negate (Float)) (Float) diff --git a/test/fixtures/python/corpus/float.parseB.txt b/test/fixtures/python/corpus/float.parseB.txt index ffe9ae0e3..c3cd2858d 100644 --- a/test/fixtures/python/corpus/float.parseB.txt +++ b/test/fixtures/python/corpus/float.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Negate (Float)) (Float) diff --git a/test/fixtures/python/corpus/for-statement.diffA-B.txt b/test/fixtures/python/corpus/for-statement.diffA-B.txt index 7513a42ec..7249fc231 100644 --- a/test/fixtures/python/corpus/for-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/for-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(ForEach {+(Identifier)+} {+(Array diff --git a/test/fixtures/python/corpus/for-statement.diffB-A.txt b/test/fixtures/python/corpus/for-statement.diffB-A.txt index 19dd5c34f..886ff9387 100644 --- a/test/fixtures/python/corpus/for-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/for-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Else {+(ForEach {+(Statements diff --git a/test/fixtures/python/corpus/for-statement.parseA.txt b/test/fixtures/python/corpus/for-statement.parseA.txt index 59e599336..98ae9a0fe 100644 --- a/test/fixtures/python/corpus/for-statement.parseA.txt +++ b/test/fixtures/python/corpus/for-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Else (ForEach (Statements diff --git a/test/fixtures/python/corpus/for-statement.parseB.txt b/test/fixtures/python/corpus/for-statement.parseB.txt index d48c01f77..ccd3a7212 100644 --- a/test/fixtures/python/corpus/for-statement.parseB.txt +++ b/test/fixtures/python/corpus/for-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForEach (Identifier) (Array diff --git a/test/fixtures/python/corpus/function-definition.diffA-B.txt b/test/fixtures/python/corpus/function-definition.diffA-B.txt index 1858a3b8f..ae299a143 100644 --- a/test/fixtures/python/corpus/function-definition.diffA-B.txt +++ b/test/fixtures/python/corpus/function-definition.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(Annotation {-(Function {-(Identifier)-} diff --git a/test/fixtures/python/corpus/function-definition.diffB-A.txt b/test/fixtures/python/corpus/function-definition.diffB-A.txt index 1edd02066..ffdfecdd1 100644 --- a/test/fixtures/python/corpus/function-definition.diffB-A.txt +++ b/test/fixtures/python/corpus/function-definition.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Annotation (Function { (Identifier) diff --git a/test/fixtures/python/corpus/function-definition.parseA.txt b/test/fixtures/python/corpus/function-definition.parseA.txt index 2725b11ab..d5cb6173f 100644 --- a/test/fixtures/python/corpus/function-definition.parseA.txt +++ b/test/fixtures/python/corpus/function-definition.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Annotation (Function (Identifier) diff --git a/test/fixtures/python/corpus/function-definition.parseB.txt b/test/fixtures/python/corpus/function-definition.parseB.txt index c9507ccb7..27071c200 100644 --- a/test/fixtures/python/corpus/function-definition.parseB.txt +++ b/test/fixtures/python/corpus/function-definition.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Annotation (Function (Identifier) diff --git a/test/fixtures/python/corpus/generator-expression.diffA-B.txt b/test/fixtures/python/corpus/generator-expression.diffA-B.txt index 34837f585..09a31273e 100644 --- a/test/fixtures/python/corpus/generator-expression.diffA-B.txt +++ b/test/fixtures/python/corpus/generator-expression.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension { (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 7cbbefea7..f3362aa15 100644 --- a/test/fixtures/python/corpus/generator-expression.diffB-A.txt +++ b/test/fixtures/python/corpus/generator-expression.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension { (Identifier) ->(Identifier) } diff --git a/test/fixtures/python/corpus/generator-expression.parseA.txt b/test/fixtures/python/corpus/generator-expression.parseA.txt index 926348cdc..ead6841ee 100644 --- a/test/fixtures/python/corpus/generator-expression.parseA.txt +++ b/test/fixtures/python/corpus/generator-expression.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension (Identifier) (Statements diff --git a/test/fixtures/python/corpus/generator-expression.parseB.txt b/test/fixtures/python/corpus/generator-expression.parseB.txt index d5f7c1f64..9afbdfa93 100644 --- a/test/fixtures/python/corpus/generator-expression.parseB.txt +++ b/test/fixtures/python/corpus/generator-expression.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension (Identifier) (Statements diff --git a/test/fixtures/python/corpus/global-statement.diffA-B.txt b/test/fixtures/python/corpus/global-statement.diffA-B.txt index 9485d606f..e825c618e 100644 --- a/test/fixtures/python/corpus/global-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/global-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) {+(Identifier)+} diff --git a/test/fixtures/python/corpus/global-statement.diffB-A.txt b/test/fixtures/python/corpus/global-statement.diffB-A.txt index cf5086530..31548c001 100644 --- a/test/fixtures/python/corpus/global-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/global-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) {-(Identifier)-} diff --git a/test/fixtures/python/corpus/global-statement.parseA.txt b/test/fixtures/python/corpus/global-statement.parseA.txt index 84107fae6..e1dc96503 100644 --- a/test/fixtures/python/corpus/global-statement.parseA.txt +++ b/test/fixtures/python/corpus/global-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/global-statement.parseB.txt b/test/fixtures/python/corpus/global-statement.parseB.txt index 04a22e553..3f92988c5 100644 --- a/test/fixtures/python/corpus/global-statement.parseB.txt +++ b/test/fixtures/python/corpus/global-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/identifier.diffA-B.txt b/test/fixtures/python/corpus/identifier.diffA-B.txt index e16d74e6a..b8a308641 100644 --- a/test/fixtures/python/corpus/identifier.diffA-B.txt +++ b/test/fixtures/python/corpus/identifier.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Identifier) ->(Identifier) } {+(Identifier)+}) diff --git a/test/fixtures/python/corpus/identifier.diffB-A.txt b/test/fixtures/python/corpus/identifier.diffB-A.txt index b35673ab9..f20ec58a9 100644 --- a/test/fixtures/python/corpus/identifier.diffB-A.txt +++ b/test/fixtures/python/corpus/identifier.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Identifier) ->(Identifier) } {-(Identifier)-}) diff --git a/test/fixtures/python/corpus/identifier.parseA.txt b/test/fixtures/python/corpus/identifier.parseA.txt index 67b75f388..5f0ab64c1 100644 --- a/test/fixtures/python/corpus/identifier.parseA.txt +++ b/test/fixtures/python/corpus/identifier.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Identifier)) diff --git a/test/fixtures/python/corpus/identifier.parseB.txt b/test/fixtures/python/corpus/identifier.parseB.txt index 1002352c1..8aac190e1 100644 --- a/test/fixtures/python/corpus/identifier.parseB.txt +++ b/test/fixtures/python/corpus/identifier.parseB.txt @@ -1,3 +1,3 @@ -(Program +(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 73708da79..e6ee07be7 100644 --- a/test/fixtures/python/corpus/if-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/if-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If { (Identifier) ->(Identifier) } diff --git a/test/fixtures/python/corpus/if-statement.diffB-A.txt b/test/fixtures/python/corpus/if-statement.diffB-A.txt index c604cad8a..49ac3de8b 100644 --- a/test/fixtures/python/corpus/if-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/if-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If { (Identifier) ->(Identifier) } diff --git a/test/fixtures/python/corpus/if-statement.parseA.txt b/test/fixtures/python/corpus/if-statement.parseA.txt index 97223d23b..5c119db77 100644 --- a/test/fixtures/python/corpus/if-statement.parseA.txt +++ b/test/fixtures/python/corpus/if-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Identifier) (Statements diff --git a/test/fixtures/python/corpus/if-statement.parseB.txt b/test/fixtures/python/corpus/if-statement.parseB.txt index 14179ed8a..b289f3fe5 100644 --- a/test/fixtures/python/corpus/if-statement.parseB.txt +++ b/test/fixtures/python/corpus/if-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Identifier) (Statements diff --git a/test/fixtures/python/corpus/import-from-statement.diffA-B.txt b/test/fixtures/python/corpus/import-from-statement.diffA-B.txt index 53c9173af..707005652 100644 --- a/test/fixtures/python/corpus/import-from-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/import-from-statement.diffA-B.txt @@ -1,12 +1,12 @@ -(Program +(Statements {+(Import)+} -{ (Import) -->(Import) } {+(Import)+} {+(Import)+} {+(Import)+} { (Import) ->(Import) } +{+(Import)+} +{-(Import)-} {-(Import)-} {-(Import)-} {-(Import)-}) diff --git a/test/fixtures/python/corpus/import-from-statement.diffB-A.txt b/test/fixtures/python/corpus/import-from-statement.diffB-A.txt index 0daabb2ab..691652350 100644 --- a/test/fixtures/python/corpus/import-from-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/import-from-statement.diffB-A.txt @@ -1,10 +1,10 @@ -(Program -{+(Import)+} -{ (Import) -->(Import) } +(Statements {+(Import)+} {+(Import)+} {+(Import)+} +{+(Import)+} +{+(Import)+} +{-(Import)-} {-(Import)-} {-(Import)-} {-(Import)-} diff --git a/test/fixtures/python/corpus/import-from-statement.parseA.txt b/test/fixtures/python/corpus/import-from-statement.parseA.txt index f2e8736da..510bca55c 100644 --- a/test/fixtures/python/corpus/import-from-statement.parseA.txt +++ b/test/fixtures/python/corpus/import-from-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Import) (Import) (Import) diff --git a/test/fixtures/python/corpus/import-from-statement.parseB.txt b/test/fixtures/python/corpus/import-from-statement.parseB.txt index 4b21a908e..d6f817026 100644 --- a/test/fixtures/python/corpus/import-from-statement.parseB.txt +++ b/test/fixtures/python/corpus/import-from-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Import) (Import) (Import) diff --git a/test/fixtures/python/corpus/import-statement.diffA-B.txt b/test/fixtures/python/corpus/import-statement.diffA-B.txt index b6263e2ee..2c386e960 100644 --- a/test/fixtures/python/corpus/import-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/import-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Statements {+(QualifiedImport)+} (QualifiedImport) diff --git a/test/fixtures/python/corpus/import-statement.diffB-A.txt b/test/fixtures/python/corpus/import-statement.diffB-A.txt index 66546a122..463fd0d8a 100644 --- a/test/fixtures/python/corpus/import-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/import-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Statements {-(QualifiedImport)-} (QualifiedImport) diff --git a/test/fixtures/python/corpus/import-statement.parseA.txt b/test/fixtures/python/corpus/import-statement.parseA.txt index cd5a2f551..a9d6a1fae 100644 --- a/test/fixtures/python/corpus/import-statement.parseA.txt +++ b/test/fixtures/python/corpus/import-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Statements (QualifiedImport) (QualifiedAliasedImport diff --git a/test/fixtures/python/corpus/import-statement.parseB.txt b/test/fixtures/python/corpus/import-statement.parseB.txt index ff6acffe2..85547b552 100644 --- a/test/fixtures/python/corpus/import-statement.parseB.txt +++ b/test/fixtures/python/corpus/import-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Statements (QualifiedImport) (QualifiedImport)) diff --git a/test/fixtures/python/corpus/integer.diffA-B.txt b/test/fixtures/python/corpus/integer.diffA-B.txt index 2b582e9e5..d1cfb8f5e 100644 --- a/test/fixtures/python/corpus/integer.diffA-B.txt +++ b/test/fixtures/python/corpus/integer.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Negate { (Integer) ->(Integer) }) diff --git a/test/fixtures/python/corpus/integer.diffB-A.txt b/test/fixtures/python/corpus/integer.diffB-A.txt index 2468ca1f1..bda594203 100644 --- a/test/fixtures/python/corpus/integer.diffB-A.txt +++ b/test/fixtures/python/corpus/integer.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Negate { (Integer) ->(Integer) }) diff --git a/test/fixtures/python/corpus/integer.parseA.txt b/test/fixtures/python/corpus/integer.parseA.txt index 1741f3139..d8be2686b 100644 --- a/test/fixtures/python/corpus/integer.parseA.txt +++ b/test/fixtures/python/corpus/integer.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Negate (Integer)) (Integer) diff --git a/test/fixtures/python/corpus/integer.parseB.txt b/test/fixtures/python/corpus/integer.parseB.txt index 1741f3139..d8be2686b 100644 --- a/test/fixtures/python/corpus/integer.parseB.txt +++ b/test/fixtures/python/corpus/integer.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Negate (Integer)) (Integer) diff --git a/test/fixtures/python/corpus/keyword-identifier.diffA-B.txt b/test/fixtures/python/corpus/keyword-identifier.diffA-B.txt index c76e21f67..5081651ba 100644 --- a/test/fixtures/python/corpus/keyword-identifier.diffA-B.txt +++ b/test/fixtures/python/corpus/keyword-identifier.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(Identifier)-} (Identifier) {+(Identifier)+}) diff --git a/test/fixtures/python/corpus/keyword-identifier.diffB-A.txt b/test/fixtures/python/corpus/keyword-identifier.diffB-A.txt index c76e21f67..5081651ba 100644 --- a/test/fixtures/python/corpus/keyword-identifier.diffB-A.txt +++ b/test/fixtures/python/corpus/keyword-identifier.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(Identifier)-} (Identifier) {+(Identifier)+}) diff --git a/test/fixtures/python/corpus/keyword-identifier.parseA.txt b/test/fixtures/python/corpus/keyword-identifier.parseA.txt index 1002352c1..8aac190e1 100644 --- a/test/fixtures/python/corpus/keyword-identifier.parseA.txt +++ b/test/fixtures/python/corpus/keyword-identifier.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Identifier) (Identifier)) diff --git a/test/fixtures/python/corpus/keyword-identifier.parseB.txt b/test/fixtures/python/corpus/keyword-identifier.parseB.txt index 1002352c1..8aac190e1 100644 --- a/test/fixtures/python/corpus/keyword-identifier.parseB.txt +++ b/test/fixtures/python/corpus/keyword-identifier.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Identifier) (Identifier)) diff --git a/test/fixtures/python/corpus/lambda.diffA-B.txt b/test/fixtures/python/corpus/lambda.diffA-B.txt index 0c5631fd5..2ce004746 100644 --- a/test/fixtures/python/corpus/lambda.diffA-B.txt +++ b/test/fixtures/python/corpus/lambda.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Annotation (Function (Empty) diff --git a/test/fixtures/python/corpus/lambda.diffB-A.txt b/test/fixtures/python/corpus/lambda.diffB-A.txt index bed42b97e..61334f517 100644 --- a/test/fixtures/python/corpus/lambda.diffB-A.txt +++ b/test/fixtures/python/corpus/lambda.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Annotation (Function (Empty) diff --git a/test/fixtures/python/corpus/lambda.parseA.txt b/test/fixtures/python/corpus/lambda.parseA.txt index 3cc3af09a..7743aab52 100644 --- a/test/fixtures/python/corpus/lambda.parseA.txt +++ b/test/fixtures/python/corpus/lambda.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Annotation (Function (Empty) diff --git a/test/fixtures/python/corpus/lambda.parseB.txt b/test/fixtures/python/corpus/lambda.parseB.txt index bab436fe7..863d7cb17 100644 --- a/test/fixtures/python/corpus/lambda.parseB.txt +++ b/test/fixtures/python/corpus/lambda.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Annotation (Function (Empty) diff --git a/test/fixtures/python/corpus/list-comprehension.diffA-B.txt b/test/fixtures/python/corpus/list-comprehension.diffA-B.txt index a47830074..c42289ed3 100644 --- a/test/fixtures/python/corpus/list-comprehension.diffA-B.txt +++ b/test/fixtures/python/corpus/list-comprehension.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension { (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 fc4c064af..5a6999be5 100644 --- a/test/fixtures/python/corpus/list-comprehension.diffB-A.txt +++ b/test/fixtures/python/corpus/list-comprehension.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension { (Identifier) ->(Identifier) } diff --git a/test/fixtures/python/corpus/list-comprehension.parseA.txt b/test/fixtures/python/corpus/list-comprehension.parseA.txt index 927e76638..669c723df 100644 --- a/test/fixtures/python/corpus/list-comprehension.parseA.txt +++ b/test/fixtures/python/corpus/list-comprehension.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension (Identifier) (Statements diff --git a/test/fixtures/python/corpus/list-comprehension.parseB.txt b/test/fixtures/python/corpus/list-comprehension.parseB.txt index 59256c488..fcddcd1b9 100644 --- a/test/fixtures/python/corpus/list-comprehension.parseB.txt +++ b/test/fixtures/python/corpus/list-comprehension.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension (Identifier) (Statements diff --git a/test/fixtures/python/corpus/list.diffA-B.txt b/test/fixtures/python/corpus/list.diffA-B.txt index 98d27a18f..39f11b37b 100644 --- a/test/fixtures/python/corpus/list.diffA-B.txt +++ b/test/fixtures/python/corpus/list.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array {+(Identifier)+}) (Array diff --git a/test/fixtures/python/corpus/list.diffB-A.txt b/test/fixtures/python/corpus/list.diffB-A.txt index 0eedc09eb..0468d70b9 100644 --- a/test/fixtures/python/corpus/list.diffB-A.txt +++ b/test/fixtures/python/corpus/list.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array {-(Identifier)-}) (Array diff --git a/test/fixtures/python/corpus/list.parseA.txt b/test/fixtures/python/corpus/list.parseA.txt index cd8c64524..8d9030127 100644 --- a/test/fixtures/python/corpus/list.parseA.txt +++ b/test/fixtures/python/corpus/list.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array) (Array (Integer) diff --git a/test/fixtures/python/corpus/list.parseB.txt b/test/fixtures/python/corpus/list.parseB.txt index 81b55aec9..b8b3d71a9 100644 --- a/test/fixtures/python/corpus/list.parseB.txt +++ b/test/fixtures/python/corpus/list.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array (Identifier)) (Array diff --git a/test/fixtures/python/corpus/non-local-statement.diffA-B.txt b/test/fixtures/python/corpus/non-local-statement.diffA-B.txt index b0e558bc3..a8b76704c 100644 --- a/test/fixtures/python/corpus/non-local-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/non-local-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/python/corpus/non-local-statement.diffB-A.txt b/test/fixtures/python/corpus/non-local-statement.diffB-A.txt index b0e558bc3..a8b76704c 100644 --- a/test/fixtures/python/corpus/non-local-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/non-local-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) { (Identifier) diff --git a/test/fixtures/python/corpus/non-local-statement.parseA.txt b/test/fixtures/python/corpus/non-local-statement.parseA.txt index 8c6420c8a..3e6149a15 100644 --- a/test/fixtures/python/corpus/non-local-statement.parseA.txt +++ b/test/fixtures/python/corpus/non-local-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/non-local-statement.parseB.txt b/test/fixtures/python/corpus/non-local-statement.parseB.txt index 8c6420c8a..3e6149a15 100644 --- a/test/fixtures/python/corpus/non-local-statement.parseB.txt +++ b/test/fixtures/python/corpus/non-local-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/none.diffA-B.txt b/test/fixtures/python/corpus/none.diffA-B.txt index 15408d92c..2006c5a73 100644 --- a/test/fixtures/python/corpus/none.diffA-B.txt +++ b/test/fixtures/python/corpus/none.diffA-B.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Null) {-(Null)-}) diff --git a/test/fixtures/python/corpus/none.diffB-A.txt b/test/fixtures/python/corpus/none.diffB-A.txt index 63cb0320e..a769a6399 100644 --- a/test/fixtures/python/corpus/none.diffB-A.txt +++ b/test/fixtures/python/corpus/none.diffB-A.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Null) {+(Null)+}) diff --git a/test/fixtures/python/corpus/none.parseA.txt b/test/fixtures/python/corpus/none.parseA.txt index 1d7363fea..4af9c5927 100644 --- a/test/fixtures/python/corpus/none.parseA.txt +++ b/test/fixtures/python/corpus/none.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Null) (Null)) diff --git a/test/fixtures/python/corpus/none.parseB.txt b/test/fixtures/python/corpus/none.parseB.txt index d6499ddef..5c722556e 100644 --- a/test/fixtures/python/corpus/none.parseB.txt +++ b/test/fixtures/python/corpus/none.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Null)) diff --git a/test/fixtures/python/corpus/not.diffA-B.txt b/test/fixtures/python/corpus/not.diffA-B.txt index d33587836..78afc4a9b 100644 --- a/test/fixtures/python/corpus/not.diffA-B.txt +++ b/test/fixtures/python/corpus/not.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Not { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/python/corpus/not.diffB-A.txt b/test/fixtures/python/corpus/not.diffB-A.txt index eff337a9b..24fcbd97c 100644 --- a/test/fixtures/python/corpus/not.diffB-A.txt +++ b/test/fixtures/python/corpus/not.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Not { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/python/corpus/not.parseA.txt b/test/fixtures/python/corpus/not.parseA.txt index ba7207ca8..2aac4ecc8 100644 --- a/test/fixtures/python/corpus/not.parseA.txt +++ b/test/fixtures/python/corpus/not.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Not (Identifier))) diff --git a/test/fixtures/python/corpus/not.parseB.txt b/test/fixtures/python/corpus/not.parseB.txt index 26535be9e..8a8d2c144 100644 --- a/test/fixtures/python/corpus/not.parseB.txt +++ b/test/fixtures/python/corpus/not.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Not (Identifier)) (Not diff --git a/test/fixtures/python/corpus/pass-statement.diffA-B.txt b/test/fixtures/python/corpus/pass-statement.diffA-B.txt index 51a32360d..ff8ff9320 100644 --- a/test/fixtures/python/corpus/pass-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/pass-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (NoOp (Empty)) {+(NoOp diff --git a/test/fixtures/python/corpus/pass-statement.diffB-A.txt b/test/fixtures/python/corpus/pass-statement.diffB-A.txt index 057a3e8dc..ef1a562ab 100644 --- a/test/fixtures/python/corpus/pass-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/pass-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (NoOp (Empty)) {-(NoOp diff --git a/test/fixtures/python/corpus/pass-statement.parseA.txt b/test/fixtures/python/corpus/pass-statement.parseA.txt index 71624e145..acbee74d6 100644 --- a/test/fixtures/python/corpus/pass-statement.parseA.txt +++ b/test/fixtures/python/corpus/pass-statement.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (NoOp (Empty))) diff --git a/test/fixtures/python/corpus/pass-statement.parseB.txt b/test/fixtures/python/corpus/pass-statement.parseB.txt index cc7e642c3..ce27612bd 100644 --- a/test/fixtures/python/corpus/pass-statement.parseB.txt +++ b/test/fixtures/python/corpus/pass-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (NoOp (Empty)) (NoOp diff --git a/test/fixtures/python/corpus/print-statement.diffA-B.txt b/test/fixtures/python/corpus/print-statement.diffA-B.txt index 0ba7ad0ba..18c6765ce 100644 --- a/test/fixtures/python/corpus/print-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/print-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) {+(Identifier)+} diff --git a/test/fixtures/python/corpus/print-statement.diffB-A.txt b/test/fixtures/python/corpus/print-statement.diffB-A.txt index 9a797a52d..8a64fc3f3 100644 --- a/test/fixtures/python/corpus/print-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/print-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) {-(Identifier)-} diff --git a/test/fixtures/python/corpus/print-statement.parseA.txt b/test/fixtures/python/corpus/print-statement.parseA.txt index 78f451d79..dc1c75d2f 100644 --- a/test/fixtures/python/corpus/print-statement.parseA.txt +++ b/test/fixtures/python/corpus/print-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/print-statement.parseB.txt b/test/fixtures/python/corpus/print-statement.parseB.txt index 78f451d79..dc1c75d2f 100644 --- a/test/fixtures/python/corpus/print-statement.parseB.txt +++ b/test/fixtures/python/corpus/print-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (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 a05bf8019..f2adf4cd5 100644 --- a/test/fixtures/python/corpus/raise-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/raise-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Throw {+(Call {+(Identifier)+} diff --git a/test/fixtures/python/corpus/raise-statement.diffB-A.txt b/test/fixtures/python/corpus/raise-statement.diffB-A.txt index 2217380cb..49186a822 100644 --- a/test/fixtures/python/corpus/raise-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/raise-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(Throw {-(Call {-(Identifier)-} diff --git a/test/fixtures/python/corpus/raise-statement.parseA.txt b/test/fixtures/python/corpus/raise-statement.parseA.txt index c3f6865e0..b0ee65fa0 100644 --- a/test/fixtures/python/corpus/raise-statement.parseA.txt +++ b/test/fixtures/python/corpus/raise-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Throw (Statements)) (Throw diff --git a/test/fixtures/python/corpus/raise-statement.parseB.txt b/test/fixtures/python/corpus/raise-statement.parseB.txt index 2f21ece90..b6730223e 100644 --- a/test/fixtures/python/corpus/raise-statement.parseB.txt +++ b/test/fixtures/python/corpus/raise-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Throw (Call (Identifier) diff --git a/test/fixtures/python/corpus/return-statement.diffA-B.txt b/test/fixtures/python/corpus/return-statement.diffA-B.txt index b346595d2..41d698d2a 100644 --- a/test/fixtures/python/corpus/return-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/return-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Return {+(Statements {+(Plus diff --git a/test/fixtures/python/corpus/return-statement.diffB-A.txt b/test/fixtures/python/corpus/return-statement.diffB-A.txt index 44783eaaa..fc41dede9 100644 --- a/test/fixtures/python/corpus/return-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/return-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(Return {-(Statements {-(Plus diff --git a/test/fixtures/python/corpus/return-statement.parseA.txt b/test/fixtures/python/corpus/return-statement.parseA.txt index 581590159..cd8b4535c 100644 --- a/test/fixtures/python/corpus/return-statement.parseA.txt +++ b/test/fixtures/python/corpus/return-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return (Empty)) (Return diff --git a/test/fixtures/python/corpus/return-statement.parseB.txt b/test/fixtures/python/corpus/return-statement.parseB.txt index bf6bee6ed..86edac90a 100644 --- a/test/fixtures/python/corpus/return-statement.parseB.txt +++ b/test/fixtures/python/corpus/return-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return (Statements (Plus diff --git a/test/fixtures/python/corpus/set-comprehension.diffA-B.txt b/test/fixtures/python/corpus/set-comprehension.diffA-B.txt index 34837f585..09a31273e 100644 --- a/test/fixtures/python/corpus/set-comprehension.diffA-B.txt +++ b/test/fixtures/python/corpus/set-comprehension.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension { (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 7cbbefea7..f3362aa15 100644 --- a/test/fixtures/python/corpus/set-comprehension.diffB-A.txt +++ b/test/fixtures/python/corpus/set-comprehension.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension { (Identifier) ->(Identifier) } diff --git a/test/fixtures/python/corpus/set-comprehension.parseA.txt b/test/fixtures/python/corpus/set-comprehension.parseA.txt index 926348cdc..ead6841ee 100644 --- a/test/fixtures/python/corpus/set-comprehension.parseA.txt +++ b/test/fixtures/python/corpus/set-comprehension.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension (Identifier) (Statements diff --git a/test/fixtures/python/corpus/set-comprehension.parseB.txt b/test/fixtures/python/corpus/set-comprehension.parseB.txt index d5f7c1f64..9afbdfa93 100644 --- a/test/fixtures/python/corpus/set-comprehension.parseB.txt +++ b/test/fixtures/python/corpus/set-comprehension.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comprehension (Identifier) (Statements diff --git a/test/fixtures/python/corpus/set.diffA-B.txt b/test/fixtures/python/corpus/set.diffA-B.txt index 8226f9c7e..1014b0eea 100644 --- a/test/fixtures/python/corpus/set.diffA-B.txt +++ b/test/fixtures/python/corpus/set.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Set {+(Integer)+})+} {+(Set diff --git a/test/fixtures/python/corpus/set.diffB-A.txt b/test/fixtures/python/corpus/set.diffB-A.txt index 430c4a5e8..8e84f3a70 100644 --- a/test/fixtures/python/corpus/set.diffB-A.txt +++ b/test/fixtures/python/corpus/set.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Hash)+} (Set (Integer) diff --git a/test/fixtures/python/corpus/set.parseA.txt b/test/fixtures/python/corpus/set.parseA.txt index d27462208..a34a7adcd 100644 --- a/test/fixtures/python/corpus/set.parseA.txt +++ b/test/fixtures/python/corpus/set.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash) (Set (Integer) diff --git a/test/fixtures/python/corpus/set.parseB.txt b/test/fixtures/python/corpus/set.parseB.txt index 73c4a2cba..2ca89b7cd 100644 --- a/test/fixtures/python/corpus/set.parseB.txt +++ b/test/fixtures/python/corpus/set.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Set (Integer)) (Set diff --git a/test/fixtures/python/corpus/slice.diffA-B.txt b/test/fixtures/python/corpus/slice.diffA-B.txt index 9c8359760..8dc202bf8 100644 --- a/test/fixtures/python/corpus/slice.diffA-B.txt +++ b/test/fixtures/python/corpus/slice.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Subscript {+(Identifier)+} {+(Enumeration diff --git a/test/fixtures/python/corpus/slice.diffB-A.txt b/test/fixtures/python/corpus/slice.diffB-A.txt index ca1727a92..4a0e0a245 100644 --- a/test/fixtures/python/corpus/slice.diffB-A.txt +++ b/test/fixtures/python/corpus/slice.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(Subscript {-(Identifier)-} {-(Enumeration diff --git a/test/fixtures/python/corpus/slice.parseA.txt b/test/fixtures/python/corpus/slice.parseA.txt index 00c917b88..bca8cd11b 100644 --- a/test/fixtures/python/corpus/slice.parseA.txt +++ b/test/fixtures/python/corpus/slice.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) (Enumeration diff --git a/test/fixtures/python/corpus/slice.parseB.txt b/test/fixtures/python/corpus/slice.parseB.txt index 86e99a046..aee117b12 100644 --- a/test/fixtures/python/corpus/slice.parseB.txt +++ b/test/fixtures/python/corpus/slice.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) (Enumeration diff --git a/test/fixtures/python/corpus/string.diffA-B.txt b/test/fixtures/python/corpus/string.diffA-B.txt index 9cf35b73f..5a04148c9 100644 --- a/test/fixtures/python/corpus/string.diffA-B.txt +++ b/test/fixtures/python/corpus/string.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(TextElement)+} (TextElement) {+(TextElement)+} diff --git a/test/fixtures/python/corpus/string.diffB-A.txt b/test/fixtures/python/corpus/string.diffB-A.txt index f96350334..e13f561f3 100644 --- a/test/fixtures/python/corpus/string.diffB-A.txt +++ b/test/fixtures/python/corpus/string.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(TextElement)-} (TextElement) {+(TextElement)+} diff --git a/test/fixtures/python/corpus/string.parseA.txt b/test/fixtures/python/corpus/string.parseA.txt index 576378c44..f7fef4dfe 100644 --- a/test/fixtures/python/corpus/string.parseA.txt +++ b/test/fixtures/python/corpus/string.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (TextElement) (TextElement) (TextElement) diff --git a/test/fixtures/python/corpus/string.parseB.txt b/test/fixtures/python/corpus/string.parseB.txt index a73b5ae21..9d589ddfd 100644 --- a/test/fixtures/python/corpus/string.parseB.txt +++ b/test/fixtures/python/corpus/string.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (TextElement) (TextElement) (TextElement) diff --git a/test/fixtures/python/corpus/subscript.diffA-B.txt b/test/fixtures/python/corpus/subscript.diffA-B.txt index 2598bfe20..aeebfe854 100644 --- a/test/fixtures/python/corpus/subscript.diffA-B.txt +++ b/test/fixtures/python/corpus/subscript.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript { (Identifier) ->(Identifier) } diff --git a/test/fixtures/python/corpus/subscript.diffB-A.txt b/test/fixtures/python/corpus/subscript.diffB-A.txt index 2598bfe20..aeebfe854 100644 --- a/test/fixtures/python/corpus/subscript.diffB-A.txt +++ b/test/fixtures/python/corpus/subscript.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript { (Identifier) ->(Identifier) } diff --git a/test/fixtures/python/corpus/subscript.parseA.txt b/test/fixtures/python/corpus/subscript.parseA.txt index d51465cb0..e2c7fbd55 100644 --- a/test/fixtures/python/corpus/subscript.parseA.txt +++ b/test/fixtures/python/corpus/subscript.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) (Identifier))) diff --git a/test/fixtures/python/corpus/subscript.parseB.txt b/test/fixtures/python/corpus/subscript.parseB.txt index d51465cb0..e2c7fbd55 100644 --- a/test/fixtures/python/corpus/subscript.parseB.txt +++ b/test/fixtures/python/corpus/subscript.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (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 386b10bc4..4c2a4f4d7 100644 --- a/test/fixtures/python/corpus/try-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/try-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try { (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 6505dab19..ccfc1525f 100644 --- a/test/fixtures/python/corpus/try-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/try-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try { (Identifier) ->(Identifier) } diff --git a/test/fixtures/python/corpus/try-statement.parseA.txt b/test/fixtures/python/corpus/try-statement.parseA.txt index 57f428a7f..6b6385b0a 100644 --- a/test/fixtures/python/corpus/try-statement.parseA.txt +++ b/test/fixtures/python/corpus/try-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/try-statement.parseB.txt b/test/fixtures/python/corpus/try-statement.parseB.txt index 1eefadf9b..6a18c7a54 100644 --- a/test/fixtures/python/corpus/try-statement.parseB.txt +++ b/test/fixtures/python/corpus/try-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Identifier) (Finally diff --git a/test/fixtures/python/corpus/tuple.diffA-B.txt b/test/fixtures/python/corpus/tuple.diffA-B.txt index d0fdb2952..d11ebeb95 100644 --- a/test/fixtures/python/corpus/tuple.diffA-B.txt +++ b/test/fixtures/python/corpus/tuple.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Tuple {-(Identifier)-} (Identifier) diff --git a/test/fixtures/python/corpus/tuple.diffB-A.txt b/test/fixtures/python/corpus/tuple.diffB-A.txt index 2418ffb6a..0128e9b42 100644 --- a/test/fixtures/python/corpus/tuple.diffB-A.txt +++ b/test/fixtures/python/corpus/tuple.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Tuple {-(Identifier)-} {-(Identifier)-} diff --git a/test/fixtures/python/corpus/tuple.parseA.txt b/test/fixtures/python/corpus/tuple.parseA.txt index f935830d8..22c207c41 100644 --- a/test/fixtures/python/corpus/tuple.parseA.txt +++ b/test/fixtures/python/corpus/tuple.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Tuple (Identifier) (Identifier)) diff --git a/test/fixtures/python/corpus/tuple.parseB.txt b/test/fixtures/python/corpus/tuple.parseB.txt index fb142601c..0cf31e5b2 100644 --- a/test/fixtures/python/corpus/tuple.parseB.txt +++ b/test/fixtures/python/corpus/tuple.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Tuple (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/unary-operator.diffA-B.txt b/test/fixtures/python/corpus/unary-operator.diffA-B.txt index d6e01087b..59a51dbb9 100644 --- a/test/fixtures/python/corpus/unary-operator.diffA-B.txt +++ b/test/fixtures/python/corpus/unary-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Complement {+(Identifier)+})+} (Negate diff --git a/test/fixtures/python/corpus/unary-operator.diffB-A.txt b/test/fixtures/python/corpus/unary-operator.diffB-A.txt index f339844f8..a0086cd4b 100644 --- a/test/fixtures/python/corpus/unary-operator.diffB-A.txt +++ b/test/fixtures/python/corpus/unary-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Negate {+(Identifier)+})+} {+(Identifier)+} diff --git a/test/fixtures/python/corpus/unary-operator.parseA.txt b/test/fixtures/python/corpus/unary-operator.parseA.txt index 1f12cb383..e92f638ae 100644 --- a/test/fixtures/python/corpus/unary-operator.parseA.txt +++ b/test/fixtures/python/corpus/unary-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Negate (Identifier)) (Identifier) diff --git a/test/fixtures/python/corpus/unary-operator.parseB.txt b/test/fixtures/python/corpus/unary-operator.parseB.txt index 4fc5fea1c..f3d6e2da6 100644 --- a/test/fixtures/python/corpus/unary-operator.parseB.txt +++ b/test/fixtures/python/corpus/unary-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Complement (Identifier)) (Negate diff --git a/test/fixtures/python/corpus/while-statement.diffA-B.txt b/test/fixtures/python/corpus/while-statement.diffA-B.txt index 29439f949..57262fafc 100644 --- a/test/fixtures/python/corpus/while-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/while-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While { (Identifier) ->(Identifier) } diff --git a/test/fixtures/python/corpus/while-statement.diffB-A.txt b/test/fixtures/python/corpus/while-statement.diffB-A.txt index 8fde658c7..5cead7f7d 100644 --- a/test/fixtures/python/corpus/while-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/while-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While { (Identifier) ->(Identifier) } diff --git a/test/fixtures/python/corpus/while-statement.parseA.txt b/test/fixtures/python/corpus/while-statement.parseA.txt index bdfdc70cc..f8687d813 100644 --- a/test/fixtures/python/corpus/while-statement.parseA.txt +++ b/test/fixtures/python/corpus/while-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Identifier) (Statements diff --git a/test/fixtures/python/corpus/while-statement.parseB.txt b/test/fixtures/python/corpus/while-statement.parseB.txt index 05289b27e..a6059e837 100644 --- a/test/fixtures/python/corpus/while-statement.parseB.txt +++ b/test/fixtures/python/corpus/while-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Identifier) (Statements diff --git a/test/fixtures/python/corpus/with-statement.diffA-B.txt b/test/fixtures/python/corpus/with-statement.diffA-B.txt index aad270979..eb79b9464 100644 --- a/test/fixtures/python/corpus/with-statement.diffA-B.txt +++ b/test/fixtures/python/corpus/with-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Let { (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 aad270979..eb79b9464 100644 --- a/test/fixtures/python/corpus/with-statement.diffB-A.txt +++ b/test/fixtures/python/corpus/with-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Let { (Identifier) ->(Identifier) } diff --git a/test/fixtures/python/corpus/with-statement.parseA.txt b/test/fixtures/python/corpus/with-statement.parseA.txt index bc2fe3e49..b5a13bb95 100644 --- a/test/fixtures/python/corpus/with-statement.parseA.txt +++ b/test/fixtures/python/corpus/with-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Let (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/with-statement.parseB.txt b/test/fixtures/python/corpus/with-statement.parseB.txt index bc2fe3e49..b5a13bb95 100644 --- a/test/fixtures/python/corpus/with-statement.parseB.txt +++ b/test/fixtures/python/corpus/with-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Let (Identifier) (Identifier) diff --git a/test/fixtures/python/corpus/with.diffA-B.txt b/test/fixtures/python/corpus/with.diffA-B.txt index 201cc0ac9..907193ef5 100644 --- a/test/fixtures/python/corpus/with.diffA-B.txt +++ b/test/fixtures/python/corpus/with.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Let { (Identifier) ->(Empty) } diff --git a/test/fixtures/python/corpus/with.diffB-A.txt b/test/fixtures/python/corpus/with.diffB-A.txt index 0171c4924..845718ee1 100644 --- a/test/fixtures/python/corpus/with.diffB-A.txt +++ b/test/fixtures/python/corpus/with.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Let { (Empty) ->(Identifier) } diff --git a/test/fixtures/python/corpus/with.parseA.txt b/test/fixtures/python/corpus/with.parseA.txt index edc854479..43c0db99e 100644 --- a/test/fixtures/python/corpus/with.parseA.txt +++ b/test/fixtures/python/corpus/with.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Let (Identifier) (Call diff --git a/test/fixtures/python/corpus/with.parseB.txt b/test/fixtures/python/corpus/with.parseB.txt index 23dcb54a1..dcd325629 100644 --- a/test/fixtures/python/corpus/with.parseB.txt +++ b/test/fixtures/python/corpus/with.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Let (Empty) (MemberAccess diff --git a/test/fixtures/python/corpus/yield.diffA-B.txt b/test/fixtures/python/corpus/yield.diffA-B.txt index cd88626a7..30b540d27 100644 --- a/test/fixtures/python/corpus/yield.diffA-B.txt +++ b/test/fixtures/python/corpus/yield.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Yield (Empty)) {+(Yield diff --git a/test/fixtures/python/corpus/yield.diffB-A.txt b/test/fixtures/python/corpus/yield.diffB-A.txt index f4ba57152..578e8045f 100644 --- a/test/fixtures/python/corpus/yield.diffB-A.txt +++ b/test/fixtures/python/corpus/yield.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Yield (Empty)) {-(Yield diff --git a/test/fixtures/python/corpus/yield.parseA.txt b/test/fixtures/python/corpus/yield.parseA.txt index b8748d919..8663d7d6f 100644 --- a/test/fixtures/python/corpus/yield.parseA.txt +++ b/test/fixtures/python/corpus/yield.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Yield (Empty))) diff --git a/test/fixtures/python/corpus/yield.parseB.txt b/test/fixtures/python/corpus/yield.parseB.txt index 65ec948aa..0f843e453 100644 --- a/test/fixtures/python/corpus/yield.parseB.txt +++ b/test/fixtures/python/corpus/yield.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Yield (Empty)) (Yield diff --git a/test/fixtures/ruby/corpus/alias.parseA.txt b/test/fixtures/ruby/corpus/alias.parseA.txt index 27cc8cba6..69731d50a 100644 --- a/test/fixtures/ruby/corpus/alias.parseA.txt +++ b/test/fixtures/ruby/corpus/alias.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Symbol) diff --git a/test/fixtures/ruby/corpus/and-or.diffA-B.txt b/test/fixtures/ruby/corpus/and-or.diffA-B.txt index 59064ebaa..6001a69d8 100644 --- a/test/fixtures/ruby/corpus/and-or.diffA-B.txt +++ b/test/fixtures/ruby/corpus/and-or.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(LowOr {+(Send {+(Identifier)+})+} diff --git a/test/fixtures/ruby/corpus/and-or.diffB-A.txt b/test/fixtures/ruby/corpus/and-or.diffB-A.txt index 1373e5c10..e594e31db 100644 --- a/test/fixtures/ruby/corpus/and-or.diffB-A.txt +++ b/test/fixtures/ruby/corpus/and-or.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(LowAnd {+(Send {+(Identifier)+})+} diff --git a/test/fixtures/ruby/corpus/and-or.parseA.txt b/test/fixtures/ruby/corpus/and-or.parseA.txt index ec8570ce4..0267bc80c 100644 --- a/test/fixtures/ruby/corpus/and-or.parseA.txt +++ b/test/fixtures/ruby/corpus/and-or.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (LowAnd (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/and-or.parseB.txt b/test/fixtures/ruby/corpus/and-or.parseB.txt index 86b46393a..64d04781c 100644 --- a/test/fixtures/ruby/corpus/and-or.parseB.txt +++ b/test/fixtures/ruby/corpus/and-or.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (LowOr (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/array.diffA-B.txt b/test/fixtures/ruby/corpus/array.diffA-B.txt index cc77602d8..938d583ec 100644 --- a/test/fixtures/ruby/corpus/array.diffA-B.txt +++ b/test/fixtures/ruby/corpus/array.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array {+(TextElement)+} {+(TextElement)+} diff --git a/test/fixtures/ruby/corpus/array.diffB-A.txt b/test/fixtures/ruby/corpus/array.diffB-A.txt index c8bf11ccd..bc0d98524 100644 --- a/test/fixtures/ruby/corpus/array.diffB-A.txt +++ b/test/fixtures/ruby/corpus/array.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array {+(Integer)+} {+(Integer)+} diff --git a/test/fixtures/ruby/corpus/array.parseA.txt b/test/fixtures/ruby/corpus/array.parseA.txt index e64c2f6ff..d32cf5a62 100644 --- a/test/fixtures/ruby/corpus/array.parseA.txt +++ b/test/fixtures/ruby/corpus/array.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array (Integer) (Integer) diff --git a/test/fixtures/ruby/corpus/array.parseB.txt b/test/fixtures/ruby/corpus/array.parseB.txt index 7f436bca1..23b9ce5ed 100644 --- a/test/fixtures/ruby/corpus/array.parseB.txt +++ b/test/fixtures/ruby/corpus/array.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array (TextElement) (TextElement) diff --git a/test/fixtures/ruby/corpus/assignment.diffA-B.txt b/test/fixtures/ruby/corpus/assignment.diffA-B.txt index 42d959bff..bf5bd9f1f 100644 --- a/test/fixtures/ruby/corpus/assignment.diffA-B.txt +++ b/test/fixtures/ruby/corpus/assignment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) { (Integer) diff --git a/test/fixtures/ruby/corpus/assignment.diffB-A.txt b/test/fixtures/ruby/corpus/assignment.diffB-A.txt index 42d959bff..bf5bd9f1f 100644 --- a/test/fixtures/ruby/corpus/assignment.diffB-A.txt +++ b/test/fixtures/ruby/corpus/assignment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) { (Integer) diff --git a/test/fixtures/ruby/corpus/assignment.parseA.txt b/test/fixtures/ruby/corpus/assignment.parseA.txt index 47645e871..96467e900 100644 --- a/test/fixtures/ruby/corpus/assignment.parseA.txt +++ b/test/fixtures/ruby/corpus/assignment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Integer))) diff --git a/test/fixtures/ruby/corpus/assignment.parseB.txt b/test/fixtures/ruby/corpus/assignment.parseB.txt index 47645e871..96467e900 100644 --- a/test/fixtures/ruby/corpus/assignment.parseB.txt +++ b/test/fixtures/ruby/corpus/assignment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Integer))) diff --git a/test/fixtures/ruby/corpus/begin-block.diffA-B.txt b/test/fixtures/ruby/corpus/begin-block.diffA-B.txt index 589587a85..3031d9ead 100644 --- a/test/fixtures/ruby/corpus/begin-block.diffA-B.txt +++ b/test/fixtures/ruby/corpus/begin-block.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Send {+(Identifier)+})+} (ScopeEntry diff --git a/test/fixtures/ruby/corpus/begin-block.diffB-A.txt b/test/fixtures/ruby/corpus/begin-block.diffB-A.txt index 7e879840b..53708d238 100644 --- a/test/fixtures/ruby/corpus/begin-block.diffB-A.txt +++ b/test/fixtures/ruby/corpus/begin-block.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(ScopeEntry {+(Send {+(Identifier)+})+})+} diff --git a/test/fixtures/ruby/corpus/begin-block.parseA.txt b/test/fixtures/ruby/corpus/begin-block.parseA.txt index d34ffb026..7a735f831 100644 --- a/test/fixtures/ruby/corpus/begin-block.parseA.txt +++ b/test/fixtures/ruby/corpus/begin-block.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ScopeEntry (Send (Identifier)))) diff --git a/test/fixtures/ruby/corpus/begin-block.parseB.txt b/test/fixtures/ruby/corpus/begin-block.parseB.txt index ae6f5c244..bfa9115b8 100644 --- a/test/fixtures/ruby/corpus/begin-block.parseB.txt +++ b/test/fixtures/ruby/corpus/begin-block.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier)) (ScopeEntry diff --git a/test/fixtures/ruby/corpus/begin.diffA-B.txt b/test/fixtures/ruby/corpus/begin.diffA-B.txt index 4f983b578..f48e6e0ac 100644 --- a/test/fixtures/ruby/corpus/begin.diffA-B.txt +++ b/test/fixtures/ruby/corpus/begin.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) diff --git a/test/fixtures/ruby/corpus/begin.diffB-A.txt b/test/fixtures/ruby/corpus/begin.diffB-A.txt index 623e25948..6f2d71e71 100644 --- a/test/fixtures/ruby/corpus/begin.diffB-A.txt +++ b/test/fixtures/ruby/corpus/begin.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) diff --git a/test/fixtures/ruby/corpus/begin.parseA.txt b/test/fixtures/ruby/corpus/begin.parseA.txt index 806a217d3..c78fdebfe 100644 --- a/test/fixtures/ruby/corpus/begin.parseA.txt +++ b/test/fixtures/ruby/corpus/begin.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) diff --git a/test/fixtures/ruby/corpus/begin.parseB.txt b/test/fixtures/ruby/corpus/begin.parseB.txt index 41a6a6fb2..48f91279a 100644 --- a/test/fixtures/ruby/corpus/begin.parseB.txt +++ b/test/fixtures/ruby/corpus/begin.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) diff --git a/test/fixtures/ruby/corpus/binary.parseA.txt b/test/fixtures/ruby/corpus/binary.parseA.txt index 0c5b11c8a..2e3cdc250 100644 --- a/test/fixtures/ruby/corpus/binary.parseA.txt +++ b/test/fixtures/ruby/corpus/binary.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (And (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/bitwise-operator.diffA-B.txt b/test/fixtures/ruby/corpus/bitwise-operator.diffA-B.txt index fc321e39c..46752e4d7 100644 --- a/test/fixtures/ruby/corpus/bitwise-operator.diffA-B.txt +++ b/test/fixtures/ruby/corpus/bitwise-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (BOr {-(Send {-(Identifier)-})-} diff --git a/test/fixtures/ruby/corpus/bitwise-operator.diffB-A.txt b/test/fixtures/ruby/corpus/bitwise-operator.diffB-A.txt index 618eabcdf..63873b8c9 100644 --- a/test/fixtures/ruby/corpus/bitwise-operator.diffB-A.txt +++ b/test/fixtures/ruby/corpus/bitwise-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (BAnd {-(Send {-(Identifier)-})-} diff --git a/test/fixtures/ruby/corpus/bitwise-operator.parseA.txt b/test/fixtures/ruby/corpus/bitwise-operator.parseA.txt index 0a5e552c0..54eee4aab 100644 --- a/test/fixtures/ruby/corpus/bitwise-operator.parseA.txt +++ b/test/fixtures/ruby/corpus/bitwise-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (BOr (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/bitwise-operator.parseB.txt b/test/fixtures/ruby/corpus/bitwise-operator.parseB.txt index 93dd893b3..bf057bbf1 100644 --- a/test/fixtures/ruby/corpus/bitwise-operator.parseB.txt +++ b/test/fixtures/ruby/corpus/bitwise-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (BAnd (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/boolean-operator.diffA-B.txt b/test/fixtures/ruby/corpus/boolean-operator.diffA-B.txt index 24c997557..5cf1cd77c 100644 --- a/test/fixtures/ruby/corpus/boolean-operator.diffA-B.txt +++ b/test/fixtures/ruby/corpus/boolean-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Or {-(Send {-(Identifier)-})-} diff --git a/test/fixtures/ruby/corpus/boolean-operator.diffB-A.txt b/test/fixtures/ruby/corpus/boolean-operator.diffB-A.txt index 6fc07b317..f1c2b9ff3 100644 --- a/test/fixtures/ruby/corpus/boolean-operator.diffB-A.txt +++ b/test/fixtures/ruby/corpus/boolean-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (And {-(Send {-(Identifier)-})-} diff --git a/test/fixtures/ruby/corpus/boolean-operator.parseA.txt b/test/fixtures/ruby/corpus/boolean-operator.parseA.txt index b8c198b5a..14f55cb03 100644 --- a/test/fixtures/ruby/corpus/boolean-operator.parseA.txt +++ b/test/fixtures/ruby/corpus/boolean-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Or (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/boolean-operator.parseB.txt b/test/fixtures/ruby/corpus/boolean-operator.parseB.txt index 3f3c6c943..86762f3f7 100644 --- a/test/fixtures/ruby/corpus/boolean-operator.parseB.txt +++ b/test/fixtures/ruby/corpus/boolean-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (And (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/break.diffA-B.txt b/test/fixtures/ruby/corpus/break.diffA-B.txt index 1153a02e8..0ac902943 100644 --- a/test/fixtures/ruby/corpus/break.diffA-B.txt +++ b/test/fixtures/ruby/corpus/break.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While { (Send {-(Identifier)-}) diff --git a/test/fixtures/ruby/corpus/break.diffB-A.txt b/test/fixtures/ruby/corpus/break.diffB-A.txt index 8604a22d2..4accb55da 100644 --- a/test/fixtures/ruby/corpus/break.diffB-A.txt +++ b/test/fixtures/ruby/corpus/break.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While { (Not {-(Send diff --git a/test/fixtures/ruby/corpus/break.parseA.txt b/test/fixtures/ruby/corpus/break.parseA.txt index 223395e7e..4cbb02603 100644 --- a/test/fixtures/ruby/corpus/break.parseA.txt +++ b/test/fixtures/ruby/corpus/break.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/break.parseB.txt b/test/fixtures/ruby/corpus/break.parseB.txt index 4232fbc78..1bc83882c 100644 --- a/test/fixtures/ruby/corpus/break.parseB.txt +++ b/test/fixtures/ruby/corpus/break.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Not (Send diff --git a/test/fixtures/ruby/corpus/calls.parseA.txt b/test/fixtures/ruby/corpus/calls.parseA.txt index 5de43aea0..8d9f8f8d3 100644 --- a/test/fixtures/ruby/corpus/calls.parseA.txt +++ b/test/fixtures/ruby/corpus/calls.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (Send diff --git a/test/fixtures/ruby/corpus/chained-string.parseA.txt b/test/fixtures/ruby/corpus/chained-string.parseA.txt index 19e02b4a3..61cbbe9cf 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 (Statements (TextElement) (TextElement))) diff --git a/test/fixtures/ruby/corpus/class.diffA-B.txt b/test/fixtures/ruby/corpus/class.diffA-B.txt index 55399d0a4..0bacb0a83 100644 --- a/test/fixtures/ruby/corpus/class.diffA-B.txt +++ b/test/fixtures/ruby/corpus/class.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) {-(Identifier)-} diff --git a/test/fixtures/ruby/corpus/class.diffB-A.txt b/test/fixtures/ruby/corpus/class.diffB-A.txt index ab35adee4..8076bfd38 100644 --- a/test/fixtures/ruby/corpus/class.diffB-A.txt +++ b/test/fixtures/ruby/corpus/class.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) {+(Identifier)+} diff --git a/test/fixtures/ruby/corpus/class.parseA.txt b/test/fixtures/ruby/corpus/class.parseA.txt index f6d5f0629..ad9d8e46a 100644 --- a/test/fixtures/ruby/corpus/class.parseA.txt +++ b/test/fixtures/ruby/corpus/class.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Identifier) diff --git a/test/fixtures/ruby/corpus/class.parseB.txt b/test/fixtures/ruby/corpus/class.parseB.txt index 5b8137020..6aff83ea3 100644 --- a/test/fixtures/ruby/corpus/class.parseB.txt +++ b/test/fixtures/ruby/corpus/class.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Method diff --git a/test/fixtures/ruby/corpus/comment.diffA-B.txt b/test/fixtures/ruby/corpus/comment.diffA-B.txt index ab0622e59..5229a390d 100644 --- a/test/fixtures/ruby/corpus/comment.diffA-B.txt +++ b/test/fixtures/ruby/corpus/comment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context { (Comment) ->(Comment) } diff --git a/test/fixtures/ruby/corpus/comment.diffB-A.txt b/test/fixtures/ruby/corpus/comment.diffB-A.txt index ab0622e59..5229a390d 100644 --- a/test/fixtures/ruby/corpus/comment.diffB-A.txt +++ b/test/fixtures/ruby/corpus/comment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context { (Comment) ->(Comment) } diff --git a/test/fixtures/ruby/corpus/comment.parseA.txt b/test/fixtures/ruby/corpus/comment.parseA.txt index a4f06fd8c..4568b6b78 100644 --- a/test/fixtures/ruby/corpus/comment.parseA.txt +++ b/test/fixtures/ruby/corpus/comment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context (Comment) (Empty))) diff --git a/test/fixtures/ruby/corpus/comment.parseB.txt b/test/fixtures/ruby/corpus/comment.parseB.txt index a4f06fd8c..4568b6b78 100644 --- a/test/fixtures/ruby/corpus/comment.parseB.txt +++ b/test/fixtures/ruby/corpus/comment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context (Comment) (Empty))) diff --git a/test/fixtures/ruby/corpus/comparision-operator.diffA-B.txt b/test/fixtures/ruby/corpus/comparision-operator.diffA-B.txt index 00f151a2a..855900d22 100644 --- a/test/fixtures/ruby/corpus/comparision-operator.diffA-B.txt +++ b/test/fixtures/ruby/corpus/comparision-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (LessThan {-(Send {-(Identifier)-})-} diff --git a/test/fixtures/ruby/corpus/comparision-operator.diffB-A.txt b/test/fixtures/ruby/corpus/comparision-operator.diffB-A.txt index d4a424e5d..ec4379f2b 100644 --- a/test/fixtures/ruby/corpus/comparision-operator.diffB-A.txt +++ b/test/fixtures/ruby/corpus/comparision-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (LessThanEqual {-(Send {-(Identifier)-})-} diff --git a/test/fixtures/ruby/corpus/comparision-operator.parseA.txt b/test/fixtures/ruby/corpus/comparision-operator.parseA.txt index 56dda8ed2..6db4d3ba2 100644 --- a/test/fixtures/ruby/corpus/comparision-operator.parseA.txt +++ b/test/fixtures/ruby/corpus/comparision-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (LessThan (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/comparision-operator.parseB.txt b/test/fixtures/ruby/corpus/comparision-operator.parseB.txt index 82463b901..c01a2cd30 100644 --- a/test/fixtures/ruby/corpus/comparision-operator.parseB.txt +++ b/test/fixtures/ruby/corpus/comparision-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (LessThanEqual (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/conditional-assignment.diffA-B.txt b/test/fixtures/ruby/corpus/conditional-assignment.diffA-B.txt index e89045c82..f155a229b 100644 --- a/test/fixtures/ruby/corpus/conditional-assignment.diffA-B.txt +++ b/test/fixtures/ruby/corpus/conditional-assignment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (And diff --git a/test/fixtures/ruby/corpus/conditional-assignment.diffB-A.txt b/test/fixtures/ruby/corpus/conditional-assignment.diffB-A.txt index e89045c82..f155a229b 100644 --- a/test/fixtures/ruby/corpus/conditional-assignment.diffB-A.txt +++ b/test/fixtures/ruby/corpus/conditional-assignment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (And diff --git a/test/fixtures/ruby/corpus/conditional-assignment.parseA.txt b/test/fixtures/ruby/corpus/conditional-assignment.parseA.txt index 2263a1b1f..37805c538 100644 --- a/test/fixtures/ruby/corpus/conditional-assignment.parseA.txt +++ b/test/fixtures/ruby/corpus/conditional-assignment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (And diff --git a/test/fixtures/ruby/corpus/conditional-assignment.parseB.txt b/test/fixtures/ruby/corpus/conditional-assignment.parseB.txt index 2263a1b1f..37805c538 100644 --- a/test/fixtures/ruby/corpus/conditional-assignment.parseB.txt +++ b/test/fixtures/ruby/corpus/conditional-assignment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (And diff --git a/test/fixtures/ruby/corpus/delimiter.diffA-B.txt b/test/fixtures/ruby/corpus/delimiter.diffA-B.txt index cb091f81c..08ea7c6ad 100644 --- a/test/fixtures/ruby/corpus/delimiter.diffA-B.txt +++ b/test/fixtures/ruby/corpus/delimiter.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(TextElement)+} {+(TextElement)+} {+(TextElement)+} diff --git a/test/fixtures/ruby/corpus/delimiter.diffB-A.txt b/test/fixtures/ruby/corpus/delimiter.diffB-A.txt index b5e91bd92..a6b2c7b43 100644 --- a/test/fixtures/ruby/corpus/delimiter.diffB-A.txt +++ b/test/fixtures/ruby/corpus/delimiter.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(TextElement)+} {+(TextElement)+} { (TextElement) diff --git a/test/fixtures/ruby/corpus/delimiter.parseA.txt b/test/fixtures/ruby/corpus/delimiter.parseA.txt index 02841df90..0709fbb9e 100644 --- a/test/fixtures/ruby/corpus/delimiter.parseA.txt +++ b/test/fixtures/ruby/corpus/delimiter.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (TextElement) (TextElement) (TextElement) diff --git a/test/fixtures/ruby/corpus/delimiter.parseB.txt b/test/fixtures/ruby/corpus/delimiter.parseB.txt index 02841df90..0709fbb9e 100644 --- a/test/fixtures/ruby/corpus/delimiter.parseB.txt +++ b/test/fixtures/ruby/corpus/delimiter.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (TextElement) (TextElement) (TextElement) diff --git a/test/fixtures/ruby/corpus/element-reference.diffA-B.txt b/test/fixtures/ruby/corpus/element-reference.diffA-B.txt index 33e0d958e..078f19289 100644 --- a/test/fixtures/ruby/corpus/element-reference.diffA-B.txt +++ b/test/fixtures/ruby/corpus/element-reference.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Send { (Identifier) diff --git a/test/fixtures/ruby/corpus/element-reference.diffB-A.txt b/test/fixtures/ruby/corpus/element-reference.diffB-A.txt index d2324731c..702be1fad 100644 --- a/test/fixtures/ruby/corpus/element-reference.diffB-A.txt +++ b/test/fixtures/ruby/corpus/element-reference.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Send { (Identifier) diff --git a/test/fixtures/ruby/corpus/element-reference.parseA.txt b/test/fixtures/ruby/corpus/element-reference.parseA.txt index 3e2ef30aa..08a6a8055 100644 --- a/test/fixtures/ruby/corpus/element-reference.parseA.txt +++ b/test/fixtures/ruby/corpus/element-reference.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/element-reference.parseB.txt b/test/fixtures/ruby/corpus/element-reference.parseB.txt index 477c6ca27..02bf48c4f 100644 --- a/test/fixtures/ruby/corpus/element-reference.parseB.txt +++ b/test/fixtures/ruby/corpus/element-reference.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/else.diffA-B.txt b/test/fixtures/ruby/corpus/else.diffA-B.txt index d6cdeb537..17717bf5f 100644 --- a/test/fixtures/ruby/corpus/else.diffA-B.txt +++ b/test/fixtures/ruby/corpus/else.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/else.diffB-A.txt b/test/fixtures/ruby/corpus/else.diffB-A.txt index 0b124ce02..990e13eae 100644 --- a/test/fixtures/ruby/corpus/else.diffB-A.txt +++ b/test/fixtures/ruby/corpus/else.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/else.parseA.txt b/test/fixtures/ruby/corpus/else.parseA.txt index 1db3bb723..142cb9e55 100644 --- a/test/fixtures/ruby/corpus/else.parseA.txt +++ b/test/fixtures/ruby/corpus/else.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/else.parseB.txt b/test/fixtures/ruby/corpus/else.parseB.txt index 53227067f..ba36aecf1 100644 --- a/test/fixtures/ruby/corpus/else.parseB.txt +++ b/test/fixtures/ruby/corpus/else.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/elsif.diffA-B.txt b/test/fixtures/ruby/corpus/elsif.diffA-B.txt index 1b0d86d2d..aa41121d2 100644 --- a/test/fixtures/ruby/corpus/elsif.diffA-B.txt +++ b/test/fixtures/ruby/corpus/elsif.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/elsif.diffB-A.txt b/test/fixtures/ruby/corpus/elsif.diffB-A.txt index 46dc82c55..4a15793b1 100644 --- a/test/fixtures/ruby/corpus/elsif.diffB-A.txt +++ b/test/fixtures/ruby/corpus/elsif.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/elsif.parseA.txt b/test/fixtures/ruby/corpus/elsif.parseA.txt index dcb8c47b7..ca6b3d606 100644 --- a/test/fixtures/ruby/corpus/elsif.parseA.txt +++ b/test/fixtures/ruby/corpus/elsif.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/elsif.parseB.txt b/test/fixtures/ruby/corpus/elsif.parseB.txt index 2ef63a59e..bb1e52af4 100644 --- a/test/fixtures/ruby/corpus/elsif.parseB.txt +++ b/test/fixtures/ruby/corpus/elsif.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/empty-statement.parseA.txt b/test/fixtures/ruby/corpus/empty-statement.parseA.txt index e2189ff2c..04eca4c77 100644 --- a/test/fixtures/ruby/corpus/empty-statement.parseA.txt +++ b/test/fixtures/ruby/corpus/empty-statement.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Empty)) diff --git a/test/fixtures/ruby/corpus/end-block.diffA-B.txt b/test/fixtures/ruby/corpus/end-block.diffA-B.txt index 8f99625d9..a32d35e0b 100644 --- a/test/fixtures/ruby/corpus/end-block.diffA-B.txt +++ b/test/fixtures/ruby/corpus/end-block.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Send {+(Identifier)+})+} (ScopeExit diff --git a/test/fixtures/ruby/corpus/end-block.diffB-A.txt b/test/fixtures/ruby/corpus/end-block.diffB-A.txt index 6eaa6e5d8..ecfb4aafa 100644 --- a/test/fixtures/ruby/corpus/end-block.diffB-A.txt +++ b/test/fixtures/ruby/corpus/end-block.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(ScopeExit {+(Send {+(Identifier)+})+})+} diff --git a/test/fixtures/ruby/corpus/end-block.parseA.txt b/test/fixtures/ruby/corpus/end-block.parseA.txt index 25c3a9495..919071711 100644 --- a/test/fixtures/ruby/corpus/end-block.parseA.txt +++ b/test/fixtures/ruby/corpus/end-block.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ScopeExit (Send (Identifier)))) diff --git a/test/fixtures/ruby/corpus/end-block.parseB.txt b/test/fixtures/ruby/corpus/end-block.parseB.txt index ab8b7a91d..53f70e1cd 100644 --- a/test/fixtures/ruby/corpus/end-block.parseB.txt +++ b/test/fixtures/ruby/corpus/end-block.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier)) (ScopeExit diff --git a/test/fixtures/ruby/corpus/ensure.diffA-B.txt b/test/fixtures/ruby/corpus/ensure.diffA-B.txt index c47d54df8..ba3c7cbbf 100644 --- a/test/fixtures/ruby/corpus/ensure.diffA-B.txt +++ b/test/fixtures/ruby/corpus/ensure.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/ensure.diffB-A.txt b/test/fixtures/ruby/corpus/ensure.diffB-A.txt index 5c8fe9c24..6d67ef6d5 100644 --- a/test/fixtures/ruby/corpus/ensure.diffB-A.txt +++ b/test/fixtures/ruby/corpus/ensure.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/ensure.parseA.txt b/test/fixtures/ruby/corpus/ensure.parseA.txt index d9ac44bc3..a454eb984 100644 --- a/test/fixtures/ruby/corpus/ensure.parseA.txt +++ b/test/fixtures/ruby/corpus/ensure.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/ensure.parseB.txt b/test/fixtures/ruby/corpus/ensure.parseB.txt index 2dbf9e402..449aef23a 100644 --- a/test/fixtures/ruby/corpus/ensure.parseB.txt +++ b/test/fixtures/ruby/corpus/ensure.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/for.diffA-B.txt b/test/fixtures/ruby/corpus/for.diffA-B.txt index 0b93f83b4..81b11ef1a 100644 --- a/test/fixtures/ruby/corpus/for.diffA-B.txt +++ b/test/fixtures/ruby/corpus/for.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(ForEach {+(Statements {+(Send diff --git a/test/fixtures/ruby/corpus/for.diffB-A.txt b/test/fixtures/ruby/corpus/for.diffB-A.txt index 330945146..145df1768 100644 --- a/test/fixtures/ruby/corpus/for.diffB-A.txt +++ b/test/fixtures/ruby/corpus/for.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(ForEach {+(Statements {+(Send diff --git a/test/fixtures/ruby/corpus/for.parseA.txt b/test/fixtures/ruby/corpus/for.parseA.txt index 5fdbf737a..dd475f04b 100644 --- a/test/fixtures/ruby/corpus/for.parseA.txt +++ b/test/fixtures/ruby/corpus/for.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForEach (Statements (Send diff --git a/test/fixtures/ruby/corpus/for.parseB.txt b/test/fixtures/ruby/corpus/for.parseB.txt index cedbfe26c..267b02aa0 100644 --- a/test/fixtures/ruby/corpus/for.parseB.txt +++ b/test/fixtures/ruby/corpus/for.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForEach (Statements (Send diff --git a/test/fixtures/ruby/corpus/hash.diffA-B.txt b/test/fixtures/ruby/corpus/hash.diffA-B.txt index 29badf95d..bf1a1d711 100644 --- a/test/fixtures/ruby/corpus/hash.diffA-B.txt +++ b/test/fixtures/ruby/corpus/hash.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash {+(KeyValue {+(Symbol)+} diff --git a/test/fixtures/ruby/corpus/hash.diffB-A.txt b/test/fixtures/ruby/corpus/hash.diffB-A.txt index 56b5ffa0a..40fe9a9fb 100644 --- a/test/fixtures/ruby/corpus/hash.diffB-A.txt +++ b/test/fixtures/ruby/corpus/hash.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash {+(KeyValue {+(Symbol)+} diff --git a/test/fixtures/ruby/corpus/hash.parseA.txt b/test/fixtures/ruby/corpus/hash.parseA.txt index 96da7f0a7..ec65f4952 100644 --- a/test/fixtures/ruby/corpus/hash.parseA.txt +++ b/test/fixtures/ruby/corpus/hash.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (KeyValue (Symbol) diff --git a/test/fixtures/ruby/corpus/hash.parseB.txt b/test/fixtures/ruby/corpus/hash.parseB.txt index 769ab31b8..05e0ef38c 100644 --- a/test/fixtures/ruby/corpus/hash.parseB.txt +++ b/test/fixtures/ruby/corpus/hash.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (KeyValue (Symbol) diff --git a/test/fixtures/ruby/corpus/heredoc.diffA-B.txt b/test/fixtures/ruby/corpus/heredoc.diffA-B.txt index c95f20db7..17270f058 100644 --- a/test/fixtures/ruby/corpus/heredoc.diffA-B.txt +++ b/test/fixtures/ruby/corpus/heredoc.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Send {+(Send {+(Identifier)+} diff --git a/test/fixtures/ruby/corpus/heredoc.diffB-A.txt b/test/fixtures/ruby/corpus/heredoc.diffB-A.txt index 0e4948ace..0cbd28c4d 100644 --- a/test/fixtures/ruby/corpus/heredoc.diffB-A.txt +++ b/test/fixtures/ruby/corpus/heredoc.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(TextElement)+} {+(TextElement)+} {-(Send diff --git a/test/fixtures/ruby/corpus/heredoc.parseA.txt b/test/fixtures/ruby/corpus/heredoc.parseA.txt index 09152da25..6cbd0b081 100644 --- a/test/fixtures/ruby/corpus/heredoc.parseA.txt +++ b/test/fixtures/ruby/corpus/heredoc.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (TextElement) (TextElement)) diff --git a/test/fixtures/ruby/corpus/heredoc.parseB.txt b/test/fixtures/ruby/corpus/heredoc.parseB.txt index b21f0d865..ea484a239 100644 --- a/test/fixtures/ruby/corpus/heredoc.parseB.txt +++ b/test/fixtures/ruby/corpus/heredoc.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Send (Identifier) diff --git a/test/fixtures/ruby/corpus/if-unless-modifiers.diffA-B.txt b/test/fixtures/ruby/corpus/if-unless-modifiers.diffA-B.txt index 69aa53763..2c4a11e01 100644 --- a/test/fixtures/ruby/corpus/if-unless-modifiers.diffA-B.txt +++ b/test/fixtures/ruby/corpus/if-unless-modifiers.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If { (Not {-(Send diff --git a/test/fixtures/ruby/corpus/if-unless-modifiers.diffB-A.txt b/test/fixtures/ruby/corpus/if-unless-modifiers.diffB-A.txt index 7fad257f8..48b4f01a5 100644 --- a/test/fixtures/ruby/corpus/if-unless-modifiers.diffB-A.txt +++ b/test/fixtures/ruby/corpus/if-unless-modifiers.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If { (Send {-(Identifier)-}) diff --git a/test/fixtures/ruby/corpus/if-unless-modifiers.parseA.txt b/test/fixtures/ruby/corpus/if-unless-modifiers.parseA.txt index ab715989a..84d59247d 100644 --- a/test/fixtures/ruby/corpus/if-unless-modifiers.parseA.txt +++ b/test/fixtures/ruby/corpus/if-unless-modifiers.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Not (Send diff --git a/test/fixtures/ruby/corpus/if-unless-modifiers.parseB.txt b/test/fixtures/ruby/corpus/if-unless-modifiers.parseB.txt index c1129987d..6e4333e8e 100644 --- a/test/fixtures/ruby/corpus/if-unless-modifiers.parseB.txt +++ b/test/fixtures/ruby/corpus/if-unless-modifiers.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/if.diffA-B.txt b/test/fixtures/ruby/corpus/if.diffA-B.txt index 9ef5ed990..ee09c8179 100644 --- a/test/fixtures/ruby/corpus/if.diffA-B.txt +++ b/test/fixtures/ruby/corpus/if.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Send { (Identifier) diff --git a/test/fixtures/ruby/corpus/if.diffB-A.txt b/test/fixtures/ruby/corpus/if.diffB-A.txt index f16730bd8..68c2a1709 100644 --- a/test/fixtures/ruby/corpus/if.diffB-A.txt +++ b/test/fixtures/ruby/corpus/if.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Send { (Identifier) diff --git a/test/fixtures/ruby/corpus/if.parseA.txt b/test/fixtures/ruby/corpus/if.parseA.txt index 41430c07e..ea7e7f39b 100644 --- a/test/fixtures/ruby/corpus/if.parseA.txt +++ b/test/fixtures/ruby/corpus/if.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/if.parseB.txt b/test/fixtures/ruby/corpus/if.parseB.txt index c023a1d11..ff39ff4e3 100644 --- a/test/fixtures/ruby/corpus/if.parseB.txt +++ b/test/fixtures/ruby/corpus/if.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/interpolation.diffA-B.txt b/test/fixtures/ruby/corpus/interpolation.diffA-B.txt index c0a24bfee..f14121f50 100644 --- a/test/fixtures/ruby/corpus/interpolation.diffA-B.txt +++ b/test/fixtures/ruby/corpus/interpolation.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Symbol) ->(Symbol) } { (TextElement) diff --git a/test/fixtures/ruby/corpus/interpolation.diffB-A.txt b/test/fixtures/ruby/corpus/interpolation.diffB-A.txt index c0a24bfee..f14121f50 100644 --- a/test/fixtures/ruby/corpus/interpolation.diffB-A.txt +++ b/test/fixtures/ruby/corpus/interpolation.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Symbol) ->(Symbol) } { (TextElement) diff --git a/test/fixtures/ruby/corpus/interpolation.parseA.txt b/test/fixtures/ruby/corpus/interpolation.parseA.txt index f79250703..a57625026 100644 --- a/test/fixtures/ruby/corpus/interpolation.parseA.txt +++ b/test/fixtures/ruby/corpus/interpolation.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Symbol) (TextElement)) diff --git a/test/fixtures/ruby/corpus/interpolation.parseB.txt b/test/fixtures/ruby/corpus/interpolation.parseB.txt index f79250703..a57625026 100644 --- a/test/fixtures/ruby/corpus/interpolation.parseB.txt +++ b/test/fixtures/ruby/corpus/interpolation.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Symbol) (TextElement)) diff --git a/test/fixtures/ruby/corpus/keywords.parseA.txt b/test/fixtures/ruby/corpus/keywords.parseA.txt index b92c55e9f..8b7d4d0bf 100644 --- a/test/fixtures/ruby/corpus/keywords.parseA.txt +++ b/test/fixtures/ruby/corpus/keywords.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (File) (Line) (Send 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 e6c297e5d..d30002f71 100644 --- a/test/fixtures/ruby/corpus/lambda-dash-rocket.diffA-B.txt +++ b/test/fixtures/ruby/corpus/lambda-dash-rocket.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) {-(Identifier)-} 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 6abae706a..1bde2c96c 100644 --- a/test/fixtures/ruby/corpus/lambda-dash-rocket.diffB-A.txt +++ b/test/fixtures/ruby/corpus/lambda-dash-rocket.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) {+(Identifier)+} diff --git a/test/fixtures/ruby/corpus/lambda-dash-rocket.parseA.txt b/test/fixtures/ruby/corpus/lambda-dash-rocket.parseA.txt index ff5b12b04..bd2fdcda5 100644 --- a/test/fixtures/ruby/corpus/lambda-dash-rocket.parseA.txt +++ b/test/fixtures/ruby/corpus/lambda-dash-rocket.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Identifier) diff --git a/test/fixtures/ruby/corpus/lambda-dash-rocket.parseB.txt b/test/fixtures/ruby/corpus/lambda-dash-rocket.parseB.txt index cbe35bb4b..71a75c95e 100644 --- a/test/fixtures/ruby/corpus/lambda-dash-rocket.parseB.txt +++ b/test/fixtures/ruby/corpus/lambda-dash-rocket.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Function diff --git a/test/fixtures/ruby/corpus/lambda.diffA-B.txt b/test/fixtures/ruby/corpus/lambda.diffA-B.txt index a432cec2e..cce073d0d 100644 --- a/test/fixtures/ruby/corpus/lambda.diffA-B.txt +++ b/test/fixtures/ruby/corpus/lambda.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (Function diff --git a/test/fixtures/ruby/corpus/lambda.diffB-A.txt b/test/fixtures/ruby/corpus/lambda.diffB-A.txt index df872e722..c89610dfd 100644 --- a/test/fixtures/ruby/corpus/lambda.diffB-A.txt +++ b/test/fixtures/ruby/corpus/lambda.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (Function diff --git a/test/fixtures/ruby/corpus/lambda.parseA.txt b/test/fixtures/ruby/corpus/lambda.parseA.txt index b88439a6a..ae28ba4ae 100644 --- a/test/fixtures/ruby/corpus/lambda.parseA.txt +++ b/test/fixtures/ruby/corpus/lambda.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (Function diff --git a/test/fixtures/ruby/corpus/lambda.parseB.txt b/test/fixtures/ruby/corpus/lambda.parseB.txt index 23f3795f0..c40754edc 100644 --- a/test/fixtures/ruby/corpus/lambda.parseB.txt +++ b/test/fixtures/ruby/corpus/lambda.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (Function diff --git a/test/fixtures/ruby/corpus/literals.parseA.txt b/test/fixtures/ruby/corpus/literals.parseA.txt index 37708d778..94fb77141 100644 --- a/test/fixtures/ruby/corpus/literals.parseA.txt +++ b/test/fixtures/ruby/corpus/literals.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Boolean) (Boolean) (Null) diff --git a/test/fixtures/ruby/corpus/math-assignment.diffA-B.txt b/test/fixtures/ruby/corpus/math-assignment.diffA-B.txt index edd324c85..8a0f00e51 100644 --- a/test/fixtures/ruby/corpus/math-assignment.diffA-B.txt +++ b/test/fixtures/ruby/corpus/math-assignment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Plus diff --git a/test/fixtures/ruby/corpus/math-assignment.diffB-A.txt b/test/fixtures/ruby/corpus/math-assignment.diffB-A.txt index edd324c85..8a0f00e51 100644 --- a/test/fixtures/ruby/corpus/math-assignment.diffB-A.txt +++ b/test/fixtures/ruby/corpus/math-assignment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Plus diff --git a/test/fixtures/ruby/corpus/math-assignment.parseA.txt b/test/fixtures/ruby/corpus/math-assignment.parseA.txt index b2bfa40e5..f63b8be09 100644 --- a/test/fixtures/ruby/corpus/math-assignment.parseA.txt +++ b/test/fixtures/ruby/corpus/math-assignment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Plus diff --git a/test/fixtures/ruby/corpus/math-assignment.parseB.txt b/test/fixtures/ruby/corpus/math-assignment.parseB.txt index b2bfa40e5..f63b8be09 100644 --- a/test/fixtures/ruby/corpus/math-assignment.parseB.txt +++ b/test/fixtures/ruby/corpus/math-assignment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Plus diff --git a/test/fixtures/ruby/corpus/method-calls-hash-args.diffA-B.txt b/test/fixtures/ruby/corpus/method-calls-hash-args.diffA-B.txt index 36b32e871..2818a6f20 100644 --- a/test/fixtures/ruby/corpus/method-calls-hash-args.diffA-B.txt +++ b/test/fixtures/ruby/corpus/method-calls-hash-args.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (KeyValue diff --git a/test/fixtures/ruby/corpus/method-calls-hash-args.diffB-A.txt b/test/fixtures/ruby/corpus/method-calls-hash-args.diffB-A.txt index 7348a10ea..4572faaad 100644 --- a/test/fixtures/ruby/corpus/method-calls-hash-args.diffB-A.txt +++ b/test/fixtures/ruby/corpus/method-calls-hash-args.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (KeyValue diff --git a/test/fixtures/ruby/corpus/method-calls-hash-args.parseA.txt b/test/fixtures/ruby/corpus/method-calls-hash-args.parseA.txt index 4a1b85927..885d56116 100644 --- a/test/fixtures/ruby/corpus/method-calls-hash-args.parseA.txt +++ b/test/fixtures/ruby/corpus/method-calls-hash-args.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (KeyValue diff --git a/test/fixtures/ruby/corpus/method-calls-hash-args.parseB.txt b/test/fixtures/ruby/corpus/method-calls-hash-args.parseB.txt index 082424e40..d8ba59c99 100644 --- a/test/fixtures/ruby/corpus/method-calls-hash-args.parseB.txt +++ b/test/fixtures/ruby/corpus/method-calls-hash-args.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (KeyValue diff --git a/test/fixtures/ruby/corpus/method-calls-keyword-args.diffA-B.txt b/test/fixtures/ruby/corpus/method-calls-keyword-args.diffA-B.txt index 36b32e871..2818a6f20 100644 --- a/test/fixtures/ruby/corpus/method-calls-keyword-args.diffA-B.txt +++ b/test/fixtures/ruby/corpus/method-calls-keyword-args.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (KeyValue diff --git a/test/fixtures/ruby/corpus/method-calls-keyword-args.diffB-A.txt b/test/fixtures/ruby/corpus/method-calls-keyword-args.diffB-A.txt index 7348a10ea..4572faaad 100644 --- a/test/fixtures/ruby/corpus/method-calls-keyword-args.diffB-A.txt +++ b/test/fixtures/ruby/corpus/method-calls-keyword-args.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (KeyValue diff --git a/test/fixtures/ruby/corpus/method-calls-keyword-args.parseA.txt b/test/fixtures/ruby/corpus/method-calls-keyword-args.parseA.txt index 4a1b85927..885d56116 100644 --- a/test/fixtures/ruby/corpus/method-calls-keyword-args.parseA.txt +++ b/test/fixtures/ruby/corpus/method-calls-keyword-args.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (KeyValue diff --git a/test/fixtures/ruby/corpus/method-calls-keyword-args.parseB.txt b/test/fixtures/ruby/corpus/method-calls-keyword-args.parseB.txt index 082424e40..d8ba59c99 100644 --- a/test/fixtures/ruby/corpus/method-calls-keyword-args.parseB.txt +++ b/test/fixtures/ruby/corpus/method-calls-keyword-args.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (KeyValue diff --git a/test/fixtures/ruby/corpus/method-calls.diffA-B.txt b/test/fixtures/ruby/corpus/method-calls.diffA-B.txt index a79b2c5aa..6998278a1 100644 --- a/test/fixtures/ruby/corpus/method-calls.diffA-B.txt +++ b/test/fixtures/ruby/corpus/method-calls.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send {-(Send {-(Identifier)-})-} diff --git a/test/fixtures/ruby/corpus/method-calls.diffB-A.txt b/test/fixtures/ruby/corpus/method-calls.diffB-A.txt index 99a2dd8d7..05047bbb1 100644 --- a/test/fixtures/ruby/corpus/method-calls.diffB-A.txt +++ b/test/fixtures/ruby/corpus/method-calls.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send {+(Send {+(Identifier)+})+} diff --git a/test/fixtures/ruby/corpus/method-calls.parseA.txt b/test/fixtures/ruby/corpus/method-calls.parseA.txt index f76956a89..a78a08b13 100644 --- a/test/fixtures/ruby/corpus/method-calls.parseA.txt +++ b/test/fixtures/ruby/corpus/method-calls.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/method-calls.parseB.txt b/test/fixtures/ruby/corpus/method-calls.parseB.txt index 28fc4d141..e8f542583 100644 --- a/test/fixtures/ruby/corpus/method-calls.parseB.txt +++ b/test/fixtures/ruby/corpus/method-calls.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Send (Identifier))) 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 53a62bc41..480c2d411 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 94e20230e..799a52cca 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 298d2bcd8..ebb34bf77 100644 --- a/test/fixtures/ruby/corpus/method-declaration-keyword-param.parseA.txt +++ b/test/fixtures/ruby/corpus/method-declaration-keyword-param.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 d37ef9a8c..25509296e 100644 --- a/test/fixtures/ruby/corpus/method-declaration-keyword-param.parseB.txt +++ b/test/fixtures/ruby/corpus/method-declaration-keyword-param.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 53a62bc41..480c2d411 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 94e20230e..799a52cca 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 298d2bcd8..ebb34bf77 100644 --- a/test/fixtures/ruby/corpus/method-declaration-param-default.parseA.txt +++ b/test/fixtures/ruby/corpus/method-declaration-param-default.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 d37ef9a8c..25509296e 100644 --- a/test/fixtures/ruby/corpus/method-declaration-param-default.parseB.txt +++ b/test/fixtures/ruby/corpus/method-declaration-param-default.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 e54025850..3dc45c298 100644 --- a/test/fixtures/ruby/corpus/method-declaration-params.diffA-B.txt +++ b/test/fixtures/ruby/corpus/method-declaration-params.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 e2a20b25c..38a80defc 100644 --- a/test/fixtures/ruby/corpus/method-declaration-params.diffB-A.txt +++ b/test/fixtures/ruby/corpus/method-declaration-params.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) diff --git a/test/fixtures/ruby/corpus/method-declaration-params.parseA.txt b/test/fixtures/ruby/corpus/method-declaration-params.parseA.txt index d37ef9a8c..25509296e 100644 --- a/test/fixtures/ruby/corpus/method-declaration-params.parseA.txt +++ b/test/fixtures/ruby/corpus/method-declaration-params.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) diff --git a/test/fixtures/ruby/corpus/method-declaration-params.parseB.txt b/test/fixtures/ruby/corpus/method-declaration-params.parseB.txt index 3ba89843c..5747b6d24 100644 --- a/test/fixtures/ruby/corpus/method-declaration-params.parseB.txt +++ b/test/fixtures/ruby/corpus/method-declaration-params.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 53a62bc41..480c2d411 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 94e20230e..799a52cca 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 298d2bcd8..ebb34bf77 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 d37ef9a8c..25509296e 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 5518ef711..64565dd01 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 27239ae3f..d512d8cab 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 d37ef9a8c..25509296e 100644 --- a/test/fixtures/ruby/corpus/method-declaration-unnamed-param.parseA.txt +++ b/test/fixtures/ruby/corpus/method-declaration-unnamed-param.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) 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 9d41bda94..9fb912132 100644 --- a/test/fixtures/ruby/corpus/method-declaration-unnamed-param.parseB.txt +++ b/test/fixtures/ruby/corpus/method-declaration-unnamed-param.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) diff --git a/test/fixtures/ruby/corpus/method-declaration.diffA-B.txt b/test/fixtures/ruby/corpus/method-declaration.diffA-B.txt index 6dfccf172..d79728d85 100644 --- a/test/fixtures/ruby/corpus/method-declaration.diffA-B.txt +++ b/test/fixtures/ruby/corpus/method-declaration.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) { (Identifier) diff --git a/test/fixtures/ruby/corpus/method-declaration.diffB-A.txt b/test/fixtures/ruby/corpus/method-declaration.diffB-A.txt index 61ab57f96..ac9d3bb10 100644 --- a/test/fixtures/ruby/corpus/method-declaration.diffB-A.txt +++ b/test/fixtures/ruby/corpus/method-declaration.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) { (Identifier) diff --git a/test/fixtures/ruby/corpus/method-declaration.parseA.txt b/test/fixtures/ruby/corpus/method-declaration.parseA.txt index 298d2bcd8..ebb34bf77 100644 --- a/test/fixtures/ruby/corpus/method-declaration.parseA.txt +++ b/test/fixtures/ruby/corpus/method-declaration.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) diff --git a/test/fixtures/ruby/corpus/method-declaration.parseB.txt b/test/fixtures/ruby/corpus/method-declaration.parseB.txt index 958ef8851..87671e4b8 100644 --- a/test/fixtures/ruby/corpus/method-declaration.parseB.txt +++ b/test/fixtures/ruby/corpus/method-declaration.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) diff --git a/test/fixtures/ruby/corpus/method-invocation.diffA-B.txt b/test/fixtures/ruby/corpus/method-invocation.diffA-B.txt index 04f0d5ce1..a51d81b68 100644 --- a/test/fixtures/ruby/corpus/method-invocation.diffA-B.txt +++ b/test/fixtures/ruby/corpus/method-invocation.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) {+(TextElement)+}) diff --git a/test/fixtures/ruby/corpus/method-invocation.diffB-A.txt b/test/fixtures/ruby/corpus/method-invocation.diffB-A.txt index 9e4934ad1..922185372 100644 --- a/test/fixtures/ruby/corpus/method-invocation.diffB-A.txt +++ b/test/fixtures/ruby/corpus/method-invocation.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) {-(TextElement)-}) diff --git a/test/fixtures/ruby/corpus/method-invocation.parseA.txt b/test/fixtures/ruby/corpus/method-invocation.parseA.txt index c9c800039..b56a39555 100644 --- a/test/fixtures/ruby/corpus/method-invocation.parseA.txt +++ b/test/fixtures/ruby/corpus/method-invocation.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier)) (Send diff --git a/test/fixtures/ruby/corpus/method-invocation.parseB.txt b/test/fixtures/ruby/corpus/method-invocation.parseB.txt index 2b9590185..5b0d9738f 100644 --- a/test/fixtures/ruby/corpus/method-invocation.parseB.txt +++ b/test/fixtures/ruby/corpus/method-invocation.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (TextElement)) diff --git a/test/fixtures/ruby/corpus/methods.parseA.txt b/test/fixtures/ruby/corpus/methods.parseA.txt index f9c8a1f04..a5db758c8 100644 --- a/test/fixtures/ruby/corpus/methods.parseA.txt +++ b/test/fixtures/ruby/corpus/methods.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Method (Empty) (Identifier) diff --git a/test/fixtures/ruby/corpus/misc.parseA.txt b/test/fixtures/ruby/corpus/misc.parseA.txt index e51f4e761..4b36d2e1d 100644 --- a/test/fixtures/ruby/corpus/misc.parseA.txt +++ b/test/fixtures/ruby/corpus/misc.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Send (Identifier) (Send diff --git a/test/fixtures/ruby/corpus/module.diffA-B.txt b/test/fixtures/ruby/corpus/module.diffA-B.txt index 8f0937a13..05b88b7e4 100644 --- a/test/fixtures/ruby/corpus/module.diffA-B.txt +++ b/test/fixtures/ruby/corpus/module.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Module (Identifier) {+(Method diff --git a/test/fixtures/ruby/corpus/module.diffB-A.txt b/test/fixtures/ruby/corpus/module.diffB-A.txt index 06b13c3c9..0c3b8494c 100644 --- a/test/fixtures/ruby/corpus/module.diffB-A.txt +++ b/test/fixtures/ruby/corpus/module.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Module (Identifier) {-(Method diff --git a/test/fixtures/ruby/corpus/module.parseA.txt b/test/fixtures/ruby/corpus/module.parseA.txt index a80e2e6e2..cef5fd7ce 100644 --- a/test/fixtures/ruby/corpus/module.parseA.txt +++ b/test/fixtures/ruby/corpus/module.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Module (Identifier)) (Module diff --git a/test/fixtures/ruby/corpus/module.parseB.txt b/test/fixtures/ruby/corpus/module.parseB.txt index b73290959..f7f87e0e5 100644 --- a/test/fixtures/ruby/corpus/module.parseB.txt +++ b/test/fixtures/ruby/corpus/module.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Module (Identifier) (Method diff --git a/test/fixtures/ruby/corpus/multiple-assignments.diffA-B.txt b/test/fixtures/ruby/corpus/multiple-assignments.diffA-B.txt index bbd4b921c..169eb3dbc 100644 --- a/test/fixtures/ruby/corpus/multiple-assignments.diffA-B.txt +++ b/test/fixtures/ruby/corpus/multiple-assignments.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Statements (Identifier) diff --git a/test/fixtures/ruby/corpus/multiple-assignments.diffB-A.txt b/test/fixtures/ruby/corpus/multiple-assignments.diffB-A.txt index 1eda9f932..56b3b9ceb 100644 --- a/test/fixtures/ruby/corpus/multiple-assignments.diffB-A.txt +++ b/test/fixtures/ruby/corpus/multiple-assignments.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Statements (Identifier) diff --git a/test/fixtures/ruby/corpus/multiple-assignments.parseA.txt b/test/fixtures/ruby/corpus/multiple-assignments.parseA.txt index ea1fb4950..5fb6f2e6d 100644 --- a/test/fixtures/ruby/corpus/multiple-assignments.parseA.txt +++ b/test/fixtures/ruby/corpus/multiple-assignments.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Statements (Identifier) diff --git a/test/fixtures/ruby/corpus/multiple-assignments.parseB.txt b/test/fixtures/ruby/corpus/multiple-assignments.parseB.txt index 166f46fdb..ce115f429 100644 --- a/test/fixtures/ruby/corpus/multiple-assignments.parseB.txt +++ b/test/fixtures/ruby/corpus/multiple-assignments.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Statements (Identifier) diff --git a/test/fixtures/ruby/corpus/next.parseA.txt b/test/fixtures/ruby/corpus/next.parseA.txt index c6a6b22b9..58c02e119 100644 --- a/test/fixtures/ruby/corpus/next.parseA.txt +++ b/test/fixtures/ruby/corpus/next.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForEach (Statements (Send diff --git a/test/fixtures/ruby/corpus/number.diffA-B.txt b/test/fixtures/ruby/corpus/number.diffA-B.txt index 0049f4c90..3e5155e3a 100644 --- a/test/fixtures/ruby/corpus/number.diffA-B.txt +++ b/test/fixtures/ruby/corpus/number.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Integer)+} { (Integer) ->(Integer) } diff --git a/test/fixtures/ruby/corpus/number.diffB-A.txt b/test/fixtures/ruby/corpus/number.diffB-A.txt index 433ee8148..3abef44c1 100644 --- a/test/fixtures/ruby/corpus/number.diffB-A.txt +++ b/test/fixtures/ruby/corpus/number.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Integer)+} {+(Integer)+} {+(Integer)+} diff --git a/test/fixtures/ruby/corpus/number.parseA.txt b/test/fixtures/ruby/corpus/number.parseA.txt index d169a576f..d3d0be8ba 100644 --- a/test/fixtures/ruby/corpus/number.parseA.txt +++ b/test/fixtures/ruby/corpus/number.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Integer) (Integer) (Integer) diff --git a/test/fixtures/ruby/corpus/number.parseB.txt b/test/fixtures/ruby/corpus/number.parseB.txt index d169a576f..d3d0be8ba 100644 --- a/test/fixtures/ruby/corpus/number.parseB.txt +++ b/test/fixtures/ruby/corpus/number.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Integer) (Integer) (Integer) diff --git a/test/fixtures/ruby/corpus/percent-array.diffA-B.txt b/test/fixtures/ruby/corpus/percent-array.diffA-B.txt index 816d3f1cb..7db3982ec 100644 --- a/test/fixtures/ruby/corpus/percent-array.diffA-B.txt +++ b/test/fixtures/ruby/corpus/percent-array.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array {+(Send {+(Identifier)+})+})) diff --git a/test/fixtures/ruby/corpus/percent-array.diffB-A.txt b/test/fixtures/ruby/corpus/percent-array.diffB-A.txt index 6fa764e68..ae1086c5e 100644 --- a/test/fixtures/ruby/corpus/percent-array.diffB-A.txt +++ b/test/fixtures/ruby/corpus/percent-array.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array {-(Send {-(Identifier)-})-})) diff --git a/test/fixtures/ruby/corpus/percent-array.parseA.txt b/test/fixtures/ruby/corpus/percent-array.parseA.txt index 9f20014fb..ba8db451b 100644 --- a/test/fixtures/ruby/corpus/percent-array.parseA.txt +++ b/test/fixtures/ruby/corpus/percent-array.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Array)) diff --git a/test/fixtures/ruby/corpus/percent-array.parseB.txt b/test/fixtures/ruby/corpus/percent-array.parseB.txt index 06ea45410..f163a5a11 100644 --- a/test/fixtures/ruby/corpus/percent-array.parseB.txt +++ b/test/fixtures/ruby/corpus/percent-array.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array (Send (Identifier)))) diff --git a/test/fixtures/ruby/corpus/pseudo-variables.diffA-B.txt b/test/fixtures/ruby/corpus/pseudo-variables.diffA-B.txt index c54d72b02..1d600d137 100644 --- a/test/fixtures/ruby/corpus/pseudo-variables.diffA-B.txt +++ b/test/fixtures/ruby/corpus/pseudo-variables.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(Null)-} (Identifier) {+(Null)+} diff --git a/test/fixtures/ruby/corpus/pseudo-variables.diffB-A.txt b/test/fixtures/ruby/corpus/pseudo-variables.diffB-A.txt index de078d730..af9ea6f01 100644 --- a/test/fixtures/ruby/corpus/pseudo-variables.diffB-A.txt +++ b/test/fixtures/ruby/corpus/pseudo-variables.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {-(Identifier)-} (Null) {+(Identifier)+} diff --git a/test/fixtures/ruby/corpus/pseudo-variables.parseA.txt b/test/fixtures/ruby/corpus/pseudo-variables.parseA.txt index 0aefde7a3..d2b965f23 100644 --- a/test/fixtures/ruby/corpus/pseudo-variables.parseA.txt +++ b/test/fixtures/ruby/corpus/pseudo-variables.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Null) (Identifier) (Boolean) diff --git a/test/fixtures/ruby/corpus/pseudo-variables.parseB.txt b/test/fixtures/ruby/corpus/pseudo-variables.parseB.txt index f3885ed9d..829db3af5 100644 --- a/test/fixtures/ruby/corpus/pseudo-variables.parseB.txt +++ b/test/fixtures/ruby/corpus/pseudo-variables.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Identifier) (Null) (Boolean) diff --git a/test/fixtures/ruby/corpus/regex.diffA-B.txt b/test/fixtures/ruby/corpus/regex.diffA-B.txt index fb3fb0954..14f498104 100644 --- a/test/fixtures/ruby/corpus/regex.diffA-B.txt +++ b/test/fixtures/ruby/corpus/regex.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Regex) ->(Regex) } {+(Regex)+}) diff --git a/test/fixtures/ruby/corpus/regex.diffB-A.txt b/test/fixtures/ruby/corpus/regex.diffB-A.txt index 0edbcd5e1..729c93c60 100644 --- a/test/fixtures/ruby/corpus/regex.diffB-A.txt +++ b/test/fixtures/ruby/corpus/regex.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Regex) ->(Regex) } {-(Regex)-}) diff --git a/test/fixtures/ruby/corpus/regex.parseA.txt b/test/fixtures/ruby/corpus/regex.parseA.txt index a72f52076..b154d3ebe 100644 --- a/test/fixtures/ruby/corpus/regex.parseA.txt +++ b/test/fixtures/ruby/corpus/regex.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Regex)) diff --git a/test/fixtures/ruby/corpus/regex.parseB.txt b/test/fixtures/ruby/corpus/regex.parseB.txt index e9614fe14..1d4342edd 100644 --- a/test/fixtures/ruby/corpus/regex.parseB.txt +++ b/test/fixtures/ruby/corpus/regex.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Regex) (Regex)) diff --git a/test/fixtures/ruby/corpus/relational-operator.diffA-B.txt b/test/fixtures/ruby/corpus/relational-operator.diffA-B.txt index 9e83444ee..d4d5b5c27 100644 --- a/test/fixtures/ruby/corpus/relational-operator.diffA-B.txt +++ b/test/fixtures/ruby/corpus/relational-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Equal {-(Send {-(Identifier)-})-} diff --git a/test/fixtures/ruby/corpus/relational-operator.diffB-A.txt b/test/fixtures/ruby/corpus/relational-operator.diffB-A.txt index 3fe29af28..c80173643 100644 --- a/test/fixtures/ruby/corpus/relational-operator.diffB-A.txt +++ b/test/fixtures/ruby/corpus/relational-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Comparison {-(Send {-(Identifier)-})-} diff --git a/test/fixtures/ruby/corpus/relational-operator.parseA.txt b/test/fixtures/ruby/corpus/relational-operator.parseA.txt index 53b7e0147..05d6e4436 100644 --- a/test/fixtures/ruby/corpus/relational-operator.parseA.txt +++ b/test/fixtures/ruby/corpus/relational-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Equal (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/relational-operator.parseB.txt b/test/fixtures/ruby/corpus/relational-operator.parseB.txt index d5441e01e..f637867c5 100644 --- a/test/fixtures/ruby/corpus/relational-operator.parseB.txt +++ b/test/fixtures/ruby/corpus/relational-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Comparison (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/require.diffA-B.txt b/test/fixtures/ruby/corpus/require.diffA-B.txt index 627790c44..a09e53380 100644 --- a/test/fixtures/ruby/corpus/require.diffA-B.txt +++ b/test/fixtures/ruby/corpus/require.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Require { (TextElement) ->(TextElement) }) diff --git a/test/fixtures/ruby/corpus/require.diffB-A.txt b/test/fixtures/ruby/corpus/require.diffB-A.txt index e55fea24f..a164d17ba 100644 --- a/test/fixtures/ruby/corpus/require.diffB-A.txt +++ b/test/fixtures/ruby/corpus/require.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Require { (TextElement) ->(TextElement) }) diff --git a/test/fixtures/ruby/corpus/require.parseA.txt b/test/fixtures/ruby/corpus/require.parseA.txt index 7c20ab878..43f3ca463 100644 --- a/test/fixtures/ruby/corpus/require.parseA.txt +++ b/test/fixtures/ruby/corpus/require.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Require (TextElement)) (Send diff --git a/test/fixtures/ruby/corpus/require.parseB.txt b/test/fixtures/ruby/corpus/require.parseB.txt index 25ff2f139..160447756 100644 --- a/test/fixtures/ruby/corpus/require.parseB.txt +++ b/test/fixtures/ruby/corpus/require.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Require (TextElement)) (Send diff --git a/test/fixtures/ruby/corpus/rescue-empty.diffA-B.txt b/test/fixtures/ruby/corpus/rescue-empty.diffA-B.txt index 0c35e8b0e..fb1d0ab8d 100644 --- a/test/fixtures/ruby/corpus/rescue-empty.diffA-B.txt +++ b/test/fixtures/ruby/corpus/rescue-empty.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/rescue-empty.diffB-A.txt b/test/fixtures/ruby/corpus/rescue-empty.diffB-A.txt index 9c21fe36d..5122a3947 100644 --- a/test/fixtures/ruby/corpus/rescue-empty.diffB-A.txt +++ b/test/fixtures/ruby/corpus/rescue-empty.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/rescue-empty.parseA.txt b/test/fixtures/ruby/corpus/rescue-empty.parseA.txt index 142f19085..23369a90d 100644 --- a/test/fixtures/ruby/corpus/rescue-empty.parseA.txt +++ b/test/fixtures/ruby/corpus/rescue-empty.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/rescue-empty.parseB.txt b/test/fixtures/ruby/corpus/rescue-empty.parseB.txt index 5b9052323..047d5c62c 100644 --- a/test/fixtures/ruby/corpus/rescue-empty.parseB.txt +++ b/test/fixtures/ruby/corpus/rescue-empty.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send 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 a1842467f..fc5d949d5 100644 --- a/test/fixtures/ruby/corpus/rescue-last-ex.diffA-B.txt +++ b/test/fixtures/ruby/corpus/rescue-last-ex.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send 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 25678b843..5225b91f7 100644 --- a/test/fixtures/ruby/corpus/rescue-last-ex.diffB-A.txt +++ b/test/fixtures/ruby/corpus/rescue-last-ex.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/rescue-last-ex.parseA.txt b/test/fixtures/ruby/corpus/rescue-last-ex.parseA.txt index a7585b32b..f9b9a9484 100644 --- a/test/fixtures/ruby/corpus/rescue-last-ex.parseA.txt +++ b/test/fixtures/ruby/corpus/rescue-last-ex.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/rescue-last-ex.parseB.txt b/test/fixtures/ruby/corpus/rescue-last-ex.parseB.txt index 2aa62b05c..abc7249bc 100644 --- a/test/fixtures/ruby/corpus/rescue-last-ex.parseB.txt +++ b/test/fixtures/ruby/corpus/rescue-last-ex.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/rescue-modifier.diffA-B.txt b/test/fixtures/ruby/corpus/rescue-modifier.diffA-B.txt index 509fab25d..13f57b535 100644 --- a/test/fixtures/ruby/corpus/rescue-modifier.diffA-B.txt +++ b/test/fixtures/ruby/corpus/rescue-modifier.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/rescue-modifier.diffB-A.txt b/test/fixtures/ruby/corpus/rescue-modifier.diffB-A.txt index 4c1f4d125..ff784cd29 100644 --- a/test/fixtures/ruby/corpus/rescue-modifier.diffB-A.txt +++ b/test/fixtures/ruby/corpus/rescue-modifier.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/rescue-modifier.parseA.txt b/test/fixtures/ruby/corpus/rescue-modifier.parseA.txt index 7d9f2e4fb..7bccd3640 100644 --- a/test/fixtures/ruby/corpus/rescue-modifier.parseA.txt +++ b/test/fixtures/ruby/corpus/rescue-modifier.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/rescue-modifier.parseB.txt b/test/fixtures/ruby/corpus/rescue-modifier.parseB.txt index bc98ab542..e73b54b06 100644 --- a/test/fixtures/ruby/corpus/rescue-modifier.parseB.txt +++ b/test/fixtures/ruby/corpus/rescue-modifier.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/rescue-modifier2.diffA-B.txt b/test/fixtures/ruby/corpus/rescue-modifier2.diffA-B.txt index 2be307e31..6713a5943 100644 --- a/test/fixtures/ruby/corpus/rescue-modifier2.diffA-B.txt +++ b/test/fixtures/ruby/corpus/rescue-modifier2.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Send { (Identifier) diff --git a/test/fixtures/ruby/corpus/rescue-modifier2.diffB-A.txt b/test/fixtures/ruby/corpus/rescue-modifier2.diffB-A.txt index 2be307e31..6713a5943 100644 --- a/test/fixtures/ruby/corpus/rescue-modifier2.diffB-A.txt +++ b/test/fixtures/ruby/corpus/rescue-modifier2.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Send { (Identifier) diff --git a/test/fixtures/ruby/corpus/rescue-modifier2.parseA.txt b/test/fixtures/ruby/corpus/rescue-modifier2.parseA.txt index 7d9f2e4fb..7bccd3640 100644 --- a/test/fixtures/ruby/corpus/rescue-modifier2.parseA.txt +++ b/test/fixtures/ruby/corpus/rescue-modifier2.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/rescue-modifier2.parseB.txt b/test/fixtures/ruby/corpus/rescue-modifier2.parseB.txt index 7d9f2e4fb..7bccd3640 100644 --- a/test/fixtures/ruby/corpus/rescue-modifier2.parseB.txt +++ b/test/fixtures/ruby/corpus/rescue-modifier2.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/rescue.diffA-B.txt b/test/fixtures/ruby/corpus/rescue.diffA-B.txt index 47e0ced9b..556a95dd0 100644 --- a/test/fixtures/ruby/corpus/rescue.diffA-B.txt +++ b/test/fixtures/ruby/corpus/rescue.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Try {+(Statements {+(Send diff --git a/test/fixtures/ruby/corpus/rescue.diffB-A.txt b/test/fixtures/ruby/corpus/rescue.diffB-A.txt index 2dbe5f598..a81cb19bc 100644 --- a/test/fixtures/ruby/corpus/rescue.diffB-A.txt +++ b/test/fixtures/ruby/corpus/rescue.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Try {+(Statements {+(Send diff --git a/test/fixtures/ruby/corpus/rescue.parseA.txt b/test/fixtures/ruby/corpus/rescue.parseA.txt index c3b90edec..5c078a1c9 100644 --- a/test/fixtures/ruby/corpus/rescue.parseA.txt +++ b/test/fixtures/ruby/corpus/rescue.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/rescue.parseB.txt b/test/fixtures/ruby/corpus/rescue.parseB.txt index d5a5ed658..a6eb894bd 100644 --- a/test/fixtures/ruby/corpus/rescue.parseB.txt +++ b/test/fixtures/ruby/corpus/rescue.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Send diff --git a/test/fixtures/ruby/corpus/return.diffA-B.txt b/test/fixtures/ruby/corpus/return.diffA-B.txt index 91eed3c30..c4bc4b1c0 100644 --- a/test/fixtures/ruby/corpus/return.diffA-B.txt +++ b/test/fixtures/ruby/corpus/return.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return { (Send {-(Identifier)-}) diff --git a/test/fixtures/ruby/corpus/return.diffB-A.txt b/test/fixtures/ruby/corpus/return.diffB-A.txt index a20d9027c..96e629474 100644 --- a/test/fixtures/ruby/corpus/return.diffB-A.txt +++ b/test/fixtures/ruby/corpus/return.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return { (Empty) ->(Send diff --git a/test/fixtures/ruby/corpus/return.parseA.txt b/test/fixtures/ruby/corpus/return.parseA.txt index c5734dd38..4391a3ea1 100644 --- a/test/fixtures/ruby/corpus/return.parseA.txt +++ b/test/fixtures/ruby/corpus/return.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return (Send (Identifier)))) diff --git a/test/fixtures/ruby/corpus/return.parseB.txt b/test/fixtures/ruby/corpus/return.parseB.txt index 7d27dcae1..878ee5e75 100644 --- a/test/fixtures/ruby/corpus/return.parseB.txt +++ b/test/fixtures/ruby/corpus/return.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Empty))) diff --git a/test/fixtures/ruby/corpus/singleton-class.parseA.txt b/test/fixtures/ruby/corpus/singleton-class.parseA.txt index 2d718006d..bde386452 100644 --- a/test/fixtures/ruby/corpus/singleton-class.parseA.txt +++ b/test/fixtures/ruby/corpus/singleton-class.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Statements)) diff --git a/test/fixtures/ruby/corpus/string.diffA-B.txt b/test/fixtures/ruby/corpus/string.diffA-B.txt index f88ed6117..9b2f3490f 100644 --- a/test/fixtures/ruby/corpus/string.diffA-B.txt +++ b/test/fixtures/ruby/corpus/string.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (TextElement) ->(TextElement) } { (TextElement) diff --git a/test/fixtures/ruby/corpus/string.diffB-A.txt b/test/fixtures/ruby/corpus/string.diffB-A.txt index f88ed6117..9b2f3490f 100644 --- a/test/fixtures/ruby/corpus/string.diffB-A.txt +++ b/test/fixtures/ruby/corpus/string.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (TextElement) ->(TextElement) } { (TextElement) diff --git a/test/fixtures/ruby/corpus/string.parseA.txt b/test/fixtures/ruby/corpus/string.parseA.txt index 09152da25..6cbd0b081 100644 --- a/test/fixtures/ruby/corpus/string.parseA.txt +++ b/test/fixtures/ruby/corpus/string.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (TextElement) (TextElement)) diff --git a/test/fixtures/ruby/corpus/string.parseB.txt b/test/fixtures/ruby/corpus/string.parseB.txt index 09152da25..6cbd0b081 100644 --- a/test/fixtures/ruby/corpus/string.parseB.txt +++ b/test/fixtures/ruby/corpus/string.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (TextElement) (TextElement)) diff --git a/test/fixtures/ruby/corpus/subshell.diffA-B.txt b/test/fixtures/ruby/corpus/subshell.diffA-B.txt index c368003ca..93e83c046 100644 --- a/test/fixtures/ruby/corpus/subshell.diffA-B.txt +++ b/test/fixtures/ruby/corpus/subshell.diffA-B.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (TextElement) ->(TextElement) }) diff --git a/test/fixtures/ruby/corpus/subshell.diffB-A.txt b/test/fixtures/ruby/corpus/subshell.diffB-A.txt index c368003ca..93e83c046 100644 --- a/test/fixtures/ruby/corpus/subshell.diffB-A.txt +++ b/test/fixtures/ruby/corpus/subshell.diffB-A.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (TextElement) ->(TextElement) }) diff --git a/test/fixtures/ruby/corpus/subshell.parseA.txt b/test/fixtures/ruby/corpus/subshell.parseA.txt index 7eb233a5b..244724dcd 100644 --- a/test/fixtures/ruby/corpus/subshell.parseA.txt +++ b/test/fixtures/ruby/corpus/subshell.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (TextElement)) diff --git a/test/fixtures/ruby/corpus/subshell.parseB.txt b/test/fixtures/ruby/corpus/subshell.parseB.txt index 7eb233a5b..244724dcd 100644 --- a/test/fixtures/ruby/corpus/subshell.parseB.txt +++ b/test/fixtures/ruby/corpus/subshell.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (TextElement)) diff --git a/test/fixtures/ruby/corpus/symbol.diffA-B.txt b/test/fixtures/ruby/corpus/symbol.diffA-B.txt index 5097907fa..8a4097008 100644 --- a/test/fixtures/ruby/corpus/symbol.diffA-B.txt +++ b/test/fixtures/ruby/corpus/symbol.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Symbol) ->(Symbol) } { (Symbol) diff --git a/test/fixtures/ruby/corpus/symbol.diffB-A.txt b/test/fixtures/ruby/corpus/symbol.diffB-A.txt index 5097907fa..8a4097008 100644 --- a/test/fixtures/ruby/corpus/symbol.diffB-A.txt +++ b/test/fixtures/ruby/corpus/symbol.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Symbol) ->(Symbol) } { (Symbol) diff --git a/test/fixtures/ruby/corpus/symbol.parseA.txt b/test/fixtures/ruby/corpus/symbol.parseA.txt index 2e2a29525..b35df4f80 100644 --- a/test/fixtures/ruby/corpus/symbol.parseA.txt +++ b/test/fixtures/ruby/corpus/symbol.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Symbol) (Symbol) (Symbol)) diff --git a/test/fixtures/ruby/corpus/symbol.parseB.txt b/test/fixtures/ruby/corpus/symbol.parseB.txt index 2e2a29525..b35df4f80 100644 --- a/test/fixtures/ruby/corpus/symbol.parseB.txt +++ b/test/fixtures/ruby/corpus/symbol.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Symbol) (Symbol) (Symbol)) diff --git a/test/fixtures/ruby/corpus/ternary.diffA-B.txt b/test/fixtures/ruby/corpus/ternary.diffA-B.txt index 35d0c9d69..aa9aea3df 100644 --- a/test/fixtures/ruby/corpus/ternary.diffA-B.txt +++ b/test/fixtures/ruby/corpus/ternary.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Send { (Identifier) diff --git a/test/fixtures/ruby/corpus/ternary.diffB-A.txt b/test/fixtures/ruby/corpus/ternary.diffB-A.txt index 35d0c9d69..aa9aea3df 100644 --- a/test/fixtures/ruby/corpus/ternary.diffB-A.txt +++ b/test/fixtures/ruby/corpus/ternary.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Send { (Identifier) diff --git a/test/fixtures/ruby/corpus/ternary.parseA.txt b/test/fixtures/ruby/corpus/ternary.parseA.txt index 5f8701c9b..5c1b86d1b 100644 --- a/test/fixtures/ruby/corpus/ternary.parseA.txt +++ b/test/fixtures/ruby/corpus/ternary.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/ternary.parseB.txt b/test/fixtures/ruby/corpus/ternary.parseB.txt index 5f8701c9b..5c1b86d1b 100644 --- a/test/fixtures/ruby/corpus/ternary.parseB.txt +++ b/test/fixtures/ruby/corpus/ternary.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/unary.parseA.txt b/test/fixtures/ruby/corpus/unary.parseA.txt index 6a1bb5d57..668327e6f 100644 --- a/test/fixtures/ruby/corpus/unary.parseA.txt +++ b/test/fixtures/ruby/corpus/unary.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Complement (Send (Identifier))) diff --git a/test/fixtures/ruby/corpus/undef.parseA.txt b/test/fixtures/ruby/corpus/undef.parseA.txt index aa534d9a7..3d0dab178 100644 --- a/test/fixtures/ruby/corpus/undef.parseA.txt +++ b/test/fixtures/ruby/corpus/undef.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Symbol) diff --git a/test/fixtures/ruby/corpus/unless.diffA-B.txt b/test/fixtures/ruby/corpus/unless.diffA-B.txt index ad44d6732..5097e8529 100644 --- a/test/fixtures/ruby/corpus/unless.diffA-B.txt +++ b/test/fixtures/ruby/corpus/unless.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Not (Send diff --git a/test/fixtures/ruby/corpus/unless.diffB-A.txt b/test/fixtures/ruby/corpus/unless.diffB-A.txt index 4ee118f9d..9b84c28f8 100644 --- a/test/fixtures/ruby/corpus/unless.diffB-A.txt +++ b/test/fixtures/ruby/corpus/unless.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Not (Send diff --git a/test/fixtures/ruby/corpus/unless.parseA.txt b/test/fixtures/ruby/corpus/unless.parseA.txt index 81b87e968..05c6cc1bf 100644 --- a/test/fixtures/ruby/corpus/unless.parseA.txt +++ b/test/fixtures/ruby/corpus/unless.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Not (Send diff --git a/test/fixtures/ruby/corpus/unless.parseB.txt b/test/fixtures/ruby/corpus/unless.parseB.txt index 0d627eb22..9662e1fab 100644 --- a/test/fixtures/ruby/corpus/unless.parseB.txt +++ b/test/fixtures/ruby/corpus/unless.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Not (Send diff --git a/test/fixtures/ruby/corpus/until.diffA-B.txt b/test/fixtures/ruby/corpus/until.diffA-B.txt index fc6b6b977..41ad03204 100644 --- a/test/fixtures/ruby/corpus/until.diffA-B.txt +++ b/test/fixtures/ruby/corpus/until.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Not (Send diff --git a/test/fixtures/ruby/corpus/until.diffB-A.txt b/test/fixtures/ruby/corpus/until.diffB-A.txt index f6f7e3d00..1bfbb828e 100644 --- a/test/fixtures/ruby/corpus/until.diffB-A.txt +++ b/test/fixtures/ruby/corpus/until.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Not (Send diff --git a/test/fixtures/ruby/corpus/until.parseA.txt b/test/fixtures/ruby/corpus/until.parseA.txt index 2c714334f..f36973e6f 100644 --- a/test/fixtures/ruby/corpus/until.parseA.txt +++ b/test/fixtures/ruby/corpus/until.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Not (Send diff --git a/test/fixtures/ruby/corpus/until.parseB.txt b/test/fixtures/ruby/corpus/until.parseB.txt index 0169df2f1..35145db60 100644 --- a/test/fixtures/ruby/corpus/until.parseB.txt +++ b/test/fixtures/ruby/corpus/until.parseB.txt @@ -1,4 +1,4 @@ -(Program +(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 5fe140f15..08579b880 100644 --- a/test/fixtures/ruby/corpus/when-else.diffA-B.txt +++ b/test/fixtures/ruby/corpus/when-else.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/when-else.diffB-A.txt b/test/fixtures/ruby/corpus/when-else.diffB-A.txt index a663a07f4..b130388e8 100644 --- a/test/fixtures/ruby/corpus/when-else.diffB-A.txt +++ b/test/fixtures/ruby/corpus/when-else.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/when-else.parseA.txt b/test/fixtures/ruby/corpus/when-else.parseA.txt index 9a0b2fe67..e782e5233 100644 --- a/test/fixtures/ruby/corpus/when-else.parseA.txt +++ b/test/fixtures/ruby/corpus/when-else.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/when-else.parseB.txt b/test/fixtures/ruby/corpus/when-else.parseB.txt index 0bf7a8e0b..d01cc541f 100644 --- a/test/fixtures/ruby/corpus/when-else.parseB.txt +++ b/test/fixtures/ruby/corpus/when-else.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/when.diffA-B.txt b/test/fixtures/ruby/corpus/when.diffA-B.txt index 424b74924..e9b501002 100644 --- a/test/fixtures/ruby/corpus/when.diffA-B.txt +++ b/test/fixtures/ruby/corpus/when.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/when.diffB-A.txt b/test/fixtures/ruby/corpus/when.diffB-A.txt index 85c2ab01e..7d2880cc0 100644 --- a/test/fixtures/ruby/corpus/when.diffB-A.txt +++ b/test/fixtures/ruby/corpus/when.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/when.parseA.txt b/test/fixtures/ruby/corpus/when.parseA.txt index d4fda449b..f7fca4599 100644 --- a/test/fixtures/ruby/corpus/when.parseA.txt +++ b/test/fixtures/ruby/corpus/when.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/when.parseB.txt b/test/fixtures/ruby/corpus/when.parseB.txt index 9e2ad6051..3c54f2901 100644 --- a/test/fixtures/ruby/corpus/when.parseB.txt +++ b/test/fixtures/ruby/corpus/when.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/while.diffA-B.txt b/test/fixtures/ruby/corpus/while.diffA-B.txt index 6d36323a9..7c2535aa3 100644 --- a/test/fixtures/ruby/corpus/while.diffA-B.txt +++ b/test/fixtures/ruby/corpus/while.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/while.diffB-A.txt b/test/fixtures/ruby/corpus/while.diffB-A.txt index 9ae46e79c..0d26013ab 100644 --- a/test/fixtures/ruby/corpus/while.diffB-A.txt +++ b/test/fixtures/ruby/corpus/while.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/while.parseA.txt b/test/fixtures/ruby/corpus/while.parseA.txt index 4f8aa8649..088b940d4 100644 --- a/test/fixtures/ruby/corpus/while.parseA.txt +++ b/test/fixtures/ruby/corpus/while.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/while.parseB.txt b/test/fixtures/ruby/corpus/while.parseB.txt index 7fd7dda40..76e7e1725 100644 --- a/test/fixtures/ruby/corpus/while.parseB.txt +++ b/test/fixtures/ruby/corpus/while.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Send (Identifier)) diff --git a/test/fixtures/ruby/corpus/yield.diffA-B.txt b/test/fixtures/ruby/corpus/yield.diffA-B.txt index 5982d3d5f..98af068e6 100644 --- a/test/fixtures/ruby/corpus/yield.diffA-B.txt +++ b/test/fixtures/ruby/corpus/yield.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Yield { (Send {-(Identifier)-}) diff --git a/test/fixtures/ruby/corpus/yield.diffB-A.txt b/test/fixtures/ruby/corpus/yield.diffB-A.txt index 7f8e21d19..512cbb029 100644 --- a/test/fixtures/ruby/corpus/yield.diffB-A.txt +++ b/test/fixtures/ruby/corpus/yield.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Yield { (Empty) ->(Send diff --git a/test/fixtures/ruby/corpus/yield.parseA.txt b/test/fixtures/ruby/corpus/yield.parseA.txt index e86849a79..e144574f9 100644 --- a/test/fixtures/ruby/corpus/yield.parseA.txt +++ b/test/fixtures/ruby/corpus/yield.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Yield (Send (Identifier)))) diff --git a/test/fixtures/ruby/corpus/yield.parseB.txt b/test/fixtures/ruby/corpus/yield.parseB.txt index b8748d919..8663d7d6f 100644 --- a/test/fixtures/ruby/corpus/yield.parseB.txt +++ b/test/fixtures/ruby/corpus/yield.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Yield (Empty))) diff --git a/test/fixtures/typescript/corpus/ambient-declarations.diffA-B.txt b/test/fixtures/typescript/corpus/ambient-declarations.diffA-B.txt index aa4d45b54..19766d866 100644 --- a/test/fixtures/typescript/corpus/ambient-declarations.diffA-B.txt +++ b/test/fixtures/typescript/corpus/ambient-declarations.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(AmbientDeclaration {+(InternalModule {+(Identifier)+})+})+} diff --git a/test/fixtures/typescript/corpus/ambient-declarations.diffB-A.txt b/test/fixtures/typescript/corpus/ambient-declarations.diffB-A.txt index 2ec101943..1e283e178 100644 --- a/test/fixtures/typescript/corpus/ambient-declarations.diffB-A.txt +++ b/test/fixtures/typescript/corpus/ambient-declarations.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(AmbientDeclaration {+(Class {+(Identifier)+} diff --git a/test/fixtures/typescript/corpus/ambient-declarations.parseA.txt b/test/fixtures/typescript/corpus/ambient-declarations.parseA.txt index f028e9b5b..40133edb5 100644 --- a/test/fixtures/typescript/corpus/ambient-declarations.parseA.txt +++ b/test/fixtures/typescript/corpus/ambient-declarations.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (AmbientDeclaration (Class (Identifier) diff --git a/test/fixtures/typescript/corpus/ambient-declarations.parseB.txt b/test/fixtures/typescript/corpus/ambient-declarations.parseB.txt index 0d0519272..60a04c19c 100644 --- a/test/fixtures/typescript/corpus/ambient-declarations.parseB.txt +++ b/test/fixtures/typescript/corpus/ambient-declarations.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (AmbientDeclaration (InternalModule (Identifier))) diff --git a/test/fixtures/typescript/corpus/ambient-exports.diffA-B.txt b/test/fixtures/typescript/corpus/ambient-exports.diffA-B.txt index 400442a30..5fd6df395 100644 --- a/test/fixtures/typescript/corpus/ambient-exports.diffA-B.txt +++ b/test/fixtures/typescript/corpus/ambient-exports.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (DefaultExport { (Class {-(Identifier)-} diff --git a/test/fixtures/typescript/corpus/ambient-exports.diffB-A.txt b/test/fixtures/typescript/corpus/ambient-exports.diffB-A.txt index ac045fe1e..9208b88b7 100644 --- a/test/fixtures/typescript/corpus/ambient-exports.diffB-A.txt +++ b/test/fixtures/typescript/corpus/ambient-exports.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (DefaultExport { (Function {-(Empty)-} diff --git a/test/fixtures/typescript/corpus/ambient-exports.parseA.txt b/test/fixtures/typescript/corpus/ambient-exports.parseA.txt index 29e69c225..e3c2e46bf 100644 --- a/test/fixtures/typescript/corpus/ambient-exports.parseA.txt +++ b/test/fixtures/typescript/corpus/ambient-exports.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (DefaultExport (Class (Identifier) diff --git a/test/fixtures/typescript/corpus/ambient-exports.parseB.txt b/test/fixtures/typescript/corpus/ambient-exports.parseB.txt index daab22e4f..eb81cb9cf 100644 --- a/test/fixtures/typescript/corpus/ambient-exports.parseB.txt +++ b/test/fixtures/typescript/corpus/ambient-exports.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (DefaultExport (Function (Empty) diff --git a/test/fixtures/typescript/corpus/ambient-type-declarations.diffA-B.txt b/test/fixtures/typescript/corpus/ambient-type-declarations.diffA-B.txt index 13944750f..b631f3881 100644 --- a/test/fixtures/typescript/corpus/ambient-type-declarations.diffA-B.txt +++ b/test/fixtures/typescript/corpus/ambient-type-declarations.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(TypeAlias {+(Empty)+} {+(Identifier)+} diff --git a/test/fixtures/typescript/corpus/ambient-type-declarations.diffB-A.txt b/test/fixtures/typescript/corpus/ambient-type-declarations.diffB-A.txt index 02b4eb398..2678f24e9 100644 --- a/test/fixtures/typescript/corpus/ambient-type-declarations.diffB-A.txt +++ b/test/fixtures/typescript/corpus/ambient-type-declarations.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(AmbientDeclaration {+(TypeAlias {+(Empty)+} diff --git a/test/fixtures/typescript/corpus/ambient-type-declarations.parseA.txt b/test/fixtures/typescript/corpus/ambient-type-declarations.parseA.txt index 0006d09ab..61049abbd 100644 --- a/test/fixtures/typescript/corpus/ambient-type-declarations.parseA.txt +++ b/test/fixtures/typescript/corpus/ambient-type-declarations.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (AmbientDeclaration (TypeAlias (Empty) diff --git a/test/fixtures/typescript/corpus/ambient-type-declarations.parseB.txt b/test/fixtures/typescript/corpus/ambient-type-declarations.parseB.txt index c6887ea04..a508d4161 100644 --- a/test/fixtures/typescript/corpus/ambient-type-declarations.parseB.txt +++ b/test/fixtures/typescript/corpus/ambient-type-declarations.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (TypeAlias (Empty) (Identifier) diff --git a/test/fixtures/typescript/corpus/anonymous-function.diffA-B.txt b/test/fixtures/typescript/corpus/anonymous-function.diffA-B.txt index a413f45aa..d526868af 100644 --- a/test/fixtures/typescript/corpus/anonymous-function.diffA-B.txt +++ b/test/fixtures/typescript/corpus/anonymous-function.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/anonymous-function.diffB-A.txt b/test/fixtures/typescript/corpus/anonymous-function.diffB-A.txt index 14e2117e6..963fa9460 100644 --- a/test/fixtures/typescript/corpus/anonymous-function.diffB-A.txt +++ b/test/fixtures/typescript/corpus/anonymous-function.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/anonymous-function.parseA.txt b/test/fixtures/typescript/corpus/anonymous-function.parseA.txt index 410fa0126..0984eea18 100644 --- a/test/fixtures/typescript/corpus/anonymous-function.parseA.txt +++ b/test/fixtures/typescript/corpus/anonymous-function.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/anonymous-function.parseB.txt b/test/fixtures/typescript/corpus/anonymous-function.parseB.txt index f4cf6bbd8..270de0665 100644 --- a/test/fixtures/typescript/corpus/anonymous-function.parseB.txt +++ b/test/fixtures/typescript/corpus/anonymous-function.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) 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 33fc55d49..ddb22e178 100644 --- a/test/fixtures/typescript/corpus/anonymous-parameterless-function.diffA-B.txt +++ b/test/fixtures/typescript/corpus/anonymous-parameterless-function.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) 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 33fc55d49..ddb22e178 100644 --- a/test/fixtures/typescript/corpus/anonymous-parameterless-function.diffB-A.txt +++ b/test/fixtures/typescript/corpus/anonymous-parameterless-function.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseA.txt b/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseA.txt index bb24b8ce4..58a9e2102 100644 --- a/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseA.txt +++ b/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseB.txt b/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseB.txt index bb24b8ce4..58a9e2102 100644 --- a/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseB.txt +++ b/test/fixtures/typescript/corpus/anonymous-parameterless-function.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/array-type.diffA-B.txt b/test/fixtures/typescript/corpus/array-type.diffA-B.txt index e42d1bb54..f0a98a621 100644 --- a/test/fixtures/typescript/corpus/array-type.diffA-B.txt +++ b/test/fixtures/typescript/corpus/array-type.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/array-type.diffB-A.txt b/test/fixtures/typescript/corpus/array-type.diffB-A.txt index f7f72c9f5..6f6b9fd33 100644 --- a/test/fixtures/typescript/corpus/array-type.diffB-A.txt +++ b/test/fixtures/typescript/corpus/array-type.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/array-type.parseA.txt b/test/fixtures/typescript/corpus/array-type.parseA.txt index ed3a4660f..3155372a9 100644 --- a/test/fixtures/typescript/corpus/array-type.parseA.txt +++ b/test/fixtures/typescript/corpus/array-type.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/array-type.parseB.txt b/test/fixtures/typescript/corpus/array-type.parseB.txt index 3e6b217cf..60d64c00a 100644 --- a/test/fixtures/typescript/corpus/array-type.parseB.txt +++ b/test/fixtures/typescript/corpus/array-type.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/array.diffA-B.txt b/test/fixtures/typescript/corpus/array.diffA-B.txt index 991e26a26..d91bf8637 100644 --- a/test/fixtures/typescript/corpus/array.diffA-B.txt +++ b/test/fixtures/typescript/corpus/array.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array (TextElement) {+(TextElement)+})) diff --git a/test/fixtures/typescript/corpus/array.diffB-A.txt b/test/fixtures/typescript/corpus/array.diffB-A.txt index c5bd3b828..4acede0f6 100644 --- a/test/fixtures/typescript/corpus/array.diffB-A.txt +++ b/test/fixtures/typescript/corpus/array.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array (TextElement) {-(TextElement)-})) diff --git a/test/fixtures/typescript/corpus/array.parseA.txt b/test/fixtures/typescript/corpus/array.parseA.txt index 0965f1f9f..d5891f355 100644 --- a/test/fixtures/typescript/corpus/array.parseA.txt +++ b/test/fixtures/typescript/corpus/array.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Array (TextElement))) diff --git a/test/fixtures/typescript/corpus/array.parseB.txt b/test/fixtures/typescript/corpus/array.parseB.txt index 69ab394db..4de5832a5 100644 --- a/test/fixtures/typescript/corpus/array.parseB.txt +++ b/test/fixtures/typescript/corpus/array.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Array (TextElement) (TextElement))) diff --git a/test/fixtures/typescript/corpus/arrow-function.diffA-B.txt b/test/fixtures/typescript/corpus/arrow-function.diffA-B.txt index 600b385ff..182077320 100644 --- a/test/fixtures/typescript/corpus/arrow-function.diffA-B.txt +++ b/test/fixtures/typescript/corpus/arrow-function.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/arrow-function.diffB-A.txt b/test/fixtures/typescript/corpus/arrow-function.diffB-A.txt index 600b385ff..182077320 100644 --- a/test/fixtures/typescript/corpus/arrow-function.diffB-A.txt +++ b/test/fixtures/typescript/corpus/arrow-function.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/arrow-function.parseA.txt b/test/fixtures/typescript/corpus/arrow-function.parseA.txt index e178c9e7c..66bcd0037 100644 --- a/test/fixtures/typescript/corpus/arrow-function.parseA.txt +++ b/test/fixtures/typescript/corpus/arrow-function.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/arrow-function.parseB.txt b/test/fixtures/typescript/corpus/arrow-function.parseB.txt index e178c9e7c..66bcd0037 100644 --- a/test/fixtures/typescript/corpus/arrow-function.parseB.txt +++ b/test/fixtures/typescript/corpus/arrow-function.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/assignment-pattern.diffA-B.txt b/test/fixtures/typescript/corpus/assignment-pattern.diffA-B.txt index e2d3e4509..18cea23ed 100644 --- a/test/fixtures/typescript/corpus/assignment-pattern.diffA-B.txt +++ b/test/fixtures/typescript/corpus/assignment-pattern.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/assignment-pattern.diffB-A.txt b/test/fixtures/typescript/corpus/assignment-pattern.diffB-A.txt index e2d3e4509..18cea23ed 100644 --- a/test/fixtures/typescript/corpus/assignment-pattern.diffB-A.txt +++ b/test/fixtures/typescript/corpus/assignment-pattern.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/assignment-pattern.parseA.txt b/test/fixtures/typescript/corpus/assignment-pattern.parseA.txt index 668ff126f..2db3947ee 100644 --- a/test/fixtures/typescript/corpus/assignment-pattern.parseA.txt +++ b/test/fixtures/typescript/corpus/assignment-pattern.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/assignment-pattern.parseB.txt b/test/fixtures/typescript/corpus/assignment-pattern.parseB.txt index 668ff126f..2db3947ee 100644 --- a/test/fixtures/typescript/corpus/assignment-pattern.parseB.txt +++ b/test/fixtures/typescript/corpus/assignment-pattern.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/assignment.diffA-B.txt b/test/fixtures/typescript/corpus/assignment.diffA-B.txt index 9572881a4..3f9ac8708 100644 --- a/test/fixtures/typescript/corpus/assignment.diffA-B.txt +++ b/test/fixtures/typescript/corpus/assignment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) { (Float) diff --git a/test/fixtures/typescript/corpus/assignment.diffB-A.txt b/test/fixtures/typescript/corpus/assignment.diffB-A.txt index 9572881a4..3f9ac8708 100644 --- a/test/fixtures/typescript/corpus/assignment.diffB-A.txt +++ b/test/fixtures/typescript/corpus/assignment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) { (Float) diff --git a/test/fixtures/typescript/corpus/assignment.parseA.txt b/test/fixtures/typescript/corpus/assignment.parseA.txt index 7631b5f93..e68803f14 100644 --- a/test/fixtures/typescript/corpus/assignment.parseA.txt +++ b/test/fixtures/typescript/corpus/assignment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Float))) diff --git a/test/fixtures/typescript/corpus/assignment.parseB.txt b/test/fixtures/typescript/corpus/assignment.parseB.txt index 7631b5f93..e68803f14 100644 --- a/test/fixtures/typescript/corpus/assignment.parseB.txt +++ b/test/fixtures/typescript/corpus/assignment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Float))) diff --git a/test/fixtures/typescript/corpus/bitwise-operator.diffA-B.txt b/test/fixtures/typescript/corpus/bitwise-operator.diffA-B.txt index b039bc977..643068d8f 100644 --- a/test/fixtures/typescript/corpus/bitwise-operator.diffA-B.txt +++ b/test/fixtures/typescript/corpus/bitwise-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (RShift (Identifier) { (Identifier) diff --git a/test/fixtures/typescript/corpus/bitwise-operator.diffB-A.txt b/test/fixtures/typescript/corpus/bitwise-operator.diffB-A.txt index b039bc977..643068d8f 100644 --- a/test/fixtures/typescript/corpus/bitwise-operator.diffB-A.txt +++ b/test/fixtures/typescript/corpus/bitwise-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (RShift (Identifier) { (Identifier) diff --git a/test/fixtures/typescript/corpus/bitwise-operator.parseA.txt b/test/fixtures/typescript/corpus/bitwise-operator.parseA.txt index 4f83e3ae5..3be6465cf 100644 --- a/test/fixtures/typescript/corpus/bitwise-operator.parseA.txt +++ b/test/fixtures/typescript/corpus/bitwise-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (RShift (Identifier) (Identifier))) diff --git a/test/fixtures/typescript/corpus/bitwise-operator.parseB.txt b/test/fixtures/typescript/corpus/bitwise-operator.parseB.txt index 4f83e3ae5..3be6465cf 100644 --- a/test/fixtures/typescript/corpus/bitwise-operator.parseB.txt +++ b/test/fixtures/typescript/corpus/bitwise-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (RShift (Identifier) (Identifier))) diff --git a/test/fixtures/typescript/corpus/boolean-operator.diffA-B.txt b/test/fixtures/typescript/corpus/boolean-operator.diffA-B.txt index 365405c5c..a257366e8 100644 --- a/test/fixtures/typescript/corpus/boolean-operator.diffA-B.txt +++ b/test/fixtures/typescript/corpus/boolean-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (Or {-(Identifier)-} {-(Identifier)-}) diff --git a/test/fixtures/typescript/corpus/boolean-operator.diffB-A.txt b/test/fixtures/typescript/corpus/boolean-operator.diffB-A.txt index bab8a9ceb..ef610ad5c 100644 --- a/test/fixtures/typescript/corpus/boolean-operator.diffB-A.txt +++ b/test/fixtures/typescript/corpus/boolean-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (And {-(Identifier)-} {-(Identifier)-}) diff --git a/test/fixtures/typescript/corpus/boolean-operator.parseA.txt b/test/fixtures/typescript/corpus/boolean-operator.parseA.txt index ac8cbd824..90cabac73 100644 --- a/test/fixtures/typescript/corpus/boolean-operator.parseA.txt +++ b/test/fixtures/typescript/corpus/boolean-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Or (Identifier) (Identifier))) diff --git a/test/fixtures/typescript/corpus/boolean-operator.parseB.txt b/test/fixtures/typescript/corpus/boolean-operator.parseB.txt index c45251d63..8fa994bf7 100644 --- a/test/fixtures/typescript/corpus/boolean-operator.parseB.txt +++ b/test/fixtures/typescript/corpus/boolean-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (And (Identifier) (Identifier))) diff --git a/test/fixtures/typescript/corpus/break.diffA-B.txt b/test/fixtures/typescript/corpus/break.diffA-B.txt index 46eb71902..7a6ade058 100644 --- a/test/fixtures/typescript/corpus/break.diffA-B.txt +++ b/test/fixtures/typescript/corpus/break.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/typescript/corpus/break.diffB-A.txt b/test/fixtures/typescript/corpus/break.diffB-A.txt index 44e6c7bdc..e57de03a9 100644 --- a/test/fixtures/typescript/corpus/break.diffB-A.txt +++ b/test/fixtures/typescript/corpus/break.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/typescript/corpus/break.parseA.txt b/test/fixtures/typescript/corpus/break.parseA.txt index c0af1c973..7e374ef00 100644 --- a/test/fixtures/typescript/corpus/break.parseA.txt +++ b/test/fixtures/typescript/corpus/break.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/typescript/corpus/break.parseB.txt b/test/fixtures/typescript/corpus/break.parseB.txt index 0c30ef033..33b8ce898 100644 --- a/test/fixtures/typescript/corpus/break.parseB.txt +++ b/test/fixtures/typescript/corpus/break.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/typescript/corpus/chained-callbacks.diffA-B.txt b/test/fixtures/typescript/corpus/chained-callbacks.diffA-B.txt index ba36adf30..33edbf7a2 100644 --- a/test/fixtures/typescript/corpus/chained-callbacks.diffA-B.txt +++ b/test/fixtures/typescript/corpus/chained-callbacks.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (This) diff --git a/test/fixtures/typescript/corpus/chained-callbacks.diffB-A.txt b/test/fixtures/typescript/corpus/chained-callbacks.diffB-A.txt index ba36adf30..33edbf7a2 100644 --- a/test/fixtures/typescript/corpus/chained-callbacks.diffB-A.txt +++ b/test/fixtures/typescript/corpus/chained-callbacks.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (This) diff --git a/test/fixtures/typescript/corpus/chained-callbacks.parseA.txt b/test/fixtures/typescript/corpus/chained-callbacks.parseA.txt index a6043e559..545dc8174 100644 --- a/test/fixtures/typescript/corpus/chained-callbacks.parseA.txt +++ b/test/fixtures/typescript/corpus/chained-callbacks.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (This) diff --git a/test/fixtures/typescript/corpus/chained-callbacks.parseB.txt b/test/fixtures/typescript/corpus/chained-callbacks.parseB.txt index a6043e559..545dc8174 100644 --- a/test/fixtures/typescript/corpus/chained-callbacks.parseB.txt +++ b/test/fixtures/typescript/corpus/chained-callbacks.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (This) diff --git a/test/fixtures/typescript/corpus/chained-property-access.diffA-B.txt b/test/fixtures/typescript/corpus/chained-property-access.diffA-B.txt index 1c4c5c60f..4cbf4df13 100644 --- a/test/fixtures/typescript/corpus/chained-property-access.diffA-B.txt +++ b/test/fixtures/typescript/corpus/chained-property-access.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return (Call (MemberAccess diff --git a/test/fixtures/typescript/corpus/chained-property-access.diffB-A.txt b/test/fixtures/typescript/corpus/chained-property-access.diffB-A.txt index 1c4c5c60f..4cbf4df13 100644 --- a/test/fixtures/typescript/corpus/chained-property-access.diffB-A.txt +++ b/test/fixtures/typescript/corpus/chained-property-access.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return (Call (MemberAccess diff --git a/test/fixtures/typescript/corpus/chained-property-access.parseA.txt b/test/fixtures/typescript/corpus/chained-property-access.parseA.txt index c45050ddf..52d369111 100644 --- a/test/fixtures/typescript/corpus/chained-property-access.parseA.txt +++ b/test/fixtures/typescript/corpus/chained-property-access.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return (Call (MemberAccess diff --git a/test/fixtures/typescript/corpus/chained-property-access.parseB.txt b/test/fixtures/typescript/corpus/chained-property-access.parseB.txt index c45050ddf..52d369111 100644 --- a/test/fixtures/typescript/corpus/chained-property-access.parseB.txt +++ b/test/fixtures/typescript/corpus/chained-property-access.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return (Call (MemberAccess diff --git a/test/fixtures/typescript/corpus/class.diffA-B.txt b/test/fixtures/typescript/corpus/class.diffA-B.txt index e5098c83c..7567c2eb0 100644 --- a/test/fixtures/typescript/corpus/class.diffA-B.txt +++ b/test/fixtures/typescript/corpus/class.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (TypeParameter { (Identifier) diff --git a/test/fixtures/typescript/corpus/class.diffB-A.txt b/test/fixtures/typescript/corpus/class.diffB-A.txt index 25a835604..aa3082cc2 100644 --- a/test/fixtures/typescript/corpus/class.diffB-A.txt +++ b/test/fixtures/typescript/corpus/class.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (TypeParameter { (Identifier) diff --git a/test/fixtures/typescript/corpus/class.parseA.txt b/test/fixtures/typescript/corpus/class.parseA.txt index 0d3c5096e..98dcd26a0 100644 --- a/test/fixtures/typescript/corpus/class.parseA.txt +++ b/test/fixtures/typescript/corpus/class.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (TypeParameter (Identifier) diff --git a/test/fixtures/typescript/corpus/class.parseB.txt b/test/fixtures/typescript/corpus/class.parseB.txt index 79c19acf2..7202698bb 100644 --- a/test/fixtures/typescript/corpus/class.parseB.txt +++ b/test/fixtures/typescript/corpus/class.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (TypeParameter (Identifier) diff --git a/test/fixtures/typescript/corpus/comma-operator.diffA-B.txt b/test/fixtures/typescript/corpus/comma-operator.diffA-B.txt index 1d77d4600..15fc0c2b3 100644 --- a/test/fixtures/typescript/corpus/comma-operator.diffA-B.txt +++ b/test/fixtures/typescript/corpus/comma-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Assignment {+(Identifier)+} {+(Hash diff --git a/test/fixtures/typescript/corpus/comma-operator.diffB-A.txt b/test/fixtures/typescript/corpus/comma-operator.diffB-A.txt index 3baaed40f..8a6943ae5 100644 --- a/test/fixtures/typescript/corpus/comma-operator.diffB-A.txt +++ b/test/fixtures/typescript/corpus/comma-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(SequenceExpression {+(Assignment {+(Identifier)+} diff --git a/test/fixtures/typescript/corpus/comma-operator.parseA.txt b/test/fixtures/typescript/corpus/comma-operator.parseA.txt index 73999dc0d..06fbde18f 100644 --- a/test/fixtures/typescript/corpus/comma-operator.parseA.txt +++ b/test/fixtures/typescript/corpus/comma-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (SequenceExpression (Assignment (Identifier) diff --git a/test/fixtures/typescript/corpus/comma-operator.parseB.txt b/test/fixtures/typescript/corpus/comma-operator.parseB.txt index 071db7345..acf60ac42 100644 --- a/test/fixtures/typescript/corpus/comma-operator.parseB.txt +++ b/test/fixtures/typescript/corpus/comma-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Hash diff --git a/test/fixtures/typescript/corpus/comment.diffA-B.txt b/test/fixtures/typescript/corpus/comment.diffA-B.txt index ab0622e59..5229a390d 100644 --- a/test/fixtures/typescript/corpus/comment.diffA-B.txt +++ b/test/fixtures/typescript/corpus/comment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context { (Comment) ->(Comment) } diff --git a/test/fixtures/typescript/corpus/comment.diffB-A.txt b/test/fixtures/typescript/corpus/comment.diffB-A.txt index ab0622e59..5229a390d 100644 --- a/test/fixtures/typescript/corpus/comment.diffB-A.txt +++ b/test/fixtures/typescript/corpus/comment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context { (Comment) ->(Comment) } diff --git a/test/fixtures/typescript/corpus/comment.parseA.txt b/test/fixtures/typescript/corpus/comment.parseA.txt index a4f06fd8c..4568b6b78 100644 --- a/test/fixtures/typescript/corpus/comment.parseA.txt +++ b/test/fixtures/typescript/corpus/comment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context (Comment) (Empty))) diff --git a/test/fixtures/typescript/corpus/comment.parseB.txt b/test/fixtures/typescript/corpus/comment.parseB.txt index a4f06fd8c..4568b6b78 100644 --- a/test/fixtures/typescript/corpus/comment.parseB.txt +++ b/test/fixtures/typescript/corpus/comment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Context (Comment) (Empty))) diff --git a/test/fixtures/typescript/corpus/constructor-call.diffA-B.txt b/test/fixtures/typescript/corpus/constructor-call.diffA-B.txt index 4cd5b5e65..029bd21e8 100644 --- a/test/fixtures/typescript/corpus/constructor-call.diffA-B.txt +++ b/test/fixtures/typescript/corpus/constructor-call.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (New (Call (MemberAccess diff --git a/test/fixtures/typescript/corpus/constructor-call.diffB-A.txt b/test/fixtures/typescript/corpus/constructor-call.diffB-A.txt index 4cd5b5e65..029bd21e8 100644 --- a/test/fixtures/typescript/corpus/constructor-call.diffB-A.txt +++ b/test/fixtures/typescript/corpus/constructor-call.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (New (Call (MemberAccess diff --git a/test/fixtures/typescript/corpus/constructor-call.parseA.txt b/test/fixtures/typescript/corpus/constructor-call.parseA.txt index 14fd6d198..2618e8ed8 100644 --- a/test/fixtures/typescript/corpus/constructor-call.parseA.txt +++ b/test/fixtures/typescript/corpus/constructor-call.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (New (Call (MemberAccess diff --git a/test/fixtures/typescript/corpus/constructor-call.parseB.txt b/test/fixtures/typescript/corpus/constructor-call.parseB.txt index 14fd6d198..2618e8ed8 100644 --- a/test/fixtures/typescript/corpus/constructor-call.parseB.txt +++ b/test/fixtures/typescript/corpus/constructor-call.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (New (Call (MemberAccess diff --git a/test/fixtures/typescript/corpus/continue.diffA-B.txt b/test/fixtures/typescript/corpus/continue.diffA-B.txt index 44e6c7bdc..e57de03a9 100644 --- a/test/fixtures/typescript/corpus/continue.diffA-B.txt +++ b/test/fixtures/typescript/corpus/continue.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/typescript/corpus/continue.diffB-A.txt b/test/fixtures/typescript/corpus/continue.diffB-A.txt index 46eb71902..7a6ade058 100644 --- a/test/fixtures/typescript/corpus/continue.diffB-A.txt +++ b/test/fixtures/typescript/corpus/continue.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/typescript/corpus/continue.parseA.txt b/test/fixtures/typescript/corpus/continue.parseA.txt index 0c30ef033..33b8ce898 100644 --- a/test/fixtures/typescript/corpus/continue.parseA.txt +++ b/test/fixtures/typescript/corpus/continue.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/typescript/corpus/continue.parseB.txt b/test/fixtures/typescript/corpus/continue.parseB.txt index c0af1c973..7e374ef00 100644 --- a/test/fixtures/typescript/corpus/continue.parseB.txt +++ b/test/fixtures/typescript/corpus/continue.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (Assignment (Identifier) diff --git a/test/fixtures/typescript/corpus/delete-operator.diffA-B.txt b/test/fixtures/typescript/corpus/delete-operator.diffA-B.txt index 2208aa02b..7405cd40e 100644 --- a/test/fixtures/typescript/corpus/delete-operator.diffA-B.txt +++ b/test/fixtures/typescript/corpus/delete-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Delete { (Subscript {-(Identifier)-} diff --git a/test/fixtures/typescript/corpus/delete-operator.diffB-A.txt b/test/fixtures/typescript/corpus/delete-operator.diffB-A.txt index b278868d6..f27ec8412 100644 --- a/test/fixtures/typescript/corpus/delete-operator.diffB-A.txt +++ b/test/fixtures/typescript/corpus/delete-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Delete { (MemberAccess {-(Identifier)-} diff --git a/test/fixtures/typescript/corpus/delete-operator.parseA.txt b/test/fixtures/typescript/corpus/delete-operator.parseA.txt index 19f110f27..1f1a1d58f 100644 --- a/test/fixtures/typescript/corpus/delete-operator.parseA.txt +++ b/test/fixtures/typescript/corpus/delete-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Delete (Subscript (Identifier) diff --git a/test/fixtures/typescript/corpus/delete-operator.parseB.txt b/test/fixtures/typescript/corpus/delete-operator.parseB.txt index 36e4bfbaa..310b7babe 100644 --- a/test/fixtures/typescript/corpus/delete-operator.parseB.txt +++ b/test/fixtures/typescript/corpus/delete-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Delete (MemberAccess (Identifier) 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 5935813f5..b2248e3d0 100644 --- a/test/fixtures/typescript/corpus/do-while-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/do-while-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (DoWhile { (Boolean) ->(Boolean) } 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 5935813f5..b2248e3d0 100644 --- a/test/fixtures/typescript/corpus/do-while-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/do-while-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (DoWhile { (Boolean) ->(Boolean) } diff --git a/test/fixtures/typescript/corpus/do-while-statement.parseA.txt b/test/fixtures/typescript/corpus/do-while-statement.parseA.txt index a75cc5e53..d518e0b65 100644 --- a/test/fixtures/typescript/corpus/do-while-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/do-while-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (DoWhile (Boolean) (Statements diff --git a/test/fixtures/typescript/corpus/do-while-statement.parseB.txt b/test/fixtures/typescript/corpus/do-while-statement.parseB.txt index a75cc5e53..d518e0b65 100644 --- a/test/fixtures/typescript/corpus/do-while-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/do-while-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (DoWhile (Boolean) (Statements diff --git a/test/fixtures/typescript/corpus/export-assignments.diffA-B.txt b/test/fixtures/typescript/corpus/export-assignments.diffA-B.txt index 280990a32..7c74f5a57 100644 --- a/test/fixtures/typescript/corpus/export-assignments.diffA-B.txt +++ b/test/fixtures/typescript/corpus/export-assignments.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Return {+(Identifier)+})+} {-(DefaultExport diff --git a/test/fixtures/typescript/corpus/export-assignments.diffB-A.txt b/test/fixtures/typescript/corpus/export-assignments.diffB-A.txt index f27880133..7807f78af 100644 --- a/test/fixtures/typescript/corpus/export-assignments.diffB-A.txt +++ b/test/fixtures/typescript/corpus/export-assignments.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(DefaultExport {+(Identifier)+})+} {-(Return diff --git a/test/fixtures/typescript/corpus/export-assignments.parseA.txt b/test/fixtures/typescript/corpus/export-assignments.parseA.txt index 98edc26e4..bd229965b 100644 --- a/test/fixtures/typescript/corpus/export-assignments.parseA.txt +++ b/test/fixtures/typescript/corpus/export-assignments.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (DefaultExport (Identifier))) diff --git a/test/fixtures/typescript/corpus/export-assignments.parseB.txt b/test/fixtures/typescript/corpus/export-assignments.parseB.txt index a8acb73dc..6a9255a58 100644 --- a/test/fixtures/typescript/corpus/export-assignments.parseB.txt +++ b/test/fixtures/typescript/corpus/export-assignments.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Identifier))) diff --git a/test/fixtures/typescript/corpus/export.diffA-B.txt b/test/fixtures/typescript/corpus/export.diffA-B.txt index c4fcacf9d..2d05a4ca2 100644 --- a/test/fixtures/typescript/corpus/export.diffA-B.txt +++ b/test/fixtures/typescript/corpus/export.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (QualifiedExport) ->(QualifiedExport) } { (QualifiedExport) @@ -35,24 +35,24 @@ (Identifier) { (Empty) ->(Identifier) }) - {+(Assignment - {+(Empty)+} - {+(Identifier)+} - {+(Empty)+})+} (Assignment (Empty) { (Identifier) ->(Identifier) } - (Empty)))) -{+(DefaultExport - {+(Identifier)+})+} + (Empty)) + {+(Assignment + {+(Empty)+} + {+(Identifier)+} + {+(Empty)+})+})) (DefaultExport { (Identifier) - ->(Function + ->(Identifier) }) +{+(DefaultExport + {+(Function {+(Empty)+} {+(Empty)+} {+(Identifier)+} - {+(Statements)+}) }) + {+(Statements)+})+})+} (DefaultExport (Function (Empty) diff --git a/test/fixtures/typescript/corpus/export.diffB-A.txt b/test/fixtures/typescript/corpus/export.diffB-A.txt index 0f430d3a8..25c78e485 100644 --- a/test/fixtures/typescript/corpus/export.diffB-A.txt +++ b/test/fixtures/typescript/corpus/export.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (QualifiedExport) ->(QualifiedExport) } { (QualifiedExport) @@ -35,22 +35,18 @@ (Identifier) { (Identifier) ->(Empty) }) - {+(Assignment - {+(Empty)+} - {+(Identifier)+} - {+(Empty)+})+} - {-(Assignment - {-(Empty)-} - {-(Identifier)-} - {-(Empty)-})-} + (Assignment + (Empty) + { (Identifier) + ->(Identifier) } + (Empty)) {-(Assignment {-(Empty)-} {-(Identifier)-} {-(Empty)-})-})) -{+(DefaultExport - {+(Identifier)+})+} -{-(DefaultExport - {-(Identifier)-})-} + (DefaultExport + { (Identifier) + ->(Identifier) }) {-(DefaultExport {-(Function {-(Empty)-} diff --git a/test/fixtures/typescript/corpus/export.parseA.txt b/test/fixtures/typescript/corpus/export.parseA.txt index c65411988..269ace8d0 100644 --- a/test/fixtures/typescript/corpus/export.parseA.txt +++ b/test/fixtures/typescript/corpus/export.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (QualifiedExport) (QualifiedExport) (DefaultExport diff --git a/test/fixtures/typescript/corpus/export.parseB.txt b/test/fixtures/typescript/corpus/export.parseB.txt index a04091e87..3d01a836a 100644 --- a/test/fixtures/typescript/corpus/export.parseB.txt +++ b/test/fixtures/typescript/corpus/export.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (QualifiedExport) (QualifiedExport) (DefaultExport diff --git a/test/fixtures/typescript/corpus/false.diffA-B.txt b/test/fixtures/typescript/corpus/false.diffA-B.txt index ac2ca170c..62f7e4e3e 100644 --- a/test/fixtures/typescript/corpus/false.diffA-B.txt +++ b/test/fixtures/typescript/corpus/false.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Return {+(Boolean)+})+} {-(Boolean)-}) diff --git a/test/fixtures/typescript/corpus/false.diffB-A.txt b/test/fixtures/typescript/corpus/false.diffB-A.txt index 846a9c224..57c1b8c70 100644 --- a/test/fixtures/typescript/corpus/false.diffB-A.txt +++ b/test/fixtures/typescript/corpus/false.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Boolean)+} {-(Return {-(Boolean)-})-}) diff --git a/test/fixtures/typescript/corpus/false.parseA.txt b/test/fixtures/typescript/corpus/false.parseA.txt index 1fdad7cac..25d98872e 100644 --- a/test/fixtures/typescript/corpus/false.parseA.txt +++ b/test/fixtures/typescript/corpus/false.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Boolean)) diff --git a/test/fixtures/typescript/corpus/false.parseB.txt b/test/fixtures/typescript/corpus/false.parseB.txt index a37bdc4ee..02e3c2a13 100644 --- a/test/fixtures/typescript/corpus/false.parseB.txt +++ b/test/fixtures/typescript/corpus/false.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Boolean))) 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 7f4c7fe4a..d311b808b 100644 --- a/test/fixtures/typescript/corpus/for-in-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/for-in-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForEach { (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 7f4c7fe4a..d311b808b 100644 --- a/test/fixtures/typescript/corpus/for-in-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/for-in-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForEach { (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 79a82b79a..6becb7a8d 100644 --- a/test/fixtures/typescript/corpus/for-in-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/for-in-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForEach (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/for-in-statement.parseB.txt b/test/fixtures/typescript/corpus/for-in-statement.parseB.txt index 79a82b79a..6becb7a8d 100644 --- a/test/fixtures/typescript/corpus/for-in-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/for-in-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForEach (Identifier) (Identifier) 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 e3184832c..bf4e69b44 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 @@ -1,4 +1,4 @@ -(Program +(Statements (For (And (Member 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 e3184832c..bf4e69b44 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 @@ -1,4 +1,4 @@ -(Program +(Statements (For (And (Member 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 0c1d70fb4..a83600b05 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 @@ -1,4 +1,4 @@ -(Program +(Statements (For (And (Member 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 0c1d70fb4..a83600b05 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 @@ -1,4 +1,4 @@ -(Program +(Statements (For (And (Member 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 f5e052f79..a17ddbf18 100644 --- a/test/fixtures/typescript/corpus/for-of-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/for-of-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForOf { (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 f5e052f79..a17ddbf18 100644 --- a/test/fixtures/typescript/corpus/for-of-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/for-of-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForOf { (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 3c9704a36..f7defa7f3 100644 --- a/test/fixtures/typescript/corpus/for-of-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/for-of-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForOf (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 3c9704a36..f7defa7f3 100644 --- a/test/fixtures/typescript/corpus/for-of-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/for-of-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (ForOf (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 1cf044616..5437569a4 100644 --- a/test/fixtures/typescript/corpus/for-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/for-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (SequenceExpression (Assignment diff --git a/test/fixtures/typescript/corpus/for-statement.diffB-A.txt b/test/fixtures/typescript/corpus/for-statement.diffB-A.txt index 1cf044616..5437569a4 100644 --- a/test/fixtures/typescript/corpus/for-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/for-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (SequenceExpression (Assignment diff --git a/test/fixtures/typescript/corpus/for-statement.parseA.txt b/test/fixtures/typescript/corpus/for-statement.parseA.txt index fe2179965..883d1fd1a 100644 --- a/test/fixtures/typescript/corpus/for-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/for-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (SequenceExpression (Assignment diff --git a/test/fixtures/typescript/corpus/for-statement.parseB.txt b/test/fixtures/typescript/corpus/for-statement.parseB.txt index fe2179965..883d1fd1a 100644 --- a/test/fixtures/typescript/corpus/for-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/for-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (For (SequenceExpression (Assignment 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 9ab5e70c0..303706eac 100644 --- a/test/fixtures/typescript/corpus/function-call-args.diffA-B.txt +++ b/test/fixtures/typescript/corpus/function-call-args.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Float) 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 46e0b5c06..8eda0d972 100644 --- a/test/fixtures/typescript/corpus/function-call-args.diffB-A.txt +++ b/test/fixtures/typescript/corpus/function-call-args.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Float) diff --git a/test/fixtures/typescript/corpus/function-call-args.parseA.txt b/test/fixtures/typescript/corpus/function-call-args.parseA.txt index ed0d71201..62f704351 100644 --- a/test/fixtures/typescript/corpus/function-call-args.parseA.txt +++ b/test/fixtures/typescript/corpus/function-call-args.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Float) diff --git a/test/fixtures/typescript/corpus/function-call-args.parseB.txt b/test/fixtures/typescript/corpus/function-call-args.parseB.txt index ed0d71201..62f704351 100644 --- a/test/fixtures/typescript/corpus/function-call-args.parseB.txt +++ b/test/fixtures/typescript/corpus/function-call-args.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (Identifier) (Float) diff --git a/test/fixtures/typescript/corpus/function-call.diffA-B.txt b/test/fixtures/typescript/corpus/function-call.diffA-B.txt index f2fa351c1..61154fe7c 100644 --- a/test/fixtures/typescript/corpus/function-call.diffA-B.txt +++ b/test/fixtures/typescript/corpus/function-call.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call { (TypeIdentifier) ->(TypeIdentifier) } diff --git a/test/fixtures/typescript/corpus/function-call.diffB-A.txt b/test/fixtures/typescript/corpus/function-call.diffB-A.txt index f2fa351c1..61154fe7c 100644 --- a/test/fixtures/typescript/corpus/function-call.diffB-A.txt +++ b/test/fixtures/typescript/corpus/function-call.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call { (TypeIdentifier) ->(TypeIdentifier) } diff --git a/test/fixtures/typescript/corpus/function-call.parseA.txt b/test/fixtures/typescript/corpus/function-call.parseA.txt index b849f4df7..3c5298c68 100644 --- a/test/fixtures/typescript/corpus/function-call.parseA.txt +++ b/test/fixtures/typescript/corpus/function-call.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (TypeIdentifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/function-call.parseB.txt b/test/fixtures/typescript/corpus/function-call.parseB.txt index b849f4df7..3c5298c68 100644 --- a/test/fixtures/typescript/corpus/function-call.parseB.txt +++ b/test/fixtures/typescript/corpus/function-call.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (TypeIdentifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/function-type.diffA-B.txt b/test/fixtures/typescript/corpus/function-type.diffA-B.txt index 0a5fc2d8a..c23155e87 100644 --- a/test/fixtures/typescript/corpus/function-type.diffA-B.txt +++ b/test/fixtures/typescript/corpus/function-type.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/function-type.diffB-A.txt b/test/fixtures/typescript/corpus/function-type.diffB-A.txt index a260139bd..abcf21175 100644 --- a/test/fixtures/typescript/corpus/function-type.diffB-A.txt +++ b/test/fixtures/typescript/corpus/function-type.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/function-type.parseA.txt b/test/fixtures/typescript/corpus/function-type.parseA.txt index f0a329747..9f45697c9 100644 --- a/test/fixtures/typescript/corpus/function-type.parseA.txt +++ b/test/fixtures/typescript/corpus/function-type.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/function-type.parseB.txt b/test/fixtures/typescript/corpus/function-type.parseB.txt index ed3a4660f..3155372a9 100644 --- a/test/fixtures/typescript/corpus/function-type.parseB.txt +++ b/test/fixtures/typescript/corpus/function-type.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/function.diffA-B.txt b/test/fixtures/typescript/corpus/function.diffA-B.txt index 90c7297b0..5c54f63d9 100644 --- a/test/fixtures/typescript/corpus/function.diffA-B.txt +++ b/test/fixtures/typescript/corpus/function.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function {+(Empty)+} {+(Annotation diff --git a/test/fixtures/typescript/corpus/function.diffB-A.txt b/test/fixtures/typescript/corpus/function.diffB-A.txt index a3184822d..7a9134389 100644 --- a/test/fixtures/typescript/corpus/function.diffB-A.txt +++ b/test/fixtures/typescript/corpus/function.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function {+(TypeParameters {+(TypeParameter diff --git a/test/fixtures/typescript/corpus/function.parseA.txt b/test/fixtures/typescript/corpus/function.parseA.txt index b98eff32c..c50656cda 100644 --- a/test/fixtures/typescript/corpus/function.parseA.txt +++ b/test/fixtures/typescript/corpus/function.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (TypeParameters (TypeParameter diff --git a/test/fixtures/typescript/corpus/function.parseB.txt b/test/fixtures/typescript/corpus/function.parseB.txt index 493f1a5fc..ca569aa63 100644 --- a/test/fixtures/typescript/corpus/function.parseB.txt +++ b/test/fixtures/typescript/corpus/function.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Annotation diff --git a/test/fixtures/typescript/corpus/generator-function.diffA-B.txt b/test/fixtures/typescript/corpus/generator-function.diffA-B.txt index 2f4f58433..bcc4a72fd 100644 --- a/test/fixtures/typescript/corpus/generator-function.diffA-B.txt +++ b/test/fixtures/typescript/corpus/generator-function.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/generator-function.diffB-A.txt b/test/fixtures/typescript/corpus/generator-function.diffB-A.txt index 2f4f58433..bcc4a72fd 100644 --- a/test/fixtures/typescript/corpus/generator-function.diffB-A.txt +++ b/test/fixtures/typescript/corpus/generator-function.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/generator-function.parseA.txt b/test/fixtures/typescript/corpus/generator-function.parseA.txt index fd25c91b3..d621cd07d 100644 --- a/test/fixtures/typescript/corpus/generator-function.parseA.txt +++ b/test/fixtures/typescript/corpus/generator-function.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/generator-function.parseB.txt b/test/fixtures/typescript/corpus/generator-function.parseB.txt index fd25c91b3..d621cd07d 100644 --- a/test/fixtures/typescript/corpus/generator-function.parseB.txt +++ b/test/fixtures/typescript/corpus/generator-function.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/identifier.diffA-B.txt b/test/fixtures/typescript/corpus/identifier.diffA-B.txt index 6ac9cd896..d2449f436 100644 --- a/test/fixtures/typescript/corpus/identifier.diffA-B.txt +++ b/test/fixtures/typescript/corpus/identifier.diffA-B.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/typescript/corpus/identifier.diffB-A.txt b/test/fixtures/typescript/corpus/identifier.diffB-A.txt index 6ac9cd896..d2449f436 100644 --- a/test/fixtures/typescript/corpus/identifier.diffB-A.txt +++ b/test/fixtures/typescript/corpus/identifier.diffB-A.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/typescript/corpus/identifier.parseA.txt b/test/fixtures/typescript/corpus/identifier.parseA.txt index 67b75f388..5f0ab64c1 100644 --- a/test/fixtures/typescript/corpus/identifier.parseA.txt +++ b/test/fixtures/typescript/corpus/identifier.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Identifier)) diff --git a/test/fixtures/typescript/corpus/identifier.parseB.txt b/test/fixtures/typescript/corpus/identifier.parseB.txt index 67b75f388..5f0ab64c1 100644 --- a/test/fixtures/typescript/corpus/identifier.parseB.txt +++ b/test/fixtures/typescript/corpus/identifier.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Identifier)) diff --git a/test/fixtures/typescript/corpus/if-else.diffA-B.txt b/test/fixtures/typescript/corpus/if-else.diffA-B.txt index 41281f5e5..c11bb2001 100644 --- a/test/fixtures/typescript/corpus/if-else.diffA-B.txt +++ b/test/fixtures/typescript/corpus/if-else.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If { (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 a7e842460..8c5267811 100644 --- a/test/fixtures/typescript/corpus/if-else.diffB-A.txt +++ b/test/fixtures/typescript/corpus/if-else.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If { (Identifier) ->(Identifier) } diff --git a/test/fixtures/typescript/corpus/if-else.parseA.txt b/test/fixtures/typescript/corpus/if-else.parseA.txt index f3737b63e..09d678134 100644 --- a/test/fixtures/typescript/corpus/if-else.parseA.txt +++ b/test/fixtures/typescript/corpus/if-else.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/if-else.parseB.txt b/test/fixtures/typescript/corpus/if-else.parseB.txt index 2402f8fd0..49c8b8af1 100644 --- a/test/fixtures/typescript/corpus/if-else.parseB.txt +++ b/test/fixtures/typescript/corpus/if-else.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/if.diffA-B.txt b/test/fixtures/typescript/corpus/if.diffA-B.txt index 329dbee61..dc1da1028 100644 --- a/test/fixtures/typescript/corpus/if.diffA-B.txt +++ b/test/fixtures/typescript/corpus/if.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If { (Identifier) ->(MemberAccess diff --git a/test/fixtures/typescript/corpus/if.diffB-A.txt b/test/fixtures/typescript/corpus/if.diffB-A.txt index 58379f889..1f5a16737 100644 --- a/test/fixtures/typescript/corpus/if.diffB-A.txt +++ b/test/fixtures/typescript/corpus/if.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If { (MemberAccess {-(Identifier)-} diff --git a/test/fixtures/typescript/corpus/if.parseA.txt b/test/fixtures/typescript/corpus/if.parseA.txt index c319b1eb0..63f3ac321 100644 --- a/test/fixtures/typescript/corpus/if.parseA.txt +++ b/test/fixtures/typescript/corpus/if.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Identifier) (Statements diff --git a/test/fixtures/typescript/corpus/if.parseB.txt b/test/fixtures/typescript/corpus/if.parseB.txt index 4c23c44b9..0b58858fd 100644 --- a/test/fixtures/typescript/corpus/if.parseB.txt +++ b/test/fixtures/typescript/corpus/if.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/import.diffA-B.txt b/test/fixtures/typescript/corpus/import.diffA-B.txt index b7e287342..5da631177 100644 --- a/test/fixtures/typescript/corpus/import.diffA-B.txt +++ b/test/fixtures/typescript/corpus/import.diffA-B.txt @@ -1,8 +1,9 @@ -(Program +(Statements {+(Import)+} {+(QualifiedAliasedImport {+(Identifier)+})+} -{+(Import)+} +{ (Import) +->(Import) } {+(Import)+} {+(Import)+} {+(Statements @@ -13,7 +14,6 @@ {+(QualifiedAliasedImport {+(Identifier)+})+})+} {+(SideEffectImport)+} -{-(Import)-} {-(QualifiedAliasedImport {-(Identifier)-})-} {-(Import)-} diff --git a/test/fixtures/typescript/corpus/import.diffB-A.txt b/test/fixtures/typescript/corpus/import.diffB-A.txt index ed443bef3..b19df5534 100644 --- a/test/fixtures/typescript/corpus/import.diffB-A.txt +++ b/test/fixtures/typescript/corpus/import.diffB-A.txt @@ -1,9 +1,8 @@ -(Program +(Statements {+(Import)+} {+(QualifiedAliasedImport {+(Identifier)+})+} -{ (Import) -->(Import) } +{+(Import)+} {+(Import)+} {+(Import)+} {+(Statements @@ -16,6 +15,7 @@ {+(SideEffectImport)+} {+(QualifiedAliasedImport {+(Identifier)+})+} +{-(Import)-} {-(QualifiedAliasedImport {-(Identifier)-})-} {-(Import)-} diff --git a/test/fixtures/typescript/corpus/import.parseA.txt b/test/fixtures/typescript/corpus/import.parseA.txt index 0441b60eb..df178a4be 100644 --- a/test/fixtures/typescript/corpus/import.parseA.txt +++ b/test/fixtures/typescript/corpus/import.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Import) (QualifiedAliasedImport (Identifier)) diff --git a/test/fixtures/typescript/corpus/import.parseB.txt b/test/fixtures/typescript/corpus/import.parseB.txt index 069afffe6..828eb6ea7 100644 --- a/test/fixtures/typescript/corpus/import.parseB.txt +++ b/test/fixtures/typescript/corpus/import.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Import) (QualifiedAliasedImport (Identifier)) diff --git a/test/fixtures/typescript/corpus/interface.diffA-B.txt b/test/fixtures/typescript/corpus/interface.diffA-B.txt index eb5d80467..5010c4149 100644 --- a/test/fixtures/typescript/corpus/interface.diffA-B.txt +++ b/test/fixtures/typescript/corpus/interface.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (InterfaceDeclaration {-(TypeParameters {-(TypeParameter diff --git a/test/fixtures/typescript/corpus/interface.diffB-A.txt b/test/fixtures/typescript/corpus/interface.diffB-A.txt index 61744ba1e..09d1a01c7 100644 --- a/test/fixtures/typescript/corpus/interface.diffB-A.txt +++ b/test/fixtures/typescript/corpus/interface.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (InterfaceDeclaration {+(TypeParameters {+(TypeParameter diff --git a/test/fixtures/typescript/corpus/interface.parseA.txt b/test/fixtures/typescript/corpus/interface.parseA.txt index 99f4125d3..9cb98a509 100644 --- a/test/fixtures/typescript/corpus/interface.parseA.txt +++ b/test/fixtures/typescript/corpus/interface.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (InterfaceDeclaration (TypeParameters (TypeParameter diff --git a/test/fixtures/typescript/corpus/interface.parseB.txt b/test/fixtures/typescript/corpus/interface.parseB.txt index 97d1ef48b..d08c9ddce 100644 --- a/test/fixtures/typescript/corpus/interface.parseB.txt +++ b/test/fixtures/typescript/corpus/interface.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (InterfaceDeclaration (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/intersection-type.diffA-B.txt b/test/fixtures/typescript/corpus/intersection-type.diffA-B.txt index 772fde238..fc2af5686 100644 --- a/test/fixtures/typescript/corpus/intersection-type.diffA-B.txt +++ b/test/fixtures/typescript/corpus/intersection-type.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/intersection-type.diffB-A.txt b/test/fixtures/typescript/corpus/intersection-type.diffB-A.txt index ae2915e67..d43cb00ca 100644 --- a/test/fixtures/typescript/corpus/intersection-type.diffB-A.txt +++ b/test/fixtures/typescript/corpus/intersection-type.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/intersection-type.parseA.txt b/test/fixtures/typescript/corpus/intersection-type.parseA.txt index a47aea539..65cacc725 100644 --- a/test/fixtures/typescript/corpus/intersection-type.parseA.txt +++ b/test/fixtures/typescript/corpus/intersection-type.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/intersection-type.parseB.txt b/test/fixtures/typescript/corpus/intersection-type.parseB.txt index 35b6f9485..0d8b6cb08 100644 --- a/test/fixtures/typescript/corpus/intersection-type.parseB.txt +++ b/test/fixtures/typescript/corpus/intersection-type.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/jsx-elements.diffA-B.txt b/test/fixtures/typescript/corpus/jsx-elements.diffA-B.txt index 222aaadd2..9e330c8d5 100644 --- a/test/fixtures/typescript/corpus/jsx-elements.diffA-B.txt +++ b/test/fixtures/typescript/corpus/jsx-elements.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/jsx-elements.diffB-A.txt b/test/fixtures/typescript/corpus/jsx-elements.diffB-A.txt index 621841a81..6f4ba9f23 100644 --- a/test/fixtures/typescript/corpus/jsx-elements.diffB-A.txt +++ b/test/fixtures/typescript/corpus/jsx-elements.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/jsx-elements.parseA.txt b/test/fixtures/typescript/corpus/jsx-elements.parseA.txt index 1aea1cfe1..85d98a035 100644 --- a/test/fixtures/typescript/corpus/jsx-elements.parseA.txt +++ b/test/fixtures/typescript/corpus/jsx-elements.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/jsx-elements.parseB.txt b/test/fixtures/typescript/corpus/jsx-elements.parseB.txt index e774bc0c4..32aee1e26 100644 --- a/test/fixtures/typescript/corpus/jsx-elements.parseB.txt +++ b/test/fixtures/typescript/corpus/jsx-elements.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/math-assignment-operator.diffA-B.txt b/test/fixtures/typescript/corpus/math-assignment-operator.diffA-B.txt index 467bac8dc..b1aa79ef3 100644 --- a/test/fixtures/typescript/corpus/math-assignment-operator.diffA-B.txt +++ b/test/fixtures/typescript/corpus/math-assignment-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Plus diff --git a/test/fixtures/typescript/corpus/math-assignment-operator.diffB-A.txt b/test/fixtures/typescript/corpus/math-assignment-operator.diffB-A.txt index 467bac8dc..b1aa79ef3 100644 --- a/test/fixtures/typescript/corpus/math-assignment-operator.diffB-A.txt +++ b/test/fixtures/typescript/corpus/math-assignment-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Plus diff --git a/test/fixtures/typescript/corpus/math-assignment-operator.parseA.txt b/test/fixtures/typescript/corpus/math-assignment-operator.parseA.txt index f6247a719..5403b2a5e 100644 --- a/test/fixtures/typescript/corpus/math-assignment-operator.parseA.txt +++ b/test/fixtures/typescript/corpus/math-assignment-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Plus diff --git a/test/fixtures/typescript/corpus/math-assignment-operator.parseB.txt b/test/fixtures/typescript/corpus/math-assignment-operator.parseB.txt index f6247a719..5403b2a5e 100644 --- a/test/fixtures/typescript/corpus/math-assignment-operator.parseB.txt +++ b/test/fixtures/typescript/corpus/math-assignment-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Identifier) (Plus diff --git a/test/fixtures/typescript/corpus/math-operator.diffA-B.txt b/test/fixtures/typescript/corpus/math-operator.diffA-B.txt index 48df33060..a7c867465 100644 --- a/test/fixtures/typescript/corpus/math-operator.diffA-B.txt +++ b/test/fixtures/typescript/corpus/math-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Minus (Plus (Identifier) diff --git a/test/fixtures/typescript/corpus/math-operator.diffB-A.txt b/test/fixtures/typescript/corpus/math-operator.diffB-A.txt index 48df33060..a7c867465 100644 --- a/test/fixtures/typescript/corpus/math-operator.diffB-A.txt +++ b/test/fixtures/typescript/corpus/math-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Minus (Plus (Identifier) diff --git a/test/fixtures/typescript/corpus/math-operator.parseA.txt b/test/fixtures/typescript/corpus/math-operator.parseA.txt index f18864aac..023fa5c6a 100644 --- a/test/fixtures/typescript/corpus/math-operator.parseA.txt +++ b/test/fixtures/typescript/corpus/math-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Minus (Plus (Identifier) diff --git a/test/fixtures/typescript/corpus/math-operator.parseB.txt b/test/fixtures/typescript/corpus/math-operator.parseB.txt index f18864aac..023fa5c6a 100644 --- a/test/fixtures/typescript/corpus/math-operator.parseB.txt +++ b/test/fixtures/typescript/corpus/math-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Minus (Plus (Identifier) diff --git a/test/fixtures/typescript/corpus/member-access-assignment.diffA-B.txt b/test/fixtures/typescript/corpus/member-access-assignment.diffA-B.txt index 971eac6e7..6ddc09680 100644 --- a/test/fixtures/typescript/corpus/member-access-assignment.diffA-B.txt +++ b/test/fixtures/typescript/corpus/member-access-assignment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/member-access-assignment.diffB-A.txt b/test/fixtures/typescript/corpus/member-access-assignment.diffB-A.txt index 971eac6e7..6ddc09680 100644 --- a/test/fixtures/typescript/corpus/member-access-assignment.diffB-A.txt +++ b/test/fixtures/typescript/corpus/member-access-assignment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/member-access-assignment.parseA.txt b/test/fixtures/typescript/corpus/member-access-assignment.parseA.txt index 7d15e4ab4..a4d274369 100644 --- a/test/fixtures/typescript/corpus/member-access-assignment.parseA.txt +++ b/test/fixtures/typescript/corpus/member-access-assignment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/member-access-assignment.parseB.txt b/test/fixtures/typescript/corpus/member-access-assignment.parseB.txt index 7d15e4ab4..a4d274369 100644 --- a/test/fixtures/typescript/corpus/member-access-assignment.parseB.txt +++ b/test/fixtures/typescript/corpus/member-access-assignment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/member-access.diffA-B.txt b/test/fixtures/typescript/corpus/member-access.diffA-B.txt index 032d939dd..e09883b07 100644 --- a/test/fixtures/typescript/corpus/member-access.diffA-B.txt +++ b/test/fixtures/typescript/corpus/member-access.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess (Identifier) { (Identifier) diff --git a/test/fixtures/typescript/corpus/member-access.diffB-A.txt b/test/fixtures/typescript/corpus/member-access.diffB-A.txt index 032d939dd..e09883b07 100644 --- a/test/fixtures/typescript/corpus/member-access.diffB-A.txt +++ b/test/fixtures/typescript/corpus/member-access.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess (Identifier) { (Identifier) diff --git a/test/fixtures/typescript/corpus/member-access.parseA.txt b/test/fixtures/typescript/corpus/member-access.parseA.txt index 3a5c9e565..70674960a 100644 --- a/test/fixtures/typescript/corpus/member-access.parseA.txt +++ b/test/fixtures/typescript/corpus/member-access.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess (Identifier) (Identifier))) diff --git a/test/fixtures/typescript/corpus/member-access.parseB.txt b/test/fixtures/typescript/corpus/member-access.parseB.txt index 3a5c9e565..70674960a 100644 --- a/test/fixtures/typescript/corpus/member-access.parseB.txt +++ b/test/fixtures/typescript/corpus/member-access.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (MemberAccess (Identifier) (Identifier))) diff --git a/test/fixtures/typescript/corpus/method-call.diffA-B.txt b/test/fixtures/typescript/corpus/method-call.diffA-B.txt index 04b6484e5..6eafae55c 100644 --- a/test/fixtures/typescript/corpus/method-call.diffA-B.txt +++ b/test/fixtures/typescript/corpus/method-call.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/method-call.diffB-A.txt b/test/fixtures/typescript/corpus/method-call.diffB-A.txt index 04b6484e5..6eafae55c 100644 --- a/test/fixtures/typescript/corpus/method-call.diffB-A.txt +++ b/test/fixtures/typescript/corpus/method-call.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/method-call.parseA.txt b/test/fixtures/typescript/corpus/method-call.parseA.txt index 1bc561706..447b0ae78 100644 --- a/test/fixtures/typescript/corpus/method-call.parseA.txt +++ b/test/fixtures/typescript/corpus/method-call.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/method-call.parseB.txt b/test/fixtures/typescript/corpus/method-call.parseB.txt index 1bc561706..447b0ae78 100644 --- a/test/fixtures/typescript/corpus/method-call.parseB.txt +++ b/test/fixtures/typescript/corpus/method-call.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Call (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/method-definition.diffA-B.txt b/test/fixtures/typescript/corpus/method-definition.diffA-B.txt index 8c1179c02..0bbb52aaa 100644 --- a/test/fixtures/typescript/corpus/method-definition.diffA-B.txt +++ b/test/fixtures/typescript/corpus/method-definition.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Method diff --git a/test/fixtures/typescript/corpus/method-definition.diffB-A.txt b/test/fixtures/typescript/corpus/method-definition.diffB-A.txt index de3d7407c..2b621eb4b 100644 --- a/test/fixtures/typescript/corpus/method-definition.diffB-A.txt +++ b/test/fixtures/typescript/corpus/method-definition.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Method diff --git a/test/fixtures/typescript/corpus/method-definition.parseA.txt b/test/fixtures/typescript/corpus/method-definition.parseA.txt index be3406a4f..1845562be 100644 --- a/test/fixtures/typescript/corpus/method-definition.parseA.txt +++ b/test/fixtures/typescript/corpus/method-definition.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Method diff --git a/test/fixtures/typescript/corpus/method-definition.parseB.txt b/test/fixtures/typescript/corpus/method-definition.parseB.txt index 5f149585f..23f2869f3 100644 --- a/test/fixtures/typescript/corpus/method-definition.parseB.txt +++ b/test/fixtures/typescript/corpus/method-definition.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Method diff --git a/test/fixtures/typescript/corpus/module-declarations.diffA-B.txt b/test/fixtures/typescript/corpus/module-declarations.diffA-B.txt index 59bca14b9..4ec6628a0 100644 --- a/test/fixtures/typescript/corpus/module-declarations.diffA-B.txt +++ b/test/fixtures/typescript/corpus/module-declarations.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(AmbientDeclaration {+(InternalModule {+(Identifier)+})+})+} diff --git a/test/fixtures/typescript/corpus/module-declarations.diffB-A.txt b/test/fixtures/typescript/corpus/module-declarations.diffB-A.txt index 3a2174e51..619ef9184 100644 --- a/test/fixtures/typescript/corpus/module-declarations.diffB-A.txt +++ b/test/fixtures/typescript/corpus/module-declarations.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Module {+(Identifier)+})+} {-(AmbientDeclaration diff --git a/test/fixtures/typescript/corpus/module-declarations.parseA.txt b/test/fixtures/typescript/corpus/module-declarations.parseA.txt index 735cd4d9b..93d305e37 100644 --- a/test/fixtures/typescript/corpus/module-declarations.parseA.txt +++ b/test/fixtures/typescript/corpus/module-declarations.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Module (Identifier))) diff --git a/test/fixtures/typescript/corpus/module-declarations.parseB.txt b/test/fixtures/typescript/corpus/module-declarations.parseB.txt index 6b361c618..63b454b60 100644 --- a/test/fixtures/typescript/corpus/module-declarations.parseB.txt +++ b/test/fixtures/typescript/corpus/module-declarations.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (AmbientDeclaration (InternalModule (Identifier)))) diff --git a/test/fixtures/typescript/corpus/named-function.diffA-B.txt b/test/fixtures/typescript/corpus/named-function.diffA-B.txt index aec245b08..e78597819 100644 --- a/test/fixtures/typescript/corpus/named-function.diffA-B.txt +++ b/test/fixtures/typescript/corpus/named-function.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/named-function.diffB-A.txt b/test/fixtures/typescript/corpus/named-function.diffB-A.txt index 8ac7047e0..e88fc69f9 100644 --- a/test/fixtures/typescript/corpus/named-function.diffB-A.txt +++ b/test/fixtures/typescript/corpus/named-function.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/named-function.parseA.txt b/test/fixtures/typescript/corpus/named-function.parseA.txt index a0596d5bd..d03c49b95 100644 --- a/test/fixtures/typescript/corpus/named-function.parseA.txt +++ b/test/fixtures/typescript/corpus/named-function.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/named-function.parseB.txt b/test/fixtures/typescript/corpus/named-function.parseB.txt index 96d3c4033..791208cdc 100644 --- a/test/fixtures/typescript/corpus/named-function.parseB.txt +++ b/test/fixtures/typescript/corpus/named-function.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (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 00dd2f4a3..016ca6847 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) 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 00dd2f4a3..016ca6847 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) 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 618761627..fec2a038f 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) 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 618761627..fec2a038f 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 @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/nested-functions.diffA-B.txt b/test/fixtures/typescript/corpus/nested-functions.diffA-B.txt index 2a221fcdd..3882a7fe2 100644 --- a/test/fixtures/typescript/corpus/nested-functions.diffA-B.txt +++ b/test/fixtures/typescript/corpus/nested-functions.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/nested-functions.diffB-A.txt b/test/fixtures/typescript/corpus/nested-functions.diffB-A.txt index 2a221fcdd..3882a7fe2 100644 --- a/test/fixtures/typescript/corpus/nested-functions.diffB-A.txt +++ b/test/fixtures/typescript/corpus/nested-functions.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/nested-functions.parseA.txt b/test/fixtures/typescript/corpus/nested-functions.parseA.txt index bba0968bd..3d8dd1f13 100644 --- a/test/fixtures/typescript/corpus/nested-functions.parseA.txt +++ b/test/fixtures/typescript/corpus/nested-functions.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/nested-functions.parseB.txt b/test/fixtures/typescript/corpus/nested-functions.parseB.txt index bba0968bd..3d8dd1f13 100644 --- a/test/fixtures/typescript/corpus/nested-functions.parseB.txt +++ b/test/fixtures/typescript/corpus/nested-functions.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/null.diffA-B.txt b/test/fixtures/typescript/corpus/null.diffA-B.txt index 4d48f1e43..8b3d414fd 100644 --- a/test/fixtures/typescript/corpus/null.diffA-B.txt +++ b/test/fixtures/typescript/corpus/null.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Return {+(Null)+})+} {-(Null)-}) diff --git a/test/fixtures/typescript/corpus/null.diffB-A.txt b/test/fixtures/typescript/corpus/null.diffB-A.txt index 08550b95d..b56dab77f 100644 --- a/test/fixtures/typescript/corpus/null.diffB-A.txt +++ b/test/fixtures/typescript/corpus/null.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Null)+} {-(Return {-(Null)-})-}) diff --git a/test/fixtures/typescript/corpus/null.parseA.txt b/test/fixtures/typescript/corpus/null.parseA.txt index d6499ddef..5c722556e 100644 --- a/test/fixtures/typescript/corpus/null.parseA.txt +++ b/test/fixtures/typescript/corpus/null.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Null)) diff --git a/test/fixtures/typescript/corpus/null.parseB.txt b/test/fixtures/typescript/corpus/null.parseB.txt index 1572f3d32..24f16825d 100644 --- a/test/fixtures/typescript/corpus/null.parseB.txt +++ b/test/fixtures/typescript/corpus/null.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Null))) diff --git a/test/fixtures/typescript/corpus/number.diffA-B.txt b/test/fixtures/typescript/corpus/number.diffA-B.txt index 9c7b7f65e..dedbdd592 100644 --- a/test/fixtures/typescript/corpus/number.diffA-B.txt +++ b/test/fixtures/typescript/corpus/number.diffA-B.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Float) ->(Float) }) diff --git a/test/fixtures/typescript/corpus/number.diffB-A.txt b/test/fixtures/typescript/corpus/number.diffB-A.txt index 9c7b7f65e..dedbdd592 100644 --- a/test/fixtures/typescript/corpus/number.diffB-A.txt +++ b/test/fixtures/typescript/corpus/number.diffB-A.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Float) ->(Float) }) diff --git a/test/fixtures/typescript/corpus/number.parseA.txt b/test/fixtures/typescript/corpus/number.parseA.txt index ef448a3ab..ca689125a 100644 --- a/test/fixtures/typescript/corpus/number.parseA.txt +++ b/test/fixtures/typescript/corpus/number.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Float)) diff --git a/test/fixtures/typescript/corpus/number.parseB.txt b/test/fixtures/typescript/corpus/number.parseB.txt index ef448a3ab..ca689125a 100644 --- a/test/fixtures/typescript/corpus/number.parseB.txt +++ b/test/fixtures/typescript/corpus/number.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Float)) diff --git a/test/fixtures/typescript/corpus/object.diffA-B.txt b/test/fixtures/typescript/corpus/object.diffA-B.txt index f6f828919..98d338876 100644 --- a/test/fixtures/typescript/corpus/object.diffA-B.txt +++ b/test/fixtures/typescript/corpus/object.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (KeyValue (TextElement) diff --git a/test/fixtures/typescript/corpus/object.diffB-A.txt b/test/fixtures/typescript/corpus/object.diffB-A.txt index 941bef337..647a9c7eb 100644 --- a/test/fixtures/typescript/corpus/object.diffB-A.txt +++ b/test/fixtures/typescript/corpus/object.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (KeyValue (TextElement) diff --git a/test/fixtures/typescript/corpus/object.parseA.txt b/test/fixtures/typescript/corpus/object.parseA.txt index 29f6b615c..7a96e8f9f 100644 --- a/test/fixtures/typescript/corpus/object.parseA.txt +++ b/test/fixtures/typescript/corpus/object.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (KeyValue (TextElement) diff --git a/test/fixtures/typescript/corpus/object.parseB.txt b/test/fixtures/typescript/corpus/object.parseB.txt index 54fac815b..a99262911 100644 --- a/test/fixtures/typescript/corpus/object.parseB.txt +++ b/test/fixtures/typescript/corpus/object.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (KeyValue (TextElement) 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 9c40be32f..55487ab44 100644 --- a/test/fixtures/typescript/corpus/objects-with-methods.diffA-B.txt +++ b/test/fixtures/typescript/corpus/objects-with-methods.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (Method (Empty) 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 914db2372..069f3780f 100644 --- a/test/fixtures/typescript/corpus/objects-with-methods.diffB-A.txt +++ b/test/fixtures/typescript/corpus/objects-with-methods.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (Method (Empty) diff --git a/test/fixtures/typescript/corpus/objects-with-methods.parseA.txt b/test/fixtures/typescript/corpus/objects-with-methods.parseA.txt index 618957d0f..6f7f53d13 100644 --- a/test/fixtures/typescript/corpus/objects-with-methods.parseA.txt +++ b/test/fixtures/typescript/corpus/objects-with-methods.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (Method (Empty) diff --git a/test/fixtures/typescript/corpus/objects-with-methods.parseB.txt b/test/fixtures/typescript/corpus/objects-with-methods.parseB.txt index 8acf4faff..423132fb8 100644 --- a/test/fixtures/typescript/corpus/objects-with-methods.parseB.txt +++ b/test/fixtures/typescript/corpus/objects-with-methods.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Hash (Method (Empty) 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 155fe53f0..e86e54cb2 100644 --- a/test/fixtures/typescript/corpus/public-field-definition.diffA-B.txt +++ b/test/fixtures/typescript/corpus/public-field-definition.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Statements @@ -51,36 +51,57 @@ (TypeIdentifier)) (Identifier) (Float)) - (PublicFieldDefinition + {+(PublicFieldDefinition {+(Identifier)+} - (Empty) - {-(Readonly)-} - (Annotation - (TypeIdentifier)) - (Identifier) - (Float)) - (PublicFieldDefinition + {+(Empty)+} + {+(Annotation + {+(TypeIdentifier)+})+} {+(Identifier)+} + {+(Float)+})+} + {+(PublicFieldDefinition + {+(Identifier)+} + {+(Readonly)+} + {+(Annotation + {+(TypeIdentifier)+})+} + {+(Identifier)+} + {+(TextElement)+})+} + {+(PublicFieldDefinition + {+(Empty)+} + {+(Empty)+} + {+(Annotation + {+(TypeIdentifier)+})+} + {+(Identifier)+} + {+(Float)+})+} + {+(PublicFieldDefinition + {+(Empty)+} + {+(Empty)+} + {+(Empty)+} + {+(Identifier)+} + {+(Float)+})+} + {-(PublicFieldDefinition {-(Empty)-} - (Readonly) - (Annotation - { (TypeIdentifier) - ->(TypeIdentifier) }) - (Identifier) - { (Float) - ->(TextElement) }) - (PublicFieldDefinition - (Empty) - (Empty) - (Annotation - (TypeIdentifier)) - { (Identifier) - ->(Identifier) } - (Float)) - (PublicFieldDefinition - (Empty) - (Empty) - (Empty) - (Identifier) - { (Float) - ->(Float) })))) + {-(Readonly)-} + {-(Annotation + {-(TypeIdentifier)-})-} + {-(Identifier)-} + {-(Float)-})-} + {-(PublicFieldDefinition + {-(Empty)-} + {-(Readonly)-} + {-(Annotation + {-(TypeIdentifier)-})-} + {-(Identifier)-} + {-(Float)-})-} + {-(PublicFieldDefinition + {-(Empty)-} + {-(Empty)-} + {-(Annotation + {-(TypeIdentifier)-})-} + {-(Identifier)-} + {-(Float)-})-} + {-(PublicFieldDefinition + {-(Empty)-} + {-(Empty)-} + {-(Empty)-} + {-(Identifier)-} + {-(Float)-})-}))) 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 3fb59ca0b..e4fa83949 100644 --- a/test/fixtures/typescript/corpus/public-field-definition.diffB-A.txt +++ b/test/fixtures/typescript/corpus/public-field-definition.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Statements @@ -51,36 +51,52 @@ (TypeIdentifier)) (Identifier) (Float)) - (PublicFieldDefinition - {-(Identifier)-} - (Empty) - {+(Readonly)+} - (Annotation - (TypeIdentifier)) - (Identifier) - (Float)) - (PublicFieldDefinition + {+(PublicFieldDefinition {+(Empty)+} - {-(Identifier)-} - (Readonly) - (Annotation - { (TypeIdentifier) - ->(TypeIdentifier) }) - (Identifier) - { (TextElement) - ->(Float) }) + {+(Readonly)+} + {+(Annotation + {+(TypeIdentifier)+})+} + {+(Identifier)+} + {+(Float)+})+} + {+(PublicFieldDefinition + {+(Empty)+} + {+(Readonly)+} + {+(Annotation + {+(TypeIdentifier)+})+} + {+(Identifier)+} + {+(Float)+})+} (PublicFieldDefinition + {-(Identifier)-} (Empty) - (Empty) + {+(Empty)+} (Annotation (TypeIdentifier)) { (Identifier) ->(Identifier) } (Float)) - (PublicFieldDefinition - (Empty) - (Empty) - (Empty) - (Identifier) - { (Float) - ->(Float) })))) + {+(PublicFieldDefinition + {+(Empty)+} + {+(Empty)+} + {+(Empty)+} + {+(Identifier)+} + {+(Float)+})+} + {-(PublicFieldDefinition + {-(Identifier)-} + {-(Readonly)-} + {-(Annotation + {-(TypeIdentifier)-})-} + {-(Identifier)-} + {-(TextElement)-})-} + {-(PublicFieldDefinition + {-(Empty)-} + {-(Empty)-} + {-(Annotation + {-(TypeIdentifier)-})-} + {-(Identifier)-} + {-(Float)-})-} + {-(PublicFieldDefinition + {-(Empty)-} + {-(Empty)-} + {-(Empty)-} + {-(Identifier)-} + {-(Float)-})-}))) diff --git a/test/fixtures/typescript/corpus/public-field-definition.parseA.txt b/test/fixtures/typescript/corpus/public-field-definition.parseA.txt index 2076494be..c4fc6b5d6 100644 --- a/test/fixtures/typescript/corpus/public-field-definition.parseA.txt +++ b/test/fixtures/typescript/corpus/public-field-definition.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Statements diff --git a/test/fixtures/typescript/corpus/public-field-definition.parseB.txt b/test/fixtures/typescript/corpus/public-field-definition.parseB.txt index 1bec273f5..1e58aa5c4 100644 --- a/test/fixtures/typescript/corpus/public-field-definition.parseB.txt +++ b/test/fixtures/typescript/corpus/public-field-definition.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Class (Identifier) (Statements diff --git a/test/fixtures/typescript/corpus/regex.diffA-B.txt b/test/fixtures/typescript/corpus/regex.diffA-B.txt index 9c5e630f5..adc40c12d 100644 --- a/test/fixtures/typescript/corpus/regex.diffA-B.txt +++ b/test/fixtures/typescript/corpus/regex.diffA-B.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Regex) ->(Regex) }) diff --git a/test/fixtures/typescript/corpus/regex.diffB-A.txt b/test/fixtures/typescript/corpus/regex.diffB-A.txt index 9c5e630f5..adc40c12d 100644 --- a/test/fixtures/typescript/corpus/regex.diffB-A.txt +++ b/test/fixtures/typescript/corpus/regex.diffB-A.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Regex) ->(Regex) }) diff --git a/test/fixtures/typescript/corpus/regex.parseA.txt b/test/fixtures/typescript/corpus/regex.parseA.txt index a72f52076..b154d3ebe 100644 --- a/test/fixtures/typescript/corpus/regex.parseA.txt +++ b/test/fixtures/typescript/corpus/regex.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Regex)) diff --git a/test/fixtures/typescript/corpus/regex.parseB.txt b/test/fixtures/typescript/corpus/regex.parseB.txt index a72f52076..b154d3ebe 100644 --- a/test/fixtures/typescript/corpus/regex.parseB.txt +++ b/test/fixtures/typescript/corpus/regex.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Regex)) diff --git a/test/fixtures/typescript/corpus/relational-operator.diffA-B.txt b/test/fixtures/typescript/corpus/relational-operator.diffA-B.txt index b10fba844..d98198807 100644 --- a/test/fixtures/typescript/corpus/relational-operator.diffA-B.txt +++ b/test/fixtures/typescript/corpus/relational-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (LessThan {-(Identifier)-} {-(Identifier)-}) diff --git a/test/fixtures/typescript/corpus/relational-operator.diffB-A.txt b/test/fixtures/typescript/corpus/relational-operator.diffB-A.txt index 811022c76..17bca315b 100644 --- a/test/fixtures/typescript/corpus/relational-operator.diffB-A.txt +++ b/test/fixtures/typescript/corpus/relational-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements { (LessThanEqual {-(Identifier)-} {-(Identifier)-}) diff --git a/test/fixtures/typescript/corpus/relational-operator.parseA.txt b/test/fixtures/typescript/corpus/relational-operator.parseA.txt index 5e1d59256..4bacd5c81 100644 --- a/test/fixtures/typescript/corpus/relational-operator.parseA.txt +++ b/test/fixtures/typescript/corpus/relational-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (LessThan (Identifier) (Identifier))) diff --git a/test/fixtures/typescript/corpus/relational-operator.parseB.txt b/test/fixtures/typescript/corpus/relational-operator.parseB.txt index 31b057eaf..eb9125c71 100644 --- a/test/fixtures/typescript/corpus/relational-operator.parseB.txt +++ b/test/fixtures/typescript/corpus/relational-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (LessThanEqual (Identifier) (Identifier))) diff --git a/test/fixtures/typescript/corpus/return-statement.diffA-B.txt b/test/fixtures/typescript/corpus/return-statement.diffA-B.txt index fc7cd4365..f18860ea0 100644 --- a/test/fixtures/typescript/corpus/return-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/return-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return { (Float) ->(Empty) })) diff --git a/test/fixtures/typescript/corpus/return-statement.diffB-A.txt b/test/fixtures/typescript/corpus/return-statement.diffB-A.txt index b7288ed17..883b736a6 100644 --- a/test/fixtures/typescript/corpus/return-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/return-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Return { (Empty) ->(Float) })) diff --git a/test/fixtures/typescript/corpus/return-statement.parseA.txt b/test/fixtures/typescript/corpus/return-statement.parseA.txt index c116bee18..fd629221e 100644 --- a/test/fixtures/typescript/corpus/return-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/return-statement.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Float))) diff --git a/test/fixtures/typescript/corpus/return-statement.parseB.txt b/test/fixtures/typescript/corpus/return-statement.parseB.txt index 7d27dcae1..878ee5e75 100644 --- a/test/fixtures/typescript/corpus/return-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/return-statement.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Empty))) diff --git a/test/fixtures/typescript/corpus/string.diffA-B.txt b/test/fixtures/typescript/corpus/string.diffA-B.txt index c368003ca..93e83c046 100644 --- a/test/fixtures/typescript/corpus/string.diffA-B.txt +++ b/test/fixtures/typescript/corpus/string.diffA-B.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (TextElement) ->(TextElement) }) diff --git a/test/fixtures/typescript/corpus/string.diffB-A.txt b/test/fixtures/typescript/corpus/string.diffB-A.txt index c368003ca..93e83c046 100644 --- a/test/fixtures/typescript/corpus/string.diffB-A.txt +++ b/test/fixtures/typescript/corpus/string.diffB-A.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (TextElement) ->(TextElement) }) diff --git a/test/fixtures/typescript/corpus/string.parseA.txt b/test/fixtures/typescript/corpus/string.parseA.txt index 7eb233a5b..244724dcd 100644 --- a/test/fixtures/typescript/corpus/string.parseA.txt +++ b/test/fixtures/typescript/corpus/string.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (TextElement)) diff --git a/test/fixtures/typescript/corpus/string.parseB.txt b/test/fixtures/typescript/corpus/string.parseB.txt index 7eb233a5b..244724dcd 100644 --- a/test/fixtures/typescript/corpus/string.parseB.txt +++ b/test/fixtures/typescript/corpus/string.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (TextElement)) diff --git a/test/fixtures/typescript/corpus/subscript-access-assignment.diffA-B.txt b/test/fixtures/typescript/corpus/subscript-access-assignment.diffA-B.txt index 364b1a226..b87f35fd6 100644 --- a/test/fixtures/typescript/corpus/subscript-access-assignment.diffA-B.txt +++ b/test/fixtures/typescript/corpus/subscript-access-assignment.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Subscript (Identifier) diff --git a/test/fixtures/typescript/corpus/subscript-access-assignment.diffB-A.txt b/test/fixtures/typescript/corpus/subscript-access-assignment.diffB-A.txt index 364b1a226..b87f35fd6 100644 --- a/test/fixtures/typescript/corpus/subscript-access-assignment.diffB-A.txt +++ b/test/fixtures/typescript/corpus/subscript-access-assignment.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Subscript (Identifier) diff --git a/test/fixtures/typescript/corpus/subscript-access-assignment.parseA.txt b/test/fixtures/typescript/corpus/subscript-access-assignment.parseA.txt index 23430e8b8..065c52c81 100644 --- a/test/fixtures/typescript/corpus/subscript-access-assignment.parseA.txt +++ b/test/fixtures/typescript/corpus/subscript-access-assignment.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Subscript (Identifier) diff --git a/test/fixtures/typescript/corpus/subscript-access-assignment.parseB.txt b/test/fixtures/typescript/corpus/subscript-access-assignment.parseB.txt index 23430e8b8..065c52c81 100644 --- a/test/fixtures/typescript/corpus/subscript-access-assignment.parseB.txt +++ b/test/fixtures/typescript/corpus/subscript-access-assignment.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (Subscript (Identifier) diff --git a/test/fixtures/typescript/corpus/subscript-access-string.diffA-B.txt b/test/fixtures/typescript/corpus/subscript-access-string.diffA-B.txt index e89be8ff9..e95863ee0 100644 --- a/test/fixtures/typescript/corpus/subscript-access-string.diffA-B.txt +++ b/test/fixtures/typescript/corpus/subscript-access-string.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) { (TextElement) diff --git a/test/fixtures/typescript/corpus/subscript-access-string.diffB-A.txt b/test/fixtures/typescript/corpus/subscript-access-string.diffB-A.txt index e89be8ff9..e95863ee0 100644 --- a/test/fixtures/typescript/corpus/subscript-access-string.diffB-A.txt +++ b/test/fixtures/typescript/corpus/subscript-access-string.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) { (TextElement) diff --git a/test/fixtures/typescript/corpus/subscript-access-string.parseA.txt b/test/fixtures/typescript/corpus/subscript-access-string.parseA.txt index 1005056be..5d5853ad7 100644 --- a/test/fixtures/typescript/corpus/subscript-access-string.parseA.txt +++ b/test/fixtures/typescript/corpus/subscript-access-string.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) (TextElement))) diff --git a/test/fixtures/typescript/corpus/subscript-access-string.parseB.txt b/test/fixtures/typescript/corpus/subscript-access-string.parseB.txt index 1005056be..5d5853ad7 100644 --- a/test/fixtures/typescript/corpus/subscript-access-string.parseB.txt +++ b/test/fixtures/typescript/corpus/subscript-access-string.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) (TextElement))) diff --git a/test/fixtures/typescript/corpus/subscript-access-variable.diffA-B.txt b/test/fixtures/typescript/corpus/subscript-access-variable.diffA-B.txt index 428bf4bf1..0a3963195 100644 --- a/test/fixtures/typescript/corpus/subscript-access-variable.diffA-B.txt +++ b/test/fixtures/typescript/corpus/subscript-access-variable.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) { (Identifier) diff --git a/test/fixtures/typescript/corpus/subscript-access-variable.diffB-A.txt b/test/fixtures/typescript/corpus/subscript-access-variable.diffB-A.txt index 428bf4bf1..0a3963195 100644 --- a/test/fixtures/typescript/corpus/subscript-access-variable.diffB-A.txt +++ b/test/fixtures/typescript/corpus/subscript-access-variable.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) { (Identifier) diff --git a/test/fixtures/typescript/corpus/subscript-access-variable.parseA.txt b/test/fixtures/typescript/corpus/subscript-access-variable.parseA.txt index d51465cb0..e2c7fbd55 100644 --- a/test/fixtures/typescript/corpus/subscript-access-variable.parseA.txt +++ b/test/fixtures/typescript/corpus/subscript-access-variable.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) (Identifier))) diff --git a/test/fixtures/typescript/corpus/subscript-access-variable.parseB.txt b/test/fixtures/typescript/corpus/subscript-access-variable.parseB.txt index d51465cb0..e2c7fbd55 100644 --- a/test/fixtures/typescript/corpus/subscript-access-variable.parseB.txt +++ b/test/fixtures/typescript/corpus/subscript-access-variable.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Subscript (Identifier) (Identifier))) diff --git a/test/fixtures/typescript/corpus/switch-statement.diffA-B.txt b/test/fixtures/typescript/corpus/switch-statement.diffA-B.txt index 3883f69c5..b150ce8fc 100644 --- a/test/fixtures/typescript/corpus/switch-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/switch-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match { (Float) ->(Float) } diff --git a/test/fixtures/typescript/corpus/switch-statement.diffB-A.txt b/test/fixtures/typescript/corpus/switch-statement.diffB-A.txt index 3883f69c5..b150ce8fc 100644 --- a/test/fixtures/typescript/corpus/switch-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/switch-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match { (Float) ->(Float) } diff --git a/test/fixtures/typescript/corpus/switch-statement.parseA.txt b/test/fixtures/typescript/corpus/switch-statement.parseA.txt index 3e597d106..50a633ec5 100644 --- a/test/fixtures/typescript/corpus/switch-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/switch-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match (Float) (Statements diff --git a/test/fixtures/typescript/corpus/switch-statement.parseB.txt b/test/fixtures/typescript/corpus/switch-statement.parseB.txt index 3e597d106..50a633ec5 100644 --- a/test/fixtures/typescript/corpus/switch-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/switch-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Match (Float) (Statements diff --git a/test/fixtures/typescript/corpus/template-string.diffA-B.txt b/test/fixtures/typescript/corpus/template-string.diffA-B.txt index d1f43f5d8..d6d776fad 100644 --- a/test/fixtures/typescript/corpus/template-string.diffA-B.txt +++ b/test/fixtures/typescript/corpus/template-string.diffA-B.txt @@ -1,2 +1,2 @@ -(Program +(Statements (String)) diff --git a/test/fixtures/typescript/corpus/template-string.diffB-A.txt b/test/fixtures/typescript/corpus/template-string.diffB-A.txt index d1f43f5d8..d6d776fad 100644 --- a/test/fixtures/typescript/corpus/template-string.diffB-A.txt +++ b/test/fixtures/typescript/corpus/template-string.diffB-A.txt @@ -1,2 +1,2 @@ -(Program +(Statements (String)) diff --git a/test/fixtures/typescript/corpus/template-string.parseA.txt b/test/fixtures/typescript/corpus/template-string.parseA.txt index d1f43f5d8..d6d776fad 100644 --- a/test/fixtures/typescript/corpus/template-string.parseA.txt +++ b/test/fixtures/typescript/corpus/template-string.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (String)) diff --git a/test/fixtures/typescript/corpus/template-string.parseB.txt b/test/fixtures/typescript/corpus/template-string.parseB.txt index d1f43f5d8..d6d776fad 100644 --- a/test/fixtures/typescript/corpus/template-string.parseB.txt +++ b/test/fixtures/typescript/corpus/template-string.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (String)) diff --git a/test/fixtures/typescript/corpus/ternary.diffA-B.txt b/test/fixtures/typescript/corpus/ternary.diffA-B.txt index 500a7b34a..62d5ee7dc 100644 --- a/test/fixtures/typescript/corpus/ternary.diffA-B.txt +++ b/test/fixtures/typescript/corpus/ternary.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Assignment {+(MemberAccess {+(Identifier)+} diff --git a/test/fixtures/typescript/corpus/ternary.diffB-A.txt b/test/fixtures/typescript/corpus/ternary.diffB-A.txt index 4696a13d8..651fe0c1f 100644 --- a/test/fixtures/typescript/corpus/ternary.diffB-A.txt +++ b/test/fixtures/typescript/corpus/ternary.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(If {+(Identifier)+} {+(Identifier)+} diff --git a/test/fixtures/typescript/corpus/ternary.parseA.txt b/test/fixtures/typescript/corpus/ternary.parseA.txt index 76d8615b5..ff5f03d89 100644 --- a/test/fixtures/typescript/corpus/ternary.parseA.txt +++ b/test/fixtures/typescript/corpus/ternary.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (If (Identifier) (Identifier) diff --git a/test/fixtures/typescript/corpus/ternary.parseB.txt b/test/fixtures/typescript/corpus/ternary.parseB.txt index 988c986b7..93db1d9d2 100644 --- a/test/fixtures/typescript/corpus/ternary.parseB.txt +++ b/test/fixtures/typescript/corpus/ternary.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Assignment (MemberAccess (Identifier) diff --git a/test/fixtures/typescript/corpus/this-expression.diffA-B.txt b/test/fixtures/typescript/corpus/this-expression.diffA-B.txt index f5bd377a6..d02578fcf 100644 --- a/test/fixtures/typescript/corpus/this-expression.diffA-B.txt +++ b/test/fixtures/typescript/corpus/this-expression.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Return {+(This)+})+} {-(This)-}) diff --git a/test/fixtures/typescript/corpus/this-expression.diffB-A.txt b/test/fixtures/typescript/corpus/this-expression.diffB-A.txt index ca392b2b4..47b93e9e0 100644 --- a/test/fixtures/typescript/corpus/this-expression.diffB-A.txt +++ b/test/fixtures/typescript/corpus/this-expression.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(This)+} {-(Return {-(This)-})-}) diff --git a/test/fixtures/typescript/corpus/this-expression.parseA.txt b/test/fixtures/typescript/corpus/this-expression.parseA.txt index 276aa4584..2fce35ed5 100644 --- a/test/fixtures/typescript/corpus/this-expression.parseA.txt +++ b/test/fixtures/typescript/corpus/this-expression.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (This)) diff --git a/test/fixtures/typescript/corpus/this-expression.parseB.txt b/test/fixtures/typescript/corpus/this-expression.parseB.txt index 0872d6ab5..2ebca766a 100644 --- a/test/fixtures/typescript/corpus/this-expression.parseB.txt +++ b/test/fixtures/typescript/corpus/this-expression.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (This))) diff --git a/test/fixtures/typescript/corpus/throw-statement.diffA-B.txt b/test/fixtures/typescript/corpus/throw-statement.diffA-B.txt index a442e1a04..5b8fd0cab 100644 --- a/test/fixtures/typescript/corpus/throw-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/throw-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Throw (New (Call diff --git a/test/fixtures/typescript/corpus/throw-statement.diffB-A.txt b/test/fixtures/typescript/corpus/throw-statement.diffB-A.txt index a442e1a04..5b8fd0cab 100644 --- a/test/fixtures/typescript/corpus/throw-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/throw-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Throw (New (Call diff --git a/test/fixtures/typescript/corpus/throw-statement.parseA.txt b/test/fixtures/typescript/corpus/throw-statement.parseA.txt index d6347b923..f19d27175 100644 --- a/test/fixtures/typescript/corpus/throw-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/throw-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Throw (New (Call diff --git a/test/fixtures/typescript/corpus/throw-statement.parseB.txt b/test/fixtures/typescript/corpus/throw-statement.parseB.txt index d6347b923..f19d27175 100644 --- a/test/fixtures/typescript/corpus/throw-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/throw-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Throw (New (Call diff --git a/test/fixtures/typescript/corpus/true.diffA-B.txt b/test/fixtures/typescript/corpus/true.diffA-B.txt index ac2ca170c..62f7e4e3e 100644 --- a/test/fixtures/typescript/corpus/true.diffA-B.txt +++ b/test/fixtures/typescript/corpus/true.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Return {+(Boolean)+})+} {-(Boolean)-}) diff --git a/test/fixtures/typescript/corpus/true.diffB-A.txt b/test/fixtures/typescript/corpus/true.diffB-A.txt index 846a9c224..57c1b8c70 100644 --- a/test/fixtures/typescript/corpus/true.diffB-A.txt +++ b/test/fixtures/typescript/corpus/true.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Boolean)+} {-(Return {-(Boolean)-})-}) diff --git a/test/fixtures/typescript/corpus/true.parseA.txt b/test/fixtures/typescript/corpus/true.parseA.txt index 1fdad7cac..25d98872e 100644 --- a/test/fixtures/typescript/corpus/true.parseA.txt +++ b/test/fixtures/typescript/corpus/true.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Boolean)) diff --git a/test/fixtures/typescript/corpus/true.parseB.txt b/test/fixtures/typescript/corpus/true.parseB.txt index a37bdc4ee..02e3c2a13 100644 --- a/test/fixtures/typescript/corpus/true.parseB.txt +++ b/test/fixtures/typescript/corpus/true.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Boolean))) diff --git a/test/fixtures/typescript/corpus/try-statement.diffA-B.txt b/test/fixtures/typescript/corpus/try-statement.diffA-B.txt index a7241e603..e5ea1fab8 100644 --- a/test/fixtures/typescript/corpus/try-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/try-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Identifier)) diff --git a/test/fixtures/typescript/corpus/try-statement.diffB-A.txt b/test/fixtures/typescript/corpus/try-statement.diffB-A.txt index a7241e603..e5ea1fab8 100644 --- a/test/fixtures/typescript/corpus/try-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/try-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Identifier)) diff --git a/test/fixtures/typescript/corpus/try-statement.parseA.txt b/test/fixtures/typescript/corpus/try-statement.parseA.txt index 22e10b492..00902f275 100644 --- a/test/fixtures/typescript/corpus/try-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/try-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Identifier)) diff --git a/test/fixtures/typescript/corpus/try-statement.parseB.txt b/test/fixtures/typescript/corpus/try-statement.parseB.txt index 22e10b492..00902f275 100644 --- a/test/fixtures/typescript/corpus/try-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/try-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Try (Statements (Identifier)) diff --git a/test/fixtures/typescript/corpus/tuple-type.diffA-B.txt b/test/fixtures/typescript/corpus/tuple-type.diffA-B.txt index 7e86ff20d..cdd26ac98 100644 --- a/test/fixtures/typescript/corpus/tuple-type.diffA-B.txt +++ b/test/fixtures/typescript/corpus/tuple-type.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/tuple-type.diffB-A.txt b/test/fixtures/typescript/corpus/tuple-type.diffB-A.txt index 84a1e0700..5d79801a7 100644 --- a/test/fixtures/typescript/corpus/tuple-type.diffB-A.txt +++ b/test/fixtures/typescript/corpus/tuple-type.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/tuple-type.parseA.txt b/test/fixtures/typescript/corpus/tuple-type.parseA.txt index 3e6b217cf..60d64c00a 100644 --- a/test/fixtures/typescript/corpus/tuple-type.parseA.txt +++ b/test/fixtures/typescript/corpus/tuple-type.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/tuple-type.parseB.txt b/test/fixtures/typescript/corpus/tuple-type.parseB.txt index 35b6f9485..0d8b6cb08 100644 --- a/test/fixtures/typescript/corpus/tuple-type.parseB.txt +++ b/test/fixtures/typescript/corpus/tuple-type.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/type-assertions.diffA-B.txt b/test/fixtures/typescript/corpus/type-assertions.diffA-B.txt index 1ac214273..b84484c70 100644 --- a/test/fixtures/typescript/corpus/type-assertions.diffA-B.txt +++ b/test/fixtures/typescript/corpus/type-assertions.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Cast {+(Identifier)+} {+(PredefinedType)+})+} diff --git a/test/fixtures/typescript/corpus/type-assertions.diffB-A.txt b/test/fixtures/typescript/corpus/type-assertions.diffB-A.txt index 314e7dfd1..b6a09fa7b 100644 --- a/test/fixtures/typescript/corpus/type-assertions.diffB-A.txt +++ b/test/fixtures/typescript/corpus/type-assertions.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(TypeAssertion {+(TypeArguments {+(PredefinedType)+})+} diff --git a/test/fixtures/typescript/corpus/type-assertions.parseA.txt b/test/fixtures/typescript/corpus/type-assertions.parseA.txt index b1b0ac374..8af389ea2 100644 --- a/test/fixtures/typescript/corpus/type-assertions.parseA.txt +++ b/test/fixtures/typescript/corpus/type-assertions.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (TypeAssertion (TypeArguments (PredefinedType)) diff --git a/test/fixtures/typescript/corpus/type-assertions.parseB.txt b/test/fixtures/typescript/corpus/type-assertions.parseB.txt index ed7726b6d..ffba56a63 100644 --- a/test/fixtures/typescript/corpus/type-assertions.parseB.txt +++ b/test/fixtures/typescript/corpus/type-assertions.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Cast (Identifier) (PredefinedType))) diff --git a/test/fixtures/typescript/corpus/type-operator.diffA-B.txt b/test/fixtures/typescript/corpus/type-operator.diffA-B.txt index fe1dba975..41ac6e1cb 100644 --- a/test/fixtures/typescript/corpus/type-operator.diffA-B.txt +++ b/test/fixtures/typescript/corpus/type-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(InstanceOf {+(Identifier)+} {+(Identifier)+})+} diff --git a/test/fixtures/typescript/corpus/type-operator.diffB-A.txt b/test/fixtures/typescript/corpus/type-operator.diffB-A.txt index f45173af0..7ad244a67 100644 --- a/test/fixtures/typescript/corpus/type-operator.diffB-A.txt +++ b/test/fixtures/typescript/corpus/type-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Typeof {+(Identifier)+})+} {-(InstanceOf diff --git a/test/fixtures/typescript/corpus/type-operator.parseA.txt b/test/fixtures/typescript/corpus/type-operator.parseA.txt index 7953fe31a..f20b03753 100644 --- a/test/fixtures/typescript/corpus/type-operator.parseA.txt +++ b/test/fixtures/typescript/corpus/type-operator.parseA.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Typeof (Identifier))) diff --git a/test/fixtures/typescript/corpus/type-operator.parseB.txt b/test/fixtures/typescript/corpus/type-operator.parseB.txt index 79142c960..6087bffac 100644 --- a/test/fixtures/typescript/corpus/type-operator.parseB.txt +++ b/test/fixtures/typescript/corpus/type-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (InstanceOf (Identifier) (Identifier))) diff --git a/test/fixtures/typescript/corpus/typeof-types.diffA-B.txt b/test/fixtures/typescript/corpus/typeof-types.diffA-B.txt index 17eb42cb4..eea2bf878 100644 --- a/test/fixtures/typescript/corpus/typeof-types.diffA-B.txt +++ b/test/fixtures/typescript/corpus/typeof-types.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/typeof-types.diffB-A.txt b/test/fixtures/typescript/corpus/typeof-types.diffB-A.txt index 904b0ca4a..fb04a40af 100644 --- a/test/fixtures/typescript/corpus/typeof-types.diffB-A.txt +++ b/test/fixtures/typescript/corpus/typeof-types.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/typeof-types.parseA.txt b/test/fixtures/typescript/corpus/typeof-types.parseA.txt index 45a982188..993d76461 100644 --- a/test/fixtures/typescript/corpus/typeof-types.parseA.txt +++ b/test/fixtures/typescript/corpus/typeof-types.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/typeof-types.parseB.txt b/test/fixtures/typescript/corpus/typeof-types.parseB.txt index 8487c46c0..4a77aaa66 100644 --- a/test/fixtures/typescript/corpus/typeof-types.parseB.txt +++ b/test/fixtures/typescript/corpus/typeof-types.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/undefined.diffA-B.txt b/test/fixtures/typescript/corpus/undefined.diffA-B.txt index 8edd91ab0..e0aaaa117 100644 --- a/test/fixtures/typescript/corpus/undefined.diffA-B.txt +++ b/test/fixtures/typescript/corpus/undefined.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Return {+(Undefined)+})+} {-(Undefined)-}) diff --git a/test/fixtures/typescript/corpus/undefined.diffB-A.txt b/test/fixtures/typescript/corpus/undefined.diffB-A.txt index a74390230..6736d273a 100644 --- a/test/fixtures/typescript/corpus/undefined.diffB-A.txt +++ b/test/fixtures/typescript/corpus/undefined.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements {+(Undefined)+} {-(Return {-(Undefined)-})-}) diff --git a/test/fixtures/typescript/corpus/undefined.parseA.txt b/test/fixtures/typescript/corpus/undefined.parseA.txt index 87378cd50..ea5e6fca6 100644 --- a/test/fixtures/typescript/corpus/undefined.parseA.txt +++ b/test/fixtures/typescript/corpus/undefined.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Undefined)) diff --git a/test/fixtures/typescript/corpus/undefined.parseB.txt b/test/fixtures/typescript/corpus/undefined.parseB.txt index 0afc44c9e..58c1a9eaf 100644 --- a/test/fixtures/typescript/corpus/undefined.parseB.txt +++ b/test/fixtures/typescript/corpus/undefined.parseB.txt @@ -1,3 +1,3 @@ -(Program +(Statements (Return (Undefined))) diff --git a/test/fixtures/typescript/corpus/union-type.diffA-B.txt b/test/fixtures/typescript/corpus/union-type.diffA-B.txt index 47f461391..751bfbe4e 100644 --- a/test/fixtures/typescript/corpus/union-type.diffA-B.txt +++ b/test/fixtures/typescript/corpus/union-type.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/union-type.diffB-A.txt b/test/fixtures/typescript/corpus/union-type.diffB-A.txt index 831fc91ab..937cefcf2 100644 --- a/test/fixtures/typescript/corpus/union-type.diffB-A.txt +++ b/test/fixtures/typescript/corpus/union-type.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/union-type.parseA.txt b/test/fixtures/typescript/corpus/union-type.parseA.txt index 35b6f9485..0d8b6cb08 100644 --- a/test/fixtures/typescript/corpus/union-type.parseA.txt +++ b/test/fixtures/typescript/corpus/union-type.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/union-type.parseB.txt b/test/fixtures/typescript/corpus/union-type.parseB.txt index f2ac2419d..34575c862 100644 --- a/test/fixtures/typescript/corpus/union-type.parseB.txt +++ b/test/fixtures/typescript/corpus/union-type.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Annotation diff --git a/test/fixtures/typescript/corpus/var-declaration.diffA-B.txt b/test/fixtures/typescript/corpus/var-declaration.diffA-B.txt index f7607a355..125c37429 100644 --- a/test/fixtures/typescript/corpus/var-declaration.diffA-B.txt +++ b/test/fixtures/typescript/corpus/var-declaration.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/var-declaration.diffB-A.txt b/test/fixtures/typescript/corpus/var-declaration.diffB-A.txt index 57e89c6ec..190ddb8ff 100644 --- a/test/fixtures/typescript/corpus/var-declaration.diffB-A.txt +++ b/test/fixtures/typescript/corpus/var-declaration.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/var-declaration.parseA.txt b/test/fixtures/typescript/corpus/var-declaration.parseA.txt index f6cc57179..1634cc36e 100644 --- a/test/fixtures/typescript/corpus/var-declaration.parseA.txt +++ b/test/fixtures/typescript/corpus/var-declaration.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/var-declaration.parseB.txt b/test/fixtures/typescript/corpus/var-declaration.parseB.txt index 66abdae58..2ffadbf28 100644 --- a/test/fixtures/typescript/corpus/var-declaration.parseB.txt +++ b/test/fixtures/typescript/corpus/var-declaration.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (VariableDeclaration (Assignment (Empty) diff --git a/test/fixtures/typescript/corpus/variable.diffA-B.txt b/test/fixtures/typescript/corpus/variable.diffA-B.txt index 6ac9cd896..d2449f436 100644 --- a/test/fixtures/typescript/corpus/variable.diffA-B.txt +++ b/test/fixtures/typescript/corpus/variable.diffA-B.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/typescript/corpus/variable.diffB-A.txt b/test/fixtures/typescript/corpus/variable.diffB-A.txt index 6ac9cd896..d2449f436 100644 --- a/test/fixtures/typescript/corpus/variable.diffB-A.txt +++ b/test/fixtures/typescript/corpus/variable.diffB-A.txt @@ -1,3 +1,3 @@ -(Program +(Statements { (Identifier) ->(Identifier) }) diff --git a/test/fixtures/typescript/corpus/variable.parseA.txt b/test/fixtures/typescript/corpus/variable.parseA.txt index 67b75f388..5f0ab64c1 100644 --- a/test/fixtures/typescript/corpus/variable.parseA.txt +++ b/test/fixtures/typescript/corpus/variable.parseA.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Identifier)) diff --git a/test/fixtures/typescript/corpus/variable.parseB.txt b/test/fixtures/typescript/corpus/variable.parseB.txt index 67b75f388..5f0ab64c1 100644 --- a/test/fixtures/typescript/corpus/variable.parseB.txt +++ b/test/fixtures/typescript/corpus/variable.parseB.txt @@ -1,2 +1,2 @@ -(Program +(Statements (Identifier)) diff --git a/test/fixtures/typescript/corpus/void-operator.diffA-B.txt b/test/fixtures/typescript/corpus/void-operator.diffA-B.txt index 1478a4241..8b8801ab7 100644 --- a/test/fixtures/typescript/corpus/void-operator.diffA-B.txt +++ b/test/fixtures/typescript/corpus/void-operator.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Void (Call { (Identifier) diff --git a/test/fixtures/typescript/corpus/void-operator.diffB-A.txt b/test/fixtures/typescript/corpus/void-operator.diffB-A.txt index 1478a4241..8b8801ab7 100644 --- a/test/fixtures/typescript/corpus/void-operator.diffB-A.txt +++ b/test/fixtures/typescript/corpus/void-operator.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Void (Call { (Identifier) diff --git a/test/fixtures/typescript/corpus/void-operator.parseA.txt b/test/fixtures/typescript/corpus/void-operator.parseA.txt index 71c1d3bd3..71bb37891 100644 --- a/test/fixtures/typescript/corpus/void-operator.parseA.txt +++ b/test/fixtures/typescript/corpus/void-operator.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Void (Call (Identifier) diff --git a/test/fixtures/typescript/corpus/void-operator.parseB.txt b/test/fixtures/typescript/corpus/void-operator.parseB.txt index 71c1d3bd3..71bb37891 100644 --- a/test/fixtures/typescript/corpus/void-operator.parseB.txt +++ b/test/fixtures/typescript/corpus/void-operator.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Void (Call (Identifier) diff --git a/test/fixtures/typescript/corpus/while-statement.diffA-B.txt b/test/fixtures/typescript/corpus/while-statement.diffA-B.txt index 6c6581fbe..123a81df0 100644 --- a/test/fixtures/typescript/corpus/while-statement.diffA-B.txt +++ b/test/fixtures/typescript/corpus/while-statement.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While { (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 6c6581fbe..123a81df0 100644 --- a/test/fixtures/typescript/corpus/while-statement.diffB-A.txt +++ b/test/fixtures/typescript/corpus/while-statement.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While { (Identifier) ->(Identifier) } diff --git a/test/fixtures/typescript/corpus/while-statement.parseA.txt b/test/fixtures/typescript/corpus/while-statement.parseA.txt index 41960b042..9d2e8f0d8 100644 --- a/test/fixtures/typescript/corpus/while-statement.parseA.txt +++ b/test/fixtures/typescript/corpus/while-statement.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Identifier) (Statements diff --git a/test/fixtures/typescript/corpus/while-statement.parseB.txt b/test/fixtures/typescript/corpus/while-statement.parseB.txt index 41960b042..9d2e8f0d8 100644 --- a/test/fixtures/typescript/corpus/while-statement.parseB.txt +++ b/test/fixtures/typescript/corpus/while-statement.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (While (Identifier) (Statements diff --git a/test/fixtures/typescript/corpus/yield.diffA-B.txt b/test/fixtures/typescript/corpus/yield.diffA-B.txt index ccde7b2d7..7d14f5b38 100644 --- a/test/fixtures/typescript/corpus/yield.diffA-B.txt +++ b/test/fixtures/typescript/corpus/yield.diffA-B.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/yield.diffB-A.txt b/test/fixtures/typescript/corpus/yield.diffB-A.txt index d7dd3fc20..28d99fdcc 100644 --- a/test/fixtures/typescript/corpus/yield.diffB-A.txt +++ b/test/fixtures/typescript/corpus/yield.diffB-A.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/yield.parseA.txt b/test/fixtures/typescript/corpus/yield.parseA.txt index 47d764d16..ead5d4445 100644 --- a/test/fixtures/typescript/corpus/yield.parseA.txt +++ b/test/fixtures/typescript/corpus/yield.parseA.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) diff --git a/test/fixtures/typescript/corpus/yield.parseB.txt b/test/fixtures/typescript/corpus/yield.parseB.txt index 54eada74e..ba8875d78 100644 --- a/test/fixtures/typescript/corpus/yield.parseB.txt +++ b/test/fixtures/typescript/corpus/yield.parseB.txt @@ -1,4 +1,4 @@ -(Program +(Statements (Function (Empty) (Empty) From 0741aa424111a55c97d8bbabd48d4eef996b1415 Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Fri, 1 Jun 2018 14:43:11 -0700 Subject: [PATCH 16/16] Add a note about this Map --- src/Data/JSON/Fields.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Data/JSON/Fields.hs b/src/Data/JSON/Fields.hs index 602e1ba8c..6d2504e57 100644 --- a/src/Data/JSON/Fields.hs +++ b/src/Data/JSON/Fields.hs @@ -90,6 +90,9 @@ instance (GConstructorName1 f, GConstructorName1 g) => GConstructorName1 (f :+: -- | A typeclass to calculate a list of 'KeyValue's describing the record selector names and associated values on a datatype. class GToJSONFields1 f where + -- FIXME: Not ideal to allocate a Map each time here, but not an obvious way + -- to deal with product types without record selectors that all end up as an + -- array under a "children" property. gtoJSONFields1 :: (ToJSON a) => f a -> Map.Map Text [SomeJSON] instance GToJSONFields1 f => GToJSONFields1 (M1 D c f) where