2016-02-25 23:20:25 +03:00
|
|
|
module Renderer.Patch (
|
2015-12-18 17:48:04 +03:00
|
|
|
patch,
|
|
|
|
hunks
|
|
|
|
) where
|
2015-12-18 01:22:09 +03:00
|
|
|
|
2016-02-28 22:01:56 +03:00
|
|
|
import Alignment
|
2015-12-18 01:22:53 +03:00
|
|
|
import Diff
|
2015-12-25 02:11:19 +03:00
|
|
|
import Line
|
2015-12-30 20:35:27 +03:00
|
|
|
import Range
|
2016-01-14 21:18:40 +03:00
|
|
|
import Renderer
|
2015-12-25 01:41:45 +03:00
|
|
|
import Row
|
2015-12-31 01:42:18 +03:00
|
|
|
import Source hiding ((++), break)
|
2016-02-28 21:40:49 +03:00
|
|
|
import SplitDiff
|
2015-12-25 02:11:19 +03:00
|
|
|
import Control.Comonad.Cofree
|
|
|
|
import Control.Monad.Free
|
2016-02-29 05:43:47 +03:00
|
|
|
import Data.Functor.Both
|
2015-12-31 02:29:52 +03:00
|
|
|
import Data.Maybe
|
2015-12-30 23:56:12 +03:00
|
|
|
import Data.Monoid
|
2015-12-18 01:22:53 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | Render a diff in the traditional patch format.
|
2016-01-14 21:18:40 +03:00
|
|
|
patch :: Renderer a String
|
2016-02-10 00:18:43 +03:00
|
|
|
patch diff sources = mconcat $ showHunk sources <$> hunks diff sources
|
2015-12-18 16:00:01 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | A hunk in a patch, including the offset, changes, and context.
|
2016-02-29 05:29:59 +03:00
|
|
|
data Hunk a = Hunk { offset :: Both (Sum Int), changes :: [Change a], trailingContext :: [Row a] }
|
2015-12-25 02:11:38 +03:00
|
|
|
deriving (Eq, Show)
|
2015-12-18 16:25:37 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | A change in a patch hunk, along with its preceding context.
|
2015-12-25 02:28:31 +03:00
|
|
|
data Change a = Change { context :: [Row a], contents :: [Row a] }
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | The number of lines in the hunk before and after.
|
2016-02-29 05:29:59 +03:00
|
|
|
hunkLength :: Hunk a -> Both (Sum Int)
|
2015-12-31 00:25:18 +03:00
|
|
|
hunkLength hunk = mconcat $ (changeLength <$> changes hunk) <> (rowLength <$> trailingContext hunk)
|
2015-12-30 23:57:36 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | The number of lines in change before and after.
|
2016-02-29 05:29:59 +03:00
|
|
|
changeLength :: Change a -> Both (Sum Int)
|
2015-12-30 23:56:52 +03:00
|
|
|
changeLength change = mconcat $ (rowLength <$> context change) <> (rowLength <$> contents change)
|
2015-12-30 23:56:12 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | The number of lines in the row, each being either 0 or 1.
|
2016-02-29 05:29:59 +03:00
|
|
|
rowLength :: Row a -> Both (Sum Int)
|
2016-02-29 17:22:52 +03:00
|
|
|
rowLength = fmap lineLength . unRow
|
2015-12-30 23:56:03 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | The length of the line, being either 0 or 1.
|
2015-12-30 23:55:55 +03:00
|
|
|
lineLength :: Line a -> Sum Int
|
|
|
|
lineLength EmptyLine = 0
|
|
|
|
lineLength _ = 1
|
|
|
|
|
2016-02-23 02:13:27 +03:00
|
|
|
-- | Given the before and after sources, render a hunk to a string.
|
2016-02-29 05:29:59 +03:00
|
|
|
showHunk :: Both SourceBlob -> Hunk (SplitDiff a Info) -> String
|
|
|
|
showHunk blobs hunk = header blobs hunk ++ concat (showChange sources <$> changes hunk) ++ showLines (snd $ runBoth sources) ' ' (unRight <$> trailingContext hunk)
|
2016-02-29 05:28:24 +03:00
|
|
|
where sources = source <$> blobs
|
2015-12-25 02:50:39 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | Given the before and after sources, render a change to a string.
|
2016-02-29 05:29:59 +03:00
|
|
|
showChange :: Both (Source Char) -> Change (SplitDiff a Info) -> String
|
|
|
|
showChange sources change = showLines (snd $ runBoth sources) ' ' (unRight <$> context change) ++ deleted ++ inserted
|
|
|
|
where (deleted, inserted) = runBoth $ pure showLines <*> sources <*> Both ('-', '+') <*> (pure fmap <*> Both (unLeft, unRight) <*> pure (contents change))
|
2015-12-30 23:27:04 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | Given a source, render a set of lines to a string with a prefix.
|
2015-12-31 02:34:55 +03:00
|
|
|
showLines :: Source Char -> Char -> [Line (SplitDiff leaf Info)] -> String
|
2016-02-22 23:31:52 +03:00
|
|
|
showLines source prefix lines = fromMaybe "" . mconcat $ fmap prepend . showLine source <$> lines
|
|
|
|
where prepend "" = ""
|
|
|
|
prepend source = prefix : source
|
2015-12-31 02:34:55 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | Given a source, render a line to a string.
|
2015-12-31 00:03:38 +03:00
|
|
|
showLine :: Source Char -> Line (SplitDiff leaf Info) -> Maybe String
|
|
|
|
showLine _ EmptyLine = Nothing
|
|
|
|
showLine source line = Just . toString . (`slice` source) . unionRanges $ getRange <$> unLine line
|
2015-12-30 23:32:51 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | Return the range from a split diff.
|
2015-12-30 23:26:49 +03:00
|
|
|
getRange :: SplitDiff leaf Info -> Range
|
|
|
|
getRange (Free (Annotated (Info range _) _)) = range
|
2016-02-24 01:08:11 +03:00
|
|
|
getRange (Pure patch) = let Info range _ :< _ = getSplitTerm patch in range
|
2015-12-25 02:11:19 +03:00
|
|
|
|
2016-02-23 02:13:27 +03:00
|
|
|
-- | Returns the header given two source blobs and a hunk.
|
2016-02-29 05:29:59 +03:00
|
|
|
header :: Both SourceBlob -> Hunk a -> String
|
2016-02-29 05:10:56 +03:00
|
|
|
header blobs hunk = "diff --git a/" ++ pathA ++ " b/" ++ pathB ++ "\n" ++
|
|
|
|
"index " ++ oidA ++ ".." ++ oidB ++ "\n" ++
|
2016-02-05 01:58:01 +03:00
|
|
|
"@@ -" ++ show offsetA ++ "," ++ show lengthA ++ " +" ++ show offsetB ++ "," ++ show lengthB ++ " @@\n"
|
2016-02-29 05:29:59 +03:00
|
|
|
where (lengthA, lengthB) = runBoth . fmap getSum $ hunkLength hunk
|
|
|
|
(offsetA, offsetB) = runBoth . fmap getSum $ offset hunk
|
|
|
|
(pathA, pathB) = runBoth $ path <$> blobs
|
|
|
|
(oidA, oidB) = runBoth $ oid <$> blobs
|
2015-12-18 16:07:43 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | Render a diff as a series of hunks.
|
2016-02-03 00:53:48 +03:00
|
|
|
hunks :: Renderer a [Hunk (SplitDiff a Info)]
|
2016-02-29 06:43:48 +03:00
|
|
|
hunks diff blobs = hunksInRows (Both (1, 1)) . fst $ splitDiffByLines diff (pure 0) (source <$> blobs)
|
2016-02-29 05:10:02 +03:00
|
|
|
|
2016-02-04 01:55:16 +03:00
|
|
|
-- | Given beginning line numbers, turn rows in a split diff into hunks in a
|
|
|
|
-- | patch.
|
2016-02-29 05:29:59 +03:00
|
|
|
hunksInRows :: Both (Sum Int) -> [Row (SplitDiff a Info)] -> [Hunk (SplitDiff a Info)]
|
2015-12-31 00:26:02 +03:00
|
|
|
hunksInRows start rows = case nextHunk start rows of
|
2015-12-25 01:42:22 +03:00
|
|
|
Nothing -> []
|
2015-12-31 00:26:02 +03:00
|
|
|
Just (hunk, rest) -> hunk : hunksInRows (offset hunk <> hunkLength hunk) rest
|
2015-12-25 01:42:22 +03:00
|
|
|
|
2016-02-04 01:55:16 +03:00
|
|
|
-- | Given beginning line numbers, return the next hunk and the remaining rows
|
|
|
|
-- | of the split diff.
|
2016-02-29 05:29:59 +03:00
|
|
|
nextHunk :: Both (Sum Int) -> [Row (SplitDiff a Info)] -> Maybe (Hunk (SplitDiff a Info), [Row (SplitDiff a Info)])
|
2015-12-31 01:52:18 +03:00
|
|
|
nextHunk start rows = case nextChange start rows of
|
2015-12-25 02:52:33 +03:00
|
|
|
Nothing -> Nothing
|
2015-12-31 01:52:18 +03:00
|
|
|
Just (offset, change, rest) -> let (changes, rest') = contiguousChanges rest in Just (Hunk offset (change : changes) $ take 3 rest', drop 3 rest')
|
2015-12-31 02:06:47 +03:00
|
|
|
where contiguousChanges rows = case break rowHasChanges (take 7 rows) of
|
2015-12-31 02:08:06 +03:00
|
|
|
(_, []) -> ([], rows)
|
2015-12-31 02:19:17 +03:00
|
|
|
(context, _) -> case changeIncludingContext context (drop (length context) rows) of
|
2015-12-31 01:54:27 +03:00
|
|
|
Nothing -> ([], rows)
|
2015-12-31 01:52:18 +03:00
|
|
|
Just (change, rest) -> let (changes, rest') = contiguousChanges rest in (change : changes, rest')
|
2015-12-25 01:42:08 +03:00
|
|
|
|
2016-02-04 01:55:16 +03:00
|
|
|
-- | Given beginning line numbers, return the number of lines to the next
|
|
|
|
-- | the next change, and the remaining rows of the split diff.
|
2016-02-29 05:29:59 +03:00
|
|
|
nextChange :: Both (Sum Int) -> [Row (SplitDiff a Info)] -> Maybe (Both (Sum Int), Change (SplitDiff a Info), [Row (SplitDiff a Info)])
|
2015-12-31 02:10:58 +03:00
|
|
|
nextChange start rows = case changeIncludingContext leadingContext afterLeadingContext of
|
2015-12-31 01:43:46 +03:00
|
|
|
Nothing -> Nothing
|
|
|
|
Just (change, afterChanges) -> Just (start <> mconcat (rowLength <$> skippedContext), change, afterChanges)
|
2015-12-31 02:10:58 +03:00
|
|
|
where (leadingRows, afterLeadingContext) = break rowHasChanges rows
|
2015-12-31 00:33:45 +03:00
|
|
|
(skippedContext, leadingContext) = splitAt (max (length leadingRows - 3) 0) leadingRows
|
2015-12-25 02:28:37 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | Return a Change with the given context and the rows from the begginning of
|
|
|
|
-- | the given rows that have changes, or Nothing if the first row has no
|
|
|
|
-- | changes.
|
2015-12-31 02:05:29 +03:00
|
|
|
changeIncludingContext :: [Row (SplitDiff a Info)] -> [Row (SplitDiff a Info)] -> Maybe (Change (SplitDiff a Info), [Row (SplitDiff a Info)])
|
|
|
|
changeIncludingContext leadingContext rows = case changes of
|
2015-12-31 01:41:24 +03:00
|
|
|
[] -> Nothing
|
|
|
|
_ -> Just (Change leadingContext changes, afterChanges)
|
2015-12-31 02:05:29 +03:00
|
|
|
where (changes, afterChanges) = span rowHasChanges rows
|
2015-12-31 01:41:24 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | Whether a row has changes on either side.
|
2015-12-25 02:14:19 +03:00
|
|
|
rowHasChanges :: Row (SplitDiff a Info) -> Bool
|
2016-02-29 17:22:52 +03:00
|
|
|
rowHasChanges (Row lines) = or (lineHasChanges <$> lines)
|
2015-12-25 02:14:19 +03:00
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | Whether a line has changes.
|
2015-12-25 02:14:19 +03:00
|
|
|
lineHasChanges :: Line (SplitDiff a Info) -> Bool
|
|
|
|
lineHasChanges = or . fmap diffHasChanges
|
|
|
|
|
2016-02-03 20:58:54 +03:00
|
|
|
-- | Whether a split diff has changes.
|
2015-12-25 02:14:19 +03:00
|
|
|
diffHasChanges :: SplitDiff a Info -> Bool
|
|
|
|
diffHasChanges = or . fmap (const True)
|