1
1
mirror of https://github.com/github/semantic.git synced 2024-12-01 09:15:01 +03:00
semantic/test/Reprinting/Spec.hs
Patrick Thomson ef696d3c41 Split up Semantic.IO.
This looks like a big patch, but it's very straightforward: no
behavior has changed.

After the umpteenth time spent hitting a compile error because I
passed a `FilePath` rather than a `File` to `readBlobFromPath`, I
decided to finally make the needed refactors to Semantic.IO, and to
split off the `File` type and `Files` effect. This patch:

* adds the `MonadIO` class to `Prologue`'s export list
* moves `File` into `Data.File`
* moves `Handle` into `Data.Handle`
* moves `Files` into `Semantic.Task.Files`
* moves functions for reading blobs into `Data.Blob`
* keeps general IO helpers in Semantic.IO
* renames `readFile` to `readBlobFromFile`
* renames `readBlobFromPath` to `readBlobFromFile'`

This should have a positive effect on compile times and ease of
navigation throughout the codebase.
2018-10-23 15:37:49 -04:00

68 lines
2.5 KiB
Haskell

{-# LANGUAGE OverloadedLists, TypeOperators #-}
module Reprinting.Spec where
import SpecHelpers hiding (inject, project)
import Data.Foldable
import Data.Functor.Foldable (cata, embed)
import qualified Data.Machine as Machine
import Control.Rewriting hiding (context)
import Data.Algebra
import Data.Blob
import qualified Data.Language as Language
import Data.Reprinting.Scope
import Data.Reprinting.Token
import Data.Sum
import qualified Data.Syntax.Literal as Literal
import Language.JSON.PrettyPrint
import Language.Python.PrettyPrint
import Language.Ruby.PrettyPrint
import Reprinting.Pipeline
import Reprinting.Tokenize
import Semantic.IO
import Semantic.Util.Rewriting hiding (parseFile)
spec :: Spec
spec = describe "reprinting" $ do
context "JSON" $ do
let path = "test/fixtures/javascript/reprinting/map.json"
(src, tree) <- runIO $ do
src <- blobSource <$> readBlobFromFile' (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 = Machine.run $ tokenizing src tagged
toks `shouldSatisfy` not . null
head toks `shouldSatisfy` isControl
last toks `shouldSatisfy` isChunk
it "should emit control tokens but only 1 chunk for a wholly-modified tree" $ do
let toks = Machine.run $ tokenizing src (mark Refactored tree)
for_ @[] [List, Hash] $ \t -> do
toks `shouldSatisfy` elem (Control (Enter t))
toks `shouldSatisfy` elem (Control (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 (Right tagged) = rewrite (somewhere increaseNumbers markRefactored) () (mark Unmodified tree)
let (Right printed) = runReprinter src defaultJSONPipeline tagged
tree' <- runTask (parse jsonParser (Blob printed path Language.JSON))
length tree' `shouldSatisfy` (/= 0)