mirror of
https://github.com/github/semantic.git
synced 2024-12-20 13:21:59 +03:00
Generalize Alignment over annotations with ranges.
This commit is contained in:
parent
8b5dc22797
commit
87552e0ecb
@ -1,4 +1,4 @@
|
||||
{-# LANGUAGE RankNTypes, ScopedTypeVariables #-}
|
||||
{-# LANGUAGE FlexibleContexts, RankNTypes, ScopedTypeVariables #-}
|
||||
module Alignment
|
||||
( hasChanges
|
||||
, numberedRows
|
||||
@ -18,6 +18,7 @@ import Data.Functor.Foldable (hylo)
|
||||
import Data.List (partition)
|
||||
import Data.Maybe (fromJust)
|
||||
import qualified Data.OrderedMap as Map
|
||||
import Data.Record
|
||||
import Data.These
|
||||
import Diff
|
||||
import Info
|
||||
@ -43,11 +44,11 @@ hasChanges :: SplitDiff leaf annotation -> Bool
|
||||
hasChanges = or . (True <$)
|
||||
|
||||
-- | Align a Diff into a list of Join These SplitDiffs representing the (possibly blank) lines on either side.
|
||||
alignDiff :: Show leaf => Both (Source Char) -> Diff leaf Info -> [Join These (SplitDiff leaf Info)]
|
||||
alignDiff :: (Show leaf, Show (Record fields), HasField fields Range) => Both (Source Char) -> Diff leaf (Record fields) -> [Join These (SplitDiff leaf (Record fields))]
|
||||
alignDiff sources diff = iter (alignSyntax (runBothWith ((Join .) . These)) (free . Free) getRange sources) (alignPatch sources <$> diff)
|
||||
|
||||
-- | Align the contents of a patch into a list of lines on the corresponding side(s) of the diff.
|
||||
alignPatch :: forall leaf. Show leaf => Both (Source Char) -> Patch (Term leaf Info) -> [Join These (SplitDiff leaf Info)]
|
||||
alignPatch :: forall fields leaf. (Show leaf, Show (Record fields), HasField fields Range) => Both (Source Char) -> Patch (Term leaf (Record fields)) -> [Join These (SplitDiff leaf (Record fields))]
|
||||
alignPatch sources patch = case patch of
|
||||
Delete term -> fmap (pure . SplitDelete) <$> alignSyntax' this (fst sources) term
|
||||
Insert term -> fmap (pure . SplitInsert) <$> alignSyntax' that (snd sources) term
|
||||
@ -55,13 +56,13 @@ alignPatch sources patch = case patch of
|
||||
(alignSyntax' this (fst sources) term1)
|
||||
(alignSyntax' that (snd sources) term2)
|
||||
where getRange = characterRange . extract
|
||||
alignSyntax' :: (forall a. Identity a -> Join These a) -> Source Char -> Term leaf Info -> [Join These (Term leaf Info)]
|
||||
alignSyntax' :: (forall a. Identity a -> Join These a) -> Source Char -> Term leaf (Record fields) -> [Join These (Term leaf (Record fields))]
|
||||
alignSyntax' side source term = hylo (alignSyntax side cofree getRange (Identity source)) runCofree (Identity <$> term)
|
||||
this = Join . This . runIdentity
|
||||
that = Join . That . runIdentity
|
||||
|
||||
-- | The Applicative instance f is either Identity or Both. Identity is for Terms in Patches, Both is for Diffs in unchanged portions of the diff.
|
||||
alignSyntax :: (Applicative f, Show term) => (forall a. f a -> Join These a) -> (CofreeF (Syntax leaf) Info term -> term) -> (term -> Range) -> f (Source Char) -> CofreeF (Syntax leaf) (f Info) [Join These term] -> [Join These term]
|
||||
alignSyntax :: (Applicative f, Show term, HasField fields Range) => (forall a. f a -> Join These a) -> (CofreeF (Syntax leaf) (Record fields) term -> term) -> (term -> Range) -> f (Source Char) -> CofreeF (Syntax leaf) (f (Record fields)) [Join These term] -> [Join These term]
|
||||
alignSyntax toJoinThese toNode getRange sources (infos :< syntax) = case syntax of
|
||||
Leaf s -> catMaybes $ wrapInBranch (const (Leaf s)) . fmap (flip (,) []) <$> sequenceL lineRanges
|
||||
Indexed children -> catMaybes $ wrapInBranch Indexed <$> alignBranch getRange (join children) bothRanges
|
||||
|
Loading…
Reference in New Issue
Block a user