Realign virtual tabs when applying fix
Fix an off-by-one error, in the case that is commented `should never happen`. It happens when the end of a range is the at the end of a line. In that case we should update the real column count (probably just by +1) instead of returning it. I modified makeNonVirtual to use a helper, realign, that works on Ranged. That way we can share the code to realign a PositionedComment and also a Replacement. Fixes #1420
This commit is contained in:
parent
9acc8fcb53
commit
461be74976
|
@ -16,20 +16,38 @@ class Ranged a where
|
||||||
yEnd = end y
|
yEnd = end y
|
||||||
xStart = start x
|
xStart = start x
|
||||||
xEnd = end x
|
xEnd = end x
|
||||||
|
-- Set a new start and end position on a Ranged
|
||||||
|
setRange :: (Position, Position) -> a -> a
|
||||||
|
|
||||||
|
instance Ranged PositionedComment where
|
||||||
|
start = pcStartPos
|
||||||
|
end = pcEndPos
|
||||||
|
setRange (s, e) pc = pc {
|
||||||
|
pcStartPos = s,
|
||||||
|
pcEndPos = e
|
||||||
|
}
|
||||||
|
|
||||||
instance Ranged Replacement where
|
instance Ranged Replacement where
|
||||||
start = repStartPos
|
start = repStartPos
|
||||||
end = repEndPos
|
end = repEndPos
|
||||||
|
setRange (s, e) r = r {
|
||||||
|
repStartPos = s,
|
||||||
|
repEndPos = e
|
||||||
|
}
|
||||||
|
|
||||||
instance Ranged a => Ranged [a] where
|
instance Ranged a => Ranged [a] where
|
||||||
start [] = newPosition
|
start [] = newPosition
|
||||||
start xs = (minimum . map start) xs
|
start xs = (minimum . map start) xs
|
||||||
end [] = newPosition
|
end [] = newPosition
|
||||||
end xs = (maximum . map end) xs
|
end xs = (maximum . map end) xs
|
||||||
|
setRange (s, e) rs = map (setRange (s, e)) rs
|
||||||
|
|
||||||
instance Ranged Fix where
|
instance Ranged Fix where
|
||||||
start = start . fixReplacements
|
start = start . fixReplacements
|
||||||
end = end . fixReplacements
|
end = end . fixReplacements
|
||||||
|
setRange (s, e) f = f {
|
||||||
|
fixReplacements = setRange (s, e) (fixReplacements f)
|
||||||
|
}
|
||||||
|
|
||||||
-- The Monoid instance for Fix merges replacements that do not overlap.
|
-- The Monoid instance for Fix merges replacements that do not overlap.
|
||||||
instance Monoid Fix where
|
instance Monoid Fix where
|
||||||
|
|
|
@ -21,6 +21,7 @@ module ShellCheck.Formatter.Format where
|
||||||
|
|
||||||
import ShellCheck.Data
|
import ShellCheck.Data
|
||||||
import ShellCheck.Interface
|
import ShellCheck.Interface
|
||||||
|
import ShellCheck.Fixer
|
||||||
|
|
||||||
-- A formatter that carries along an arbitrary piece of data
|
-- A formatter that carries along an arbitrary piece of data
|
||||||
data Formatter = Formatter {
|
data Formatter = Formatter {
|
||||||
|
@ -51,20 +52,29 @@ makeNonVirtual comments contents =
|
||||||
map fix comments
|
map fix comments
|
||||||
where
|
where
|
||||||
ls = lines contents
|
ls = lines contents
|
||||||
fix c = c {
|
fix c = realign c ls
|
||||||
pcStartPos = (pcStartPos c) {
|
|
||||||
posColumn = realignColumn lineNo colNo c
|
-- Realign a Ranged from a tabstop of 8 to 1
|
||||||
}
|
realign :: Ranged a => a -> [String] -> a
|
||||||
, pcEndPos = (pcEndPos c) {
|
realign range ls =
|
||||||
posColumn = realignColumn endLineNo endColNo c
|
let startColumn = realignColumn lineNo colNo range
|
||||||
}
|
endColumn = realignColumn endLineNo endColNo range
|
||||||
}
|
startPosition = (start range) { posColumn = startColumn }
|
||||||
|
endPosition = (end range) { posColumn = endColumn } in
|
||||||
|
setRange (startPosition, endPosition) range
|
||||||
|
where
|
||||||
realignColumn lineNo colNo c =
|
realignColumn lineNo colNo c =
|
||||||
if lineNo c > 0 && lineNo c <= fromIntegral (length ls)
|
if lineNo c > 0 && lineNo c <= fromIntegral (length ls)
|
||||||
then real (ls !! fromIntegral (lineNo c - 1)) 0 0 (colNo c)
|
then real (ls !! fromIntegral (lineNo c - 1)) 0 0 (colNo c)
|
||||||
else colNo c
|
else colNo c
|
||||||
real _ r v target | target <= v = r
|
real _ r v target | target <= v = r
|
||||||
real [] r v _ = r -- should never happen
|
-- hit this case at the end of line, and if we don't hit the target
|
||||||
real ('\t':rest) r v target =
|
-- return real + (target - v)
|
||||||
real rest (r+1) (v + 8 - (v `mod` 8)) target
|
real [] r v target = r + (target - v)
|
||||||
|
real ('\t':rest) r v target = real rest (r+1) (v + 8 - (v `mod` 8)) target
|
||||||
real (_:rest) r v target = real rest (r+1) (v+1) target
|
real (_:rest) r v target = real rest (r+1) (v+1) target
|
||||||
|
lineNo = posLine . start
|
||||||
|
endLineNo = posLine . end
|
||||||
|
colNo = posColumn . start
|
||||||
|
endColNo = posColumn . end
|
||||||
|
|
||||||
|
|
|
@ -153,10 +153,13 @@ showFixedString color comments lineNum fileLines =
|
||||||
-- fixes for that single line. We can fold the fixes (which removes
|
-- fixes for that single line. We can fold the fixes (which removes
|
||||||
-- overlaps), and apply it as a single fix with multiple replacements.
|
-- overlaps), and apply it as a single fix with multiple replacements.
|
||||||
applicableComments -> do
|
applicableComments -> do
|
||||||
let mergedFix = (fold . catMaybes . (map pcFix)) applicableComments
|
let mergedFix = (realignFix . fold . catMaybes . (map pcFix)) applicableComments
|
||||||
-- 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 $ unlines $ fixedString mergedFix fileLines
|
putStrLn $ unlines $ fixedString mergedFix fileLines
|
||||||
|
where
|
||||||
|
realignFix f = f { fixReplacements = map fix (fixReplacements f) }
|
||||||
|
fix r = realign r fileLines
|
||||||
|
|
||||||
fixedString :: Fix -> [String] -> [String]
|
fixedString :: Fix -> [String] -> [String]
|
||||||
fixedString fix fileLines =
|
fixedString fix fileLines =
|
||||||
|
|
Loading…
Reference in New Issue