mirror of
https://github.com/github/semantic.git
synced 2024-12-26 08:25:19 +03:00
Merge branch 'master' into factor-out-packages
# Conflicts: # semantic-diff.cabal
This commit is contained in:
commit
bbf76ad1e6
@ -25,17 +25,19 @@ library
|
||||
, Row
|
||||
, Data.OrderedMap
|
||||
, Patch
|
||||
, PatchOutput
|
||||
, Renderer
|
||||
, Renderer.Patch
|
||||
, Renderer.Split
|
||||
, Renderer.Unified
|
||||
, SES
|
||||
, Category
|
||||
, Term
|
||||
, Range
|
||||
, Split
|
||||
, Unified
|
||||
, Parser
|
||||
, Renderer
|
||||
, TreeSitter
|
||||
, Source
|
||||
, Control.Monad.Free
|
||||
, Control.Comonad.Cofree
|
||||
build-depends: base >= 4.8 && < 5
|
||||
, bifunctors
|
||||
, blaze-html
|
||||
@ -45,7 +47,6 @@ library
|
||||
, containers
|
||||
, directory
|
||||
, filepath
|
||||
, free
|
||||
, mtl
|
||||
, rainbow
|
||||
, semigroups
|
||||
@ -72,7 +73,6 @@ executable semantic-diff
|
||||
, containers
|
||||
, directory
|
||||
, filepath
|
||||
, free
|
||||
, optparse-applicative
|
||||
, semantic-diff
|
||||
, text >= 1.2.1.3
|
||||
@ -108,7 +108,6 @@ test-suite semantic-diff-test
|
||||
, containers
|
||||
, deepseq
|
||||
, filepath
|
||||
, free
|
||||
, Glob
|
||||
, hspec >= 2.1.10
|
||||
, QuickCheck >= 2.8.1
|
||||
|
17
src/Control/Comonad/Cofree.hs
Normal file
17
src/Control/Comonad/Cofree.hs
Normal file
@ -0,0 +1,17 @@
|
||||
{-# LANGUAGE UndecidableInstances #-}
|
||||
module Control.Comonad.Cofree where
|
||||
|
||||
data Cofree functor annotation = annotation :< (functor (Cofree functor annotation))
|
||||
deriving (Functor, Foldable, Traversable)
|
||||
|
||||
instance (Eq annotation, Eq (functor (Cofree functor annotation))) => Eq (Cofree functor annotation) where
|
||||
a :< f == b :< g = a == b && f == g
|
||||
|
||||
instance (Show annotation, Show (functor (Cofree functor annotation))) => Show (Cofree functor annotation) where
|
||||
showsPrec n (a :< f) = showsPrec n a . (" :< " ++) . showsPrec n f
|
||||
|
||||
unwrap :: Cofree functor annotation -> functor (Cofree functor annotation)
|
||||
unwrap (_ :< f) = f
|
||||
|
||||
unfold :: Functor functor => (seed -> (annotation, functor seed)) -> seed -> Cofree functor annotation
|
||||
unfold grow seed = case grow seed of (annotation, functor) -> annotation :< (unfold grow <$> functor)
|
18
src/Control/Monad/Free.hs
Normal file
18
src/Control/Monad/Free.hs
Normal file
@ -0,0 +1,18 @@
|
||||
{-# LANGUAGE UndecidableInstances #-}
|
||||
module Control.Monad.Free where
|
||||
|
||||
data Free functor pure = Free (functor (Free functor pure)) | Pure pure
|
||||
deriving (Functor, Foldable, Traversable)
|
||||
|
||||
instance (Eq pure, Eq (functor (Free functor pure))) => Eq (Free functor pure) where
|
||||
Pure a == Pure b = a == b
|
||||
Free f == Free g = f == g
|
||||
_ == _ = False
|
||||
|
||||
instance (Show pure, Show (functor (Free functor pure))) => Show (Free functor pure) where
|
||||
showsPrec n (Pure a) = ("Pure " ++) . showsPrec n a
|
||||
showsPrec n (Free f) = ("Free " ++) . showsPrec n f
|
||||
|
||||
iter :: Functor functor => (functor pure -> pure) -> Free functor pure -> pure
|
||||
iter _ (Pure a) = a
|
||||
iter f (Free g) = f (iter f <$> g)
|
@ -4,13 +4,13 @@ import Diffing
|
||||
import qualified Data.ByteString.Char8 as B1
|
||||
import Parser
|
||||
import Source
|
||||
import Split
|
||||
import Unified
|
||||
import System.Directory
|
||||
import System.FilePath
|
||||
import qualified System.IO as IO
|
||||
import qualified Data.Text.Lazy.IO as TextIO
|
||||
import qualified PatchOutput
|
||||
import qualified Renderer.Patch as P
|
||||
import Renderer.Split
|
||||
import Renderer.Unified
|
||||
import Rainbow
|
||||
|
||||
-- | The available types of diff rendering.
|
||||
@ -34,5 +34,5 @@ printDiff parser arguments sources = case format arguments of
|
||||
let outputPath = if isDir
|
||||
then path </> (takeFileName outputPath -<.> ".html")
|
||||
else path
|
||||
IO.withFile outputPath IO.WriteMode (flip TextIO.hPutStr rendered)
|
||||
Patch -> putStr =<< diffFiles parser PatchOutput.patch sources
|
||||
IO.withFile outputPath IO.WriteMode (`TextIO.hPutStr` rendered)
|
||||
Patch -> putStr =<< diffFiles parser P.patch sources
|
||||
|
@ -1,4 +1,4 @@
|
||||
module PatchOutput (
|
||||
module Renderer.Patch (
|
||||
patch,
|
||||
hunks
|
||||
) where
|
||||
@ -9,7 +9,7 @@ import Range
|
||||
import Renderer
|
||||
import Row
|
||||
import Source hiding ((++), break)
|
||||
import Split
|
||||
import Renderer.Split
|
||||
import Control.Comonad.Cofree
|
||||
import Control.Monad.Free
|
||||
import Data.Maybe
|
@ -1,5 +1,5 @@
|
||||
{-# LANGUAGE FlexibleInstances #-}
|
||||
module Split where
|
||||
module Renderer.Split where
|
||||
|
||||
import Prelude hiding (div, head, span)
|
||||
import Category
|
@ -1,4 +1,4 @@
|
||||
module Unified (unified, substring) where
|
||||
module Renderer.Unified (unified, substring) where
|
||||
|
||||
import Diff
|
||||
import Patch
|
@ -1,10 +1,10 @@
|
||||
module CorpusSpec where
|
||||
|
||||
import Diffing
|
||||
import PatchOutput
|
||||
import Renderer
|
||||
import Split
|
||||
import Unified
|
||||
import qualified Renderer.Patch as P
|
||||
import qualified Renderer.Split as Split
|
||||
import qualified Renderer.Unified as Unified
|
||||
|
||||
import qualified Source as S
|
||||
import Control.DeepSeq
|
||||
@ -43,11 +43,11 @@ spec = parallel $ do
|
||||
correctTests paths@(_, _, Nothing, Nothing, Nothing) = testsForPaths paths
|
||||
correctTests paths = List.filter (\(_, _, _, _, output) -> isJust output) $ testsForPaths paths
|
||||
testsForPaths :: (FilePath, FilePath, Maybe FilePath, Maybe FilePath, Maybe FilePath) -> [(String, Renderer a String, FilePath, FilePath, Maybe FilePath)]
|
||||
testsForPaths (a, b, patch, split, unified) = [ ("patch", PatchOutput.patch, a, b, patch), ("split", testSplit, a, b, split), ("unified", testUnified, a, b, unified) ]
|
||||
testsForPaths (a, b, patch, split, unified) = [ ("patch", P.patch, a, b, patch), ("split", testSplit, a, b, split), ("unified", testUnified, a, b, unified) ]
|
||||
testSplit :: Renderer a String
|
||||
testSplit diff sources = TL.unpack $ Split.split diff sources
|
||||
testUnified :: Renderer a String
|
||||
testUnified diff sources = B1.unpack $ mconcat $ chunksToByteStrings toByteStringsColors0 $ unified diff sources
|
||||
testUnified diff sources = B1.unpack $ mconcat $ chunksToByteStrings toByteStringsColors0 $ Unified.unified diff sources
|
||||
|
||||
|
||||
-- | Return all the examples from the given directory. Examples are expected to
|
||||
|
@ -1,7 +1,7 @@
|
||||
module PatchOutputSpec where
|
||||
|
||||
import Diff
|
||||
import PatchOutput
|
||||
import Renderer.Patch
|
||||
import Range
|
||||
import Source
|
||||
import Syntax
|
||||
|
@ -14,7 +14,7 @@ import Source hiding ((++))
|
||||
import Line
|
||||
import Row
|
||||
import Range
|
||||
import Split
|
||||
import Renderer.Split
|
||||
import Syntax
|
||||
import ArbitraryTerm ()
|
||||
|
||||
|
Loading…
Reference in New Issue
Block a user