diff --git a/CHANGELOG.md b/CHANGELOG.md index 669579f..cef16f4 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -5,6 +5,8 @@ - SC2318: Warn about backreferences in 'declare x=1 y=$x' - SC2319/SC2320: Warn when $? refers to echo/printf/[ ]/[[ ]]/test - SC2321: Suggest removing $((..)) in array[$((idx))]=val +- SC2322: Suggest collapsing double parentheses in arithmetic contexts +- SC2323: Suggest removing wrapping parentheses in a[(x+1)]=val ### Fixed - SC2086: Now uses DFA to make more accurate predictions about values diff --git a/src/ShellCheck/AST.hs b/src/ShellCheck/AST.hs index 2cd2f6f..ca5007a 100644 --- a/src/ShellCheck/AST.hs +++ b/src/ShellCheck/AST.hs @@ -45,6 +45,7 @@ data InnerToken t = | Inner_TA_Variable String [t] | Inner_TA_Expansion [t] | Inner_TA_Sequence [t] + | Inner_TA_Parenthesis t | Inner_TA_Trinary t t t | Inner_TA_Unary String t | Inner_TC_And ConditionType String t t @@ -204,6 +205,7 @@ pattern T_Annotation id anns t = OuterToken id (Inner_T_Annotation anns t) pattern T_Arithmetic id c = OuterToken id (Inner_T_Arithmetic c) pattern T_Array id t = OuterToken id (Inner_T_Array t) pattern TA_Sequence id l = OuterToken id (Inner_TA_Sequence l) +pattern TA_Parentesis id t = OuterToken id (Inner_TA_Parenthesis t) pattern T_Assignment id mode var indices value = OuterToken id (Inner_T_Assignment mode var indices value) pattern TA_Trinary id t1 t2 t3 = OuterToken id (Inner_TA_Trinary t1 t2 t3) pattern TA_Unary id op t1 = OuterToken id (Inner_TA_Unary op t1) @@ -256,7 +258,7 @@ pattern T_Subshell id l = OuterToken id (Inner_T_Subshell l) pattern T_UntilExpression id c l = OuterToken id (Inner_T_UntilExpression c l) pattern T_WhileExpression id c l = OuterToken id (Inner_T_WhileExpression c l) -{-# COMPLETE T_AND_IF, T_Bang, T_Case, TC_Empty, T_CLOBBER, T_DGREAT, T_DLESS, T_DLESSDASH, T_Do, T_DollarSingleQuoted, T_Done, T_DSEMI, T_Elif, T_Else, T_EOF, T_Esac, T_Fi, T_For, T_Glob, T_GREATAND, T_Greater, T_If, T_In, T_Lbrace, T_Less, T_LESSAND, T_LESSGREAT, T_Literal, T_Lparen, T_NEWLINE, T_OR_IF, T_ParamSubSpecialChar, T_Pipe, T_Rbrace, T_Rparen, T_Select, T_Semi, T_SingleQuoted, T_Then, T_UnparsedIndex, T_Until, T_While, TA_Assignment, TA_Binary, TA_Expansion, T_AndIf, T_Annotation, T_Arithmetic, T_Array, TA_Sequence, T_Assignment, TA_Trinary, TA_Unary, TA_Variable, T_Backgrounded, T_Backticked, T_Banged, T_BatsTest, T_BraceExpansion, T_BraceGroup, TC_And, T_CaseExpression, TC_Binary, TC_Group, TC_Nullary, T_Condition, T_CoProcBody, T_CoProc, TC_Or, TC_Unary, T_DollarArithmetic, T_DollarBraceCommandExpansion, T_DollarBraced, T_DollarBracket, T_DollarDoubleQuoted, T_DollarExpansion, T_DoubleQuoted, T_Extglob, T_FdRedirect, T_ForArithmetic, T_ForIn, T_Function, T_HereDoc, T_HereString, T_IfExpression, T_Include, T_IndexedElement, T_IoDuplicate, T_IoFile, T_NormalWord, T_OrIf, T_Pipeline, T_ProcSub, T_Redirecting, T_Script, T_SelectIn, T_SimpleCommand, T_SourceCommand, T_Subshell, T_UntilExpression, T_WhileExpression #-} +{-# COMPLETE T_AND_IF, T_Bang, T_Case, TC_Empty, T_CLOBBER, T_DGREAT, T_DLESS, T_DLESSDASH, T_Do, T_DollarSingleQuoted, T_Done, T_DSEMI, T_Elif, T_Else, T_EOF, T_Esac, T_Fi, T_For, T_Glob, T_GREATAND, T_Greater, T_If, T_In, T_Lbrace, T_Less, T_LESSAND, T_LESSGREAT, T_Literal, T_Lparen, T_NEWLINE, T_OR_IF, T_ParamSubSpecialChar, T_Pipe, T_Rbrace, T_Rparen, T_Select, T_Semi, T_SingleQuoted, T_Then, T_UnparsedIndex, T_Until, T_While, TA_Assignment, TA_Binary, TA_Expansion, T_AndIf, T_Annotation, T_Arithmetic, T_Array, TA_Sequence, TA_Parentesis, T_Assignment, TA_Trinary, TA_Unary, TA_Variable, T_Backgrounded, T_Backticked, T_Banged, T_BatsTest, T_BraceExpansion, T_BraceGroup, TC_And, T_CaseExpression, TC_Binary, TC_Group, TC_Nullary, T_Condition, T_CoProcBody, T_CoProc, TC_Or, TC_Unary, T_DollarArithmetic, T_DollarBraceCommandExpansion, T_DollarBraced, T_DollarBracket, T_DollarDoubleQuoted, T_DollarExpansion, T_DoubleQuoted, T_Extglob, T_FdRedirect, T_ForArithmetic, T_ForIn, T_Function, T_HereDoc, T_HereString, T_IfExpression, T_Include, T_IndexedElement, T_IoDuplicate, T_IoFile, T_NormalWord, T_OrIf, T_Pipeline, T_ProcSub, T_Redirecting, T_Script, T_SelectIn, T_SimpleCommand, T_SourceCommand, T_Subshell, T_UntilExpression, T_WhileExpression #-} instance Eq Token where OuterToken _ a == OuterToken _ b = a == b diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index e92f3ff..eed2d25 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -207,6 +207,7 @@ nodeChecks = [ ,checkSpacefulnessCfg ,checkOverwrittenExitCode ,checkUnnecessaryArithmeticExpansionIndex + ,checkUnnecessaryParens ] optionalChecks = map fst optionalTreeChecks @@ -3280,6 +3281,7 @@ checkReturnAgainstZero params token = _:next@(TA_Unary _ "!" _):_ -> isOnlyTestInCommand next _:next@(TC_Group {}):_ -> isOnlyTestInCommand next _:next@(TA_Sequence _ [_]):_ -> isOnlyTestInCommand next + _:next@(TA_Parentesis _ _):_ -> isOnlyTestInCommand next _ -> False -- TODO: Do better $? tracking and filter on whether @@ -4931,5 +4933,36 @@ checkUnnecessaryArithmeticExpansionIndex params t = ] +prop_checkUnnecessaryParens1 = verify checkUnnecessaryParens "echo $(( ((1+1)) ))" +prop_checkUnnecessaryParens2 = verify checkUnnecessaryParens "x[((1+1))+1]=1" +prop_checkUnnecessaryParens3 = verify checkUnnecessaryParens "x[(1+1)]=1" +prop_checkUnnecessaryParens4 = verify checkUnnecessaryParens "$(( (x) ))" +prop_checkUnnecessaryParens5 = verify checkUnnecessaryParens "(( (x) ))" +prop_checkUnnecessaryParens6 = verifyNot checkUnnecessaryParens "x[(1+1)+1]=1" +prop_checkUnnecessaryParens7 = verifyNot checkUnnecessaryParens "(( (1*1)+1 ))" +prop_checkUnnecessaryParens8 = verifyNot checkUnnecessaryParens "(( (1)+1 ))" +checkUnnecessaryParens params t = + case t of + T_DollarArithmetic _ t -> checkLeading "$(( (x) )) is the same as $(( x ))" t + T_ForArithmetic _ x y z _ -> mapM_ (checkLeading "for (((x); (y); (z))) is the same as for ((x; y; z))") [x,y,z] + T_Assignment _ _ _ [t] _ -> checkLeading "a[(x)] is the same as a[x]" t + T_Arithmetic _ t -> checkLeading "(( (x) )) is the same as (( x ))" t + TA_Parentesis _ (TA_Sequence _ [ TA_Parentesis id _ ]) -> + styleWithFix id 2322 "In arithmetic contexts, ((x)) is the same as (x). Prefer only one layer of parentheses." $ fix id + _ -> return () + where + + checkLeading str t = + case t of + TA_Sequence _ [TA_Parentesis id _ ] -> styleWithFix id 2323 (str ++ ". Prefer not wrapping in additional parentheses.") $ fix id + _ -> return () + + fix id = + fixWith [ + replaceStart id params 1 "", -- Remove "(" + replaceEnd id params 1 "" -- Remove ")" + ] + + return [] runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |]) diff --git a/src/ShellCheck/CFG.hs b/src/ShellCheck/CFG.hs index 1085d8f..6f6d4f1 100644 --- a/src/ShellCheck/CFG.hs +++ b/src/ShellCheck/CFG.hs @@ -479,6 +479,7 @@ build t = do TA_Binary _ _ a b -> sequentially [a,b] TA_Expansion _ list -> sequentially list TA_Sequence _ list -> sequentially list + TA_Parentesis _ t -> build t TA_Trinary _ cond a b -> do condition <- build cond diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index e6a2999..0dd6621 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -821,11 +821,13 @@ readArithmeticContents = return $ TA_Expansion id pieces readGroup = do + start <- startSpan char '(' s <- readSequence char ')' + id <- endSpan start spacing - return s + return $ TA_Parentesis id s readArithTerm = readGroup <|> readVariable <|> readExpansion