From 4b046e6f4e917465b3e19abb2069c2791a0ca74f Mon Sep 17 00:00:00 2001 From: joshvera Date: Mon, 28 Mar 2016 13:31:10 -0400 Subject: [PATCH 01/13] Return IO Text from printDiff --- src/DiffOutput.hs | 17 ++++++++++++----- src/Renderer/JSON.hs | 14 ++++++-------- src/Renderer/Patch.hs | 5 +++-- src/Renderer/Split.hs | 5 +++-- 4 files changed, 24 insertions(+), 17 deletions(-) diff --git a/src/DiffOutput.hs b/src/DiffOutput.hs index 6fd0bb386..277d1c0ba 100644 --- a/src/DiffOutput.hs +++ b/src/DiffOutput.hs @@ -1,7 +1,6 @@ module DiffOutput where -import qualified Data.ByteString.Lazy as B -import qualified Data.Text.Lazy.IO as TextIO +import qualified Data.Text.IO as TextIO import Data.Functor.Both import Diffing import Parser @@ -12,6 +11,8 @@ import Source import System.Directory import System.FilePath import qualified System.IO as IO +import Data.String +import Data.Text hiding (split) -- | The available types of diff rendering. data Format = Split | Patch | JSON @@ -19,8 +20,14 @@ data Format = Split | Patch | JSON data DiffArguments = DiffArguments { format :: Format, output :: Maybe FilePath, outputPath :: FilePath } -- | Return a renderer from the command-line arguments that will print the diff. -printDiff :: Parser -> DiffArguments -> Both SourceBlob -> IO () +printDiff :: Parser -> DiffArguments -> Both SourceBlob -> IO Text printDiff parser arguments sources = case format arguments of + Split -> diffFiles parser split sources + Patch -> diffFiles parser P.patch sources + JSON -> diffFiles parser J.json sources + +printDiff' :: Parser -> DiffArguments -> Both SourceBlob -> IO () +printDiff' parser arguments sources = case format arguments of Split -> put (output arguments) =<< diffFiles parser split sources where put Nothing rendered = TextIO.putStr rendered @@ -30,5 +37,5 @@ printDiff parser arguments sources = case format arguments of then path (takeFileName outputPath -<.> ".html") else path IO.withFile outputPath IO.WriteMode (`TextIO.hPutStr` rendered) - Patch -> putStr =<< diffFiles parser P.patch sources - JSON -> B.putStr =<< diffFiles parser J.json sources + Patch -> TextIO.putStr =<< diffFiles parser P.patch sources + JSON -> TextIO.putStr =<< diffFiles parser J.json sources diff --git a/src/Renderer/JSON.hs b/src/Renderer/JSON.hs index 496d838c3..01d2ea98a 100644 --- a/src/Renderer/JSON.hs +++ b/src/Renderer/JSON.hs @@ -9,11 +9,12 @@ import Category import Control.Comonad.Cofree import Control.Monad.Free import Data.Aeson hiding (json) -import Data.ByteString.Builder -import Data.ByteString.Lazy +import Data.Aeson.Encode import Data.Functor.Both -import Data.Monoid 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 Data.Vector hiding (toList) import Diff @@ -26,11 +27,8 @@ import Syntax import Term -- | Render a diff to a string representing its JSON. -json :: Renderer a ByteString -json diff sources = toLazyByteString . fromEncoding . pairs $ - "rows" .= annotateRows (splitDiffByLines (source <$> sources) diff) - <> "oids" .= (oid <$> sources) - <> "paths" .= (path <$> sources) +json :: Renderer a Text +json diff sources = toStrict . toLazyText . encodeToTextBuilder $ object ["rows" .= annotateRows (splitDiffByLines (source <$> sources) diff), "oids" .= (oid <$> sources), "paths" .= (path <$> sources)] where annotateRows = fmap (fmap NumberedLine) . numberedRows newtype NumberedLine a = NumberedLine (Int, Line a) diff --git a/src/Renderer/Patch.hs b/src/Renderer/Patch.hs index a41d831be..8ef23b497 100644 --- a/src/Renderer/Patch.hs +++ b/src/Renderer/Patch.hs @@ -19,10 +19,11 @@ import Data.Functor.Both as Both import Data.List import Data.Maybe import Data.Monoid +import Data.Text (pack, Text) -- | Render a diff in the traditional patch format. -patch :: Renderer a String -patch diff sources = case getLast $ foldMap (Last . Just) string of +patch :: Renderer a Text +patch diff sources = pack $ case getLast (foldMap (Last . Just) string) of Just c | c /= '\n' -> string ++ "\n\\ No newline at end of file\n" _ -> string where string = mconcat $ showHunk sources <$> hunks diff sources diff --git a/src/Renderer/Split.hs b/src/Renderer/Split.hs index c899de5ec..451d5d01a 100644 --- a/src/Renderer/Split.hs +++ b/src/Renderer/Split.hs @@ -8,6 +8,7 @@ import Control.Monad.Free import Data.Foldable import Data.Functor.Both import Data.Monoid +import qualified Data.Text as T import qualified Data.Text.Lazy as TL import Diff import Line @@ -51,8 +52,8 @@ splitPatchToClassName patch = stringValue $ "patch " ++ case patch of SplitReplace _ -> "replace" -- | Render a diff as an HTML split diff. -split :: Renderer leaf TL.Text -split diff blobs = renderHtml +split :: Renderer leaf T.Text +split diff blobs = TL.toStrict . renderHtml . docTypeHtml . ((head $ link ! A.rel "stylesheet" ! A.href "style.css") <>) . body From 7947bc1911781af46836a5700105fa17a2ce7d43 Mon Sep 17 00:00:00 2001 From: joshvera Date: Fri, 1 Apr 2016 15:34:52 -0400 Subject: [PATCH 02/13] Move DiffArguments to Renderer.hs --- src/DiffOutput.hs | 6 +----- src/Renderer.hs | 5 +++++ 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/src/DiffOutput.hs b/src/DiffOutput.hs index 277d1c0ba..0fa5ef6ae 100644 --- a/src/DiffOutput.hs +++ b/src/DiffOutput.hs @@ -6,6 +6,7 @@ import Diffing import Parser import qualified Renderer.JSON as J import qualified Renderer.Patch as P +import Renderer import Renderer.Split import Source import System.Directory @@ -14,11 +15,6 @@ import qualified System.IO as IO import Data.String import Data.Text hiding (split) --- | The available types of diff rendering. -data Format = Split | Patch | JSON - -data DiffArguments = DiffArguments { format :: Format, output :: Maybe FilePath, outputPath :: FilePath } - -- | Return a renderer from the command-line arguments that will print the diff. printDiff :: Parser -> DiffArguments -> Both SourceBlob -> IO Text printDiff parser arguments sources = case format arguments of diff --git a/src/Renderer.hs b/src/Renderer.hs index ea381c406..35f1f5f43 100644 --- a/src/Renderer.hs +++ b/src/Renderer.hs @@ -7,3 +7,8 @@ import Source -- | A function that will render a diff, given the two source files. type Renderer a b = Diff a Info -> Both SourceBlob -> b + +data DiffArguments = DiffArguments { format :: Format, output :: Maybe FilePath, outputPath :: FilePath } + +-- | The available types of diff rendering. +data Format = Split | Patch | JSON From a18c2649d37881feac9f928a91decbe985d9af51 Mon Sep 17 00:00:00 2001 From: joshvera Date: Fri, 1 Apr 2016 15:35:09 -0400 Subject: [PATCH 03/13] Add a truncatePatch function --- src/DiffOutput.hs | 6 ++++++ src/Renderer/Patch.hs | 7 ++++++- 2 files changed, 12 insertions(+), 1 deletion(-) diff --git a/src/DiffOutput.hs b/src/DiffOutput.hs index 0fa5ef6ae..3d0a8fc93 100644 --- a/src/DiffOutput.hs +++ b/src/DiffOutput.hs @@ -22,6 +22,12 @@ printDiff parser arguments sources = case format arguments of Patch -> diffFiles parser P.patch sources JSON -> diffFiles parser J.json sources +truncatedDiff :: DiffArguments -> Both SourceBlob -> IO Text +truncatedDiff arguments sources = case format arguments of + Split -> return "" + Patch -> return $ P.truncatePatch arguments sources + JSON -> return "{}" + printDiff' :: Parser -> DiffArguments -> Both SourceBlob -> IO () printDiff' parser arguments sources = case format arguments of Split -> put (output arguments) =<< diffFiles parser split sources diff --git a/src/Renderer/Patch.hs b/src/Renderer/Patch.hs index cf226dcfa..93c64ffba 100644 --- a/src/Renderer/Patch.hs +++ b/src/Renderer/Patch.hs @@ -1,7 +1,8 @@ module Renderer.Patch ( patch, hunks, - Hunk(..) + Hunk(..), + truncatePatch ) where import Alignment @@ -22,6 +23,10 @@ import Data.Maybe 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. patch :: Renderer a Text patch diff blobs = pack $ case getLast (foldMap (Last . Just) string) of From 842a0f30afc79ce97265f3dc39ca0dfc73c78d60 Mon Sep 17 00:00:00 2001 From: joshvera Date: Fri, 1 Apr 2016 15:35:21 -0400 Subject: [PATCH 04/13] Move emptyHunk to a function --- src/Renderer/Patch.hs | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/src/Renderer/Patch.hs b/src/Renderer/Patch.hs index 93c64ffba..6cba19849 100644 --- a/src/Renderer/Patch.hs +++ b/src/Renderer/Patch.hs @@ -113,13 +113,16 @@ header blobs = intercalate "\n" [filepathHeader, fileModeHeader, beforeFilepath, (oidA, oidB) = runBoth $ oid <$> blobs (modeA, modeB) = runBoth $ blobKind <$> blobs +emptyHunk :: Hunk (SplitDiff a Info) +emptyHunk = Hunk { offset = mempty, changes = [], trailingContext = [] } + -- | Render a diff as a series of hunks. hunks :: Renderer a [Hunk (SplitDiff a Info)] hunks _ blobs | sources <- source <$> blobs , sourcesEqual <- runBothWith (==) sources , sourcesNull <- runBothWith (&&) (null <$> sources) , sourcesEqual || sourcesNull - = [Hunk { offset = mempty, changes = [], trailingContext = [] }] + = [emptyHunk] hunks diff blobs = hunksInRows (Both (1, 1)) $ fmap (fmap Prelude.fst) <$> splitDiffByLines (source <$> blobs) diff -- | Given beginning line numbers, turn rows in a split diff into hunks in a From cf898c66c64260f055e3c254b788b46c571e9ee4 Mon Sep 17 00:00:00 2001 From: joshvera Date: Fri, 1 Apr 2016 15:35:38 -0400 Subject: [PATCH 05/13] Strictly render in diffFiles --- src/Diffing.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Diffing.hs b/src/Diffing.hs index 63730807b..619a94fcd 100644 --- a/src/Diffing.hs +++ b/src/Diffing.hs @@ -75,4 +75,4 @@ diffFiles parser renderer sourceBlobs = do let sources = source <$> sourceBlobs terms <- sequence $ parser <$> sources let replaceLeaves = breakDownLeavesByWord <$> sources - return $ renderer (runBothWith diffTerms $ replaceLeaves <*> terms) sourceBlobs + return $! renderer (runBothWith diffTerms $ replaceLeaves <*> terms) sourceBlobs From 4a7004394b21f43d5e79c58dee65e403975a9809 Mon Sep 17 00:00:00 2001 From: joshvera Date: Fri, 1 Apr 2016 15:53:16 -0400 Subject: [PATCH 06/13] fix tests --- test/CorpusSpec.hs | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/test/CorpusSpec.hs b/test/CorpusSpec.hs index 70bd559df..7dcf0a298 100644 --- a/test/CorpusSpec.hs +++ b/test/CorpusSpec.hs @@ -44,11 +44,13 @@ spec = parallel $ do correctTests paths@(_, Nothing, Nothing, Nothing) = 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 (paths, json, patch, split) = [ ("json", testJSON, paths, json), ("patch", P.patch, paths, patch), ("split", testSplit, paths, split) ] + testsForPaths (paths, json, patch, split) = [ ("json", testJSON, paths, json), ("patch", testPatch, paths, patch), ("split", testSplit, paths, split) ] + testPatch :: Renderer a String + testPatch diff sources = T.unpack $ P.patch diff sources testSplit :: Renderer a String - testSplit diff sources = TL.unpack $ Split.split diff sources + testSplit diff sources = T.unpack $ Split.split diff sources testJSON :: Renderer a String - testJSON diff sources = B.unpack $ J.json diff sources + testJSON diff sources = T.unpack $ J.json diff sources -- | Return all the examples from the given directory. Examples are expected to From 4512344e3aa6b180f55f6809477cae743c6bc913 Mon Sep 17 00:00:00 2001 From: joshvera Date: Fri, 1 Apr 2016 16:07:05 -0400 Subject: [PATCH 07/13] update dictionary.json.js --- test/diffs/dictionary.json.js | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/test/diffs/dictionary.json.js b/test/diffs/dictionary.json.js index 0fd2f4ee8..fe957e0cc 100644 --- a/test/diffs/dictionary.json.js +++ b/test/diffs/dictionary.json.js @@ -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"]} \ No newline at end of file +{"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":["",""]} \ No newline at end of file From ba8fef376ae37491a7ee732193c63bb01fa8cc81 Mon Sep 17 00:00:00 2001 From: joshvera Date: Sat, 2 Apr 2016 13:28:17 -0400 Subject: [PATCH 08/13] move to where clause --- test/CorpusSpec.hs | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/test/CorpusSpec.hs b/test/CorpusSpec.hs index 7dcf0a298..cd1bb688f 100644 --- a/test/CorpusSpec.hs +++ b/test/CorpusSpec.hs @@ -79,12 +79,16 @@ normalizeName path = addExtension (dropExtension $ dropExtension path) (takeExte -- | is true, but the diff will still be calculated. testDiff :: Renderer T.Text String -> Both FilePath -> Maybe FilePath -> (String -> String -> Expectation) -> Expectation testDiff renderer paths diff matcher = do - let parser = parserForFilepath (fst 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 case diff of Nothing -> matcher actual actual Just file -> do expected <- readFile file matcher actual expected + where parser = parserForFilepath (fst paths) + sourceBlobs = Both (S.SourceBlob, S.SourceBlob) <*> + sources <*> + pure mempty <*> + paths <*> + pure (Just S.defaultPlainBlob) From 506abacbc68e2e25f9eca62e80433b17be0101a7 Mon Sep 17 00:00:00 2001 From: joshvera Date: Mon, 4 Apr 2016 17:03:35 -0400 Subject: [PATCH 09/13] Document use of strictness in diffFiles --- src/Diffing.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/Diffing.hs b/src/Diffing.hs index 619a94fcd..6e9fd0e69 100644 --- a/src/Diffing.hs +++ b/src/Diffing.hs @@ -70,6 +70,8 @@ readAndTranscodeFile path = do -- | Given a parser and renderer, diff two sources and return the rendered -- | result. +-- | Returns the rendered result strictly, so it's always fully evaluated +-- | with respect to other IO actions. diffFiles :: Parser -> Renderer T.Text b -> Both SourceBlob -> IO b diffFiles parser renderer sourceBlobs = do let sources = source <$> sourceBlobs From 90013b1235fc6361b11c1951fe443f604f665de2 Mon Sep 17 00:00:00 2001 From: joshvera Date: Mon, 4 Apr 2016 17:08:29 -0400 Subject: [PATCH 10/13] Rename printDiff to textDiff and printDiff' to printDiff --- src/DiffOutput.hs | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/src/DiffOutput.hs b/src/DiffOutput.hs index 3d0a8fc93..cd6f09acb 100644 --- a/src/DiffOutput.hs +++ b/src/DiffOutput.hs @@ -16,8 +16,8 @@ import Data.String import Data.Text hiding (split) -- | Return a renderer from the command-line arguments that will print the diff. -printDiff :: Parser -> DiffArguments -> Both SourceBlob -> IO Text -printDiff parser arguments sources = case format arguments of +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 @@ -28,8 +28,8 @@ truncatedDiff arguments sources = case format arguments of Patch -> return $ P.truncatePatch arguments sources JSON -> return "{}" -printDiff' :: Parser -> DiffArguments -> Both SourceBlob -> IO () -printDiff' parser arguments sources = case format arguments of +printDiff :: Parser -> DiffArguments -> Both SourceBlob -> IO () +printDiff parser arguments sources = case format arguments of Split -> put (output arguments) =<< diffFiles parser split sources where put Nothing rendered = TextIO.putStr rendered From 3b752b834cdcaa435cfdadcf390a172ba8df9fef Mon Sep 17 00:00:00 2001 From: joshvera Date: Mon, 4 Apr 2016 17:12:02 -0400 Subject: [PATCH 11/13] docs --- src/DiffOutput.hs | 4 +++- src/Renderer/Patch.hs | 1 + 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/src/DiffOutput.hs b/src/DiffOutput.hs index cd6f09acb..8516a0ee9 100644 --- a/src/DiffOutput.hs +++ b/src/DiffOutput.hs @@ -15,19 +15,21 @@ import qualified System.IO as IO import Data.String import Data.Text hiding (split) --- | Return a renderer from the command-line arguments that will print the diff. +-- | Returns a rendered diff given a parser, diff arguments and two source blobs. 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 +-- | 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 "{}" +-- | 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 arguments sources = case format arguments of Split -> put (output arguments) =<< diffFiles parser split sources diff --git a/src/Renderer/Patch.hs b/src/Renderer/Patch.hs index 6cba19849..44a7ebc7d 100644 --- a/src/Renderer/Patch.hs +++ b/src/Renderer/Patch.hs @@ -113,6 +113,7 @@ header blobs = intercalate "\n" [filepathHeader, fileModeHeader, beforeFilepath, (oidA, oidB) = runBoth $ oid <$> blobs (modeA, modeB) = runBoth $ blobKind <$> blobs +-- | A hunk representing no changes. emptyHunk :: Hunk (SplitDiff a Info) emptyHunk = Hunk { offset = mempty, changes = [], trailingContext = [] } From a5537091125ba408d2d6d908d33e9d84aafff1f6 Mon Sep 17 00:00:00 2001 From: joshvera Date: Mon, 4 Apr 2016 17:20:26 -0400 Subject: [PATCH 12/13] Specialize Renderer to Text --- src/Diffing.hs | 2 +- src/Renderer.hs | 3 ++- src/Renderer/JSON.hs | 2 +- src/Renderer/Patch.hs | 4 ++-- src/Renderer/Split.hs | 2 +- test/CorpusSpec.hs | 30 +++++++++++++----------------- 6 files changed, 20 insertions(+), 23 deletions(-) diff --git a/src/Diffing.hs b/src/Diffing.hs index 6e9fd0e69..a3440dbd6 100644 --- a/src/Diffing.hs +++ b/src/Diffing.hs @@ -72,7 +72,7 @@ readAndTranscodeFile path = do -- | result. -- | Returns the rendered result strictly, so it's always fully evaluated -- | with respect to other IO actions. -diffFiles :: Parser -> Renderer T.Text b -> Both SourceBlob -> IO b +diffFiles :: Parser -> Renderer T.Text -> Both SourceBlob -> IO T.Text diffFiles parser renderer sourceBlobs = do let sources = source <$> sourceBlobs terms <- sequence $ parser <$> sources diff --git a/src/Renderer.hs b/src/Renderer.hs index 35f1f5f43..740e1a236 100644 --- a/src/Renderer.hs +++ b/src/Renderer.hs @@ -4,9 +4,10 @@ import Data.Functor.Both import Diff import Info import Source +import Data.Text -- | 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 } diff --git a/src/Renderer/JSON.hs b/src/Renderer/JSON.hs index 42500aec6..1cf8ca78f 100644 --- a/src/Renderer/JSON.hs +++ b/src/Renderer/JSON.hs @@ -28,7 +28,7 @@ import Syntax import Term -- | Render a diff to a string representing its JSON. -json :: Renderer a Text +json :: Renderer a json diff sources = toStrict . toLazyText . encodeToTextBuilder $ object ["rows" .= annotateRows (splitDiffByLines (source <$> sources) diff), "oids" .= (oid <$> sources), "paths" .= (path <$> sources)] where annotateRows = fmap (fmap NumberedLine) . numberedRows diff --git a/src/Renderer/Patch.hs b/src/Renderer/Patch.hs index 44a7ebc7d..972bfe557 100644 --- a/src/Renderer/Patch.hs +++ b/src/Renderer/Patch.hs @@ -28,7 +28,7 @@ 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. -patch :: Renderer a Text +patch :: Renderer a patch diff blobs = pack $ case getLast (foldMap (Last . Just) string) of Just c | c /= '\n' -> string ++ "\n\\ No newline at end of file\n" _ -> string @@ -118,7 +118,7 @@ emptyHunk :: Hunk (SplitDiff a Info) emptyHunk = Hunk { offset = mempty, changes = [], trailingContext = [] } -- | 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 , sourcesEqual <- runBothWith (==) sources , sourcesNull <- runBothWith (&&) (null <$> sources) diff --git a/src/Renderer/Split.hs b/src/Renderer/Split.hs index b98934a3a..d9a9ae7cb 100644 --- a/src/Renderer/Split.hs +++ b/src/Renderer/Split.hs @@ -53,7 +53,7 @@ splitPatchToClassName patch = stringValue $ "patch " ++ case patch of SplitReplace _ -> "replace" -- | Render a diff as an HTML split diff. -split :: Renderer leaf T.Text +split :: Renderer leaf split diff blobs = TL.toStrict . renderHtml . docTypeHtml . ((head $ link ! A.rel "stylesheet" ! A.href "style.css") <>) diff --git a/test/CorpusSpec.hs b/test/CorpusSpec.hs index cd1bb688f..f201ce097 100644 --- a/test/CorpusSpec.hs +++ b/test/CorpusSpec.hs @@ -34,23 +34,23 @@ spec = parallel $ do examples "test/diffs/" `shouldNotReturn` [] where - runTestsIn :: String -> (String -> String -> Expectation) -> SpecWith () + runTestsIn :: String -> (T.Text -> T.Text -> Expectation) -> SpecWith () runTestsIn directory matcher = do paths <- runIO $ examples directory let tests = correctTests =<< paths 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 = 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", testPatch, paths, patch), ("split", testSplit, paths, split) ] - testPatch :: Renderer a String - testPatch diff sources = T.unpack $ P.patch diff sources - testSplit :: Renderer a String - testSplit diff sources = T.unpack $ Split.split diff sources - testJSON :: Renderer a String - testJSON diff sources = T.unpack $ J.json diff sources + testPatch :: Renderer a + testPatch diff sources = P.patch diff sources + testSplit :: Renderer a + testSplit diff sources = Split.split diff sources + testJSON :: Renderer a + testJSON diff sources = J.json diff sources -- | Return all the examples from the given directory. Examples are expected to @@ -77,18 +77,14 @@ normalizeName path = addExtension (dropExtension $ dropExtension path) (takeExte -- | 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 -- | 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 sources <- sequence $ readAndTranscodeFile <$> paths - actual <- diffFiles parser renderer sourceBlobs + actual <- diffFiles parser renderer (sourceBlobs sources) case diff of Nothing -> matcher actual actual Just file -> do - expected <- readFile file + expected <- T.pack <$> readFile file matcher actual expected where parser = parserForFilepath (fst paths) - sourceBlobs = Both (S.SourceBlob, S.SourceBlob) <*> - sources <*> - pure mempty <*> - paths <*> - pure (Just S.defaultPlainBlob) + sourceBlobs sources = Both (S.SourceBlob, S.SourceBlob) <*> sources <*> pure mempty <*> paths <*> pure (Just S.defaultPlainBlob) From 928087e1f5341df9a7fe228afe20c3a95efdc4a6 Mon Sep 17 00:00:00 2001 From: joshvera Date: Mon, 4 Apr 2016 17:38:41 -0400 Subject: [PATCH 13/13] :fire: --- test/CorpusSpec.hs | 9 +-------- 1 file changed, 1 insertion(+), 8 deletions(-) diff --git a/test/CorpusSpec.hs b/test/CorpusSpec.hs index f201ce097..2ddc22a61 100644 --- a/test/CorpusSpec.hs +++ b/test/CorpusSpec.hs @@ -44,14 +44,7 @@ spec = parallel $ do correctTests paths@(_, Nothing, Nothing, Nothing) = testsForPaths paths correctTests paths = List.filter (\(_, _, _, output) -> isJust output) $ testsForPaths paths 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", testPatch, paths, patch), ("split", testSplit, paths, split) ] - testPatch :: Renderer a - testPatch diff sources = P.patch diff sources - testSplit :: Renderer a - testSplit diff sources = Split.split diff sources - testJSON :: Renderer a - testJSON diff sources = J.json diff sources - + testsForPaths (paths, json, patch, split) = [ ("json", J.json, paths, json), ("patch", P.patch, paths, patch), ("split", Split.split, paths, split) ] -- | 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