2017-02-22 01:02:31 +03:00
|
|
|
{-# 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
|
2017-02-23 21:06:49 +03:00
|
|
|
examples "test/fixtures/go/" `shouldNotReturn` []
|
2017-02-23 20:55:30 +03:00
|
|
|
examples "test/fixtures/javascript/" `shouldNotReturn` []
|
2017-02-24 19:44:50 +03:00
|
|
|
examples "test/fixtures/ruby/" `shouldNotReturn` []
|
2017-02-22 01:02:31 +03:00
|
|
|
|
2017-02-23 21:06:49 +03:00
|
|
|
describe "go" $ runTestsIn "test/fixtures/go/"
|
2017-02-23 20:55:30 +03:00
|
|
|
describe "javascript" $ runTestsIn "test/fixtures/javascript/"
|
2017-02-23 07:06:05 +03:00
|
|
|
describe "ruby" $ runTestsIn "test/fixtures/ruby/"
|
2017-02-22 01:02:31 +03:00
|
|
|
|
|
|
|
where
|
2017-02-22 03:05:08 +03:00
|
|
|
runTestsIn :: FilePath -> SpecWith ()
|
|
|
|
runTestsIn directory = do
|
|
|
|
examples <- runIO $ examples directory
|
2017-02-22 03:30:39 +03:00
|
|
|
traverse_ runTest examples
|
2017-02-23 07:06:05 +03:00
|
|
|
runTest ParseExample{..} = it ("parses " <> file) $ testParse file parseOutput
|
|
|
|
runTest DiffExample{..} = it ("diffs " <> diffOutput) $ testDiff (Renderer.sExpression TreeOnly) (both fileA fileB) diffOutput
|
2017-02-22 01:02:31 +03:00
|
|
|
|
2017-02-22 22:31:56 +03:00
|
|
|
data Example = DiffExample { fileA :: FilePath, fileB :: FilePath, diffOutput :: FilePath }
|
|
|
|
| ParseExample { file :: FilePath, parseOutput :: FilePath }
|
2017-02-22 03:30:39 +03:00
|
|
|
deriving (Eq, Show)
|
2017-02-22 01:02:31 +03:00
|
|
|
|
|
|
|
-- | Return all the examples from the given directory. Examples are expected to
|
2017-02-22 19:32:19 +03:00
|
|
|
-- | have the form:
|
2017-02-22 01:02:31 +03:00
|
|
|
-- |
|
2017-02-23 01:07:47 +03:00
|
|
|
-- | example-name.A.rb - The left hand side of the diff.
|
|
|
|
-- | example-name.B.rb - The right hand side of the diff.
|
2017-02-22 03:05:08 +03:00
|
|
|
-- |
|
2017-02-23 01:07:47 +03:00
|
|
|
-- | 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.
|
2017-02-22 03:05:08 +03:00
|
|
|
-- |
|
2017-02-23 01:07:47 +03:00
|
|
|
-- | 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
|
2017-02-22 03:30:39 +03:00
|
|
|
examples :: FilePath -> IO [Example]
|
2017-02-22 01:02:31 +03:00
|
|
|
examples directory = do
|
|
|
|
as <- globFor "*.A.*"
|
|
|
|
bs <- globFor "*.B.*"
|
2017-02-22 22:31:56 +03:00
|
|
|
sExpAs <- globFor "*.parseA.txt"
|
|
|
|
sExpBs <- globFor "*.parseB.txt"
|
|
|
|
sExpDiffsAB <- globFor "*.diffA-B.txt"
|
|
|
|
sExpDiffsBA <- globFor "*.diffB-A.txt"
|
2017-02-22 01:02:31 +03:00
|
|
|
|
2017-02-23 01:07:47 +03:00
|
|
|
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
|
2017-02-22 01:02:31 +03:00
|
|
|
|
|
|
|
let keys = (normalizeName <$> as) `union` (normalizeName <$> bs)
|
2017-02-23 01:07:47 +03:00
|
|
|
pure $ getExamples exampleDiff sExpDiffsAB keys
|
|
|
|
<> getExamples exampleDiff' sExpDiffsBA keys
|
|
|
|
<> getExamples (exampleParse as) sExpAs keys
|
|
|
|
<> getExamples (exampleParse bs) sExpBs keys
|
2017-02-22 01:02:31 +03:00
|
|
|
where
|
2017-02-23 01:07:47 +03:00
|
|
|
-- 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
|
|
|
|
|
2017-02-22 03:05:08 +03:00
|
|
|
lookupNormalized :: FilePath -> [FilePath] -> FilePath
|
|
|
|
lookupNormalized name xs = fromMaybe
|
2017-02-22 22:31:56 +03:00
|
|
|
(panic ("cannot find " <> T.pack name <> " make sure .A, .B and exist." :: Text))
|
2017-02-23 01:07:47 +03:00
|
|
|
(lookupNormalized' name xs)
|
|
|
|
|
|
|
|
lookupNormalized' :: FilePath -> [FilePath] -> Maybe FilePath
|
|
|
|
lookupNormalized' name = find ((== name) . normalizeName)
|
|
|
|
|
2017-02-22 01:02:31 +03:00
|
|
|
globFor :: FilePath -> IO [FilePath]
|
|
|
|
globFor p = globDir1 (compile p) directory
|
|
|
|
|
2017-02-22 03:05:08 +03:00
|
|
|
-- | Given a test name like "foo.A.js", return "foo".
|
2017-02-22 01:02:31 +03:00
|
|
|
normalizeName :: FilePath -> FilePath
|
|
|
|
normalizeName path = dropExtension $ dropExtension path
|
|
|
|
|
2017-02-22 19:32:19 +03:00
|
|
|
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
|
|
|
|
|
2017-02-23 02:15:32 +03:00
|
|
|
testDiff :: Renderer (Record '[Range, Category, SourceSpan]) -> Both FilePath -> FilePath -> Expectation
|
2017-02-22 03:05:08 +03:00
|
|
|
testDiff renderer paths diff = do
|
2017-02-23 19:29:55 +03:00
|
|
|
sources <- traverse readAndTranscodeFile paths
|
2017-02-22 03:05:08 +03:00
|
|
|
diff' <- diffFiles parser renderer (sourceBlobs sources)
|
|
|
|
let actual = (Verbatim . stripWhitespace. concatOutputs . pure) diff'
|
|
|
|
expected <- (Verbatim . stripWhitespace) <$> readFile diff
|
|
|
|
actual `shouldBe` expected
|
2017-02-22 01:02:31 +03:00
|
|
|
where
|
2017-02-23 02:15:32 +03:00
|
|
|
parser = parserForFilepath (fst paths)
|
2017-02-22 03:05:08 +03:00
|
|
|
sourceBlobs sources = Source.SourceBlob <$> sources <*> pure mempty <*> paths <*> pure (Just Source.defaultPlainBlob)
|
2017-02-22 01:02:31 +03:00
|
|
|
|
2017-02-22 19:32:19 +03:00
|
|
|
stripWhitespace :: Text -> Text
|
|
|
|
stripWhitespace = T.foldl' go T.empty
|
|
|
|
where go acc x | x `elem` [' ', '\t', '\n'] = acc
|
|
|
|
| otherwise = T.snoc acc x
|
2017-02-22 01:02:31 +03:00
|
|
|
|
|
|
|
-- | 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 ++)
|