1
1
mirror of https://github.com/github/semantic.git synced 2024-12-11 08:45:48 +03:00

Export a parseBlobs helper from Semantic.

This commit is contained in:
Rob Rix 2017-05-31 12:35:18 -04:00
parent 4b5ad434e8
commit 514a55a62b
2 changed files with 7 additions and 4 deletions

View File

@ -1,6 +1,7 @@
{-# LANGUAGE GADTs #-}
module Semantic
( parseBlob
( parseBlobs
, parseBlob
, diffBlobPair
, diffAndRenderTermPair
) where
@ -28,6 +29,9 @@ import Term
-- - Built in concurrency where appropriate.
-- - Easy to consume this interface from other application (e.g a cmdline or web server app).
parseBlobs :: (Monoid output, StringConv output ByteString) => TermRenderer output -> [SourceBlob] -> Task ByteString
parseBlobs renderer = fmap toS . distributeFoldMap (parseBlob renderer) . filter (not . nonExistentBlob)
-- | A task to parse a 'SourceBlob' and render the resulting 'Term'.
parseBlob :: TermRenderer output -> SourceBlob -> Task output
parseBlob renderer blob@SourceBlob{..} = case renderer of

View File

@ -14,14 +14,13 @@ import Prologue hiding (concurrently, fst, snd, readFile)
import qualified Data.ByteString as B
import qualified Paths_semantic_diff as Library (version)
import qualified Semantic.Task as Task
import Source (nonExistentBlob)
import System.Directory
import System.Environment
import System.FilePath.Posix (takeFileName, (-<.>))
import System.IO.Error (IOError)
import System.IO (stdin)
import Text.Regex
import qualified Semantic (parseBlob, diffBlobPair)
import qualified Semantic (parseBlobs, diffBlobPair)
main :: IO ()
main = do
@ -62,7 +61,7 @@ runParse ParseArguments{..} = do
ParsePaths paths -> traverse (uncurry readFile) paths
ParseCommit sha paths -> readFilesAtSHA gitDir alternateObjectDirs paths sha
ParseStdin -> readBlobsFromHandle stdin
Task.runTask . fmap toS $ Task.distributeFoldMap (Semantic.parseBlob parseTreeRenderer) (filter (not . nonExistentBlob) blobs)
Task.runTask (Semantic.parseBlobs parseTreeRenderer blobs)
-- | A parser for the application's command-line arguments.
arguments :: FilePath -> [FilePath] -> ParserInfo Arguments