1
1
mirror of https://github.com/github/semantic.git synced 2024-12-21 13:51:44 +03:00
semantic/src/Diff.hs

53 lines
2.6 KiB
Haskell
Raw Blame History

This file contains ambiguous Unicode characters

This file contains Unicode characters that might be confused with other characters. If you think that this is intentional, you can safely ignore this warning. Use the Escape button to reveal them.

{-# LANGUAGE TypeSynonymInstances, ScopedTypeVariables #-}
module Diff where
import Prologue
import Data.Functor.Both as Both
import Data.Mergeable
import Data.Record
import Patch
import Syntax
import Term
-- | An annotated series of patches of terms.
type DiffF f annotation = FreeF (TermF f (Both annotation)) (Patch (Term f annotation))
type Diff f annotation = Free (TermF f (Both annotation)) (Patch (Term f annotation))
type SyntaxDiff leaf fields = Diff (Syntax leaf) (Record fields)
diffSum :: (Foldable f, Functor f) => (Patch (Term f annotation) -> Int) -> Diff f annotation -> Int
diffSum patchCost diff = sum $ fmap patchCost diff
-- | The sum of the node count of the diffs patches.
diffCost :: (Foldable f, Functor f) => Diff f annotation -> Int
diffCost = diffSum $ patchSum termSize
-- | Merge a diff using a function to provide the Term (in Maybe, to simplify recovery of the before/after state) for every Patch.
mergeMaybe :: forall f annotation. Mergeable f => (Patch (Term f annotation) -> Maybe (Term f annotation)) -> (Both annotation -> annotation) -> Diff f annotation -> Maybe (Term f annotation)
mergeMaybe transform extractAnnotation = iter algebra . fmap transform
where algebra :: TermF f (Both annotation) (Maybe (Term f annotation)) -> Maybe (Term f annotation)
algebra (annotations :< syntax) = cofree . (extractAnnotation annotations :<) <$> sequenceAlt syntax
-- | Recover the before state of a diff.
beforeTerm :: Mergeable f => Diff f annotation -> Maybe (Term f annotation)
beforeTerm = mergeMaybe before Both.fst
-- | Recover the after state of a diff.
afterTerm :: Mergeable f => Diff f annotation -> Maybe (Term f annotation)
afterTerm = mergeMaybe after Both.snd
-- | Map a function over the annotations in a diff, whether in diff or term nodes.
--
-- Typed using Free so as to accommodate Free structures derived from diffs that dont fit into the Diff type synonym.
mapAnnotations :: (Functor f, Functor g)
=> (annotation -> annotation')
-> Free (TermF f (g annotation)) (Patch (Term f annotation))
-> Free (TermF f (g annotation')) (Patch (Term f annotation'))
mapAnnotations f = iter (\ (h :< functor) -> wrap (fmap f h :< functor)) . fmap (pure . fmap (fmap f))
-- | Map a function over the annotations of a single diff node, if it is in Free.
modifyAnnotations :: (Functor f, Functor g) => (annotation -> annotation) -> Free (TermF f (g annotation)) a -> Free (TermF f (g annotation)) a
modifyAnnotations f r = case runFree r of
Free (ga :< functor) -> wrap (fmap f ga :< functor)
_ -> r