1
1
mirror of https://github.com/github/semantic.git synced 2024-12-21 05:41:54 +03:00
semantic/test/Reprinting/Spec.hs

79 lines
2.8 KiB
Haskell
Raw Normal View History

{-# LANGUAGE OverloadedLists, TypeOperators #-}
2018-07-31 03:05:44 +03:00
2018-07-31 17:43:46 +03:00
module Reprinting.Spec where
2018-07-30 23:00:09 +03:00
import SpecHelpers hiding (project, inject)
2018-07-30 23:00:09 +03:00
import Data.Functor.Foldable (embed, cata)
2018-07-30 23:00:09 +03:00
import qualified Data.Language as Language
import qualified Data.Syntax.Literal as Literal
import Data.Algebra
import Reprinting.Tokenize
2018-07-31 19:44:20 +03:00
import Reprinting.Pipeline
import Data.Sum
2018-08-16 00:01:58 +03:00
import Data.Foldable
2018-07-30 23:00:09 +03:00
import Semantic.IO
import Semantic.Util.Rewriting hiding (parseFile)
2018-07-30 23:00:09 +03:00
import Data.Blob
2018-08-22 23:35:40 +03:00
import Language.JSON.PrettyPrint
2018-08-22 23:47:30 +03:00
import Language.Ruby.PrettyPrint
2018-07-30 23:00:09 +03:00
spec :: Spec
2018-07-31 21:07:16 +03:00
spec = describe "reprinting" $ do
2018-08-22 23:47:30 +03:00
context "JSON" $ do
let path = "test/fixtures/javascript/reprinting/map.json"
(src, tree) <- runIO $ do
src <- blobSource <$> readBlobFromPath (File path Language.JSON)
tree <- parseFile jsonParser path
pure (src, tree)
describe "tokenization" $ do
it "should pass over a pristine tree" $ do
let tagged = mark Unmodified tree
let toks = tokenizing src tagged
toks `shouldBe` [Chunk src]
it "should emit control tokens but only 1 chunk for a wholly-modified tree" $ do
let toks = tokenizing src (mark Refactored tree)
for_ @[] [TList, THash] $ \t -> do
toks `shouldSatisfy` elem (TControl (Enter t))
toks `shouldSatisfy` elem (TControl (Exit t))
describe "pipeline" $ do
it "should roundtrip exactly over a pristine tree" $ do
let tagged = mark Unmodified tree
let printed = runReprinter src defaultJSONPipeline tagged
printed `shouldBe` Right src
it "should roundtrip exactly over a wholly-modified tree" $ do
let tagged = mark Refactored tree
let printed = runReprinter src defaultJSONPipeline tagged
printed `shouldBe` Right src
it "should be able to parse the output of a refactor" $ do
let tagged = increaseNumbers (mark Refactored tree)
let (Right printed) = runReprinter src defaultJSONPipeline tagged
tree' <- runTask (parse jsonParser (Blob printed path Language.JSON))
length tree' `shouldSatisfy` (/= 0)
context "Ruby" $ do
let dir = "test/fixtures/ruby/reprinting"
let path = dir </> "function.rb"
let expectedPath = dir </> "function.out.rb"
(src, tree, expected) <- runIO $ do
expected <- blobSource <$> readBlobFromPath (File expectedPath Language.Ruby)
src <- blobSource <$> readBlobFromPath (File path Language.Ruby)
tree <- parseFile miniRubyParser path
pure (src, tree, expected)
describe "pipeline" $ do
it "should roundtrip over a wholly-modified tree" $ do
let tagged = mark Refactored tree
let (Right printed) = runReprinter src printingRuby tagged
printed `shouldBe` expected
tree' <- runTask (parse miniRubyParser (Blob printed expectedPath Language.Ruby))
length tree' `shouldSatisfy` (/= 0)