Minor renaming and output fixes
This commit is contained in:
parent
5ed89d2241
commit
a8376a09a9
|
@ -242,7 +242,7 @@ isCondition (child:parent:rest) =
|
||||||
_ -> []
|
_ -> []
|
||||||
|
|
||||||
-- helpers to build replacements
|
-- helpers to build replacements
|
||||||
replace_start id params n r =
|
replaceStart id params n r =
|
||||||
let tp = tokenPositions params
|
let tp = tokenPositions params
|
||||||
(start, _) = tp Map.! id
|
(start, _) = tp Map.! id
|
||||||
new_end = start {
|
new_end = start {
|
||||||
|
@ -254,7 +254,7 @@ replace_start id params n r =
|
||||||
repEndPos = new_end,
|
repEndPos = new_end,
|
||||||
repString = r
|
repString = r
|
||||||
}
|
}
|
||||||
replace_end id params n r =
|
replaceEnd id params n r =
|
||||||
-- because of the way we count columns 1-based
|
-- because of the way we count columns 1-based
|
||||||
-- we have to offset end columns by 1
|
-- we have to offset end columns by 1
|
||||||
let tp = tokenPositions params
|
let tp = tokenPositions params
|
||||||
|
@ -271,8 +271,8 @@ replace_end id params n r =
|
||||||
repEndPos = new_end,
|
repEndPos = new_end,
|
||||||
repString = r
|
repString = r
|
||||||
}
|
}
|
||||||
surround_with id params s =
|
surroundWidth id params s = fixWith [replaceStart id params 0 s, replaceEnd id params 0 s]
|
||||||
[replace_start id params 0 s, replace_end id params 0 s]
|
fixWith fixes = newFix { fixReplacements = fixes }
|
||||||
|
|
||||||
prop_checkEchoWc3 = verify checkEchoWc "n=$(echo $foo | wc -c)"
|
prop_checkEchoWc3 = verify checkEchoWc "n=$(echo $foo | wc -c)"
|
||||||
checkEchoWc _ (T_Pipeline id _ [a, b]) =
|
checkEchoWc _ (T_Pipeline id _ [a, b]) =
|
||||||
|
@ -1371,8 +1371,7 @@ prop_checkBackticks3 = verifyNot checkBackticks "echo `#inlined comment` foo"
|
||||||
checkBackticks params (T_Backticked id list) | not (null list) =
|
checkBackticks params (T_Backticked id list) | not (null list) =
|
||||||
addComment $
|
addComment $
|
||||||
makeCommentWithFix StyleC id 2006 "Use $(...) notation instead of legacy backticked `...`."
|
makeCommentWithFix StyleC id 2006 "Use $(...) notation instead of legacy backticked `...`."
|
||||||
[(replace_start id params 1 "$("), (replace_end id params 1 ")")]
|
(fixWith [replaceStart id params 1 "$(", replaceEnd id params 1 ")"])
|
||||||
-- style id 2006 "Use $(...) notation instead of legacy backticked `...`."
|
|
||||||
checkBackticks _ _ = return ()
|
checkBackticks _ _ = return ()
|
||||||
|
|
||||||
prop_checkIndirectExpansion1 = verify checkIndirectExpansion "${foo$n}"
|
prop_checkIndirectExpansion1 = verify checkIndirectExpansion "${foo$n}"
|
||||||
|
@ -1677,7 +1676,7 @@ checkSpacefulness params t =
|
||||||
"This default assignment may cause DoS due to globbing. Quote it."
|
"This default assignment may cause DoS due to globbing. Quote it."
|
||||||
else
|
else
|
||||||
makeCommentWithFix InfoC (getId token) 2086
|
makeCommentWithFix InfoC (getId token) 2086
|
||||||
"Double quote to prevent globbing and word splitting." (surround_with (getId token) params "\"")
|
"Double quote to prevent globbing and word splitting." (surroundWidth (getId token) params "\"")
|
||||||
-- makeComment InfoC (getId token) 2086
|
-- makeComment InfoC (getId token) 2086
|
||||||
-- "Double quote to prevent globbing and word splitting."
|
-- "Double quote to prevent globbing and word splitting."
|
||||||
|
|
||||||
|
@ -2576,9 +2575,8 @@ checkUncheckedCdPushdPopd params root =
|
||||||
&& not (isSafeDir t)
|
&& not (isSafeDir t)
|
||||||
&& not (name t `elem` ["pushd", "popd"] && ("n" `elem` map snd (getAllFlags t)))
|
&& not (name t `elem` ["pushd", "popd"] && ("n" `elem` map snd (getAllFlags t)))
|
||||||
&& not (isCondition $ getPath (parentMap params) t)) $
|
&& not (isCondition $ getPath (parentMap params) t)) $
|
||||||
-- warn (getId t) 2164 "Use 'cd ... || exit' or 'cd ... || return' in case cd fails."
|
|
||||||
warnWithFix (getId t) 2164 "Use 'cd ... || exit' or 'cd ... || return' in case cd fails."
|
warnWithFix (getId t) 2164 "Use 'cd ... || exit' or 'cd ... || return' in case cd fails."
|
||||||
[replace_end (getId t) params 0 " || exit"]
|
(fixWith [replaceEnd (getId t) params 0 " || exit"])
|
||||||
checkElement _ = return ()
|
checkElement _ = return ()
|
||||||
name t = fromMaybe "" $ getCommandName t
|
name t = fromMaybe "" $ getCommandName t
|
||||||
isSafeDir t = case oversimplify t of
|
isSafeDir t = case oversimplify t of
|
||||||
|
@ -2735,7 +2733,7 @@ checkArrayAssignmentIndices params root =
|
||||||
T_Literal id str -> [(id,str)]
|
T_Literal id str -> [(id,str)]
|
||||||
_ -> []
|
_ -> []
|
||||||
guard $ '=' `elem` str
|
guard $ '=' `elem` str
|
||||||
return $ warnWithFix id 2191 "The = here is literal. To assign by index, use ( [index]=value ) with no spaces. To keep as literal, quote it." (surround_with id params "\"")
|
return $ warnWithFix id 2191 "The = here is literal. To assign by index, use ( [index]=value ) with no spaces. To keep as literal, quote it." (surroundWidth id params "\"")
|
||||||
in
|
in
|
||||||
if null literalEquals && isAssociative
|
if null literalEquals && isAssociative
|
||||||
then warn (getId t) 2190 "Elements in associative arrays need index, e.g. array=( [index]=value ) ."
|
then warn (getId t) 2190 "Elements in associative arrays need index, e.g. array=( [index]=value ) ."
|
||||||
|
|
|
@ -52,7 +52,7 @@ instance ToJSON Replacement where
|
||||||
"replaceWith" .= str
|
"replaceWith" .= str
|
||||||
]
|
]
|
||||||
|
|
||||||
instance ToJSON (PositionedComment) where
|
instance ToJSON PositionedComment where
|
||||||
toJSON comment =
|
toJSON comment =
|
||||||
let start = pcStartPos comment
|
let start = pcStartPos comment
|
||||||
end = pcEndPos comment
|
end = pcEndPos comment
|
||||||
|
@ -82,9 +82,14 @@ instance ToJSON (PositionedComment) where
|
||||||
<> "level" .= severityText comment
|
<> "level" .= severityText comment
|
||||||
<> "code" .= cCode c
|
<> "code" .= cCode c
|
||||||
<> "message" .= cMessage c
|
<> "message" .= cMessage c
|
||||||
<> "replaceWith" .= pcFix comment
|
<> "fix" .= pcFix comment
|
||||||
)
|
)
|
||||||
|
|
||||||
|
instance ToJSON Fix where
|
||||||
|
toJSON fix = object [
|
||||||
|
"replacements" .= fixReplacements fix
|
||||||
|
]
|
||||||
|
|
||||||
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg
|
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg
|
||||||
collectResult ref result _ =
|
collectResult ref result _ =
|
||||||
modifyIORef ref (\x -> crComments result ++ x)
|
modifyIORef ref (\x -> crComments result ++ x)
|
||||||
|
|
|
@ -25,6 +25,7 @@ import ShellCheck.Formatter.Format
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Data.IORef
|
import Data.IORef
|
||||||
import Data.List
|
import Data.List
|
||||||
|
import Data.Maybe
|
||||||
import GHC.Exts
|
import GHC.Exts
|
||||||
import System.IO
|
import System.IO
|
||||||
import System.Info
|
import System.Info
|
||||||
|
@ -129,35 +130,53 @@ outputForFile color sys comments = do
|
||||||
putStrLn (color "source" line)
|
putStrLn (color "source" line)
|
||||||
mapM_ (\c -> putStrLn (color (severityText c) $ cuteIndent c)) commentsForLine
|
mapM_ (\c -> putStrLn (color (severityText c) $ cuteIndent c)) commentsForLine
|
||||||
putStrLn ""
|
putStrLn ""
|
||||||
-- in the spirit of error prone
|
-- FIXME: Enable when reasonably stable
|
||||||
mapM_ (\c -> putStrLn "Did you mean:" >> putStrLn (fixedString c line)) commentsForLine
|
-- showFixedString color comments lineNum line
|
||||||
) groups
|
) groups
|
||||||
|
|
||||||
|
hasApplicableFix lineNum comment = fromMaybe False $ do
|
||||||
|
replacements <- fixReplacements <$> pcFix comment
|
||||||
|
guard $ all (\c -> onSameLine (repStartPos c) && onSameLine (repEndPos c)) replacements
|
||||||
|
return True
|
||||||
|
where
|
||||||
|
onSameLine pos = posLine pos == lineNum
|
||||||
|
|
||||||
|
-- FIXME: Work correctly with multiple replacements
|
||||||
|
showFixedString color comments lineNum line =
|
||||||
|
case filter (hasApplicableFix lineNum) comments of
|
||||||
|
(first:_) -> do
|
||||||
|
-- in the spirit of error prone
|
||||||
|
putStrLn $ color "message" "Did you mean: "
|
||||||
|
putStrLn $ fixedString first line
|
||||||
|
putStrLn ""
|
||||||
|
_ -> return ()
|
||||||
|
|
||||||
-- need to do something smart about sorting by end index
|
-- need to do something smart about sorting by end index
|
||||||
fixedString :: PositionedComment -> String -> String
|
fixedString :: PositionedComment -> String -> String
|
||||||
fixedString comment line =
|
fixedString comment line =
|
||||||
case (pcFix comment) of
|
case (pcFix comment) of
|
||||||
Nothing -> ""
|
Nothing -> ""
|
||||||
Just rs ->
|
Just rs ->
|
||||||
apply_replacement rs line 0
|
applyReplacement (fixReplacements rs) line 0
|
||||||
where
|
where
|
||||||
apply_replacement [] s _ = s
|
applyReplacement [] s _ = s
|
||||||
apply_replacement (rep:xs) s offset =
|
applyReplacement (rep:xs) s offset =
|
||||||
let replacementString = repString rep
|
let replacementString = repString rep
|
||||||
start = (posColumn . repStartPos) rep
|
start = (posColumn . repStartPos) rep
|
||||||
end = (posColumn . repEndPos) rep
|
end = (posColumn . repEndPos) rep
|
||||||
z = do_replace start end s replacementString
|
z = doReplace start end s replacementString
|
||||||
len_r = (fromIntegral . length) replacementString in
|
len_r = (fromIntegral . length) replacementString in
|
||||||
apply_replacement xs z (offset + (end - start) + len_r)
|
applyReplacement xs z (offset + (end - start) + len_r)
|
||||||
|
|
||||||
|
-- FIXME: Work correctly with tabs
|
||||||
-- start and end comes from pos, which is 1 based
|
-- start and end comes from pos, which is 1 based
|
||||||
-- do_replace 0 0 "1234" "A" -> "A1234" -- technically not valid
|
-- doReplace 0 0 "1234" "A" -> "A1234" -- technically not valid
|
||||||
-- do_replace 1 1 "1234" "A" -> "A1234"
|
-- doReplace 1 1 "1234" "A" -> "A1234"
|
||||||
-- do_replace 1 2 "1234" "A" -> "A234"
|
-- doReplace 1 2 "1234" "A" -> "A234"
|
||||||
-- do_replace 3 3 "1234" "A" -> "12A34"
|
-- doReplace 3 3 "1234" "A" -> "12A34"
|
||||||
-- do_replace 4 4 "1234" "A" -> "123A4"
|
-- doReplace 4 4 "1234" "A" -> "123A4"
|
||||||
-- do_replace 5 5 "1234" "A" -> "1234A"
|
-- doReplace 5 5 "1234" "A" -> "1234A"
|
||||||
do_replace start end o r =
|
doReplace start end o r =
|
||||||
let si = fromIntegral (start-1)
|
let si = fromIntegral (start-1)
|
||||||
ei = fromIntegral (end-1)
|
ei = fromIntegral (end-1)
|
||||||
(x, xs) = splitAt si o
|
(x, xs) = splitAt si o
|
||||||
|
|
|
@ -49,7 +49,8 @@ module ShellCheck.Interface
|
||||||
, emptyCheckSpec
|
, emptyCheckSpec
|
||||||
, newPositionedComment
|
, newPositionedComment
|
||||||
, newComment
|
, newComment
|
||||||
, Fix
|
, Fix(fixReplacements)
|
||||||
|
, newFix
|
||||||
, Replacement(repStartPos, repEndPos, repString)
|
, Replacement(repStartPos, repEndPos, repString)
|
||||||
, newReplacement
|
, newReplacement
|
||||||
) where
|
) where
|
||||||
|
@ -209,7 +210,13 @@ newReplacement = Replacement {
|
||||||
repString = ""
|
repString = ""
|
||||||
}
|
}
|
||||||
|
|
||||||
type Fix = [Replacement]
|
data Fix = Fix {
|
||||||
|
fixReplacements :: [Replacement]
|
||||||
|
} deriving (Show, Eq)
|
||||||
|
|
||||||
|
newFix = Fix {
|
||||||
|
fixReplacements = []
|
||||||
|
}
|
||||||
|
|
||||||
data PositionedComment = PositionedComment {
|
data PositionedComment = PositionedComment {
|
||||||
pcStartPos :: Position,
|
pcStartPos :: Position,
|
||||||
|
|
Loading…
Reference in New Issue