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