forked from ndmitchell/hlint
-
Notifications
You must be signed in to change notification settings - Fork 0
/
Copy pathRefact.hs
88 lines (75 loc) · 3.32 KB
/
Refact.hs
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE LambdaCase #-}
module Refact
( substVars
, toRefactSrcSpan
, toSS, toSSA, toSSAnc
, checkRefactor, refactorPath, runRefactoring
) where
import Control.Exception.Extra
import Control.Monad
import Data.List.NonEmpty qualified as NE
import Data.Maybe
import Data.Version.Extra
import GHC.LanguageExtensions.Type
import System.Console.CmdArgs.Verbosity
import System.Directory.Extra
import System.Exit
import System.IO.Extra
import System.Process.Extra
import Refact.Types qualified as R
import GHC.Types.SrcLoc qualified as GHC
import GHC.Parser.Annotation qualified as GHC
import GHC.Util.SrcLoc (getAncLoc)
substVars :: [String]
substVars = [letter : number | number <- "" : map show [0..], letter <- ['a'..'z']]
toRefactSrcSpan :: GHC.SrcSpan -> R.SrcSpan
toRefactSrcSpan = \case
GHC.RealSrcSpan span _ ->
R.SrcSpan (GHC.srcSpanStartLine span)
(GHC.srcSpanStartCol span)
(GHC.srcSpanEndLine span)
(GHC.srcSpanEndCol span)
GHC.UnhelpfulSpan _ ->
R.SrcSpan (-1) (-1) (-1) (-1)
-- | Don't crash in case ghc gives us a \"fake\" span,
-- opting instead to show @-1 -1 -1 -1@ coordinates.
toSS :: GHC.Located a -> R.SrcSpan
toSS = toRefactSrcSpan . GHC.getLoc
toSSA :: GHC.GenLocated (GHC.EpAnn a) e -> R.SrcSpan
toSSA = toRefactSrcSpan . GHC.getLocA
toSSAnc :: GHC.GenLocated GHC.NoCommentsLocation e -> R.SrcSpan
toSSAnc = toRefactSrcSpan . getAncLoc
checkRefactor :: Maybe FilePath -> IO FilePath
checkRefactor = refactorPath >=> either errorIO pure
refactorPath :: Maybe FilePath -> IO (Either String FilePath)
refactorPath rpath = do
let excPath = fromMaybe "refactor" rpath
mexc <- findExecutable excPath
case mexc of
Just exc -> do
ver <- readVersion . NE.tail . NE.fromList <$> readProcess exc ["--version"] ""
pure $ if ver >= minRefactorVersion
then Right exc
else Left $ "Your version of refactor is too old, please install apply-refact "
++ showVersion minRefactorVersion
++ " or later. Apply-refact can be installed from Cabal or Stack."
Nothing -> pure $ Left $ unlines
[ "Could not find 'refactor' executable"
, "Tried to find '" ++ excPath ++ "' on the PATH"
, "'refactor' is provided by the 'apply-refact' package and has to be installed"
, "<https://github.com/mpickering/apply-refact>"
]
runRefactoring :: FilePath -> FilePath -> FilePath -> [Extension] -> [Extension] -> String -> IO ExitCode
runRefactoring rpath fin hints enabled disabled opts = do
let args = [fin, "-v0"] ++ words opts ++ ["--refact-file", hints]
++ [arg | e <- enabled, arg <- ["-X", show e]]
++ [arg | e <- disabled, arg <- ["-X", "No" ++ show e]]
whenLoud $ putStrLn $ "Running refactor: " ++ showCommandForUser rpath args
(_, _, _, phand) <- createProcess $ proc rpath args
try $ hSetBuffering stdin LineBuffering :: IO (Either IOException ())
hSetBuffering stdout LineBuffering
-- Propagate the exit code from the spawn process
waitForProcess phand
minRefactorVersion :: Version
minRefactorVersion = makeVersion [0,9,1,0]