2017-04-21 01:13:28 +03:00
|
|
|
module CommandSpec where
|
2017-03-01 01:55:57 +03:00
|
|
|
|
2017-04-04 00:39:04 +03:00
|
|
|
import Command
|
2017-04-21 23:56:19 +03:00
|
|
|
import Data.Functor.Both as Both
|
2017-04-04 00:39:04 +03:00
|
|
|
import Data.Maybe
|
2017-04-21 01:13:28 +03:00
|
|
|
import Data.String
|
2017-05-10 01:49:38 +03:00
|
|
|
import Language
|
2017-04-21 01:13:28 +03:00
|
|
|
import Prologue hiding (readFile, toList)
|
2017-04-04 03:09:02 +03:00
|
|
|
import Source
|
2017-03-01 01:55:57 +03:00
|
|
|
import Test.Hspec hiding (shouldBe, shouldNotBe, shouldThrow, errorCall)
|
|
|
|
import Test.Hspec.Expectations.Pretty
|
|
|
|
|
|
|
|
spec :: Spec
|
|
|
|
spec = parallel $ do
|
2017-04-21 01:13:28 +03:00
|
|
|
describe "readFile" $ do
|
|
|
|
it "returns a blob for extant files" $ do
|
2017-06-15 17:17:41 +03:00
|
|
|
blob <- readFile "semantic-diff.cabal" Nothing
|
2017-04-21 20:25:47 +03:00
|
|
|
path blob `shouldBe` "semantic-diff.cabal"
|
2017-04-21 01:13:28 +03:00
|
|
|
|
2017-04-21 20:25:47 +03:00
|
|
|
it "returns a nullBlob for absent files" $ do
|
2017-06-15 17:17:41 +03:00
|
|
|
blob <- readFile "this file should not exist" Nothing
|
2017-04-21 20:25:47 +03:00
|
|
|
nullBlob blob `shouldBe` True
|
2017-04-21 01:13:28 +03:00
|
|
|
|
2017-05-17 22:53:05 +03:00
|
|
|
describe "readBlobPairsFromHandle" $ do
|
2017-05-23 21:00:20 +03:00
|
|
|
let a = sourceBlob "method.rb" (Just Ruby) "def foo; end"
|
|
|
|
let b = sourceBlob "method.rb" (Just Ruby) "def bar(x); end"
|
2017-05-17 22:47:45 +03:00
|
|
|
it "returns blobs for valid JSON encoded diff input" $ do
|
2017-05-23 21:00:20 +03:00
|
|
|
blobs <- blobsFromFilePath "test/fixtures/input/diff.json"
|
2017-05-17 22:47:45 +03:00
|
|
|
blobs `shouldBe` [both a b]
|
|
|
|
|
2017-05-23 21:00:20 +03:00
|
|
|
it "returns blobs when there's no before" $ do
|
|
|
|
blobs <- blobsFromFilePath "test/fixtures/input/diff-no-before.json"
|
|
|
|
blobs `shouldBe` [both (emptySourceBlob "method.rb") b]
|
|
|
|
|
|
|
|
it "returns blobs when there's null before" $ do
|
|
|
|
blobs <- blobsFromFilePath "test/fixtures/input/diff-null-before.json"
|
|
|
|
blobs `shouldBe` [both (emptySourceBlob "method.rb") b]
|
|
|
|
|
|
|
|
it "returns blobs when there's no after" $ do
|
|
|
|
blobs <- blobsFromFilePath "test/fixtures/input/diff-no-after.json"
|
|
|
|
blobs `shouldBe` [both a (emptySourceBlob "method.rb")]
|
|
|
|
|
|
|
|
it "returns blobs when there's null after" $ do
|
|
|
|
blobs <- blobsFromFilePath "test/fixtures/input/diff-null-after.json"
|
|
|
|
blobs `shouldBe` [both a (emptySourceBlob "method.rb")]
|
|
|
|
|
|
|
|
|
2017-05-19 00:04:44 +03:00
|
|
|
it "returns blobs for unsupported language" $ do
|
|
|
|
h <- openFile "test/fixtures/input/diff-unsupported-language.json" ReadMode
|
2017-06-15 17:17:41 +03:00
|
|
|
blobs <- readBlobPairsFromHandle h
|
2017-05-23 21:00:20 +03:00
|
|
|
let b' = sourceBlob "test.kt" Nothing "fun main(args: Array<String>) {\nprintln(\"hi\")\n}\n"
|
|
|
|
blobs `shouldBe` [both (emptySourceBlob "test.kt") b']
|
2017-05-19 00:04:44 +03:00
|
|
|
|
|
|
|
it "detects language based on filepath for empty language" $ do
|
2017-05-23 21:00:20 +03:00
|
|
|
blobs <- blobsFromFilePath "test/fixtures/input/diff-empty-language.json"
|
2017-05-19 00:04:44 +03:00
|
|
|
blobs `shouldBe` [both a b]
|
|
|
|
|
|
|
|
it "throws on blank input" $ do
|
2017-05-17 22:47:45 +03:00
|
|
|
h <- openFile "test/fixtures/input/blank.json" ReadMode
|
2017-06-15 17:17:41 +03:00
|
|
|
readBlobPairsFromHandle h `shouldThrow` (== ExitFailure 1)
|
2017-05-17 22:47:45 +03:00
|
|
|
|
2017-05-19 00:04:44 +03:00
|
|
|
it "throws if language field not given" $ do
|
|
|
|
h <- openFile "test/fixtures/input/diff-no-language.json" ReadMode
|
2017-06-15 17:17:41 +03:00
|
|
|
readBlobsFromHandle h `shouldThrow` (== ExitFailure 1)
|
2017-05-19 00:04:44 +03:00
|
|
|
|
2017-05-17 23:34:09 +03:00
|
|
|
describe "readBlobsFromHandle" $ do
|
|
|
|
it "returns blobs for valid JSON encoded parse input" $ do
|
|
|
|
h <- openFile "test/fixtures/input/parse.json" ReadMode
|
2017-06-15 17:17:41 +03:00
|
|
|
blobs <- readBlobsFromHandle h
|
2017-05-19 00:04:44 +03:00
|
|
|
let a = sourceBlob "method.rb" (Just Ruby) "def foo; end"
|
2017-05-17 23:34:09 +03:00
|
|
|
blobs `shouldBe` [a]
|
|
|
|
|
2017-05-19 00:04:44 +03:00
|
|
|
it "throws on blank input" $ do
|
2017-05-17 23:34:09 +03:00
|
|
|
h <- openFile "test/fixtures/input/blank.json" ReadMode
|
2017-06-15 17:17:41 +03:00
|
|
|
readBlobsFromHandle h `shouldThrow` (== ExitFailure 1)
|
2017-05-17 23:34:09 +03:00
|
|
|
|
2017-06-15 06:20:12 +03:00
|
|
|
where blobsFromFilePath path = do
|
2017-05-23 21:00:20 +03:00
|
|
|
h <- openFile path ReadMode
|
2017-06-15 17:17:41 +03:00
|
|
|
blobs <- readBlobPairsFromHandle h
|
2017-05-23 21:00:20 +03:00
|
|
|
pure blobs
|
2017-04-21 01:13:28 +03:00
|
|
|
|
2017-04-21 20:25:47 +03:00
|
|
|
data Fixture = Fixture { shas :: Both String, expectedBlobs :: [Both SourceBlob] }
|