1
1
mirror of https://github.com/github/semantic.git synced 2024-12-19 12:51:52 +03:00

Put some formatting back.

This commit is contained in:
Rob Rix 2016-07-22 13:52:48 -04:00
parent 819470afea
commit c92cc987ed
5 changed files with 7 additions and 3 deletions

View File

@ -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

View File

@ -1,5 +1,4 @@
{-# LANGUAGE DataKinds, TypeFamilies, ScopedTypeVariables #-}
module DiffSummary (DiffSummary(..), diffSummary, DiffInfo(..)) where
import Prologue hiding (snd, intercalate)

View File

@ -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

View File

@ -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)

View File

@ -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