{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TupleSections #-}
module Retrie.Run
( runScript
, runScriptWithModifiedOptions
, execute
, run
, WriteFn
, writeCountLines
, writeDiff
, writeSearch
, writeExtract
) where
import Control.Monad.State.Strict
import Data.Char
import Data.List
import Data.Monoid
import System.Console.ANSI
import Retrie.CPP
import Retrie.ExactPrint
import Retrie.GHC
import Retrie.Monad
import Retrie.Options
import Retrie.Pretty
import Retrie.Replace
import Retrie.Util
runScript :: (Options -> IO (Retrie ())) -> IO ()
runScript f = runScriptWithModifiedOptions (\opts -> (opts,) <$> f opts)
runScriptWithModifiedOptions :: (Options -> IO (Options, Retrie ())) -> IO ()
runScriptWithModifiedOptions f = do
opts <- parseOptions mempty
(opts', retrie) <- f opts
execute opts' retrie
execute :: Options -> Retrie () -> IO ()
execute opts@Options{..} retrie0 = do
let retrie = iterateR iterateN retrie0
case executionMode of
ExecDryRun -> void $ run (writeDiff opts) id opts retrie
ExecExtract -> void $ run (writeExtract opts) id opts retrie
ExecRewrite -> do
s <- mconcat <$> run writeCountLines id opts retrie
when (verbosity > Silent) $
putStrLn $ "Done! " ++ show (getSum s) ++ " lines changed."
ExecSearch -> void $ run (writeSearch opts) id opts retrie
type WriteFn a b = [Replacement] -> String -> a -> IO b
run
:: Monoid b
=> (FilePath -> WriteFn a b)
-> (IO b -> IO c)
-> Options -> Retrie a -> IO [c]
run writeFn wrapper opts@Options{..} r = do
fps <- getTargetFiles opts (getGroundTerms r)
forFn opts fps $ \ fp -> wrapper $ do
debugPrint verbosity "Processing:" [fp]
p <- trySync $ parseCPPFile (parseContent fixityEnv) fp
case p of
Left ex -> do
when (verbosity > Silent) $ print ex
return mempty
Right cpp -> runOneModule (writeFn fp) opts r cpp
runOneModule
:: Monoid b
=> WriteFn a b
-> Options
-> Retrie a
-> CPP AnnotatedModule
-> IO b
runOneModule writeFn Options{..} r cpp = do
(x, cpp', changed) <- runRetrie fixityEnv r cpp
case changed of
NoChange -> return mempty
Change repls imports -> do
let cpp'' = addImportsCPP (additionalImports:imports) cpp'
writeFn repls (printCPP repls cpp'') x
writeCountLines :: FilePath -> WriteFn a (Sum Int)
writeCountLines fp reps str _ = do
let lc = lineCount $ map replLocation reps
putStrLn $ "Writing: " ++ fp ++ " (" ++ show lc ++ " lines changed)"
writeFile fp str
return $ Sum lc
writeDiff :: Options -> FilePath -> WriteFn a (Sum Int)
writeDiff Options{..} fp repls _ _ = do
fl <- linesMap fp
forM_ repls $ \Replacement{..} -> do
let ppLines lineStart color = unlines
. map (lineStart ++)
. ppRepl fl replLocation
. colorise Vivid color
putStrLn $ mconcat
[ ppSrcSpan colorise replLocation
, "\n"
, ppLines "- " Red replOriginal
, ppLines "+ " Green replReplacement
]
return $ Sum $ lineCount $ map replLocation repls
writeSearch :: Options -> FilePath -> WriteFn a ()
writeSearch Options{..} fp repls _ _ = do
fl <- linesMap fp
forM_ repls $ \Replacement{..} ->
putStrLn $ mconcat
[ ppSrcSpan colorise replLocation
, ppLine
$ ppRepl fl replLocation
$ colorise Vivid Red replOriginal
]
where
ppLine [] = ""
ppLine [x] = strip x
ppLine xs = '\n': dropWhileEnd isSpace (unlines xs)
writeExtract :: Options -> FilePath -> WriteFn a ()
writeExtract Options{..} _ repls _ _ = do
forM_ repls $ \Replacement{..} -> do
putStrLn $ mconcat
[ ppSrcSpan colorise replLocation
, strip replReplacement
]