From 49b0d55ee564496d24dcade06bf10d8b5c31ad86 Mon Sep 17 00:00:00 2001 From: Timothy Clem Date: Mon, 2 Oct 2017 13:25:33 -0700 Subject: [PATCH 01/44] Always use assignment parser for Ruby --- src/Semantic.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Semantic.hs b/src/Semantic.hs index cac03c51c..e23c50703 100644 --- a/src/Semantic.hs +++ b/src/Semantic.hs @@ -74,6 +74,7 @@ diffBlobPair :: DiffRenderer output -> Both Blob -> Task output diffBlobPair renderer blobs = case (renderer, effectiveLanguage) of (OldToCDiffRenderer, Just Language.Markdown) -> run (\ blob -> parse markdownParser blob >>= decorate (markupSectionAlgebra blob)) diffTerms (renderToCDiff blobs) (OldToCDiffRenderer, Just Language.Python) -> run (\ blob -> parse pythonParser blob >>= decorate (declarationAlgebra blob)) diffTerms (renderToCDiff blobs) + (OldToCDiffRenderer, Just Language.Ruby) -> run (\ blob -> parse rubyParser blob >>= decorate (declarationAlgebra blob)) diffTerms (renderToCDiff blobs) (OldToCDiffRenderer, _) | Just syntaxParser <- syntaxParser -> run (\ blob -> parse syntaxParser blob >>= decorate (syntaxDeclarationAlgebra blob)) diffSyntaxTerms (renderToCDiff blobs) (ToCDiffRenderer, Just Language.Markdown) -> run (\ blob -> parse markdownParser blob >>= decorate (markupSectionAlgebra blob)) diffTerms (renderToCDiff blobs) From b75fc8cc8889e71eb7941779e6d15f192a9a4720 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 12:20:52 -0400 Subject: [PATCH 02/44] Name the variables in Diffable a1/a2 &c consistently. --- src/Algorithm.hs | 40 ++++++++++++++++++++-------------------- 1 file changed, 20 insertions(+), 20 deletions(-) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index bf3bfefe8..e6eeb01ba 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -41,7 +41,7 @@ type Algorithm term1 term2 result = Freer (AlgorithmF term1 term2 result) -- | Diff two terms without specifying the algorithm to be used. diff :: term1 -> term2 -> Algorithm term1 term2 result result -diff = (liftF .) . Algorithm.Diff +diff a1 a2 = Algorithm.Diff a1 a2 `Then` return -- | Diff a These of terms without specifying the algorithm to be used. diffThese :: These term1 term2 -> Algorithm term1 term2 result result @@ -49,30 +49,30 @@ diffThese = these byDeleting byInserting diff -- | Diff a pair of optional terms without specifying the algorithm to be used. diffMaybe :: Maybe term1 -> Maybe term2 -> Algorithm term1 term2 result (Maybe result) -diffMaybe (Just a) (Just b) = Just <$> diff a b -diffMaybe (Just a) _ = Just <$> byDeleting a -diffMaybe _ (Just b) = Just <$> byInserting b -diffMaybe _ _ = pure Nothing +diffMaybe (Just a1) (Just a2) = Just <$> diff a1 a2 +diffMaybe (Just a1) _ = Just <$> byDeleting a1 +diffMaybe _ (Just a2) = Just <$> byInserting a2 +diffMaybe _ _ = pure Nothing -- | Diff two terms linearly. linearly :: term1 -> term2 -> Algorithm term1 term2 result result -linearly f1 f2 = liftF (Linear f1 f2) +linearly f1 f2 = Linear f1 f2 `Then` return -- | Diff two terms using RWS. byRWS :: [term1] -> [term2] -> Algorithm term1 term2 result [result] -byRWS a b = liftF (RWS a b) +byRWS as1 as2 = RWS as1 as2 `Then` return -- | Delete a term. byDeleting :: term1 -> Algorithm term1 term2 result result -byDeleting = liftF . Delete +byDeleting a1 = Delete a1 `Then` return -- | Insert a term. byInserting :: term2 -> Algorithm term1 term2 result result -byInserting = liftF . Insert +byInserting a2 = Insert a2 `Then` return -- | Replace one term with another. byReplacing :: term1 -> term2 -> Algorithm term1 term2 result result -byReplacing = (liftF .) . Replace +byReplacing a1 a2 = Replace a1 a2 `Then` return instance (Show term1, Show term2) => Show1 (AlgorithmF term1 term2 result) where @@ -90,9 +90,9 @@ instance (Show term1, Show term2) => Show1 (AlgorithmF term1 term2 result) where instance Alternative (Algorithm term1 term2 result) where empty = Empty `Then` return - (Empty `Then` _) <|> b = b - a <|> (Empty `Then` _) = a - a <|> b = Alt a b `Then` id + (Empty `Then` _) <|> a2 = a2 + a1 <|> (Empty `Then` _) = a1 + a1 <|> a2 = Alt a1 a2 `Then` id -- | Diff two terms based on their generic Diffable instances. If the terms are not diffable @@ -163,7 +163,7 @@ instance Diffable [] where -- | Diff two non-empty lists using RWS. instance Diffable NonEmpty where - algorithmFor (a:|as) (b:|bs) = (\ (d:ds) -> d:|ds) <$> byRWS (a:as) (b:bs) + algorithmFor (a1:|as1) (a2:|as2) = (\ (a:as) -> a:|as) <$> byRWS (a1:as1) (a2:as2) -- | A generic type class for diffing two terms defined by the Generic1 interface. class GDiffable f where @@ -171,7 +171,7 @@ class GDiffable f where -- | Diff two constructors (M1 is the Generic1 newtype for meta-information (possibly related to type constructors, record selectors, and data types)) instance GDiffable f => GDiffable (M1 i c f) where - galgorithmFor (M1 a) (M1 b) = M1 <$> galgorithmFor a b + galgorithmFor (M1 a1) (M1 a2) = M1 <$> galgorithmFor a1 a2 -- | Diff the fields of a product type. -- i.e. data Foo a b = Foo a b (the 'Foo a b' is captured by 'a :*: b'). @@ -181,19 +181,19 @@ instance (GDiffable f, GDiffable g) => GDiffable (f :*: g) where -- | Diff the constructors of a sum type. -- i.e. data Foo a = Foo a | Bar a (the 'Foo a' is captured by L1 and 'Bar a' is R1). instance (GDiffable f, GDiffable g) => GDiffable (f :+: g) where - galgorithmFor (L1 a) (L1 b) = L1 <$> galgorithmFor a b - galgorithmFor (R1 a) (R1 b) = R1 <$> galgorithmFor a b + galgorithmFor (L1 a1) (L1 a2) = L1 <$> galgorithmFor a1 a2 + galgorithmFor (R1 b1) (R1 b2) = R1 <$> galgorithmFor b1 b2 galgorithmFor _ _ = empty -- | Diff two parameters (Par1 is the Generic1 newtype representing a type parameter). -- i.e. data Foo a = Foo a (the 'a' is captured by Par1). instance GDiffable Par1 where - galgorithmFor (Par1 a) (Par1 b) = Par1 <$> diff a b + galgorithmFor (Par1 a1) (Par1 a2) = Par1 <$> diff a1 a2 -- | Diff two constant parameters (K1 is the Generic1 newtype representing type parameter constants). -- i.e. data Foo = Foo Int (the 'Int' is a constant parameter). instance Eq c => GDiffable (K1 i c) where - galgorithmFor (K1 a) (K1 b) = guard (a == b) *> pure (K1 a) + galgorithmFor (K1 a1) (K1 a2) = guard (a1 == a2) *> pure (K1 a1) -- | Diff two terms whose constructors contain 0 type parameters. -- i.e. data Foo = Foo. @@ -202,4 +202,4 @@ instance GDiffable U1 where -- | Diff two 'Diffable' containers of parameters. instance Diffable f => GDiffable (Rec1 f) where - galgorithmFor a b = Rec1 <$> algorithmFor (unRec1 a) (unRec1 b) + galgorithmFor a1 a2 = Rec1 <$> algorithmFor (unRec1 a1) (unRec1 a2) From 9c4969889413d15678bb5f929e48b7af934df1af Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 12:22:23 -0400 Subject: [PATCH 03/44] Correct the docs for algorithmForTerms. --- src/Algorithm.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index e6eeb01ba..b3854c2ae 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -95,8 +95,7 @@ instance Alternative (Algorithm term1 term2 result) where a1 <|> a2 = Alt a1 a2 `Then` id --- | Diff two terms based on their generic Diffable instances. If the terms are not diffable --- (represented by a Nothing diff returned from algorithmFor) replace one term with another. +-- | Diff two terms based on their 'Diffable' instances, performing substructural comparisons iff the initial comparison fails. algorithmForTerms :: Diffable syntax => Term syntax ann1 -> Term syntax ann2 From 1e14133272cb7299da153fbf33fdf13cee86a31b Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 12:28:15 -0400 Subject: [PATCH 04/44] =?UTF-8?q?Remove=20the=20suffix=20when=20we=20don?= =?UTF-8?q?=E2=80=99t=20know=20which=20side=20it=E2=80=99s=20on.?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- src/Algorithm.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index b3854c2ae..5acb32092 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -150,7 +150,7 @@ genericAlgorithmFor a b = to1 <$> galgorithmFor (from1 a) (from1 b) instance Apply Diffable fs => Diffable (Union fs) where algorithmFor u1 u2 = fromMaybe empty (apply2' (Proxy :: Proxy Diffable) (\ inj f1 f2 -> inj <$> algorithmFor f1 f2) u1 u2) - subalgorithmFor blur focus = apply' (Proxy :: Proxy Diffable) (\ inj f1 -> inj <$> subalgorithmFor blur focus f1) + subalgorithmFor blur focus = apply' (Proxy :: Proxy Diffable) (\ inj f -> inj <$> subalgorithmFor blur focus f) -- | Diff two 'Maybe's. instance Diffable Maybe where From fcc24d572feff27009306bc2f79dc788fcdb76de Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 13:25:17 -0400 Subject: [PATCH 05/44] Rename the bindings in subalgorithmFor. --- src/Data/Syntax.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index b31498e0f..46486df19 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -168,7 +168,7 @@ data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a } deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Diffable Context where - subalgorithmFor blur focus (Context n1 s1) = Context <$> traverse blur n1 <*> focus s1 + subalgorithmFor blur focus (Context n s) = Context <$> traverse blur n <*> focus s instance Eq1 Context where liftEq = genericLiftEq instance Ord1 Context where liftCompare = genericLiftCompare From 124e2b30a60c260da9ac40355b871f5f51afe5ab Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 13:25:27 -0400 Subject: [PATCH 06/44] Define a subequivalence method on Diffable. --- src/Algorithm.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index 5acb32092..1800f3b0c 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -136,6 +136,9 @@ class Diffable f where -> g (f b) -- ^ The resulting algorithm (or other 'Alternative' context), producing the traversed syntax. subalgorithmFor _ _ _ = empty + subequivalenceTo :: (a -> Bool) -> f a -> Bool + subequivalenceTo _ _ = False + genericAlgorithmFor :: (Generic1 f, GDiffable (Rep1 f)) => f term1 -> f term2 From 2fc976dd0efcea2a0d564cd034f530cf4d489711 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 13:26:02 -0400 Subject: [PATCH 07/44] Define subequivalence of Unions. --- src/Algorithm.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index 1800f3b0c..eefcf50c5 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -155,6 +155,8 @@ instance Apply Diffable fs => Diffable (Union fs) where subalgorithmFor blur focus = apply' (Proxy :: Proxy Diffable) (\ inj f -> inj <$> subalgorithmFor blur focus f) + subequivalenceTo focus = apply (Proxy :: Proxy Diffable) (subequivalenceTo focus) + -- | Diff two 'Maybe's. instance Diffable Maybe where algorithmFor = diffMaybe From 67cb2b3ea73b0703f4663ea4f86f49c4e45e28d8 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 13:26:08 -0400 Subject: [PATCH 08/44] Define subequivalence of Context nodes. --- src/Data/Syntax.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index 46486df19..5ed549e91 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -170,6 +170,8 @@ data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a } instance Diffable Context where subalgorithmFor blur focus (Context n s) = Context <$> traverse blur n <*> focus s + subequivalenceTo focus = focus . contextSubject + instance Eq1 Context where liftEq = genericLiftEq instance Ord1 Context where liftCompare = genericLiftCompare instance Show1 Context where liftShowsPrec = genericLiftShowsPrec From e52e69e08b4f4caa00e5d7aa89142fd794662776 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 13:26:17 -0400 Subject: [PATCH 09/44] Define subequivalence of Functions. --- src/Data/Syntax/Declaration.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Data/Syntax/Declaration.hs b/src/Data/Syntax/Declaration.hs index 9bb1ef512..7c79abf54 100644 --- a/src/Data/Syntax/Declaration.hs +++ b/src/Data/Syntax/Declaration.hs @@ -10,7 +10,10 @@ import Data.Mergeable import GHC.Generics data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + +instance Diffable Function where + subequivalenceTo focus = focus . functionName instance Eq1 Function where liftEq = genericLiftEq instance Ord1 Function where liftCompare = genericLiftCompare From 98ac25fe84c614605c95d123d914a2c418762a1a Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 13:26:29 -0400 Subject: [PATCH 10/44] Define subequivalence of Methods. --- src/Data/Syntax/Declaration.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Data/Syntax/Declaration.hs b/src/Data/Syntax/Declaration.hs index 7c79abf54..efb1e4e89 100644 --- a/src/Data/Syntax/Declaration.hs +++ b/src/Data/Syntax/Declaration.hs @@ -22,7 +22,10 @@ instance Show1 Function where liftShowsPrec = genericLiftShowsPrec -- TODO: How should we represent function types, where applicable? data Method a = Method { methodContext :: ![a], methodReceiver :: !a, methodName :: !a, methodParameters :: ![a], methodBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + +instance Diffable Method where + subequivalenceTo focus = focus . methodName instance Eq1 Method where liftEq = genericLiftEq instance Ord1 Method where liftCompare = genericLiftCompare From 82244515f828351948580bc93bf9b1a5e36c2f2d Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 13:27:02 -0400 Subject: [PATCH 11/44] Define a function computing the equivalence of terms based on subequivalence. --- src/Algorithm.hs | 8 ++++++++ src/Interpreter.hs | 2 +- 2 files changed, 9 insertions(+), 1 deletion(-) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index eefcf50c5..096aa0bf7 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -106,6 +106,14 @@ algorithmForTerms t1@(Term (In ann1 f1)) t2@(Term (In ann2 f2)) <|> insertF . In ann2 <$> subalgorithmFor byInserting ( mergeFor t1) f2 where mergeFor (Term (In ann1 f1)) (Term (In ann2 f2)) = merge (ann1, ann2) <$> algorithmFor f1 f2 +equivalentTerms :: Diffable syntax + => Term syntax ann1 + -> Term syntax ann2 + -> Bool +equivalentTerms term1@(Term (In _ syntax1)) term2@(Term (In _ syntax2)) + = subequivalenceTo (flip equivalentTerms term2) syntax1 + || subequivalenceTo ( equivalentTerms term1) syntax2 + -- | A type class for determining what algorithm to use for diffing two terms. class Diffable f where -- | Construct an algorithm to diff a pair of @f@s populated with disjoint terms. diff --git a/src/Interpreter.hs b/src/Interpreter.hs index 9123f5922..87bce34ce 100644 --- a/src/Interpreter.hs +++ b/src/Interpreter.hs @@ -6,7 +6,7 @@ module Interpreter , equivalentTerms ) where -import Algorithm +import Algorithm hiding (equivalentTerms) import Control.Applicative (Alternative(..)) import Control.Monad.Free.Freer import Data.Align.Generic From 695ceb7d6274932def4f25ac6d26e717c86c20ce Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 13:33:04 -0400 Subject: [PATCH 12/44] Define equivalence in terms of lifted equality. --- src/Interpreter.hs | 9 +++------ 1 file changed, 3 insertions(+), 6 deletions(-) diff --git a/src/Interpreter.hs b/src/Interpreter.hs index 87bce34ce..5f3663f2c 100644 --- a/src/Interpreter.hs +++ b/src/Interpreter.hs @@ -20,7 +20,6 @@ import Data.Syntax.Algebra import qualified Data.Syntax.Declaration as Declaration import Data.Term import Data.Text (Text) -import Data.These import Data.Union import Info hiding (Empty, Return) import RWS @@ -35,7 +34,7 @@ diffSyntaxTerms :: (HasField fields1 Category, HasField fields2 Category) diffSyntaxTerms = decoratingWith comparableByCategory (equalTerms comparableByCategory) getLabel getLabel -- | Diff two à la carte terms recursively. -diffTerms :: (Declaration.Method :< fs, Declaration.Function :< fs, Syntax.Context :< fs, Apply Diffable fs, Apply Foldable fs, Apply Functor fs, Apply GAlign fs, Apply Show1 fs, Apply Traversable fs) +diffTerms :: (Declaration.Method :< fs, Declaration.Function :< fs, Syntax.Context :< fs, Apply Diffable fs, Apply Eq1 fs, Apply Foldable fs, Apply Functor fs, Apply GAlign fs, Apply Show1 fs, Apply Traversable fs) => Term (Union fs) (Record fields1) -> Term (Union fs) (Record fields2) -> Diff (Union fs) (Record fields1) (Record fields2) @@ -112,7 +111,7 @@ comparableByConstructor (In _ u1) (In _ u2) -- | Equivalency relation for terms. Equivalence is determined by functions and -- methods with equal identifiers/names and recursively by equivalent terms with -- identical shapes. -equivalentTerms :: (Declaration.Method :< fs, Declaration.Function :< fs, Syntax.Context :< fs, Apply Foldable fs, Apply GAlign fs) +equivalentTerms :: (Declaration.Method :< fs, Declaration.Function :< fs, Syntax.Context :< fs, Apply Eq1 fs, Apply Foldable fs) => Term (Union fs) ann1 -> Term (Union fs) ann2 -> Bool @@ -130,6 +129,4 @@ equivalentTerms t1@(Term (In _ u1)) t2@(Term (In _ u2)) = equivalentTerms s1 t2 | Just (Syntax.Context _ s2) <- prj u2 = equivalentTerms t1 s2 - | Just aligned <- galignWith (Just . these (const False) (const False) equivalentTerms) u1 u2 - = and aligned - | otherwise = False + | otherwise = liftEq equivalentTerms u1 u2 From 1c5db3a82ffc062b6b4e652a10ae2e17431b2db1 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:12:37 -0400 Subject: [PATCH 13/44] Revert "Define subequivalence of Methods." This reverts commit 902db7cde56b43143212ac9d491a63c64d8f8ff8. --- src/Data/Syntax/Declaration.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Data/Syntax/Declaration.hs b/src/Data/Syntax/Declaration.hs index efb1e4e89..7c79abf54 100644 --- a/src/Data/Syntax/Declaration.hs +++ b/src/Data/Syntax/Declaration.hs @@ -22,10 +22,7 @@ instance Show1 Function where liftShowsPrec = genericLiftShowsPrec -- TODO: How should we represent function types, where applicable? data Method a = Method { methodContext :: ![a], methodReceiver :: !a, methodName :: !a, methodParameters :: ![a], methodBody :: !a } - deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) - -instance Diffable Method where - subequivalenceTo focus = focus . methodName + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 Method where liftEq = genericLiftEq instance Ord1 Method where liftCompare = genericLiftCompare From 8471486d1a16a41d53dc5bef67d7d58e60ef1770 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:12:41 -0400 Subject: [PATCH 14/44] Revert "Define subequivalence of Functions." This reverts commit da65ddc832de7a61ba93e5463bc17128762e7600. --- src/Data/Syntax/Declaration.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Data/Syntax/Declaration.hs b/src/Data/Syntax/Declaration.hs index 7c79abf54..9bb1ef512 100644 --- a/src/Data/Syntax/Declaration.hs +++ b/src/Data/Syntax/Declaration.hs @@ -10,10 +10,7 @@ import Data.Mergeable import GHC.Generics data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a } - deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) - -instance Diffable Function where - subequivalenceTo focus = focus . functionName + deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) instance Eq1 Function where liftEq = genericLiftEq instance Ord1 Function where liftCompare = genericLiftCompare From aca3a2cf9992579ec316b3dba25b49546c5cc80d Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:18:55 -0400 Subject: [PATCH 15/44] Add a Diffable method to select a subterm to compute equivalence by. --- src/Algorithm.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index 096aa0bf7..273d3ad27 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -147,6 +147,9 @@ class Diffable f where subequivalenceTo :: (a -> Bool) -> f a -> Bool subequivalenceTo _ _ = False + equivalentBySubterm :: f a -> Maybe a + equivalentBySubterm _ = Nothing + genericAlgorithmFor :: (Generic1 f, GDiffable (Rep1 f)) => f term1 -> f term2 From 910c179bbe0e295e05c7a92f1ef33171d0085184 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:19:26 -0400 Subject: [PATCH 16/44] Determine equivalence by the nominated subterm first. --- src/Algorithm.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index 273d3ad27..fad7cf42a 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -111,7 +111,8 @@ equivalentTerms :: Diffable syntax -> Term syntax ann2 -> Bool equivalentTerms term1@(Term (In _ syntax1)) term2@(Term (In _ syntax2)) - = subequivalenceTo (flip equivalentTerms term2) syntax1 + = fromMaybe False (equivalentTerms <$> equivalentBySubterm syntax1 <*> equivalentBySubterm syntax2) + || subequivalenceTo (flip equivalentTerms term2) syntax1 || subequivalenceTo ( equivalentTerms term1) syntax2 -- | A type class for determining what algorithm to use for diffing two terms. From 6718a713e24c0441acf871573250d55fba18f32d Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:20:06 -0400 Subject: [PATCH 17/44] Determine equivalence by subject for Context. --- src/Data/Syntax.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index 5ed549e91..ab5300f9f 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -172,6 +172,8 @@ instance Diffable Context where subequivalenceTo focus = focus . contextSubject + equivalentBySubterm = Just . contextSubject + instance Eq1 Context where liftEq = genericLiftEq instance Ord1 Context where liftCompare = genericLiftCompare instance Show1 Context where liftShowsPrec = genericLiftShowsPrec From 614c26749ea2b13a114ec3339a84cdfd1eb0cf78 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:20:45 -0400 Subject: [PATCH 18/44] Determine equivalence by name for Declaration.Function. --- src/Data/Syntax/Declaration.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Data/Syntax/Declaration.hs b/src/Data/Syntax/Declaration.hs index 9bb1ef512..1d704ff3e 100644 --- a/src/Data/Syntax/Declaration.hs +++ b/src/Data/Syntax/Declaration.hs @@ -10,7 +10,10 @@ import Data.Mergeable import GHC.Generics data Function a = Function { functionContext :: ![a], functionName :: !a, functionParameters :: ![a], functionBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + +instance Diffable Function where + equivalentBySubterm = Just . functionName instance Eq1 Function where liftEq = genericLiftEq instance Ord1 Function where liftCompare = genericLiftCompare From 407d368c90f05fcca7c45ddcc0d67e9e158fa7c4 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:21:06 -0400 Subject: [PATCH 19/44] Determine equivalence by name for Declaration.Method. --- src/Data/Syntax/Declaration.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Data/Syntax/Declaration.hs b/src/Data/Syntax/Declaration.hs index 1d704ff3e..6ad6b717d 100644 --- a/src/Data/Syntax/Declaration.hs +++ b/src/Data/Syntax/Declaration.hs @@ -22,7 +22,10 @@ instance Show1 Function where liftShowsPrec = genericLiftShowsPrec -- TODO: How should we represent function types, where applicable? data Method a = Method { methodContext :: ![a], methodReceiver :: !a, methodName :: !a, methodParameters :: ![a], methodBody :: !a } - deriving (Diffable, Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + deriving (Eq, Foldable, Functor, GAlign, Generic1, Mergeable, Ord, Show, Traversable) + +instance Diffable Method where + equivalentBySubterm = Just . methodName instance Eq1 Method where liftEq = genericLiftEq instance Ord1 Method where liftCompare = genericLiftCompare From 6536c4b06f728d4c1f7e1a15fe729964e082af29 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:31:06 -0400 Subject: [PATCH 20/44] Term equivalence falls back to recursively lifted equality. --- src/Algorithm.hs | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index fad7cf42a..fefd61297 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -106,7 +106,7 @@ algorithmForTerms t1@(Term (In ann1 f1)) t2@(Term (In ann2 f2)) <|> insertF . In ann2 <$> subalgorithmFor byInserting ( mergeFor t1) f2 where mergeFor (Term (In ann1 f1)) (Term (In ann2 f2)) = merge (ann1, ann2) <$> algorithmFor f1 f2 -equivalentTerms :: Diffable syntax +equivalentTerms :: (Diffable syntax, Eq1 syntax) => Term syntax ann1 -> Term syntax ann2 -> Bool @@ -114,6 +114,7 @@ equivalentTerms term1@(Term (In _ syntax1)) term2@(Term (In _ syntax2)) = fromMaybe False (equivalentTerms <$> equivalentBySubterm syntax1 <*> equivalentBySubterm syntax2) || subequivalenceTo (flip equivalentTerms term2) syntax1 || subequivalenceTo ( equivalentTerms term1) syntax2 + || liftEq equivalentTerms syntax1 syntax2 -- | A type class for determining what algorithm to use for diffing two terms. class Diffable f where From 59ee7e2251243b9b9deb743403f27c62a7771177 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:31:54 -0400 Subject: [PATCH 21/44] =?UTF-8?q?Use=20the=20Diffable-generic=20definition?= =?UTF-8?q?=20of=20term=20equivalence=20for=20=C3=A0=20la=20carte=20syntax?= =?UTF-8?q?.?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- src/Interpreter.hs | 25 +------------------------ 1 file changed, 1 insertion(+), 24 deletions(-) diff --git a/src/Interpreter.hs b/src/Interpreter.hs index 5f3663f2c..ca42ddef0 100644 --- a/src/Interpreter.hs +++ b/src/Interpreter.hs @@ -6,7 +6,7 @@ module Interpreter , equivalentTerms ) where -import Algorithm hiding (equivalentTerms) +import Algorithm import Control.Applicative (Alternative(..)) import Control.Monad.Free.Freer import Data.Align.Generic @@ -107,26 +107,3 @@ comparableByConstructor (In _ u1) (In _ u2) | Just Syntax.Context{} <- prj u1 = True | Just Syntax.Context{} <- prj u2 = True | otherwise = isJust (galign u1 u2) - --- | Equivalency relation for terms. Equivalence is determined by functions and --- methods with equal identifiers/names and recursively by equivalent terms with --- identical shapes. -equivalentTerms :: (Declaration.Method :< fs, Declaration.Function :< fs, Syntax.Context :< fs, Apply Eq1 fs, Apply Foldable fs) - => Term (Union fs) ann1 - -> Term (Union fs) ann2 - -> Bool -equivalentTerms t1@(Term (In _ u1)) t2@(Term (In _ u2)) - | Just (Declaration.Method _ _ identifier1 _ _) <- prj u1 - , Just (Declaration.Method _ _ identifier2 _ _) <- prj u2 - = equivalentTerms identifier1 identifier2 - | Just (Declaration.Function _ identifier1 _ _) <- prj u1 - , Just (Declaration.Function _ identifier2 _ _) <- prj u2 - = equivalentTerms identifier1 identifier2 - | Just (Syntax.Context _ s1) <- prj u1 - , Just (Syntax.Context _ s2) <- prj u2 - = equivalentTerms s1 s2 - | Just (Syntax.Context _ s1) <- prj u1 - = equivalentTerms s1 t2 - | Just (Syntax.Context _ s2) <- prj u2 - = equivalentTerms t1 s2 - | otherwise = liftEq equivalentTerms u1 u2 From ced2396fde5bc49af77914881556aeab28976e0a Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:38:10 -0400 Subject: [PATCH 22/44] Lift subterm equivalence into Unions. --- src/Algorithm.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index fefd61297..de5fd380c 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -170,6 +170,8 @@ instance Apply Diffable fs => Diffable (Union fs) where subequivalenceTo focus = apply (Proxy :: Proxy Diffable) (subequivalenceTo focus) + equivalentBySubterm = apply (Proxy :: Proxy Diffable) equivalentBySubterm + -- | Diff two 'Maybe's. instance Diffable Maybe where algorithmFor = diffMaybe From 22f5fd46d38ac68bade5ac2f92be3d973b10e6dd Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:44:14 -0400 Subject: [PATCH 23/44] Rename the genericAlgorithmFor bindings. --- src/Algorithm.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index de5fd380c..eee8217d7 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -156,7 +156,7 @@ genericAlgorithmFor :: (Generic1 f, GDiffable (Rep1 f)) => f term1 -> f term2 -> Algorithm term1 term2 result (f result) -genericAlgorithmFor a b = to1 <$> galgorithmFor (from1 a) (from1 b) +genericAlgorithmFor a1 a2 = to1 <$> galgorithmFor (from1 a1) (from1 a2) -- | Diff a Union of Syntax terms. Left is the "rest" of the Syntax terms in the Union, From adcaed3ec01585f505bd24aa2ba377cd82abe854 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:57:06 -0400 Subject: [PATCH 24/44] Define a Diffable method to determine comparability. --- src/Algorithm.hs | 19 +++++++++++++++++++ 1 file changed, 19 insertions(+) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index eee8217d7..ed37ddc5e 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -152,12 +152,19 @@ class Diffable f where equivalentBySubterm :: f a -> Maybe a equivalentBySubterm _ = Nothing + comparableTo :: f term1 -> f term2 -> Bool + default comparableTo :: (Generic1 f, GDiffable (Rep1 f)) => f term1 -> f term2 -> Bool + comparableTo = genericComparableTo + genericAlgorithmFor :: (Generic1 f, GDiffable (Rep1 f)) => f term1 -> f term2 -> Algorithm term1 term2 result (f result) genericAlgorithmFor a1 a2 = to1 <$> galgorithmFor (from1 a1) (from1 a2) +genericComparableTo :: (Generic1 f, GDiffable (Rep1 f)) => f term1 -> f term2 -> Bool +genericComparableTo a1 a2 = gcomparableTo (from1 a1) (from1 a2) + -- | Diff a Union of Syntax terms. Left is the "rest" of the Syntax terms in the Union, -- Right is the "head" of the Union. 'weaken' relaxes the Union to allow the possible @@ -172,6 +179,9 @@ instance Apply Diffable fs => Diffable (Union fs) where equivalentBySubterm = apply (Proxy :: Proxy Diffable) equivalentBySubterm + comparableTo u1 u2 = fromMaybe False (apply2 proxy comparableTo u1 u2 <|> True <$ subalgorithmFor pure pure u1 <|> True <$ subalgorithmFor pure pure u2) + where proxy = Proxy :: Proxy Diffable + -- | Diff two 'Maybe's. instance Diffable Maybe where algorithmFor = diffMaybe @@ -188,10 +198,15 @@ instance Diffable NonEmpty where class GDiffable f where galgorithmFor :: f term1 -> f term2 -> Algorithm term1 term2 result (f result) + gcomparableTo :: f term1 -> f term2 -> Bool + gcomparableTo _ _ = True + -- | Diff two constructors (M1 is the Generic1 newtype for meta-information (possibly related to type constructors, record selectors, and data types)) instance GDiffable f => GDiffable (M1 i c f) where galgorithmFor (M1 a1) (M1 a2) = M1 <$> galgorithmFor a1 a2 + gcomparableTo (M1 a1) (M1 a2) = gcomparableTo a1 a2 + -- | Diff the fields of a product type. -- i.e. data Foo a b = Foo a b (the 'Foo a b' is captured by 'a :*: b'). instance (GDiffable f, GDiffable g) => GDiffable (f :*: g) where @@ -204,6 +219,10 @@ instance (GDiffable f, GDiffable g) => GDiffable (f :+: g) where galgorithmFor (R1 b1) (R1 b2) = R1 <$> galgorithmFor b1 b2 galgorithmFor _ _ = empty + gcomparableTo (L1 _) (L1 _) = True + gcomparableTo (R1 _) (R1 _) = True + gcomparableTo _ _ = False + -- | Diff two parameters (Par1 is the Generic1 newtype representing a type parameter). -- i.e. data Foo a = Foo a (the 'a' is captured by Par1). instance GDiffable Par1 where From d453a7f2df8b2dd07c77bed46b4b64c243e80ba3 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:58:14 -0400 Subject: [PATCH 25/44] Define a comparability relation for terms. --- src/Algorithm.hs | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index ed37ddc5e..f42c520a7 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -106,6 +106,12 @@ algorithmForTerms t1@(Term (In ann1 f1)) t2@(Term (In ann2 f2)) <|> insertF . In ann2 <$> subalgorithmFor byInserting ( mergeFor t1) f2 where mergeFor (Term (In ann1 f1)) (Term (In ann2 f2)) = merge (ann1, ann2) <$> algorithmFor f1 f2 +comparableTerms :: Diffable syntax + => TermF syntax ann1 term1 + -> TermF syntax ann2 term2 + -> Bool +comparableTerms (In _ syntax1) (In _ syntax2) = comparableTo syntax1 syntax2 + equivalentTerms :: (Diffable syntax, Eq1 syntax) => Term syntax ann1 -> Term syntax ann2 From ecfb920291eac4efa91d57e1d78a9dff168a1887 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:59:19 -0400 Subject: [PATCH 26/44] :fire: the export of equivalentTerms from Interpreter. --- src/Interpreter.hs | 1 - 1 file changed, 1 deletion(-) diff --git a/src/Interpreter.hs b/src/Interpreter.hs index ca42ddef0..d5ca55925 100644 --- a/src/Interpreter.hs +++ b/src/Interpreter.hs @@ -3,7 +3,6 @@ module Interpreter ( diffTerms , diffSyntaxTerms , comparableByConstructor -, equivalentTerms ) where import Algorithm From 0d790823abe00493e818bfaf8271f1f2dc983c49 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 14:59:41 -0400 Subject: [PATCH 27/44] =?UTF-8?q?Use=20comparableTerms=20as=20the=20compar?= =?UTF-8?q?ability=20relation=20for=20=C3=A0=20la=20carte=20terms.?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- src/Interpreter.hs | 12 ++---------- 1 file changed, 2 insertions(+), 10 deletions(-) diff --git a/src/Interpreter.hs b/src/Interpreter.hs index d5ca55925..a0f333409 100644 --- a/src/Interpreter.hs +++ b/src/Interpreter.hs @@ -2,7 +2,6 @@ module Interpreter ( diffTerms , diffSyntaxTerms -, comparableByConstructor ) where import Algorithm @@ -12,7 +11,7 @@ import Data.Align.Generic import Data.Diff import Data.Functor.Classes import Data.Hashable (Hashable) -import Data.Maybe (fromMaybe, isJust) +import Data.Maybe (fromMaybe) import Data.Record import qualified Data.Syntax as Syntax import Data.Syntax.Algebra @@ -37,7 +36,7 @@ diffTerms :: (Declaration.Method :< fs, Declaration.Function :< fs, Syntax.Conte => Term (Union fs) (Record fields1) -> Term (Union fs) (Record fields2) -> Diff (Union fs) (Record fields1) (Record fields2) -diffTerms = decoratingWith comparableByConstructor equivalentTerms constructorNameAndConstantFields constructorNameAndConstantFields +diffTerms = decoratingWith comparableTerms equivalentTerms constructorNameAndConstantFields constructorNameAndConstantFields -- | Diff two terms by decorating with feature vectors computed using the supplied labelling algebra, and stripping the feature vectors from the resulting diff. decoratingWith :: (Hashable label, Diffable syntax, GAlign syntax, Traversable syntax) @@ -99,10 +98,3 @@ getLabel (In h t) = (Info.category h, case t of -- | Test whether two terms are comparable by their Category. comparableByCategory :: (HasField fields1 Category, HasField fields2 Category) => ComparabilityRelation syntax (Record fields1) (Record fields2) comparableByCategory (In a _) (In b _) = category a == category b - --- | Test whether two terms are comparable by their constructor. -comparableByConstructor :: (Syntax.Context :< fs, Apply GAlign fs) => ComparabilityRelation (Union fs) ann1 ann2 -comparableByConstructor (In _ u1) (In _ u2) - | Just Syntax.Context{} <- prj u1 = True - | Just Syntax.Context{} <- prj u2 = True - | otherwise = isJust (galign u1 u2) From 27758821e899c7b705e69727cdbda9e34455fea1 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:10:11 -0400 Subject: [PATCH 28/44] Use the comparableTerms relation in the RWS tests. --- test/Data/RandomWalkSimilarity/Spec.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/test/Data/RandomWalkSimilarity/Spec.hs b/test/Data/RandomWalkSimilarity/Spec.hs index cb0db7cd2..43167826d 100644 --- a/test/Data/RandomWalkSimilarity/Spec.hs +++ b/test/Data/RandomWalkSimilarity/Spec.hs @@ -1,6 +1,7 @@ {-# LANGUAGE DataKinds #-} module Data.RandomWalkSimilarity.Spec where +import Algorithm import Data.Array.IArray import Data.Bifunctor import Data.Diff @@ -35,12 +36,12 @@ spec = parallel $ do \ (as, bs) -> let tas = decorate <$> (as :: [Term ListableSyntax (Record '[])]) tbs = decorate <$> (bs :: [Term ListableSyntax (Record '[])]) wrap = termIn Nil . inj - diff = merge (Nil, Nil) (inj (stripDiff . diffThese <$> rws comparableByConstructor (equalTerms comparableByConstructor) tas tbs)) in + diff = merge (Nil, Nil) (inj (stripDiff . diffThese <$> rws comparableTerms (equalTerms comparableTerms) tas tbs)) in (beforeTerm diff, afterTerm diff) `shouldBe` (Just (wrap (stripTerm <$> tas)), Just (wrap (stripTerm <$> tbs))) it "produces unbiased insertions within branches" $ let (a, b) = (decorate (termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier "a")) ])), decorate (termIn Nil (inj [ termIn Nil (inj (Syntax.Identifier "b")) ]))) in - fmap (bimap stripTerm stripTerm) (rws comparableByConstructor (equalTerms comparableByConstructor) [ b ] [ a, b ]) `shouldBe` fmap (bimap stripTerm stripTerm) [ That a, These b b ] + fmap (bimap stripTerm stripTerm) (rws comparableTerms (equalTerms comparableTerms) [ b ] [ a, b ]) `shouldBe` fmap (bimap stripTerm stripTerm) [ That a, These b b ] where decorate = defaultFeatureVectorDecorator constructorNameAndConstantFields From 0fecda703a473923e774f215d643e24d8b5fa8a5 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:26:50 -0400 Subject: [PATCH 29/44] Update the fixtures. --- test/fixtures/javascript/comment.diffA-B.txt | 4 +-- test/fixtures/javascript/comment.diffB-A.txt | 4 +-- .../javascript/constructor-call.diffA-B.txt | 4 +-- .../javascript/constructor-call.diffB-A.txt | 4 +-- .../javascript/do-while-statement.diffA-B.txt | 4 +-- .../javascript/do-while-statement.diffB-A.txt | 4 +-- test/fixtures/javascript/export.diffA-B.txt | 4 +-- test/fixtures/javascript/export.diffB-A.txt | 12 +++---- .../javascript/for-of-statement.diffA-B.txt | 4 +-- .../javascript/for-of-statement.diffB-A.txt | 4 +-- .../javascript/function-call-args.diffA-B.txt | 12 +++---- .../javascript/function-call-args.diffB-A.txt | 12 +++---- .../javascript/function-call.diffA-B.txt | 4 +-- .../javascript/function-call.diffB-A.txt | 4 +-- test/fixtures/javascript/function.diffA-B.txt | 4 +-- test/fixtures/javascript/function.diffB-A.txt | 4 +-- .../javascript/identifier.diffA-B.txt | 4 +-- .../javascript/identifier.diffB-A.txt | 4 +-- test/fixtures/javascript/if.diffA-B.txt | 4 +-- test/fixtures/javascript/if.diffB-A.txt | 4 +-- test/fixtures/javascript/import.diffA-B.txt | 32 +++++++++---------- test/fixtures/javascript/import.diffB-A.txt | 32 +++++++++---------- .../javascript/method-call.diffA-B.txt | 4 +-- .../javascript/method-call.diffB-A.txt | 4 +-- .../nested-do-while-in-function.diffA-B.txt | 4 +-- .../nested-do-while-in-function.diffB-A.txt | 4 +-- .../javascript/nested-functions.diffA-B.txt | 8 ++--- .../javascript/nested-functions.diffB-A.txt | 8 ++--- test/fixtures/javascript/number.diffA-B.txt | 4 +-- test/fixtures/javascript/number.diffB-A.txt | 4 +-- test/fixtures/javascript/regex.diffA-B.txt | 4 +-- test/fixtures/javascript/regex.diffB-A.txt | 4 +-- .../relational-operator.diffA-B.txt | 10 +++--- .../relational-operator.diffB-A.txt | 10 +++--- test/fixtures/javascript/string.diffA-B.txt | 4 +-- test/fixtures/javascript/string.diffB-A.txt | 4 +-- .../subscript-access-string.diffA-B.txt | 4 +-- .../subscript-access-string.diffB-A.txt | 4 +-- .../subscript-access-variable.diffA-B.txt | 4 +-- .../subscript-access-variable.diffB-A.txt | 4 +-- .../javascript/switch-statement.diffA-B.txt | 4 +-- .../javascript/switch-statement.diffB-A.txt | 4 +-- .../javascript/throw-statement.diffA-B.txt | 4 +-- .../javascript/throw-statement.diffB-A.txt | 4 +-- .../javascript/try-statement.diffA-B.txt | 8 ++--- .../javascript/try-statement.diffB-A.txt | 8 ++--- test/fixtures/javascript/variable.diffA-B.txt | 4 +-- test/fixtures/javascript/variable.diffB-A.txt | 4 +-- .../async-function-definition.diffA-B.txt | 8 ++--- .../async-function-definition.diffB-A.txt | 12 +++---- test/fixtures/python/await.diffA-B.txt | 4 +-- test/fixtures/python/await.diffB-A.txt | 4 +-- .../python/binary-operator.diffA-B.txt | 10 +++--- test/fixtures/python/boolean.diffA-B.txt | 6 ++-- test/fixtures/python/boolean.diffB-A.txt | 6 ++-- test/fixtures/python/comment.diffB-A.txt | 4 +-- .../python/concatenated-string.diffB-A.txt | 4 +-- .../python/conditional-expression.diffB-A.txt | 4 +-- .../python/decorated-definition.diffA-B.txt | 8 ++--- .../python/decorated-definition.diffB-A.txt | 8 ++--- .../dictionary-comprehension.diffA-B.txt | 16 +++++----- .../dictionary-comprehension.diffB-A.txt | 16 +++++----- .../python/exec-statement.diffA-B.txt | 4 +-- .../python/exec-statement.diffB-A.txt | 4 +-- .../python/expression-statement.diffB-A.txt | 4 +-- test/fixtures/python/float.diffA-B.txt | 12 +++---- test/fixtures/python/float.diffB-A.txt | 18 +++++------ .../fixtures/python/for-statement.diffA-B.txt | 12 +++---- .../fixtures/python/for-statement.diffB-A.txt | 8 ++--- .../python/function-definition.diffA-B.txt | 16 +++++----- .../python/function-definition.diffB-A.txt | 16 +++++----- .../python/generator-expression.diffA-B.txt | 16 +++++----- .../python/generator-expression.diffB-A.txt | 16 +++++----- .../python/global-statement.diffA-B.txt | 4 +-- .../python/global-statement.diffB-A.txt | 4 +-- test/fixtures/python/identifier.diffA-B.txt | 6 ++-- test/fixtures/python/identifier.diffB-A.txt | 4 +-- test/fixtures/python/if-statement.diffA-B.txt | 6 ++-- .../python/import-from-statement.diffA-B.txt | 4 +-- .../python/import-from-statement.diffB-A.txt | 4 +-- .../python/import-statement.diffA-B.txt | 4 +-- .../python/import-statement.diffB-A.txt | 4 +-- test/fixtures/python/integer.diffA-B.txt | 4 +-- test/fixtures/python/integer.diffB-A.txt | 14 ++++---- .../python/list-comprehension.diffA-B.txt | 16 +++++----- .../python/list-comprehension.diffB-A.txt | 16 +++++----- .../python/non-local-statement.diffA-B.txt | 4 +-- .../python/non-local-statement.diffB-A.txt | 4 +-- .../python/print-statement.diffA-B.txt | 8 ++--- .../python/print-statement.diffB-A.txt | 4 +-- .../python/raise-statement.diffA-B.txt | 12 +++---- .../python/return-statement.diffA-B.txt | 4 +-- .../python/set-comprehension.diffA-B.txt | 16 +++++----- .../python/set-comprehension.diffB-A.txt | 16 +++++----- test/fixtures/python/string.diffA-B.txt | 4 +-- test/fixtures/python/string.diffB-A.txt | 8 ++--- test/fixtures/python/subscript.diffA-B.txt | 4 +-- test/fixtures/python/subscript.diffB-A.txt | 4 +-- .../python/with-statement.diffA-B.txt | 4 +-- .../python/with-statement.diffB-A.txt | 4 +-- test/fixtures/ruby/begin-block.diffA-B.txt | 4 +-- .../ruby/bitwise-operator.diffA-B.txt | 20 ++++++------ .../ruby/bitwise-operator.diffB-A.txt | 22 ++++++------- test/fixtures/ruby/comment.diffA-B.txt | 4 +-- test/fixtures/ruby/comment.diffB-A.txt | 4 +-- .../ruby/comparision-operator.diffA-B.txt | 10 +++--- .../ruby/comparision-operator.diffB-A.txt | 10 +++--- test/fixtures/ruby/delimiter.diffA-B.txt | 8 ++--- test/fixtures/ruby/delimiter.diffB-A.txt | 8 ++--- .../ruby/element-reference.diffA-B.txt | 4 +-- .../ruby/element-reference.diffB-A.txt | 4 +-- test/fixtures/ruby/end-block.diffA-B.txt | 4 +-- test/fixtures/ruby/for.diffB-A.txt | 4 +-- test/fixtures/ruby/interpolation.diffA-B.txt | 8 ++--- test/fixtures/ruby/interpolation.diffB-A.txt | 8 ++--- .../ruby/multiple-assignments.diffA-B.txt | 4 +-- .../ruby/multiple-assignments.diffB-A.txt | 6 ++-- test/fixtures/ruby/number.diffA-B.txt | 4 +-- test/fixtures/ruby/regex.diffA-B.txt | 6 ++-- test/fixtures/ruby/regex.diffB-A.txt | 4 +-- test/fixtures/ruby/string.diffA-B.txt | 8 ++--- test/fixtures/ruby/string.diffB-A.txt | 8 ++--- test/fixtures/ruby/subshell.diffA-B.txt | 4 +-- test/fixtures/ruby/subshell.diffB-A.txt | 4 +-- test/fixtures/ruby/symbol.diffA-B.txt | 8 ++--- test/fixtures/ruby/symbol.diffB-A.txt | 4 +-- test/fixtures/ruby/when-else.diffA-B.txt | 4 +-- test/fixtures/ruby/when-else.diffB-A.txt | 4 +-- test/fixtures/typescript/class.diffA-B.txt | 4 +-- test/fixtures/typescript/class.diffB-A.txt | 4 +-- test/fixtures/typescript/comment.diffA-B.txt | 4 +-- test/fixtures/typescript/comment.diffB-A.txt | 4 +-- .../typescript/constructor-call.diffA-B.txt | 4 +-- .../typescript/constructor-call.diffB-A.txt | 4 +-- .../typescript/do-while-statement.diffA-B.txt | 4 +-- .../typescript/do-while-statement.diffB-A.txt | 4 +-- test/fixtures/typescript/export.diffA-B.txt | 4 +-- test/fixtures/typescript/export.diffB-A.txt | 12 +++---- .../typescript/for-of-statement.diffA-B.txt | 4 +-- .../typescript/for-of-statement.diffB-A.txt | 4 +-- .../typescript/function-call-args.diffA-B.txt | 12 +++---- .../typescript/function-call-args.diffB-A.txt | 12 +++---- .../typescript/function-call.diffA-B.txt | 8 ++--- .../typescript/function-call.diffB-A.txt | 8 ++--- test/fixtures/typescript/function.diffA-B.txt | 4 +-- test/fixtures/typescript/function.diffB-A.txt | 4 +-- .../typescript/identifier.diffA-B.txt | 4 +-- .../typescript/identifier.diffB-A.txt | 4 +-- test/fixtures/typescript/if.diffA-B.txt | 4 +-- test/fixtures/typescript/if.diffB-A.txt | 4 +-- test/fixtures/typescript/import.diffA-B.txt | 32 +++++++++---------- test/fixtures/typescript/import.diffB-A.txt | 32 +++++++++---------- .../typescript/method-call.diffA-B.txt | 4 +-- .../typescript/method-call.diffB-A.txt | 4 +-- .../nested-do-while-in-function.diffA-B.txt | 4 +-- .../nested-do-while-in-function.diffB-A.txt | 4 +-- .../typescript/nested-functions.diffA-B.txt | 8 ++--- .../typescript/nested-functions.diffB-A.txt | 8 ++--- test/fixtures/typescript/number.diffA-B.txt | 4 +-- test/fixtures/typescript/number.diffB-A.txt | 4 +-- test/fixtures/typescript/regex.diffA-B.txt | 4 +-- test/fixtures/typescript/regex.diffB-A.txt | 4 +-- .../relational-operator.diffA-B.txt | 10 +++--- .../relational-operator.diffB-A.txt | 10 +++--- test/fixtures/typescript/string.diffA-B.txt | 4 +-- test/fixtures/typescript/string.diffB-A.txt | 4 +-- .../subscript-access-string.diffA-B.txt | 4 +-- .../subscript-access-string.diffB-A.txt | 4 +-- .../subscript-access-variable.diffA-B.txt | 4 +-- .../subscript-access-variable.diffB-A.txt | 4 +-- .../typescript/switch-statement.diffA-B.txt | 4 +-- .../typescript/switch-statement.diffB-A.txt | 4 +-- .../typescript/throw-statement.diffA-B.txt | 4 +-- .../typescript/throw-statement.diffB-A.txt | 4 +-- .../typescript/try-statement.diffA-B.txt | 8 ++--- .../typescript/try-statement.diffB-A.txt | 8 ++--- test/fixtures/typescript/variable.diffA-B.txt | 4 +-- test/fixtures/typescript/variable.diffB-A.txt | 4 +-- 178 files changed, 614 insertions(+), 614 deletions(-) diff --git a/test/fixtures/javascript/comment.diffA-B.txt b/test/fixtures/javascript/comment.diffA-B.txt index d313b7cf4..ab0622e59 100644 --- a/test/fixtures/javascript/comment.diffA-B.txt +++ b/test/fixtures/javascript/comment.diffA-B.txt @@ -1,5 +1,5 @@ (Program (Context - {+(Comment)+} - {-(Comment)-} + { (Comment) + ->(Comment) } (Empty))) diff --git a/test/fixtures/javascript/comment.diffB-A.txt b/test/fixtures/javascript/comment.diffB-A.txt index d313b7cf4..ab0622e59 100644 --- a/test/fixtures/javascript/comment.diffB-A.txt +++ b/test/fixtures/javascript/comment.diffB-A.txt @@ -1,5 +1,5 @@ (Program (Context - {+(Comment)+} - {-(Comment)-} + { (Comment) + ->(Comment) } (Empty))) diff --git a/test/fixtures/javascript/constructor-call.diffA-B.txt b/test/fixtures/javascript/constructor-call.diffA-B.txt index 12476992a..4cd5b5e65 100644 --- a/test/fixtures/javascript/constructor-call.diffA-B.txt +++ b/test/fixtures/javascript/constructor-call.diffA-B.txt @@ -5,6 +5,6 @@ (Identifier) (Identifier)) (Float) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty)))) diff --git a/test/fixtures/javascript/constructor-call.diffB-A.txt b/test/fixtures/javascript/constructor-call.diffB-A.txt index 12476992a..4cd5b5e65 100644 --- a/test/fixtures/javascript/constructor-call.diffB-A.txt +++ b/test/fixtures/javascript/constructor-call.diffB-A.txt @@ -5,6 +5,6 @@ (Identifier) (Identifier)) (Float) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty)))) diff --git a/test/fixtures/javascript/do-while-statement.diffA-B.txt b/test/fixtures/javascript/do-while-statement.diffA-B.txt index cc0d9d703..30c06d609 100644 --- a/test/fixtures/javascript/do-while-statement.diffA-B.txt +++ b/test/fixtures/javascript/do-while-statement.diffA-B.txt @@ -7,6 +7,6 @@ (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))))) diff --git a/test/fixtures/javascript/do-while-statement.diffB-A.txt b/test/fixtures/javascript/do-while-statement.diffB-A.txt index cc0d9d703..30c06d609 100644 --- a/test/fixtures/javascript/do-while-statement.diffB-A.txt +++ b/test/fixtures/javascript/do-while-statement.diffB-A.txt @@ -7,6 +7,6 @@ (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))))) diff --git a/test/fixtures/javascript/export.diffA-B.txt b/test/fixtures/javascript/export.diffA-B.txt index 45d600a90..d3c55c9dd 100644 --- a/test/fixtures/javascript/export.diffA-B.txt +++ b/test/fixtures/javascript/export.diffA-B.txt @@ -83,8 +83,8 @@ {+(Identifier)+} {+(Empty)+})+})) (Export - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) {+(Export {+(Function {+(Empty)+} diff --git a/test/fixtures/javascript/export.diffB-A.txt b/test/fixtures/javascript/export.diffB-A.txt index bc3a1ec6d..6629857ba 100644 --- a/test/fixtures/javascript/export.diffB-A.txt +++ b/test/fixtures/javascript/export.diffB-A.txt @@ -81,8 +81,8 @@ {-(Identifier)-} {-(Empty)-})-})) (Export - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) {-(Export {-(Function {-(Empty)-} @@ -111,8 +111,8 @@ {+(Identifier)+} {+(Identifier)+})+})+})+} (Export - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Export (ExportClause (ImportExportSpecifier @@ -131,8 +131,8 @@ {-(ImportExportSpecifier {-(Identifier)-} {-(Empty)-})-}) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) {+(Export {+(ExportClause {+(ImportExportSpecifier diff --git a/test/fixtures/javascript/for-of-statement.diffA-B.txt b/test/fixtures/javascript/for-of-statement.diffA-B.txt index 8fdf44a8b..9886795f9 100644 --- a/test/fixtures/javascript/for-of-statement.diffA-B.txt +++ b/test/fixtures/javascript/for-of-statement.diffA-B.txt @@ -7,7 +7,7 @@ ( (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)))) (Empty)) diff --git a/test/fixtures/javascript/for-of-statement.diffB-A.txt b/test/fixtures/javascript/for-of-statement.diffB-A.txt index 8fdf44a8b..9886795f9 100644 --- a/test/fixtures/javascript/for-of-statement.diffB-A.txt +++ b/test/fixtures/javascript/for-of-statement.diffB-A.txt @@ -7,7 +7,7 @@ ( (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)))) (Empty)) diff --git a/test/fixtures/javascript/function-call-args.diffA-B.txt b/test/fixtures/javascript/function-call-args.diffA-B.txt index 1d17d16e4..fd9317247 100644 --- a/test/fixtures/javascript/function-call-args.diffA-B.txt +++ b/test/fixtures/javascript/function-call-args.diffA-B.txt @@ -2,8 +2,8 @@ (Call (Identifier) (Float) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Function (Empty) (Empty) @@ -31,12 +31,12 @@ (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) (Return { (Identifier) ->(Identifier) }))) - {+(Boolean)+} - {-(Boolean)-} + { (Boolean) + ->(Boolean) } (Empty))) diff --git a/test/fixtures/javascript/function-call-args.diffB-A.txt b/test/fixtures/javascript/function-call-args.diffB-A.txt index 2425e211a..4f9a10527 100644 --- a/test/fixtures/javascript/function-call-args.diffB-A.txt +++ b/test/fixtures/javascript/function-call-args.diffB-A.txt @@ -2,8 +2,8 @@ (Call (Identifier) (Float) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Function (Empty) (Empty) @@ -26,12 +26,12 @@ (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) (Return { (Identifier) ->(Identifier) }))) - {+(Boolean)+} - {-(Boolean)-} + { (Boolean) + ->(Boolean) } (Empty))) diff --git a/test/fixtures/javascript/function-call.diffA-B.txt b/test/fixtures/javascript/function-call.diffA-B.txt index 50e7600e6..9ff4cf165 100644 --- a/test/fixtures/javascript/function-call.diffA-B.txt +++ b/test/fixtures/javascript/function-call.diffA-B.txt @@ -2,6 +2,6 @@ (Call (Identifier) (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty))) diff --git a/test/fixtures/javascript/function-call.diffB-A.txt b/test/fixtures/javascript/function-call.diffB-A.txt index 50e7600e6..9ff4cf165 100644 --- a/test/fixtures/javascript/function-call.diffB-A.txt +++ b/test/fixtures/javascript/function-call.diffB-A.txt @@ -2,6 +2,6 @@ (Call (Identifier) (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty))) diff --git a/test/fixtures/javascript/function.diffA-B.txt b/test/fixtures/javascript/function.diffA-B.txt index 961661db8..65fa21e40 100644 --- a/test/fixtures/javascript/function.diffA-B.txt +++ b/test/fixtures/javascript/function.diffA-B.txt @@ -16,6 +16,6 @@ (Identifier) (Empty))) ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Empty)) diff --git a/test/fixtures/javascript/function.diffB-A.txt b/test/fixtures/javascript/function.diffB-A.txt index 961661db8..65fa21e40 100644 --- a/test/fixtures/javascript/function.diffB-A.txt +++ b/test/fixtures/javascript/function.diffB-A.txt @@ -16,6 +16,6 @@ (Identifier) (Empty))) ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Empty)) diff --git a/test/fixtures/javascript/identifier.diffA-B.txt b/test/fixtures/javascript/identifier.diffA-B.txt index 815fc5225..6ac9cd896 100644 --- a/test/fixtures/javascript/identifier.diffA-B.txt +++ b/test/fixtures/javascript/identifier.diffA-B.txt @@ -1,3 +1,3 @@ (Program -{+(Identifier)+} -{-(Identifier)-}) +{ (Identifier) +->(Identifier) }) diff --git a/test/fixtures/javascript/identifier.diffB-A.txt b/test/fixtures/javascript/identifier.diffB-A.txt index 815fc5225..6ac9cd896 100644 --- a/test/fixtures/javascript/identifier.diffB-A.txt +++ b/test/fixtures/javascript/identifier.diffB-A.txt @@ -1,3 +1,3 @@ (Program -{+(Identifier)+} -{-(Identifier)-}) +{ (Identifier) +->(Identifier) }) diff --git a/test/fixtures/javascript/if.diffA-B.txt b/test/fixtures/javascript/if.diffA-B.txt index c69dacb57..2a90eee30 100644 --- a/test/fixtures/javascript/if.diffA-B.txt +++ b/test/fixtures/javascript/if.diffA-B.txt @@ -7,8 +7,8 @@ ( (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) {+(Identifier)+}) (Empty))) diff --git a/test/fixtures/javascript/if.diffB-A.txt b/test/fixtures/javascript/if.diffB-A.txt index 5795a5f1f..a6742d0e3 100644 --- a/test/fixtures/javascript/if.diffB-A.txt +++ b/test/fixtures/javascript/if.diffB-A.txt @@ -7,8 +7,8 @@ ( (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) {-(Identifier)-}) (Empty))) diff --git a/test/fixtures/javascript/import.diffA-B.txt b/test/fixtures/javascript/import.diffA-B.txt index bea68ce51..a570b2cfa 100644 --- a/test/fixtures/javascript/import.diffA-B.txt +++ b/test/fixtures/javascript/import.diffA-B.txt @@ -2,15 +2,15 @@ (Import (ImportClause (Identifier)) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamespaceImport { (Identifier) ->(Identifier) })) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamedImports @@ -18,8 +18,8 @@ { (Identifier) ->(Identifier) } (Empty)))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamedImports @@ -31,8 +31,8 @@ { (Identifier) ->(Identifier) } (Empty)))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamedImports @@ -45,8 +45,8 @@ ->(Identifier) } { (Identifier) ->(Identifier) }))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (Identifier) @@ -60,16 +60,16 @@ ->(Identifier) } { (Identifier) ->(Identifier) }))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (Identifier) (NamespaceImport { (Identifier) ->(Identifier) })) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import - {+(TextElement)+} - {-(TextElement)-})) + { (TextElement) + ->(TextElement) })) diff --git a/test/fixtures/javascript/import.diffB-A.txt b/test/fixtures/javascript/import.diffB-A.txt index bea68ce51..a570b2cfa 100644 --- a/test/fixtures/javascript/import.diffB-A.txt +++ b/test/fixtures/javascript/import.diffB-A.txt @@ -2,15 +2,15 @@ (Import (ImportClause (Identifier)) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamespaceImport { (Identifier) ->(Identifier) })) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamedImports @@ -18,8 +18,8 @@ { (Identifier) ->(Identifier) } (Empty)))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamedImports @@ -31,8 +31,8 @@ { (Identifier) ->(Identifier) } (Empty)))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamedImports @@ -45,8 +45,8 @@ ->(Identifier) } { (Identifier) ->(Identifier) }))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (Identifier) @@ -60,16 +60,16 @@ ->(Identifier) } { (Identifier) ->(Identifier) }))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (Identifier) (NamespaceImport { (Identifier) ->(Identifier) })) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import - {+(TextElement)+} - {-(TextElement)-})) + { (TextElement) + ->(TextElement) })) diff --git a/test/fixtures/javascript/method-call.diffA-B.txt b/test/fixtures/javascript/method-call.diffA-B.txt index 8430f65f5..04b6484e5 100644 --- a/test/fixtures/javascript/method-call.diffA-B.txt +++ b/test/fixtures/javascript/method-call.diffA-B.txt @@ -4,6 +4,6 @@ (Identifier) (Identifier)) (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty))) diff --git a/test/fixtures/javascript/method-call.diffB-A.txt b/test/fixtures/javascript/method-call.diffB-A.txt index 8430f65f5..04b6484e5 100644 --- a/test/fixtures/javascript/method-call.diffB-A.txt +++ b/test/fixtures/javascript/method-call.diffB-A.txt @@ -4,6 +4,6 @@ (Identifier) (Identifier)) (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty))) diff --git a/test/fixtures/javascript/nested-do-while-in-function.diffA-B.txt b/test/fixtures/javascript/nested-do-while-in-function.diffA-B.txt index ba5df0f57..df8b4c724 100644 --- a/test/fixtures/javascript/nested-do-while-in-function.diffA-B.txt +++ b/test/fixtures/javascript/nested-do-while-in-function.diffA-B.txt @@ -22,6 +22,6 @@ ( (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))))))) diff --git a/test/fixtures/javascript/nested-do-while-in-function.diffB-A.txt b/test/fixtures/javascript/nested-do-while-in-function.diffB-A.txt index ba5df0f57..df8b4c724 100644 --- a/test/fixtures/javascript/nested-do-while-in-function.diffB-A.txt +++ b/test/fixtures/javascript/nested-do-while-in-function.diffB-A.txt @@ -22,6 +22,6 @@ ( (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))))))) diff --git a/test/fixtures/javascript/nested-functions.diffA-B.txt b/test/fixtures/javascript/nested-functions.diffA-B.txt index cd11fbc69..66b665736 100644 --- a/test/fixtures/javascript/nested-functions.diffA-B.txt +++ b/test/fixtures/javascript/nested-functions.diffA-B.txt @@ -37,13 +37,13 @@ (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) (Call (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))))))) diff --git a/test/fixtures/javascript/nested-functions.diffB-A.txt b/test/fixtures/javascript/nested-functions.diffB-A.txt index cd11fbc69..66b665736 100644 --- a/test/fixtures/javascript/nested-functions.diffB-A.txt +++ b/test/fixtures/javascript/nested-functions.diffB-A.txt @@ -37,13 +37,13 @@ (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) (Call (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))))))) diff --git a/test/fixtures/javascript/number.diffA-B.txt b/test/fixtures/javascript/number.diffA-B.txt index 5741a6028..9c7b7f65e 100644 --- a/test/fixtures/javascript/number.diffA-B.txt +++ b/test/fixtures/javascript/number.diffA-B.txt @@ -1,3 +1,3 @@ (Program -{+(Float)+} -{-(Float)-}) +{ (Float) +->(Float) }) diff --git a/test/fixtures/javascript/number.diffB-A.txt b/test/fixtures/javascript/number.diffB-A.txt index 5741a6028..9c7b7f65e 100644 --- a/test/fixtures/javascript/number.diffB-A.txt +++ b/test/fixtures/javascript/number.diffB-A.txt @@ -1,3 +1,3 @@ (Program -{+(Float)+} -{-(Float)-}) +{ (Float) +->(Float) }) diff --git a/test/fixtures/javascript/regex.diffA-B.txt b/test/fixtures/javascript/regex.diffA-B.txt index 91633c360..9c5e630f5 100644 --- a/test/fixtures/javascript/regex.diffA-B.txt +++ b/test/fixtures/javascript/regex.diffA-B.txt @@ -1,3 +1,3 @@ (Program -{+(Regex)+} -{-(Regex)-}) +{ (Regex) +->(Regex) }) diff --git a/test/fixtures/javascript/regex.diffB-A.txt b/test/fixtures/javascript/regex.diffB-A.txt index 91633c360..9c5e630f5 100644 --- a/test/fixtures/javascript/regex.diffB-A.txt +++ b/test/fixtures/javascript/regex.diffB-A.txt @@ -1,3 +1,3 @@ (Program -{+(Regex)+} -{-(Regex)-}) +{ (Regex) +->(Regex) }) diff --git a/test/fixtures/javascript/relational-operator.diffA-B.txt b/test/fixtures/javascript/relational-operator.diffA-B.txt index 3beb3939f..b10fba844 100644 --- a/test/fixtures/javascript/relational-operator.diffA-B.txt +++ b/test/fixtures/javascript/relational-operator.diffA-B.txt @@ -1,7 +1,7 @@ (Program -{+(LessThanEqual - {+(Identifier)+} - {+(Identifier)+})+} -{-(LessThan +{ (LessThan {-(Identifier)-} - {-(Identifier)-})-}) + {-(Identifier)-}) +->(LessThanEqual + {+(Identifier)+} + {+(Identifier)+}) }) diff --git a/test/fixtures/javascript/relational-operator.diffB-A.txt b/test/fixtures/javascript/relational-operator.diffB-A.txt index b08ba1cfd..811022c76 100644 --- a/test/fixtures/javascript/relational-operator.diffB-A.txt +++ b/test/fixtures/javascript/relational-operator.diffB-A.txt @@ -1,7 +1,7 @@ (Program -{+(LessThan - {+(Identifier)+} - {+(Identifier)+})+} -{-(LessThanEqual +{ (LessThanEqual {-(Identifier)-} - {-(Identifier)-})-}) + {-(Identifier)-}) +->(LessThan + {+(Identifier)+} + {+(Identifier)+}) }) diff --git a/test/fixtures/javascript/string.diffA-B.txt b/test/fixtures/javascript/string.diffA-B.txt index 0695d0f25..c368003ca 100644 --- a/test/fixtures/javascript/string.diffA-B.txt +++ b/test/fixtures/javascript/string.diffA-B.txt @@ -1,3 +1,3 @@ (Program -{+(TextElement)+} -{-(TextElement)-}) +{ (TextElement) +->(TextElement) }) diff --git a/test/fixtures/javascript/string.diffB-A.txt b/test/fixtures/javascript/string.diffB-A.txt index 0695d0f25..c368003ca 100644 --- a/test/fixtures/javascript/string.diffB-A.txt +++ b/test/fixtures/javascript/string.diffB-A.txt @@ -1,3 +1,3 @@ (Program -{+(TextElement)+} -{-(TextElement)-}) +{ (TextElement) +->(TextElement) }) diff --git a/test/fixtures/javascript/subscript-access-string.diffA-B.txt b/test/fixtures/javascript/subscript-access-string.diffA-B.txt index 3ed3b9d54..e89be8ff9 100644 --- a/test/fixtures/javascript/subscript-access-string.diffA-B.txt +++ b/test/fixtures/javascript/subscript-access-string.diffA-B.txt @@ -1,5 +1,5 @@ (Program (Subscript (Identifier) - {+(TextElement)+} - {-(TextElement)-})) + { (TextElement) + ->(TextElement) })) diff --git a/test/fixtures/javascript/subscript-access-string.diffB-A.txt b/test/fixtures/javascript/subscript-access-string.diffB-A.txt index 3ed3b9d54..e89be8ff9 100644 --- a/test/fixtures/javascript/subscript-access-string.diffB-A.txt +++ b/test/fixtures/javascript/subscript-access-string.diffB-A.txt @@ -1,5 +1,5 @@ (Program (Subscript (Identifier) - {+(TextElement)+} - {-(TextElement)-})) + { (TextElement) + ->(TextElement) })) diff --git a/test/fixtures/javascript/subscript-access-variable.diffA-B.txt b/test/fixtures/javascript/subscript-access-variable.diffA-B.txt index 52c195a4f..428bf4bf1 100644 --- a/test/fixtures/javascript/subscript-access-variable.diffA-B.txt +++ b/test/fixtures/javascript/subscript-access-variable.diffA-B.txt @@ -1,5 +1,5 @@ (Program (Subscript (Identifier) - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) diff --git a/test/fixtures/javascript/subscript-access-variable.diffB-A.txt b/test/fixtures/javascript/subscript-access-variable.diffB-A.txt index 52c195a4f..428bf4bf1 100644 --- a/test/fixtures/javascript/subscript-access-variable.diffB-A.txt +++ b/test/fixtures/javascript/subscript-access-variable.diffB-A.txt @@ -1,5 +1,5 @@ (Program (Subscript (Identifier) - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) diff --git a/test/fixtures/javascript/switch-statement.diffA-B.txt b/test/fixtures/javascript/switch-statement.diffA-B.txt index 4d8fab67e..e72d89a5b 100644 --- a/test/fixtures/javascript/switch-statement.diffA-B.txt +++ b/test/fixtures/javascript/switch-statement.diffA-B.txt @@ -10,8 +10,8 @@ (Pattern (Float) ( - {+(Float)+} - {-(Float)-})) + { (Float) + ->(Float) })) (Pattern (Float) ( diff --git a/test/fixtures/javascript/switch-statement.diffB-A.txt b/test/fixtures/javascript/switch-statement.diffB-A.txt index 4d8fab67e..e72d89a5b 100644 --- a/test/fixtures/javascript/switch-statement.diffB-A.txt +++ b/test/fixtures/javascript/switch-statement.diffB-A.txt @@ -10,8 +10,8 @@ (Pattern (Float) ( - {+(Float)+} - {-(Float)-})) + { (Float) + ->(Float) })) (Pattern (Float) ( diff --git a/test/fixtures/javascript/throw-statement.diffA-B.txt b/test/fixtures/javascript/throw-statement.diffA-B.txt index ce5253324..a442e1a04 100644 --- a/test/fixtures/javascript/throw-statement.diffA-B.txt +++ b/test/fixtures/javascript/throw-statement.diffA-B.txt @@ -3,6 +3,6 @@ (New (Call (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty))))) diff --git a/test/fixtures/javascript/throw-statement.diffB-A.txt b/test/fixtures/javascript/throw-statement.diffB-A.txt index ce5253324..a442e1a04 100644 --- a/test/fixtures/javascript/throw-statement.diffB-A.txt +++ b/test/fixtures/javascript/throw-statement.diffB-A.txt @@ -3,6 +3,6 @@ (New (Call (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty))))) diff --git a/test/fixtures/javascript/try-statement.diffA-B.txt b/test/fixtures/javascript/try-statement.diffA-B.txt index 95160f872..a1448e34d 100644 --- a/test/fixtures/javascript/try-statement.diffA-B.txt +++ b/test/fixtures/javascript/try-statement.diffA-B.txt @@ -5,10 +5,10 @@ (Catch (Empty) ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Finally ( - {+(Identifier)+} - {-(Identifier)-}))) + { (Identifier) + ->(Identifier) }))) (Empty)) diff --git a/test/fixtures/javascript/try-statement.diffB-A.txt b/test/fixtures/javascript/try-statement.diffB-A.txt index 95160f872..a1448e34d 100644 --- a/test/fixtures/javascript/try-statement.diffB-A.txt +++ b/test/fixtures/javascript/try-statement.diffB-A.txt @@ -5,10 +5,10 @@ (Catch (Empty) ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Finally ( - {+(Identifier)+} - {-(Identifier)-}))) + { (Identifier) + ->(Identifier) }))) (Empty)) diff --git a/test/fixtures/javascript/variable.diffA-B.txt b/test/fixtures/javascript/variable.diffA-B.txt index 815fc5225..6ac9cd896 100644 --- a/test/fixtures/javascript/variable.diffA-B.txt +++ b/test/fixtures/javascript/variable.diffA-B.txt @@ -1,3 +1,3 @@ (Program -{+(Identifier)+} -{-(Identifier)-}) +{ (Identifier) +->(Identifier) }) diff --git a/test/fixtures/javascript/variable.diffB-A.txt b/test/fixtures/javascript/variable.diffB-A.txt index 815fc5225..6ac9cd896 100644 --- a/test/fixtures/javascript/variable.diffB-A.txt +++ b/test/fixtures/javascript/variable.diffB-A.txt @@ -1,3 +1,3 @@ (Program -{+(Identifier)+} -{-(Identifier)-}) +{ (Identifier) +->(Identifier) }) diff --git a/test/fixtures/python/async-function-definition.diffA-B.txt b/test/fixtures/python/async-function-definition.diffA-B.txt index 3630742ea..56b1fa7a3 100644 --- a/test/fixtures/python/async-function-definition.diffA-B.txt +++ b/test/fixtures/python/async-function-definition.diffA-B.txt @@ -8,8 +8,8 @@ (Identifier) {+(Identifier)+} ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Empty)) (Identifier)) (Annotation @@ -17,8 +17,8 @@ (Function (Identifier) ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Empty)) (Identifier)) {+(Annotation diff --git a/test/fixtures/python/async-function-definition.diffB-A.txt b/test/fixtures/python/async-function-definition.diffB-A.txt index 7fa6cb8b7..16c78756e 100644 --- a/test/fixtures/python/async-function-definition.diffB-A.txt +++ b/test/fixtures/python/async-function-definition.diffB-A.txt @@ -14,8 +14,8 @@ (Function (Identifier) ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Empty)) (Identifier)) (Annotation @@ -23,12 +23,12 @@ (Function { (Identifier) ->(Identifier) } + { (Identifier) + ->(Identifier) } {+(Identifier)+} - {+(Identifier)+} - {-(Identifier)-} ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Empty)) (Identifier)) {+(Annotation diff --git a/test/fixtures/python/await.diffA-B.txt b/test/fixtures/python/await.diffA-B.txt index d24a86379..08efc600b 100644 --- a/test/fixtures/python/await.diffA-B.txt +++ b/test/fixtures/python/await.diffA-B.txt @@ -8,6 +8,6 @@ (Empty)) (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))) diff --git a/test/fixtures/python/await.diffB-A.txt b/test/fixtures/python/await.diffB-A.txt index d24a86379..08efc600b 100644 --- a/test/fixtures/python/await.diffB-A.txt +++ b/test/fixtures/python/await.diffB-A.txt @@ -8,6 +8,6 @@ (Empty)) (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))) diff --git a/test/fixtures/python/binary-operator.diffA-B.txt b/test/fixtures/python/binary-operator.diffA-B.txt index e53b7c359..f32a3f3bf 100644 --- a/test/fixtures/python/binary-operator.diffA-B.txt +++ b/test/fixtures/python/binary-operator.diffA-B.txt @@ -32,9 +32,12 @@ {+(DividedBy {+(Identifier)+} {+(Identifier)+})+} -{+(Modulo +{ (DividedBy + {-(Identifier)-} + {-(Identifier)-}) +->(Modulo {+(Identifier)+} - {+(Identifier)+})+} + {+(Identifier)+}) } {+(DividedBy {+(Identifier)+} {+(Identifier)+})+} @@ -47,9 +50,6 @@ {+(Plus {+(Identifier)+} {+(Identifier)+})+} -{-(DividedBy - {-(Identifier)-} - {-(Identifier)-})-} {-(Power {-(Identifier)-} {-(Identifier)-})-} diff --git a/test/fixtures/python/boolean.diffA-B.txt b/test/fixtures/python/boolean.diffA-B.txt index fd4a0f410..79f1741d7 100644 --- a/test/fixtures/python/boolean.diffA-B.txt +++ b/test/fixtures/python/boolean.diffA-B.txt @@ -1,6 +1,6 @@ (Program {-(Boolean)-} (Boolean) -{+(Boolean)+} -{+(Boolean)+} -{-(Boolean)-}) +{ (Boolean) +->(Boolean) } +{+(Boolean)+}) diff --git a/test/fixtures/python/boolean.diffB-A.txt b/test/fixtures/python/boolean.diffB-A.txt index fd4a0f410..79f1741d7 100644 --- a/test/fixtures/python/boolean.diffB-A.txt +++ b/test/fixtures/python/boolean.diffB-A.txt @@ -1,6 +1,6 @@ (Program {-(Boolean)-} (Boolean) -{+(Boolean)+} -{+(Boolean)+} -{-(Boolean)-}) +{ (Boolean) +->(Boolean) } +{+(Boolean)+}) diff --git a/test/fixtures/python/comment.diffB-A.txt b/test/fixtures/python/comment.diffB-A.txt index 0dbbdf0e1..57d15fc24 100644 --- a/test/fixtures/python/comment.diffB-A.txt +++ b/test/fixtures/python/comment.diffB-A.txt @@ -2,6 +2,6 @@ (Context {-(Comment)-} (Comment) - {+(Comment)+} - {-(Comment)-} + { (Comment) + ->(Comment) } (Empty))) diff --git a/test/fixtures/python/concatenated-string.diffB-A.txt b/test/fixtures/python/concatenated-string.diffB-A.txt index 88cf4b274..4387d6826 100644 --- a/test/fixtures/python/concatenated-string.diffB-A.txt +++ b/test/fixtures/python/concatenated-string.diffB-A.txt @@ -2,6 +2,6 @@ ( {-(TextElement)-} (TextElement) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (TextElement))) diff --git a/test/fixtures/python/conditional-expression.diffB-A.txt b/test/fixtures/python/conditional-expression.diffB-A.txt index 51ad749da..22eb503ae 100644 --- a/test/fixtures/python/conditional-expression.diffB-A.txt +++ b/test/fixtures/python/conditional-expression.diffB-A.txt @@ -15,8 +15,8 @@ { (Identifier) ->(Identifier) } ( - {+(Identifier)+} - {-(Identifier)-}))) + { (Identifier) + ->(Identifier) }))) {-(If {-(Identifier)-} {-(Call diff --git a/test/fixtures/python/decorated-definition.diffA-B.txt b/test/fixtures/python/decorated-definition.diffA-B.txt index 635b5f69e..b65592463 100644 --- a/test/fixtures/python/decorated-definition.diffA-B.txt +++ b/test/fixtures/python/decorated-definition.diffA-B.txt @@ -12,15 +12,15 @@ ([]) (Decorator (ScopeResolution - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) ( {+(Identifier)+} {-(Integer)-}) (Decorator (ScopeResolution - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) ( {+(Identifier)+} {-(Integer)-} diff --git a/test/fixtures/python/decorated-definition.diffB-A.txt b/test/fixtures/python/decorated-definition.diffB-A.txt index d29b48719..b6992d978 100644 --- a/test/fixtures/python/decorated-definition.diffB-A.txt +++ b/test/fixtures/python/decorated-definition.diffB-A.txt @@ -12,15 +12,15 @@ ([]) (Decorator (ScopeResolution - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) ( {+(Integer)+} {-(Identifier)-}) (Decorator (ScopeResolution - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) ( {+(Integer)+} {+(Integer)+} diff --git a/test/fixtures/python/dictionary-comprehension.diffA-B.txt b/test/fixtures/python/dictionary-comprehension.diffA-B.txt index cac4deb1b..9230afb5b 100644 --- a/test/fixtures/python/dictionary-comprehension.diffA-B.txt +++ b/test/fixtures/python/dictionary-comprehension.diffA-B.txt @@ -8,10 +8,10 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) }) {+( {+(Identifier)+})+})) (Comprehension @@ -23,9 +23,9 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) }) {-( {-(Identifier)-})-}))) diff --git a/test/fixtures/python/dictionary-comprehension.diffB-A.txt b/test/fixtures/python/dictionary-comprehension.diffB-A.txt index a0cbf55b2..a6b913255 100644 --- a/test/fixtures/python/dictionary-comprehension.diffB-A.txt +++ b/test/fixtures/python/dictionary-comprehension.diffB-A.txt @@ -8,10 +8,10 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) }) {-( {-(Identifier)-})-})) (Comprehension @@ -23,9 +23,9 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) }) {+( {+(Identifier)+})+}))) diff --git a/test/fixtures/python/exec-statement.diffA-B.txt b/test/fixtures/python/exec-statement.diffA-B.txt index 02272e43b..8862037e8 100644 --- a/test/fixtures/python/exec-statement.diffA-B.txt +++ b/test/fixtures/python/exec-statement.diffA-B.txt @@ -1,9 +1,9 @@ (Program (Call (Identifier) - {+(TextElement)+} + { (TextElement) + ->(TextElement) } {+(Identifier)+} - {-(TextElement)-} (Empty)) (Call (Identifier) diff --git a/test/fixtures/python/exec-statement.diffB-A.txt b/test/fixtures/python/exec-statement.diffB-A.txt index 5c7cc1e96..583d2e1de 100644 --- a/test/fixtures/python/exec-statement.diffB-A.txt +++ b/test/fixtures/python/exec-statement.diffB-A.txt @@ -1,8 +1,8 @@ (Program (Call (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } {-(Identifier)-} (Empty)) (Call diff --git a/test/fixtures/python/expression-statement.diffB-A.txt b/test/fixtures/python/expression-statement.diffB-A.txt index 1bbccbc08..3146293b1 100644 --- a/test/fixtures/python/expression-statement.diffB-A.txt +++ b/test/fixtures/python/expression-statement.diffB-A.txt @@ -1,5 +1,6 @@ (Program -{+(Identifier)+} +{ (Identifier) +->(Identifier) } {+(Plus {+(Identifier)+} {+(Identifier)+})+} @@ -11,7 +12,6 @@ {+(Integer)+} {+(Integer)+} {+(Integer)+})+} -{-(Identifier)-} {-( {-(Integer)-} {-(Integer)-} diff --git a/test/fixtures/python/float.diffA-B.txt b/test/fixtures/python/float.diffA-B.txt index 8c49b18b7..52d2dd464 100644 --- a/test/fixtures/python/float.diffA-B.txt +++ b/test/fixtures/python/float.diffA-B.txt @@ -2,18 +2,18 @@ (Negate { (Float) ->(Float) }) +{ (Float) +->(Float) } {+(Float)+} {+(Float)+} {+(Float)+} +{ (Float) +->(Float) } {+(Float)+} {+(Float)+} +{ (Float) +->(Float) } {+(Float)+} -{+(Float)+} -{+(Float)+} -{+(Float)+} -{-(Float)-} -{-(Float)-} -{-(Float)-} {-(Float)-} {-(Float)-} {-(Float)-} diff --git a/test/fixtures/python/float.diffB-A.txt b/test/fixtures/python/float.diffB-A.txt index 8c49b18b7..916dc8f79 100644 --- a/test/fixtures/python/float.diffB-A.txt +++ b/test/fixtures/python/float.diffB-A.txt @@ -2,19 +2,19 @@ (Negate { (Float) ->(Float) }) +{ (Float) +->(Float) } {+(Float)+} {+(Float)+} +{ (Float) +->(Float) } +{ (Float) +->(Float) } +{+(Float)+} +{ (Float) +->(Float) } {+(Float)+} {+(Float)+} -{+(Float)+} -{+(Float)+} -{+(Float)+} -{+(Float)+} -{+(Float)+} -{-(Float)-} -{-(Float)-} -{-(Float)-} -{-(Float)-} {-(Float)-} {-(Float)-} {-(Float)-} diff --git a/test/fixtures/python/for-statement.diffA-B.txt b/test/fixtures/python/for-statement.diffA-B.txt index 2ad4cb300..55c13a7db 100644 --- a/test/fixtures/python/for-statement.diffA-B.txt +++ b/test/fixtures/python/for-statement.diffA-B.txt @@ -15,8 +15,8 @@ (ForEach ( (Identifier) - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) (Identifier) ( (Call @@ -26,8 +26,8 @@ (ForEach ( (Identifier) - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) (Identifier) ( (Call @@ -37,8 +37,8 @@ ( (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)))) {-(ForEach {-( diff --git a/test/fixtures/python/for-statement.diffB-A.txt b/test/fixtures/python/for-statement.diffB-A.txt index 704fff387..d94cab68b 100644 --- a/test/fixtures/python/for-statement.diffB-A.txt +++ b/test/fixtures/python/for-statement.diffB-A.txt @@ -27,8 +27,8 @@ {+(Empty)+})+})+})+} (ForEach ( - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) (Array (Tuple (Integer)) @@ -37,8 +37,8 @@ (Tuple (Integer))) ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) {-(Else {-(ForEach {-( diff --git a/test/fixtures/python/function-definition.diffA-B.txt b/test/fixtures/python/function-definition.diffA-B.txt index 78eebd591..168dad37d 100644 --- a/test/fixtures/python/function-definition.diffA-B.txt +++ b/test/fixtures/python/function-definition.diffA-B.txt @@ -15,13 +15,13 @@ (Annotation (Function (Identifier) - {+(Identifier)+} - {+(Identifier)+} - {-(Identifier)-} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } + { (Identifier) + ->(Identifier) } ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Empty)) {+(Annotation {+(Function @@ -55,8 +55,8 @@ ->(Integer) }) { (Identifier) ->(Identifier) }) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } ( (Identifier))) (Empty))) diff --git a/test/fixtures/python/function-definition.diffB-A.txt b/test/fixtures/python/function-definition.diffB-A.txt index d0ff011d2..bf7d101bf 100644 --- a/test/fixtures/python/function-definition.diffB-A.txt +++ b/test/fixtures/python/function-definition.diffB-A.txt @@ -18,19 +18,19 @@ (Identifier) {+(Identifier)+} ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Empty)) (Annotation (Function { (Identifier) ->(Identifier) } + { (Identifier) + ->(Identifier) } {+(Identifier)+} - {+(Identifier)+} - {-(Identifier)-} ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Empty)) {+(Annotation {+(Function @@ -51,8 +51,8 @@ ->(TextElement) }) { (Identifier) ->(Identifier) }) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } ( (Identifier))) (Empty))) diff --git a/test/fixtures/python/generator-expression.diffA-B.txt b/test/fixtures/python/generator-expression.diffA-B.txt index f100ebddc..889af8894 100644 --- a/test/fixtures/python/generator-expression.diffA-B.txt +++ b/test/fixtures/python/generator-expression.diffA-B.txt @@ -5,10 +5,10 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-}))) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) }))) (Comprehension { (Identifier) ->(Plus @@ -17,7 +17,7 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-})))) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) })))) diff --git a/test/fixtures/python/generator-expression.diffB-A.txt b/test/fixtures/python/generator-expression.diffB-A.txt index c190fac0f..91806a53e 100644 --- a/test/fixtures/python/generator-expression.diffB-A.txt +++ b/test/fixtures/python/generator-expression.diffB-A.txt @@ -5,10 +5,10 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-}))) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) }))) (Comprehension { (Plus {-(Identifier)-} @@ -17,7 +17,7 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-})))) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) })))) diff --git a/test/fixtures/python/global-statement.diffA-B.txt b/test/fixtures/python/global-statement.diffA-B.txt index aeba128f4..9485d606f 100644 --- a/test/fixtures/python/global-statement.diffA-B.txt +++ b/test/fixtures/python/global-statement.diffA-B.txt @@ -6,7 +6,7 @@ (Empty)) (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } {-(Identifier)-} (Empty))) diff --git a/test/fixtures/python/global-statement.diffB-A.txt b/test/fixtures/python/global-statement.diffB-A.txt index 1b90b4ec1..cf5086530 100644 --- a/test/fixtures/python/global-statement.diffB-A.txt +++ b/test/fixtures/python/global-statement.diffB-A.txt @@ -6,7 +6,7 @@ (Empty)) (Call (Identifier) + { (Identifier) + ->(Identifier) } {+(Identifier)+} - {+(Identifier)+} - {-(Identifier)-} (Empty))) diff --git a/test/fixtures/python/identifier.diffA-B.txt b/test/fixtures/python/identifier.diffA-B.txt index e350145f7..e16d74e6a 100644 --- a/test/fixtures/python/identifier.diffA-B.txt +++ b/test/fixtures/python/identifier.diffA-B.txt @@ -1,4 +1,4 @@ (Program -{+(Identifier)+} -{+(Identifier)+} -{-(Identifier)-}) +{ (Identifier) +->(Identifier) } +{+(Identifier)+}) diff --git a/test/fixtures/python/identifier.diffB-A.txt b/test/fixtures/python/identifier.diffB-A.txt index 34ff44b49..b35673ab9 100644 --- a/test/fixtures/python/identifier.diffB-A.txt +++ b/test/fixtures/python/identifier.diffB-A.txt @@ -1,4 +1,4 @@ (Program -{+(Identifier)+} -{-(Identifier)-} +{ (Identifier) +->(Identifier) } {-(Identifier)-}) diff --git a/test/fixtures/python/if-statement.diffA-B.txt b/test/fixtures/python/if-statement.diffA-B.txt index 4df75d39b..140ca836c 100644 --- a/test/fixtures/python/if-statement.diffA-B.txt +++ b/test/fixtures/python/if-statement.diffA-B.txt @@ -3,9 +3,9 @@ { (Identifier) ->(Identifier) } ( - {+(Identifier)+} - (Identifier) - {-(Identifier)-}) + { (Identifier) + ->(Identifier) } + (Identifier)) { (If {-(Identifier)-} {-( diff --git a/test/fixtures/python/import-from-statement.diffA-B.txt b/test/fixtures/python/import-from-statement.diffA-B.txt index faee12692..bacc78836 100644 --- a/test/fixtures/python/import-from-statement.diffA-B.txt +++ b/test/fixtures/python/import-from-statement.diffA-B.txt @@ -17,6 +17,6 @@ {+(Identifier)+})+}) (Import (ScopeResolution - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) (Identifier))) diff --git a/test/fixtures/python/import-from-statement.diffB-A.txt b/test/fixtures/python/import-from-statement.diffB-A.txt index 712e6683a..56c486f9e 100644 --- a/test/fixtures/python/import-from-statement.diffB-A.txt +++ b/test/fixtures/python/import-from-statement.diffB-A.txt @@ -15,6 +15,6 @@ (Identifier))) (Import (ScopeResolution - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) (Identifier))) diff --git a/test/fixtures/python/import-statement.diffA-B.txt b/test/fixtures/python/import-statement.diffA-B.txt index be2e4cfdb..84f434a98 100644 --- a/test/fixtures/python/import-statement.diffA-B.txt +++ b/test/fixtures/python/import-statement.diffA-B.txt @@ -14,8 +14,8 @@ { (Identifier) ->(Identifier) } (ScopeResolution - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Identifier)) (Empty)) {-(ScopeResolution diff --git a/test/fixtures/python/import-statement.diffB-A.txt b/test/fixtures/python/import-statement.diffB-A.txt index e744e0340..f9b71efde 100644 --- a/test/fixtures/python/import-statement.diffB-A.txt +++ b/test/fixtures/python/import-statement.diffB-A.txt @@ -14,8 +14,8 @@ { (Identifier) ->(Identifier) } (ScopeResolution - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Identifier)) (Empty)) {+(ScopeResolution diff --git a/test/fixtures/python/integer.diffA-B.txt b/test/fixtures/python/integer.diffA-B.txt index 35436f3e5..8df16fdb3 100644 --- a/test/fixtures/python/integer.diffA-B.txt +++ b/test/fixtures/python/integer.diffA-B.txt @@ -2,7 +2,8 @@ (Negate { (Integer) ->(Integer) }) -{+(Integer)+} +{ (Integer) +->(Integer) } {+(Integer)+} {+(Integer)+} {+(Negate @@ -17,7 +18,6 @@ {+(Integer)+} {-(Integer)-} {-(Integer)-} -{-(Integer)-} {-(Negate {-(Integer)-})-} {-(Integer)-} diff --git a/test/fixtures/python/integer.diffB-A.txt b/test/fixtures/python/integer.diffB-A.txt index 35436f3e5..cac966d3c 100644 --- a/test/fixtures/python/integer.diffB-A.txt +++ b/test/fixtures/python/integer.diffB-A.txt @@ -2,22 +2,22 @@ (Negate { (Integer) ->(Integer) }) -{+(Integer)+} +{ (Integer) +->(Integer) } {+(Integer)+} {+(Integer)+} {+(Negate {+(Integer)+})+} {+(Integer)+} +{ (Integer) +->(Integer) } +{+(Integer)+} +{ (Integer) +->(Integer) } {+(Integer)+} {+(Integer)+} {+(Integer)+} {+(Integer)+} -{+(Integer)+} -{+(Integer)+} -{+(Integer)+} -{-(Integer)-} -{-(Integer)-} -{-(Integer)-} {-(Negate {-(Integer)-})-} {-(Integer)-} diff --git a/test/fixtures/python/list-comprehension.diffA-B.txt b/test/fixtures/python/list-comprehension.diffA-B.txt index 0f524dd87..38547d7f4 100644 --- a/test/fixtures/python/list-comprehension.diffA-B.txt +++ b/test/fixtures/python/list-comprehension.diffA-B.txt @@ -5,10 +5,10 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) }) {+( {+(Call {+(Identifier)+} @@ -29,9 +29,9 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) }) {-( {-(Identifier)-})-}))) diff --git a/test/fixtures/python/list-comprehension.diffB-A.txt b/test/fixtures/python/list-comprehension.diffB-A.txt index 9e9a52a3b..53ee58672 100644 --- a/test/fixtures/python/list-comprehension.diffB-A.txt +++ b/test/fixtures/python/list-comprehension.diffB-A.txt @@ -5,10 +5,10 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) }) {-( {-(Call {-(Identifier)-} @@ -29,9 +29,9 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) }) {+( {+(Identifier)+})+}))) diff --git a/test/fixtures/python/non-local-statement.diffA-B.txt b/test/fixtures/python/non-local-statement.diffA-B.txt index 51e9d1f45..b0e558bc3 100644 --- a/test/fixtures/python/non-local-statement.diffA-B.txt +++ b/test/fixtures/python/non-local-statement.diffA-B.txt @@ -1,6 +1,6 @@ (Program (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))) diff --git a/test/fixtures/python/non-local-statement.diffB-A.txt b/test/fixtures/python/non-local-statement.diffB-A.txt index 51e9d1f45..b0e558bc3 100644 --- a/test/fixtures/python/non-local-statement.diffB-A.txt +++ b/test/fixtures/python/non-local-statement.diffB-A.txt @@ -1,6 +1,6 @@ (Program (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))) diff --git a/test/fixtures/python/print-statement.diffA-B.txt b/test/fixtures/python/print-statement.diffA-B.txt index c27148c0f..08522ada5 100644 --- a/test/fixtures/python/print-statement.diffA-B.txt +++ b/test/fixtures/python/print-statement.diffA-B.txt @@ -1,14 +1,14 @@ (Program (Call (Identifier) - {+(Identifier)+} + { (Identifier) + ->(Identifier) } (Identifier) - {-(Identifier)-} (Empty)) (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) (Call (Identifier) diff --git a/test/fixtures/python/print-statement.diffB-A.txt b/test/fixtures/python/print-statement.diffB-A.txt index 8ca2d5ff0..9a797a52d 100644 --- a/test/fixtures/python/print-statement.diffB-A.txt +++ b/test/fixtures/python/print-statement.diffB-A.txt @@ -7,8 +7,8 @@ (Empty)) (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) (Call (Identifier) diff --git a/test/fixtures/python/raise-statement.diffA-B.txt b/test/fixtures/python/raise-statement.diffA-B.txt index 32c80833c..1df340c41 100644 --- a/test/fixtures/python/raise-statement.diffA-B.txt +++ b/test/fixtures/python/raise-statement.diffA-B.txt @@ -3,17 +3,17 @@ ( (Call (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty)))) (Throw ( (Call (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty)) - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Throw ([]))) diff --git a/test/fixtures/python/return-statement.diffA-B.txt b/test/fixtures/python/return-statement.diffA-B.txt index 20723b2e1..c9e2603b7 100644 --- a/test/fixtures/python/return-statement.diffA-B.txt +++ b/test/fixtures/python/return-statement.diffA-B.txt @@ -6,8 +6,8 @@ ->(Identifier) } { (Identifier) ->(Identifier) }) - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Return (Empty)) {+(Return diff --git a/test/fixtures/python/set-comprehension.diffA-B.txt b/test/fixtures/python/set-comprehension.diffA-B.txt index f100ebddc..889af8894 100644 --- a/test/fixtures/python/set-comprehension.diffA-B.txt +++ b/test/fixtures/python/set-comprehension.diffA-B.txt @@ -5,10 +5,10 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-}))) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) }))) (Comprehension { (Identifier) ->(Plus @@ -17,7 +17,7 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-})))) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) })))) diff --git a/test/fixtures/python/set-comprehension.diffB-A.txt b/test/fixtures/python/set-comprehension.diffB-A.txt index c190fac0f..91806a53e 100644 --- a/test/fixtures/python/set-comprehension.diffB-A.txt +++ b/test/fixtures/python/set-comprehension.diffB-A.txt @@ -5,10 +5,10 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-}))) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) }))) (Comprehension { (Plus {-(Identifier)-} @@ -17,7 +17,7 @@ ( ( ( - {+(Identifier)+} - {-(Identifier)-}) - {+(Identifier)+} - {-(Identifier)-})))) + { (Identifier) + ->(Identifier) }) + { (Identifier) + ->(Identifier) })))) diff --git a/test/fixtures/python/string.diffA-B.txt b/test/fixtures/python/string.diffA-B.txt index afbe89b51..558b37e44 100644 --- a/test/fixtures/python/string.diffA-B.txt +++ b/test/fixtures/python/string.diffA-B.txt @@ -1,5 +1,6 @@ (Program -{+(TextElement)+} +{ (TextElement) +->(TextElement) } (TextElement) {+(TextElement)+} {+(TextElement)+} @@ -10,7 +11,6 @@ {-(TextElement)-} {-(TextElement)-} {-(TextElement)-} -{-(TextElement)-} {-(TextElement)-} (TextElement) {-(TextElement)-}) diff --git a/test/fixtures/python/string.diffB-A.txt b/test/fixtures/python/string.diffB-A.txt index 3c7a825d6..55414460b 100644 --- a/test/fixtures/python/string.diffB-A.txt +++ b/test/fixtures/python/string.diffB-A.txt @@ -2,13 +2,13 @@ {-(TextElement)-} (TextElement) {+(TextElement)+} +{ (TextElement) +->(TextElement) } {+(TextElement)+} {+(TextElement)+} {+(TextElement)+} -{+(TextElement)+} -{+(TextElement)+} -{-(TextElement)-} -{-(TextElement)-} +{ (TextElement) +->(TextElement) } {-(TextElement)-} {-(TextElement)-} {-(TextElement)-} diff --git a/test/fixtures/python/subscript.diffA-B.txt b/test/fixtures/python/subscript.diffA-B.txt index 3b930367e..2598bfe20 100644 --- a/test/fixtures/python/subscript.diffA-B.txt +++ b/test/fixtures/python/subscript.diffA-B.txt @@ -2,5 +2,5 @@ (Subscript { (Identifier) ->(Identifier) } - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) diff --git a/test/fixtures/python/subscript.diffB-A.txt b/test/fixtures/python/subscript.diffB-A.txt index 3b930367e..2598bfe20 100644 --- a/test/fixtures/python/subscript.diffB-A.txt +++ b/test/fixtures/python/subscript.diffB-A.txt @@ -2,5 +2,5 @@ (Subscript { (Identifier) ->(Identifier) } - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) diff --git a/test/fixtures/python/with-statement.diffA-B.txt b/test/fixtures/python/with-statement.diffA-B.txt index 39a3ee8f6..7e25d1e9e 100644 --- a/test/fixtures/python/with-statement.diffA-B.txt +++ b/test/fixtures/python/with-statement.diffA-B.txt @@ -5,5 +5,5 @@ { (Identifier) ->(Identifier) } ( - {+(Identifier)+} - {-(Identifier)-}))) + { (Identifier) + ->(Identifier) }))) diff --git a/test/fixtures/python/with-statement.diffB-A.txt b/test/fixtures/python/with-statement.diffB-A.txt index 39a3ee8f6..7e25d1e9e 100644 --- a/test/fixtures/python/with-statement.diffB-A.txt +++ b/test/fixtures/python/with-statement.diffB-A.txt @@ -5,5 +5,5 @@ { (Identifier) ->(Identifier) } ( - {+(Identifier)+} - {-(Identifier)-}))) + { (Identifier) + ->(Identifier) }))) diff --git a/test/fixtures/ruby/begin-block.diffA-B.txt b/test/fixtures/ruby/begin-block.diffA-B.txt index 25c1fcd5e..bce079417 100644 --- a/test/fixtures/ruby/begin-block.diffA-B.txt +++ b/test/fixtures/ruby/begin-block.diffA-B.txt @@ -1,5 +1,5 @@ (Program {+(Identifier)+} (ScopeEntry - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) diff --git a/test/fixtures/ruby/bitwise-operator.diffA-B.txt b/test/fixtures/ruby/bitwise-operator.diffA-B.txt index 9ff097cd4..564f3f500 100644 --- a/test/fixtures/ruby/bitwise-operator.diffA-B.txt +++ b/test/fixtures/ruby/bitwise-operator.diffA-B.txt @@ -1,16 +1,16 @@ (Program -{+(BAnd - {+(Identifier)+} - {+(Identifier)+})+} -{+(LShift - {+(Identifier)+} - {+(Identifier)+})+} -{-(BOr +{ (BOr {-(Identifier)-} - {-(Identifier)-})-} -{-(RShift + {-(Identifier)-}) +->(BAnd + {+(Identifier)+} + {+(Identifier)+}) } +{ (RShift {-(Identifier)-} - {-(Identifier)-})-} + {-(Identifier)-}) +->(LShift + {+(Identifier)+} + {+(Identifier)+}) } {-(BXOr {-(Identifier)-} {-(Identifier)-})-}) diff --git a/test/fixtures/ruby/bitwise-operator.diffB-A.txt b/test/fixtures/ruby/bitwise-operator.diffB-A.txt index 38b0d0ef4..c0f6cdb2e 100644 --- a/test/fixtures/ruby/bitwise-operator.diffB-A.txt +++ b/test/fixtures/ruby/bitwise-operator.diffB-A.txt @@ -1,16 +1,16 @@ (Program -{+(BOr +{ (BAnd + {-(Identifier)-} + {-(Identifier)-}) +->(BOr {+(Identifier)+} - {+(Identifier)+})+} -{+(RShift + {+(Identifier)+}) } +{ (LShift + {-(Identifier)-} + {-(Identifier)-}) +->(RShift {+(Identifier)+} - {+(Identifier)+})+} + {+(Identifier)+}) } {+(BXOr {+(Identifier)+} - {+(Identifier)+})+} -{-(BAnd - {-(Identifier)-} - {-(Identifier)-})-} -{-(LShift - {-(Identifier)-} - {-(Identifier)-})-}) + {+(Identifier)+})+}) diff --git a/test/fixtures/ruby/comment.diffA-B.txt b/test/fixtures/ruby/comment.diffA-B.txt index d313b7cf4..ab0622e59 100644 --- a/test/fixtures/ruby/comment.diffA-B.txt +++ b/test/fixtures/ruby/comment.diffA-B.txt @@ -1,5 +1,5 @@ (Program (Context - {+(Comment)+} - {-(Comment)-} + { (Comment) + ->(Comment) } (Empty))) diff --git a/test/fixtures/ruby/comment.diffB-A.txt b/test/fixtures/ruby/comment.diffB-A.txt index d313b7cf4..ab0622e59 100644 --- a/test/fixtures/ruby/comment.diffB-A.txt +++ b/test/fixtures/ruby/comment.diffB-A.txt @@ -1,5 +1,5 @@ (Program (Context - {+(Comment)+} - {-(Comment)-} + { (Comment) + ->(Comment) } (Empty))) diff --git a/test/fixtures/ruby/comparision-operator.diffA-B.txt b/test/fixtures/ruby/comparision-operator.diffA-B.txt index 6e5e66dc7..05236df2d 100644 --- a/test/fixtures/ruby/comparision-operator.diffA-B.txt +++ b/test/fixtures/ruby/comparision-operator.diffA-B.txt @@ -1,13 +1,13 @@ (Program -{+(LessThanEqual +{ (LessThan + {-(Identifier)-} + {-(Identifier)-}) +->(LessThanEqual {+(Identifier)+} - {+(Identifier)+})+} + {+(Identifier)+}) } {+(GreaterThanEqual {+(Identifier)+} {+(Identifier)+})+} -{-(LessThan - {-(Identifier)-} - {-(Identifier)-})-} {-(GreaterThan {-(Identifier)-} {-(Identifier)-})-}) diff --git a/test/fixtures/ruby/comparision-operator.diffB-A.txt b/test/fixtures/ruby/comparision-operator.diffB-A.txt index a7175163a..4c2443911 100644 --- a/test/fixtures/ruby/comparision-operator.diffB-A.txt +++ b/test/fixtures/ruby/comparision-operator.diffB-A.txt @@ -1,13 +1,13 @@ (Program -{+(LessThan +{ (LessThanEqual + {-(Identifier)-} + {-(Identifier)-}) +->(LessThan {+(Identifier)+} - {+(Identifier)+})+} + {+(Identifier)+}) } {+(GreaterThan {+(Identifier)+} {+(Identifier)+})+} -{-(LessThanEqual - {-(Identifier)-} - {-(Identifier)-})-} {-(GreaterThanEqual {-(Identifier)-} {-(Identifier)-})-}) diff --git a/test/fixtures/ruby/delimiter.diffA-B.txt b/test/fixtures/ruby/delimiter.diffA-B.txt index cb091f81c..e7e1220f2 100644 --- a/test/fixtures/ruby/delimiter.diffA-B.txt +++ b/test/fixtures/ruby/delimiter.diffA-B.txt @@ -3,10 +3,10 @@ {+(TextElement)+} {+(TextElement)+} {+(TextElement)+} -{+(TextElement)+} -{+(TextElement)+} -{-(TextElement)-} -{-(TextElement)-} +{ (TextElement) +->(TextElement) } +{ (TextElement) +->(TextElement) } {-(TextElement)-} {-(TextElement)-} {-(TextElement)-} diff --git a/test/fixtures/ruby/delimiter.diffB-A.txt b/test/fixtures/ruby/delimiter.diffB-A.txt index cb091f81c..f69979390 100644 --- a/test/fixtures/ruby/delimiter.diffB-A.txt +++ b/test/fixtures/ruby/delimiter.diffB-A.txt @@ -1,12 +1,12 @@ (Program {+(TextElement)+} +{ (TextElement) +->(TextElement) } {+(TextElement)+} {+(TextElement)+} {+(TextElement)+} -{+(TextElement)+} -{+(TextElement)+} -{-(TextElement)-} -{-(TextElement)-} +{ (TextElement) +->(TextElement) } {-(TextElement)-} {-(TextElement)-} {-(TextElement)-} diff --git a/test/fixtures/ruby/element-reference.diffA-B.txt b/test/fixtures/ruby/element-reference.diffA-B.txt index 41e511609..aafa20058 100644 --- a/test/fixtures/ruby/element-reference.diffA-B.txt +++ b/test/fixtures/ruby/element-reference.diffA-B.txt @@ -7,8 +7,8 @@ (Subscript { (Identifier) ->(Identifier) } - {+(Symbol)+} - {-(Symbol)-}) + { (Symbol) + ->(Symbol) }) {-(Assignment {-(Subscript {-(Identifier)-} diff --git a/test/fixtures/ruby/element-reference.diffB-A.txt b/test/fixtures/ruby/element-reference.diffB-A.txt index d8603e4c4..6598ed5e2 100644 --- a/test/fixtures/ruby/element-reference.diffB-A.txt +++ b/test/fixtures/ruby/element-reference.diffB-A.txt @@ -7,8 +7,8 @@ (Subscript { (Identifier) ->(Identifier) } - {+(Symbol)+} - {-(Symbol)-}) + { (Symbol) + ->(Symbol) }) {+(Assignment {+(Subscript {+(Identifier)+} diff --git a/test/fixtures/ruby/end-block.diffA-B.txt b/test/fixtures/ruby/end-block.diffA-B.txt index 81f64fa1a..761acb510 100644 --- a/test/fixtures/ruby/end-block.diffA-B.txt +++ b/test/fixtures/ruby/end-block.diffA-B.txt @@ -1,5 +1,5 @@ (Program {+(Identifier)+} (ScopeExit - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) diff --git a/test/fixtures/ruby/for.diffB-A.txt b/test/fixtures/ruby/for.diffB-A.txt index 98916ef1c..396c9dcf2 100644 --- a/test/fixtures/ruby/for.diffB-A.txt +++ b/test/fixtures/ruby/for.diffB-A.txt @@ -12,8 +12,8 @@ {+(Identifier)+})+} (ForEach ( - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) { (Array {-(Integer)-} {-(Integer)-} diff --git a/test/fixtures/ruby/interpolation.diffA-B.txt b/test/fixtures/ruby/interpolation.diffA-B.txt index 8d6ffecdb..c0a24bfee 100644 --- a/test/fixtures/ruby/interpolation.diffA-B.txt +++ b/test/fixtures/ruby/interpolation.diffA-B.txt @@ -1,5 +1,5 @@ (Program -{+(Symbol)+} -{+(TextElement)+} -{-(Symbol)-} -{-(TextElement)-}) +{ (Symbol) +->(Symbol) } +{ (TextElement) +->(TextElement) }) diff --git a/test/fixtures/ruby/interpolation.diffB-A.txt b/test/fixtures/ruby/interpolation.diffB-A.txt index 8d6ffecdb..c0a24bfee 100644 --- a/test/fixtures/ruby/interpolation.diffB-A.txt +++ b/test/fixtures/ruby/interpolation.diffB-A.txt @@ -1,5 +1,5 @@ (Program -{+(Symbol)+} -{+(TextElement)+} -{-(Symbol)-} -{-(TextElement)-}) +{ (Symbol) +->(Symbol) } +{ (TextElement) +->(TextElement) }) diff --git a/test/fixtures/ruby/multiple-assignments.diffA-B.txt b/test/fixtures/ruby/multiple-assignments.diffA-B.txt index c2d26304f..8645f3aef 100644 --- a/test/fixtures/ruby/multiple-assignments.diffA-B.txt +++ b/test/fixtures/ruby/multiple-assignments.diffA-B.txt @@ -2,8 +2,8 @@ (Assignment ( (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } {-(Identifier)-}) (Array (Integer) diff --git a/test/fixtures/ruby/multiple-assignments.diffB-A.txt b/test/fixtures/ruby/multiple-assignments.diffB-A.txt index 07ac0d537..9ed61e0d3 100644 --- a/test/fixtures/ruby/multiple-assignments.diffB-A.txt +++ b/test/fixtures/ruby/multiple-assignments.diffB-A.txt @@ -2,9 +2,9 @@ (Assignment ( (Identifier) - {+(Identifier)+} - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) } + {+(Identifier)+}) (Array (Integer) (Integer) diff --git a/test/fixtures/ruby/number.diffA-B.txt b/test/fixtures/ruby/number.diffA-B.txt index 433ee8148..edc5fb6dc 100644 --- a/test/fixtures/ruby/number.diffA-B.txt +++ b/test/fixtures/ruby/number.diffA-B.txt @@ -1,6 +1,7 @@ (Program {+(Integer)+} -{+(Integer)+} +{ (Integer) +->(Integer) } {+(Integer)+} {+(Integer)+} {+(Integer)+} @@ -11,5 +12,4 @@ {-(Integer)-} {-(Integer)-} {-(Integer)-} -{-(Integer)-} {-(Float)-}) diff --git a/test/fixtures/ruby/regex.diffA-B.txt b/test/fixtures/ruby/regex.diffA-B.txt index 732d2e573..fb3fb0954 100644 --- a/test/fixtures/ruby/regex.diffA-B.txt +++ b/test/fixtures/ruby/regex.diffA-B.txt @@ -1,4 +1,4 @@ (Program -{+(Regex)+} -{+(Regex)+} -{-(Regex)-}) +{ (Regex) +->(Regex) } +{+(Regex)+}) diff --git a/test/fixtures/ruby/regex.diffB-A.txt b/test/fixtures/ruby/regex.diffB-A.txt index cfee1709a..0edbcd5e1 100644 --- a/test/fixtures/ruby/regex.diffB-A.txt +++ b/test/fixtures/ruby/regex.diffB-A.txt @@ -1,4 +1,4 @@ (Program -{+(Regex)+} -{-(Regex)-} +{ (Regex) +->(Regex) } {-(Regex)-}) diff --git a/test/fixtures/ruby/string.diffA-B.txt b/test/fixtures/ruby/string.diffA-B.txt index e8dece007..f88ed6117 100644 --- a/test/fixtures/ruby/string.diffA-B.txt +++ b/test/fixtures/ruby/string.diffA-B.txt @@ -1,5 +1,5 @@ (Program -{+(TextElement)+} -{+(TextElement)+} -{-(TextElement)-} -{-(TextElement)-}) +{ (TextElement) +->(TextElement) } +{ (TextElement) +->(TextElement) }) diff --git a/test/fixtures/ruby/string.diffB-A.txt b/test/fixtures/ruby/string.diffB-A.txt index e8dece007..f88ed6117 100644 --- a/test/fixtures/ruby/string.diffB-A.txt +++ b/test/fixtures/ruby/string.diffB-A.txt @@ -1,5 +1,5 @@ (Program -{+(TextElement)+} -{+(TextElement)+} -{-(TextElement)-} -{-(TextElement)-}) +{ (TextElement) +->(TextElement) } +{ (TextElement) +->(TextElement) }) diff --git a/test/fixtures/ruby/subshell.diffA-B.txt b/test/fixtures/ruby/subshell.diffA-B.txt index 0695d0f25..c368003ca 100644 --- a/test/fixtures/ruby/subshell.diffA-B.txt +++ b/test/fixtures/ruby/subshell.diffA-B.txt @@ -1,3 +1,3 @@ (Program -{+(TextElement)+} -{-(TextElement)-}) +{ (TextElement) +->(TextElement) }) diff --git a/test/fixtures/ruby/subshell.diffB-A.txt b/test/fixtures/ruby/subshell.diffB-A.txt index 0695d0f25..c368003ca 100644 --- a/test/fixtures/ruby/subshell.diffB-A.txt +++ b/test/fixtures/ruby/subshell.diffB-A.txt @@ -1,3 +1,3 @@ (Program -{+(TextElement)+} -{-(TextElement)-}) +{ (TextElement) +->(TextElement) }) diff --git a/test/fixtures/ruby/symbol.diffA-B.txt b/test/fixtures/ruby/symbol.diffA-B.txt index 8be3df5c2..4e4701d0f 100644 --- a/test/fixtures/ruby/symbol.diffA-B.txt +++ b/test/fixtures/ruby/symbol.diffA-B.txt @@ -1,7 +1,7 @@ (Program +{ (Symbol) +->(Symbol) } {+(Symbol)+} -{+(Symbol)+} -{+(Symbol)+} -{-(Symbol)-} -{-(Symbol)-} +{ (Symbol) +->(Symbol) } {-(Symbol)-}) diff --git a/test/fixtures/ruby/symbol.diffB-A.txt b/test/fixtures/ruby/symbol.diffB-A.txt index 8be3df5c2..f78d2a84b 100644 --- a/test/fixtures/ruby/symbol.diffB-A.txt +++ b/test/fixtures/ruby/symbol.diffB-A.txt @@ -1,7 +1,7 @@ (Program +{ (Symbol) +->(Symbol) } {+(Symbol)+} {+(Symbol)+} -{+(Symbol)+} -{-(Symbol)-} {-(Symbol)-} {-(Symbol)-}) diff --git a/test/fixtures/ruby/when-else.diffA-B.txt b/test/fixtures/ruby/when-else.diffA-B.txt index 27858eab3..351ee5af5 100644 --- a/test/fixtures/ruby/when-else.diffA-B.txt +++ b/test/fixtures/ruby/when-else.diffA-B.txt @@ -4,8 +4,8 @@ ( (Pattern ( - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) ( {+(Identifier)+} {+(Identifier)+} diff --git a/test/fixtures/ruby/when-else.diffB-A.txt b/test/fixtures/ruby/when-else.diffB-A.txt index 968de42bc..6faa8148c 100644 --- a/test/fixtures/ruby/when-else.diffB-A.txt +++ b/test/fixtures/ruby/when-else.diffB-A.txt @@ -4,8 +4,8 @@ ( (Pattern ( - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) ( {+(Pattern {+( diff --git a/test/fixtures/typescript/class.diffA-B.txt b/test/fixtures/typescript/class.diffA-B.txt index f476d41be..fb37bba0c 100644 --- a/test/fixtures/typescript/class.diffA-B.txt +++ b/test/fixtures/typescript/class.diffA-B.txt @@ -7,8 +7,8 @@ { (Identifier) ->(Identifier) } (ExtendsClause - {+(TypeIdentifier)+} - {-(TypeIdentifier)-}) + { (TypeIdentifier) + ->(TypeIdentifier) }) {+(Method {+(Empty)+} {+(Empty)+} diff --git a/test/fixtures/typescript/class.diffB-A.txt b/test/fixtures/typescript/class.diffB-A.txt index b2417d64f..ea8642cf5 100644 --- a/test/fixtures/typescript/class.diffB-A.txt +++ b/test/fixtures/typescript/class.diffB-A.txt @@ -7,8 +7,8 @@ { (Identifier) ->(Identifier) } (ExtendsClause - {+(TypeIdentifier)+} - {-(TypeIdentifier)-}) + { (TypeIdentifier) + ->(TypeIdentifier) }) {+(PublicFieldDefinition {+(Empty)+} {+(Empty)+} diff --git a/test/fixtures/typescript/comment.diffA-B.txt b/test/fixtures/typescript/comment.diffA-B.txt index d313b7cf4..ab0622e59 100644 --- a/test/fixtures/typescript/comment.diffA-B.txt +++ b/test/fixtures/typescript/comment.diffA-B.txt @@ -1,5 +1,5 @@ (Program (Context - {+(Comment)+} - {-(Comment)-} + { (Comment) + ->(Comment) } (Empty))) diff --git a/test/fixtures/typescript/comment.diffB-A.txt b/test/fixtures/typescript/comment.diffB-A.txt index d313b7cf4..ab0622e59 100644 --- a/test/fixtures/typescript/comment.diffB-A.txt +++ b/test/fixtures/typescript/comment.diffB-A.txt @@ -1,5 +1,5 @@ (Program (Context - {+(Comment)+} - {-(Comment)-} + { (Comment) + ->(Comment) } (Empty))) diff --git a/test/fixtures/typescript/constructor-call.diffA-B.txt b/test/fixtures/typescript/constructor-call.diffA-B.txt index 12476992a..4cd5b5e65 100644 --- a/test/fixtures/typescript/constructor-call.diffA-B.txt +++ b/test/fixtures/typescript/constructor-call.diffA-B.txt @@ -5,6 +5,6 @@ (Identifier) (Identifier)) (Float) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty)))) diff --git a/test/fixtures/typescript/constructor-call.diffB-A.txt b/test/fixtures/typescript/constructor-call.diffB-A.txt index 12476992a..4cd5b5e65 100644 --- a/test/fixtures/typescript/constructor-call.diffB-A.txt +++ b/test/fixtures/typescript/constructor-call.diffB-A.txt @@ -5,6 +5,6 @@ (Identifier) (Identifier)) (Float) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty)))) diff --git a/test/fixtures/typescript/do-while-statement.diffA-B.txt b/test/fixtures/typescript/do-while-statement.diffA-B.txt index cc0d9d703..30c06d609 100644 --- a/test/fixtures/typescript/do-while-statement.diffA-B.txt +++ b/test/fixtures/typescript/do-while-statement.diffA-B.txt @@ -7,6 +7,6 @@ (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))))) diff --git a/test/fixtures/typescript/do-while-statement.diffB-A.txt b/test/fixtures/typescript/do-while-statement.diffB-A.txt index cc0d9d703..30c06d609 100644 --- a/test/fixtures/typescript/do-while-statement.diffB-A.txt +++ b/test/fixtures/typescript/do-while-statement.diffB-A.txt @@ -7,6 +7,6 @@ (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))))) diff --git a/test/fixtures/typescript/export.diffA-B.txt b/test/fixtures/typescript/export.diffA-B.txt index 45d600a90..d3c55c9dd 100644 --- a/test/fixtures/typescript/export.diffA-B.txt +++ b/test/fixtures/typescript/export.diffA-B.txt @@ -83,8 +83,8 @@ {+(Identifier)+} {+(Empty)+})+})) (Export - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) {+(Export {+(Function {+(Empty)+} diff --git a/test/fixtures/typescript/export.diffB-A.txt b/test/fixtures/typescript/export.diffB-A.txt index bc3a1ec6d..6629857ba 100644 --- a/test/fixtures/typescript/export.diffB-A.txt +++ b/test/fixtures/typescript/export.diffB-A.txt @@ -81,8 +81,8 @@ {-(Identifier)-} {-(Empty)-})-})) (Export - {+(Identifier)+} - {-(Identifier)-}) + { (Identifier) + ->(Identifier) }) {-(Export {-(Function {-(Empty)-} @@ -111,8 +111,8 @@ {+(Identifier)+} {+(Identifier)+})+})+})+} (Export - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Export (ExportClause (ImportExportSpecifier @@ -131,8 +131,8 @@ {-(ImportExportSpecifier {-(Identifier)-} {-(Empty)-})-}) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) {+(Export {+(ExportClause {+(ImportExportSpecifier diff --git a/test/fixtures/typescript/for-of-statement.diffA-B.txt b/test/fixtures/typescript/for-of-statement.diffA-B.txt index 8fdf44a8b..9886795f9 100644 --- a/test/fixtures/typescript/for-of-statement.diffA-B.txt +++ b/test/fixtures/typescript/for-of-statement.diffA-B.txt @@ -7,7 +7,7 @@ ( (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)))) (Empty)) diff --git a/test/fixtures/typescript/for-of-statement.diffB-A.txt b/test/fixtures/typescript/for-of-statement.diffB-A.txt index 8fdf44a8b..9886795f9 100644 --- a/test/fixtures/typescript/for-of-statement.diffB-A.txt +++ b/test/fixtures/typescript/for-of-statement.diffB-A.txt @@ -7,7 +7,7 @@ ( (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)))) (Empty)) diff --git a/test/fixtures/typescript/function-call-args.diffA-B.txt b/test/fixtures/typescript/function-call-args.diffA-B.txt index 1d17d16e4..fd9317247 100644 --- a/test/fixtures/typescript/function-call-args.diffA-B.txt +++ b/test/fixtures/typescript/function-call-args.diffA-B.txt @@ -2,8 +2,8 @@ (Call (Identifier) (Float) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Function (Empty) (Empty) @@ -31,12 +31,12 @@ (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) (Return { (Identifier) ->(Identifier) }))) - {+(Boolean)+} - {-(Boolean)-} + { (Boolean) + ->(Boolean) } (Empty))) diff --git a/test/fixtures/typescript/function-call-args.diffB-A.txt b/test/fixtures/typescript/function-call-args.diffB-A.txt index 2425e211a..4f9a10527 100644 --- a/test/fixtures/typescript/function-call-args.diffB-A.txt +++ b/test/fixtures/typescript/function-call-args.diffB-A.txt @@ -2,8 +2,8 @@ (Call (Identifier) (Float) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Function (Empty) (Empty) @@ -26,12 +26,12 @@ (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) (Return { (Identifier) ->(Identifier) }))) - {+(Boolean)+} - {-(Boolean)-} + { (Boolean) + ->(Boolean) } (Empty))) diff --git a/test/fixtures/typescript/function-call.diffA-B.txt b/test/fixtures/typescript/function-call.diffA-B.txt index 841f8af73..f2fa351c1 100644 --- a/test/fixtures/typescript/function-call.diffA-B.txt +++ b/test/fixtures/typescript/function-call.diffA-B.txt @@ -1,9 +1,9 @@ (Program (Call - {+(TypeIdentifier)+} - {-(TypeIdentifier)-} + { (TypeIdentifier) + ->(TypeIdentifier) } (Identifier) (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty))) diff --git a/test/fixtures/typescript/function-call.diffB-A.txt b/test/fixtures/typescript/function-call.diffB-A.txt index 841f8af73..f2fa351c1 100644 --- a/test/fixtures/typescript/function-call.diffB-A.txt +++ b/test/fixtures/typescript/function-call.diffB-A.txt @@ -1,9 +1,9 @@ (Program (Call - {+(TypeIdentifier)+} - {-(TypeIdentifier)-} + { (TypeIdentifier) + ->(TypeIdentifier) } (Identifier) (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty))) diff --git a/test/fixtures/typescript/function.diffA-B.txt b/test/fixtures/typescript/function.diffA-B.txt index d645bc87d..3e30524f1 100644 --- a/test/fixtures/typescript/function.diffA-B.txt +++ b/test/fixtures/typescript/function.diffA-B.txt @@ -23,6 +23,6 @@ (Identifier) (Empty))) ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Empty)) diff --git a/test/fixtures/typescript/function.diffB-A.txt b/test/fixtures/typescript/function.diffB-A.txt index 4c0aa96d7..4687cb905 100644 --- a/test/fixtures/typescript/function.diffB-A.txt +++ b/test/fixtures/typescript/function.diffB-A.txt @@ -23,6 +23,6 @@ (Identifier) (Empty))) ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Empty)) diff --git a/test/fixtures/typescript/identifier.diffA-B.txt b/test/fixtures/typescript/identifier.diffA-B.txt index 815fc5225..6ac9cd896 100644 --- a/test/fixtures/typescript/identifier.diffA-B.txt +++ b/test/fixtures/typescript/identifier.diffA-B.txt @@ -1,3 +1,3 @@ (Program -{+(Identifier)+} -{-(Identifier)-}) +{ (Identifier) +->(Identifier) }) diff --git a/test/fixtures/typescript/identifier.diffB-A.txt b/test/fixtures/typescript/identifier.diffB-A.txt index 815fc5225..6ac9cd896 100644 --- a/test/fixtures/typescript/identifier.diffB-A.txt +++ b/test/fixtures/typescript/identifier.diffB-A.txt @@ -1,3 +1,3 @@ (Program -{+(Identifier)+} -{-(Identifier)-}) +{ (Identifier) +->(Identifier) }) diff --git a/test/fixtures/typescript/if.diffA-B.txt b/test/fixtures/typescript/if.diffA-B.txt index c69dacb57..2a90eee30 100644 --- a/test/fixtures/typescript/if.diffA-B.txt +++ b/test/fixtures/typescript/if.diffA-B.txt @@ -7,8 +7,8 @@ ( (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) {+(Identifier)+}) (Empty))) diff --git a/test/fixtures/typescript/if.diffB-A.txt b/test/fixtures/typescript/if.diffB-A.txt index 5795a5f1f..a6742d0e3 100644 --- a/test/fixtures/typescript/if.diffB-A.txt +++ b/test/fixtures/typescript/if.diffB-A.txt @@ -7,8 +7,8 @@ ( (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) {-(Identifier)-}) (Empty))) diff --git a/test/fixtures/typescript/import.diffA-B.txt b/test/fixtures/typescript/import.diffA-B.txt index bea68ce51..a570b2cfa 100644 --- a/test/fixtures/typescript/import.diffA-B.txt +++ b/test/fixtures/typescript/import.diffA-B.txt @@ -2,15 +2,15 @@ (Import (ImportClause (Identifier)) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamespaceImport { (Identifier) ->(Identifier) })) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamedImports @@ -18,8 +18,8 @@ { (Identifier) ->(Identifier) } (Empty)))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamedImports @@ -31,8 +31,8 @@ { (Identifier) ->(Identifier) } (Empty)))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamedImports @@ -45,8 +45,8 @@ ->(Identifier) } { (Identifier) ->(Identifier) }))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (Identifier) @@ -60,16 +60,16 @@ ->(Identifier) } { (Identifier) ->(Identifier) }))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (Identifier) (NamespaceImport { (Identifier) ->(Identifier) })) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import - {+(TextElement)+} - {-(TextElement)-})) + { (TextElement) + ->(TextElement) })) diff --git a/test/fixtures/typescript/import.diffB-A.txt b/test/fixtures/typescript/import.diffB-A.txt index bea68ce51..a570b2cfa 100644 --- a/test/fixtures/typescript/import.diffB-A.txt +++ b/test/fixtures/typescript/import.diffB-A.txt @@ -2,15 +2,15 @@ (Import (ImportClause (Identifier)) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamespaceImport { (Identifier) ->(Identifier) })) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamedImports @@ -18,8 +18,8 @@ { (Identifier) ->(Identifier) } (Empty)))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamedImports @@ -31,8 +31,8 @@ { (Identifier) ->(Identifier) } (Empty)))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (NamedImports @@ -45,8 +45,8 @@ ->(Identifier) } { (Identifier) ->(Identifier) }))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (Identifier) @@ -60,16 +60,16 @@ ->(Identifier) } { (Identifier) ->(Identifier) }))) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import (ImportClause (Identifier) (NamespaceImport { (Identifier) ->(Identifier) })) - {+(TextElement)+} - {-(TextElement)-}) + { (TextElement) + ->(TextElement) }) (Import - {+(TextElement)+} - {-(TextElement)-})) + { (TextElement) + ->(TextElement) })) diff --git a/test/fixtures/typescript/method-call.diffA-B.txt b/test/fixtures/typescript/method-call.diffA-B.txt index 8430f65f5..04b6484e5 100644 --- a/test/fixtures/typescript/method-call.diffA-B.txt +++ b/test/fixtures/typescript/method-call.diffA-B.txt @@ -4,6 +4,6 @@ (Identifier) (Identifier)) (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty))) diff --git a/test/fixtures/typescript/method-call.diffB-A.txt b/test/fixtures/typescript/method-call.diffB-A.txt index 8430f65f5..04b6484e5 100644 --- a/test/fixtures/typescript/method-call.diffB-A.txt +++ b/test/fixtures/typescript/method-call.diffB-A.txt @@ -4,6 +4,6 @@ (Identifier) (Identifier)) (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty))) diff --git a/test/fixtures/typescript/nested-do-while-in-function.diffA-B.txt b/test/fixtures/typescript/nested-do-while-in-function.diffA-B.txt index ba5df0f57..df8b4c724 100644 --- a/test/fixtures/typescript/nested-do-while-in-function.diffA-B.txt +++ b/test/fixtures/typescript/nested-do-while-in-function.diffA-B.txt @@ -22,6 +22,6 @@ ( (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))))))) diff --git a/test/fixtures/typescript/nested-do-while-in-function.diffB-A.txt b/test/fixtures/typescript/nested-do-while-in-function.diffB-A.txt index ba5df0f57..df8b4c724 100644 --- a/test/fixtures/typescript/nested-do-while-in-function.diffB-A.txt +++ b/test/fixtures/typescript/nested-do-while-in-function.diffB-A.txt @@ -22,6 +22,6 @@ ( (Call (Identifier) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))))))) diff --git a/test/fixtures/typescript/nested-functions.diffA-B.txt b/test/fixtures/typescript/nested-functions.diffA-B.txt index cd11fbc69..66b665736 100644 --- a/test/fixtures/typescript/nested-functions.diffA-B.txt +++ b/test/fixtures/typescript/nested-functions.diffA-B.txt @@ -37,13 +37,13 @@ (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) (Call (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))))))) diff --git a/test/fixtures/typescript/nested-functions.diffB-A.txt b/test/fixtures/typescript/nested-functions.diffB-A.txt index cd11fbc69..66b665736 100644 --- a/test/fixtures/typescript/nested-functions.diffB-A.txt +++ b/test/fixtures/typescript/nested-functions.diffB-A.txt @@ -37,13 +37,13 @@ (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty)) (Call (MemberAccess (Identifier) (Identifier)) - {+(Identifier)+} - {-(Identifier)-} + { (Identifier) + ->(Identifier) } (Empty))))))) diff --git a/test/fixtures/typescript/number.diffA-B.txt b/test/fixtures/typescript/number.diffA-B.txt index 5741a6028..9c7b7f65e 100644 --- a/test/fixtures/typescript/number.diffA-B.txt +++ b/test/fixtures/typescript/number.diffA-B.txt @@ -1,3 +1,3 @@ (Program -{+(Float)+} -{-(Float)-}) +{ (Float) +->(Float) }) diff --git a/test/fixtures/typescript/number.diffB-A.txt b/test/fixtures/typescript/number.diffB-A.txt index 5741a6028..9c7b7f65e 100644 --- a/test/fixtures/typescript/number.diffB-A.txt +++ b/test/fixtures/typescript/number.diffB-A.txt @@ -1,3 +1,3 @@ (Program -{+(Float)+} -{-(Float)-}) +{ (Float) +->(Float) }) diff --git a/test/fixtures/typescript/regex.diffA-B.txt b/test/fixtures/typescript/regex.diffA-B.txt index 91633c360..9c5e630f5 100644 --- a/test/fixtures/typescript/regex.diffA-B.txt +++ b/test/fixtures/typescript/regex.diffA-B.txt @@ -1,3 +1,3 @@ (Program -{+(Regex)+} -{-(Regex)-}) +{ (Regex) +->(Regex) }) diff --git a/test/fixtures/typescript/regex.diffB-A.txt b/test/fixtures/typescript/regex.diffB-A.txt index 91633c360..9c5e630f5 100644 --- a/test/fixtures/typescript/regex.diffB-A.txt +++ b/test/fixtures/typescript/regex.diffB-A.txt @@ -1,3 +1,3 @@ (Program -{+(Regex)+} -{-(Regex)-}) +{ (Regex) +->(Regex) }) diff --git a/test/fixtures/typescript/relational-operator.diffA-B.txt b/test/fixtures/typescript/relational-operator.diffA-B.txt index 3beb3939f..b10fba844 100644 --- a/test/fixtures/typescript/relational-operator.diffA-B.txt +++ b/test/fixtures/typescript/relational-operator.diffA-B.txt @@ -1,7 +1,7 @@ (Program -{+(LessThanEqual - {+(Identifier)+} - {+(Identifier)+})+} -{-(LessThan +{ (LessThan {-(Identifier)-} - {-(Identifier)-})-}) + {-(Identifier)-}) +->(LessThanEqual + {+(Identifier)+} + {+(Identifier)+}) }) diff --git a/test/fixtures/typescript/relational-operator.diffB-A.txt b/test/fixtures/typescript/relational-operator.diffB-A.txt index b08ba1cfd..811022c76 100644 --- a/test/fixtures/typescript/relational-operator.diffB-A.txt +++ b/test/fixtures/typescript/relational-operator.diffB-A.txt @@ -1,7 +1,7 @@ (Program -{+(LessThan - {+(Identifier)+} - {+(Identifier)+})+} -{-(LessThanEqual +{ (LessThanEqual {-(Identifier)-} - {-(Identifier)-})-}) + {-(Identifier)-}) +->(LessThan + {+(Identifier)+} + {+(Identifier)+}) }) diff --git a/test/fixtures/typescript/string.diffA-B.txt b/test/fixtures/typescript/string.diffA-B.txt index 0695d0f25..c368003ca 100644 --- a/test/fixtures/typescript/string.diffA-B.txt +++ b/test/fixtures/typescript/string.diffA-B.txt @@ -1,3 +1,3 @@ (Program -{+(TextElement)+} -{-(TextElement)-}) +{ (TextElement) +->(TextElement) }) diff --git a/test/fixtures/typescript/string.diffB-A.txt b/test/fixtures/typescript/string.diffB-A.txt index 0695d0f25..c368003ca 100644 --- a/test/fixtures/typescript/string.diffB-A.txt +++ b/test/fixtures/typescript/string.diffB-A.txt @@ -1,3 +1,3 @@ (Program -{+(TextElement)+} -{-(TextElement)-}) +{ (TextElement) +->(TextElement) }) diff --git a/test/fixtures/typescript/subscript-access-string.diffA-B.txt b/test/fixtures/typescript/subscript-access-string.diffA-B.txt index 3ed3b9d54..e89be8ff9 100644 --- a/test/fixtures/typescript/subscript-access-string.diffA-B.txt +++ b/test/fixtures/typescript/subscript-access-string.diffA-B.txt @@ -1,5 +1,5 @@ (Program (Subscript (Identifier) - {+(TextElement)+} - {-(TextElement)-})) + { (TextElement) + ->(TextElement) })) diff --git a/test/fixtures/typescript/subscript-access-string.diffB-A.txt b/test/fixtures/typescript/subscript-access-string.diffB-A.txt index 3ed3b9d54..e89be8ff9 100644 --- a/test/fixtures/typescript/subscript-access-string.diffB-A.txt +++ b/test/fixtures/typescript/subscript-access-string.diffB-A.txt @@ -1,5 +1,5 @@ (Program (Subscript (Identifier) - {+(TextElement)+} - {-(TextElement)-})) + { (TextElement) + ->(TextElement) })) diff --git a/test/fixtures/typescript/subscript-access-variable.diffA-B.txt b/test/fixtures/typescript/subscript-access-variable.diffA-B.txt index 52c195a4f..428bf4bf1 100644 --- a/test/fixtures/typescript/subscript-access-variable.diffA-B.txt +++ b/test/fixtures/typescript/subscript-access-variable.diffA-B.txt @@ -1,5 +1,5 @@ (Program (Subscript (Identifier) - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) diff --git a/test/fixtures/typescript/subscript-access-variable.diffB-A.txt b/test/fixtures/typescript/subscript-access-variable.diffB-A.txt index 52c195a4f..428bf4bf1 100644 --- a/test/fixtures/typescript/subscript-access-variable.diffB-A.txt +++ b/test/fixtures/typescript/subscript-access-variable.diffB-A.txt @@ -1,5 +1,5 @@ (Program (Subscript (Identifier) - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) diff --git a/test/fixtures/typescript/switch-statement.diffA-B.txt b/test/fixtures/typescript/switch-statement.diffA-B.txt index 4d8fab67e..e72d89a5b 100644 --- a/test/fixtures/typescript/switch-statement.diffA-B.txt +++ b/test/fixtures/typescript/switch-statement.diffA-B.txt @@ -10,8 +10,8 @@ (Pattern (Float) ( - {+(Float)+} - {-(Float)-})) + { (Float) + ->(Float) })) (Pattern (Float) ( diff --git a/test/fixtures/typescript/switch-statement.diffB-A.txt b/test/fixtures/typescript/switch-statement.diffB-A.txt index 4d8fab67e..e72d89a5b 100644 --- a/test/fixtures/typescript/switch-statement.diffB-A.txt +++ b/test/fixtures/typescript/switch-statement.diffB-A.txt @@ -10,8 +10,8 @@ (Pattern (Float) ( - {+(Float)+} - {-(Float)-})) + { (Float) + ->(Float) })) (Pattern (Float) ( diff --git a/test/fixtures/typescript/throw-statement.diffA-B.txt b/test/fixtures/typescript/throw-statement.diffA-B.txt index ce5253324..a442e1a04 100644 --- a/test/fixtures/typescript/throw-statement.diffA-B.txt +++ b/test/fixtures/typescript/throw-statement.diffA-B.txt @@ -3,6 +3,6 @@ (New (Call (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty))))) diff --git a/test/fixtures/typescript/throw-statement.diffB-A.txt b/test/fixtures/typescript/throw-statement.diffB-A.txt index ce5253324..a442e1a04 100644 --- a/test/fixtures/typescript/throw-statement.diffB-A.txt +++ b/test/fixtures/typescript/throw-statement.diffB-A.txt @@ -3,6 +3,6 @@ (New (Call (Identifier) - {+(TextElement)+} - {-(TextElement)-} + { (TextElement) + ->(TextElement) } (Empty))))) diff --git a/test/fixtures/typescript/try-statement.diffA-B.txt b/test/fixtures/typescript/try-statement.diffA-B.txt index 95160f872..a1448e34d 100644 --- a/test/fixtures/typescript/try-statement.diffA-B.txt +++ b/test/fixtures/typescript/try-statement.diffA-B.txt @@ -5,10 +5,10 @@ (Catch (Empty) ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Finally ( - {+(Identifier)+} - {-(Identifier)-}))) + { (Identifier) + ->(Identifier) }))) (Empty)) diff --git a/test/fixtures/typescript/try-statement.diffB-A.txt b/test/fixtures/typescript/try-statement.diffB-A.txt index 95160f872..a1448e34d 100644 --- a/test/fixtures/typescript/try-statement.diffB-A.txt +++ b/test/fixtures/typescript/try-statement.diffB-A.txt @@ -5,10 +5,10 @@ (Catch (Empty) ( - {+(Identifier)+} - {-(Identifier)-})) + { (Identifier) + ->(Identifier) })) (Finally ( - {+(Identifier)+} - {-(Identifier)-}))) + { (Identifier) + ->(Identifier) }))) (Empty)) diff --git a/test/fixtures/typescript/variable.diffA-B.txt b/test/fixtures/typescript/variable.diffA-B.txt index 815fc5225..6ac9cd896 100644 --- a/test/fixtures/typescript/variable.diffA-B.txt +++ b/test/fixtures/typescript/variable.diffA-B.txt @@ -1,3 +1,3 @@ (Program -{+(Identifier)+} -{-(Identifier)-}) +{ (Identifier) +->(Identifier) }) diff --git a/test/fixtures/typescript/variable.diffB-A.txt b/test/fixtures/typescript/variable.diffB-A.txt index 815fc5225..6ac9cd896 100644 --- a/test/fixtures/typescript/variable.diffB-A.txt +++ b/test/fixtures/typescript/variable.diffB-A.txt @@ -1,3 +1,3 @@ (Program -{+(Identifier)+} -{-(Identifier)-}) +{ (Identifier) +->(Identifier) }) From d2c9faf96f031f17b26b1ffabcfd67dbfe5ce883 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:27:36 -0400 Subject: [PATCH 30/44] :fire: the membership constraints on diffTerms. --- src/Interpreter.hs | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/src/Interpreter.hs b/src/Interpreter.hs index a0f333409..ad49c6bcf 100644 --- a/src/Interpreter.hs +++ b/src/Interpreter.hs @@ -13,9 +13,7 @@ import Data.Functor.Classes import Data.Hashable (Hashable) import Data.Maybe (fromMaybe) import Data.Record -import qualified Data.Syntax as Syntax import Data.Syntax.Algebra -import qualified Data.Syntax.Declaration as Declaration import Data.Term import Data.Text (Text) import Data.Union @@ -32,7 +30,7 @@ diffSyntaxTerms :: (HasField fields1 Category, HasField fields2 Category) diffSyntaxTerms = decoratingWith comparableByCategory (equalTerms comparableByCategory) getLabel getLabel -- | Diff two à la carte terms recursively. -diffTerms :: (Declaration.Method :< fs, Declaration.Function :< fs, Syntax.Context :< fs, Apply Diffable fs, Apply Eq1 fs, Apply Foldable fs, Apply Functor fs, Apply GAlign fs, Apply Show1 fs, Apply Traversable fs) +diffTerms :: (Apply Diffable fs, Apply Eq1 fs, Apply Foldable fs, Apply Functor fs, Apply GAlign fs, Apply Show1 fs, Apply Traversable fs) => Term (Union fs) (Record fields1) -> Term (Union fs) (Record fields2) -> Diff (Union fs) (Record fields1) (Record fields2) From 4717bde7a8216d3e1fafabfcb6eb45fa16680ec8 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:28:40 -0400 Subject: [PATCH 31/44] Generalize diffTerms over the syntax functor. --- src/Interpreter.hs | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/src/Interpreter.hs b/src/Interpreter.hs index ad49c6bcf..f7eb32fa3 100644 --- a/src/Interpreter.hs +++ b/src/Interpreter.hs @@ -16,7 +16,6 @@ import Data.Record import Data.Syntax.Algebra import Data.Term import Data.Text (Text) -import Data.Union import Info hiding (Empty, Return) import RWS import Syntax (Syntax(Leaf)) @@ -30,10 +29,10 @@ diffSyntaxTerms :: (HasField fields1 Category, HasField fields2 Category) diffSyntaxTerms = decoratingWith comparableByCategory (equalTerms comparableByCategory) getLabel getLabel -- | Diff two à la carte terms recursively. -diffTerms :: (Apply Diffable fs, Apply Eq1 fs, Apply Foldable fs, Apply Functor fs, Apply GAlign fs, Apply Show1 fs, Apply Traversable fs) - => Term (Union fs) (Record fields1) - -> Term (Union fs) (Record fields2) - -> Diff (Union fs) (Record fields1) (Record fields2) +diffTerms :: (Diffable syntax, Eq1 syntax, Foldable syntax, Functor syntax, GAlign syntax, Show1 syntax, Traversable syntax) + => Term syntax (Record fields1) + -> Term syntax (Record fields2) + -> Diff syntax (Record fields1) (Record fields2) diffTerms = decoratingWith comparableTerms equivalentTerms constructorNameAndConstantFields constructorNameAndConstantFields -- | Diff two terms by decorating with feature vectors computed using the supplied labelling algebra, and stripping the feature vectors from the resulting diff. From d2382539d1d35097e5125d74573e8494d280cc06 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:29:37 -0400 Subject: [PATCH 32/44] :fire: Declaration.Function, Declaration.Method, & Syntax.Context from Markdown syntax. --- src/Language/Markdown/Syntax.hs | 5 ----- 1 file changed, 5 deletions(-) diff --git a/src/Language/Markdown/Syntax.hs b/src/Language/Markdown/Syntax.hs index 214c5deb4..dac54d807 100644 --- a/src/Language/Markdown/Syntax.hs +++ b/src/Language/Markdown/Syntax.hs @@ -14,7 +14,6 @@ import Data.Syntax (makeTerm) import qualified Data.Syntax as Syntax import Data.Syntax.Assignment hiding (Assignment, Error) import qualified Data.Syntax.Assignment as Assignment -import qualified Data.Syntax.Declaration as Declaration import qualified Data.Syntax.Markup as Markup import Data.Term as Term (Term(..), TermF(..), termIn, unwrap) import qualified Data.Text as Text @@ -46,10 +45,6 @@ type Syntax = , Markup.Strong , Markup.Text , Markup.Strikethrough - -- NB: Diffing requires Methods, Functions, and Context in the union. - , Declaration.Method - , Declaration.Function - , Syntax.Context -- Assignment errors; cmark does not provide parse errors. , Syntax.Error , [] From 1a10479af66f314756a3c535d6c713a2f7aff4fa Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:30:13 -0400 Subject: [PATCH 33/44] :fire: Declaration.Function, Declaration.Method, & Syntax.Context from JSON syntax. --- src/Language/JSON/Syntax.hs | 5 ----- 1 file changed, 5 deletions(-) diff --git a/src/Language/JSON/Syntax.hs b/src/Language/JSON/Syntax.hs index f26ade54d..0a5f77557 100644 --- a/src/Language/JSON/Syntax.hs +++ b/src/Language/JSON/Syntax.hs @@ -11,7 +11,6 @@ import Data.Syntax (makeTerm, parseError) import qualified Data.Syntax as Syntax import Data.Syntax.Assignment hiding (Assignment, Error) import qualified Data.Syntax.Assignment as Assignment -import qualified Data.Syntax.Declaration as Declaration import qualified Data.Syntax.Literal as Literal import qualified Data.Term as Term import Data.Union @@ -27,10 +26,6 @@ type Syntax = , Literal.Null , Literal.String , Literal.TextElement - -- NB: Diffing requires Methods, Functions, and Context in the union. - , Declaration.Method - , Declaration.Function - , Syntax.Context , Syntax.Error , [] ] From b0723ee027eb8dc1927fc2a4cbcf76d6e906f8ca Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:31:18 -0400 Subject: [PATCH 34/44] Clarify the comment on the inclusion of Method in Python. --- src/Language/Python/Syntax.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Language/Python/Syntax.hs b/src/Language/Python/Syntax.hs index e49f713b1..b12cb2c1d 100644 --- a/src/Language/Python/Syntax.hs +++ b/src/Language/Python/Syntax.hs @@ -39,7 +39,7 @@ type Syntax = , Declaration.Decorator , Declaration.Function , Declaration.Import - -- NB: Diffing requires Methods in the union. + -- NB: ToC rendering requires Methods in the union. , Declaration.Method , Declaration.Variable , Expression.Arithmetic From 8c9be81e51354d17c419a0919c3fef0a9ffea75c Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:37:17 -0400 Subject: [PATCH 35/44] Define an Equivalence functor. --- src/Algorithm.hs | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index f42c520a7..30661d16a 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -122,6 +122,17 @@ equivalentTerms term1@(Term (In _ syntax1)) term2@(Term (In _ syntax2)) || subequivalenceTo ( equivalentTerms term1) syntax2 || liftEq equivalentTerms syntax1 syntax2 +newtype Equivalence a = Equivalence { runEquivalence :: Bool } + deriving (Eq, Functor) + +instance Applicative Equivalence where + pure _ = Equivalence True + Equivalence a <*> Equivalence b = Equivalence (a && b) + +instance Alternative Equivalence where + empty = Equivalence False + Equivalence a <|> Equivalence b = Equivalence (a || b) + -- | A type class for determining what algorithm to use for diffing two terms. class Diffable f where -- | Construct an algorithm to diff a pair of @f@s populated with disjoint terms. From cceed477437139aba65d5e3b8334e8fe60014aa8 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:37:42 -0400 Subject: [PATCH 36/44] Determine subequivalence using Equivalence & subalgorithmFor. --- src/Algorithm.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index 30661d16a..9b0ba662e 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -118,8 +118,8 @@ equivalentTerms :: (Diffable syntax, Eq1 syntax) -> Bool equivalentTerms term1@(Term (In _ syntax1)) term2@(Term (In _ syntax2)) = fromMaybe False (equivalentTerms <$> equivalentBySubterm syntax1 <*> equivalentBySubterm syntax2) - || subequivalenceTo (flip equivalentTerms term2) syntax1 - || subequivalenceTo ( equivalentTerms term1) syntax2 + || runEquivalence (subalgorithmFor pure (Equivalence . flip equivalentTerms term2) syntax1) + || runEquivalence (subalgorithmFor pure (Equivalence . equivalentTerms term1) syntax2) || liftEq equivalentTerms syntax1 syntax2 newtype Equivalence a = Equivalence { runEquivalence :: Bool } From 8e9158c7f0f80ac4391745f608eece6f3e72c875 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:37:51 -0400 Subject: [PATCH 37/44] :fire: subequivalenceTo. --- src/Algorithm.hs | 5 ----- src/Data/Syntax.hs | 2 -- 2 files changed, 7 deletions(-) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index 9b0ba662e..96131e3c8 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -163,9 +163,6 @@ class Diffable f where -> g (f b) -- ^ The resulting algorithm (or other 'Alternative' context), producing the traversed syntax. subalgorithmFor _ _ _ = empty - subequivalenceTo :: (a -> Bool) -> f a -> Bool - subequivalenceTo _ _ = False - equivalentBySubterm :: f a -> Maybe a equivalentBySubterm _ = Nothing @@ -192,8 +189,6 @@ instance Apply Diffable fs => Diffable (Union fs) where subalgorithmFor blur focus = apply' (Proxy :: Proxy Diffable) (\ inj f -> inj <$> subalgorithmFor blur focus f) - subequivalenceTo focus = apply (Proxy :: Proxy Diffable) (subequivalenceTo focus) - equivalentBySubterm = apply (Proxy :: Proxy Diffable) equivalentBySubterm comparableTo u1 u2 = fromMaybe False (apply2 proxy comparableTo u1 u2 <|> True <$ subalgorithmFor pure pure u1 <|> True <$ subalgorithmFor pure pure u2) diff --git a/src/Data/Syntax.hs b/src/Data/Syntax.hs index ab5300f9f..1184ceeda 100644 --- a/src/Data/Syntax.hs +++ b/src/Data/Syntax.hs @@ -170,8 +170,6 @@ data Context a = Context { contextTerms :: NonEmpty a, contextSubject :: a } instance Diffable Context where subalgorithmFor blur focus (Context n s) = Context <$> traverse blur n <*> focus s - subequivalenceTo focus = focus . contextSubject - equivalentBySubterm = Just . contextSubject instance Eq1 Context where liftEq = genericLiftEq From 048f66dec85a363f90b7d15e6525dea1bc9a10c3 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:49:06 -0400 Subject: [PATCH 38/44] :memo: equivalentBySubterm. --- src/Algorithm.hs | 5 +++++ 1 file changed, 5 insertions(+) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index 96131e3c8..dd4ee326a 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -163,6 +163,11 @@ class Diffable f where -> g (f b) -- ^ The resulting algorithm (or other 'Alternative' context), producing the traversed syntax. subalgorithmFor _ _ _ = empty + -- | Syntax having a human-provided identifier, such as function/method definitions, can use equivalence of identifiers as a proxy for their overall equivalence, improving the quality & efficiency of the diff as a whole. + -- + -- This can also be used for annotation nodes to ensure that their subjects’ equivalence is weighed appropriately. + -- + -- Other syntax should use the default definition, and thus have equivalence computed piece-wise. equivalentBySubterm :: f a -> Maybe a equivalentBySubterm _ = Nothing From e7306fa43e082e4547496fdc8791c8d5bc461bc0 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:51:56 -0400 Subject: [PATCH 39/44] :memo: comparableTo. --- src/Algorithm.hs | 3 +++ 1 file changed, 3 insertions(+) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index dd4ee326a..672b9bc87 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -171,6 +171,9 @@ class Diffable f where equivalentBySubterm :: f a -> Maybe a equivalentBySubterm _ = Nothing + -- | A relation on syntax values indicating their In general this should be true iff both values have the same constructor (this is the relation computed by the default, generic definition). + -- + -- For syntax with constant fields which serve as a classifier, this method can be overloaded to consider equality on that classifier in addition to/instead of the constructors themselves, and thus limit the comparisons accordingly. comparableTo :: f term1 -> f term2 -> Bool default comparableTo :: (Generic1 f, GDiffable (Rep1 f)) => f term1 -> f term2 -> Bool comparableTo = genericComparableTo From 8f09c1c1bcfae89882e2f26698b5c34648b10638 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:55:12 -0400 Subject: [PATCH 40/44] :memo: comparableTerms. --- src/Algorithm.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index 672b9bc87..0b3fa4358 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -106,6 +106,7 @@ algorithmForTerms t1@(Term (In ann1 f1)) t2@(Term (In ann2 f2)) <|> insertF . In ann2 <$> subalgorithmFor byInserting ( mergeFor t1) f2 where mergeFor (Term (In ann1 f1)) (Term (In ann2 f2)) = merge (ann1, ann2) <$> algorithmFor f1 f2 +-- | An O(1) relation on terms indicating their non-recursive comparability (i.e. are they of the same “kind” in a way that warrants comparison), defined in terms of the comparability of their respective syntax. comparableTerms :: Diffable syntax => TermF syntax ann1 term1 -> TermF syntax ann2 term2 From 2c7e9010430e5891ad849816c2bed6da81a34d37 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 15:58:52 -0400 Subject: [PATCH 41/44] :memo: equivalentTerms. --- src/Algorithm.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index 0b3fa4358..9d2c2adfd 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -113,6 +113,7 @@ comparableTerms :: Diffable syntax -> Bool comparableTerms (In _ syntax1) (In _ syntax2) = comparableTo syntax1 syntax2 +-- | An O(n) relation on terms indicating their recursive equivalence (i.e. are they _notionally_ “the same,” as distinct from literal equality), defined at each node in terms of the equivalence of their respective syntax, computed first on a nominated subterm (if any), falling back to substructural equivalence (e.g. equivalence of one term against the subject of the other, annotating term), and finally to equality. equivalentTerms :: (Diffable syntax, Eq1 syntax) => Term syntax ann1 -> Term syntax ann2 From b4f0cee1382d50b40c909fa612bfe9460ec3988e Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 16:00:35 -0400 Subject: [PATCH 42/44] :memo: Equivalence. --- src/Algorithm.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index 9d2c2adfd..bc07e6178 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -124,6 +124,7 @@ equivalentTerms term1@(Term (In _ syntax1)) term2@(Term (In _ syntax2)) || runEquivalence (subalgorithmFor pure (Equivalence . equivalentTerms term1) syntax2) || liftEq equivalentTerms syntax1 syntax2 +-- | A constant 'Alternative' functor used by 'equivalentTerms' to compute the substructural equivalence of syntax. newtype Equivalence a = Equivalence { runEquivalence :: Bool } deriving (Eq, Functor) From 0c1f0b0e46b285661c2b60fdcd5fbb4ebf306473 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 16:02:23 -0400 Subject: [PATCH 43/44] Correct the docs for the Diffable instance for Unions. --- src/Algorithm.hs | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index bc07e6178..cc672a273 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -191,10 +191,7 @@ genericComparableTo :: (Generic1 f, GDiffable (Rep1 f)) => f term1 -> f term2 -> genericComparableTo a1 a2 = gcomparableTo (from1 a1) (from1 a2) --- | Diff a Union of Syntax terms. Left is the "rest" of the Syntax terms in the Union, --- Right is the "head" of the Union. 'weaken' relaxes the Union to allow the possible --- diff terms from the "rest" of the Union, and 'inj' adds the diff terms into the Union. --- NB: If Left or Right Syntax terms in our Union don't match, we fail fast by returning Nothing. +-- | 'Diffable' for 'Union's of syntax functors is defined in general by straightforward lifting of each method into the functors in the 'Union'. instance Apply Diffable fs => Diffable (Union fs) where algorithmFor u1 u2 = fromMaybe empty (apply2' (Proxy :: Proxy Diffable) (\ inj f1 f2 -> inj <$> algorithmFor f1 f2) u1 u2) From d9a0a87531bfc3f039d947d069b383184f2000fb Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Tue, 3 Oct 2017 16:04:22 -0400 Subject: [PATCH 44/44] :memo: comparableTo on Union. --- src/Algorithm.hs | 1 + 1 file changed, 1 insertion(+) diff --git a/src/Algorithm.hs b/src/Algorithm.hs index cc672a273..cf4e9fede 100644 --- a/src/Algorithm.hs +++ b/src/Algorithm.hs @@ -199,6 +199,7 @@ instance Apply Diffable fs => Diffable (Union fs) where equivalentBySubterm = apply (Proxy :: Proxy Diffable) equivalentBySubterm + -- | Comparability on 'Union's is defined first by comparability of their contained functors (when they’re the same), falling back to using 'subalgorithmFor' to opt substructurally-diffable syntax into comparisons (e.g. to allow annotating nodes to be compared against the kind of nodes they annotate). comparableTo u1 u2 = fromMaybe False (apply2 proxy comparableTo u1 u2 <|> True <$ subalgorithmFor pure pure u1 <|> True <$ subalgorithmFor pure pure u2) where proxy = Proxy :: Proxy Diffable