mirror of
https://github.com/github/semantic.git
synced 2024-12-29 18:06:14 +03:00
Import the command modules directly.
This commit is contained in:
parent
f172c1b6ae
commit
37e21217e2
@ -2,7 +2,8 @@
|
||||
module SemanticDiff (main) where
|
||||
|
||||
import Arguments
|
||||
import Command
|
||||
import Command.Diff
|
||||
import Command.Parse
|
||||
import Prologue hiding (fst, snd)
|
||||
import Data.String
|
||||
import Data.Functor.Both
|
||||
|
@ -2,7 +2,8 @@
|
||||
module IntegrationSpec where
|
||||
|
||||
import Category as C
|
||||
import Command
|
||||
import Command.Diff
|
||||
import Command.Parse
|
||||
import Data.Functor.Both
|
||||
import Data.Record
|
||||
import qualified Data.Text as T
|
||||
@ -39,7 +40,7 @@ spec = parallel $ do
|
||||
examples <- runIO $ examples directory
|
||||
traverse_ runTest examples
|
||||
runTest ParseExample{..} = it ("parses " <> file) $ testParse file parseOutput
|
||||
runTest DiffExample{..} = it ("diffs " <> diffOutput) $ testDiff (Renderer.sExpression TreeOnly) (both fileA fileB) diffOutput
|
||||
runTest DiffExample{..} = it ("diffs " <> diffOutput) $ testDiff ((SExpressionOutput .) . Renderer.sExpression TreeOnly) (both fileA fileB) diffOutput
|
||||
|
||||
data Example = DiffExample { fileA :: FilePath, fileB :: FilePath, diffOutput :: FilePath }
|
||||
| ParseExample { file :: FilePath, parseOutput :: FilePath }
|
||||
|
@ -3,7 +3,8 @@ module TOCSpec where
|
||||
|
||||
import Data.Aeson
|
||||
import Category as C
|
||||
import Command
|
||||
import Command.Diff
|
||||
import Command.Parse
|
||||
import Data.Functor.Both
|
||||
import Data.Functor.Listable
|
||||
import Data.RandomWalkSimilarity
|
||||
@ -124,7 +125,7 @@ diffOutput :: Both SourceBlob -> IO ByteString
|
||||
diffOutput sourceBlobs = do
|
||||
let parser = parserForFilepath (path (fst sourceBlobs))
|
||||
diff <- diffFiles parser sourceBlobs
|
||||
pure $ concatOutputs [toc sourceBlobs diff]
|
||||
pure $ concatOutputs [TOCOutput (toc sourceBlobs diff)]
|
||||
|
||||
numTocSummaries :: Diff' -> Int
|
||||
numTocSummaries diff = Prologue.length $ filter (not . isErrorSummary) (diffTOC blankDiffBlobs diff)
|
||||
|
Loading…
Reference in New Issue
Block a user