2016-10-21 01:19:42 +03:00
{- # LANGUAGE TypeFamilies, TypeSynonymInstances, ScopedTypeVariables # -}
2016-06-30 19:59:26 +03:00
{- # OPTIONS_GHC - fno - warn - orphans # -}
2015-11-18 00:25:36 +03:00
module Diff where
2016-05-26 19:58:04 +03:00
import Prologue
2016-09-16 18:48:58 +03:00
import Data.Functor.Foldable as F
2016-06-27 19:02:25 +03:00
import Data.Functor.Both as Both
2016-07-23 00:38:10 +03:00
import Data.Mergeable
2016-09-12 20:40:22 +03:00
import Data.Record
2015-11-18 05:23:53 +03:00
import Patch
2016-09-12 20:40:22 +03:00
import Syntax
2016-02-29 18:04:59 +03:00
import Term
2015-11-18 00:25:36 +03:00
2016-01-14 20:30:21 +03:00
-- | An annotated series of patches of terms.
2016-09-09 21:46:50 +03:00
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 ) )
2016-05-03 22:50:38 +03:00
2016-09-12 20:40:22 +03:00
type SyntaxDiff leaf fields = Diff ( Syntax leaf ) ( Record fields )
2016-05-04 21:37:24 +03:00
type instance Base ( Free f a ) = FreeF f a
2016-09-14 23:12:47 +03:00
instance Functor f => Recursive ( Free f a ) where project = runFree
instance Functor f => Corecursive ( Free f a ) where embed = free
2015-11-18 00:25:36 +03:00
2016-09-14 23:12:47 +03:00
diffSum :: ( Foldable f , Functor f ) => ( Patch ( Term f annotation ) -> Int ) -> Diff f annotation -> Int
2015-12-01 18:13:05 +03:00
diffSum patchCost diff = sum $ fmap patchCost diff
2015-12-01 03:06:48 +03:00
2016-04-11 22:06:59 +03:00
-- | The sum of the node count of the diff’ s patches.
2016-09-14 23:12:47 +03:00
diffCost :: ( Foldable f , Functor f ) => Diff f annotation -> Int
2015-12-01 03:16:22 +03:00
diffCost = diffSum $ patchSum termSize
2016-06-27 19:02:25 +03:00
2016-07-05 16:45:28 +03:00
-- | Merge a diff using a function to provide the Term (in Maybe, to simplify recovery of the before/after state) for every Patch.
2016-10-21 01:19:42 +03:00
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
2016-10-21 00:22:45 +03:00
2016-07-05 16:45:28 +03:00
-- | Recover the before state of a diff.
2016-09-15 00:13:10 +03:00
beforeTerm :: Mergeable f => Diff f annotation -> Maybe ( Term f annotation )
2016-10-21 01:19:42 +03:00
beforeTerm = mergeMaybe before Both . fst
2016-06-27 19:50:25 +03:00
2016-07-05 16:45:28 +03:00
-- | Recover the after state of a diff.
2016-10-21 00:33:47 +03:00
afterTerm :: Mergeable f => Diff f annotation -> Maybe ( Term f annotation )
2016-10-21 01:19:42 +03:00
afterTerm = mergeMaybe after Both . snd
2017-02-07 22:57:42 +03:00
2017-02-07 22:58:11 +03:00
-- | Map a function over the annotations in a diff, whether in diff or term nodes.
2017-02-07 23:03:59 +03:00
--
-- Typed using Free so as to accommodate Free structures derived from diffs that don’ t fit into the Diff type synonym (e.g. because the leaves aren’ t in Patch).
2017-02-07 23:02:40 +03:00
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' ) )
2017-02-07 22:57:42 +03:00
mapAnnotations f = iter ( \ ( h :< functor ) -> wrap ( fmap f h :< functor ) ) . fmap ( pure . fmap ( fmap f ) )