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
import Control.Monad.Free
2016-03-03 07:11:24 +03:00
import Data.Copointed
2016-03-02 00:29:42 +03:00
import Data.Foldable ( foldl' )
2016-02-29 05:43:47 +03:00
import Data.Functor.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-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 Row
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 ) ]
numberedRows = foldl' numberRows []
where numberRows rows row = ( ( , ) <$> ( ( + ) <$> count rows <*> ( valueOf <$> unRow row ) ) <*> unRow row ) : rows
count = maybe ( pure 0 ) ( fmap Prelude . fst ) . maybeFirst
valueOf EmptyLine = 0
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-02-28 22:01:56 +03:00
-- | Split a diff, which may span multiple lines, into rows of split diffs.
2016-02-29 06:43:48 +03:00
splitDiffByLines :: Diff leaf Info -> Both Int -> Both ( Source Char ) -> ( [ Row ( SplitDiff leaf Info ) ] , Both Range )
splitDiffByLines diff previous sources = case diff of
2016-03-03 00:03:14 +03:00
Free ( Annotated annotation syntax ) -> ( splitAnnotatedByLines sources ( ranges annotation ) ( Diff . categories <$> annotation ) syntax , ranges annotation )
2016-03-03 00:05:34 +03:00
Pure patch -> splitPatchByLines patch previous sources
where ranges annotations = characterRange <$> annotations
2016-03-03 00:05:59 +03:00
-- | Split a patch, which may span multiple lines, into rows of split diffs.
2016-03-03 00:05:34 +03:00
splitPatchByLines :: Patch ( Term leaf Info ) -> Both Int -> Both ( Source Char ) -> ( [ Row ( SplitDiff leaf Info ) ] , Both Range )
splitPatchByLines patch previous sources = case patch of
2016-03-03 19:36:33 +03:00
Insert term -> let ( lines , range ) = splitAbstractedTerm copoint unwrap ( :< ) ( snd sources ) term in
2016-03-03 02:19:29 +03:00
( makeRow EmptyLine . fmap ( Pure . SplitInsert ) <$> lines , both ( rangeAt $ fst previous ) range )
2016-03-03 19:36:33 +03:00
Delete term -> let ( lines , range ) = splitAbstractedTerm copoint unwrap ( :< ) ( fst sources ) term in
2016-03-03 02:19:29 +03:00
( flip makeRow EmptyLine . fmap ( Pure . SplitDelete ) <$> lines , both range ( rangeAt $ snd previous ) )
2016-03-03 00:08:49 +03:00
Replace leftTerm rightTerm -> ( zipWithDefaults makeRow ( pure mempty ) $ fmap ( fmap ( Pure . SplitReplace ) ) <$> lines , ranges )
2016-03-03 19:36:33 +03:00
where ( lines , ranges ) = transpose $ splitAbstractedTerm copoint unwrap ( :< ) <$> sources <*> both leftTerm rightTerm
2016-02-28 22:01:56 +03:00
2016-03-03 19:40:52 +03:00
-- | Split a `term` (abstracted by two destructors and one constructor) up into one `term` per line in `Source`.
2016-03-03 19:42:25 +03:00
splitAbstractedTerm :: ( inTerm -> Info ) -> ( inTerm -> Syntax leaf inTerm ) -> ( Info -> Syntax leaf outTerm -> outTerm ) -> Source Char -> inTerm -> ( [ Line outTerm ] , Range )
2016-03-03 19:27:29 +03:00
splitAbstractedTerm getInfo getSyntax makeTerm source term = flip ( , ) ( characterRange ( getInfo term ) ) $ case getSyntax term of
Leaf a -> pure . ( ` makeTerm ` Leaf a ) . ( ` Info ` ( Diff . categories ( getInfo term ) ) ) <$> actualLineRanges ( characterRange ( getInfo term ) ) source
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 )
where adjoin = reverse . foldl ( adjoinLinesBy ( openRangePair source ) ) []
adjoinChildLines constructor children = let ( lines , previous ) = foldl childLines ( [] , start ( characterRange ( getInfo term ) ) ) children in
fmap ( wrapLineContents $ wrap constructor ) . adjoin $ lines ++ ( pure . flip ( , ) Nothing <$> actualLineRanges ( Range previous $ end ( characterRange ( getInfo term ) ) ) source )
wrap constructor children = ( makeTerm $ Info ( unionRanges $ Prelude . fst <$> children ) ( Diff . categories ( getInfo term ) ) ) . constructor . catMaybes $ Prelude . snd <$> children
childLines ( lines , previous ) child = let ( childLines , childRange ) = splitAbstractedTerm getInfo getSyntax makeTerm source ( copoint child ) in
( adjoin $ lines ++ ( pure . flip ( , ) Nothing <$> actualLineRanges ( Range previous $ start childRange ) source ) ++ ( fmap ( ( , ) childRange . Just . ( <$ child ) ) <$> childLines ) , end childRange )
2016-02-28 22:01:56 +03:00
-- | Split a annotated diff into rows of split diffs.
2016-02-29 06:10:02 +03:00
splitAnnotatedByLines :: Both ( Source Char ) -> Both Range -> Both ( Set . Set Category ) -> Syntax leaf ( Diff leaf Info ) -> [ Row ( SplitDiff leaf Info ) ]
2016-02-28 22:01:56 +03:00
splitAnnotatedByLines sources ranges categories syntax = case syntax of
2016-03-03 18:10:58 +03:00
Leaf a -> zipWithDefaults makeRow ( pure mempty ) $ fmap <$> ( ( ( pure . Free . ( ` Annotated ` Leaf a ) ) . ) <$> flip Info <$> 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-02 22:57:42 +03:00
Keyed children -> adjoinChildRows ( Keyed . Map . fromList ) ( List . sortOn ( diffRanges . Prelude . snd ) $ Map . toList children )
2016-03-03 18:16:04 +03:00
where adjoin :: [ Row ( Range , Maybe ( f ( SplitDiff leaf Info ) ) ) ] -> [ Row ( Range , Maybe ( f ( SplitDiff leaf Info ) ) ) ]
2016-03-03 16:19:08 +03:00
adjoin = reverse . foldl ( adjoinRowsBy ( openRangePair <$> sources ) ) []
2016-02-28 22:01:56 +03:00
2016-03-03 07:23:34 +03:00
adjoinChildRows :: ( Copointed f , Functor f ) => ( [ f ( SplitDiff leaf Info ) ] -> Syntax leaf ( SplitDiff leaf Info ) ) -> [ f ( Diff leaf Info ) ] -> [ Row ( SplitDiff leaf Info ) ]
2016-02-29 06:43:48 +03:00
adjoinChildRows constructor children = let ( rows , previous ) = foldl childRows ( [] , start <$> ranges ) children in
2016-03-03 18:13:16 +03:00
fmap ( wrapRowContents ( wrap constructor <$> categories ) ) . adjoin $ rows ++ zipWithDefaults makeRow ( pure mempty ) ( fmap ( pure . flip ( , ) Nothing ) <$> ( actualLineRanges <$> ( makeRanges previous ( end <$> ranges ) ) <*> sources ) )
2016-02-28 22:01:56 +03:00
2016-03-03 16:54:59 +03:00
wrap :: ( [ f ( SplitDiff leaf Info ) ] -> Syntax leaf ( SplitDiff leaf Info ) ) -> Set . Set Category -> [ ( Range , Maybe ( f ( SplitDiff leaf Info ) ) ) ] -> SplitDiff leaf Info
2016-03-03 16:19:08 +03:00
wrap constructor categories children = Free . Annotated ( Info ( unionRanges $ Prelude . fst <$> children ) categories ) . constructor . catMaybes $ Prelude . snd <$> children
2016-02-28 22:01:56 +03:00
2016-03-03 16:37:56 +03:00
getRange :: SplitDiff leaf Info -> Range
getRange ( Pure patch ) = characterRange ( copoint ( getSplitTerm patch ) )
getRange ( Free ( Annotated info _ ) ) = characterRange info
2016-03-03 16:30:06 +03:00
2016-03-03 16:19:08 +03:00
childRows :: ( Copointed f , Functor f ) => ( [ Row ( Range , Maybe ( f ( SplitDiff leaf Info ) ) ) ] , Both Int ) -> f ( Diff leaf Info ) -> ( [ Row ( Range , Maybe ( f ( SplitDiff leaf Info ) ) ) ] , Both Int )
2016-03-03 07:23:34 +03:00
childRows ( rows , previous ) child = let ( childRows , childRanges ) = splitDiffByLines ( copoint child ) previous sources 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-03 18:53:41 +03:00
if or $ ( < ) . start <$> childRanges <*> previous
then ( rows , previous )
2016-03-03 19:05:30 +03:00
else ( adjoin $ rows ++ zipWithDefaults makeRow ( pure mempty ) ( fmap ( pure . flip ( , ) Nothing ) <$> ( actualLineRanges <$> ( makeRanges previous ( start <$> childRanges ) ) <*> sources ) ) ++ ( fmap ( getRange &&& Just . ( <$ child ) ) <$> childRows ) , end <$> childRanges )
2016-02-28 22:01:56 +03:00
2016-03-02 22:37:25 +03:00
makeRanges :: Both Int -> Both Int -> Both Range
2016-03-03 18:42:13 +03:00
makeRanges a b = runBothWith Range <$> sequenceA ( both a b )
2016-02-28 22:01:56 +03:00
2016-03-02 22:15:20 +03:00
-- | Produces the starting indices of a diff.
2016-03-02 22:19:36 +03:00
diffRanges :: Diff leaf Info -> Both ( Maybe Range )
2016-03-02 22:20:17 +03:00
diffRanges ( Free ( Annotated infos _ ) ) = Just . characterRange <$> infos
2016-03-03 07:11:24 +03:00
diffRanges ( Pure patch ) = fmap ( characterRange . copoint ) <$> unPatch patch
2016-03-02 22:15:20 +03:00
2016-03-03 15:59:03 +03:00
-- | MaybeOpen test for (Range, a) pairs.
2016-03-03 15:58:36 +03:00
openRangePair :: Source Char -> MaybeOpen ( Range , a )
openRangePair source pair = pair <$ openRange source ( Prelude . fst pair )
2016-02-28 22:01:56 +03:00
-- | Given a source and a range, returns nothing if it ends with a `\n`;
-- | otherwise returns the range.
openRange :: Source Char -> MaybeOpen Range
openRange source range = case ( source ` at ` ) <$> maybeLastIndex range of
Just '\ n' -> Nothing
_ -> Just range