Expose token positions in params, use that to construct fixes
This commit is contained in:
parent
41613babd9
commit
4a87d2a3de
|
@ -241,6 +241,31 @@ isCondition (child:parent:rest) =
|
||||||
T_UntilExpression id c l -> take 1 . reverse $ c
|
T_UntilExpression id c l -> take 1 . reverse $ c
|
||||||
_ -> []
|
_ -> []
|
||||||
|
|
||||||
|
-- helpers to build replacements
|
||||||
|
replace_start id params n r =
|
||||||
|
let tp = tokenPositions params
|
||||||
|
(start, _) = tp Map.! id
|
||||||
|
new_end = start {
|
||||||
|
posColumn = posColumn start + n
|
||||||
|
}
|
||||||
|
in
|
||||||
|
[R start new_end r]
|
||||||
|
replace_end id params n r =
|
||||||
|
-- because of the way we count columns 1-based
|
||||||
|
-- we have to offset end columns by 1
|
||||||
|
let tp = tokenPositions params
|
||||||
|
(_, end) = tp Map.! id
|
||||||
|
new_start = end {
|
||||||
|
posColumn = posColumn end - n + 1
|
||||||
|
}
|
||||||
|
new_end = end {
|
||||||
|
posColumn = posColumn end + 1
|
||||||
|
}
|
||||||
|
in
|
||||||
|
[R new_start new_end r]
|
||||||
|
surround_with id params s =
|
||||||
|
(replace_start id params 0 s) ++ (replace_end id params 0 s)
|
||||||
|
|
||||||
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]) =
|
||||||
when (acmd == ["echo", "${VAR}"]) $
|
when (acmd == ["echo", "${VAR}"]) $
|
||||||
|
@ -1335,10 +1360,10 @@ checkPS1Assignments _ _ = return ()
|
||||||
prop_checkBackticks1 = verify checkBackticks "echo `foo`"
|
prop_checkBackticks1 = verify checkBackticks "echo `foo`"
|
||||||
prop_checkBackticks2 = verifyNot checkBackticks "echo $(foo)"
|
prop_checkBackticks2 = verifyNot checkBackticks "echo $(foo)"
|
||||||
prop_checkBackticks3 = verifyNot checkBackticks "echo `#inlined comment` foo"
|
prop_checkBackticks3 = verifyNot checkBackticks "echo `#inlined comment` foo"
|
||||||
checkBackticks _ (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 `...`."
|
||||||
((replaceStart 1 "$(") ++ (replaceEnd 1 ")"))
|
((replace_start id params 1 "$(") ++ (replace_end id params 1 ")"))
|
||||||
-- style id 2006 "Use $(...) notation instead of legacy backticked `...`."
|
-- style id 2006 "Use $(...) notation instead of legacy backticked `...`."
|
||||||
checkBackticks _ _ = return ()
|
checkBackticks _ _ = return ()
|
||||||
|
|
||||||
|
@ -1644,7 +1669,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." (surroundWith "\"")
|
"Double quote to prevent globbing and word splitting." (surround_with (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."
|
||||||
|
|
||||||
|
@ -2545,7 +2570,7 @@ checkUncheckedCdPushdPopd params root =
|
||||||
&& 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."
|
-- 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."
|
||||||
(replaceEnd 0 " || exit")
|
(replace_end (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
|
||||||
|
@ -2702,7 +2727,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." (surroundWith "\"")
|
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 "\"")
|
||||||
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 ) ."
|
||||||
|
|
|
@ -81,7 +81,8 @@ data Parameters = Parameters {
|
||||||
parentMap :: Map.Map Id Token, -- A map from Id to parent Token
|
parentMap :: Map.Map Id Token, -- A map from Id to parent Token
|
||||||
shellType :: Shell, -- The shell type, such as Bash or Ksh
|
shellType :: Shell, -- The shell type, such as Bash or Ksh
|
||||||
shellTypeSpecified :: Bool, -- True if shell type was forced via flags
|
shellTypeSpecified :: Bool, -- True if shell type was forced via flags
|
||||||
rootNode :: Token -- The root node of the AST
|
rootNode :: Token, -- The root node of the AST
|
||||||
|
tokenPositions :: Map.Map Id (Position, Position) -- map from token id to start and end position
|
||||||
}
|
}
|
||||||
|
|
||||||
-- TODO: Cache results of common AST ops here
|
-- TODO: Cache results of common AST ops here
|
||||||
|
@ -177,7 +178,8 @@ makeParameters spec =
|
||||||
|
|
||||||
shellTypeSpecified = isJust $ asShellType spec,
|
shellTypeSpecified = isJust $ asShellType spec,
|
||||||
parentMap = getParentTree root,
|
parentMap = getParentTree root,
|
||||||
variableFlow = getVariableFlow params root
|
variableFlow = getVariableFlow params root,
|
||||||
|
tokenPositions = asTokenPositions spec
|
||||||
} in params
|
} in params
|
||||||
where root = asScript spec
|
where root = asScript spec
|
||||||
|
|
||||||
|
|
|
@ -64,11 +64,20 @@ checkScript sys spec = do
|
||||||
psShellTypeOverride = csShellTypeOverride spec
|
psShellTypeOverride = csShellTypeOverride spec
|
||||||
}
|
}
|
||||||
let parseMessages = prComments result
|
let parseMessages = prComments result
|
||||||
|
let tokenPositions = prTokenPositions result
|
||||||
|
let analysisSpec root =
|
||||||
|
as {
|
||||||
|
asScript = root,
|
||||||
|
asShellType = csShellTypeOverride spec,
|
||||||
|
asCheckSourced = csCheckSourced spec,
|
||||||
|
asExecutionMode = Executed,
|
||||||
|
asTokenPositions = tokenPositions
|
||||||
|
} where as = newAnalysisSpec root
|
||||||
let analysisMessages =
|
let analysisMessages =
|
||||||
fromMaybe [] $
|
fromMaybe [] $
|
||||||
(arComments . analyzeScript . analysisSpec)
|
(arComments . analyzeScript . analysisSpec)
|
||||||
<$> prRoot result
|
<$> prRoot result
|
||||||
let translator = tokenToPosition (prTokenPositions result)
|
let translator = tokenToPosition tokenPositions
|
||||||
return . nub . sortMessages . filter shouldInclude $
|
return . nub . sortMessages . filter shouldInclude $
|
||||||
(parseMessages ++ map translator analysisMessages)
|
(parseMessages ++ map translator analysisMessages)
|
||||||
|
|
||||||
|
@ -91,13 +100,6 @@ checkScript sys spec = do
|
||||||
cMessage comment)
|
cMessage comment)
|
||||||
getPosition = pcStartPos
|
getPosition = pcStartPos
|
||||||
|
|
||||||
analysisSpec root =
|
|
||||||
as {
|
|
||||||
asScript = root,
|
|
||||||
asShellType = csShellTypeOverride spec,
|
|
||||||
asCheckSourced = csCheckSourced spec,
|
|
||||||
asExecutionMode = Executed
|
|
||||||
} where as = newAnalysisSpec root
|
|
||||||
|
|
||||||
getErrors sys spec =
|
getErrors sys spec =
|
||||||
sort . map getCode . crComments $
|
sort . map getCode . crComments $
|
||||||
|
|
|
@ -118,8 +118,8 @@ outputForFile color sys comments = do
|
||||||
let fileLines = lines contents
|
let fileLines = lines contents
|
||||||
let lineCount = fromIntegral $ length fileLines
|
let lineCount = fromIntegral $ length fileLines
|
||||||
let groups = groupWith lineNo comments
|
let groups = groupWith lineNo comments
|
||||||
mapM_ (\x -> do
|
mapM_ (\commentsForLine -> do
|
||||||
let lineNum = lineNo (head x)
|
let lineNum = lineNo (head commentsForLine)
|
||||||
let line = if lineNum < 1 || lineNum > lineCount
|
let line = if lineNum < 1 || lineNum > lineCount
|
||||||
then ""
|
then ""
|
||||||
else fileLines !! fromIntegral (lineNum - 1)
|
else fileLines !! fromIntegral (lineNum - 1)
|
||||||
|
@ -127,9 +127,10 @@ outputForFile color sys comments = do
|
||||||
putStrLn $ color "message" $
|
putStrLn $ color "message" $
|
||||||
"In " ++ fileName ++" line " ++ show lineNum ++ ":"
|
"In " ++ fileName ++" line " ++ show lineNum ++ ":"
|
||||||
putStrLn (color "source" line)
|
putStrLn (color "source" line)
|
||||||
mapM_ (\c -> putStrLn (color (severityText c) $ cuteIndent c)) x
|
mapM_ (\c -> putStrLn (color (severityText c) $ cuteIndent c)) commentsForLine
|
||||||
putStrLn ""
|
putStrLn ""
|
||||||
mapM_ (\c -> putStrLn "Did you mean:" >> putStrLn (fixedString c line)) x
|
-- in the spirit of error prone
|
||||||
|
mapM_ (\c -> putStrLn "Did you mean:" >> putStrLn (fixedString c line)) commentsForLine
|
||||||
) groups
|
) groups
|
||||||
|
|
||||||
-- need to do something smart about sorting by end index
|
-- need to do something smart about sorting by end index
|
||||||
|
@ -141,16 +142,9 @@ fixedString comment line =
|
||||||
apply_replacement rs line 0
|
apply_replacement rs line 0
|
||||||
where
|
where
|
||||||
apply_replacement [] s _ = s
|
apply_replacement [] s _ = s
|
||||||
apply_replacement ((Start n r):xs) s offset =
|
apply_replacement ((R startp endp r):xs) s offset =
|
||||||
let start = (posColumn . pcStartPos) comment
|
let start = posColumn startp
|
||||||
end = start + n
|
end = posColumn endp
|
||||||
z = do_replace start end s r
|
|
||||||
len_r = (fromIntegral . length) r in
|
|
||||||
apply_replacement xs z (offset + (end - start) + len_r)
|
|
||||||
apply_replacement ((End n r):xs) s offset =
|
|
||||||
-- tricky math because column is 1 based
|
|
||||||
let end = (posColumn . pcEndPos) comment + 1
|
|
||||||
start = end - n
|
|
||||||
z = do_replace start end s r
|
z = do_replace start end s r
|
||||||
len_r = (fromIntegral . length) r in
|
len_r = (fromIntegral . length) r in
|
||||||
apply_replacement xs z (offset + (end - start) + len_r)
|
apply_replacement xs z (offset + (end - start) + len_r)
|
||||||
|
|
|
@ -24,7 +24,7 @@ module ShellCheck.Interface
|
||||||
, CheckResult(crFilename, crComments)
|
, CheckResult(crFilename, crComments)
|
||||||
, ParseSpec(psFilename, psScript, psCheckSourced, psShellTypeOverride)
|
, ParseSpec(psFilename, psScript, psCheckSourced, psShellTypeOverride)
|
||||||
, ParseResult(prComments, prTokenPositions, prRoot)
|
, ParseResult(prComments, prTokenPositions, prRoot)
|
||||||
, AnalysisSpec(asScript, asShellType, asExecutionMode, asCheckSourced)
|
, AnalysisSpec(asScript, asShellType, asExecutionMode, asCheckSourced, asTokenPositions)
|
||||||
, AnalysisResult(arComments)
|
, AnalysisResult(arComments)
|
||||||
, FormatterOptions(foColorOption, foWikiLinkCount)
|
, FormatterOptions(foColorOption, foWikiLinkCount)
|
||||||
, Shell(Ksh, Sh, Bash, Dash)
|
, Shell(Ksh, Sh, Bash, Dash)
|
||||||
|
@ -50,10 +50,7 @@ module ShellCheck.Interface
|
||||||
, newPositionedComment
|
, newPositionedComment
|
||||||
, newComment
|
, newComment
|
||||||
, Fix
|
, Fix
|
||||||
, Replacement(Start, End)
|
, Replacement(R)
|
||||||
, surroundWith
|
|
||||||
, replaceStart
|
|
||||||
, replaceEnd
|
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import ShellCheck.AST
|
import ShellCheck.AST
|
||||||
|
@ -132,14 +129,16 @@ data AnalysisSpec = AnalysisSpec {
|
||||||
asScript :: Token,
|
asScript :: Token,
|
||||||
asShellType :: Maybe Shell,
|
asShellType :: Maybe Shell,
|
||||||
asExecutionMode :: ExecutionMode,
|
asExecutionMode :: ExecutionMode,
|
||||||
asCheckSourced :: Bool
|
asCheckSourced :: Bool,
|
||||||
|
asTokenPositions :: Map.Map Id (Position, Position)
|
||||||
}
|
}
|
||||||
|
|
||||||
newAnalysisSpec token = AnalysisSpec {
|
newAnalysisSpec token = AnalysisSpec {
|
||||||
asScript = token,
|
asScript = token,
|
||||||
asShellType = Nothing,
|
asShellType = Nothing,
|
||||||
asExecutionMode = Executed,
|
asExecutionMode = Executed,
|
||||||
asCheckSourced = False
|
asCheckSourced = False,
|
||||||
|
asTokenPositions = Map.empty
|
||||||
}
|
}
|
||||||
|
|
||||||
newtype AnalysisResult = AnalysisResult {
|
newtype AnalysisResult = AnalysisResult {
|
||||||
|
@ -198,23 +197,11 @@ newComment = Comment {
|
||||||
|
|
||||||
-- only support single line for now
|
-- only support single line for now
|
||||||
data Replacement =
|
data Replacement =
|
||||||
Start Integer String
|
R Position Position String
|
||||||
| End Integer String
|
|
||||||
deriving (Show, Eq)
|
deriving (Show, Eq)
|
||||||
|
|
||||||
type Fix = [Replacement]
|
type Fix = [Replacement]
|
||||||
|
|
||||||
surroundWith s =
|
|
||||||
(replaceStart 0 s) ++ (replaceEnd 0 s)
|
|
||||||
|
|
||||||
-- replace first n chars
|
|
||||||
replaceStart n r =
|
|
||||||
[ Start n r ]
|
|
||||||
|
|
||||||
-- replace last n chars
|
|
||||||
replaceEnd n r =
|
|
||||||
[ End n r ]
|
|
||||||
|
|
||||||
data PositionedComment = PositionedComment {
|
data PositionedComment = PositionedComment {
|
||||||
pcStartPos :: Position,
|
pcStartPos :: Position,
|
||||||
pcEndPos :: Position,
|
pcEndPos :: Position,
|
||||||
|
|
Loading…
Reference in New Issue