mirror of
https://github.com/github/semantic.git
synced 2024-11-29 02:44:36 +03:00
Port TOCSpec to Command.
This commit is contained in:
parent
6b1459f80d
commit
48ddf53099
@ -3,7 +3,7 @@ module TOCSpec where
|
|||||||
|
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
import Category as C
|
import Category as C
|
||||||
import Command.Diff
|
import Command
|
||||||
import Command.Parse
|
import Command.Parse
|
||||||
import Data.Functor.Both
|
import Data.Functor.Both
|
||||||
import Data.Functor.Listable
|
import Data.Functor.Listable
|
||||||
@ -122,10 +122,10 @@ type Diff' = SyntaxDiff String DefaultFields
|
|||||||
type Term' = SyntaxTerm String DefaultFields
|
type Term' = SyntaxTerm String DefaultFields
|
||||||
|
|
||||||
diffOutput :: Both SourceBlob -> IO ByteString
|
diffOutput :: Both SourceBlob -> IO ByteString
|
||||||
diffOutput sourceBlobs = do
|
diffOutput blobs = runCommand $ do
|
||||||
let parser = parserForFilepath (path (fst sourceBlobs))
|
terms <- for blobs parseBlob
|
||||||
diff <- diffFiles parser sourceBlobs
|
diff' <- runBothWith diff terms
|
||||||
pure $ concatOutputs [TOCOutput (toc sourceBlobs diff)]
|
toS . encode . unSummaries <$> renderDiffs ToCRenderer [ (blobs, diff') ]
|
||||||
|
|
||||||
numTocSummaries :: Diff' -> Int
|
numTocSummaries :: Diff' -> Int
|
||||||
numTocSummaries diff = Prologue.length $ filter (not . isErrorSummary) (diffTOC blankDiffBlobs diff)
|
numTocSummaries diff = Prologue.length $ filter (not . isErrorSummary) (diffTOC blankDiffBlobs diff)
|
||||||
@ -188,9 +188,9 @@ isMethodOrFunction a = case runCofree (unListableF a) of
|
|||||||
_ -> False
|
_ -> False
|
||||||
|
|
||||||
testDiff :: Both SourceBlob -> IO (Diff (Syntax Text) (Record DefaultFields))
|
testDiff :: Both SourceBlob -> IO (Diff (Syntax Text) (Record DefaultFields))
|
||||||
testDiff sourceBlobs = diffFiles parser sourceBlobs
|
testDiff blobs = runCommand $ do
|
||||||
where
|
terms <- for blobs parseBlob
|
||||||
parser = parserForFilepath (path . fst $ sourceBlobs)
|
runBothWith diff terms
|
||||||
|
|
||||||
blobsForPaths :: Both FilePath -> IO (Both SourceBlob)
|
blobsForPaths :: Both FilePath -> IO (Both SourceBlob)
|
||||||
blobsForPaths paths = do
|
blobsForPaths paths = do
|
||||||
|
Loading…
Reference in New Issue
Block a user