2016-02-28 21:55:19 +03:00
module Alignment where
2016-02-28 22:01:56 +03:00
import Category
2016-03-03 16:47:37 +03:00
import Control.Arrow
2016-02-28 22:01:56 +03:00
import Control.Comonad.Cofree
2016-03-05 04:18:49 +03:00
import Control.Monad
2016-02-28 22:01:56 +03:00
import Control.Monad.Free
2016-03-03 07:11:24 +03:00
import Data.Copointed
2016-03-05 04:18:49 +03:00
import Data.Functor.Both as Both
2016-02-28 22:01:56 +03:00
import Data.Functor.Identity
2016-03-02 22:57:42 +03:00
import qualified Data.List as List
2016-03-03 15:53:23 +03:00
import Data.Maybe
2016-03-05 04:18:49 +03:00
import Data.Option
2016-02-28 22:01:56 +03:00
import qualified Data.OrderedMap as Map
import qualified Data.Set as Set
import Diff
import Line
import Patch
2016-03-01 03:39:04 +03:00
import Prelude hiding ( fst , snd )
import qualified Prelude
2016-02-28 22:01:56 +03:00
import Range
import Source hiding ( ( ++ ) )
import SplitDiff
import Syntax
import Term
2016-03-02 00:29:42 +03:00
-- | Assign line numbers to the lines on each side of a list of rows.
numberedRows :: [ Row a ] -> [ Both ( Int , Line a ) ]
2016-03-08 01:13:51 +03:00
numberedRows = countUp ( pure 1 )
2016-03-09 09:35:01 +03:00
where countUp from ( row : rows ) = ( ( , ) <$> from <*> row ) : countUp ( ( + ) <$> from <*> ( valueOf <$> row ) ) rows
2016-03-08 01:13:51 +03:00
countUp _ [] = []
2016-03-09 08:58:09 +03:00
valueOf ( Line [] ) = 0
2016-03-02 00:29:42 +03:00
valueOf _ = 1
2016-03-02 16:05:18 +03:00
-- | Determine whether a line contains any patches.
hasChanges :: Line ( SplitDiff leaf Info ) -> Bool
hasChanges = or . fmap ( or . ( True <$ ) )
2016-03-07 20:05:21 +03:00
-- | Split a diff, which may span multiple lines, into rows of split diffs paired with the Range of characters spanned by that Row on each side of the diff.
2016-03-05 03:29:57 +03:00
splitDiffByLines :: Both ( Source Char ) -> Diff leaf Info -> [ Row ( SplitDiff leaf Info , Range ) ]
2016-03-09 07:37:11 +03:00
splitDiffByLines sources = iter ( \ ( Annotated info syntax ) -> splitAnnotatedByLines ( ( Free . ) . Annotated ) sources info syntax ) . fmap ( splitPatchByLines sources )
2016-03-03 00:05:34 +03:00
2016-03-03 00:05:59 +03:00
-- | Split a patch, which may span multiple lines, into rows of split diffs.
2016-03-05 03:07:54 +03:00
splitPatchByLines :: Both ( Source Char ) -> Patch ( Term leaf Info ) -> [ Row ( SplitDiff leaf Info , Range ) ]
2016-03-09 09:35:47 +03:00
splitPatchByLines sources patch = zipWithDefaults both ( pure mempty ) $ fmap ( fmap ( first ( Pure . constructor patch ) ) ) <$> lines
2016-03-07 21:14:34 +03:00
where lines = maybe [] . cata . splitAbstractedTerm ( :< ) <$> sources <*> unPatch patch
2016-03-03 20:30:23 +03:00
constructor ( Replace _ _ ) = SplitReplace
constructor ( Insert _ ) = SplitInsert
constructor ( Delete _ ) = SplitDelete
2016-02-28 22:01:56 +03:00
2016-03-05 05:12:49 +03:00
-- | Split a term comprised of an Info & Syntax up into one `outTerm` (abstracted by a constructor) per line in `Source`.
splitAbstractedTerm :: ( Info -> Syntax leaf outTerm -> outTerm ) -> Source Char -> Info -> Syntax leaf [ Line ( outTerm , Range ) ] -> [ Line ( outTerm , Range ) ]
splitAbstractedTerm makeTerm source ( Info range categories ) syntax = case syntax of
Leaf a -> pure . ( ( ` makeTerm ` Leaf a ) . ( ` Info ` categories ) &&& id ) <$> actualLineRanges range source
2016-03-09 07:21:02 +03:00
Indexed children -> adjoinChildLines ( Indexed . fmap copoint ) ( Identity <$> children )
Fixed children -> adjoinChildLines ( Fixed . fmap copoint ) ( Identity <$> children )
Keyed children -> adjoinChildLines ( Keyed . Map . fromList ) ( Map . toList children )
2016-03-07 23:52:12 +03:00
where adjoinChildLines constructor children = let ( lines , next ) = foldr childLines ( [] , end range ) children in
2016-03-08 03:40:05 +03:00
fmap ( wrapLineContents ( makeBranchTerm ( \ info -> makeTerm info . constructor ) categories next ) ) . foldr ( adjoinLinesBy ( openRangePair source ) ) [] $
( pure . ( , ) Nothing <$> actualLineRanges ( Range ( start range ) next ) source ) ++ lines
2016-03-03 19:27:29 +03:00
2016-03-07 23:52:12 +03:00
childLines child ( lines , next ) = let childRange = unionLineRangesFrom ( rangeAt next ) ( copoint child ) in
2016-03-09 07:21:02 +03:00
( ( fmap ( first ( Just . ( <$ child ) ) ) <$> copoint child )
2016-03-07 23:52:12 +03:00
++ ( pure . ( , ) Nothing <$> actualLineRanges ( Range ( end childRange ) next ) source )
++ lines , start childRange )
2016-03-03 21:41:56 +03:00
2016-03-05 05:09:00 +03:00
-- | Split an annotated diff into rows of split diffs.
2016-03-09 07:37:11 +03:00
splitAnnotatedByLines :: ( Info -> Syntax leaf outTerm -> outTerm ) -> Both ( Source Char ) -> Both Info -> Syntax leaf [ Row ( outTerm , Range ) ] -> [ Row ( outTerm , Range ) ]
splitAnnotatedByLines makeTerm sources infos syntax = case syntax of
2016-03-09 09:35:47 +03:00
Leaf a -> zipWithDefaults both ( pure mempty ) $ fmap <$> ( ( \ categories range -> pure ( makeTerm ( Info range categories ) ( Leaf a ) , range ) ) <$> categories ) <*> ( actualLineRanges <$> ranges <*> sources )
2016-03-03 07:23:34 +03:00
Indexed children -> adjoinChildRows ( Indexed . fmap copoint ) ( Identity <$> children )
Fixed children -> adjoinChildRows ( Fixed . fmap copoint ) ( Identity <$> children )
2016-03-05 04:18:57 +03:00
Keyed children -> adjoinChildRows ( Keyed . Map . fromList ) ( List . sortOn ( rowRanges . Prelude . snd ) $ Map . toList children )
2016-03-05 04:25:33 +03:00
where ranges = characterRange <$> infos
categories = Diff . categories <$> infos
2016-03-08 00:05:40 +03:00
adjoinChildRows constructor children = let ( rows , next ) = foldr childRows ( [] , end <$> ranges ) children in
2016-03-09 09:35:01 +03:00
fmap ( wrapLineContents <$> ( makeBranchTerm ( \ info -> makeTerm info . constructor ) <$> categories <*> next ) <*> ) . foldr ( adjoinRowsBy ( openRangePair <$> sources ) ) [] $
2016-03-09 09:35:47 +03:00
zipWithDefaults both ( pure mempty ) ( fmap ( pure . ( , ) Nothing ) <$> ( actualLineRanges <$> ( Range <$> ( start <$> ranges ) <*> next ) <*> sources ) ) ++ rows
2016-02-28 22:01:56 +03:00
2016-03-09 09:35:01 +03:00
childRows child ( rows , next ) = let childRanges = unionLineRangesFrom <$> ( rangeAt <$> next ) <*> sequenceA ( copoint child ) in
2016-03-03 18:56:31 +03:00
-- We depend on source ranges increasing monotonically. If a child invalidates that, e.g. if it’ s a move in a Keyed node, we don’ t output rows for it in this iteration. (It will still show up in the diff as context rows.) This works around https://github.com/github/semantic-diff/issues/488.
2016-03-08 00:05:40 +03:00
if or $ ( > ) . end <$> childRanges <*> next
then ( rows , next )
2016-03-09 09:35:01 +03:00
else ( ( fmap ( fmap ( first ( Just . ( <$ child ) ) ) ) <$> copoint child )
2016-03-09 09:35:47 +03:00
++ zipWithDefaults both ( pure mempty ) ( fmap ( pure . ( , ) Nothing ) <$> ( actualLineRanges <$> ( Range <$> ( end <$> childRanges ) <*> next ) <*> sources ) )
2016-03-08 00:05:40 +03:00
++ rows , start <$> childRanges )
2016-02-28 22:01:56 +03:00
2016-03-04 16:54:59 +03:00
-- | Wrap a list of child terms in a branch.
2016-03-05 01:17:17 +03:00
makeBranchTerm :: ( Info -> [ inTerm ] -> outTerm ) -> Set . Set Category -> Int -> [ ( Maybe inTerm , Range ) ] -> ( outTerm , Range )
2016-03-07 23:52:12 +03:00
makeBranchTerm constructor categories next children = ( constructor ( Info range categories ) . catMaybes $ Prelude . fst <$> children , range )
where range = unionRangesFrom ( rangeAt next ) $ Prelude . snd <$> children
2016-03-04 16:39:40 +03:00
2016-03-04 18:00:35 +03:00
-- | Compute the union of the ranges in a list of ranged lines.
2016-03-04 21:07:34 +03:00
unionLineRangesFrom :: Range -> [ Line ( a , Range ) ] -> Range
unionLineRangesFrom start lines = unionRangesFrom start ( lines >>= ( fmap Prelude . snd . unLine ) )
2016-03-04 17:41:57 +03:00
2016-03-05 04:18:49 +03:00
-- | Returns the ranges of a list of Rows.
rowRanges :: [ Row ( a , Range ) ] -> Both ( Maybe Range )
2016-03-09 09:35:01 +03:00
rowRanges rows = maybeConcat . join <$> Both . unzip ( fmap ( fmap Prelude . snd . unLine ) <$> rows )
2016-03-02 22:15:20 +03:00
2016-03-09 06:07:38 +03:00
-- | Openness predicate for (Range, a) pairs.
openRangePair :: Source Char -> ( a , Range ) -> Bool
openRangePair source pair = openRange source ( Prelude . snd pair )
2016-03-03 15:58:36 +03:00
2016-03-09 06:07:38 +03:00
-- | Does this Range in this Source end with a newline?
openRange :: Source Char -> Range -> Bool
2016-03-09 06:13:31 +03:00
openRange source range = ( at source <$> maybeLastIndex range ) /= Just '\ n'
2016-03-09 09:36:40 +03:00
2016-03-09 09:38:59 +03:00
-- | A row in a split diff, composed of a before line and an after line.
type Row a = Both ( Line a )
2016-03-09 09:36:40 +03:00
-- | Merge open lines and prepend closed lines (as determined by a pair of functions) onto a list of rows.
adjoinRowsBy :: Both ( a -> Bool ) -> Row a -> [ Row a ] -> [ Row a ]
adjoinRowsBy _ row [] = [ row ]
adjoinRowsBy f row ( nextRow : rows ) = zipWithDefaults both mempty ( coalesceLinesBy <$> f <*> row <*> nextRow ) ++ rows