diff --git a/ShellCheck/AST.hs b/ShellCheck/AST.hs index 1c9a6c7..b82f775 100644 --- a/ShellCheck/AST.hs +++ b/ShellCheck/AST.hs @@ -32,14 +32,11 @@ data ForInType = NormalForIn | ShortForIn deriving (Show, Eq) data CaseType = CaseBreak | CaseFallThrough | CaseContinue deriving (Show, Eq) data Token = - TA_Base Id String Token - | TA_Binary Id String Token Token - | TA_Expansion Id Token - | TA_Literal Id String + TA_Binary Id String Token Token + | TA_Expansion Id [Token] | TA_Sequence Id [Token] | TA_Trinary Id Token Token Token | TA_Unary Id String Token - | TA_Variable Id String | TC_And Id ConditionType String Token Token | TC_Binary Id ConditionType String Token Token | TC_Group Id ConditionType Token @@ -244,8 +241,7 @@ analyze f g i = b <- round t2 c <- round t3 return $ TA_Trinary id a b c - delve (TA_Expansion id t) = d1 t $ TA_Expansion id - delve (TA_Base id b t) = d1 t $ TA_Base id b + delve (TA_Expansion id t) = dl t $ TA_Expansion id delve (T_Annotation id anns t) = d1 t $ T_Annotation id anns delve t = return t @@ -328,11 +324,8 @@ getId t = case t of TA_Binary id _ _ _ -> id TA_Unary id _ _ -> id TA_Sequence id _ -> id - TA_Variable id _ -> id TA_Trinary id _ _ _ -> id TA_Expansion id _ -> id - TA_Literal id _ -> id - TA_Base id _ _ -> id T_ProcSub id _ _ -> id T_Glob id _ -> id T_ForArithmetic id _ _ _ _ -> id diff --git a/ShellCheck/Analytics.hs b/ShellCheck/Analytics.hs index 3744ce1..aee50e1 100644 --- a/ShellCheck/Analytics.hs +++ b/ShellCheck/Analytics.hs @@ -620,6 +620,10 @@ checkBashisms _ = bashism | t `isCommand` "source" = warnMsg id "'source' in place of '.' is" bashism (T_FdRedirect id "&" (T_IoFile _ (T_Greater _) _)) = warnMsg id "&> is" + bashism t@(TA_Expansion id _) | getLiteralString t == Just "RANDOM" = + warnMsg id "RANDOM is" + bashism t@(T_DollarBraced id _) | getBracedReference (bracedString t) == "RANDOM" = + warnMsg id "$RANDOM is" bashism (T_DollarBraced id token) = mapM_ check expansion where @@ -637,8 +641,6 @@ checkBashisms _ = bashism warnMsg (getId arg) "exec flags are" bashism t@(T_SimpleCommand id _ _) | t `isCommand` "let" = warnMsg id "'let' is" - bashism t@(TA_Variable id "RANDOM") = - warnMsg id "RANDOM is" bashism t@(T_Pipe id "|&") = warnMsg id "|& in place of 2>&1 | is" bashism (T_Array id _) = @@ -1163,8 +1165,11 @@ checkBraceExpansionVars _ (T_BraceExpansion id s) | "..$" `isInfixOf` s = checkBraceExpansionVars _ _ = return () prop_checkForDecimals = verify checkForDecimals "((3.14*c))" -checkForDecimals _ (TA_Literal id s) | '.' `elem` s = - err id 2079 "(( )) doesn't support decimals. Use bc or awk." +checkForDecimals _ t@(TA_Expansion id _) = potentially $ do + str <- getLiteralString t + first <- str !!! 0 + guard $ isDigit first && '.' `elem` str + return $ err id 2079 "(( )) doesn't support decimals. Use bc or awk." checkForDecimals _ _ = return () prop_checkDivBeforeMult = verify checkDivBeforeMult "echo $((c/n*100))" @@ -1178,24 +1183,25 @@ prop_checkArithmeticDeref2 = verify checkArithmeticDeref "cow=14; (( s+= $cow )) prop_checkArithmeticDeref3 = verifyNot checkArithmeticDeref "cow=1/40; (( s+= ${cow%%/*} ))" prop_checkArithmeticDeref4 = verifyNot checkArithmeticDeref "(( ! $? ))" prop_checkArithmeticDeref5 = verifyNot checkArithmeticDeref "(($1))" -prop_checkArithmeticDeref6 = verifyNot checkArithmeticDeref "(( ${a[$i]} ))" +prop_checkArithmeticDeref6 = verify checkArithmeticDeref "(( a[$i] ))" prop_checkArithmeticDeref7 = verifyNot checkArithmeticDeref "(( 10#$n ))" -checkArithmeticDeref params t@(TA_Expansion _ (T_DollarBraced id l)) = - unless (excepting (bracedString l) || inBaseExpression) $ +checkArithmeticDeref params t@(TA_Expansion _ [T_DollarBraced id l]) = + unless (excepting $ bracedString l) $ style id 2004 "$ on variables in (( )) is unnecessary." where - inBaseExpression = any isBase $ parents params t - isBase (TA_Base {}) = True - isBase _ = False excepting [] = True - excepting s = any (`elem` "/.:#%?*@[]") s || isDigit (head s) + excepting s = any (`elem` "/.:#%?*@") s || isDigit (head s) checkArithmeticDeref _ _ = return () prop_checkArithmeticBadOctal1 = verify checkArithmeticBadOctal "(( 0192 ))" prop_checkArithmeticBadOctal2 = verifyNot checkArithmeticBadOctal "(( 0x192 ))" prop_checkArithmeticBadOctal3 = verifyNot checkArithmeticBadOctal "(( 1 ^ 0777 ))" -checkArithmeticBadOctal _ (TA_Base id "0" (TA_Literal _ str)) | '9' `elem` str || '8' `elem` str = - err id 2080 "Numbers with leading 0 are considered octal." +checkArithmeticBadOctal _ t@(TA_Expansion id _) = potentially $ do + str <- getLiteralString t + guard $ str `matches` octalRE + return $ err id 2080 "Numbers with leading 0 are considered octal." + where + octalRE = mkRegex "^0[0-7]*[8-9]" checkArithmeticBadOctal _ _ = return () prop_checkComparisonAgainstGlob = verify checkComparisonAgainstGlob "[[ $cow == $bar ]]" @@ -1285,10 +1291,8 @@ isQuoteFree tree t = TC_Noary _ DoubleBracket _ -> return True TC_Unary _ DoubleBracket _ _ -> return True TC_Binary _ DoubleBracket _ _ _ -> return True - TA_Unary {} -> return True - TA_Binary {} -> return True - TA_Trinary {} -> return True - TA_Expansion _ _ -> return True + TA_Sequence {} -> return True + T_Arithmetic {} -> return True T_Assignment {} -> return True T_Redirecting {} -> return $ any (isCommand t) ["local", "declare", "typeset", "export"] @@ -1359,10 +1363,11 @@ getGlobOrLiteralString = getLiteralStringExt f getLiteralStringExt more = g where - allInList l = let foo = map g l in if all isJust foo then return $ concat (catMaybes foo) else Nothing - g s@(T_DoubleQuoted _ l) = allInList l - g s@(T_DollarDoubleQuoted _ l) = allInList l - g s@(T_NormalWord _ l) = allInList l + allInList = liftM concat . sequence . map g + g (T_DoubleQuoted _ l) = allInList l + g (T_DollarDoubleQuoted _ l) = allInList l + g (T_NormalWord _ l) = allInList l + g (TA_Expansion _ l) = allInList l g (T_SingleQuoted _ s) = return s g (T_Literal _ s) = return s g x = more x @@ -1899,10 +1904,16 @@ getModifiedVariables t = c@(T_SimpleCommand {}) -> getModifiedVariableCommand c - TA_Unary _ "++|" (TA_Variable id name) -> [(t, t, name, DataFrom [t])] - TA_Unary _ "|++" (TA_Variable id name) -> [(t, t, name, DataFrom [t])] - TA_Binary _ op (TA_Variable id name) rhs -> - [(t, t, name, DataFrom [rhs]) | op `elem` ["=", "*=", "/=", "%=", "+=", "-=", "<<=", ">>=", "&=", "^=", "|="]] + TA_Unary _ "++|" var -> maybeToList $ do + name <- getLiteralString var + return (t, t, name, DataFrom [t]) + TA_Unary _ "|++" var -> maybeToList $ do + name <- getLiteralString var + return (t, t, name, DataFrom [t]) + TA_Binary _ op lhs rhs -> maybeToList $ do + guard $ op `elem` ["=", "*=", "/=", "%=", "+=", "-=", "<<=", ">>=", "&=", "^=", "|="] + name <- getLiteralString lhs + return (t, t, name, DataFrom [rhs]) --Points to 'for' rather than variable T_ForIn id _ strs words _ -> map (\str -> (t, t, str, DataFrom words)) strs @@ -1976,8 +1987,9 @@ getReferencedVariables t = T_DollarBraced id l -> let str = bracedString l in (t, t, getBracedReference str) : map (\x -> (l, l, x)) (getIndexReferences str) - TA_Variable id str -> - map (\x -> (t, t, x)) $ getBracedReference str:getIndexReferences str + TA_Expansion id _ -> maybeToList $ do + str <- getLiteralStringExt (const $ return "#") t + return (t, t, getBracedReference str) T_Assignment id Append str _ _ -> [(t, t, str)] x -> getReferencedVariableCommand x diff --git a/ShellCheck/Data.hs b/ShellCheck/Data.hs index 781d277..0717bb1 100644 --- a/ShellCheck/Data.hs +++ b/ShellCheck/Data.hs @@ -1,9 +1,9 @@ module ShellCheck.Data where import Data.Version (showVersion) -import Paths_ShellCheck (version) +--import Paths_ShellCheck (version) -shellcheckVersion = showVersion version +shellcheckVersion = "1" --showVersion version internalVariables = [ -- Generic diff --git a/ShellCheck/Parser.hs b/ShellCheck/Parser.hs index a87a5de..adde1a0 100644 --- a/ShellCheck/Parser.hs +++ b/ShellCheck/Parser.hs @@ -111,7 +111,7 @@ nbsp = do data Note = Note Id Severity Code String deriving (Show, Eq) data ParseNote = ParseNote SourcePos Severity Code String deriving (Show, Eq) data Severity = ErrorC | WarningC | InfoC | StyleC deriving (Show, Eq, Ord) -data Context = ContextName SourcePos String | ContextAnnotation [Annotation] +data Context = ContextName SourcePos String | ContextAnnotation [Annotation] deriving (Show) type Code = Integer codeForParseNote (ParseNote _ _ code _) = code @@ -468,6 +468,7 @@ prop_aC = isOk readArithmeticContents "\"$((3+2))\" + '37'" prop_aD = isOk readArithmeticContents "foo[9*y+x]++" prop_aE = isOk readArithmeticContents "1+`echo 2`" prop_aF = isOk readArithmeticContents "foo[`echo foo | sed s/foo/4/g` * 3] + 4" +prop_a10= isOk readArithmeticContents "$foo$bar" readArithmeticContents = readSequence where @@ -485,25 +486,35 @@ readArithmeticContents = spacing return $ token id op - readVar = do - id <- getNextId - x <- readVariableName - y <- readArrayIndex <|> return "" - optional spacing - return $ TA_Variable id (x ++ y) - - -- Doesn't help with foo[foo] readArrayIndex = do - char '[' - x <- many1 $ noneOf "]" - char ']' - return $ "[" ++ x ++ "]" + id <- getNextId + start <- literal "[" + middle <- readArithmeticContents + end <- literal "]" + return $ T_NormalWord id [start, middle, end] + + literal s = do + id <- getNextId + string s + return $ T_Literal id s + + readArithmeticLiteral = + readArrayIndex <|> literal "#" readExpansion = do id <- getNextId - x <- readNormalDollar <|> readBackTicked + pieces <- many1 $ choice [ + readArithmeticLiteral, + readSingleQuoted, + readDoubleQuoted, + readNormalDollar, + readBraced, + readBackTicked, + readProcSub, + readNormalLiteral "+-*/=%^,]" + ] spacing - return $ TA_Expansion id x + return $ TA_Expansion id pieces readGroup = do char '(' @@ -512,40 +523,7 @@ readArithmeticContents = spacing return s - readNumber = do - id <- getNextId - num <- many1 $ oneOf "0123456789." - return $ TA_Literal id num - - readBased = getArbitrary <|> getHex <|> getOct - where - getThing prefix litchars = try $ do - id <- getNextId - x <- prefix - t <- readExpansion <|> (do - i <- getNextId - stuff <- many1 litchars - return $ TA_Literal i stuff) - return $ TA_Base id x t - - getArbitrary = getThing arbitrary variableChars - getHex = getThing hex hexDigit - getOct = getThing oct digit - - arbitrary = try $ do - b <- many1 digit - s <- char '#' - return (b ++ [s]) - hex = try $ do - z <- char '0' - x <- oneOf "xX" - return [z, x] - oct = string "0" - - readArithTerm = readBased <|> readArithTermUnit - readArithTermUnit = readGroup <|> readExpansion <|> readQuoted <|> readNumber <|> readVar - - readQuoted = readDoubleQuoted <|> readSingleQuoted + readArithTerm = readGroup <|> readExpansion readSequence = do spacing @@ -724,6 +702,7 @@ checkPossibleTermination pos [T_Literal _ x] = checkPossibleTermination _ _ = return () readNormalWordPart end = do + notFollowedBy2 $ oneOf end checkForParenthesis choice [ readSingleQuoted, @@ -858,7 +837,7 @@ readBackTicked = called "backtick expansion" $ do disregard (char '`') <|> do pos <- getPosition char '´' - parseProblemAt pos ErrorC 1077 + parseProblemAt pos ErrorC 1077 "For command expansion, the tick should slant left (` vs ´)." subParse pos parser input = do