Move Ranged definition to Fixer to avoid overpromising
This commit is contained in:
parent
0636e7023c
commit
897f019353
|
@ -1,9 +1,44 @@
|
||||||
module ShellCheck.Fixer (applyFix , replaceMultiLines) where
|
module ShellCheck.Fixer (applyFix , replaceMultiLines, Ranged(..)) where
|
||||||
|
|
||||||
import ShellCheck.Interface
|
import ShellCheck.Interface
|
||||||
|
|
||||||
import Data.List
|
import Data.List
|
||||||
|
|
||||||
|
-- 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
|
||||||
|
|
||||||
|
instance Semigroup Fix where
|
||||||
|
f1 <> f2 = if overlap f1 f2 then f1 else newFix {
|
||||||
|
fixReplacements = fixReplacements f1 ++ fixReplacements f2
|
||||||
|
}
|
||||||
|
|
||||||
applyFix fix fileLines =
|
applyFix fix fileLines =
|
||||||
-- apply replacements in sorted order by end position
|
-- apply replacements in sorted order by end position
|
||||||
let sorted = (removeOverlap . reverse . sort) (fixReplacements fix) in
|
let sorted = (removeOverlap . reverse . sort) (fixReplacements fix) in
|
||||||
|
|
|
@ -54,7 +54,6 @@ 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
|
||||||
|
@ -274,36 +273,3 @@ 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