diff --git a/src/ShellCheck/Analytics.hs b/src/ShellCheck/Analytics.hs index aabb22b..ffa04c8 100644 --- a/src/ShellCheck/Analytics.hs +++ b/src/ShellCheck/Analytics.hs @@ -2293,7 +2293,7 @@ checkWhileReadPitfalls _ (T_WhileExpression id [command] contents) isStdinReadCommand (T_Pipeline _ _ [T_Redirecting id redirs cmd]) = let plaintext = oversimplify cmd - in head (plaintext ++ [""]) == "read" + in headOrDefault "" plaintext == "read" && ("-u" `notElem` plaintext) && all (not . stdinRedirect) redirs isStdinReadCommand _ = False diff --git a/src/ShellCheck/AnalyzerLib.hs b/src/ShellCheck/AnalyzerLib.hs index 212e7bc..364722b 100644 --- a/src/ShellCheck/AnalyzerLib.hs +++ b/src/ShellCheck/AnalyzerLib.hs @@ -255,7 +255,7 @@ determineShell fallbackShell t = fromMaybe Bash $ executableFromShebang :: String -> String executableFromShebang = shellFor where - shellFor s | "/env " `isInfixOf` s = head (drop 1 (words s)++[""]) + shellFor s | "/env " `isInfixOf` s = headOrDefault "" (drop 1 $ words s) shellFor s | ' ' `elem` s = shellFor $ takeWhile (/= ' ') s shellFor s = reverse . takeWhile (/= '/') . reverse $ s @@ -295,7 +295,7 @@ isQuoteFree = isQuoteFreeNode False isQuoteFreeNode strict tree t = (isQuoteFreeElement t == Just True) || - head (mapMaybe isQuoteFreeContext (drop 1 $ getPath tree t) ++ [False]) + headOrDefault False (mapMaybe isQuoteFreeContext (drop 1 $ getPath tree t)) where -- Is this node self-quoting in itself? isQuoteFreeElement t = @@ -758,9 +758,8 @@ getReferencedVariables parents t = _ -> Nothing getIfReference context token = maybeToList $ do - str <- getLiteralStringExt literalizer token - guard . not $ null str - when (isDigit $ head str) $ fail "is a number" + str@(h:_) <- getLiteralStringExt literalizer token + when (isDigit h) $ fail "is a number" return (context, token, getBracedReference str) isDereferencing = (`elem` ["-eq", "-ne", "-lt", "-le", "-gt", "-ge"]) diff --git a/src/ShellCheck/Checks/Commands.hs b/src/ShellCheck/Checks/Commands.hs index 97de0f6..3407030 100644 --- a/src/ShellCheck/Checks/Commands.hs +++ b/src/ShellCheck/Checks/Commands.hs @@ -279,10 +279,10 @@ checkGrepRe = CommandCheck (Basename "grep") check where grepGlobFlags = ["fixed-strings", "F", "include", "exclude", "exclude-dir", "o", "only-matching"] wordStartingWith c = - head . filter ([c] `isPrefixOf`) $ candidates + headOrDefault (c:"test") . filter ([c] `isPrefixOf`) $ candidates where candidates = - sampleWords ++ map (\(x:r) -> toUpper x : r) sampleWords ++ [c:"test"] + sampleWords ++ map (\(x:r) -> toUpper x : r) sampleWords getSuspiciousRegexWildcard str = if not $ str `matches` contra diff --git a/src/ShellCheck/Checks/ShellSupport.hs b/src/ShellCheck/Checks/ShellSupport.hs index 4e0655d..924b002 100644 --- a/src/ShellCheck/Checks/ShellSupport.hs +++ b/src/ShellCheck/Checks/ShellSupport.hs @@ -457,8 +457,8 @@ checkEchoSed = ForShell [Bash, Ksh] f -- This should have used backreferences, but TDFA doesn't support them sedRe = mkRegex "^s(.)([^\n]*)g?$" isSimpleSed s = fromMaybe False $ do - [first,rest] <- matchRegex sedRe s - let delimiters = filter (== head first) rest + [h:_,rest] <- matchRegex sedRe s + let delimiters = filter (== h) rest guard $ length delimiters == 2 return True checkIn id s = diff --git a/src/ShellCheck/Parser.hs b/src/ShellCheck/Parser.hs index 30529e0..f37a56a 100644 --- a/src/ShellCheck/Parser.hs +++ b/src/ShellCheck/Parser.hs @@ -186,12 +186,12 @@ getNextIdSpanningTokens startTok endTok = do -- Get an ID starting from the first token of the list, and ending after the last getNextIdSpanningTokenList list = - if null list - then do + case list of + [] -> do pos <- getPosition getNextIdBetween pos pos - else - getNextIdSpanningTokens (head list) (last list) + (h:_) -> + getNextIdSpanningTokens h (last list) -- Get the span covered by an id getSpanForId :: Monad m => Id -> SCParser m (SourcePos, SourcePos) @@ -1826,7 +1826,7 @@ readPendingHereDocs = do let thereIsNoTrailer = null trailingSpace && null trailer let leaderIsOk = null leadingSpace || dashed == Dashed && leadingSpacesAreTabs - let trailerStart = if null trailer then '\0' else head trailer + let trailerStart = case trailer of [] -> '\0'; (h:_) -> h let hasTrailingSpace = not $ null trailingSpace let hasTrailer = not $ null trailer let ppt = parseProblemAt trailerPos ErrorC