Smarter sorting and application of fix to handle multiple replacements

This commit is contained in:
Ng Zhi An 2018-11-02 22:13:49 -07:00
parent d5ba41035b
commit 3471ad45b1
3 changed files with 57 additions and 39 deletions

View File

@ -255,15 +255,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 {

View File

@ -130,7 +130,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 +141,43 @@ 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 "" 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 = let lineNum = lineNo comment
line = fileLines !! fromIntegral (lineNum - 1) in
case (pcFix comment) of case (pcFix comment) of
Nothing -> "" Nothing -> [""]
Just rs -> Just rs ->
applyReplacement (fixReplacements rs) line 0 -- apply replacements in sorted order by end position
where -- assert no overlaps, or maybe remove overlaps?
applyReplacement [] s _ = s let sorted = (reverse . sort) (fixReplacements rs)
applyReplacement (rep:xs) s offset = (start, end) = calculateOverlap sorted 1 1
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 in
x ++ r ++ z -- applyReplacement returns the full update file, we really only care about the changed lines
-- so we calculate overlapping lines using replacements
-- TODO separate this logic of printing affected lines out
-- since for some output we might want to have the full file output
drop (fromIntegral start) $ take (fromIntegral end) $ applyReplacement sorted fileLines
where
applyReplacement [] s = s
applyReplacement (rep:xs) s =
let result = replaceMultiLines rep s
in
applyReplacement xs result
calculateOverlap [] s e = (s, e)
calculateOverlap (rep:xs) s e =
calculateOverlap xs (min s (posLine (repStartPos rep))) (max e (posLine (repEndPos rep)))
-- A replacement that spans multiple line is applied by: -- A replacement that spans multiple line is applied by:
-- 1. merging the affected lines into a single string using `unlines` -- 1. merging the affected lines into a single string using `unlines`
@ -206,7 +202,7 @@ doReplace start end o r =
-- Multiline replacements completely overwrite new lines in the original string. -- Multiline replacements completely overwrite new lines in the original string.
-- e.g. if the replacement spans 2 lines, but the replacement string does not -- 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. -- have a '\n', then the number of replaced lines will be 1 shorter.
replaceMultiLines fileLines rep = replaceMultiLines rep fileLines = -- this can replace doReplace
let startRow = fromIntegral $ (posLine . repStartPos) rep let startRow = fromIntegral $ (posLine . repStartPos) rep
endRow = fromIntegral $ (posLine . repEndPos) rep endRow = fromIntegral $ (posLine . repEndPos) rep
(ys, zs) = splitAt endRow fileLines (ys, zs) = splitAt endRow fileLines
@ -220,6 +216,27 @@ replaceMultiLines fileLines rep =
in in
xs ++ replacedLines ++ zs 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
start = newPosition { posLine = 2, posColumn = 3 }
end = newPosition { posLine = 2, posColumn = 4 }
r = newReplacement { repStartPos = start, repEndPos = end, repString = "hello" }
filelines = ["first", "second", "third", "fourth"]
cuteIndent :: PositionedComment -> String cuteIndent :: PositionedComment -> String
cuteIndent comment = cuteIndent comment =
replicate (fromIntegral $ colNo comment - 1) ' ' ++ replicate (fromIntegral $ colNo comment - 1) ' ' ++

View File

@ -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,