{-# LANGUAGE DuplicateRecordFields #-} module SemanticCmdLineSpec where import Prologue import Arguments import SemanticCmdLine import Data.Functor.Listable import Test.Hspec hiding (shouldBe, shouldNotBe, shouldThrow, errorCall) import Test.Hspec.Expectations.Pretty import Test.Hspec.LeanCheck spec :: Spec spec = parallel $ do prop "runDiff for all modes and formats" $ \ DiffFixture{..} -> do output <- runDiff arguments output `shouldBe'` expected prop "runParse for all modes and formats" $ \ ParseFixture{..} -> do output <- runParse arguments output `shouldBe'` expected where shouldBe' actual expected = do when (actual /= expected) $ print actual actual `shouldBe` expected data ParseFixture = ParseFixture { arguments :: ParseArguments , expected :: ByteString } deriving (Show) instance Listable ParseFixture where tiers = cons0 (ParseFixture (sExpressionParseTree pathMode "" []) sExpressionParseTreeOutput) \/ cons0 (ParseFixture (jsonParseTree False pathMode "" []) jsonParseTreeOutput) \/ cons0 (ParseFixture (jsonIndexParseTree False pathMode "" []) jsonIndexParseTreeOutput) \/ cons0 (ParseFixture (sExpressionParseTree commitMode repo []) "(Program\n (Method\n (Identifier)))") \/ cons0 (ParseFixture (jsonParseTree False commitMode repo []) "[{\"filePath\":\"methods.rb\",\"programNode\":{\"category\":\"Program\",\"children\":[{\"category\":\"Method\",\"children\":[{\"category\":\"Identifier\",\"children\":[],\"sourceRange\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}}],\"identifier\":\"foo\",\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,4]}}],\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,1]}}},[]]\n") \/ cons0 (ParseFixture (jsonIndexParseTree False commitMode repo []) "[{\"programNodes\":[{\"category\":\"Program\",\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,1]}},{\"category\":\"Method\",\"identifier\":\"foo\",\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,4]}},{\"category\":\"Identifier\",\"sourceRange\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}}],\"filePath\":\"methods.rb\"},[]]\n") where pathMode = ParsePaths ["test/fixtures/ruby/and-or.A.rb"] commitMode = ParseCommit "2e4144eb8c44f007463ec34cb66353f0041161fe" ["methods.rb"] sExpressionParseTreeOutput = "(Program\n (Binary\n (Identifier)\n (Other \"and\")\n (Identifier)))" jsonParseTreeOutput = "[{\"filePath\":\"test/fixtures/ruby/and-or.A.rb\",\"programNode\":{\"category\":\"Program\",\"children\":[{\"category\":\"Binary\",\"children\":[{\"category\":\"Identifier\",\"children\":[],\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},{\"category\":\"Other \\\"and\\\"\",\"children\":[],\"sourceRange\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}},{\"category\":\"Identifier\",\"children\":[],\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}}],\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,12]}}],\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,1]}}},[]]\n" jsonIndexParseTreeOutput = "[{\"programNodes\":[{\"category\":\"Program\",\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,1]}},{\"category\":\"Binary\",\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,12]}},{\"category\":\"Identifier\",\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},{\"category\":\"Other \\\"and\\\"\",\"sourceRange\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}},{\"category\":\"Identifier\",\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,12]}}],\"filePath\":\"test/fixtures/ruby/and-or.A.rb\"},[]]\n" data DiffFixture = DiffFixture { arguments :: DiffArguments , expected :: ByteString } deriving (Show) instance Listable DiffFixture where tiers = cons0 (DiffFixture (patchDiff pathMode "" []) patchOutput) \/ cons0 (DiffFixture (splitDiff pathMode "" []) splitOutput) \/ cons0 (DiffFixture (jsonDiff pathMode "" []) jsonOutput) \/ cons0 (DiffFixture (summaryDiff pathMode "" []) summaryOutput) \/ cons0 (DiffFixture (sExpressionDiff pathMode "" []) sExpressionOutput) \/ cons0 (DiffFixture (tocDiff pathMode "" []) tocOutput) \/ cons0 (DiffFixture (patchDiff commitMode repo []) patchOutput') \/ cons0 (DiffFixture (splitDiff commitMode repo []) splitOutput') \/ cons0 (DiffFixture (jsonDiff commitMode repo []) jsonOutput') \/ cons0 (DiffFixture (summaryDiff commitMode repo []) summaryOutput') \/ cons0 (DiffFixture (sExpressionDiff commitMode repo []) sExpressionOutput') \/ cons0 (DiffFixture (tocDiff commitMode repo []) tocOutput') where pathMode = DiffPaths "test/fixtures/ruby/method-declaration.A.rb" "test/fixtures/ruby/method-declaration.B.rb" commitMode = DiffCommits "dfac8fd681b0749af137aebf3203e77a06fbafc2" "2e4144eb8c44f007463ec34cb66353f0041161fe" ["methods.rb"] patchOutput = "diff --git a/test/fixtures/ruby/method-declaration.A.rb b/test/fixtures/ruby/method-declaration.B.rb\nindex 0000000000000000000000000000000000000000..0000000000000000000000000000000000000000 100644\n--- a/test/fixtures/ruby/method-declaration.A.rb\n+++ b/test/fixtures/ruby/method-declaration.B.rb\n@@ -1,3 +1,4 @@\n-def foo\n+def bar(a)\n+ baz\n end\n\n" patchOutput' = "diff --git a/methods.rb b/methods.rb\nnew file mode 100644\nindex 0000000000000000000000000000000000000000..ff7bbbe9495f61d9e1e58c597502d152bab1761e\n--- /dev/null\n+++ b/methods.rb\n+def foo\n+end\n\n" splitOutput = "\n\n\n\n\n\n\n\n\n\n\n\n\n
1
    • def
    • foo
    • \n
1
    • def
    • bar
      • (
      • a
      • )\n
2
    • baz
    • \n
2
    • end
  • \n
3
    • end
  • \n
3
    4
      \n" splitOutput' = "\n\n\n\n\n\n\n\n\n\n
      1
        • def
        • foo
        • \n
      2
        • end
      • \n
      3
        \n" summaryOutput = "{\"changes\":{\"test/fixtures/ruby/method-declaration.A.rb -> test/fixtures/ruby/method-declaration.B.rb\":[{\"span\":{\"replace\":[{\"start\":[1,5],\"end\":[1,8]},{\"start\":[1,5],\"end\":[1,8]}]},\"summary\":\"Replaced the 'foo' identifier with the 'bar' identifier in the 'bar(\226\128\166)' method\"},{\"span\":{\"insert\":{\"start\":[1,9],\"end\":[1,10]}},\"summary\":\"Added the 'a' identifier in the 'bar(\226\128\166)' method\"},{\"span\":{\"insert\":{\"start\":[2,3],\"end\":[2,6]}},\"summary\":\"Added the 'baz' identifier in the 'bar(\226\128\166)' method\"}]},\"errors\":{}}\n" summaryOutput' = "{\"changes\":{\"methods.rb\":[{\"span\":{\"insert\":{\"start\":[1,1],\"end\":[2,4]}},\"summary\":\"Added the 'foo()' method\"}]},\"errors\":{}}\n" jsonOutput = "{\"oids\":[\"0000000000000000000000000000000000000000\",\"0000000000000000000000000000000000000000\"],\"paths\":[\"test/fixtures/ruby/method-declaration.A.rb\",\"test/fixtures/ruby/method-declaration.B.rb\"],\"rows\":[[{\"terms\":[{\"category\":\"Program\",\"children\":[{\"category\":\"Method\",\"children\":[{\"category\":\"Identifier\",\"patch\":\"replace\",\"range\":[4,7]}],\"range\":[0,8]}],\"range\":[0,8]}],\"hasChanges\":true,\"range\":[0,8],\"number\":1},{\"terms\":[{\"category\":\"Program\",\"children\":[{\"category\":\"Method\",\"children\":[{\"category\":\"Identifier\",\"patch\":\"replace\",\"range\":[4,7]},{\"category\":\"Params\",\"children\":[{\"category\":\"Identifier\",\"range\":[8,9]}],\"patch\":\"insert\",\"range\":[7,11]}],\"range\":[0,11]}],\"range\":[0,11]}],\"hasChanges\":true,\"range\":[0,11],\"number\":1}],[{\"terms\":[{\"category\":\"Program\",\"children\":[{\"category\":\"Method\",\"children\":[{\"category\":\"Params\",\"children\":[],\"patch\":\"insert\",\"range\":[11,13]},{\"category\":\"Identifier\",\"patch\":\"insert\",\"range\":[13,16]}],\"range\":[11,17]}],\"range\":[11,17]}],\"hasChanges\":true,\"range\":[11,17],\"number\":2}],[{\"terms\":[{\"category\":\"Program\",\"children\":[{\"category\":\"Method\",\"children\":[],\"range\":[8,11]}],\"range\":[8,12]}],\"hasChanges\":false,\"range\":[8,12],\"number\":2},{\"terms\":[{\"category\":\"Program\",\"children\":[{\"category\":\"Method\",\"children\":[],\"range\":[17,20]}],\"range\":[17,21]}],\"hasChanges\":false,\"range\":[17,21],\"number\":3}],[{\"terms\":[{\"category\":\"Program\",\"children\":[],\"range\":[12,12]}],\"hasChanges\":false,\"range\":[12,12],\"number\":3},{\"terms\":[{\"category\":\"Program\",\"children\":[],\"range\":[21,21]}],\"hasChanges\":false,\"range\":[21,21],\"number\":4}]]}\n" jsonOutput' = "{\"oids\":[\"0000000000000000000000000000000000000000\",\"ff7bbbe9495f61d9e1e58c597502d152bab1761e\"],\"paths\":[\"methods.rb\",\"methods.rb\"],\"rows\":[[{\"terms\":[{\"category\":\"Program\",\"children\":[{\"category\":\"Method\",\"children\":[{\"category\":\"Identifier\",\"range\":[4,7]}],\"range\":[0,8]}],\"patch\":\"insert\",\"range\":[0,8]}],\"hasChanges\":true,\"range\":[0,8],\"number\":1}],[{\"terms\":[{\"category\":\"Program\",\"children\":[{\"category\":\"Method\",\"children\":[],\"range\":[8,11]}],\"patch\":\"insert\",\"range\":[8,12]}],\"hasChanges\":true,\"range\":[8,12],\"number\":2}],[{\"terms\":[{\"category\":\"Program\",\"children\":[],\"patch\":\"insert\",\"range\":[12,12]}],\"hasChanges\":true,\"range\":[12,12],\"number\":3}]]}\n" sExpressionOutput = "(Program\n (Method\n { (Identifier)\n ->(Identifier) }\n {+(Params\n (Identifier))+}\n {+(Identifier)+}))" sExpressionOutput' = "{+(Program\n (Method\n (Identifier)))+}" tocOutput = "{\"changes\":{\"test/fixtures/ruby/method-declaration.A.rb -> test/fixtures/ruby/method-declaration.B.rb\":[{\"span\":{\"start\":[1,1],\"end\":[3,4]},\"category\":\"Method\",\"term\":\"bar\",\"changeType\":\"modified\"}]},\"errors\":{}}\n" tocOutput' = "{\"changes\":{\"methods.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"foo\",\"changeType\":\"added\"}]},\"errors\":{}}\n" repo :: FilePath repo = "test/fixtures/git/examples/all-languages.git"