Use the Identity monad to avoid unnecessary uses of fromJust

This commit is contained in:
Joseph C. Sible 2020-02-08 23:06:57 -05:00
parent 61b073d507
commit aaffe38198
4 changed files with 10 additions and 7 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
@ -177,7 +178,7 @@ getLiteralString = getLiteralStringExt (const Nothing)
-- 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 = runIdentity . getLiteralStringExt (const $ return "")
-- 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 +217,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

@ -806,7 +806,7 @@ isVariableName (x:r) = isVariableStartChar x && all isVariableChar r
isVariableName _ = False isVariableName _ = False
getVariablesFromLiteralToken token = getVariablesFromLiteralToken token =
getVariablesFromLiteral (fromJust $ getLiteralStringExt (const $ return " ") token) getVariablesFromLiteral (runIdentity $ getLiteralStringExt (const $ return " ") 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
@ -348,7 +349,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"
@ -735,7 +736,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 = runIdentity $ getLiteralStringExt (const $ return "_") 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 +782,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 = runIdentity $ getLiteralStringExt (const $ return "___") 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
@ -488,7 +489,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