2017-04-21 23:56:19 +03:00
|
|
|
{-# LANGUAGE DuplicateRecordFields #-}
|
2017-04-20 00:22:24 +03:00
|
|
|
module SemanticCmdLineSpec where
|
2017-04-11 03:10:34 +03:00
|
|
|
|
2017-07-28 21:37:02 +03:00
|
|
|
import Control.Monad (when)
|
|
|
|
import Data.ByteString (ByteString)
|
|
|
|
import Data.Foldable (for_)
|
2017-07-20 03:01:59 +03:00
|
|
|
import Data.Functor.Both
|
2017-07-28 21:37:02 +03:00
|
|
|
import Data.Semigroup ((<>))
|
2017-05-10 01:49:38 +03:00
|
|
|
import Language
|
2017-06-16 19:40:13 +03:00
|
|
|
import Renderer
|
2017-07-20 00:23:44 +03:00
|
|
|
import Semantic.Task
|
2017-04-20 00:22:24 +03:00
|
|
|
import SemanticCmdLine
|
2017-07-28 21:37:02 +03:00
|
|
|
import System.IO (Handle)
|
2017-04-11 03:10:34 +03:00
|
|
|
import Test.Hspec hiding (shouldBe, shouldNotBe, shouldThrow, errorCall)
|
|
|
|
import Test.Hspec.Expectations.Pretty
|
|
|
|
|
|
|
|
spec :: Spec
|
|
|
|
spec = parallel $ do
|
2017-06-16 19:51:42 +03:00
|
|
|
describe "runDiff" $
|
2017-07-19 21:01:56 +03:00
|
|
|
for_ diffFixtures $ \ (diffRenderer, diffMode, expected) ->
|
2017-06-16 19:51:42 +03:00
|
|
|
it ("renders to " <> show diffRenderer <> " in mode " <> show diffMode) $ do
|
2017-07-20 00:23:44 +03:00
|
|
|
output <- runTask $ runDiff diffRenderer diffMode
|
2017-04-21 23:56:19 +03:00
|
|
|
output `shouldBe'` expected
|
2017-06-16 19:47:47 +03:00
|
|
|
|
|
|
|
describe "runParse" $
|
2017-07-19 21:01:56 +03:00
|
|
|
for_ parseFixtures $ \ (parseTreeRenderer, parseMode, expected) ->
|
2017-06-16 19:47:47 +03:00
|
|
|
it ("renders to " <> show parseTreeRenderer <> " in mode " <> show parseMode) $ do
|
2017-07-20 00:23:44 +03:00
|
|
|
output <- runTask $ runParse parseTreeRenderer parseMode
|
2017-04-21 23:56:19 +03:00
|
|
|
output `shouldBe'` expected
|
2017-04-21 01:13:28 +03:00
|
|
|
where
|
2017-04-21 23:56:19 +03:00
|
|
|
shouldBe' actual expected = do
|
|
|
|
when (actual /= expected) $ print actual
|
|
|
|
actual `shouldBe` expected
|
|
|
|
|
2017-07-19 22:40:56 +03:00
|
|
|
parseFixtures :: [(SomeRenderer TermRenderer, Either Handle [(FilePath, Maybe Language)], ByteString)]
|
2017-06-16 19:47:47 +03:00
|
|
|
parseFixtures =
|
2017-07-19 21:01:56 +03:00
|
|
|
[ (SomeRenderer SExpressionTermRenderer, pathMode, sExpressionParseTreeOutput)
|
|
|
|
, (SomeRenderer JSONTermRenderer, pathMode, jsonParseTreeOutput)
|
|
|
|
, (SomeRenderer JSONTermRenderer, pathMode', jsonParseTreeOutput')
|
2017-07-19 22:40:56 +03:00
|
|
|
, (SomeRenderer JSONTermRenderer, Right [], emptyJsonParseTreeOutput)
|
|
|
|
, (SomeRenderer JSONTermRenderer, Right [("not-a-file.rb", Just Ruby)], emptyJsonParseTreeOutput)
|
|
|
|
, (SomeRenderer ToCTermRenderer, Right [("test/fixtures/ruby/method-declaration.A.rb", Just Ruby)], tocOutput)
|
2017-06-16 19:47:47 +03:00
|
|
|
]
|
2017-07-19 22:40:56 +03:00
|
|
|
where pathMode = Right [("test/fixtures/ruby/and-or.A.rb", Just Ruby)]
|
|
|
|
pathMode' = Right [("test/fixtures/ruby/and-or.A.rb", Just Ruby), ("test/fixtures/ruby/and-or.B.rb", Just Ruby)]
|
2017-06-16 19:47:47 +03:00
|
|
|
|
2017-08-24 21:46:26 +03:00
|
|
|
sExpressionParseTreeOutput = "(Program\n (And\n (Identifier)\n (Identifier)))\n"
|
|
|
|
jsonParseTreeOutput = "[{\"filePath\":\"test/fixtures/ruby/and-or.A.rb\",\"programNode\":{\"category\":\"Program\",\"children\":[{\"category\":\"And\",\"children\":[{\"category\":\"Identifier\",\"children\":[],\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},{\"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]}},\"language\":\"Ruby\"}]\n"
|
|
|
|
jsonParseTreeOutput' = "[{\"filePath\":\"test/fixtures/ruby/and-or.A.rb\",\"programNode\":{\"category\":\"Program\",\"children\":[{\"category\":\"And\",\"children\":[{\"category\":\"Identifier\",\"children\":[],\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},{\"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]}},\"language\":\"Ruby\"},{\"filePath\":\"test/fixtures/ruby/and-or.B.rb\",\"programNode\":{\"category\":\"Program\",\"children\":[{\"category\":\"Or\",\"children\":[{\"category\":\"Identifier\",\"children\":[],\"sourceRange\":[0,3],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,4]}},{\"category\":\"Identifier\",\"children\":[],\"sourceRange\":[7,10],\"sourceSpan\":{\"start\":[1,8],\"end\":[1,11]}}],\"sourceRange\":[0,10],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,11]}},{\"category\":\"And\",\"children\":[{\"category\":\"Or\",\"children\":[{\"category\":\"Identifier\",\"children\":[],\"sourceRange\":[11,12],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,2]}},{\"category\":\"Identifier\",\"children\":[],\"sourceRange\":[16,17],\"sourceSpan\":{\"start\":[2,6],\"end\":[2,7]}}],\"sourceRange\":[11,17],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,7]}},{\"category\":\"Identifier\",\"children\":[],\"sourceRange\":[22,23],\"sourceSpan\":{\"start\":[2,12],\"end\":[2,13]}}],\"sourceRange\":[11,23],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,13]}}],\"sourceRange\":[0,24],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,1]}},\"language\":\"Ruby\"}]\n"
|
2017-06-16 19:47:47 +03:00
|
|
|
emptyJsonParseTreeOutput = "[]\n"
|
2017-06-16 19:55:13 +03:00
|
|
|
tocOutput = "{\"changes\":{\"test/fixtures/ruby/method-declaration.A.rb\":[{\"span\":{\"start\":[1,1],\"end\":[2,4]},\"category\":\"Method\",\"term\":\"foo\",\"changeType\":\"unchanged\"}]},\"errors\":{}}\n"
|
2017-04-21 23:56:19 +03:00
|
|
|
|
|
|
|
|
2017-07-19 22:40:56 +03:00
|
|
|
diffFixtures :: [(SomeRenderer DiffRenderer, Either Handle [Both (FilePath, Maybe Language)], ByteString)]
|
2017-06-16 19:51:42 +03:00
|
|
|
diffFixtures =
|
2017-07-19 21:01:56 +03:00
|
|
|
[ (SomeRenderer PatchDiffRenderer, pathMode, patchOutput)
|
|
|
|
, (SomeRenderer JSONDiffRenderer, pathMode, jsonOutput)
|
|
|
|
, (SomeRenderer SExpressionDiffRenderer, pathMode, sExpressionOutput)
|
2017-09-25 18:24:48 +03:00
|
|
|
, (SomeRenderer OldToCDiffRenderer, pathMode, tocOutput)
|
2017-06-16 19:51:42 +03:00
|
|
|
]
|
2017-07-20 03:01:59 +03:00
|
|
|
where pathMode = Right [both ("test/fixtures/ruby/method-declaration.A.rb", Just Ruby) ("test/fixtures/ruby/method-declaration.B.rb", Just Ruby)]
|
2017-04-21 23:56:19 +03:00
|
|
|
|
2017-06-16 19:51:42 +03:00
|
|
|
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"
|
2017-05-08 15:28:01 +03:00
|
|
|
|
2017-10-06 17:55:46 +03:00
|
|
|
jsonOutput = "{\"diff\":{\"merge\":{\"after\":{\"sourceRange\":[0,21],\"sourceSpan\":{\"start\":[1,1],\"end\":[4,1]}},\"children\":[{\"merge\":{\"after\":{\"sourceRange\":[0,20],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,4]}},\"children\":[{\"merge\":{\"after\":{\"sourceRange\":[0,0],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,1]}},\"children\":[],\"before\":{\"sourceRange\":[0,0],\"sourceSpan\":{\"start\":[1,1],\"end\":[1,1]}}}},{\"patch\":{\"replace\":[{\"children\":[],\"sourceRange\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}},{\"children\":[],\"sourceRange\":[4,7],\"sourceSpan\":{\"start\":[1,5],\"end\":[1,8]}}]}},{\"patch\":{\"insert\":{\"children\":[],\"sourceRange\":[8,9],\"sourceSpan\":{\"start\":[1,9],\"end\":[1,10]}}}},{\"merge\":{\"after\":{\"sourceRange\":[13,16],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,6]}},\"children\":[{\"patch\":{\"insert\":{\"children\":[],\"sourceRange\":[13,16],\"sourceSpan\":{\"start\":[2,3],\"end\":[2,6]}}}}],\"before\":{\"sourceRange\":[8,11],\"sourceSpan\":{\"start\":[2,1],\"end\":[2,4]}}}}],\"before\":{\"sourceRange\":[0,11],\"sourceSpan\":{\"start\":[1,1],\"end\":[2,4]}}}}],\"before\":{\"sourceRange\":[0,12],\"sourceSpan\":{\"start\":[1,1],\"end\":[3,1]}}}},\"oids\":[\"0000000000000000000000000000000000000000\",\"0000000000000000000000000000000000000000\"],\"paths\":[\"test/fixtures/ruby/method-declaration.A.rb\",\"test/fixtures/ruby/method-declaration.B.rb\"]}\n"
|
2017-08-24 21:46:26 +03:00
|
|
|
sExpressionOutput = "(Program\n (Method\n (Empty)\n { (Identifier)\n ->(Identifier) }\n {+(Identifier)+}\n (\n {+(Identifier)+})))\n"
|
2017-06-16 19:51:42 +03:00
|
|
|
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"
|