From 74c199b51ac28a6019716c7f18bb3955507fef4e Mon Sep 17 00:00:00 2001
From: Vidar Holen <spam@vidarholen.net>
Date: Sat, 16 Sep 2017 15:23:51 -0700
Subject: [PATCH] Warn when one case pattern overrides another.

---
 ShellCheck/ASTLib.hs    | 30 ++++++++++++++++++++++++++++++
 ShellCheck/Analytics.hs | 40 ++++++++++++++++++++++++++++++++++------
 2 files changed, 64 insertions(+), 6 deletions(-)

diff --git a/ShellCheck/ASTLib.hs b/ShellCheck/ASTLib.hs
index 77839af..a23db4f 100644
--- a/ShellCheck/ASTLib.hs
+++ b/ShellCheck/ASTLib.hs
@@ -371,6 +371,19 @@ wordToPseudoGlob word =
 
         _ -> return [PGMany]
 
+-- Turn a word into a PG pattern, but only if we can preserve
+-- exact semantics.
+wordToExactPseudoGlob :: Token -> Maybe [PseudoGlob]
+wordToExactPseudoGlob word =
+    simplifyPseudoGlob . concat <$> mapM f (getWordParts word)
+  where
+    f x = case x of
+        T_Literal _ s -> return $ map PGChar s
+        T_SingleQuoted _ s -> return $ map PGChar s
+        T_Glob _ "?" -> return [PGAny]
+        T_Glob _ "*" -> return [PGMany]
+        _ -> fail "Unknown token type"
+
 -- Reorder a PseudoGlob for more efficient matching, e.g.
 -- f?*?**g -> f??*g
 simplifyPseudoGlob :: [PseudoGlob] -> [PseudoGlob]
@@ -402,5 +415,22 @@ pseudoGlobsCanOverlap = matchable
     matchable (_:_) [] = False
     matchable [] r = matchable r []
 
+-- Check whether the first pattern always overlaps the second.
+pseudoGlobIsSuperSetof :: [PseudoGlob] -> [PseudoGlob] -> Bool
+pseudoGlobIsSuperSetof = matchable
+  where
+    matchable x@(xf:xs) y@(yf:ys) =
+        case (xf, yf) of
+            (PGMany, PGMany) -> matchable x ys
+            (PGMany, _) -> matchable x ys || matchable xs y
+            (_, PGMany) -> False
+            (PGAny, _) -> matchable xs ys
+            (_, PGAny) -> False
+            (_, _) -> xf == yf && matchable xs ys
+
+    matchable [] [] = True
+    matchable (PGMany : rest) [] = matchable rest []
+    matchable _ _ = False
+
 wordsCanBeEqual x y = fromMaybe True $
     liftM2 pseudoGlobsCanOverlap (wordToPseudoGlob x) (wordToPseudoGlob y)
diff --git a/ShellCheck/Analytics.hs b/ShellCheck/Analytics.hs
index d153d2b..d6831c4 100644
--- a/ShellCheck/Analytics.hs
+++ b/ShellCheck/Analytics.hs
@@ -2665,23 +2665,51 @@ prop_checkUnmatchableCases1 = verify checkUnmatchableCases "case foo in bar) tru
 prop_checkUnmatchableCases2 = verify checkUnmatchableCases "case foo-$bar in ??|*) true; esac"
 prop_checkUnmatchableCases3 = verify checkUnmatchableCases "case foo in foo) true; esac"
 prop_checkUnmatchableCases4 = verifyNot checkUnmatchableCases "case foo-$bar in foo*|*bar|*baz*) true; esac"
+prop_checkUnmatchableCases5 = verify checkUnmatchableCases "case $f in *.txt) true;; f??.txt) false;; esac"
+prop_checkUnmatchableCases6 = verifyNot checkUnmatchableCases "case $f in ?*) true;; *) false;; esac"
+prop_checkUnmatchableCases7 = verifyNot checkUnmatchableCases "case $f in $(x)) true;; asdf) false;; esac"
+prop_checkUnmatchableCases8 = verify checkUnmatchableCases "case $f in cow) true;; bar|cow) false;; esac"
 checkUnmatchableCases _ t =
     case t of
-        T_CaseExpression _ word list ->
+        T_CaseExpression _ word list -> do
+            let patterns = concatMap snd3 list
+
             if isConstant word
-            then warn (getId word) 2194
-                    "This word is constant. Did you forget the $ on a variable?"
-            else  potentially $ do
-                pg <- wordToPseudoGlob word
-                return $ mapM_ (check pg) (concatMap (\(_,x,_) -> x) list)
+                then warn (getId word) 2194
+                        "This word is constant. Did you forget the $ on a variable?"
+                else  potentially $ do
+                    pg <- wordToPseudoGlob word
+                    return $ mapM_ (check pg) patterns
+
+            let exactGlobs = tupMap wordToExactPseudoGlob patterns
+            let fuzzyGlobs = tupMap wordToPseudoGlob patterns
+            let dominators = zip exactGlobs (tails $ drop 1 fuzzyGlobs)
+
+            mapM_ checkDoms dominators
+
         _ -> return ()
   where
+    snd3 (_,x,_) = x
     check target candidate = potentially $ 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."
 
+    tupMap f l = zip l (map f l)
+    checkDoms ((glob, Just x), rest) =
+        case filter (\(_, p) -> x `pseudoGlobIsSuperSetof` p) valids of
+            ((first,_):_) -> do
+                warn (getId glob) 2221 "This pattern always overrides a later one."
+                warn (getId first) 2222 "This pattern never matches because of a previous pattern."
+            _ -> return ()
+      where
+        valids = concatMap f rest
+        f (x, Just y) = [(x,y)]
+        f _ = []
+    checkDoms _ = return ()
+
+
 prop_checkSubshellAsTest1 = verify checkSubshellAsTest "( -e file )"
 prop_checkSubshellAsTest2 = verify checkSubshellAsTest "( 1 -gt 2 )"
 prop_checkSubshellAsTest3 = verifyNot checkSubshellAsTest "( grep -c foo bar )"