From c92cc987ed0b4355ee71f90822fd2768bbcb7df9 Mon Sep 17 00:00:00 2001 From: Rob Rix Date: Fri, 22 Jul 2016 13:52:48 -0400 Subject: [PATCH] Put some formatting back. --- src/Diff/Arbitrary.hs | 1 + src/DiffSummary.hs | 1 - src/Interpreter.hs | 6 ++++-- src/Syntax.hs | 1 + src/Term/Arbitrary.hs | 1 + 5 files changed, 7 insertions(+), 3 deletions(-) diff --git a/src/Diff/Arbitrary.hs b/src/Diff/Arbitrary.hs index 948f31c9b..b6fd009a4 100644 --- a/src/Diff/Arbitrary.hs +++ b/src/Diff/Arbitrary.hs @@ -49,4 +49,5 @@ instance (Eq leaf, Eq annotation, Arbitrary leaf, Arbitrary annotation) => Arbit arbitrary = sized $ \ n -> do m <- choose (0, n) diffOfSize m + shrink = genericShrink diff --git a/src/DiffSummary.hs b/src/DiffSummary.hs index 6f15bc75b..9a74e1796 100644 --- a/src/DiffSummary.hs +++ b/src/DiffSummary.hs @@ -1,5 +1,4 @@ {-# LANGUAGE DataKinds, TypeFamilies, ScopedTypeVariables #-} - module DiffSummary (DiffSummary(..), diffSummary, DiffInfo(..)) where import Prologue hiding (snd, intercalate) diff --git a/src/Interpreter.hs b/src/Interpreter.hs index 3ffec2810..16f396538 100644 --- a/src/Interpreter.hs +++ b/src/Interpreter.hs @@ -1,10 +1,10 @@ module Interpreter (Comparable, DiffConstructor, diffTerms) where import Algorithm -import Category (Category) +import Category import Data.Align.Generic import Data.Functor.Foldable -import Data.Functor.Both hiding (fst, snd) +import Data.Functor.Both import Data.Hashable import Data.RandomWalkSimilarity import Data.Record @@ -48,7 +48,9 @@ run construct comparable cost algorithm = case runFree algorithm of Free (Recursive t1 t2 f) -> run construct comparable cost . f $ recur a b where (annotation1 :< a, annotation2 :< b) = (runCofree t1, runCofree t2) annotate = construct . (both annotation1 annotation2 :<) + recur a b = maybe (pure (Replace t1 t2)) (annotate . fmap diffThese) (galign a b) + diffThese = these (pure . Delete) (pure . Insert) (diffTerms construct comparable cost) Free (ByIndex a b f) -> run construct comparable cost . f $ ses (constructAndRun construct comparable cost) cost a b diff --git a/src/Syntax.hs b/src/Syntax.hs index 8f50ec863..7bfad9204 100644 --- a/src/Syntax.hs +++ b/src/Syntax.hs @@ -51,6 +51,7 @@ data Syntax | Commented [f] (Maybe f) deriving (Eq, Foldable, Functor, Generic, Generic1, Ord, Show, Traversable) + -- Instances syntaxOfSize :: Arbitrary leaf => (Int -> Gen f) -> Int -> Gen (Syntax leaf f) diff --git a/src/Term/Arbitrary.hs b/src/Term/Arbitrary.hs index 039009de3..c79b572b7 100644 --- a/src/Term/Arbitrary.hs +++ b/src/Term/Arbitrary.hs @@ -33,4 +33,5 @@ instance (Eq leaf, Eq annotation, Arbitrary leaf, Arbitrary annotation) => Arbit arbitrary = sized $ \ n -> do m <- choose (0, n) termOfSize m + shrink = genericShrink