1
1
mirror of https://github.com/github/semantic.git synced 2024-12-22 06:11:49 +03:00
semantic/src/Diff.hs
2016-05-26 14:46:13 -04:00

24 lines
820 B
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 TypeFamilies, TypeSynonymInstances, FlexibleInstances #-}
module Diff where
import Prologue
import Data.Functor.Foldable as Foldable
import Data.Functor.Both
import Patch
import Syntax
import Term
-- | An annotated series of patches of terms.
type Diff a annotation = Free (CofreeF (Syntax a) (Both annotation)) (Patch (Term a annotation))
type instance Base (Free f a) = FreeF f a
instance (Functor f) => Foldable.Foldable (Free f a) where project = runFree
instance (Functor f) => Foldable.Unfoldable (Free f a) where embed = free
diffSum :: (Patch (Term a annotation) -> Integer) -> Diff a annotation -> Integer
diffSum patchCost diff = sum $ fmap patchCost diff
-- | The sum of the node count of the diffs patches.
diffCost :: Diff a annotation -> Integer
diffCost = diffSum $ patchSum termSize