1
1
mirror of https://github.com/github/semantic.git synced 2024-11-24 08:54:07 +03:00

Merge origin/master into git-diff

This commit is contained in:
joshvera 2016-01-15 16:15:44 -05:00
commit 33b2331a23
5 changed files with 20 additions and 20 deletions

View File

@ -8,6 +8,7 @@ import qualified Parsers as P
import Syntax import Syntax
import Range import Range
import qualified PatchOutput import qualified PatchOutput
import Renderer
import Split import Split
import Term import Term
import Unified import Unified
@ -57,7 +58,7 @@ main = do
let parse = (P.parserForType . T.pack . takeExtension) filepath let parse = (P.parserForType . T.pack . takeExtension) filepath
terms <- sequence $ parse <$> sources terms <- sequence $ parse <$> sources
let replaceLeaves = breakDownLeavesByWord <$> sources let replaceLeaves = breakDownLeavesByWord <$> sources
printDiff arguments filepath (runJoin sources) (runJoin $ replaceLeaves <*> terms) printDiff arguments filepath (uncurry diff . runJoin $ replaceLeaves <*> terms) (runJoin sources)
where opts = info (helper <*> arguments) where opts = info (helper <*> arguments)
(fullDesc <> progDesc "Diff some things" <> header "semantic-diff - diff semantically") (fullDesc <> progDesc "Diff some things" <> header "semantic-diff - diff semantically")
@ -79,25 +80,24 @@ fetchFromGitRepo repoPath path sha = join $ withRepository lgFactory repoPath $
return s return s
return $ transcode bytestring return $ transcode bytestring
-- | Print a diff, given the command-line arguments, source files, and terms. -- | Diff two terms.
printDiff :: Arguments -> FilePath -> (Source Char, Source Char) -> (Term T.Text Info, Term T.Text Info) -> IO () diff :: (Eq a, Eq annotation, Categorizable annotation) => Term a annotation -> Term a annotation -> Diff a annotation
printDiff arguments filepath (aSource, bSource) (aTerm, bTerm) = case format arguments of diff = interpret comparable
Unified -> do
rendered <- unified diff aSource bSource -- | Return a renderer from the command-line arguments that will print the diff.
B1.putStr rendered printDiff :: Arguments -> FilePath -> Renderer T.Text (IO ())
Split -> do printDiff arguments filepath diff sources = case format arguments of
rendered <- split diff aSource bSource Unified -> B1.putStr =<< unified diff sources
case output arguments of Split -> put (output arguments) =<< split diff sources
Just path -> do where
put Nothing rendered = TextIO.putStr rendered
put (Just path) rendered = do
isDir <- doesDirectoryExist path isDir <- doesDirectoryExist path
let outputPath = if isDir let outputPath = if isDir
then path </> (takeFileName filepath -<.> ".html") then path </> (takeFileName filepath -<.> ".html")
else path else path
IO.withFile outputPath IO.WriteMode (write rendered) IO.withFile outputPath IO.WriteMode (flip TextIO.hPutStr rendered)
Nothing -> TextIO.putStr rendered Patch -> putStr $ PatchOutput.patch diff sources
Patch -> putStr $ PatchOutput.patch diff aSource bSource
where diff = interpret comparable aTerm bTerm
write rendered h = TextIO.hPutStr h rendered
-- | Replace every string leaf with leaves of the words in the string. -- | Replace every string leaf with leaves of the words in the string.
breakDownLeavesByWord :: Source Char -> Term T.Text Info -> Term T.Text Info breakDownLeavesByWord :: Source Char -> Term T.Text Info -> Term T.Text Info

View File

@ -17,7 +17,7 @@ import Data.Maybe
import Data.Monoid import Data.Monoid
patch :: Renderer a String patch :: Renderer a String
patch diff sourceA sourceB = mconcat $ showHunk (sourceA, sourceB) <$> hunks diff (sourceA, sourceB) patch diff (sourceA, sourceB) = mconcat $ showHunk (sourceA, sourceB) <$> hunks diff (sourceA, sourceB)
data Hunk a = Hunk { offset :: (Sum Int, Sum Int), changes :: [Change a], trailingContext :: [Row a] } data Hunk a = Hunk { offset :: (Sum Int, Sum Int), changes :: [Change a], trailingContext :: [Row a] }
deriving (Eq, Show) deriving (Eq, Show)

View File

@ -4,4 +4,4 @@ import Diff
import Source import Source
-- | A function that will render a diff, given the two source files. -- | A function that will render a diff, given the two source files.
type Renderer a b = Diff a Info -> Source Char -> Source Char -> b type Renderer a b = Diff a Info -> (Source Char, Source Char) -> b

View File

@ -32,7 +32,7 @@ classifyMarkup :: Foldable f => f String -> Markup -> Markup
classifyMarkup categories element = maybe element ((element !) . A.class_ . stringValue . ("category-" ++)) $ maybeFirst categories classifyMarkup categories element = maybe element ((element !) . A.class_ . stringValue . ("category-" ++)) $ maybeFirst categories
split :: Renderer leaf (IO TL.Text) split :: Renderer leaf (IO TL.Text)
split diff before after = return . renderHtml split diff (before, after) = return . renderHtml
. docTypeHtml . docTypeHtml
. ((head $ link ! A.rel "stylesheet" ! A.href "style.css") <>) . ((head $ link ! A.rel "stylesheet" ! A.href "style.css") <>)
. body . body

View File

@ -15,7 +15,7 @@ import qualified Data.OrderedMap as Map
import Rainbow import Rainbow
unified :: Renderer a (IO ByteString) unified :: Renderer a (IO ByteString)
unified diff before after = do unified diff (before, after) = do
renderer <- byteStringMakerFromEnvironment renderer <- byteStringMakerFromEnvironment
return . mconcat . chunksToByteStrings renderer . fst $ iter g mapped where return . mconcat . chunksToByteStrings renderer . fst $ iter g mapped where
mapped = fmap (unifiedPatch &&& range) diff mapped = fmap (unifiedPatch &&& range) diff