Make Fixer responsible for realigning tab stops

This commit is contained in:
Vidar Holen 2019-01-09 18:08:59 -08:00
parent df7f00eaed
commit fd2beaadfa
3 changed files with 39 additions and 44 deletions

View File

@ -19,7 +19,7 @@
-} -}
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module ShellCheck.Fixer (applyFix, mapPositions, Ranged(..), runTests) where module ShellCheck.Fixer (applyFix, removeTabStops, mapPositions, Ranged(..), runTests) where
import ShellCheck.Interface import ShellCheck.Interface
import Control.Monad.State import Control.Monad.State
@ -111,6 +111,30 @@ mapPositions f = adjustFix
fixReplacements = map adjustReplacement $ fixReplacements fix fixReplacements = map adjustReplacement $ fixReplacements fix
} }
-- Rewrite a Ranged from a tabstop of 8 to 1
removeTabStops :: Ranged a => a -> Array Int String -> a
removeTabStops range ls =
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 =
if lineNo c > 0 && lineNo c <= fromIntegral (length ls)
then real (ls ! fromIntegral (lineNo c)) 0 0 (colNo c)
else colNo c
real _ r v target | target <= v = r
-- hit this case at the end of line, and if we don't hit the target
-- return real + (target - v)
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
lineNo = posLine . start
endLineNo = posLine . end
colNo = posColumn . start
endColNo = posColumn . end
-- 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`
@ -154,8 +178,15 @@ multiToSingleLine fixes lines =
-- the function does not return an array. -- the function does not return an array.
applyFix :: Fix -> Array Int String -> [String] applyFix :: Fix -> Array Int String -> [String]
applyFix fix fileLines = applyFix fix fileLines =
let (adjustedFixes, singleLine) = multiToSingleLine [fix] fileLines let
in lines . runFixer $ applyFixes2 adjustedFixes singleLine untabbed = fix {
fixReplacements =
map (\c -> removeTabStops c fileLines) $
fixReplacements fix
}
(adjustedFixes, singleLine) = multiToSingleLine [untabbed] fileLines
in
lines . runFixer $ applyFixes2 adjustedFixes singleLine
-- start and end comes from pos, which is 1 based -- start and end comes from pos, which is 1 based

View File

@ -54,29 +54,5 @@ makeNonVirtual comments contents =
where where
list = lines contents list = lines contents
arr = listArray (1, length list) list arr = listArray (1, length list) list
fix c = realign c arr fix c = removeTabStops c arr
-- Realign a Ranged from a tabstop of 8 to 1
realign :: Ranged a => a -> Array Int String -> a
realign range ls =
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 =
if lineNo c > 0 && lineNo c <= fromIntegral (length ls)
then real (ls ! fromIntegral (lineNo c)) 0 0 (colNo c)
else colNo c
real _ r v target | target <= v = r
-- hit this case at the end of line, and if we don't hit the target
-- return real + (target - v)
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
lineNo = posLine . start
endLineNo = posLine . end
colNo = posColumn . start
endColNo = posColumn . end

View File

@ -163,25 +163,13 @@ showFixedString color comments lineNum fileLines =
[] -> return () [] -> return ()
fixes -> do fixes -> do
-- Folding automatically removes overlap -- Folding automatically removes overlap
let mergedFix = realignFix $ fold fixes let mergedFix = fold fixes
-- We show the complete, associated fixes, whether or not it includes this and/or unrelated lines. -- We show the complete, associated fixes, whether or not it includes this
-- and/or other unrelated lines.
let (excerptFix, excerpt) = sliceFile mergedFix fileLines let (excerptFix, excerpt) = sliceFile mergedFix fileLines
-- 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 excerptFix excerpt putStrLn $ unlines $ applyFix excerptFix excerpt
where
-- FIXME: This should be handled by Fixer
realignFix f = f { fixReplacements = map fix (fixReplacements f) }
fix r = realign r fileLines
fixedString :: Fix -> Array Int String -> [String]
fixedString fix fileLines =
case (fixReplacements fix) of
[] -> []
reps ->
-- applyReplacement returns the full update file, we really only care about the changed lines
-- so we calculate overlapping lines using replacements
applyFix fix fileLines
cuteIndent :: PositionedComment -> String cuteIndent :: PositionedComment -> String
cuteIndent comment = cuteIndent comment =