parent
08ca1ee6e9
commit
0636e7023c
|
@ -14,18 +14,9 @@ applyFix fix fileLines =
|
||||||
-- prereq: list is already sorted by start position
|
-- prereq: list is already sorted by start position
|
||||||
removeOverlap [] = []
|
removeOverlap [] = []
|
||||||
removeOverlap (x:xs) = checkoverlap x xs
|
removeOverlap (x:xs) = checkoverlap x xs
|
||||||
checkoverlap :: Replacement -> [Replacement] -> [Replacement]
|
|
||||||
checkoverlap x [] = x:[]
|
checkoverlap x [] = x:[]
|
||||||
checkoverlap x (y:ys) =
|
checkoverlap x (y:ys) =
|
||||||
if overlap x y then x:(removeOverlap ys) else x:y:(removeOverlap 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:
|
-- A replacement that spans multiple line is applied by:
|
||||||
|
|
|
@ -24,6 +24,7 @@ import ShellCheck.Interface
|
||||||
import ShellCheck.Formatter.Format
|
import ShellCheck.Formatter.Format
|
||||||
|
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
|
import Data.Foldable
|
||||||
import Data.Ord
|
import Data.Ord
|
||||||
import Data.IORef
|
import Data.IORef
|
||||||
import Data.List
|
import Data.List
|
||||||
|
@ -147,17 +148,19 @@ showFixedString color comments lineNum fileLines =
|
||||||
let line = fileLines !! fromIntegral (lineNum - 1) in
|
let line = fileLines !! fromIntegral (lineNum - 1) in
|
||||||
-- need to check overlaps
|
-- need to check overlaps
|
||||||
case filter (hasApplicableFix lineNum) comments of
|
case filter (hasApplicableFix lineNum) comments of
|
||||||
(first:_) -> do
|
[] -> return ()
|
||||||
|
-- all the fixes are single-line only, but there could be multiple
|
||||||
|
-- fixes for that single line. We can fold the fixes (which removes
|
||||||
|
-- overlaps), and apply it as a single fix with multiple replacements.
|
||||||
|
applicableComments -> do
|
||||||
|
let mergedFix = (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 first fileLines
|
putStrLn $ unlines $ fixedString mergedFix fileLines
|
||||||
_ -> return ()
|
|
||||||
|
|
||||||
fixedString :: PositionedComment -> [String] -> [String]
|
fixedString :: Fix -> [String] -> [String]
|
||||||
fixedString comment fileLines =
|
fixedString fix fileLines =
|
||||||
case (pcFix comment) of
|
case (fixReplacements fix) of
|
||||||
Nothing -> [""]
|
|
||||||
Just fix -> case (fixReplacements fix) of
|
|
||||||
[] -> []
|
[] -> []
|
||||||
reps ->
|
reps ->
|
||||||
-- applyReplacement returns the full update file, we really only care about the changed lines
|
-- applyReplacement returns the full update file, we really only care about the changed lines
|
||||||
|
|
|
@ -54,13 +54,17 @@ module ShellCheck.Interface
|
||||||
, newFix
|
, newFix
|
||||||
, Replacement(repStartPos, repEndPos, repString)
|
, Replacement(repStartPos, repEndPos, repString)
|
||||||
, newReplacement
|
, newReplacement
|
||||||
|
, Ranged(overlap)
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import ShellCheck.AST
|
import ShellCheck.AST
|
||||||
|
|
||||||
import Control.DeepSeq
|
import Control.DeepSeq
|
||||||
import Control.Monad.Identity
|
import Control.Monad.Identity
|
||||||
|
import Data.List
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
|
import Data.Ord
|
||||||
|
import Data.Semigroup
|
||||||
import GHC.Generics (Generic)
|
import GHC.Generics (Generic)
|
||||||
import qualified Data.Map as Map
|
import qualified Data.Map as Map
|
||||||
|
|
||||||
|
@ -270,3 +274,36 @@ mockedSystemInterface files = SystemInterface {
|
||||||
[] -> return $ Left "File not included in mock."
|
[] -> return $ Left "File not included in mock."
|
||||||
[(_, contents)] -> return $ Right contents
|
[(_, contents)] -> return $ Right contents
|
||||||
|
|
||||||
|
-- The Ranged class is used for types that has a start and end position.
|
||||||
|
class Ranged a where
|
||||||
|
start :: a -> Position
|
||||||
|
end :: a -> Position
|
||||||
|
overlap :: a -> a -> Bool
|
||||||
|
overlap x y =
|
||||||
|
(yStart >= xStart && yStart < xEnd) || (yStart < xStart && yEnd > xStart)
|
||||||
|
where
|
||||||
|
yStart = start y
|
||||||
|
yEnd = end y
|
||||||
|
xStart = start x
|
||||||
|
xEnd = end x
|
||||||
|
|
||||||
|
instance Ranged Replacement where
|
||||||
|
start = repStartPos
|
||||||
|
end = repEndPos
|
||||||
|
|
||||||
|
instance Ranged a => Ranged [a] where
|
||||||
|
start [] = newPosition
|
||||||
|
start xs = (minimum . map start) xs
|
||||||
|
end [] = newPosition
|
||||||
|
end xs = (maximum . map end) xs
|
||||||
|
|
||||||
|
instance Ranged Fix where
|
||||||
|
start = start . fixReplacements
|
||||||
|
end = end . fixReplacements
|
||||||
|
|
||||||
|
-- The Monoid instance for Fix merges replacements that do not overlap.
|
||||||
|
instance Monoid Fix where
|
||||||
|
mempty = newFix
|
||||||
|
f1 `mappend` f2 = if overlap f1 f2 then f1 else newFix {
|
||||||
|
fixReplacements = fixReplacements f1 ++ fixReplacements f2
|
||||||
|
}
|
||||||
|
|
Loading…
Reference in New Issue