From d0a3c517a94843f56a32c799930dfaece7af2ec2 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 26 Jan 2016 16:25:40 -0500 Subject: [PATCH 01/14] Pass around source blobs with oid info --- app/DiffOutput.hs | 2 +- app/Main.hs | 3 ++- app/SemanticDiff.hs | 29 ++++++++++++++++++----------- src/PatchOutput.hs | 5 ++++- src/Renderer.hs | 2 +- src/Source.hs | 2 ++ src/Split.hs | 4 +++- src/Unified.hs | 6 ++++-- 8 files changed, 35 insertions(+), 18 deletions(-) diff --git a/app/DiffOutput.hs b/app/DiffOutput.hs index baf5a98b7..9c5a45619 100644 --- a/app/DiffOutput.hs +++ b/app/DiffOutput.hs @@ -49,7 +49,7 @@ readAndTranscodeFile path = do text <- B1.readFile path transcode text -printDiff :: DiffArguments -> (Source Char, Source Char) -> (Term T.Text Info, Term T.Text Info) -> IO () +printDiff :: DiffArguments -> (SourceBlob, SourceBlob) -> (Term T.Text Info, Term T.Text Info) -> IO () printDiff arguments (aSource, bSource) (aTerm, bTerm) = case format arguments of Unified -> do rendered <- unified diff (aSource, bSource) diff --git a/app/Main.hs b/app/Main.hs index e2296d8e3..9120e7a6b 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -44,7 +44,8 @@ main = do let parse = DO.parserForFilepath sourceAPath terms <- sequence $ parse <$> sources let replaceLeaves = DO.breakDownLeavesByWord <$> sources - DO.printDiff (args arguments) (runJoin sources) (runJoin $ replaceLeaves <*> terms) + let sourceBlobs = runJoin $ (\s -> SourceBlob s T.empty) <$> sources + DO.printDiff (args arguments) sourceBlobs (runJoin $ replaceLeaves <*> terms) where opts = info (helper <*> arguments) (fullDesc <> progDesc "Diff some things" <> header "semantic-diff - diff semantically") args Arguments{..} = DO.DiffArguments { format = format, output = output, outputPath = sourceA } diff --git a/app/SemanticDiff.hs b/app/SemanticDiff.hs index d7768a208..9d33624c5 100644 --- a/app/SemanticDiff.hs +++ b/app/SemanticDiff.hs @@ -7,6 +7,9 @@ import Source import Options.Applicative import qualified Data.ByteString.Char8 as B1 import qualified Data.Text as T +import Control.Monad +import Control.Arrow +import Data.Bifunctor import Data.Bifunctor.Join import Git.Libgit2 import Git.Types @@ -36,18 +39,20 @@ main = do arguments@Arguments{..} <- execParser opts let shas = Join (shaA, shaB) forM_ filepaths $ \filepath -> do - sources <- sequence $ fetchFromGitRepo gitDir filepath <$> shas + sourcesAndOids <- sequence $ fetchFromGitRepo gitDir filepath <$> shas + let (sources, oids)= (Join . join bimap fst $ runJoin sourcesAndOids, join bimap snd $ runJoin sourcesAndOids) let parse = DO.parserForFilepath filepath terms <- sequence $ parse <$> sources let replaceLeaves = DO.breakDownLeavesByWord <$> sources - DO.printDiff (args arguments filepath) (runJoin sources) (runJoin $ replaceLeaves <*> terms) + let sourceBlobs = ((SourceBlob (fst $ runJoin sources) *** SourceBlob (snd $ runJoin sources)) oids) + DO.printDiff (args arguments filepath) sourceBlobs (runJoin $ replaceLeaves <*> terms) where opts = info (helper <*> arguments) (fullDesc <> progDesc "Diff some things" <> header "semantic-diff - diff semantically") args Arguments{..} filepath = DO.DiffArguments { format = format, output = output, outputPath = filepath } -- | Returns a file source given an absolute repo path, a relative file path, and the sha to look up. -fetchFromGitRepo :: FilePath -> FilePath -> String -> IO (Source Char) -fetchFromGitRepo repoPath path sha = join $ withRepository lgFactory repoPath $ do +fetchFromGitRepo :: FilePath -> FilePath -> String -> IO (Source Char, T.Text) +fetchFromGitRepo repoPath path sha = withRepository lgFactory repoPath $ do object <- unTagged <$> parseObjOid (T.pack sha) commitIHope <- lookupObject object commit <- case commitIHope of @@ -55,10 +60,12 @@ fetchFromGitRepo repoPath path sha = join $ withRepository lgFactory repoPath $ _ -> error "Expected commit SHA" tree <- lookupTree (commitTree commit) entry <- treeEntry tree (B1.pack path) - bytestring <- case entry of - Nothing -> return mempty - Just BlobEntry {..} -> do - blob <- lookupBlob blobEntryOid - let (BlobString s) = blobContents blob - return s - return $ DO.transcode bytestring + (bytestring, oid) <- case entry of + Nothing -> return (mempty, mempty) + Just BlobEntry {..} -> do + blob <- lookupBlob blobEntryOid + let (BlobString s) = blobContents blob + let oid = renderObjOid $ blobOid blob + return (s, oid) + s <- liftIO $ DO.transcode bytestring + return (s, oid) diff --git a/src/PatchOutput.hs b/src/PatchOutput.hs index 7f08f3854..ebf47202e 100644 --- a/src/PatchOutput.hs +++ b/src/PatchOutput.hs @@ -17,7 +17,10 @@ import Data.Maybe import Data.Monoid patch :: Renderer a String -patch diff (sourceA, sourceB) = mconcat $ showHunk (sourceA, sourceB) <$> hunks diff (sourceA, sourceB) +patch diff (beforeBlob, afterBlob) = mconcat $ showHunk (before, after) <$> hunks diff (before, after) + where + before = source beforeBlob + after = source afterBlob data Hunk a = Hunk { offset :: (Sum Int, Sum Int), changes :: [Change a], trailingContext :: [Row a] } deriving (Eq, Show) diff --git a/src/Renderer.hs b/src/Renderer.hs index e2a026b54..df4bcce0a 100644 --- a/src/Renderer.hs +++ b/src/Renderer.hs @@ -4,4 +4,4 @@ import Diff import Source -- | A function that will render a diff, given the two source files. -type Renderer a b = Diff a Info -> (Source Char, Source Char) -> b +type Renderer a b = Diff a Info -> (SourceBlob, SourceBlob) -> b diff --git a/src/Source.hs b/src/Source.hs index 6ad1dbbdf..d6f113a06 100644 --- a/src/Source.hs +++ b/src/Source.hs @@ -5,6 +5,8 @@ import Range import qualified Data.Vector as Vector import qualified Data.Text as T +data SourceBlob = SourceBlob { source :: Source Char, oid :: T.Text } + -- | The contents of a source file, backed by a vector for efficient slicing. newtype Source a = Source { getVector :: Vector.Vector a } deriving (Eq, Show, Functor, Foldable, Traversable) diff --git a/src/Split.hs b/src/Split.hs index 7521c27da..4f3bb0205 100644 --- a/src/Split.hs +++ b/src/Split.hs @@ -32,7 +32,7 @@ classifyMarkup :: Foldable f => f String -> Markup -> Markup classifyMarkup categories element = maybe element ((element !) . A.class_ . stringValue . ("category-" ++)) $ maybeFirst categories split :: Renderer leaf (IO TL.Text) -split diff (before, after) = return . renderHtml +split diff (beforeBlob, afterBlob) = return . renderHtml . docTypeHtml . ((head $ link ! A.rel "stylesheet" ! A.href "style.css") <>) . body @@ -40,6 +40,8 @@ split diff (before, after) = return . renderHtml ((colgroup $ (col ! A.width (stringValue . show $ columnWidth)) <> col <> (col ! A.width (stringValue . show $ columnWidth)) <> col) <>) . mconcat $ numberedLinesToMarkup <$> reverse numbered where + before = Source.source beforeBlob + after = Source.source afterBlob rows = fst (splitDiffByLines diff (0, 0) (before, after)) numbered = foldl' numberRows [] rows maxNumber = case numbered of diff --git a/src/Unified.hs b/src/Unified.hs index 104b6b9a6..0689feb4a 100644 --- a/src/Unified.hs +++ b/src/Unified.hs @@ -15,11 +15,11 @@ import qualified Data.OrderedMap as Map import Rainbow unified :: Renderer a (IO ByteString) -unified diff (before, after) = do +unified diff (beforeBlob, afterBlob) = do renderer <- byteStringMakerFromEnvironment return . mconcat . chunksToByteStrings renderer . fst $ iter g mapped where mapped = fmap (unifiedPatch &&& range) diff - g (Annotated (_, info) syntax) = annotationAndSyntaxToChunks after info syntax + g (Annotated (_, info) syntax) = annotationAndSyntaxToChunks (source afterBlob) info syntax annotationAndSyntaxToChunks source (Info range _) (Leaf _) = (pure . chunk . toList $ slice range source, Just range) annotationAndSyntaxToChunks source (Info range _) (Indexed i) = (unifiedRange range i source, Just range) annotationAndSyntaxToChunks source (Info range _) (Fixed f) = (unifiedRange range f source, Just range) @@ -27,6 +27,8 @@ unified diff (before, after) = do unifiedPatch :: Patch (Term a Info) -> [Chunk String] unifiedPatch patch = (fore red . bold <$> beforeChunk) <> (fore green . bold <$> afterChunk) where + before = source beforeBlob + after = source afterBlob beforeChunk = maybe [] (change "-" . unifiedTerm before) $ Patch.before patch afterChunk = maybe [] (change "+" . unifiedTerm after) $ Patch.after patch From 8c7d82b3634533afcdee89f8efe7922a26091e44 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 26 Jan 2016 16:46:27 -0500 Subject: [PATCH 02/14] store strings in SourceBlob --- app/Main.hs | 2 +- app/SemanticDiff.hs | 4 ++-- src/PatchOutput.hs | 7 ++++--- src/Source.hs | 2 +- 4 files changed, 8 insertions(+), 7 deletions(-) diff --git a/app/Main.hs b/app/Main.hs index 9120e7a6b..5c472eb93 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -44,7 +44,7 @@ main = do let parse = DO.parserForFilepath sourceAPath terms <- sequence $ parse <$> sources let replaceLeaves = DO.breakDownLeavesByWord <$> sources - let sourceBlobs = runJoin $ (\s -> SourceBlob s T.empty) <$> sources + let sourceBlobs = runJoin $ (\s -> SourceBlob s mempty) <$> sources DO.printDiff (args arguments) sourceBlobs (runJoin $ replaceLeaves <*> terms) where opts = info (helper <*> arguments) (fullDesc <> progDesc "Diff some things" <> header "semantic-diff - diff semantically") diff --git a/app/SemanticDiff.hs b/app/SemanticDiff.hs index 9d33624c5..48f888095 100644 --- a/app/SemanticDiff.hs +++ b/app/SemanticDiff.hs @@ -51,7 +51,7 @@ main = do args Arguments{..} filepath = DO.DiffArguments { format = format, output = output, outputPath = filepath } -- | Returns a file source given an absolute repo path, a relative file path, and the sha to look up. -fetchFromGitRepo :: FilePath -> FilePath -> String -> IO (Source Char, T.Text) +fetchFromGitRepo :: FilePath -> FilePath -> String -> IO (Source Char, String) fetchFromGitRepo repoPath path sha = withRepository lgFactory repoPath $ do object <- unTagged <$> parseObjOid (T.pack sha) commitIHope <- lookupObject object @@ -68,4 +68,4 @@ fetchFromGitRepo repoPath path sha = withRepository lgFactory repoPath $ do let oid = renderObjOid $ blobOid blob return (s, oid) s <- liftIO $ DO.transcode bytestring - return (s, oid) + return (s, T.unpack oid) diff --git a/src/PatchOutput.hs b/src/PatchOutput.hs index ebf47202e..ffdd1ac89 100644 --- a/src/PatchOutput.hs +++ b/src/PatchOutput.hs @@ -17,7 +17,7 @@ import Data.Maybe import Data.Monoid patch :: Renderer a String -patch diff (beforeBlob, afterBlob) = mconcat $ showHunk (before, after) <$> hunks diff (before, after) +patch diff (beforeBlob, afterBlob) = mconcat $ showHunk (beforeBlob, afterBlob) <$> hunks diff (before, after) where before = source beforeBlob after = source afterBlob @@ -41,8 +41,9 @@ lineLength :: Line a -> Sum Int lineLength EmptyLine = 0 lineLength _ = 1 -showHunk :: (Source Char, Source Char) -> Hunk (SplitDiff a Info) -> String -showHunk sources hunk = header hunk ++ concat (showChange sources <$> changes hunk) ++ showLines (snd sources) ' ' (unRight <$> trailingContext hunk) +showHunk :: (SourceBlob, SourceBlob) -> Hunk (SplitDiff a Info) -> String +showHunk blobs@(beforeBlob, afterBlob) hunk = header blobs hunk ++ concat (showChange sources <$> changes hunk) ++ showLines (snd sources) ' ' (unRight <$> trailingContext hunk) + where sources = (source beforeBlob, source afterBlob) showChange :: (Source Char, Source Char) -> Change (SplitDiff a Info) -> String showChange sources change = showLines (snd sources) ' ' (unRight <$> context change) ++ showLines (fst sources) '-' (unLeft <$> contents change) ++ showLines (snd sources) '+' (unRight <$> contents change) diff --git a/src/Source.hs b/src/Source.hs index d6f113a06..77395ba7c 100644 --- a/src/Source.hs +++ b/src/Source.hs @@ -5,7 +5,7 @@ import Range import qualified Data.Vector as Vector import qualified Data.Text as T -data SourceBlob = SourceBlob { source :: Source Char, oid :: T.Text } +data SourceBlob = SourceBlob { source :: Source Char, oid :: String } -- | The contents of a source file, backed by a vector for efficient slicing. newtype Source a = Source { getVector :: Vector.Vector a } From 459331fbf79fcb61568fd51ef47f4e5eadc663b0 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 26 Jan 2016 16:46:39 -0500 Subject: [PATCH 03/14] print the index string in headers --- src/PatchOutput.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/src/PatchOutput.hs b/src/PatchOutput.hs index ffdd1ac89..7467d7282 100644 --- a/src/PatchOutput.hs +++ b/src/PatchOutput.hs @@ -59,8 +59,9 @@ getRange :: SplitDiff leaf Info -> Range getRange (Free (Annotated (Info range _) _)) = range getRange (Pure (Info range _ :< _)) = range -header :: Hunk a -> String -header hunk = "@@ -" ++ show offsetA ++ "," ++ show lengthA ++ " +" ++ show offsetB ++ "," ++ show lengthB ++ " @@\n" +header :: (SourceBlob, SourceBlob) -> Hunk a -> String +header blobs hunk = "@@ -" ++ show offsetA ++ "," ++ show lengthA ++ " +" ++ show offsetB ++ "," ++ show lengthB ++ " @@\n" ++ + "index " ++ oid (fst blobs) ++ " " ++ oid (snd blobs) ++ "\n" where (lengthA, lengthB) = getSum *** getSum $ hunkLength hunk (offsetA, offsetB) = getSum *** getSum $ offset hunk From 495be107f9dddf34bfbc4b4f5e342c90717dd8bc Mon Sep 17 00:00:00 2001 From: joshvera Date: Wed, 27 Jan 2016 11:57:31 -0500 Subject: [PATCH 04/14] move index header to top --- src/PatchOutput.hs | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/src/PatchOutput.hs b/src/PatchOutput.hs index 7467d7282..780092d50 100644 --- a/src/PatchOutput.hs +++ b/src/PatchOutput.hs @@ -60,8 +60,8 @@ getRange (Free (Annotated (Info range _) _)) = range getRange (Pure (Info range _ :< _)) = range header :: (SourceBlob, SourceBlob) -> Hunk a -> String -header blobs hunk = "@@ -" ++ show offsetA ++ "," ++ show lengthA ++ " +" ++ show offsetB ++ "," ++ show lengthB ++ " @@\n" ++ - "index " ++ oid (fst blobs) ++ " " ++ oid (snd blobs) ++ "\n" +header blobs hunk = "index " ++ oid (fst blobs) ++ " " ++ oid (snd blobs) ++ "\n" ++ + "@@ -" ++ show offsetA ++ "," ++ show lengthA ++ " +" ++ show offsetB ++ "," ++ show lengthB ++ " @@\n" where (lengthA, lengthB) = getSum *** getSum $ hunkLength hunk (offsetA, offsetB) = getSum *** getSum $ offset hunk From 03dcb2c49353437249686fd770c648497d961588 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 2 Feb 2016 19:25:12 -0500 Subject: [PATCH 05/14] ++gitlib --- vendor/gitlib | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/gitlib b/vendor/gitlib index b0c3ad9a7..758d8c85f 160000 --- a/vendor/gitlib +++ b/vendor/gitlib @@ -1 +1 @@ -Subproject commit b0c3ad9a7d453fce30364b4a277799c5e2f26947 +Subproject commit 758d8c85f613dfda517cb9113ad4fc221f1fb3c0 From 2b1b8f5d8c6c2ab278eb7928b96e4da8f30cfa2e Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 2 Feb 2016 19:27:03 -0500 Subject: [PATCH 06/14] update gitmodule pin --- .gitmodules | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/.gitmodules b/.gitmodules index 93c54aaee..a099eb42c 100644 --- a/.gitmodules +++ b/.gitmodules @@ -6,4 +6,4 @@ url = https://github.com/joshvera/text-icu [submodule "vendor/gitlib"] path = vendor/gitlib - url = https://github.com/jwiegley/gitlib + url = https://github.com/joshvera/gitlib From db6ff986ffe25ce30551eadd49dd5a32c540fad5 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 2 Feb 2016 19:30:39 -0500 Subject: [PATCH 07/14] ++gitlib --- vendor/gitlib | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/gitlib b/vendor/gitlib index 758d8c85f..266e40052 160000 --- a/vendor/gitlib +++ b/vendor/gitlib @@ -1 +1 @@ -Subproject commit 758d8c85f613dfda517cb9113ad4fc221f1fb3c0 +Subproject commit 266e400528614eddef4f0e1608289d86cce065d5 From 9fd35e2a37a1b318471b67f27f0f5e305c1481c9 Mon Sep 17 00:00:00 2001 From: joshvera Date: Tue, 2 Feb 2016 19:39:28 -0500 Subject: [PATCH 08/14] ++gitlib --- vendor/gitlib | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/vendor/gitlib b/vendor/gitlib index 266e40052..3b65d9f22 160000 --- a/vendor/gitlib +++ b/vendor/gitlib @@ -1 +1 @@ -Subproject commit 266e400528614eddef4f0e1608289d86cce065d5 +Subproject commit 3b65d9f22ef4a1bc14c3b1d35d819ef9d29878b1 From acceaab0565155f06f6c8cb4f1da1da560650e45 Mon Sep 17 00:00:00 2001 From: joshvera Date: Thu, 4 Feb 2016 17:58:01 -0500 Subject: [PATCH 09/14] stub top header --- src/PatchOutput.hs | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/src/PatchOutput.hs b/src/PatchOutput.hs index 7f08f3854..45136e814 100644 --- a/src/PatchOutput.hs +++ b/src/PatchOutput.hs @@ -10,11 +10,12 @@ import Renderer import Row import Source hiding ((++), break) import Split -import Control.Arrow import Control.Comonad.Cofree import Control.Monad.Free import Data.Maybe import Data.Monoid +import Control.Monad +import Data.Bifunctor patch :: Renderer a String patch diff (sourceA, sourceB) = mconcat $ showHunk (sourceA, sourceB) <$> hunks diff (sourceA, sourceB) @@ -56,9 +57,10 @@ getRange (Free (Annotated (Info range _) _)) = range getRange (Pure (Info range _ :< _)) = range header :: Hunk a -> String -header hunk = "@@ -" ++ show offsetA ++ "," ++ show lengthA ++ " +" ++ show offsetB ++ "," ++ show lengthB ++ " @@\n" - where (lengthA, lengthB) = getSum *** getSum $ hunkLength hunk - (offsetA, offsetB) = getSum *** getSum $ offset hunk +header hunk = "diff --git a/path.txt b/path.txt\n" ++ + "@@ -" ++ show offsetA ++ "," ++ show lengthA ++ " +" ++ show offsetB ++ "," ++ show lengthB ++ " @@\n" + where (lengthA, lengthB) = join bimap getSum $ hunkLength hunk + (offsetA, offsetB) = join bimap getSum $ offset hunk hunks :: Diff a Info -> (Source Char, Source Char) -> [Hunk (SplitDiff a Info)] hunks diff sources = hunksInRows (1, 1) . fst $ splitDiffByLines diff (0, 0) sources From 44578211ffdca21418d493c45c2f5598e4079b31 Mon Sep 17 00:00:00 2001 From: joshvera Date: Wed, 10 Feb 2016 10:57:41 -0800 Subject: [PATCH 10/14] add some dots --- src/PatchOutput.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/PatchOutput.hs b/src/PatchOutput.hs index db7777ac4..759f1f4ce 100644 --- a/src/PatchOutput.hs +++ b/src/PatchOutput.hs @@ -70,7 +70,7 @@ getRange (Pure (Info range _ :< _)) = range header :: (SourceBlob, SourceBlob) -> Hunk a -> String header blobs hunk = "diff --git a/path.txt b/path.txt\n" ++ - "index " ++ oid (fst blobs) ++ " " ++ oid (snd blobs) ++ "\n" ++ + "index " ++ oid (fst blobs) ++ ".." ++ oid (snd blobs) ++ "\n" ++ "@@ -" ++ show offsetA ++ "," ++ show lengthA ++ " +" ++ show offsetB ++ "," ++ show lengthB ++ " @@\n" where (lengthA, lengthB) = join bimap getSum $ hunkLength hunk (offsetA, offsetB) = join bimap getSum $ offset hunk From e008fda7d1bea701b6e8d40663d9f016231718d6 Mon Sep 17 00:00:00 2001 From: joshvera Date: Wed, 10 Feb 2016 11:32:26 -0800 Subject: [PATCH 11/14] output the right paths in patch --- app/Main.hs | 3 ++- app/SemanticDiff.hs | 2 +- src/PatchOutput.hs | 2 +- src/Source.hs | 2 +- test/PatchOutputSpec.hs | 6 +++--- 5 files changed, 8 insertions(+), 7 deletions(-) diff --git a/app/Main.hs b/app/Main.hs index 3b94b6410..fb9a4caa9 100644 --- a/app/Main.hs +++ b/app/Main.hs @@ -26,7 +26,8 @@ main = do let parse = DO.parserForFilepath sourceAPath terms <- sequence $ parse <$> sources let replaceLeaves = DO.breakDownLeavesByWord <$> sources - let sourceBlobs = runJoin $ (\s -> SourceBlob s mempty) <$> sources + let srcs = runJoin sources + let sourceBlobs = (SourceBlob (fst srcs) mempty sourceAPath, SourceBlob (snd srcs) mempty sourceBPath) DO.printDiff (args arguments) (uncurry diffTerms . runJoin $ replaceLeaves <*> terms) sourceBlobs where opts = info (helper <*> arguments) (fullDesc <> progDesc "Diff some things" <> header "semantic-diff - diff semantically") diff --git a/app/SemanticDiff.hs b/app/SemanticDiff.hs index 3ebd68366..709b412c3 100644 --- a/app/SemanticDiff.hs +++ b/app/SemanticDiff.hs @@ -43,7 +43,7 @@ main = do let parse = DO.parserForFilepath filepath terms <- sequence $ parse <$> sources let replaceLeaves = DO.breakDownLeavesByWord <$> sources - let sourceBlobs = ((SourceBlob (fst $ runJoin sources) *** SourceBlob (snd $ runJoin sources)) oids) + let sourceBlobs = (SourceBlob (fst $ runJoin sources) (fst oids) filepath, SourceBlob (snd $ runJoin sources) (snd oids) filepath) DO.printDiff (args arguments filepath) (uncurry diffTerms . runJoin $ replaceLeaves <*> terms) sourceBlobs where opts = info (helper <*> arguments) (fullDesc <> progDesc "Diff some things" <> header "semantic-diff - diff semantically") diff --git a/src/PatchOutput.hs b/src/PatchOutput.hs index 759f1f4ce..12f1676b1 100644 --- a/src/PatchOutput.hs +++ b/src/PatchOutput.hs @@ -69,7 +69,7 @@ getRange (Free (Annotated (Info range _) _)) = range getRange (Pure (Info range _ :< _)) = range header :: (SourceBlob, SourceBlob) -> Hunk a -> String -header blobs hunk = "diff --git a/path.txt b/path.txt\n" ++ +header blobs hunk = "diff --git a/" ++ path (fst blobs) ++ " b/" ++ path (snd blobs) ++ "\n" ++ "index " ++ oid (fst blobs) ++ ".." ++ oid (snd blobs) ++ "\n" ++ "@@ -" ++ show offsetA ++ "," ++ show lengthA ++ " +" ++ show offsetB ++ "," ++ show lengthB ++ " @@\n" where (lengthA, lengthB) = join bimap getSum $ hunkLength hunk diff --git a/src/Source.hs b/src/Source.hs index 77395ba7c..0ca76a40c 100644 --- a/src/Source.hs +++ b/src/Source.hs @@ -5,7 +5,7 @@ import Range import qualified Data.Vector as Vector import qualified Data.Text as T -data SourceBlob = SourceBlob { source :: Source Char, oid :: String } +data SourceBlob = SourceBlob { source :: Source Char, oid :: String, path :: FilePath } -- | The contents of a source file, backed by a vector for efficient slicing. newtype Source a = Source { getVector :: Vector.Vector a } diff --git a/test/PatchOutputSpec.hs b/test/PatchOutputSpec.hs index 3b526046f..ab756f267 100644 --- a/test/PatchOutputSpec.hs +++ b/test/PatchOutputSpec.hs @@ -9,7 +9,7 @@ import Control.Monad.Free import Test.Hspec spec :: Spec -spec = parallel $ do - describe "hunks" $ do +spec = parallel $ + describe "hunks" $ it "empty diffs have no hunks" $ - hunks (Free . Annotated (Info (Range 0 0) mempty, Info (Range 0 0) mempty) $ Leaf "") (fromList "", fromList "") `shouldBe` [] + hunks (Free . Annotated (Info (Range 0 0) mempty, Info (Range 0 0) mempty) $ Leaf "") (SourceBlob (fromList "") "abcde" "path2.txt", SourceBlob (fromList "") "xyz" "path2.txt") `shouldBe` [] From 4e280260194557bbfae0ad60cd3a7ce193d4599e Mon Sep 17 00:00:00 2001 From: joshvera Date: Mon, 22 Feb 2016 13:40:08 -0700 Subject: [PATCH 12/14] remove diff --- app/DiffOutput.hs | 12 ------------ 1 file changed, 12 deletions(-) diff --git a/app/DiffOutput.hs b/app/DiffOutput.hs index de6abc172..4f229f598 100644 --- a/app/DiffOutput.hs +++ b/app/DiffOutput.hs @@ -51,7 +51,6 @@ readAndTranscodeFile path = do text <- B1.readFile path transcode text --- <<<<<<< HEAD -- | Return a renderer from the command-line arguments that will print the diff. printDiff :: DiffArguments -> Renderer T.Text (IO ()) printDiff arguments diff sources = case format arguments of @@ -64,17 +63,6 @@ printDiff arguments diff sources = case format arguments of where put Nothing rendered = TextIO.putStr rendered put (Just path) rendered = do --- ======= --- printDiff :: DiffArguments -> (SourceBlob, SourceBlob) -> (Term T.Text Info, Term T.Text Info) -> IO () --- printDiff arguments (aSource, bSource) (aTerm, bTerm) = case format arguments of --- Unified -> do --- rendered <- unified diff (aSource, bSource) --- B1.putStr rendered --- Split -> do --- rendered <- split diff (aSource, bSource) --- case output arguments of --- Just path -> do --- >>>>>>> source-blobs isDir <- doesDirectoryExist path let outputPath = if isDir then path (takeFileName outputPath -<.> ".html") From 35355a2e918c8b7d10e3648f49a93eeaad007a7b Mon Sep 17 00:00:00 2001 From: joshvera Date: Mon, 22 Feb 2016 14:04:39 -0700 Subject: [PATCH 13/14] Expect diff headers --- test/CorpusSpec.hs | 5 ++++- test/diffs/newline-at-eof.patch.js | 2 ++ test/diffs/no-newline-at-eof.patch.js | 2 ++ 3 files changed, 8 insertions(+), 1 deletion(-) diff --git a/test/CorpusSpec.hs b/test/CorpusSpec.hs index 74a65a7a7..afbeaa133 100644 --- a/test/CorpusSpec.hs +++ b/test/CorpusSpec.hs @@ -6,6 +6,7 @@ import Renderer import Split import Unified +import qualified Source as S import Control.DeepSeq import Data.Bifunctor.Join import qualified Data.ByteString.Char8 as B1 @@ -78,7 +79,9 @@ testDiff :: Renderer T.Text String -> FilePath -> FilePath -> Maybe FilePath -> testDiff renderer a b diff matcher = do let parser = parserForFilepath a sources <- sequence $ readAndTranscodeFile <$> Join (a, b) - actual <- diffFiles parser renderer (runJoin sources) + let srcs = runJoin sources + let sourceBlobs = (S.SourceBlob (fst srcs) mempty a, S.SourceBlob (snd srcs) mempty b) + actual <- diffFiles parser renderer sourceBlobs case diff of Nothing -> actual `deepseq` matcher (actual, actual) Just file -> do diff --git a/test/diffs/newline-at-eof.patch.js b/test/diffs/newline-at-eof.patch.js index 7d55f1c9c..ac6e41909 100644 --- a/test/diffs/newline-at-eof.patch.js +++ b/test/diffs/newline-at-eof.patch.js @@ -1,3 +1,5 @@ +diff --git a/test/diffs/newline-at-eof.A.js b/test/diffs/newline-at-eof.B.js +index .. @@ -1,2 +1,4 @@ console.log("hello, world"); diff --git a/test/diffs/no-newline-at-eof.patch.js b/test/diffs/no-newline-at-eof.patch.js index 87842a5c6..87f324855 100644 --- a/test/diffs/no-newline-at-eof.patch.js +++ b/test/diffs/no-newline-at-eof.patch.js @@ -1,3 +1,5 @@ +diff --git a/test/diffs/no-newline-at-eof.A.js b/test/diffs/no-newline-at-eof.B.js +index .. @@ -1,1 +1,3 @@ console.log("hello, world"); From 46f0b002109185dfd26f2317fe961b059877a5d0 Mon Sep 17 00:00:00 2001 From: joshvera Date: Mon, 22 Feb 2016 16:13:27 -0700 Subject: [PATCH 14/14] add docs back --- src/PatchOutput.hs | 2 ++ 1 file changed, 2 insertions(+) diff --git a/src/PatchOutput.hs b/src/PatchOutput.hs index e0a107657..9edb3f651 100644 --- a/src/PatchOutput.hs +++ b/src/PatchOutput.hs @@ -46,6 +46,7 @@ lineLength :: Line a -> Sum Int lineLength EmptyLine = 0 lineLength _ = 1 +-- | Given the before and after sources, render a hunk to a string. showHunk :: (SourceBlob, SourceBlob) -> Hunk (SplitDiff a Info) -> String showHunk blobs@(beforeBlob, afterBlob) hunk = header blobs hunk ++ concat (showChange sources <$> changes hunk) ++ showLines (snd sources) ' ' (unRight <$> trailingContext hunk) where sources = (source beforeBlob, source afterBlob) @@ -70,6 +71,7 @@ getRange :: SplitDiff leaf Info -> Range getRange (Free (Annotated (Info range _) _)) = range getRange (Pure (Info range _ :< _)) = range +-- | Returns the header given two source blobs and a hunk. header :: (SourceBlob, SourceBlob) -> Hunk a -> String header blobs hunk = "diff --git a/" ++ path (fst blobs) ++ " b/" ++ path (snd blobs) ++ "\n" ++ "index " ++ oid (fst blobs) ++ ".." ++ oid (snd blobs) ++ "\n" ++