Remove duplicate `pathTo` and unused `replaceMultiLines`

This commit is contained in:
Vidar Holen 2019-01-08 22:16:17 -08:00
parent e45b679d58
commit df7f00eaed
3 changed files with 22 additions and 41 deletions

View File

@ -380,10 +380,6 @@ isParentOf tree parent child =
parents params = getPath (parentMap params) parents params = getPath (parentMap params)
pathTo t = do
parents <- reader parentMap
return $ getPath parents t
-- Find the first match in a list where the predicate is Just True. -- Find the first match in a list where the predicate is Just True.
-- Stops if it's Just False and ignores Nothing. -- Stops if it's Just False and ignores Nothing.
findFirst :: (a -> Maybe Bool) -> [a] -> Maybe a findFirst :: (a -> Maybe Bool) -> [a] -> Maybe a

View File

@ -484,7 +484,7 @@ prop_checkInteractiveSu4 = verifyNot checkInteractiveSu "su root < script"
checkInteractiveSu = CommandCheck (Basename "su") f checkInteractiveSu = CommandCheck (Basename "su") f
where where
f cmd = when (length (arguments cmd) <= 1) $ do f cmd = when (length (arguments cmd) <= 1) $ do
path <- pathTo cmd path <- getPathM cmd
when (all undirected path) $ when (all undirected path) $
info (getId cmd) 2117 info (getId cmd) 2117
"To run commands as another user, use su -c or sudo." "To run commands as another user, use su -c or sudo."

View File

@ -97,6 +97,7 @@ instance Semigroup Fix where
fixReplacements = fixReplacements f1 ++ fixReplacements f2 fixReplacements = fixReplacements f1 ++ fixReplacements f2
} }
-- Conveniently apply a transformation to positions in a Fix
mapPositions :: (Position -> Position) -> Fix -> Fix mapPositions :: (Position -> Position) -> Fix -> Fix
mapPositions f = adjustFix mapPositions f = adjustFix
where where
@ -110,6 +111,26 @@ mapPositions f = adjustFix
fixReplacements = map adjustReplacement $ fixReplacements fix fixReplacements = map adjustReplacement $ fixReplacements fix
} }
-- A replacement that spans multiple line is applied by:
-- 1. merging the affected lines into a single string using `unlines`
-- 2. apply the replacement as if it only spanned a single line
-- The tricky part is adjusting the end column of the replacement
-- (the end line doesn't matter because there is only one line)
--
-- aaS <--- start of replacement (row 1 column 3)
-- bbbb
-- cEc
-- \------- end of replacement (row 3 column 2)
--
-- a flattened string will look like:
--
-- "aaS\nbbbb\ncEc\n"
--
-- The column of E has to be adjusted by:
-- 1. lengths of lines to be replaced, except the end row itself
-- 2. end column of the replacement
-- 3. number of '\n' by `unlines`
multiToSingleLine :: [Fix] -> Array Int String -> ([Fix], String) multiToSingleLine :: [Fix] -> Array Int String -> ([Fix], String)
multiToSingleLine fixes lines = multiToSingleLine fixes lines =
(map (mapPositions adjust) fixes, unlines $ elems lines) (map (mapPositions adjust) fixes, unlines $ elems lines)
@ -136,42 +157,6 @@ applyFix fix fileLines =
let (adjustedFixes, singleLine) = multiToSingleLine [fix] fileLines let (adjustedFixes, singleLine) = multiToSingleLine [fix] fileLines
in lines . runFixer $ applyFixes2 adjustedFixes singleLine in lines . runFixer $ applyFixes2 adjustedFixes singleLine
-- A replacement that spans multiple line is applied by:
-- 1. merging the affected lines into a single string using `unlines`
-- 2. apply the replacement as if it only spanned a single line
-- The tricky part is adjusting the end column of the replacement
-- (the end line doesn't matter because there is only one line)
--
-- aaS <--- start of replacement (row 1 column 3)
-- bbbb
-- cEc
-- \------- end of replacement (row 3 column 2)
--
-- a flattened string will look like:
--
-- "aaS\nbbbb\ncEc\n"
--
-- The column of E has to be adjusted by:
-- 1. lengths of lines to be replaced, except the end row itself
-- 2. end column of the replacement
-- 3. number of '\n' by `unlines`
-- Returns the original lines from the file with the replacement applied.
-- Multiline replacements completely overwrite new lines in the original string.
-- 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.
replaceMultiLines rep fileLines = -- this can replace doReplace
let startRow = fromIntegral $ (posLine . repStartPos) rep
endRow = fromIntegral $ (posLine . repEndPos) rep
(ys, zs) = splitAt endRow fileLines
(xs, toReplaceLines) = splitAt (startRow-1) ys
lengths = fromIntegral $ sum (map length (init toReplaceLines))
newlines = fromIntegral $ (length toReplaceLines - 1) -- for the '\n' from unlines
original = unlines toReplaceLines
startCol = ((posColumn . repStartPos) rep)
endCol = ((posColumn . repEndPos) rep + newlines + lengths)
replacedLines = (lines $ doReplace startCol endCol original (repString rep))
in
xs ++ replacedLines ++ zs
-- start and end comes from pos, which is 1 based -- start and end comes from pos, which is 1 based
prop_doReplace1 = doReplace 0 0 "1234" "A" == "A1234" -- technically not valid prop_doReplace1 = doReplace 0 0 "1234" "A" == "A1234" -- technically not valid