mirror of
https://github.com/github/semantic.git
synced 2024-11-28 10:15:55 +03:00
Merge pull request #641 from github/🔥-diff-output-module
🔥 the DiffOutput module
This commit is contained in:
commit
320a4cefef
@ -25,7 +25,6 @@ library
|
||||
, Diff
|
||||
, Diff.Arbitrary
|
||||
, Diffing
|
||||
, DiffOutput
|
||||
, Info
|
||||
, Interpreter
|
||||
, Language
|
||||
|
@ -1,52 +0,0 @@
|
||||
module DiffOutput where
|
||||
|
||||
import Category
|
||||
import Prologue
|
||||
import qualified Data.Text.IO as TextIO
|
||||
import Data.Functor.Both
|
||||
import Data.Record
|
||||
import Diffing
|
||||
import Info
|
||||
import Parser
|
||||
import Range
|
||||
import qualified Renderer.JSON as J
|
||||
import qualified Renderer.Patch as P
|
||||
import qualified Renderer.Summary as S
|
||||
import Renderer
|
||||
import Renderer.Split
|
||||
import Source
|
||||
import System.Directory
|
||||
import System.FilePath
|
||||
import qualified System.IO as IO
|
||||
|
||||
-- | Returns a rendered diff given a parser, diff arguments and two source blobs.
|
||||
textDiff :: (Eq (Record fields), HasField fields Category, HasField fields Cost, HasField fields Range) => Parser fields -> DiffArguments -> Both SourceBlob -> IO Text
|
||||
textDiff parser arguments sources = case format arguments of
|
||||
Split -> diffFiles parser split sources
|
||||
Patch -> diffFiles parser P.patch sources
|
||||
JSON -> diffFiles parser J.json sources
|
||||
Summary -> diffFiles parser S.summary sources
|
||||
|
||||
-- | Returns a truncated diff given diff arguments and two source blobs.
|
||||
truncatedDiff :: DiffArguments -> Both SourceBlob -> IO Text
|
||||
truncatedDiff arguments sources = case format arguments of
|
||||
Split -> pure ""
|
||||
Patch -> pure $ P.truncatePatch arguments sources
|
||||
JSON -> pure "{}"
|
||||
Summary -> pure ""
|
||||
|
||||
-- | Prints a rendered diff to stdio or a filepath given a parser, diff arguments and two source blobs.
|
||||
printDiff :: (Eq (Record fields), HasField fields Category, HasField fields Cost, HasField fields Range) => Parser fields -> DiffArguments -> Both SourceBlob -> IO ()
|
||||
printDiff parser arguments sources = case format arguments of
|
||||
Split -> put (output arguments) =<< diffFiles parser split sources
|
||||
where
|
||||
put Nothing rendered = TextIO.putStr rendered
|
||||
put (Just path) rendered = do
|
||||
isDir <- doesDirectoryExist path
|
||||
let outputPath = if isDir
|
||||
then path </> (takeFileName outputPath -<.> ".html")
|
||||
else path
|
||||
IO.withFile outputPath IO.WriteMode (`TextIO.hPutStr` rendered)
|
||||
Patch -> TextIO.putStr =<< diffFiles parser P.patch sources
|
||||
JSON -> TextIO.putStr =<< diffFiles parser J.json sources
|
||||
Summary -> TextIO.putStr =<< diffFiles parser S.summary sources
|
@ -7,6 +7,7 @@ import Data.Functor.Both
|
||||
import Data.Functor.Foldable
|
||||
import Data.Record
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Text.IO as TextIO
|
||||
import qualified Data.Text.ICU.Detect as Detect
|
||||
import qualified Data.Text.ICU.Convert as Convert
|
||||
import Data.These
|
||||
@ -19,9 +20,15 @@ import Parser
|
||||
import Patch
|
||||
import Range
|
||||
import Renderer
|
||||
import Renderer.JSON
|
||||
import Renderer.Patch
|
||||
import Renderer.Split
|
||||
import Renderer.Summary
|
||||
import Source hiding ((++))
|
||||
import Syntax
|
||||
import System.Directory
|
||||
import System.FilePath
|
||||
import qualified System.IO as IO
|
||||
import Term
|
||||
import TreeSitter
|
||||
import Text.Parser.TreeSitter.Language
|
||||
@ -106,3 +113,33 @@ diffCostWithCachedTermCosts :: HasField fields Cost => Diff leaf (Record fields)
|
||||
diffCostWithCachedTermCosts diff = unCost $ case runFree diff of
|
||||
Free (info :< _) -> sum (cost <$> info)
|
||||
Pure patch -> sum (cost . extract <$> patch)
|
||||
|
||||
|
||||
-- | Returns a rendered diff given a parser, diff arguments and two source blobs.
|
||||
textDiff :: (Eq (Record fields), HasField fields Category, HasField fields Cost, HasField fields Range) => Parser fields -> DiffArguments -> Both SourceBlob -> IO Text
|
||||
textDiff parser arguments sources = case format arguments of
|
||||
Split -> diffFiles parser split sources
|
||||
Patch -> diffFiles parser patch sources
|
||||
JSON -> diffFiles parser json sources
|
||||
Summary -> diffFiles parser summary sources
|
||||
|
||||
-- | Returns a truncated diff given diff arguments and two source blobs.
|
||||
truncatedDiff :: DiffArguments -> Both SourceBlob -> IO Text
|
||||
truncatedDiff arguments sources = case format arguments of
|
||||
Split -> pure ""
|
||||
Patch -> pure $ truncatePatch arguments sources
|
||||
JSON -> pure "{}"
|
||||
Summary -> pure ""
|
||||
|
||||
-- | Prints a rendered diff to stdio or a filepath given a parser, diff arguments and two source blobs.
|
||||
printDiff :: (Eq (Record fields), HasField fields Category, HasField fields Cost, HasField fields Range) => Parser fields -> DiffArguments -> Both SourceBlob -> IO ()
|
||||
printDiff parser arguments sources = do
|
||||
rendered <- textDiff parser arguments sources
|
||||
case (output arguments) of
|
||||
Nothing -> TextIO.putStr rendered
|
||||
Just path -> do
|
||||
isDir <- doesDirectoryExist path
|
||||
let outputPath = if isDir
|
||||
then path </> (takeFileName outputPath -<.> ".html")
|
||||
else path
|
||||
IO.withFile outputPath IO.WriteMode (`TextIO.hPutStr` rendered)
|
||||
|
Loading…
Reference in New Issue
Block a user