mirror of
https://github.com/github/semantic.git
synced 2024-11-24 08:54:07 +03:00
Rename Algorithm -> Diffing.Algorithm.
This commit is contained in:
parent
088c58f405
commit
cfd27ec20c
@ -13,8 +13,7 @@ cabal-version: >=1.10
|
||||
|
||||
library
|
||||
hs-source-dirs: src
|
||||
exposed-modules: Algorithm
|
||||
, Category
|
||||
exposed-modules: Category
|
||||
, Data.Align.Generic
|
||||
, Data.Blob
|
||||
, Data.Diff
|
||||
@ -43,6 +42,7 @@ library
|
||||
, Data.Syntax.Type
|
||||
, Data.Term
|
||||
, Decorator
|
||||
, Diffing.Algorithm
|
||||
, Files
|
||||
, Info
|
||||
, Interpreter
|
||||
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE DeriveAnyClass, GADTs, TypeOperators #-}
|
||||
module Data.Syntax where
|
||||
|
||||
import Algorithm hiding (Empty)
|
||||
import Diffing.Algorithm hiding (Empty)
|
||||
import Control.Applicative
|
||||
import Control.Monad.Error.Class hiding (Error)
|
||||
import Data.Align.Generic
|
||||
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
module Data.Syntax.Comment where
|
||||
|
||||
import Algorithm
|
||||
import Diffing.Algorithm
|
||||
import Data.Align.Generic
|
||||
import Data.ByteString (ByteString)
|
||||
import Data.Functor.Classes.Eq.Generic
|
||||
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
module Data.Syntax.Declaration where
|
||||
|
||||
import Algorithm
|
||||
import Diffing.Algorithm
|
||||
import Data.Align.Generic
|
||||
import Data.Functor.Classes.Eq.Generic
|
||||
import Data.Functor.Classes.Ord.Generic
|
||||
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
module Data.Syntax.Expression where
|
||||
|
||||
import Algorithm
|
||||
import Diffing.Algorithm
|
||||
import Data.Align.Generic
|
||||
import Data.Functor.Classes.Eq.Generic
|
||||
import Data.Functor.Classes.Ord.Generic
|
||||
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE DataKinds, DeriveAnyClass, DeriveGeneric #-}
|
||||
module Data.Syntax.Literal where
|
||||
|
||||
import Algorithm
|
||||
import Diffing.Algorithm
|
||||
import Data.Align.Generic
|
||||
import Data.ByteString (ByteString)
|
||||
import Data.Functor.Classes.Eq.Generic
|
||||
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE DeriveAnyClass, StandaloneDeriving #-}
|
||||
module Data.Syntax.Statement where
|
||||
|
||||
import Algorithm
|
||||
import Diffing.Algorithm
|
||||
import Data.Align.Generic
|
||||
import Data.Functor.Classes.Eq.Generic
|
||||
import Data.Functor.Classes.Ord.Generic
|
||||
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
module Data.Syntax.Type where
|
||||
|
||||
import Algorithm
|
||||
import Diffing.Algorithm
|
||||
import Data.Align.Generic
|
||||
import Data.Functor.Classes.Eq.Generic
|
||||
import Data.Functor.Classes.Ord.Generic
|
||||
|
@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE DataKinds, DefaultSignatures, GADTs, RankNTypes, TypeOperators, UndecidableInstances #-}
|
||||
module Algorithm where
|
||||
module Diffing.Algorithm where
|
||||
|
||||
import Control.Applicative (Alternative(..))
|
||||
import Control.Monad (guard)
|
||||
@ -41,7 +41,7 @@ type Algorithm term1 term2 result = Freer (AlgorithmF term1 term2 result)
|
||||
|
||||
-- | Diff two terms without specifying the algorithm to be used.
|
||||
diff :: term1 -> term2 -> Algorithm term1 term2 result result
|
||||
diff a1 a2 = Algorithm.Diff a1 a2 `Then` return
|
||||
diff a1 a2 = Diffing.Algorithm.Diff a1 a2 `Then` return
|
||||
|
||||
-- | Diff a These of terms without specifying the algorithm to be used.
|
||||
diffThese :: These term1 term2 -> Algorithm term1 term2 result result
|
||||
@ -77,7 +77,7 @@ byReplacing a1 a2 = Replace a1 a2 `Then` return
|
||||
|
||||
instance (Show term1, Show term2) => Show1 (AlgorithmF term1 term2 result) where
|
||||
liftShowsPrec sp _ d algorithm = case algorithm of
|
||||
Algorithm.Diff t1 t2 -> showsBinaryWith showsPrec showsPrec "Diff" d t1 t2
|
||||
Diffing.Algorithm.Diff t1 t2 -> showsBinaryWith showsPrec showsPrec "Diff" d t1 t2
|
||||
Linear t1 t2 -> showsBinaryWith showsPrec showsPrec "Linear" d t1 t2
|
||||
RWS as bs -> showsBinaryWith (liftShowsPrec showsPrec showList) (liftShowsPrec showsPrec showList) "RWS" d as bs
|
||||
Delete t1 -> showsUnaryWith showsPrec "Delete" d t1
|
@ -4,7 +4,7 @@ module Interpreter
|
||||
, diffSyntaxTerms
|
||||
) where
|
||||
|
||||
import Algorithm
|
||||
import Diffing.Algorithm
|
||||
import Control.Applicative (Alternative(..))
|
||||
import Control.Monad.Free.Freer
|
||||
import Data.Align.Generic
|
||||
@ -76,7 +76,7 @@ runAlgorithm comparable eqTerms = go
|
||||
result
|
||||
-> m result
|
||||
go = iterFreerA (\ step yield -> case step of
|
||||
Algorithm.Diff t1 t2 -> go (algorithmForTerms t1 t2) <|> pure (replacing t1 t2) >>= yield
|
||||
Diffing.Algorithm.Diff t1 t2 -> go (algorithmForTerms t1 t2) <|> pure (replacing t1 t2) >>= yield
|
||||
Linear (Term (In ann1 f1)) (Term (In ann2 f2)) -> merge (ann1, ann2) <$> galignWith (go . diffThese) f1 f2 >>= yield
|
||||
RWS as bs -> traverse (go . diffThese) (rws comparable eqTerms as bs) >>= yield
|
||||
Delete a -> yield (deleting a)
|
||||
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
module Language.Markdown.Syntax where
|
||||
|
||||
import Algorithm
|
||||
import Diffing.Algorithm
|
||||
import Data.Align.Generic
|
||||
import Data.ByteString (ByteString)
|
||||
import Data.Functor.Classes.Eq.Generic
|
||||
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
module Language.Python.Syntax where
|
||||
|
||||
import Algorithm
|
||||
import Diffing.Algorithm
|
||||
import Data.Align.Generic
|
||||
import Data.Functor.Classes.Eq.Generic
|
||||
import Data.Functor.Classes.Ord.Generic
|
||||
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
module Language.TypeScript.Syntax where
|
||||
|
||||
import Algorithm
|
||||
import Diffing.Algorithm
|
||||
import Data.Align.Generic
|
||||
import Data.ByteString (ByteString)
|
||||
import Data.Functor.Classes.Eq.Generic
|
||||
|
@ -7,7 +7,7 @@ module Semantic
|
||||
, diffTermPair
|
||||
) where
|
||||
|
||||
import Algorithm (Diffable)
|
||||
import Diffing.Algorithm (Diffable)
|
||||
import Control.Exception
|
||||
import Control.Monad ((>=>), guard)
|
||||
import Control.Monad.Error.Class
|
||||
|
@ -7,7 +7,7 @@ import Data.Blob
|
||||
import Files
|
||||
import Data.Record
|
||||
import Data.Functor.Classes
|
||||
import Algorithm
|
||||
import Diffing.Algorithm
|
||||
import Data.Align.Generic
|
||||
import Interpreter
|
||||
import Parser
|
||||
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
module Syntax where
|
||||
|
||||
import Algorithm
|
||||
import Diffing.Algorithm
|
||||
import Data.Aeson (ToJSON, (.=))
|
||||
import Data.Align.Generic
|
||||
import Data.Foldable (toList)
|
||||
|
@ -1,7 +1,7 @@
|
||||
{-# LANGUAGE DataKinds #-}
|
||||
module Data.RandomWalkSimilarity.Spec where
|
||||
|
||||
import Algorithm
|
||||
import Diffing.Algorithm
|
||||
import Data.Array.IArray
|
||||
import Data.Bifunctor
|
||||
import Data.Diff
|
||||
|
Loading…
Reference in New Issue
Block a user