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

85 lines
3.4 KiB
Haskell
Raw Normal View History

2015-11-18 01:44:16 +03:00
module Main where
2015-11-27 20:22:05 +03:00
import Categorizable
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
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
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
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
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.Biapplicative
import Data.Bifunctor.Join
2015-12-18 01:19:05 +03:00
data Renderer = Unified | Split | Patch
2015-12-01 19:08:04 +03:00
data Arguments = Arguments { renderer :: Renderer, output :: Maybe FilePath, sourceA :: FilePath, sourceB :: FilePath }
2015-12-01 19:08:04 +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")
<|> 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"))
<*> (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
let replaceLeaves = replaceLeavesWithWordBranches <$> sources
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")
printDiff :: Arguments -> (Source Char, Source Char) -> (Term T.Text Info, Term T.Text Info) -> IO ()
2015-12-31 02:00:44 +03:00
printDiff arguments (aSource, bSource) (aTerm, bTerm) = case renderer arguments of
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
Patch -> do
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
replaceLeavesWithWordBranches :: Source Char -> Term T.Text Info -> Term T.Text Info
replaceLeavesWithWordBranches source = cata replaceIn
where
replaceIn info@(Info range categories) (Leaf _) | ranges <- rangesAndWordsFrom (start range) (toList $ slice range source), length ranges > 1 = info :< (Indexed $ makeLeaf categories <$> ranges)
replaceIn info syntax = info :< syntax
makeLeaf categories (range, substring) = Info range categories :< Leaf (T.pack substring)
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