Merge branch 'contivero-set-flags'

This commit is contained in:
Vidar Holen 2019-02-08 22:37:21 -08:00
commit abe6afc09f
1 changed files with 59 additions and 0 deletions

View File

@ -33,6 +33,7 @@ import Data.Char
import Data.List import Data.List
import Data.Maybe import Data.Maybe
import qualified Data.Map as Map import qualified Data.Map as Map
import qualified Data.Set as Set
import Test.QuickCheck.All (forAllProperties) import Test.QuickCheck.All (forAllProperties)
import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess) import Test.QuickCheck.Test (quickCheckWithResult, stdArgs, maxSuccess)
@ -161,6 +162,15 @@ prop_checkBashisms78 = verify checkBashisms "#!/bin/sh\necho -ne foo"
prop_checkBashisms79 = verify checkBashisms "#!/bin/sh\nhash -l" prop_checkBashisms79 = verify checkBashisms "#!/bin/sh\nhash -l"
prop_checkBashisms80 = verifyNot checkBashisms "#!/bin/sh\nhash -r" prop_checkBashisms80 = verifyNot checkBashisms "#!/bin/sh\nhash -r"
prop_checkBashisms81 = verifyNot checkBashisms "#!/bin/dash\nhash -v" prop_checkBashisms81 = verifyNot checkBashisms "#!/bin/dash\nhash -v"
prop_checkBashisms82 = verifyNot checkBashisms "#!/bin/sh\nset -v +o allexport -o errexit -C"
prop_checkBashisms83 = verifyNot checkBashisms "#!/bin/sh\nset --"
prop_checkBashisms84 = verify checkBashisms "#!/bin/sh\nset -o pipefail"
prop_checkBashisms85 = verify checkBashisms "#!/bin/sh\nset -B"
prop_checkBashisms86 = verifyNot checkBashisms "#!/bin/dash\nset -o emacs"
prop_checkBashisms87 = verify checkBashisms "#!/bin/sh\nset -o emacs"
prop_checkBashisms88 = verifyNot checkBashisms "#!/bin/sh\nset -- wget -o foo 'https://some.url'"
prop_checkBashisms89 = verifyNot checkBashisms "#!/bin/sh\nopts=$-\nset -\"$opts\""
prop_checkBashisms90 = verifyNot checkBashisms "#!/bin/sh\nset -o \"$opt\""
checkBashisms = ForShell [Sh, Dash] $ \t -> do checkBashisms = ForShell [Sh, Dash] $ \t -> do
params <- ask params <- ask
kludge params t kludge params t
@ -263,6 +273,55 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do
warnMsg (getId arg) "exec flags are" warnMsg (getId arg) "exec flags are"
bashism t@(T_SimpleCommand id _ _) bashism t@(T_SimpleCommand id _ _)
| t `isCommand` "let" = warnMsg id "'let' is" | t `isCommand` "let" = warnMsg id "'let' is"
bashism t@(T_SimpleCommand _ _ (cmd:args))
| t `isCommand` "set" = unless isDash $
checkOptions $ getLiteralArgs args
where
-- Get the literal options from a list of arguments,
-- up until the first non-literal one
getLiteralArgs :: [Token] -> [(Id, String)]
getLiteralArgs (first:rest) = fromMaybe [] $ do
str <- getLiteralString first
return $ (getId first, str) : getLiteralArgs rest
getLiteralArgs [] = []
-- Check a flag-option pair (such as -o errexit)
checkOptions (flag@(fid,flag') : opt@(oid,opt') : rest)
| flag' `matches` oFlagRegex = do
when (opt' `notElem` longOptions) $
warnMsg oid $ "set option " <> opt' <> " is"
checkFlags (flag:rest)
| otherwise = checkFlags (flag:opt:rest)
checkOptions (flag:rest) = checkFlags (flag:rest)
checkOptions _ = return ()
-- Check that each option in a sequence of flags
-- (such as -aveo) is valid
checkFlags (flag@(fid, flag'):rest)
| startsOption flag' = do
unless (flag' `matches` validFlagsRegex) $
forM_ (tail flag') $ \letter ->
when (letter `notElem` optionsSet) $
warnMsg fid $ "set flag " <> ('-':letter:" is")
checkOptions rest
| beginsWithDoubleDash flag' = do
warnMsg fid $ "set flag " <> flag' <> " is"
checkOptions rest
-- Either a word that doesn't start with a dash, or simply '--',
-- so stop checking.
| otherwise = return ()
checkFlags [] = return ()
options = "abCefhmnuvxo"
optionsSet = Set.fromList options
startsOption = (`matches` mkRegex "^(\\+|-[^-])")
oFlagRegex = mkRegex $ "^[-+][" <> options <> "]*o$"
validFlagsRegex = mkRegex $ "^[-+]([" <> options <> "]+o?|o)$"
beginsWithDoubleDash = (`matches` mkRegex "^--.+$")
longOptions = Set.fromList
[ "allexport", "errexit", "ignoreeof", "monitor", "noclobber"
, "noexec", "noglob", "nolog", "notify" , "nounset", "verbose"
, "vi", "xtrace" ]
bashism t@(T_SimpleCommand id _ (cmd:rest)) = bashism t@(T_SimpleCommand id _ (cmd:rest)) =
let name = fromMaybe "" $ getCommandName t let name = fromMaybe "" $ getCommandName t