2015-11-18 01:44:16 +03:00
|
|
|
module Main where
|
|
|
|
|
2015-11-27 20:22:05 +03:00
|
|
|
import Categorizable
|
2015-11-18 22:45:23 +03:00
|
|
|
import Diff
|
2015-11-27 20:22:05 +03:00
|
|
|
import Interpreter
|
2015-12-17 00:21:49 +03:00
|
|
|
import qualified Parsers as P
|
2015-11-18 22:45:23 +03:00
|
|
|
import Syntax
|
2015-12-03 05:40:34 +03:00
|
|
|
import Range
|
2015-12-18 16:23:28 +03:00
|
|
|
import qualified PatchOutput
|
2015-12-01 19:33:16 +03:00
|
|
|
import Split
|
2015-11-27 20:41:38 +03:00
|
|
|
import Term
|
2015-11-27 20:42:00 +03:00
|
|
|
import Unified
|
2015-12-24 08:20:47 +03:00
|
|
|
import Source
|
2015-11-18 22:45:23 +03:00
|
|
|
import Control.Comonad.Cofree
|
2015-12-07 22:34:58 +03:00
|
|
|
import qualified Data.ByteString.Char8 as B1
|
2015-12-01 19:15:13 +03:00
|
|
|
import Options.Applicative
|
2015-12-16 09:28:40 +03:00
|
|
|
import System.Directory
|
2015-12-03 23:10:49 +03:00
|
|
|
import System.FilePath
|
2015-12-15 21:29:58 +03:00
|
|
|
import qualified Data.Text as T
|
2015-12-29 23:13:57 +03:00
|
|
|
import qualified Data.Text.Lazy.IO as TextIO
|
2015-12-16 08:39:07 +03:00
|
|
|
import qualified System.IO as IO
|
2015-12-30 01:34:28 +03:00
|
|
|
import qualified Data.Text.ICU.Detect as Detect
|
|
|
|
import qualified Data.Text.ICU.Convert as Convert
|
2016-01-04 22:48:55 +03:00
|
|
|
import Data.Bifunctor.Join
|
2015-12-09 18:11:30 +03:00
|
|
|
|
2016-01-12 19:35:13 +03:00
|
|
|
-- | The available types of diff rendering.
|
2016-01-14 21:12:28 +03:00
|
|
|
data Format = Unified | Split | Patch
|
2015-12-01 19:08:04 +03:00
|
|
|
|
2016-01-12 19:35:13 +03:00
|
|
|
-- | The command line arguments to the application.
|
2016-01-14 21:12:28 +03:00
|
|
|
data Arguments = Arguments { format :: Format, output :: Maybe FilePath, sourceA :: FilePath, sourceB :: FilePath }
|
2015-12-01 19:08:04 +03:00
|
|
|
|
2016-01-12 19:35:13 +03:00
|
|
|
-- | A parser for the application's command-line arguments.
|
2016-01-06 22:01:41 +03:00
|
|
|
arguments :: Parser Arguments
|
|
|
|
arguments = Arguments
|
2015-12-01 19:32:52 +03:00
|
|
|
<$> (flag Split Unified (long "unified" <> help "output a unified diff")
|
2015-12-18 01:19:13 +03:00
|
|
|
<|> flag Split Patch (long "patch" <> help "output a patch(1)-compatible diff")
|
2015-12-01 19:32:52 +03:00
|
|
|
<|> flag' Split (long "split" <> help "output a split diff"))
|
2016-01-12 19:05:10 +03:00
|
|
|
<*> optional (strOption (long "output" <> short 'o' <> help "output directory for split diffs, defaulting to stdout if unspecified"))
|
2015-12-16 07:20:33 +03:00
|
|
|
<*> strArgument (metavar "FILE a")
|
|
|
|
<*> strArgument (metavar "FILE b")
|
2015-12-01 19:15:13 +03:00
|
|
|
|
2015-11-18 01:44:16 +03:00
|
|
|
main :: IO ()
|
2015-11-20 19:36:54 +03:00
|
|
|
main = do
|
2015-12-01 19:19:40 +03:00
|
|
|
arguments <- execParser opts
|
2015-12-07 22:23:32 +03:00
|
|
|
let (sourceAPath, sourceBPath) = (sourceA arguments, sourceB arguments)
|
2016-01-04 22:50:16 +03:00
|
|
|
sources <- sequence $ readAndTranscodeFile <$> Join (sourceAPath, sourceBPath)
|
2016-01-04 22:48:55 +03:00
|
|
|
let parse = (P.parserForType . T.pack . takeExtension) sourceAPath
|
|
|
|
terms <- sequence $ parse <$> sources
|
2016-01-12 19:01:13 +03:00
|
|
|
let replaceLeaves = breakDownLeavesByWord <$> sources
|
2016-01-04 22:48:55 +03:00
|
|
|
printDiff arguments (runJoin sources) (runJoin $ replaceLeaves <*> terms)
|
2015-12-31 02:00:44 +03:00
|
|
|
where opts = info (helper <*> arguments)
|
|
|
|
(fullDesc <> progDesc "Diff some things" <> header "semantic-diff - diff semantically")
|
|
|
|
|
2016-01-12 19:35:13 +03:00
|
|
|
-- | Print a diff, given the command-line arguments, source files, and terms.
|
2016-01-06 22:01:41 +03:00
|
|
|
printDiff :: Arguments -> (Source Char, Source Char) -> (Term T.Text Info, Term T.Text Info) -> IO ()
|
2016-01-14 21:12:28 +03:00
|
|
|
printDiff arguments (aSource, bSource) (aTerm, bTerm) = case format arguments of
|
2015-12-31 02:00:44 +03:00
|
|
|
Unified -> do
|
|
|
|
rendered <- unified diff aSource bSource
|
|
|
|
B1.putStr rendered
|
|
|
|
Split -> do
|
|
|
|
rendered <- split diff aSource bSource
|
|
|
|
case output arguments of
|
|
|
|
Just path -> do
|
|
|
|
isDir <- doesDirectoryExist path
|
|
|
|
let outputPath = if isDir
|
|
|
|
then path </> (takeFileName (sourceB arguments) -<.> ".html")
|
|
|
|
else path
|
|
|
|
IO.withFile outputPath IO.WriteMode (write rendered)
|
|
|
|
Nothing -> TextIO.putStr rendered
|
2016-01-12 19:05:10 +03:00
|
|
|
Patch -> putStr $ PatchOutput.patch diff aSource bSource
|
2015-12-31 02:00:44 +03:00
|
|
|
where diff = interpret comparable aTerm bTerm
|
|
|
|
write rendered h = TextIO.hPutStr h rendered
|
2015-12-14 20:08:33 +03:00
|
|
|
|
2016-01-12 19:35:13 +03:00
|
|
|
-- | Replace every string leaf with leaves of the words in the string.
|
2016-01-12 19:01:13 +03:00
|
|
|
breakDownLeavesByWord :: Source Char -> Term T.Text Info -> Term T.Text Info
|
|
|
|
breakDownLeavesByWord source = cata replaceIn
|
2015-12-14 20:09:21 +03:00
|
|
|
where
|
2016-01-12 18:59:13 +03:00
|
|
|
replaceIn info@(Info range categories) (Leaf _) | ranges <- rangesAndWordsInSource range, length ranges > 1 = info :< (Indexed $ makeLeaf categories <$> ranges)
|
2016-01-12 18:53:45 +03:00
|
|
|
replaceIn info syntax = info :< syntax
|
2016-01-12 18:59:13 +03:00
|
|
|
rangesAndWordsInSource range = rangesAndWordsFrom (start range) (toList $ slice range source)
|
2015-12-29 23:13:57 +03:00
|
|
|
makeLeaf categories (range, substring) = Info range categories :< Leaf (T.pack substring)
|
2015-12-30 01:34:28 +03:00
|
|
|
|
2016-01-12 19:35:13 +03:00
|
|
|
-- | Read the file and convert it to Unicode.
|
2015-12-30 01:34:28 +03:00
|
|
|
readAndTranscodeFile :: FilePath -> IO (Source Char)
|
|
|
|
readAndTranscodeFile path = fromText <$> do
|
|
|
|
text <- B1.readFile path
|
|
|
|
match <- Detect.detectCharset text
|
|
|
|
converter <- Convert.open match Nothing
|
|
|
|
return $ Convert.toUnicode converter text
|