Merge pull request #1826 from josephcsible/nofromjust

Use the Identity monad to avoid unnecessary uses of fromJust
This commit is contained in:
Vidar Holen 2020-02-10 18:05:36 -08:00 committed by GitHub
commit d0beac6d0b
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
5 changed files with 20 additions and 16 deletions

View File

@ -25,6 +25,7 @@ import Control.Monad.Writer
import Control.Monad import Control.Monad
import Data.Char import Data.Char
import Data.Functor import Data.Functor
import Data.Functor.Identity
import Data.List import Data.List
import Data.Maybe import Data.Maybe
@ -175,9 +176,13 @@ willConcatInAssignment token =
getLiteralString :: Token -> Maybe String getLiteralString :: Token -> Maybe String
getLiteralString = getLiteralStringExt (const Nothing) getLiteralString = getLiteralStringExt (const Nothing)
-- Definitely get a literal string, with a given default for all non-literals
getLiteralStringDef :: String -> Token -> String
getLiteralStringDef x = runIdentity . getLiteralStringExt (const $ return x)
-- Definitely get a literal string, skipping over all non-literals -- Definitely get a literal string, skipping over all non-literals
onlyLiteralString :: Token -> String onlyLiteralString :: Token -> String
onlyLiteralString = fromJust . getLiteralStringExt (const $ return "") onlyLiteralString = getLiteralStringDef ""
-- Maybe get a literal string, but only if it's an unquoted argument. -- Maybe get a literal string, but only if it's an unquoted argument.
getUnquotedLiteral (T_NormalWord _ list) = getUnquotedLiteral (T_NormalWord _ list) =
@ -216,7 +221,7 @@ getGlobOrLiteralString = getLiteralStringExt f
-- Maybe get the literal value of a token, using a custom function -- Maybe get the literal value of a token, using a custom function
-- to map unrecognized Tokens into strings. -- to map unrecognized Tokens into strings.
getLiteralStringExt :: (Token -> Maybe String) -> Token -> Maybe String getLiteralStringExt :: Monad m => (Token -> m String) -> Token -> m String
getLiteralStringExt more = g getLiteralStringExt more = g
where where
allInList = fmap concat . mapM g allInList = fmap concat . mapM g

View File

@ -1057,9 +1057,7 @@ checkNumberComparisons params (TC_Binary id typ op lhs rhs) = do
checkStrings = checkStrings =
mapM_ stringError . find isNonNum mapM_ stringError . find isNonNum
isNonNum t = fromMaybe False $ do isNonNum t = not . all numChar $ onlyLiteralString t
s <- getLiteralStringExt (const $ return "") t
return . not . all numChar $ s
numChar x = isDigit x || x `elem` "+-. " numChar x = isDigit x || x `elem` "+-. "
stringError t = err (getId t) 2170 $ stringError t = err (getId t) 2170 $
@ -2578,7 +2576,7 @@ checkTildeInPath _ (T_SimpleCommand _ vars _) =
warn id 2147 "Literal tilde in PATH works poorly across programs." warn id 2147 "Literal tilde in PATH works poorly across programs."
checkVar _ = return () checkVar _ = return ()
hasTilde t = fromMaybe False (liftM2 elem (return '~') (getLiteralStringExt (const $ return "") t)) hasTilde t = '~' `elem` onlyLiteralString t
isQuoted T_DoubleQuoted {} = True isQuoted T_DoubleQuoted {} = True
isQuoted T_SingleQuoted {} = True isQuoted T_SingleQuoted {} = True
isQuoted _ = False isQuoted _ = False

View File

@ -801,7 +801,7 @@ isVariableName (x:r) = isVariableStartChar x && all isVariableChar r
isVariableName _ = False isVariableName _ = False
getVariablesFromLiteralToken token = getVariablesFromLiteralToken token =
getVariablesFromLiteral (fromJust $ getLiteralStringExt (const $ return " ") token) getVariablesFromLiteral (getLiteralStringDef " " token)
-- Try to get referenced variables from a literal string like "$foo" -- Try to get referenced variables from a literal string like "$foo"
-- Ignores tons of cases like arithmetic evaluation and array indices. -- Ignores tons of cases like arithmetic evaluation and array indices.

View File

@ -34,6 +34,7 @@ import ShellCheck.Regex
import Control.Monad import Control.Monad
import Control.Monad.RWS import Control.Monad.RWS
import Data.Char import Data.Char
import Data.Functor.Identity
import Data.List import Data.List
import Data.Maybe import Data.Maybe
import qualified Data.Map.Strict as Map import qualified Data.Map.Strict as Map
@ -248,13 +249,12 @@ prop_checkGrepRe23= verifyNot checkGrepRe "grep '.*' file"
checkGrepRe = CommandCheck (Basename "grep") check where checkGrepRe = CommandCheck (Basename "grep") check where
check cmd = f cmd (arguments cmd) check cmd = f cmd (arguments cmd)
-- --regex=*(extglob) doesn't work. Fixme? -- --regex=*(extglob) doesn't work. Fixme?
skippable (Just s) = not ("--regex=" `isPrefixOf` s) && "-" `isPrefixOf` s skippable s = not ("--regex=" `isPrefixOf` s) && "-" `isPrefixOf` s
skippable _ = False
f _ [] = return () f _ [] = return ()
f cmd (x:r) = f cmd (x:r) =
let str = getLiteralStringExt (const $ return "_") x let str = getLiteralStringDef "_" x
in in
if str `elem` [Just "--", Just "-e", Just "--regex"] if str `elem` ["--", "-e", "--regex"]
then checkRE cmd r -- Regex is *after* this then checkRE cmd r -- Regex is *after* this
else else
if skippable str if skippable str
@ -348,7 +348,7 @@ returnOrExit multi invalid = (f . arguments)
isInvalid s = null s || any (not . isDigit) s || length s > 5 isInvalid s = null s || any (not . isDigit) s || length s > 5
|| let value = (read s :: Integer) in value > 255 || let value = (read s :: Integer) in value > 255
literal token = fromJust $ getLiteralStringExt lit token literal token = runIdentity $ getLiteralStringExt lit token
lit (T_DollarBraced {}) = return "0" lit (T_DollarBraced {}) = return "0"
lit (T_DollarArithmetic {}) = return "0" lit (T_DollarArithmetic {}) = return "0"
lit (T_DollarExpansion {}) = return "0" lit (T_DollarExpansion {}) = return "0"
@ -365,7 +365,7 @@ checkFindExecWithSingleArgument = CommandCheck (Basename "find") (f . arguments)
check (exec:arg:term:_) = do check (exec:arg:term:_) = do
execS <- getLiteralString exec execS <- getLiteralString exec
termS <- getLiteralString term termS <- getLiteralString term
cmdS <- getLiteralStringExt (const $ return " ") arg let cmdS = getLiteralStringDef " " arg
guard $ execS `elem` ["-exec", "-execdir"] && termS `elem` [";", "+"] guard $ execS `elem` ["-exec", "-execdir"] && termS `elem` [";", "+"]
guard $ cmdS `matches` commandRegex guard $ cmdS `matches` commandRegex
@ -735,7 +735,7 @@ checkAliasesUsesArgs = CommandCheck (Exactly "alias") (f . arguments)
re = mkRegex "\\$\\{?[0-9*@]" re = mkRegex "\\$\\{?[0-9*@]"
f = mapM_ checkArg f = mapM_ checkArg
checkArg arg = checkArg arg =
let string = fromJust $ getLiteralStringExt (const $ return "_") arg in let string = getLiteralStringDef "_" arg in
when ('=' `elem` string && string `matches` re) $ when ('=' `elem` string && string `matches` re) $
err (getId arg) 2142 err (getId arg) 2142
"Aliases can't use positional parameters. Use a function." "Aliases can't use positional parameters. Use a function."
@ -781,7 +781,7 @@ checkFindWithoutPath = CommandCheck (Basename "find") f
-- path. We assume that all the pre-path flags are single characters from a -- path. We assume that all the pre-path flags are single characters from a
-- list of GNU and macOS flags. -- list of GNU and macOS flags.
hasPath (first:rest) = hasPath (first:rest) =
let flag = fromJust $ getLiteralStringExt (const $ return "___") first in let flag = getLiteralStringDef "___" first in
not ("-" `isPrefixOf` flag) || isLeadingFlag flag && hasPath rest not ("-" `isPrefixOf` flag) || isLeadingFlag flag && hasPath rest
hasPath [] = False hasPath [] = False
isLeadingFlag flag = length flag <= 2 || all (`elem` leadingFlagChars) flag isLeadingFlag flag = length flag <= 2 || all (`elem` leadingFlagChars) flag

View File

@ -30,6 +30,7 @@ import ShellCheck.Regex
import Control.Monad import Control.Monad
import Control.Monad.RWS import Control.Monad.RWS
import Data.Char import Data.Char
import Data.Functor.Identity
import Data.List import Data.List
import Data.Maybe import Data.Maybe
import qualified Data.Map as Map import qualified Data.Map as Map
@ -487,7 +488,7 @@ checkBraceExpansionVars = ForShell [Bash] f
T_DollarExpansion {} -> return "$" T_DollarExpansion {} -> return "$"
T_DollarArithmetic {} -> return "$" T_DollarArithmetic {} -> return "$"
_ -> return "-" _ -> return "-"
toString t = fromJust $ getLiteralStringExt literalExt t toString t = runIdentity $ getLiteralStringExt literalExt t
isEvaled t = do isEvaled t = do
cmd <- getClosestCommandM t cmd <- getClosestCommandM t
return $ maybe False (`isUnqualifiedCommand` "eval") cmd return $ maybe False (`isUnqualifiedCommand` "eval") cmd