mirror of
				https://github.com/koalaman/shellcheck.git
				synced 2025-11-04 09:26:10 +08:00 
			
		
		
		
	Rewrote catastrophic rm detection, now simpler and more robust.
This commit is contained in:
		@@ -2618,46 +2618,50 @@ checkFunctionDeclarations params
 | 
			
		||||
checkFunctionDeclarations _ _ = return ()
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
-- This is a lot of code for little gain. Consider whether it's worth it.
 | 
			
		||||
prop_checkCatastrophicRm1 = verify checkCatastrophicRm "rm -r $1/$2"
 | 
			
		||||
prop_checkCatastrophicRm2 = verify checkCatastrophicRm "foo=$(echo bar); rm -r /home/$foo"
 | 
			
		||||
prop_checkCatastrophicRm3 = verify checkCatastrophicRm "foo=/home; user=$(whoami); rm -r \"$foo/$user\""
 | 
			
		||||
prop_checkCatastrophicRm4 = verifyNot checkCatastrophicRm "foo=/home; user=cow; rm -r \"$foo/$user\""
 | 
			
		||||
prop_checkCatastrophicRm5 = verifyNot checkCatastrophicRm "user=$(whoami); rm -r /home/${user:?Nope}"
 | 
			
		||||
prop_checkCatastrophicRm2 = verify checkCatastrophicRm "rm -r /home/$foo"
 | 
			
		||||
prop_checkCatastrophicRm3 = verifyNot checkCatastrophicRm "rm -r /home/${USER:?}/*"
 | 
			
		||||
prop_checkCatastrophicRm4 = verify checkCatastrophicRm "rm -fr /home/$(whoami)/*"
 | 
			
		||||
prop_checkCatastrophicRm5 = verifyNot checkCatastrophicRm "rm -r /home/${USER:-thing}/*"
 | 
			
		||||
prop_checkCatastrophicRm6 = verify checkCatastrophicRm "rm --recursive /etc/*$config*"
 | 
			
		||||
prop_checkCatastrophicRm7 = verifyNot checkCatastrophicRm "var=$(cmd); if [ -n \"$var\" ]; then rm -r /etc/$var/*; fi"
 | 
			
		||||
prop_checkCatastrophicRm8 = verify checkCatastrophicRm "rm -rf /home"
 | 
			
		||||
prop_checkCatastrophicRm9 = verifyNot checkCatastrophicRm "rm -rf -- /home"
 | 
			
		||||
prop_checkCatastrophicRmA = verify checkCatastrophicRm "rm -rf /usr /lib/nvidia-current/xorg/xorg"
 | 
			
		||||
prop_checkCatastrophicRmB = verify checkCatastrophicRm "rm -rf \"$STEAMROOT/\"*"
 | 
			
		||||
checkCatastrophicRm params t@(T_SimpleCommand id _ tokens) | t `isCommand` "rm" =
 | 
			
		||||
    when (any isRecursiveFlag simpleArgs) $
 | 
			
		||||
        mapM_ checkWord tokens
 | 
			
		||||
  where
 | 
			
		||||
    -- This ugly hack is based on the fact that ids generally increase
 | 
			
		||||
    relevantMap (Id n) = liftM snd . listToMaybe . dropWhile (\(Id x, _) ->  x > n) $ flowMapR
 | 
			
		||||
    flowMapR = reverse $ (\x -> zip (scanl getScopeId (Id 0) x) (scanl addNulls defaultMap x)) $ variableFlow params
 | 
			
		||||
    simpleArgs = deadSimple t
 | 
			
		||||
    defaultMap = Map.fromList (map (\x -> (x, Nothing)) variablesWithoutSpaces)
 | 
			
		||||
 | 
			
		||||
    checkWord token =
 | 
			
		||||
        case getLiteralString token of
 | 
			
		||||
            Just str ->
 | 
			
		||||
                when (notElem "--" simpleArgs && (fixPath str `elem` importantPaths)) $
 | 
			
		||||
                    info (getId token) 2114 "Obligatory typo warning. Use 'rm --' to disable this message."
 | 
			
		||||
                    warn (getId token) 2114 "Warning: deletes a system directory. Use 'rm --' to disable this message."
 | 
			
		||||
            Nothing ->
 | 
			
		||||
                checkWord' token
 | 
			
		||||
 | 
			
		||||
    checkWord' token = fromMaybe (return ()) $ do
 | 
			
		||||
        m <- relevantMap id
 | 
			
		||||
        filename <- combine m token
 | 
			
		||||
        filename <- getPotentialPath token
 | 
			
		||||
        let path = fixPath filename
 | 
			
		||||
        return . when (path `elem` importantPaths) $
 | 
			
		||||
            warn (getId token) 2115 $ "Make sure this never accidentally expands to '" ++ path ++ "'."
 | 
			
		||||
            warn (getId token) 2115 $ "Use \"${var:?}\" to ensure this never expands to " ++ path ++ " ."
 | 
			
		||||
 | 
			
		||||
    fixPath filename =
 | 
			
		||||
        let normalized = skipRepeating '/' . skipRepeating '*' $ filename in
 | 
			
		||||
            if normalized == "/" then normalized else stripTrailing '/' normalized
 | 
			
		||||
 | 
			
		||||
    unnullable = all isVariableChar . concat . deadSimple
 | 
			
		||||
    getPotentialPath = getLiteralStringExt f
 | 
			
		||||
      where
 | 
			
		||||
        f (T_Glob _ str) = return str
 | 
			
		||||
        f (T_DollarBraced _ word) =
 | 
			
		||||
            let var = onlyLiteralString word in
 | 
			
		||||
                if any (flip isInfixOf var) [":?", ":-", ":="]
 | 
			
		||||
                then Nothing
 | 
			
		||||
                else return ""
 | 
			
		||||
        f _ = return ""
 | 
			
		||||
 | 
			
		||||
    isRecursiveFlag "--recursive" = True
 | 
			
		||||
    isRecursiveFlag ('-':'-':_) = False
 | 
			
		||||
    isRecursiveFlag ('-':str) = 'r' `elem` str || 'R' `elem` str
 | 
			
		||||
@@ -2668,55 +2672,12 @@ checkCatastrophicRm params t@(T_SimpleCommand id _ tokens) | t `isCommand` "rm"
 | 
			
		||||
    skipRepeating c (a:r) = a:skipRepeating c r
 | 
			
		||||
    skipRepeating _ [] = []
 | 
			
		||||
 | 
			
		||||
    addNulls map (Reference (_, token, name)) =
 | 
			
		||||
        if mightBeGuarded token
 | 
			
		||||
        then Map.insert name Nothing map
 | 
			
		||||
        else map
 | 
			
		||||
    addNulls map (Assignment (_, token, name, DataExternal)) =
 | 
			
		||||
        if mightBeGuarded token
 | 
			
		||||
        then Map.insert name Nothing map
 | 
			
		||||
        else Map.insert name (Just "") map
 | 
			
		||||
    addNulls m (Assignment (_, token, name, DataFrom [word]))
 | 
			
		||||
        | mightBeGuarded token = Map.insert name Nothing m
 | 
			
		||||
        | couldFail word       = m
 | 
			
		||||
        | otherwise            = Map.insert name (combine m word) m
 | 
			
		||||
    addNulls m (Assignment (_, token, name, DataFrom _)) =
 | 
			
		||||
        Map.insert name Nothing m
 | 
			
		||||
    addNulls map _ = map
 | 
			
		||||
 | 
			
		||||
    getScopeId n (Reference (_, token, _)) = getId token
 | 
			
		||||
    getScopeId n (Assignment (_, token, _, _)) = getId token
 | 
			
		||||
    getScopeId n _ = n
 | 
			
		||||
 | 
			
		||||
    joinMaybes :: [Maybe String] -> Maybe String
 | 
			
		||||
    joinMaybes = foldl (liftM2 (++)) (Just "")
 | 
			
		||||
    combine m = c
 | 
			
		||||
      where
 | 
			
		||||
        c (T_DollarBraced _ t) | unnullable t =
 | 
			
		||||
            Map.findWithDefault (Just "") (concat $ deadSimple t) m
 | 
			
		||||
        c (T_DoubleQuoted _ tokens) = joinMaybes $ map (combine m) tokens
 | 
			
		||||
        c (T_NormalWord _ tokens) = joinMaybes $ map (combine m) tokens
 | 
			
		||||
        c (T_Glob _ "*") = Just "*"
 | 
			
		||||
        c t = getLiteralString t
 | 
			
		||||
 | 
			
		||||
    couldFail (T_Backticked _ _) = True
 | 
			
		||||
    couldFail (T_DollarExpansion _ _) = True
 | 
			
		||||
    couldFail (T_DoubleQuoted _ foo) = any couldFail foo
 | 
			
		||||
    couldFail (T_NormalWord _ foo) = any couldFail foo
 | 
			
		||||
    couldFail _ = False
 | 
			
		||||
 | 
			
		||||
    mightBeGuarded token = any t (getPath (parentMap params) token)
 | 
			
		||||
      where
 | 
			
		||||
        t (T_Condition {}) = True
 | 
			
		||||
        t (T_OrIf {}) = True
 | 
			
		||||
        t (T_AndIf {}) = True
 | 
			
		||||
        t _ = False
 | 
			
		||||
 | 
			
		||||
    paths = [
 | 
			
		||||
        "/", "/etc", "/home", "/mnt", "/usr", "/usr/share", "/usr/local",
 | 
			
		||||
        "/var"
 | 
			
		||||
        "", "/bin", "/etc", "/home", "/mnt", "/usr", "/usr/share", "/usr/local",
 | 
			
		||||
        "/var", "/lib"
 | 
			
		||||
        ]
 | 
			
		||||
    importantPaths = ["", "/*", "/*/*"] >>= (\x -> map (++x) paths)
 | 
			
		||||
    importantPaths = filter (not . null) $
 | 
			
		||||
        ["", "/", "/*", "/*/*"] >>= (\x -> map (++x) paths)
 | 
			
		||||
checkCatastrophicRm _ _ = return ()
 | 
			
		||||
 | 
			
		||||
 | 
			
		||||
 
 | 
			
		||||
		Reference in New Issue
	
	Block a user