1
1
mirror of https://github.com/github/semantic.git synced 2024-12-26 08:25:19 +03:00

Merge branch 'master' into cofree-and-bifunctors-sitting-in-a-tree-a-l-i-g-n-edly

# Conflicts:
#	src/Renderer/JSON.hs
#	src/Renderer/Patch.hs
#	test/CorpusSpec.hs
This commit is contained in:
Rob Rix 2016-04-04 18:00:25 -04:00
commit 8b2a9fb6d0
8 changed files with 64 additions and 41 deletions

View File

@ -1,24 +1,35 @@
module DiffOutput where module DiffOutput where
import qualified Data.ByteString.Lazy as B import qualified Data.Text.IO as TextIO
import qualified Data.Text.Lazy.IO as TextIO
import Data.Functor.Both import Data.Functor.Both
import Diffing import Diffing
import Parser import Parser
import qualified Renderer.JSON as J import qualified Renderer.JSON as J
import qualified Renderer.Patch as P import qualified Renderer.Patch as P
import Renderer
import Renderer.Split import Renderer.Split
import Source import Source
import System.Directory import System.Directory
import System.FilePath import System.FilePath
import qualified System.IO as IO import qualified System.IO as IO
import Data.String
import Data.Text hiding (split)
-- | The available types of diff rendering. -- | Returns a rendered diff given a parser, diff arguments and two source blobs.
data Format = Split | Patch | JSON textDiff :: Parser -> DiffArguments -> Both SourceBlob -> IO Text
textDiff parser arguments sources = case format arguments of
Split -> diffFiles parser split sources
Patch -> diffFiles parser P.patch sources
JSON -> diffFiles parser J.json sources
data DiffArguments = DiffArguments { format :: Format, output :: Maybe FilePath, outputPath :: FilePath } -- | Returns a truncated diff given diff arguments and two source blobs.
truncatedDiff :: DiffArguments -> Both SourceBlob -> IO Text
truncatedDiff arguments sources = case format arguments of
Split -> return ""
Patch -> return $ P.truncatePatch arguments sources
JSON -> return "{}"
-- | Return a renderer from the command-line arguments that will print the diff. -- | Prints a rendered diff to stdio or a filepath given a parser, diff arguments and two source blobs.
printDiff :: Parser -> DiffArguments -> Both SourceBlob -> IO () printDiff :: Parser -> DiffArguments -> Both SourceBlob -> IO ()
printDiff parser arguments sources = case format arguments of printDiff parser arguments sources = case format arguments of
Split -> put (output arguments) =<< diffFiles parser split sources Split -> put (output arguments) =<< diffFiles parser split sources
@ -30,5 +41,5 @@ printDiff parser arguments sources = case format arguments of
then path </> (takeFileName outputPath -<.> ".html") then path </> (takeFileName outputPath -<.> ".html")
else path else path
IO.withFile outputPath IO.WriteMode (`TextIO.hPutStr` rendered) IO.withFile outputPath IO.WriteMode (`TextIO.hPutStr` rendered)
Patch -> putStr =<< diffFiles parser P.patch sources Patch -> TextIO.putStr =<< diffFiles parser P.patch sources
JSON -> B.putStr =<< diffFiles parser J.json sources JSON -> TextIO.putStr =<< diffFiles parser J.json sources

View File

@ -70,9 +70,11 @@ readAndTranscodeFile path = do
-- | Given a parser and renderer, diff two sources and return the rendered -- | Given a parser and renderer, diff two sources and return the rendered
-- | result. -- | result.
diffFiles :: Parser -> Renderer T.Text b -> Both SourceBlob -> IO b -- | Returns the rendered result strictly, so it's always fully evaluated
-- | with respect to other IO actions.
diffFiles :: Parser -> Renderer T.Text -> Both SourceBlob -> IO T.Text
diffFiles parser renderer sourceBlobs = do diffFiles parser renderer sourceBlobs = do
let sources = source <$> sourceBlobs let sources = source <$> sourceBlobs
terms <- sequence $ parser <$> sources terms <- sequence $ parser <$> sources
let replaceLeaves = breakDownLeavesByWord <$> sources let replaceLeaves = breakDownLeavesByWord <$> sources
return $ renderer (runBothWith diffTerms $ replaceLeaves <*> terms) sourceBlobs return $! renderer (runBothWith diffTerms $ replaceLeaves <*> terms) sourceBlobs

View File

@ -4,6 +4,12 @@ import Data.Functor.Both
import Diff import Diff
import Info import Info
import Source import Source
import Data.Text
-- | A function that will render a diff, given the two source files. -- | A function that will render a diff, given the two source files.
type Renderer a b = Diff a Info -> Both SourceBlob -> b type Renderer a = Diff a Info -> Both SourceBlob -> Text
data DiffArguments = DiffArguments { format :: Format, output :: Maybe FilePath, outputPath :: FilePath }
-- | The available types of diff rendering.
data Format = Split | Patch | JSON

View File

@ -9,12 +9,13 @@ import Category
import Control.Comonad.Cofree import Control.Comonad.Cofree
import Control.Monad.Free import Control.Monad.Free
import Data.Aeson hiding (json) import Data.Aeson hiding (json)
import Data.Aeson.Encode
import Data.Bifunctor.Join import Data.Bifunctor.Join
import Data.ByteString.Builder
import Data.ByteString.Lazy
import Data.Functor.Both import Data.Functor.Both
import Data.Monoid
import Data.OrderedMap hiding (fromList) import Data.OrderedMap hiding (fromList)
import Data.Text
import Data.Text.Lazy (toStrict)
import Data.Text.Lazy.Builder (toLazyText)
import qualified Data.Text as T import qualified Data.Text as T
import Data.Vector hiding (toList) import Data.Vector hiding (toList)
import Diff import Diff
@ -28,11 +29,8 @@ import Syntax
import Term import Term
-- | Render a diff to a string representing its JSON. -- | Render a diff to a string representing its JSON.
json :: Renderer a ByteString json :: Renderer a
json diff sources = toLazyByteString . fromEncoding . pairs $ json diff sources = toStrict . toLazyText . encodeToTextBuilder $ object ["rows" .= annotateRows (splitDiffByLines (source <$> sources) diff), "oids" .= (oid <$> sources), "paths" .= (path <$> sources)]
"rows" .= annotateRows (splitDiffByLines (source <$> sources) diff)
<> "oids" .= (oid <$> sources)
<> "paths" .= (path <$> sources)
where annotateRows = fmap (fmap NumberedLine) . numberedRows where annotateRows = fmap (fmap NumberedLine) . numberedRows
newtype NumberedLine a = NumberedLine (Int, Line a) newtype NumberedLine a = NumberedLine (Int, Line a)

View File

@ -1,7 +1,8 @@
module Renderer.Patch ( module Renderer.Patch (
patch, patch,
hunks, hunks,
Hunk(..) Hunk(..),
truncatePatch
) where ) where
import Alignment import Alignment
@ -21,10 +22,15 @@ import Data.Functor.Both as Both
import Data.List import Data.List
import Data.Maybe import Data.Maybe
import Data.Monoid import Data.Monoid
import Data.Text (pack, Text)
-- | Render a timed out file as a truncated diff.
truncatePatch :: DiffArguments -> Both SourceBlob -> Text
truncatePatch arguments blobs = pack $ header blobs ++ "#timed_out\nTruncating diff: timeout reached.\n"
-- | Render a diff in the traditional patch format. -- | Render a diff in the traditional patch format.
patch :: Renderer a String patch :: Renderer a
patch diff blobs = case getLast $ foldMap (Last . Just) string of patch diff blobs = pack $ case getLast (foldMap (Last . Just) string) of
Just c | c /= '\n' -> string ++ "\n\\ No newline at end of file\n" Just c | c /= '\n' -> string ++ "\n\\ No newline at end of file\n"
_ -> string _ -> string
where string = header blobs ++ mconcat (showHunk blobs <$> hunks diff blobs) where string = header blobs ++ mconcat (showHunk blobs <$> hunks diff blobs)
@ -108,13 +114,17 @@ header blobs = intercalate "\n" [filepathHeader, fileModeHeader, beforeFilepath,
(oidA, oidB) = runBoth $ oid <$> blobs (oidA, oidB) = runBoth $ oid <$> blobs
(modeA, modeB) = runBoth $ blobKind <$> blobs (modeA, modeB) = runBoth $ blobKind <$> blobs
-- | A hunk representing no changes.
emptyHunk :: Hunk (SplitDiff a Info)
emptyHunk = Hunk { offset = mempty, changes = [], trailingContext = [] }
-- | Render a diff as a series of hunks. -- | Render a diff as a series of hunks.
hunks :: Renderer a [Hunk (SplitDiff a Info)] hunks :: Diff a Info -> Both SourceBlob -> [Hunk (SplitDiff a Info)]
hunks _ blobs | sources <- source <$> blobs hunks _ blobs | sources <- source <$> blobs
, sourcesEqual <- runBothWith (==) sources , sourcesEqual <- runBothWith (==) sources
, sourcesNull <- runBothWith (&&) (null <$> sources) , sourcesNull <- runBothWith (&&) (null <$> sources)
, sourcesEqual || sourcesNull , sourcesEqual || sourcesNull
= [Hunk { offset = mempty, changes = [], trailingContext = [] }] = [emptyHunk]
hunks diff blobs = hunksInRows (Join (1, 1)) $ fmap (fmap Prelude.fst) <$> splitDiffByLines (source <$> blobs) diff hunks diff blobs = hunksInRows (Join (1, 1)) $ fmap (fmap Prelude.fst) <$> splitDiffByLines (source <$> blobs) diff
-- | Given beginning line numbers, turn rows in a split diff into hunks in a -- | Given beginning line numbers, turn rows in a split diff into hunks in a

View File

@ -8,6 +8,7 @@ import Control.Monad.Free
import Data.Foldable import Data.Foldable
import Data.Functor.Both import Data.Functor.Both
import Data.Monoid import Data.Monoid
import qualified Data.Text as T
import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy as TL
import Diff import Diff
import Info import Info
@ -52,8 +53,8 @@ splitPatchToClassName patch = stringValue $ "patch " ++ case patch of
SplitReplace _ -> "replace" SplitReplace _ -> "replace"
-- | Render a diff as an HTML split diff. -- | Render a diff as an HTML split diff.
split :: Renderer leaf TL.Text split :: Renderer leaf
split diff blobs = renderHtml split diff blobs = TL.toStrict . renderHtml
. docTypeHtml . docTypeHtml
. ((head $ link ! A.rel "stylesheet" ! A.href "style.css") <>) . ((head $ link ! A.rel "stylesheet" ! A.href "style.css") <>)
. body . body

View File

@ -34,22 +34,17 @@ spec = parallel $ do
examples "test/diffs/" `shouldNotReturn` [] examples "test/diffs/" `shouldNotReturn` []
where where
runTestsIn :: String -> (String -> String -> Expectation) -> SpecWith () runTestsIn :: String -> (T.Text -> T.Text -> Expectation) -> SpecWith ()
runTestsIn directory matcher = do runTestsIn directory matcher = do
paths <- runIO $ examples directory paths <- runIO $ examples directory
let tests = correctTests =<< paths let tests = correctTests =<< paths
mapM_ (\ (formatName, renderer, paths, output) -> it (normalizeName (fst paths) ++ " (" ++ formatName ++ ")") $ testDiff renderer paths output matcher) tests mapM_ (\ (formatName, renderer, paths, output) -> it (normalizeName (fst paths) ++ " (" ++ formatName ++ ")") $ testDiff renderer paths output matcher) tests
correctTests :: (Both FilePath, Maybe FilePath, Maybe FilePath, Maybe FilePath) -> [(String, Renderer a String, Both FilePath, Maybe FilePath)] correctTests :: (Both FilePath, Maybe FilePath, Maybe FilePath, Maybe FilePath) -> [(String, Renderer a, Both FilePath, Maybe FilePath)]
correctTests paths@(_, Nothing, Nothing, Nothing) = testsForPaths paths correctTests paths@(_, Nothing, Nothing, Nothing) = testsForPaths paths
correctTests paths = List.filter (\(_, _, _, output) -> isJust output) $ testsForPaths paths correctTests paths = List.filter (\(_, _, _, output) -> isJust output) $ testsForPaths paths
testsForPaths :: (Both FilePath, Maybe FilePath, Maybe FilePath, Maybe FilePath) -> [(String, Renderer a String, Both FilePath, Maybe FilePath)] testsForPaths :: (Both FilePath, Maybe FilePath, Maybe FilePath, Maybe FilePath) -> [(String, Renderer a, Both FilePath, Maybe FilePath)]
testsForPaths (paths, json, patch, split) = [ ("json", testJSON, paths, json), ("patch", P.patch, paths, patch), ("split", testSplit, paths, split) ] testsForPaths (paths, json, patch, split) = [ ("json", J.json, paths, json), ("patch", P.patch, paths, patch), ("split", Split.split, paths, split) ]
testSplit :: Renderer a String
testSplit diff sources = TL.unpack $ Split.split diff sources
testJSON :: Renderer a String
testJSON diff sources = B.unpack $ J.json diff sources
-- | Return all the examples from the given directory. Examples are expected to -- | Return all the examples from the given directory. Examples are expected to
-- | have the form "foo.A.js", "foo.B.js", "foo.patch.js". Diffs are not -- | have the form "foo.A.js", "foo.B.js", "foo.patch.js". Diffs are not
@ -75,14 +70,14 @@ normalizeName path = addExtension (dropExtension $ dropExtension path) (takeExte
-- | Given file paths for A, B, and, optionally, a diff, return whether diffing -- | Given file paths for A, B, and, optionally, a diff, return whether diffing
-- | the files will produce the diff. If no diff is provided, then the result -- | the files will produce the diff. If no diff is provided, then the result
-- | is true, but the diff will still be calculated. -- | is true, but the diff will still be calculated.
testDiff :: Renderer T.Text String -> Both FilePath -> Maybe FilePath -> (String -> String -> Expectation) -> Expectation testDiff :: Renderer T.Text -> Both FilePath -> Maybe FilePath -> (T.Text -> T.Text -> Expectation) -> Expectation
testDiff renderer paths diff matcher = do testDiff renderer paths diff matcher = do
let parser = parserForFilepath (fst paths)
sources <- sequence $ readAndTranscodeFile <$> paths sources <- sequence $ readAndTranscodeFile <$> paths
let sourceBlobs = both S.SourceBlob S.SourceBlob <*> sources <*> pure mempty <*> paths <*> pure (Just S.defaultPlainBlob) actual <- diffFiles parser renderer (sourceBlobs sources)
actual <- diffFiles parser renderer sourceBlobs
case diff of case diff of
Nothing -> matcher actual actual Nothing -> matcher actual actual
Just file -> do Just file -> do
expected <- readFile file expected <- T.pack <$> readFile file
matcher actual expected matcher actual expected
where parser = parserForFilepath (fst paths)
sourceBlobs sources = pure S.SourceBlob <*> sources <*> pure mempty <*> paths <*> pure (Just S.defaultPlainBlob)

View File

@ -1 +1 @@
{"rows":[[{"number":1,"terms":[{"range":[0,2],"categories":["program"],"children":[{"range":[0,2],"categories":["expression_statement"],"children":[{"range":[0,2],"categories":["DictionaryLiteral"],"children":{}}]}]}],"range":[0,2],"hasChanges":false},{"number":1,"terms":[{"range":[0,2],"categories":["program"],"children":[{"range":[0,2],"categories":["expression_statement"],"children":[{"range":[0,2],"categories":["DictionaryLiteral"],"children":{}}]}]}],"range":[0,2],"hasChanges":false}],[{"number":2,"terms":[{"range":[2,12],"categories":["program"],"children":[{"range":[2,12],"categories":["expression_statement"],"children":[{"range":[2,12],"categories":["DictionaryLiteral"],"children":{"\"b\"":{"range":[4,10],"categories":["Pair"],"children":[{"range":[4,7],"categories":["StringLiteral"],"children":[{"range":[4,5],"categories":["StringLiteral"]},{"range":[5,6],"categories":["StringLiteral"]},{"range":[6,7],"categories":["StringLiteral"]}]},{"patch":"replace","range":[9,10],"categories":["number"]}]}}}]}]}],"range":[2,12],"hasChanges":true},{"number":2,"terms":[{"range":[2,12],"categories":["program"],"children":[{"range":[2,12],"categories":["expression_statement"],"children":[{"range":[2,12],"categories":["DictionaryLiteral"],"children":{"\"b\"":{"range":[4,10],"categories":["Pair"],"children":[{"range":[4,7],"categories":["StringLiteral"],"children":[{"range":[4,5],"categories":["StringLiteral"]},{"range":[5,6],"categories":["StringLiteral"]},{"range":[6,7],"categories":["StringLiteral"]}]},{"patch":"replace","range":[9,10],"categories":["number"]}]}}}]}]}],"range":[2,12],"hasChanges":true}],[{"number":3,"terms":[{"range":[12,21],"categories":["program"],"children":[{"range":[12,21],"categories":["expression_statement"],"children":[{"range":[12,21],"categories":["DictionaryLiteral"],"children":{"\"a\"":{"range":[14,20],"categories":["Pair"],"children":[{"range":[14,17],"categories":["StringLiteral"],"children":[{"range":[14,15],"categories":["StringLiteral"]},{"range":[15,16],"categories":["StringLiteral"]},{"range":[16,17],"categories":["StringLiteral"]}]},{"range":[19,20],"categories":["number"]}]}}}]}]}],"range":[12,21],"hasChanges":false},{"number":3,"terms":[{"range":[12,21],"categories":["program"],"children":[{"range":[12,21],"categories":["expression_statement"],"children":[{"range":[12,21],"categories":["DictionaryLiteral"],"children":{"\"a\"":{"range":[14,20],"categories":["Pair"],"children":[{"range":[14,17],"categories":["StringLiteral"],"children":[{"range":[14,15],"categories":["StringLiteral"]},{"range":[15,16],"categories":["StringLiteral"]},{"range":[16,17],"categories":["StringLiteral"]}]},{"range":[19,20],"categories":["number"]}]}}}]}]}],"range":[12,21],"hasChanges":false}],[{"number":4,"terms":[{"range":[21,23],"categories":["program"],"children":[{"range":[21,23],"categories":["expression_statement"],"children":[{"range":[21,22],"categories":["DictionaryLiteral"],"children":{}}]}]}],"range":[21,23],"hasChanges":false},{"number":4,"terms":[{"range":[21,23],"categories":["program"],"children":[{"range":[21,23],"categories":["expression_statement"],"children":[{"range":[21,22],"categories":["DictionaryLiteral"],"children":{}}]}]}],"range":[21,23],"hasChanges":false}],[{"number":5,"terms":[{"range":[23,23],"categories":["program"],"children":[{"range":[23,23],"categories":["expression_statement"],"children":[]}]}],"range":[23,23],"hasChanges":false},{"number":5,"terms":[{"range":[23,23],"categories":["program"],"children":[{"range":[23,23],"categories":["expression_statement"],"children":[]}]}],"range":[23,23],"hasChanges":false}]],"oids":["",""],"paths":["test/diffs/dictionary.A.js","test/diffs/dictionary.B.js"]} {"rows":[[{"terms":[{"children":[{"children":[{"children":{},"categories":["DictionaryLiteral"],"range":[0,2]}],"categories":["expression_statement"],"range":[0,2]}],"categories":["program"],"range":[0,2]}],"hasChanges":false,"range":[0,2],"number":1},{"terms":[{"children":[{"children":[{"children":{},"categories":["DictionaryLiteral"],"range":[0,2]}],"categories":["expression_statement"],"range":[0,2]}],"categories":["program"],"range":[0,2]}],"hasChanges":false,"range":[0,2],"number":1}],[{"terms":[{"children":[{"children":[{"children":{"\"b\"":{"children":[{"children":[{"categories":["StringLiteral"],"range":[4,5]},{"categories":["StringLiteral"],"range":[5,6]},{"categories":["StringLiteral"],"range":[6,7]}],"categories":["StringLiteral"],"range":[4,7]},{"patch":"replace","categories":["number"],"range":[9,10]}],"categories":["Pair"],"range":[4,10]}},"categories":["DictionaryLiteral"],"range":[2,12]}],"categories":["expression_statement"],"range":[2,12]}],"categories":["program"],"range":[2,12]}],"hasChanges":true,"range":[2,12],"number":2},{"terms":[{"children":[{"children":[{"children":{"\"b\"":{"children":[{"children":[{"categories":["StringLiteral"],"range":[4,5]},{"categories":["StringLiteral"],"range":[5,6]},{"categories":["StringLiteral"],"range":[6,7]}],"categories":["StringLiteral"],"range":[4,7]},{"patch":"replace","categories":["number"],"range":[9,10]}],"categories":["Pair"],"range":[4,10]}},"categories":["DictionaryLiteral"],"range":[2,12]}],"categories":["expression_statement"],"range":[2,12]}],"categories":["program"],"range":[2,12]}],"hasChanges":true,"range":[2,12],"number":2}],[{"terms":[{"children":[{"children":[{"children":{"\"a\"":{"children":[{"children":[{"categories":["StringLiteral"],"range":[14,15]},{"categories":["StringLiteral"],"range":[15,16]},{"categories":["StringLiteral"],"range":[16,17]}],"categories":["StringLiteral"],"range":[14,17]},{"categories":["number"],"range":[19,20]}],"categories":["Pair"],"range":[14,20]}},"categories":["DictionaryLiteral"],"range":[12,21]}],"categories":["expression_statement"],"range":[12,21]}],"categories":["program"],"range":[12,21]}],"hasChanges":false,"range":[12,21],"number":3},{"terms":[{"children":[{"children":[{"children":{"\"a\"":{"children":[{"children":[{"categories":["StringLiteral"],"range":[14,15]},{"categories":["StringLiteral"],"range":[15,16]},{"categories":["StringLiteral"],"range":[16,17]}],"categories":["StringLiteral"],"range":[14,17]},{"categories":["number"],"range":[19,20]}],"categories":["Pair"],"range":[14,20]}},"categories":["DictionaryLiteral"],"range":[12,21]}],"categories":["expression_statement"],"range":[12,21]}],"categories":["program"],"range":[12,21]}],"hasChanges":false,"range":[12,21],"number":3}],[{"terms":[{"children":[{"children":[{"children":{},"categories":["DictionaryLiteral"],"range":[21,22]}],"categories":["expression_statement"],"range":[21,23]}],"categories":["program"],"range":[21,23]}],"hasChanges":false,"range":[21,23],"number":4},{"terms":[{"children":[{"children":[{"children":{},"categories":["DictionaryLiteral"],"range":[21,22]}],"categories":["expression_statement"],"range":[21,23]}],"categories":["program"],"range":[21,23]}],"hasChanges":false,"range":[21,23],"number":4}],[{"terms":[{"children":[{"children":[],"categories":["expression_statement"],"range":[23,23]}],"categories":["program"],"range":[23,23]}],"hasChanges":false,"range":[23,23],"number":5},{"terms":[{"children":[{"children":[],"categories":["expression_statement"],"range":[23,23]}],"categories":["program"],"range":[23,23]}],"hasChanges":false,"range":[23,23],"number":5}]],"paths":["test/diffs/dictionary.A.js","test/diffs/dictionary.B.js"],"oids":["",""]}