commit
5eac721fcf
|
@ -317,13 +317,11 @@ getCommandNameAndToken :: Token -> (Maybe String, Token)
|
||||||
getCommandNameAndToken t = fromMaybe (Nothing, t) $ do
|
getCommandNameAndToken t = fromMaybe (Nothing, t) $ do
|
||||||
(T_SimpleCommand _ _ (w:rest)) <- getCommand t
|
(T_SimpleCommand _ _ (w:rest)) <- getCommand t
|
||||||
s <- getLiteralString w
|
s <- getLiteralString w
|
||||||
if "busybox" `isSuffixOf` s || "builtin" == s
|
return $ case rest of
|
||||||
then
|
(applet:_) | "busybox" `isSuffixOf` s || "builtin" == s ->
|
||||||
case rest of
|
(getLiteralString applet, applet)
|
||||||
(applet:_) -> return (getLiteralString applet, applet)
|
_ ->
|
||||||
_ -> return (Just s, w)
|
(Just s, w)
|
||||||
else
|
|
||||||
return (Just s, w)
|
|
||||||
|
|
||||||
|
|
||||||
-- If a command substitution is a single command, get its name.
|
-- If a command substitution is a single command, get its name.
|
||||||
|
@ -400,10 +398,10 @@ getAssociativeArrays t =
|
||||||
f t@T_SimpleCommand {} = sequence_ $ do
|
f t@T_SimpleCommand {} = sequence_ $ do
|
||||||
name <- getCommandName t
|
name <- getCommandName t
|
||||||
let assocNames = ["declare","local","typeset"]
|
let assocNames = ["declare","local","typeset"]
|
||||||
guard $ elem name assocNames
|
guard $ name `elem` assocNames
|
||||||
let flags = getAllFlags t
|
let flags = getAllFlags t
|
||||||
guard $ elem "A" $ map snd flags
|
guard $ "A" `elem` map snd flags
|
||||||
let args = map fst . filter ((==) "" . snd) $ flags
|
let args = [arg | (arg, "") <- flags]
|
||||||
let names = mapMaybe (getLiteralStringExt nameAssignments) args
|
let names = mapMaybe (getLiteralStringExt nameAssignments) args
|
||||||
return $ tell names
|
return $ tell names
|
||||||
f _ = return ()
|
f _ = return ()
|
||||||
|
@ -421,25 +419,18 @@ data PseudoGlob = PGAny | PGMany | PGChar Char
|
||||||
|
|
||||||
-- Turn a word into a PG pattern, replacing all unknown/runtime values with
|
-- Turn a word into a PG pattern, replacing all unknown/runtime values with
|
||||||
-- PGMany.
|
-- PGMany.
|
||||||
wordToPseudoGlob :: Token -> Maybe [PseudoGlob]
|
wordToPseudoGlob :: Token -> [PseudoGlob]
|
||||||
wordToPseudoGlob word =
|
wordToPseudoGlob word =
|
||||||
simplifyPseudoGlob . concat <$> mapM f (getWordParts word)
|
simplifyPseudoGlob . concatMap f $ getWordParts word
|
||||||
where
|
where
|
||||||
f x = case x of
|
f x = case x of
|
||||||
T_Literal _ s -> return $ map PGChar s
|
T_Literal _ s -> map PGChar s
|
||||||
T_SingleQuoted _ s -> return $ map PGChar s
|
T_SingleQuoted _ s -> map PGChar s
|
||||||
|
|
||||||
T_DollarBraced {} -> return [PGMany]
|
T_Glob _ "?" -> [PGAny]
|
||||||
T_DollarExpansion {} -> return [PGMany]
|
T_Glob _ ('[':_) -> [PGAny]
|
||||||
T_Backticked {} -> return [PGMany]
|
|
||||||
|
|
||||||
T_Glob _ "?" -> return [PGAny]
|
_ -> [PGMany]
|
||||||
T_Glob _ ('[':_) -> return [PGAny]
|
|
||||||
T_Glob {} -> return [PGMany]
|
|
||||||
|
|
||||||
T_Extglob {} -> return [PGMany]
|
|
||||||
|
|
||||||
_ -> return [PGMany]
|
|
||||||
|
|
||||||
-- Turn a word into a PG pattern, but only if we can preserve
|
-- Turn a word into a PG pattern, but only if we can preserve
|
||||||
-- exact semantics.
|
-- exact semantics.
|
||||||
|
@ -502,8 +493,7 @@ pseudoGlobIsSuperSetof = matchable
|
||||||
matchable (PGMany : rest) [] = matchable rest []
|
matchable (PGMany : rest) [] = matchable rest []
|
||||||
matchable _ _ = False
|
matchable _ _ = False
|
||||||
|
|
||||||
wordsCanBeEqual x y = fromMaybe True $
|
wordsCanBeEqual x y = pseudoGlobsCanOverlap (wordToPseudoGlob x) (wordToPseudoGlob y)
|
||||||
liftM2 pseudoGlobsCanOverlap (wordToPseudoGlob x) (wordToPseudoGlob y)
|
|
||||||
|
|
||||||
-- Is this an expansion that can be quoted,
|
-- Is this an expansion that can be quoted,
|
||||||
-- e.g. $(foo) `foo` $foo (but not {foo,})?
|
-- e.g. $(foo) `foo` $foo (but not {foo,})?
|
||||||
|
|
|
@ -3137,9 +3137,7 @@ checkUnmatchableCases params t =
|
||||||
if isConstant word
|
if isConstant word
|
||||||
then warn (getId word) 2194
|
then warn (getId word) 2194
|
||||||
"This word is constant. Did you forget the $ on a variable?"
|
"This word is constant. Did you forget the $ on a variable?"
|
||||||
else sequence_ $ do
|
else mapM_ (check $ wordToPseudoGlob word) allpatterns
|
||||||
pg <- wordToPseudoGlob word
|
|
||||||
return $ mapM_ (check pg) allpatterns
|
|
||||||
|
|
||||||
let exactGlobs = tupMap wordToExactPseudoGlob breakpatterns
|
let exactGlobs = tupMap wordToExactPseudoGlob breakpatterns
|
||||||
let fuzzyGlobs = tupMap wordToPseudoGlob breakpatterns
|
let fuzzyGlobs = tupMap wordToPseudoGlob breakpatterns
|
||||||
|
@ -3152,15 +3150,13 @@ checkUnmatchableCases params t =
|
||||||
fst3 (x,_,_) = x
|
fst3 (x,_,_) = x
|
||||||
snd3 (_,x,_) = x
|
snd3 (_,x,_) = x
|
||||||
tp = tokenPositions params
|
tp = tokenPositions params
|
||||||
check target candidate = sequence_ $ do
|
check target candidate = unless (pseudoGlobsCanOverlap target $ wordToPseudoGlob candidate) $
|
||||||
candidateGlob <- wordToPseudoGlob candidate
|
warn (getId candidate) 2195
|
||||||
guard . not $ pseudoGlobsCanOverlap target candidateGlob
|
"This pattern will never match the case statement's word. Double check them."
|
||||||
return $ warn (getId candidate) 2195
|
|
||||||
"This pattern will never match the case statement's word. Double check them."
|
|
||||||
|
|
||||||
tupMap f l = map (\x -> (x, f x)) l
|
tupMap f l = map (\x -> (x, f x)) l
|
||||||
checkDoms ((glob, Just x), rest) =
|
checkDoms ((glob, Just x), rest) =
|
||||||
forM_ (find (\(_, p) -> x `pseudoGlobIsSuperSetof` p) valids) $
|
forM_ (find (\(_, p) -> x `pseudoGlobIsSuperSetof` p) rest) $
|
||||||
\(first,_) -> do
|
\(first,_) -> do
|
||||||
warn (getId glob) 2221 $ "This pattern always overrides a later one" <> patternContext (getId first)
|
warn (getId glob) 2221 $ "This pattern always overrides a later one" <> patternContext (getId first)
|
||||||
warn (getId first) 2222 $ "This pattern never matches because of a previous pattern" <> patternContext (getId glob)
|
warn (getId first) 2222 $ "This pattern never matches because of a previous pattern" <> patternContext (getId glob)
|
||||||
|
@ -3170,8 +3166,6 @@ checkUnmatchableCases params t =
|
||||||
case posLine . fst <$> Map.lookup id tp of
|
case posLine . fst <$> Map.lookup id tp of
|
||||||
Just l -> " on line " <> show l <> "."
|
Just l -> " on line " <> show l <> "."
|
||||||
_ -> "."
|
_ -> "."
|
||||||
|
|
||||||
valids = [(x,y) | (x, Just y) <- rest]
|
|
||||||
checkDoms _ = return ()
|
checkDoms _ = return ()
|
||||||
|
|
||||||
|
|
||||||
|
|
Loading…
Reference in New Issue