Merge pull request #1376 from ngzhian/autofix
Add method to apply a multi-line replacement
This commit is contained in:
commit
ecd61bfc68
|
@ -256,15 +256,13 @@ replaceStart id params n r =
|
||||||
repString = r
|
repString = r
|
||||||
}
|
}
|
||||||
replaceEnd id params n r =
|
replaceEnd id params n r =
|
||||||
-- because of the way we count columns 1-based
|
|
||||||
-- we have to offset end columns by 1
|
|
||||||
let tp = tokenPositions params
|
let tp = tokenPositions params
|
||||||
(_, end) = tp Map.! id
|
(_, end) = tp Map.! id
|
||||||
new_start = end {
|
new_start = end {
|
||||||
posColumn = posColumn end - n + 1
|
posColumn = posColumn end - n
|
||||||
}
|
}
|
||||||
new_end = end {
|
new_end = end {
|
||||||
posColumn = posColumn end + 1
|
posColumn = posColumn end
|
||||||
}
|
}
|
||||||
in
|
in
|
||||||
newReplacement {
|
newReplacement {
|
||||||
|
|
|
@ -0,0 +1,82 @@
|
||||||
|
module ShellCheck.Fixer (applyFix , replaceMultiLines) where
|
||||||
|
|
||||||
|
import ShellCheck.Interface
|
||||||
|
|
||||||
|
import Data.List
|
||||||
|
|
||||||
|
applyFix fix fileLines =
|
||||||
|
-- apply replacements in sorted order by end position
|
||||||
|
let sorted = (removeOverlap . reverse . sort) (fixReplacements fix) in
|
||||||
|
applyReplacement sorted fileLines
|
||||||
|
where
|
||||||
|
applyReplacement [] s = s
|
||||||
|
applyReplacement (rep:xs) s = applyReplacement xs $ replaceMultiLines rep s
|
||||||
|
-- prereq: list is already sorted by start position
|
||||||
|
removeOverlap [] = []
|
||||||
|
removeOverlap (x:xs) = checkoverlap x xs
|
||||||
|
checkoverlap :: Replacement -> [Replacement] -> [Replacement]
|
||||||
|
checkoverlap x [] = x:[]
|
||||||
|
checkoverlap x (y:ys) =
|
||||||
|
if overlap x y then x:(removeOverlap ys) else x:y:(removeOverlap ys)
|
||||||
|
-- two position overlaps when
|
||||||
|
overlap x y =
|
||||||
|
(yStart >= xStart && yStart < xEnd) || (yStart < xStart && yEnd > xStart)
|
||||||
|
where
|
||||||
|
yStart = repStartPos y
|
||||||
|
yEnd = repEndPos y
|
||||||
|
xStart = repStartPos x
|
||||||
|
xEnd = repEndPos x
|
||||||
|
|
||||||
|
|
||||||
|
-- A replacement that spans multiple line is applied by:
|
||||||
|
-- 1. merging the affected lines into a single string using `unlines`
|
||||||
|
-- 2. apply the replacement as if it only spanned a single line
|
||||||
|
-- The tricky part is adjusting the end column of the replacement
|
||||||
|
-- (the end line doesn't matter because there is only one line)
|
||||||
|
--
|
||||||
|
-- aaS <--- start of replacement (row 1 column 3)
|
||||||
|
-- bbbb
|
||||||
|
-- cEc
|
||||||
|
-- \------- end of replacement (row 3 column 2)
|
||||||
|
--
|
||||||
|
-- a flattened string will look like:
|
||||||
|
--
|
||||||
|
-- "aaS\nbbbb\ncEc\n"
|
||||||
|
--
|
||||||
|
-- The column of E has to be adjusted by:
|
||||||
|
-- 1. lengths of lines to be replaced, except the end row itself
|
||||||
|
-- 2. end column of the replacement
|
||||||
|
-- 3. number of '\n' by `unlines`
|
||||||
|
-- Returns the original lines from the file with the replacement applied.
|
||||||
|
-- Multiline replacements completely overwrite new lines in the original string.
|
||||||
|
-- e.g. if the replacement spans 2 lines, but the replacement string does not
|
||||||
|
-- have a '\n', then the number of replaced lines will be 1 shorter.
|
||||||
|
replaceMultiLines rep fileLines = -- this can replace doReplace
|
||||||
|
let startRow = fromIntegral $ (posLine . repStartPos) rep
|
||||||
|
endRow = fromIntegral $ (posLine . repEndPos) rep
|
||||||
|
(ys, zs) = splitAt endRow fileLines
|
||||||
|
(xs, toReplaceLines) = splitAt (startRow-1) ys
|
||||||
|
lengths = fromIntegral $ sum (map length (init toReplaceLines))
|
||||||
|
newlines = fromIntegral $ (length toReplaceLines - 1) -- for the '\n' from unlines
|
||||||
|
original = unlines toReplaceLines
|
||||||
|
startCol = ((posColumn . repStartPos) rep)
|
||||||
|
endCol = ((posColumn . repEndPos) rep + newlines + lengths)
|
||||||
|
replacedLines = (lines $ doReplace startCol endCol original (repString rep))
|
||||||
|
in
|
||||||
|
xs ++ replacedLines ++ zs
|
||||||
|
|
||||||
|
-- FIXME: Work correctly with tabs
|
||||||
|
-- start and end comes from pos, which is 1 based
|
||||||
|
-- doReplace 0 0 "1234" "A" -> "A1234" -- technically not valid
|
||||||
|
-- doReplace 1 1 "1234" "A" -> "A1234"
|
||||||
|
-- doReplace 1 2 "1234" "A" -> "A234"
|
||||||
|
-- doReplace 3 3 "1234" "A" -> "12A34"
|
||||||
|
-- doReplace 4 4 "1234" "A" -> "123A4"
|
||||||
|
-- doReplace 5 5 "1234" "A" -> "1234A"
|
||||||
|
doReplace start end o r =
|
||||||
|
let si = fromIntegral (start-1)
|
||||||
|
ei = fromIntegral (end-1)
|
||||||
|
(x, xs) = splitAt si o
|
||||||
|
(y, z) = splitAt (ei - si) xs
|
||||||
|
in
|
||||||
|
x ++ r ++ z
|
|
@ -19,10 +19,12 @@
|
||||||
-}
|
-}
|
||||||
module ShellCheck.Formatter.TTY (format) where
|
module ShellCheck.Formatter.TTY (format) where
|
||||||
|
|
||||||
|
import ShellCheck.Fixer
|
||||||
import ShellCheck.Interface
|
import ShellCheck.Interface
|
||||||
import ShellCheck.Formatter.Format
|
import ShellCheck.Formatter.Format
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
|
import Data.Ord
|
||||||
import Data.IORef
|
import Data.IORef
|
||||||
import Data.List
|
import Data.List
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
|
@ -130,7 +132,7 @@ outputForFile color sys comments = do
|
||||||
putStrLn (color "source" line)
|
putStrLn (color "source" line)
|
||||||
mapM_ (\c -> putStrLn (color (severityText c) $ cuteIndent c)) commentsForLine
|
mapM_ (\c -> putStrLn (color (severityText c) $ cuteIndent c)) commentsForLine
|
||||||
putStrLn ""
|
putStrLn ""
|
||||||
showFixedString color comments lineNum line
|
showFixedString color comments lineNum fileLines
|
||||||
) groups
|
) groups
|
||||||
|
|
||||||
hasApplicableFix lineNum comment = fromMaybe False $ do
|
hasApplicableFix lineNum comment = fromMaybe False $ do
|
||||||
|
@ -141,47 +143,29 @@ hasApplicableFix lineNum comment = fromMaybe False $ do
|
||||||
onSameLine pos = posLine pos == lineNum
|
onSameLine pos = posLine pos == lineNum
|
||||||
|
|
||||||
-- FIXME: Work correctly with multiple replacements
|
-- FIXME: Work correctly with multiple replacements
|
||||||
showFixedString color comments lineNum line =
|
showFixedString color comments lineNum fileLines =
|
||||||
|
let line = fileLines !! fromIntegral (lineNum - 1) in
|
||||||
|
-- need to check overlaps
|
||||||
case filter (hasApplicableFix lineNum) comments of
|
case filter (hasApplicableFix lineNum) comments of
|
||||||
(first:_) -> do
|
(first:_) -> do
|
||||||
-- in the spirit of error prone
|
-- in the spirit of error prone
|
||||||
putStrLn $ color "message" "Did you mean: "
|
putStrLn $ color "message" "Did you mean: "
|
||||||
putStrLn $ fixedString first line
|
putStrLn $ unlines $ fixedString first fileLines
|
||||||
putStrLn ""
|
|
||||||
_ -> return ()
|
_ -> return ()
|
||||||
|
|
||||||
-- need to do something smart about sorting by end index
|
fixedString :: PositionedComment -> [String] -> [String]
|
||||||
fixedString :: PositionedComment -> String -> String
|
fixedString comment fileLines =
|
||||||
fixedString comment line =
|
|
||||||
case (pcFix comment) of
|
case (pcFix comment) of
|
||||||
Nothing -> ""
|
Nothing -> [""]
|
||||||
Just rs ->
|
Just fix -> case (fixReplacements fix) of
|
||||||
applyReplacement (fixReplacements rs) line 0
|
[] -> []
|
||||||
|
reps ->
|
||||||
|
-- applyReplacement returns the full update file, we really only care about the changed lines
|
||||||
|
-- so we calculate overlapping lines using replacements
|
||||||
|
drop start $ take end $ applyFix fix fileLines
|
||||||
where
|
where
|
||||||
applyReplacement [] s _ = s
|
start = (fromIntegral $ minimum $ map (posLine . repStartPos) reps) - 1
|
||||||
applyReplacement (rep:xs) s offset =
|
end = fromIntegral $ maximum $ map (posLine . repEndPos) reps
|
||||||
let replacementString = repString rep
|
|
||||||
start = (posColumn . repStartPos) rep
|
|
||||||
end = (posColumn . repEndPos) rep
|
|
||||||
z = doReplace start end s replacementString
|
|
||||||
len_r = (fromIntegral . length) replacementString in
|
|
||||||
applyReplacement xs z (offset + (end - start) + len_r)
|
|
||||||
|
|
||||||
-- FIXME: Work correctly with tabs
|
|
||||||
-- start and end comes from pos, which is 1 based
|
|
||||||
-- doReplace 0 0 "1234" "A" -> "A1234" -- technically not valid
|
|
||||||
-- doReplace 1 1 "1234" "A" -> "A1234"
|
|
||||||
-- doReplace 1 2 "1234" "A" -> "A234"
|
|
||||||
-- doReplace 3 3 "1234" "A" -> "12A34"
|
|
||||||
-- doReplace 4 4 "1234" "A" -> "123A4"
|
|
||||||
-- doReplace 5 5 "1234" "A" -> "1234A"
|
|
||||||
doReplace start end o r =
|
|
||||||
let si = fromIntegral (start-1)
|
|
||||||
ei = fromIntegral (end-1)
|
|
||||||
(x, xs) = splitAt si o
|
|
||||||
(y, z) = splitAt (ei - si) xs
|
|
||||||
in
|
|
||||||
x ++ r ++ z
|
|
||||||
|
|
||||||
cuteIndent :: PositionedComment -> String
|
cuteIndent :: PositionedComment -> String
|
||||||
cuteIndent comment =
|
cuteIndent comment =
|
||||||
|
|
|
@ -180,7 +180,7 @@ data Position = Position {
|
||||||
posFile :: String, -- Filename
|
posFile :: String, -- Filename
|
||||||
posLine :: Integer, -- 1 based source line
|
posLine :: Integer, -- 1 based source line
|
||||||
posColumn :: Integer -- 1 based source column, where tabs are 8
|
posColumn :: Integer -- 1 based source column, where tabs are 8
|
||||||
} deriving (Show, Eq, Generic, NFData)
|
} deriving (Show, Eq, Generic, NFData, Ord)
|
||||||
|
|
||||||
newPosition :: Position
|
newPosition :: Position
|
||||||
newPosition = Position {
|
newPosition = Position {
|
||||||
|
@ -209,6 +209,9 @@ data Replacement = Replacement {
|
||||||
repString :: String
|
repString :: String
|
||||||
} deriving (Show, Eq, Generic, NFData)
|
} deriving (Show, Eq, Generic, NFData)
|
||||||
|
|
||||||
|
instance Ord Replacement where
|
||||||
|
compare r1 r2 = (repStartPos r1) `compare` (repStartPos r2)
|
||||||
|
|
||||||
newReplacement = Replacement {
|
newReplacement = Replacement {
|
||||||
repStartPos = newPosition,
|
repStartPos = newPosition,
|
||||||
repEndPos = newPosition,
|
repEndPos = newPosition,
|
||||||
|
|
Loading…
Reference in New Issue