mirror of
https://github.com/github/semantic.git
synced 2024-11-29 11:02:26 +03:00
Merge pull request #1018 from github/sexpression-text-based-testing
S-Expression based testing
This commit is contained in:
commit
4099ec1a81
@ -150,8 +150,10 @@ test-suite test
|
||||
, Source.Spec
|
||||
, TermSpec
|
||||
, TOCSpec
|
||||
, IntegrationSpec
|
||||
, Test.Hspec.LeanCheck
|
||||
build-depends: array
|
||||
build-depends: aeson
|
||||
, array
|
||||
, base
|
||||
, bifunctors
|
||||
, deepseq
|
||||
|
@ -64,7 +64,7 @@ textDiff :: (ToJSON (Record fields), DefaultFields fields) => Parser (Syntax Tex
|
||||
textDiff parser arguments = diffFiles parser $ case format arguments of
|
||||
Split -> split
|
||||
Patch -> patch
|
||||
SExpression -> sExpression
|
||||
SExpression -> sExpression TreeOnly
|
||||
JSON -> json
|
||||
Summary -> summary
|
||||
TOC -> toc
|
||||
|
@ -22,6 +22,9 @@ termAssignment _ category children
|
||||
-- def foo(name:); end
|
||||
-- Let it fall through to generate an Indexed syntax.
|
||||
(OptionalParameter, [ k, v ] ) -> Just $ S.Pair k v
|
||||
(AnonymousFunction, first : rest)
|
||||
| null rest -> Just $ S.AnonymousFunction [] [first]
|
||||
| otherwise -> Just $ S.AnonymousFunction (toList (unwrap first)) rest
|
||||
(ArrayLiteral, _ ) -> Just $ S.Array Nothing children
|
||||
(Assignment, [ identifier, value ]) -> Just $ S.Assignment identifier value
|
||||
(Begin, _ ) -> Just $ case partition (\x -> Info.category (extract x) == Rescue) children of
|
||||
@ -50,9 +53,6 @@ termAssignment _ category children
|
||||
-> Just $ S.MethodCall target method (toList . unwrap =<< args)
|
||||
| otherwise
|
||||
-> Just $ S.FunctionCall fn (toList . unwrap =<< args)
|
||||
(Other "lambda", first : rest)
|
||||
| null rest -> Just $ S.AnonymousFunction [] [first]
|
||||
| otherwise -> Just $ S.AnonymousFunction (toList (unwrap first)) rest
|
||||
(Object, _ ) -> Just . S.Object Nothing $ foldMap toTuple children
|
||||
(Modifier If, [ lhs, condition ]) -> Just $ S.If condition [lhs]
|
||||
(Modifier Unless, [lhs, rhs]) -> Just $ S.If (withRecord (setCategory (extract rhs) Negate) (S.Negate rhs)) [lhs]
|
||||
@ -97,8 +97,8 @@ termAssignment _ category children
|
||||
|
||||
categoryForRubyName :: Text -> Category
|
||||
categoryForRubyName = \case
|
||||
"argument_list" -> Args
|
||||
"argument_list_with_parens" -> Args
|
||||
"argument_list" -> Args
|
||||
"argument_pair" -> ArgumentPair
|
||||
"array" -> ArrayLiteral
|
||||
"assignment" -> Assignment
|
||||
@ -135,6 +135,8 @@ categoryForRubyName = \case
|
||||
"interpolation" -> Interpolation
|
||||
"keyword_parameter" -> KeywordParameter
|
||||
"lambda_parameters" -> Params
|
||||
"lambda" -> AnonymousFunction
|
||||
"left_assignment_list" -> Args
|
||||
"method_call" -> MethodCall
|
||||
"method_parameters" -> Params
|
||||
"method" -> Method
|
||||
@ -143,11 +145,13 @@ categoryForRubyName = \case
|
||||
"operator_assignment" -> OperatorAssignment
|
||||
"optional_parameter" -> OptionalParameter
|
||||
"pair" -> Pair
|
||||
"pattern" -> Args
|
||||
"program" -> Program
|
||||
"range" -> RangeExpression
|
||||
"regex" -> Regex
|
||||
"rescue_modifier" -> Modifier Rescue
|
||||
"rescue" -> Rescue
|
||||
"rest_assignment" -> SplatParameter
|
||||
"return" -> Return
|
||||
"scope_resolution" -> ScopeOperator
|
||||
"self" -> Identifier
|
||||
|
@ -38,11 +38,11 @@ data ParseJSON = ParseJSON
|
||||
|
||||
run :: Arguments -> IO ()
|
||||
run Arguments{..} = do
|
||||
sources <- sequence $ readAndTranscodeFile <$> filePaths
|
||||
sources <- traverse readAndTranscodeFile filePaths
|
||||
terms <- zipWithM (\parser sourceBlob -> parser sourceBlob) parsers (sourceBlobs sources)
|
||||
|
||||
writeToOutput output $ case format of
|
||||
SExpression -> [foldr (\t acc -> printTerm t 0 <> acc) "" terms]
|
||||
SExpression -> [foldr (\t acc -> printTerm t 0 TreeOnly <> acc) "" terms]
|
||||
_ -> toS . encodePretty . cata algebra <$> terms
|
||||
|
||||
where
|
||||
|
@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE RankNTypes, ScopedTypeVariables #-}
|
||||
module Renderer.SExpression (sExpression, printTerm) where
|
||||
module Renderer.SExpression (sExpression, printTerm, SExpressionFormat(..)) where
|
||||
|
||||
import Data.Bifunctor.Join
|
||||
import Data.Foldable
|
||||
@ -15,33 +15,36 @@ import Info
|
||||
import Syntax
|
||||
import Term
|
||||
|
||||
sExpression :: (HasField fields Category, HasField fields SourceSpan) => Renderer (Record fields)
|
||||
sExpression _ diff = SExpressionOutput $ printDiff diff 0
|
||||
data SExpressionFormat = TreeOnly | TreeAndRanges
|
||||
|
||||
printDiff :: (HasField fields Category, HasField fields SourceSpan) => Diff (Syntax Text) (Record fields) -> Int -> Text
|
||||
printDiff diff level = case runFree diff of
|
||||
sExpression :: (HasField fields Category, HasField fields SourceSpan) => SExpressionFormat -> Renderer (Record fields)
|
||||
sExpression format _ diff = SExpressionOutput $ printDiff diff 0 format
|
||||
|
||||
printDiff :: (HasField fields Category, HasField fields SourceSpan) => Diff (Syntax Text) (Record fields) -> Int -> SExpressionFormat -> Text
|
||||
printDiff diff level format = case runFree diff of
|
||||
(Pure patch) -> case patch of
|
||||
Insert term -> pad (level - 1) <> "{+" <> printTerm term level <> "+}"
|
||||
Delete term -> pad (level - 1) <> "{-" <> printTerm term level <> "-}"
|
||||
Replace a b -> pad (level - 1) <> "{" <> printTerm a level <> "->" <> printTerm b level <> "}"
|
||||
(Free (Join (_, annotation) :< syntax)) -> pad' level <> "(" <> showAnnotation annotation <> foldr (\d acc -> printDiff d (level + 1) <> acc) "" syntax <> ")"
|
||||
Insert term -> pad (level - 1) <> "{+" <> printTerm term level format <> "+}"
|
||||
Delete term -> pad (level - 1) <> "{-" <> printTerm term level format <> "-}"
|
||||
Replace a b -> pad (level - 1) <> "{ " <> printTerm a level format <> pad (level - 1) <> "->" <> printTerm b level format <> " }"
|
||||
(Free (Join (_, annotation) :< syntax)) -> pad' level <> "(" <> showAnnotation annotation format <> foldr (\d acc -> printDiff d (level + 1) format <> acc) "" syntax <> ")"
|
||||
where
|
||||
pad' n = if n < 1 then "" else pad n
|
||||
pad n | n < 0 = ""
|
||||
| n < 1 = "\n"
|
||||
| otherwise = "\n" <> mconcat (replicate n " ")
|
||||
|
||||
printTerm :: (HasField fields Category, HasField fields SourceSpan) => Term (Syntax t) (Record fields) -> Int -> Text
|
||||
printTerm term level = go term level 0
|
||||
printTerm :: (HasField fields Category, HasField fields SourceSpan) => Term (Syntax t) (Record fields) -> Int -> SExpressionFormat -> Text
|
||||
printTerm term level format = go term level 0
|
||||
where
|
||||
pad p n | n < 1 = ""
|
||||
| otherwise = "\n" <> mconcat (replicate (p + n) " ")
|
||||
go term parentLevel level = case runCofree term of
|
||||
(annotation :< Leaf _) -> pad parentLevel level <> "(" <> showAnnotation annotation <> ")"
|
||||
(annotation :< syntax) -> pad parentLevel level <> "(" <> showAnnotation annotation <> foldr (\t acc -> go t parentLevel (level + 1) <> acc) "" syntax <> ")"
|
||||
(annotation :< Leaf _) -> pad parentLevel level <> "(" <> showAnnotation annotation format <> ")"
|
||||
(annotation :< syntax) -> pad parentLevel level <> "(" <> showAnnotation annotation format <> foldr (\t acc -> go t parentLevel (level + 1) <> acc) "" syntax <> ")"
|
||||
|
||||
showAnnotation :: (HasField fields Category, HasField fields SourceSpan) => Record fields -> Text
|
||||
showAnnotation annotation = categoryName annotation <> " " <> showSourceSpan annotation
|
||||
showAnnotation :: (HasField fields Category, HasField fields SourceSpan) => Record fields -> SExpressionFormat -> Text
|
||||
showAnnotation annotation TreeOnly = categoryName annotation
|
||||
showAnnotation annotation TreeAndRanges = categoryName annotation <> " " <> showSourceSpan annotation
|
||||
where
|
||||
showSourceSpan a = start a <> " - " <> end a
|
||||
start = showPoint . spanStart . getField
|
||||
|
@ -184,5 +184,5 @@ toTermName parentOffset parentSource term = case unwrap term of
|
||||
-- The user-facing category name
|
||||
toCategoryName :: Category -> Text
|
||||
toCategoryName = \case
|
||||
C.SingletonMethod -> "method"
|
||||
C.SingletonMethod -> "Method"
|
||||
c -> show c
|
||||
|
@ -86,7 +86,7 @@ diffCommits args@Arguments{..} = do
|
||||
-- | Compare two paths on the filesystem (compariable to git diff --no-index).
|
||||
diffPaths :: Arguments -> Both FilePath -> IO ()
|
||||
diffPaths args@Arguments{..} paths = do
|
||||
sources <- sequence $ readAndTranscodeFile <$> paths
|
||||
sources <- traverse readAndTranscodeFile paths
|
||||
let sourceBlobs = Source.SourceBlob <$> sources <*> pure mempty <*> paths <*> pure (Just Source.defaultPlainBlob)
|
||||
D.printDiff (parserForFilepath (fst paths)) (diffArgs args) sourceBlobs
|
||||
where
|
||||
|
122
test/IntegrationSpec.hs
Normal file
122
test/IntegrationSpec.hs
Normal file
@ -0,0 +1,122 @@
|
||||
{-# LANGUAGE DataKinds, GeneralizedNewtypeDeriving #-}
|
||||
module IntegrationSpec where
|
||||
|
||||
import Category as C
|
||||
import Data.Functor.Both
|
||||
import Data.Record
|
||||
import qualified Data.Text as T
|
||||
import GHC.Show (Show(..))
|
||||
import Data.List (union)
|
||||
import Diffing
|
||||
import Info
|
||||
import Parse
|
||||
import Prologue hiding (fst, snd)
|
||||
import Renderer
|
||||
import Renderer.SExpression as Renderer
|
||||
import Source
|
||||
import System.FilePath
|
||||
import System.FilePath.Glob
|
||||
import Test.Hspec (Spec, describe, it, SpecWith, runIO, parallel)
|
||||
import Test.Hspec.Expectations.Pretty
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
it "lists example fixtures" $ do
|
||||
examples "test/fixtures/ruby/" `shouldNotReturn` []
|
||||
|
||||
describe "ruby" $ runTestsIn "test/fixtures/ruby/"
|
||||
|
||||
where
|
||||
runTestsIn :: FilePath -> SpecWith ()
|
||||
runTestsIn directory = do
|
||||
examples <- runIO $ examples directory
|
||||
traverse_ runTest examples
|
||||
runTest ParseExample{..} = it ("parses " <> file) $ testParse file parseOutput
|
||||
runTest DiffExample{..} = it ("diffs " <> diffOutput) $ testDiff (Renderer.sExpression TreeOnly) (both fileA fileB) diffOutput
|
||||
|
||||
data Example = DiffExample { fileA :: FilePath, fileB :: FilePath, diffOutput :: FilePath }
|
||||
| ParseExample { file :: FilePath, parseOutput :: FilePath }
|
||||
deriving (Eq, Show)
|
||||
|
||||
-- | Return all the examples from the given directory. Examples are expected to
|
||||
-- | have the form:
|
||||
-- |
|
||||
-- | example-name.A.rb - The left hand side of the diff.
|
||||
-- | example-name.B.rb - The right hand side of the diff.
|
||||
-- |
|
||||
-- | example-name.diffA-B.txt - The expected sexpression diff output for A -> B.
|
||||
-- | example-name.diffB-A.txt - The expected sexpression diff output for B -> A.
|
||||
-- |
|
||||
-- | example-name.parseA.txt - The expected sexpression parse tree for example-name.A.rb
|
||||
-- | example-name.parseB.txt - The expected sexpression parse tree for example-name.B.rb
|
||||
examples :: FilePath -> IO [Example]
|
||||
examples directory = do
|
||||
as <- globFor "*.A.*"
|
||||
bs <- globFor "*.B.*"
|
||||
sExpAs <- globFor "*.parseA.txt"
|
||||
sExpBs <- globFor "*.parseB.txt"
|
||||
sExpDiffsAB <- globFor "*.diffA-B.txt"
|
||||
sExpDiffsBA <- globFor "*.diffB-A.txt"
|
||||
|
||||
let exampleDiff out name = DiffExample (lookupNormalized name as) (lookupNormalized name bs) out
|
||||
let exampleDiff' out name = DiffExample (lookupNormalized name bs) (lookupNormalized name as) out
|
||||
let exampleParse files out name = ParseExample (lookupNormalized name files) out
|
||||
|
||||
let keys = (normalizeName <$> as) `union` (normalizeName <$> bs)
|
||||
pure $ getExamples exampleDiff sExpDiffsAB keys
|
||||
<> getExamples exampleDiff' sExpDiffsBA keys
|
||||
<> getExamples (exampleParse as) sExpAs keys
|
||||
<> getExamples (exampleParse bs) sExpBs keys
|
||||
where
|
||||
-- Only returns examples if they exist
|
||||
getExamples f list = foldr (go f list) []
|
||||
where go f list name acc = case lookupNormalized' name list of
|
||||
Just out -> f out name : acc
|
||||
Nothing -> acc
|
||||
|
||||
lookupNormalized :: FilePath -> [FilePath] -> FilePath
|
||||
lookupNormalized name xs = fromMaybe
|
||||
(panic ("cannot find " <> T.pack name <> " make sure .A, .B and exist." :: Text))
|
||||
(lookupNormalized' name xs)
|
||||
|
||||
lookupNormalized' :: FilePath -> [FilePath] -> Maybe FilePath
|
||||
lookupNormalized' name = find ((== name) . normalizeName)
|
||||
|
||||
globFor :: FilePath -> IO [FilePath]
|
||||
globFor p = globDir1 (compile p) directory
|
||||
|
||||
-- | Given a test name like "foo.A.js", return "foo".
|
||||
normalizeName :: FilePath -> FilePath
|
||||
normalizeName path = dropExtension $ dropExtension path
|
||||
|
||||
testParse :: FilePath -> FilePath -> Expectation
|
||||
testParse path expectedOutput = do
|
||||
source <- readAndTranscodeFile path
|
||||
let blob = sourceBlob source path
|
||||
term <- parserWithSource path blob
|
||||
let actual = (Verbatim . stripWhitespace) $ printTerm term 0 TreeOnly
|
||||
expected <- (Verbatim . stripWhitespace) <$> readFile expectedOutput
|
||||
actual `shouldBe` expected
|
||||
|
||||
testDiff :: Renderer (Record '[Range, Category, SourceSpan]) -> Both FilePath -> FilePath -> Expectation
|
||||
testDiff renderer paths diff = do
|
||||
sources <- traverse readAndTranscodeFile paths
|
||||
diff' <- diffFiles parser renderer (sourceBlobs sources)
|
||||
let actual = (Verbatim . stripWhitespace. concatOutputs . pure) diff'
|
||||
expected <- (Verbatim . stripWhitespace) <$> readFile diff
|
||||
actual `shouldBe` expected
|
||||
where
|
||||
parser = parserForFilepath (fst paths)
|
||||
sourceBlobs sources = Source.SourceBlob <$> sources <*> pure mempty <*> paths <*> pure (Just Source.defaultPlainBlob)
|
||||
|
||||
stripWhitespace :: Text -> Text
|
||||
stripWhitespace = T.foldl' go T.empty
|
||||
where go acc x | x `elem` [' ', '\t', '\n'] = acc
|
||||
| otherwise = T.snoc acc x
|
||||
|
||||
-- | A wrapper around `Text` with a more readable `Show` instance.
|
||||
newtype Verbatim = Verbatim Text
|
||||
deriving (Eq, NFData)
|
||||
|
||||
instance Show Verbatim where
|
||||
showsPrec _ (Verbatim text) = ('\n':) . (T.unpack text ++)
|
@ -13,6 +13,7 @@ import qualified RangeSpec
|
||||
import qualified Source.Spec
|
||||
import qualified TermSpec
|
||||
import qualified TOCSpec
|
||||
import qualified IntegrationSpec
|
||||
import Test.Hspec
|
||||
|
||||
main :: IO ()
|
||||
@ -29,3 +30,4 @@ main = hspec . parallel $ do
|
||||
describe "Source" Source.Spec.spec
|
||||
describe "Term" TermSpec.spec
|
||||
describe "TOC" TOCSpec.spec
|
||||
describe "Integration" IntegrationSpec.spec
|
||||
|
@ -1,6 +1,7 @@
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
module TOCSpec where
|
||||
|
||||
import Data.Aeson
|
||||
import Category as C
|
||||
import Data.Functor.Both
|
||||
import Data.Functor.Listable
|
||||
@ -14,6 +15,7 @@ import Interpreter
|
||||
import Parse
|
||||
import Patch
|
||||
import Prologue hiding (fst, snd)
|
||||
import Renderer
|
||||
import Renderer.TOC
|
||||
import Source
|
||||
import Syntax as S
|
||||
@ -25,7 +27,7 @@ import Test.LeanCheck
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
describe "tocSummaries" $ do
|
||||
describe "diffTOC" $ do
|
||||
it "blank if there are no methods" $
|
||||
diffTOC blankDiffBlobs blankDiff `shouldBe` [ ]
|
||||
|
||||
@ -96,6 +98,28 @@ spec = parallel $ do
|
||||
\a -> let term = defaultFeatureVectorDecorator (Info.category . headF) (unListableF a :: Term') in
|
||||
diffTOC blankDiffBlobs (diffTerms term term) `shouldBe` []
|
||||
|
||||
describe "JSONSummary" $ do
|
||||
it "encodes InSummarizable to JSON" $ do
|
||||
let summary = JSONSummary $ InSummarizable C.Method "foo" (sourceSpanBetween (1, 1) (4, 4))
|
||||
encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[4,4]},\"category\":\"Method\",\"term\":\"foo\",\"changeType\":\"modified\"}"
|
||||
|
||||
it "encodes Summarizable to JSON" $ do
|
||||
let summary = JSONSummary $ Summarizable C.SingletonMethod "self.foo" (sourceSpanBetween (1, 1) (2, 4)) "added"
|
||||
encode summary `shouldBe` "{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"}"
|
||||
|
||||
describe "diffFiles" $ do
|
||||
it "encodes to final JSON" $ do
|
||||
sourceBlobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.B.rb")
|
||||
let parser = parserForFilepath (path (fst sourceBlobs))
|
||||
output <- diffFiles parser toc sourceBlobs
|
||||
concatOutputs (pure output) `shouldBe` ("{\"changes\":{\"ruby/methods.A.rb -> ruby/methods.B.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"self.foo\",\"changeType\":\"added\"},{\"span\":{\"start\":[4,1],\"end\":[6,4]},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"modified\"},{\"span\":{\"start\":[4,1],\"end\":[5,4]},\"category\":\"Method\",\"term\":\"baz\",\"changeType\":\"removed\"}]},\"errors\":{}}" :: Text)
|
||||
|
||||
it "encodes to final JSON if there are parse errors" $ do
|
||||
sourceBlobs <- blobsForPaths (both "ruby/methods.A.rb" "ruby/methods.X.rb")
|
||||
let parser = parserForFilepath (path (fst sourceBlobs))
|
||||
output <- diffFiles parser toc sourceBlobs
|
||||
concatOutputs (pure output) `shouldBe` ("{\"changes\":{},\"errors\":{\"ruby/methods.A.rb -> ruby/methods.X.rb\":[{\"span\":{\"start\":[1,1],\"end\":[3,1]},\"error\":\"def bar\\nen\\n\"}]}}" :: Text)
|
||||
|
||||
type Diff' = SyntaxDiff String '[Range, Category, SourceSpan]
|
||||
type Term' = SyntaxTerm String '[Range, Category, SourceSpan]
|
||||
|
||||
@ -171,7 +195,7 @@ testDiff sourceBlobs = do
|
||||
|
||||
blobsForPaths :: Both FilePath -> IO (Both SourceBlob)
|
||||
blobsForPaths paths = do
|
||||
sources <- sequence $ readAndTranscodeFile . ("test/corpus/toc/" <>) <$> paths
|
||||
sources <- traverse (readAndTranscodeFile . ("test/fixtures/toc/" <>)) paths
|
||||
pure $ SourceBlob <$> sources <*> pure mempty <*> paths <*> pure (Just Source.defaultPlainBlob)
|
||||
|
||||
sourceSpanBetween :: (Int, Int) -> (Int, Int) -> SourceSpan
|
||||
|
File diff suppressed because it is too large
Load Diff
@ -1,383 +0,0 @@
|
||||
[{
|
||||
"testCaseDescription": "ruby-multiple-assignments-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"multiple-assignments.rb": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
23
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'identifier' assignment"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"multiple-assignments.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
|
||||
"index e69de29..348cf74 100644",
|
||||
"--- a/multiple-assignments.rb",
|
||||
"+++ b/multiple-assignments.rb",
|
||||
"@@ -0,0 +1 @@",
|
||||
"+x, y, z = [10, 20, 30]"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "a966f9b2783f127617cc42cbed16e6ec570b75ad..850232b2802cc99838c38bb6884e78c8675d900d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-multiple-assignments-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"multiple-assignments.rb": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
21
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'identifier' assignment"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
23
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'identifier' assignment"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"multiple-assignments.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
|
||||
"index 348cf74..242315a 100644",
|
||||
"--- a/multiple-assignments.rb",
|
||||
"+++ b/multiple-assignments.rb",
|
||||
"@@ -1 +1,3 @@",
|
||||
"+x, *y = [10, 20, 30]",
|
||||
"+x, y, z = [10, 20, 30]",
|
||||
" x, y, z = [10, 20, 30]"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "850232b2802cc99838c38bb6884e78c8675d900d..2f0556416a97d736bf681a377c0a17ad20fe03a1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-multiple-assignments-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"multiple-assignments.rb": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
4
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
5
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'y' identifier in an assignment to identifier"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
7
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
8
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'z' identifier in an assignment to identifier"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
5
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
6
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'y' identifier in an assignment to identifier"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"multiple-assignments.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
|
||||
"index 242315a..274faf2 100644",
|
||||
"--- a/multiple-assignments.rb",
|
||||
"+++ b/multiple-assignments.rb",
|
||||
"@@ -1,3 +1,3 @@",
|
||||
"-x, *y = [10, 20, 30]",
|
||||
"+x, y, z = [10, 20, 30]",
|
||||
" x, y, z = [10, 20, 30]",
|
||||
" x, y, z = [10, 20, 30]"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "2f0556416a97d736bf681a377c0a17ad20fe03a1..4cf32e342e860dec68b496ba04ed8fca1d04a08f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-multiple-assignments-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"multiple-assignments.rb": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
5
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
6
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'y' identifier in an assignment to identifier"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
4
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
5
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'y' identifier in an assignment to identifier"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
7
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
8
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'z' identifier in an assignment to identifier"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"multiple-assignments.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
|
||||
"index 274faf2..242315a 100644",
|
||||
"--- a/multiple-assignments.rb",
|
||||
"+++ b/multiple-assignments.rb",
|
||||
"@@ -1,3 +1,3 @@",
|
||||
"-x, y, z = [10, 20, 30]",
|
||||
"+x, *y = [10, 20, 30]",
|
||||
" x, y, z = [10, 20, 30]",
|
||||
" x, y, z = [10, 20, 30]"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "4cf32e342e860dec68b496ba04ed8fca1d04a08f..3d3c3f2b1d6ed385e8c69eb0de5f5db36abd1f93"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-multiple-assignments-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"multiple-assignments.rb": [
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
21
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'identifier' assignment"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
23
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'identifier' assignment"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
21
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the 'identifier' assignment"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"multiple-assignments.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
|
||||
"index 242315a..7ba9487 100644",
|
||||
"--- a/multiple-assignments.rb",
|
||||
"+++ b/multiple-assignments.rb",
|
||||
"@@ -1,3 +1,2 @@",
|
||||
"-x, *y = [10, 20, 30]",
|
||||
"-x, y, z = [10, 20, 30]",
|
||||
" x, y, z = [10, 20, 30]",
|
||||
"+x, *y = [10, 20, 30]"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "3d3c3f2b1d6ed385e8c69eb0de5f5db36abd1f93..b724179373843cb5f953b1eb84fe3cf1f787cae1"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-multiple-assignments-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"multiple-assignments.rb": [
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
23
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'identifier' assignment"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"multiple-assignments.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
|
||||
"index 7ba9487..32cf6a2 100644",
|
||||
"--- a/multiple-assignments.rb",
|
||||
"+++ b/multiple-assignments.rb",
|
||||
"@@ -1,2 +1 @@",
|
||||
"-x, y, z = [10, 20, 30]",
|
||||
" x, *y = [10, 20, 30]"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "b724179373843cb5f953b1eb84fe3cf1f787cae1..9470930d6fca5e33ec313863fbe1c443d7388dbe"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-multiple-assignments-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"multiple-assignments.rb": [
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
21
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the 'identifier' assignment"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"multiple-assignments.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/multiple-assignments.rb b/multiple-assignments.rb",
|
||||
"index 32cf6a2..e69de29 100644",
|
||||
"--- a/multiple-assignments.rb",
|
||||
"+++ b/multiple-assignments.rb",
|
||||
"@@ -1 +0,0 @@",
|
||||
"-x, *y = [10, 20, 30]"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "9470930d6fca5e33ec313863fbe1c443d7388dbe..d4996909ad6798a66c5242d7171125ce6dbe1a50"
|
||||
}]
|
@ -1,383 +0,0 @@
|
||||
[{
|
||||
"testCaseDescription": "ruby-regex-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.rb": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
19
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the '/^(foo|bar[^_])$/i' regex"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/regex.rb b/regex.rb",
|
||||
"index e69de29..02dce9d 100644",
|
||||
"--- a/regex.rb",
|
||||
"+++ b/regex.rb",
|
||||
"@@ -0,0 +1 @@",
|
||||
"+/^(foo|bar[^_])$/i"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "956b136e24f76c977fefd27d5368ecd527f721ec..49cb17b4244d627bd084dab1c7248c48a3cdb7cc"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-regex-replacement-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.rb": [
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
6
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the '%r/a/' regex"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
10
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the '%r<a<b>c>' regex"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
3,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
3,
|
||||
19
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the '/^(foo|bar[^_])$/i' regex"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/regex.rb b/regex.rb",
|
||||
"index 02dce9d..c801d61 100644",
|
||||
"--- a/regex.rb",
|
||||
"+++ b/regex.rb",
|
||||
"@@ -1 +1,4 @@",
|
||||
"+%r/a/",
|
||||
"+%r<a<b>c>",
|
||||
"+/^(foo|bar[^_])$/i",
|
||||
" /^(foo|bar[^_])$/i"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "49cb17b4244d627bd084dab1c7248c48a3cdb7cc..a73a7605d28b1fe2b09ce87d8db7426ea6295610"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-regex-delete-insert-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.rb": [
|
||||
{
|
||||
"span": {
|
||||
"replace": [
|
||||
{
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
6
|
||||
]
|
||||
},
|
||||
{
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
19
|
||||
]
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the '%r/a/' regex with the '/^(foo|bar[^_])$/i' regex"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
10
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the '%r<a<b>c>' regex"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/regex.rb b/regex.rb",
|
||||
"index c801d61..42d4984 100644",
|
||||
"--- a/regex.rb",
|
||||
"+++ b/regex.rb",
|
||||
"@@ -1,4 +1,3 @@",
|
||||
"-%r/a/",
|
||||
"-%r<a<b>c>",
|
||||
"+/^(foo|bar[^_])$/i",
|
||||
" /^(foo|bar[^_])$/i",
|
||||
" /^(foo|bar[^_])$/i"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "a73a7605d28b1fe2b09ce87d8db7426ea6295610..edcc26845e0ed493216f7b8ce1235e7a37ace55d"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-regex-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.rb": [
|
||||
{
|
||||
"span": {
|
||||
"replace": [
|
||||
{
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
19
|
||||
]
|
||||
},
|
||||
{
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
6
|
||||
]
|
||||
}
|
||||
]
|
||||
},
|
||||
"summary": "Replaced the '/^(foo|bar[^_])$/i' regex with the '%r/a/' regex"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"insert": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
10
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Added the '%r<a<b>c>' regex"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/regex.rb b/regex.rb",
|
||||
"index 42d4984..c801d61 100644",
|
||||
"--- a/regex.rb",
|
||||
"+++ b/regex.rb",
|
||||
"@@ -1,3 +1,4 @@",
|
||||
"-/^(foo|bar[^_])$/i",
|
||||
"+%r/a/",
|
||||
"+%r<a<b>c>",
|
||||
" /^(foo|bar[^_])$/i",
|
||||
" /^(foo|bar[^_])$/i"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "edcc26845e0ed493216f7b8ce1235e7a37ace55d..46655f4fd04784ed0fd995951c5f83018cc02d97"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-regex-delete-replacement-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.rb": [
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
4,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
4,
|
||||
19
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the '/^(foo|bar[^_])$/i' regex"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/regex.rb b/regex.rb",
|
||||
"index c801d61..48e43a9 100644",
|
||||
"--- a/regex.rb",
|
||||
"+++ b/regex.rb",
|
||||
"@@ -1,4 +1,3 @@",
|
||||
"+/^(foo|bar[^_])$/i",
|
||||
" %r/a/",
|
||||
" %r<a<b>c>",
|
||||
"-/^(foo|bar[^_])$/i",
|
||||
"-/^(foo|bar[^_])$/i"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "46655f4fd04784ed0fd995951c5f83018cc02d97..dd7c07f9f3797a03b8a34fbd1efdbc98b01d2e76"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-regex-delete-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.rb": [
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
19
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the '/^(foo|bar[^_])$/i' regex"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/regex.rb b/regex.rb",
|
||||
"index 48e43a9..b23927a 100644",
|
||||
"--- a/regex.rb",
|
||||
"+++ b/regex.rb",
|
||||
"@@ -1,3 +1,2 @@",
|
||||
"-/^(foo|bar[^_])$/i",
|
||||
" %r/a/",
|
||||
" %r<a<b>c>"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "dd7c07f9f3797a03b8a34fbd1efdbc98b01d2e76..a9ee657f847f069d80fe4f52e9b1fb3bf991f26f"
|
||||
}
|
||||
,{
|
||||
"testCaseDescription": "ruby-regex-delete-rest-test",
|
||||
"expectedResult": {
|
||||
"changes": {
|
||||
"regex.rb": [
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
1,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
1,
|
||||
6
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the '%r/a/' regex"
|
||||
},
|
||||
{
|
||||
"span": {
|
||||
"delete": {
|
||||
"start": [
|
||||
2,
|
||||
1
|
||||
],
|
||||
"end": [
|
||||
2,
|
||||
10
|
||||
]
|
||||
}
|
||||
},
|
||||
"summary": "Deleted the '%r<a<b>c>' regex"
|
||||
}
|
||||
]
|
||||
},
|
||||
"errors": {}
|
||||
},
|
||||
"filePaths": [
|
||||
"regex.rb"
|
||||
],
|
||||
"patch": [
|
||||
"diff --git a/regex.rb b/regex.rb",
|
||||
"index b23927a..e69de29 100644",
|
||||
"--- a/regex.rb",
|
||||
"+++ b/regex.rb",
|
||||
"@@ -1,2 +0,0 @@",
|
||||
"-%r/a/",
|
||||
"-%r<a<b>c>"
|
||||
],
|
||||
"gitDir": "test/corpus/repos/ruby",
|
||||
"shas": "a9ee657f847f069d80fe4f52e9b1fb3bf991f26f..e8c4c9b4ba151237a0e88d5a650d34ee5a5a1b61"
|
||||
}]
|
1
test/fixtures/ruby/and-or.A.rb
vendored
Normal file
1
test/fixtures/ruby/and-or.A.rb
vendored
Normal file
@ -0,0 +1 @@
|
||||
foo and bar
|
2
test/fixtures/ruby/and-or.B.rb
vendored
Normal file
2
test/fixtures/ruby/and-or.B.rb
vendored
Normal file
@ -0,0 +1,2 @@
|
||||
foo or bar
|
||||
a or b and c
|
16
test/fixtures/ruby/and-or.diffA-B.txt
vendored
Normal file
16
test/fixtures/ruby/and-or.diffA-B.txt
vendored
Normal file
@ -0,0 +1,16 @@
|
||||
(Program
|
||||
{ (Binary
|
||||
(Identifier)
|
||||
(Other "and")
|
||||
(Identifier))
|
||||
->(Binary
|
||||
(Identifier)
|
||||
(Other "or")
|
||||
(Identifier)) }
|
||||
{+(Binary
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other "or")
|
||||
(Identifier))
|
||||
(Other "and")
|
||||
(Identifier))+})
|
16
test/fixtures/ruby/and-or.diffB-A.txt
vendored
Normal file
16
test/fixtures/ruby/and-or.diffB-A.txt
vendored
Normal file
@ -0,0 +1,16 @@
|
||||
(Program
|
||||
{ (Binary
|
||||
(Identifier)
|
||||
(Other "or")
|
||||
(Identifier))
|
||||
->(Binary
|
||||
(Identifier)
|
||||
(Other "and")
|
||||
(Identifier)) }
|
||||
{-(Binary
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other "or")
|
||||
(Identifier))
|
||||
(Other "and")
|
||||
(Identifier))-})
|
5
test/fixtures/ruby/and-or.parseA.txt
vendored
Normal file
5
test/fixtures/ruby/and-or.parseA.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Program
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other "and")
|
||||
(Identifier)))
|
12
test/fixtures/ruby/and-or.parseB.txt
vendored
Normal file
12
test/fixtures/ruby/and-or.parseB.txt
vendored
Normal file
@ -0,0 +1,12 @@
|
||||
(Program
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other "or")
|
||||
(Identifier))
|
||||
(Binary
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other "or")
|
||||
(Identifier))
|
||||
(Other "and")
|
||||
(Identifier)))
|
1
test/fixtures/ruby/array.A.rb
vendored
Normal file
1
test/fixtures/ruby/array.A.rb
vendored
Normal file
@ -0,0 +1 @@
|
||||
[ 1, 2, 3]
|
1
test/fixtures/ruby/array.B.rb
vendored
Normal file
1
test/fixtures/ruby/array.B.rb
vendored
Normal file
@ -0,0 +1 @@
|
||||
['a', 'b', 'c']
|
8
test/fixtures/ruby/array.diffA-B.txt
vendored
Normal file
8
test/fixtures/ruby/array.diffA-B.txt
vendored
Normal file
@ -0,0 +1,8 @@
|
||||
(Program
|
||||
(ArrayLiteral
|
||||
{+(StringLiteral)+}
|
||||
{+(StringLiteral)+}
|
||||
{+(StringLiteral)+}
|
||||
{-(IntegerLiteral)-}
|
||||
{-(IntegerLiteral)-}
|
||||
{-(IntegerLiteral)-}))
|
8
test/fixtures/ruby/array.diffB-A.txt
vendored
Normal file
8
test/fixtures/ruby/array.diffB-A.txt
vendored
Normal file
@ -0,0 +1,8 @@
|
||||
(Program
|
||||
(ArrayLiteral
|
||||
{+(IntegerLiteral)+}
|
||||
{+(IntegerLiteral)+}
|
||||
{+(IntegerLiteral)+}
|
||||
{-(StringLiteral)-}
|
||||
{-(StringLiteral)-}
|
||||
{-(StringLiteral)-}))
|
5
test/fixtures/ruby/array.parseA.txt
vendored
Normal file
5
test/fixtures/ruby/array.parseA.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Program
|
||||
(ArrayLiteral
|
||||
(IntegerLiteral)
|
||||
(IntegerLiteral)
|
||||
(IntegerLiteral)))
|
5
test/fixtures/ruby/array.parseB.txt
vendored
Normal file
5
test/fixtures/ruby/array.parseB.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Program
|
||||
(ArrayLiteral
|
||||
(StringLiteral)
|
||||
(StringLiteral)
|
||||
(StringLiteral)))
|
1
test/fixtures/ruby/assignment.A.rb
vendored
Normal file
1
test/fixtures/ruby/assignment.A.rb
vendored
Normal file
@ -0,0 +1 @@
|
||||
x = 0
|
1
test/fixtures/ruby/assignment.B.rb
vendored
Normal file
1
test/fixtures/ruby/assignment.B.rb
vendored
Normal file
@ -0,0 +1 @@
|
||||
x = 1
|
5
test/fixtures/ruby/assignment.diffA-B.txt
vendored
Normal file
5
test/fixtures/ruby/assignment.diffA-B.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Program
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (IntegerLiteral)
|
||||
->(IntegerLiteral) }))
|
5
test/fixtures/ruby/assignment.diffB-A.txt
vendored
Normal file
5
test/fixtures/ruby/assignment.diffB-A.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Program
|
||||
(Assignment
|
||||
(Identifier)
|
||||
{ (IntegerLiteral)
|
||||
->(IntegerLiteral) }))
|
4
test/fixtures/ruby/assignment.parseA.txt
vendored
Normal file
4
test/fixtures/ruby/assignment.parseA.txt
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
(Program
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(IntegerLiteral)))
|
4
test/fixtures/ruby/assignment.parseB.txt
vendored
Normal file
4
test/fixtures/ruby/assignment.parseB.txt
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
(Program
|
||||
(Assignment
|
||||
(Identifier)
|
||||
(IntegerLiteral)))
|
3
test/fixtures/ruby/begin-block.A.rb
vendored
Normal file
3
test/fixtures/ruby/begin-block.A.rb
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
BEGIN {
|
||||
foo
|
||||
}
|
4
test/fixtures/ruby/begin-block.B.rb
vendored
Normal file
4
test/fixtures/ruby/begin-block.B.rb
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
foo
|
||||
BEGIN {
|
||||
bar
|
||||
}
|
5
test/fixtures/ruby/begin-block.diffA-B.txt
vendored
Normal file
5
test/fixtures/ruby/begin-block.diffA-B.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Program
|
||||
{+(Identifier)+}
|
||||
(BeginBlock
|
||||
{ (Identifier)
|
||||
->(Identifier) }))
|
6
test/fixtures/ruby/begin-block.diffB-A.txt
vendored
Normal file
6
test/fixtures/ruby/begin-block.diffB-A.txt
vendored
Normal file
@ -0,0 +1,6 @@
|
||||
(Program
|
||||
{+(BeginBlock
|
||||
(Identifier))+}
|
||||
{-(Identifier)-}
|
||||
{-(BeginBlock
|
||||
(Identifier))-})
|
3
test/fixtures/ruby/begin-block.parseA.txt
vendored
Normal file
3
test/fixtures/ruby/begin-block.parseA.txt
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
(Program
|
||||
(BeginBlock
|
||||
(Identifier)))
|
4
test/fixtures/ruby/begin-block.parseB.txt
vendored
Normal file
4
test/fixtures/ruby/begin-block.parseB.txt
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
(Program
|
||||
(Identifier)
|
||||
(BeginBlock
|
||||
(Identifier)))
|
4
test/fixtures/ruby/begin.A.rb
vendored
Normal file
4
test/fixtures/ruby/begin.A.rb
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
def foo
|
||||
begin
|
||||
end
|
||||
end
|
5
test/fixtures/ruby/begin.B.rb
vendored
Normal file
5
test/fixtures/ruby/begin.B.rb
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
def foo
|
||||
begin
|
||||
puts 'hi'
|
||||
end
|
||||
end
|
7
test/fixtures/ruby/begin.diffA-B.txt
vendored
Normal file
7
test/fixtures/ruby/begin.diffA-B.txt
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
(Program
|
||||
(Method
|
||||
(Identifier)
|
||||
(Begin
|
||||
{+(MethodCall
|
||||
(Identifier)
|
||||
(StringLiteral))+})))
|
7
test/fixtures/ruby/begin.diffB-A.txt
vendored
Normal file
7
test/fixtures/ruby/begin.diffB-A.txt
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
(Program
|
||||
(Method
|
||||
(Identifier)
|
||||
(Begin
|
||||
{-(MethodCall
|
||||
(Identifier)
|
||||
(StringLiteral))-})))
|
4
test/fixtures/ruby/begin.parseA.txt
vendored
Normal file
4
test/fixtures/ruby/begin.parseA.txt
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
(Program
|
||||
(Method
|
||||
(Identifier)
|
||||
(Begin)))
|
7
test/fixtures/ruby/begin.parseB.txt
vendored
Normal file
7
test/fixtures/ruby/begin.parseB.txt
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
(Program
|
||||
(Method
|
||||
(Identifier)
|
||||
(Begin
|
||||
(MethodCall
|
||||
(Identifier)
|
||||
(StringLiteral)))))
|
3
test/fixtures/ruby/bitwise-operator.A.rb
vendored
Normal file
3
test/fixtures/ruby/bitwise-operator.A.rb
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
a | b
|
||||
a >> b
|
||||
a ^ b
|
2
test/fixtures/ruby/bitwise-operator.B.rb
vendored
Normal file
2
test/fixtures/ruby/bitwise-operator.B.rb
vendored
Normal file
@ -0,0 +1,2 @@
|
||||
a & b
|
||||
a << b
|
21
test/fixtures/ruby/bitwise-operator.diffA-B.txt
vendored
Normal file
21
test/fixtures/ruby/bitwise-operator.diffA-B.txt
vendored
Normal file
@ -0,0 +1,21 @@
|
||||
(Program
|
||||
{ (Binary
|
||||
(Identifier)
|
||||
(Other "|")
|
||||
(Identifier))
|
||||
->(Binary
|
||||
(Identifier)
|
||||
(Other "&")
|
||||
(Identifier)) }
|
||||
{ (Binary
|
||||
(Identifier)
|
||||
(Other ">>")
|
||||
(Identifier))
|
||||
->(Binary
|
||||
(Identifier)
|
||||
(Other "<<")
|
||||
(Identifier)) }
|
||||
{-(Binary
|
||||
(Identifier)
|
||||
(Other "^")
|
||||
(Identifier))-})
|
21
test/fixtures/ruby/bitwise-operator.diffB-A.txt
vendored
Normal file
21
test/fixtures/ruby/bitwise-operator.diffB-A.txt
vendored
Normal file
@ -0,0 +1,21 @@
|
||||
(Program
|
||||
{ (Binary
|
||||
(Identifier)
|
||||
(Other "&")
|
||||
(Identifier))
|
||||
->(Binary
|
||||
(Identifier)
|
||||
(Other "|")
|
||||
(Identifier)) }
|
||||
{ (Binary
|
||||
(Identifier)
|
||||
(Other "<<")
|
||||
(Identifier))
|
||||
->(Binary
|
||||
(Identifier)
|
||||
(Other ">>")
|
||||
(Identifier)) }
|
||||
{+(Binary
|
||||
(Identifier)
|
||||
(Other "^")
|
||||
(Identifier))+})
|
13
test/fixtures/ruby/bitwise-operator.parseA.txt
vendored
Normal file
13
test/fixtures/ruby/bitwise-operator.parseA.txt
vendored
Normal file
@ -0,0 +1,13 @@
|
||||
(Program
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other "|")
|
||||
(Identifier))
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other ">>")
|
||||
(Identifier))
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other "^")
|
||||
(Identifier)))
|
9
test/fixtures/ruby/bitwise-operator.parseB.txt
vendored
Normal file
9
test/fixtures/ruby/bitwise-operator.parseB.txt
vendored
Normal file
@ -0,0 +1,9 @@
|
||||
(Program
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other "&")
|
||||
(Identifier))
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other "<<")
|
||||
(Identifier)))
|
1
test/fixtures/ruby/boolean-operator.A.rb
vendored
Normal file
1
test/fixtures/ruby/boolean-operator.A.rb
vendored
Normal file
@ -0,0 +1 @@
|
||||
a || b
|
1
test/fixtures/ruby/boolean-operator.B.rb
vendored
Normal file
1
test/fixtures/ruby/boolean-operator.B.rb
vendored
Normal file
@ -0,0 +1 @@
|
||||
a && b
|
9
test/fixtures/ruby/boolean-operator.diffA-B.txt
vendored
Normal file
9
test/fixtures/ruby/boolean-operator.diffA-B.txt
vendored
Normal file
@ -0,0 +1,9 @@
|
||||
(Program
|
||||
{ (Binary
|
||||
(Identifier)
|
||||
(Other "||")
|
||||
(Identifier))
|
||||
->(Binary
|
||||
(Identifier)
|
||||
(Other "&&")
|
||||
(Identifier)) })
|
9
test/fixtures/ruby/boolean-operator.diffB-A.txt
vendored
Normal file
9
test/fixtures/ruby/boolean-operator.diffB-A.txt
vendored
Normal file
@ -0,0 +1,9 @@
|
||||
(Program
|
||||
{ (Binary
|
||||
(Identifier)
|
||||
(Other "&&")
|
||||
(Identifier))
|
||||
->(Binary
|
||||
(Identifier)
|
||||
(Other "||")
|
||||
(Identifier)) })
|
5
test/fixtures/ruby/boolean-operator.parseA.txt
vendored
Normal file
5
test/fixtures/ruby/boolean-operator.parseA.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Program
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other "||")
|
||||
(Identifier)))
|
5
test/fixtures/ruby/boolean-operator.parseB.txt
vendored
Normal file
5
test/fixtures/ruby/boolean-operator.parseB.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Program
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other "&&")
|
||||
(Identifier)))
|
3
test/fixtures/ruby/class.A.rb
vendored
Normal file
3
test/fixtures/ruby/class.A.rb
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
class Foo < Super
|
||||
def test; end
|
||||
end
|
3
test/fixtures/ruby/class.B.rb
vendored
Normal file
3
test/fixtures/ruby/class.B.rb
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
class Foo
|
||||
def test; end
|
||||
end
|
7
test/fixtures/ruby/class.diffA-B.txt
vendored
Normal file
7
test/fixtures/ruby/class.diffA-B.txt
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
(Program
|
||||
(Class
|
||||
(Constant)
|
||||
{-(Superclass
|
||||
(Constant))-}
|
||||
(Method
|
||||
(Identifier))))
|
7
test/fixtures/ruby/class.diffB-A.txt
vendored
Normal file
7
test/fixtures/ruby/class.diffB-A.txt
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
(Program
|
||||
(Class
|
||||
(Constant)
|
||||
{+(Superclass
|
||||
(Constant))+}
|
||||
(Method
|
||||
(Identifier))))
|
7
test/fixtures/ruby/class.parseA.txt
vendored
Normal file
7
test/fixtures/ruby/class.parseA.txt
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
(Program
|
||||
(Class
|
||||
(Constant)
|
||||
(Superclass
|
||||
(Constant))
|
||||
(Method
|
||||
(Identifier))))
|
5
test/fixtures/ruby/class.parseB.txt
vendored
Normal file
5
test/fixtures/ruby/class.parseB.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Program
|
||||
(Class
|
||||
(Constant)
|
||||
(Method
|
||||
(Identifier))))
|
1
test/fixtures/ruby/comment.A.rb
vendored
Normal file
1
test/fixtures/ruby/comment.A.rb
vendored
Normal file
@ -0,0 +1 @@
|
||||
# This is a comment
|
4
test/fixtures/ruby/comment.B.rb
vendored
Normal file
4
test/fixtures/ruby/comment.B.rb
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
=begin
|
||||
This is a multiline
|
||||
comment
|
||||
=end
|
3
test/fixtures/ruby/comment.diffA-B.txt
vendored
Normal file
3
test/fixtures/ruby/comment.diffA-B.txt
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
(Program
|
||||
{ (Comment)
|
||||
->(Comment) })
|
3
test/fixtures/ruby/comment.diffB-A.txt
vendored
Normal file
3
test/fixtures/ruby/comment.diffB-A.txt
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
(Program
|
||||
{ (Comment)
|
||||
->(Comment) })
|
2
test/fixtures/ruby/comment.parseA.txt
vendored
Normal file
2
test/fixtures/ruby/comment.parseA.txt
vendored
Normal file
@ -0,0 +1,2 @@
|
||||
(Program
|
||||
(Comment))
|
2
test/fixtures/ruby/comment.parseB.txt
vendored
Normal file
2
test/fixtures/ruby/comment.parseB.txt
vendored
Normal file
@ -0,0 +1,2 @@
|
||||
(Program
|
||||
(Comment))
|
2
test/fixtures/ruby/comparision-operator.A.rb
vendored
Normal file
2
test/fixtures/ruby/comparision-operator.A.rb
vendored
Normal file
@ -0,0 +1,2 @@
|
||||
x < y
|
||||
a > b
|
2
test/fixtures/ruby/comparision-operator.B.rb
vendored
Normal file
2
test/fixtures/ruby/comparision-operator.B.rb
vendored
Normal file
@ -0,0 +1,2 @@
|
||||
x <= y
|
||||
a >= b
|
17
test/fixtures/ruby/comparision-operator.diffA-B.txt
vendored
Normal file
17
test/fixtures/ruby/comparision-operator.diffA-B.txt
vendored
Normal file
@ -0,0 +1,17 @@
|
||||
(Program
|
||||
{ (Binary
|
||||
(Identifier)
|
||||
(Other "<")
|
||||
(Identifier))
|
||||
->(Binary
|
||||
(Identifier)
|
||||
(Other "<=")
|
||||
(Identifier)) }
|
||||
{ (Binary
|
||||
(Identifier)
|
||||
(Other ">")
|
||||
(Identifier))
|
||||
->(Binary
|
||||
(Identifier)
|
||||
(Other ">=")
|
||||
(Identifier)) })
|
17
test/fixtures/ruby/comparision-operator.diffB-A.txt
vendored
Normal file
17
test/fixtures/ruby/comparision-operator.diffB-A.txt
vendored
Normal file
@ -0,0 +1,17 @@
|
||||
(Program
|
||||
{ (Binary
|
||||
(Identifier)
|
||||
(Other "<=")
|
||||
(Identifier))
|
||||
->(Binary
|
||||
(Identifier)
|
||||
(Other "<")
|
||||
(Identifier)) }
|
||||
{ (Binary
|
||||
(Identifier)
|
||||
(Other ">=")
|
||||
(Identifier))
|
||||
->(Binary
|
||||
(Identifier)
|
||||
(Other ">")
|
||||
(Identifier)) })
|
9
test/fixtures/ruby/comparision-operator.parseA.txt
vendored
Normal file
9
test/fixtures/ruby/comparision-operator.parseA.txt
vendored
Normal file
@ -0,0 +1,9 @@
|
||||
(Program
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other "<")
|
||||
(Identifier))
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other ">")
|
||||
(Identifier)))
|
9
test/fixtures/ruby/comparision-operator.parseB.txt
vendored
Normal file
9
test/fixtures/ruby/comparision-operator.parseB.txt
vendored
Normal file
@ -0,0 +1,9 @@
|
||||
(Program
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other "<=")
|
||||
(Identifier))
|
||||
(Binary
|
||||
(Identifier)
|
||||
(Other ">=")
|
||||
(Identifier)))
|
1
test/fixtures/ruby/conditional-assignment.A.rb
vendored
Normal file
1
test/fixtures/ruby/conditional-assignment.A.rb
vendored
Normal file
@ -0,0 +1 @@
|
||||
x ||= 5
|
1
test/fixtures/ruby/conditional-assignment.B.rb
vendored
Normal file
1
test/fixtures/ruby/conditional-assignment.B.rb
vendored
Normal file
@ -0,0 +1 @@
|
||||
x &&= 7
|
5
test/fixtures/ruby/conditional-assignment.diffA-B.txt
vendored
Normal file
5
test/fixtures/ruby/conditional-assignment.diffA-B.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Program
|
||||
(OperatorAssignment
|
||||
(Identifier)
|
||||
{ (IntegerLiteral)
|
||||
->(IntegerLiteral) }))
|
5
test/fixtures/ruby/conditional-assignment.diffB-A.txt
vendored
Normal file
5
test/fixtures/ruby/conditional-assignment.diffB-A.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Program
|
||||
(OperatorAssignment
|
||||
(Identifier)
|
||||
{ (IntegerLiteral)
|
||||
->(IntegerLiteral) }))
|
4
test/fixtures/ruby/conditional-assignment.parseA.txt
vendored
Normal file
4
test/fixtures/ruby/conditional-assignment.parseA.txt
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
(Program
|
||||
(OperatorAssignment
|
||||
(Identifier)
|
||||
(IntegerLiteral)))
|
4
test/fixtures/ruby/conditional-assignment.parseB.txt
vendored
Normal file
4
test/fixtures/ruby/conditional-assignment.parseB.txt
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
(Program
|
||||
(OperatorAssignment
|
||||
(Identifier)
|
||||
(IntegerLiteral)))
|
6
test/fixtures/ruby/delimiter.A.rb
vendored
Normal file
6
test/fixtures/ruby/delimiter.A.rb
vendored
Normal file
@ -0,0 +1,6 @@
|
||||
%q#a#
|
||||
%q<a<b>c>
|
||||
%#a#
|
||||
%Q#a#
|
||||
%<a<b>c>
|
||||
%Q<a<b>c>
|
6
test/fixtures/ruby/delimiter.B.rb
vendored
Normal file
6
test/fixtures/ruby/delimiter.B.rb
vendored
Normal file
@ -0,0 +1,6 @@
|
||||
%q/b/
|
||||
%q{d{e}f}
|
||||
%/b/
|
||||
%Q/b/
|
||||
%{d{e}f}
|
||||
%Q{d{e}f}
|
13
test/fixtures/ruby/delimiter.diffA-B.txt
vendored
Normal file
13
test/fixtures/ruby/delimiter.diffA-B.txt
vendored
Normal file
@ -0,0 +1,13 @@
|
||||
(Program
|
||||
{+(StringLiteral)+}
|
||||
{+(StringLiteral)+}
|
||||
{ (StringLiteral)
|
||||
->(StringLiteral) }
|
||||
{+(StringLiteral)+}
|
||||
{+(StringLiteral)+}
|
||||
{+(StringLiteral)+}
|
||||
{-(StringLiteral)-}
|
||||
{-(StringLiteral)-}
|
||||
{-(StringLiteral)-}
|
||||
{-(StringLiteral)-}
|
||||
{-(StringLiteral)-})
|
13
test/fixtures/ruby/delimiter.diffB-A.txt
vendored
Normal file
13
test/fixtures/ruby/delimiter.diffB-A.txt
vendored
Normal file
@ -0,0 +1,13 @@
|
||||
(Program
|
||||
{+(StringLiteral)+}
|
||||
{ (StringLiteral)
|
||||
->(StringLiteral) }
|
||||
{+(StringLiteral)+}
|
||||
{ (StringLiteral)
|
||||
->(StringLiteral) }
|
||||
{+(StringLiteral)+}
|
||||
{+(StringLiteral)+}
|
||||
{-(StringLiteral)-}
|
||||
{-(StringLiteral)-}
|
||||
{-(StringLiteral)-}
|
||||
{-(StringLiteral)-})
|
7
test/fixtures/ruby/delimiter.parseA.txt
vendored
Normal file
7
test/fixtures/ruby/delimiter.parseA.txt
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
(Program
|
||||
(StringLiteral)
|
||||
(StringLiteral)
|
||||
(StringLiteral)
|
||||
(StringLiteral)
|
||||
(StringLiteral)
|
||||
(StringLiteral))
|
7
test/fixtures/ruby/delimiter.parseB.txt
vendored
Normal file
7
test/fixtures/ruby/delimiter.parseB.txt
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
(Program
|
||||
(StringLiteral)
|
||||
(StringLiteral)
|
||||
(StringLiteral)
|
||||
(StringLiteral)
|
||||
(StringLiteral)
|
||||
(StringLiteral))
|
3
test/fixtures/ruby/element-reference.A.rb
vendored
Normal file
3
test/fixtures/ruby/element-reference.A.rb
vendored
Normal file
@ -0,0 +1,3 @@
|
||||
foo[bar]
|
||||
foo[:bar]
|
||||
foo[bar] = 1
|
2
test/fixtures/ruby/element-reference.B.rb
vendored
Normal file
2
test/fixtures/ruby/element-reference.B.rb
vendored
Normal file
@ -0,0 +1,2 @@
|
||||
x["b"]
|
||||
x[:"c"]
|
17
test/fixtures/ruby/element-reference.diffA-B.txt
vendored
Normal file
17
test/fixtures/ruby/element-reference.diffA-B.txt
vendored
Normal file
@ -0,0 +1,17 @@
|
||||
(Program
|
||||
{ (SubscriptAccess
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
->(SubscriptAccess
|
||||
(Identifier)
|
||||
(StringLiteral)) }
|
||||
(SubscriptAccess
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (SymbolLiteral)
|
||||
->(SymbolLiteral) })
|
||||
{-(Assignment
|
||||
(SubscriptAccess
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(IntegerLiteral))-})
|
17
test/fixtures/ruby/element-reference.diffB-A.txt
vendored
Normal file
17
test/fixtures/ruby/element-reference.diffB-A.txt
vendored
Normal file
@ -0,0 +1,17 @@
|
||||
(Program
|
||||
{ (SubscriptAccess
|
||||
(Identifier)
|
||||
(StringLiteral))
|
||||
->(SubscriptAccess
|
||||
(Identifier)
|
||||
(Identifier)) }
|
||||
(SubscriptAccess
|
||||
{ (Identifier)
|
||||
->(Identifier) }
|
||||
{ (SymbolLiteral)
|
||||
->(SymbolLiteral) })
|
||||
{+(Assignment
|
||||
(SubscriptAccess
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(IntegerLiteral))+})
|
12
test/fixtures/ruby/element-reference.parseA.txt
vendored
Normal file
12
test/fixtures/ruby/element-reference.parseA.txt
vendored
Normal file
@ -0,0 +1,12 @@
|
||||
(Program
|
||||
(SubscriptAccess
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(SubscriptAccess
|
||||
(Identifier)
|
||||
(SymbolLiteral))
|
||||
(Assignment
|
||||
(SubscriptAccess
|
||||
(Identifier)
|
||||
(Identifier))
|
||||
(IntegerLiteral)))
|
7
test/fixtures/ruby/element-reference.parseB.txt
vendored
Normal file
7
test/fixtures/ruby/element-reference.parseB.txt
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
(Program
|
||||
(SubscriptAccess
|
||||
(Identifier)
|
||||
(StringLiteral))
|
||||
(SubscriptAccess
|
||||
(Identifier)
|
||||
(SymbolLiteral)))
|
4
test/fixtures/ruby/else.A.rb
vendored
Normal file
4
test/fixtures/ruby/else.A.rb
vendored
Normal file
@ -0,0 +1,4 @@
|
||||
begin
|
||||
foo()
|
||||
else
|
||||
end
|
5
test/fixtures/ruby/else.B.rb
vendored
Normal file
5
test/fixtures/ruby/else.B.rb
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
begin
|
||||
foo()
|
||||
else
|
||||
bar()
|
||||
end
|
8
test/fixtures/ruby/else.diffA-B.txt
vendored
Normal file
8
test/fixtures/ruby/else.diffA-B.txt
vendored
Normal file
@ -0,0 +1,8 @@
|
||||
(Program
|
||||
(Begin
|
||||
(MethodCall
|
||||
(Identifier))
|
||||
{ (Else)
|
||||
->(Else
|
||||
(MethodCall
|
||||
(Identifier))) }))
|
8
test/fixtures/ruby/else.diffB-A.txt
vendored
Normal file
8
test/fixtures/ruby/else.diffB-A.txt
vendored
Normal file
@ -0,0 +1,8 @@
|
||||
(Program
|
||||
(Begin
|
||||
(MethodCall
|
||||
(Identifier))
|
||||
{ (Else
|
||||
(MethodCall
|
||||
(Identifier)))
|
||||
->(Else) }))
|
5
test/fixtures/ruby/else.parseA.txt
vendored
Normal file
5
test/fixtures/ruby/else.parseA.txt
vendored
Normal file
@ -0,0 +1,5 @@
|
||||
(Program
|
||||
(Begin
|
||||
(MethodCall
|
||||
(Identifier))
|
||||
(Else)))
|
7
test/fixtures/ruby/else.parseB.txt
vendored
Normal file
7
test/fixtures/ruby/else.parseB.txt
vendored
Normal file
@ -0,0 +1,7 @@
|
||||
(Program
|
||||
(Begin
|
||||
(MethodCall
|
||||
(Identifier))
|
||||
(Else
|
||||
(MethodCall
|
||||
(Identifier)))))
|
Some files were not shown because too many files have changed in this diff Show More
Loading…
Reference in New Issue
Block a user