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-09 17:50:55 +03:00
import qualified Parser as P
2015-11-18 22:45:23 +03:00
import Syntax
2015-12-03 05:40:34 +03:00
import Range
2015-12-01 19:33:16 +03:00
import Split
2015-11-27 20:41:38 +03:00
import Term
2015-12-09 17:58:15 +03:00
import TreeSitter
2015-11-27 20:42:00 +03:00
import Unified
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
import qualified Data.ByteString.Lazy as B2
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-16 08:39:07 +03:00
import qualified System.IO as IO
2015-11-18 22:45:23 +03:00
2015-12-16 07:23:45 +03:00
data Renderer = Unified | Split
2015-12-01 19:08:04 +03:00
2015-12-16 07:31:36 +03:00
data Argument = Argument { renderer :: Renderer , output :: Maybe FilePath , sourceA :: FilePath , sourceB :: FilePath }
2015-12-01 19:08:04 +03:00
2015-12-01 19:15:13 +03:00
arguments :: Parser Argument
arguments = Argument
2015-12-01 19:32:52 +03:00
<$> ( flag Split Unified ( long " unified " <> help " output a unified diff " )
<|> flag' Split ( long " split " <> help " output a split diff " ) )
2015-12-16 09:37:05 +03:00
<*> ( Just <$> ( strOption ( long " output " <> short 'o' <> help " output directory for split diffs, defaulting to stdout if unspecified " ) ) <|> flag' Nothing ( internal <> hidden ) )
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 )
aContents <- readFile sourceAPath
bContents <- readFile sourceBPath
2015-12-09 18:36:37 +03:00
( aTerm , bTerm ) <- let parse = ( parserForType . takeExtension ) sourceAPath in do
aTerm <- parse aContents
bTerm <- parse bContents
2015-12-14 20:15:28 +03:00
return ( replaceLeavesWithWordBranches aContents aTerm , replaceLeavesWithWordBranches bContents bTerm )
2015-12-07 22:34:58 +03:00
let diff = interpret comparable aTerm bTerm in
2015-12-16 07:24:04 +03:00
case renderer arguments of
2015-12-07 22:34:58 +03:00
Unified -> do
2015-12-16 08:26:13 +03:00
rendered <- unified diff aContents bContents
B1 . putStr rendered
2015-12-07 22:34:58 +03:00
Split -> do
2015-12-16 08:26:13 +03:00
rendered <- split diff aContents bContents
2015-12-16 08:43:13 +03:00
case output arguments of
2015-12-16 09:28:40 +03:00
Just path -> do
isDir <- doesDirectoryExist path
IO . withFile ( if isDir then path </> ( takeFileName $ replaceExtension " .html " sourceBPath ) else path ) IO . WriteMode ( write rendered )
2015-12-16 08:43:13 +03:00
Nothing -> B2 . putStr rendered
2015-12-07 22:34:58 +03:00
where
2015-12-01 19:19:40 +03:00
opts = info ( helper <*> arguments )
( fullDesc <> progDesc " Diff some things " <> header " semantic-diff - diff semantically " )
2015-12-16 09:22:48 +03:00
write rendered h = B2 . hPut h rendered
2015-11-25 00:51:53 +03:00
2015-12-09 18:36:37 +03:00
parserForType :: String -> P . Parser
parserForType mediaType = maybe P . lineByLineParser parseTreeSitterFile $ case mediaType of
2015-12-05 00:25:01 +03:00
" .h " -> Just ts_language_c
" .c " -> Just ts_language_c
" .js " -> Just ts_language_javascript
2015-12-03 23:10:49 +03:00
_ -> Nothing
2015-12-14 20:08:33 +03:00
2015-12-14 20:15:28 +03:00
replaceLeavesWithWordBranches :: String -> Term String Info -> Term String Info
2015-12-14 20:37:07 +03:00
replaceLeavesWithWordBranches source term = replaceIn source 0 term
2015-12-14 20:09:21 +03:00
where
2015-12-15 01:22:53 +03:00
replaceIn source startIndex ( info @ ( Info range categories ) :< syntax ) | substring <- substring ( offsetRange ( negate startIndex ) range ) source = info :< case syntax of
Leaf _ | ranges <- rangesAndWordsFrom ( start range ) substring , length ranges > 1 -> Indexed $ makeLeaf substring startIndex categories <$> ranges
2015-12-14 22:40:30 +03:00
Indexed i -> Indexed $ replaceIn substring ( start range ) <$> i
Fixed f -> Fixed $ replaceIn substring ( start range ) <$> f
Keyed k -> Keyed $ replaceIn substring ( start range ) <$> k
2015-12-14 20:17:30 +03:00
_ -> syntax
2015-12-15 01:22:53 +03:00
makeLeaf source startIndex categories ( range , substring ) = Info range categories :< Leaf substring