Change prop> to >>> prop $

As doctest doesn't make QuickCheck related magic, but only
evaluates expressions: We are fast.
This commit is contained in:
Oleg Grenrus 2018-10-17 19:29:04 +03:00
parent d510a3ef6c
commit 75949fe51e
5 changed files with 1303 additions and 1296 deletions

File diff suppressed because it is too large Load diff

View file

@ -37,6 +37,10 @@ import qualified Data.Map as Map
import Data.Maybe
import Data.Semigroup
prop :: Bool -> IO ()
prop False = putStrLn "FAIL"
prop True = return ()
type Analysis = AnalyzerM ()
type AnalyzerM a = RWS Parameters [TokenComment] Cache a
nullCheck = const $ return ()
@ -193,14 +197,14 @@ containsLastpipe root =
-- |
-- prop> determineShell (fromJust $ pScript "#!/bin/sh") == Sh
-- prop> determineShell (fromJust $ pScript "#!/usr/bin/env ksh") == Ksh
-- prop> determineShell (fromJust $ pScript "") == Bash
-- prop> determineShell (fromJust $ pScript "#!/bin/sh -e") == Sh
-- prop> determineShell (fromJust $ pScript "#!/bin/ksh\n#shellcheck shell=sh\nfoo") == Sh
-- prop> determineShell (fromJust $ pScript "#shellcheck shell=sh\nfoo") == Sh
-- prop> determineShell (fromJust $ pScript "#! /bin/sh") == Sh
-- prop> determineShell (fromJust $ pScript "#! /bin/ash") == Dash
-- >>> prop $ determineShell (fromJust $ pScript "#!/bin/sh") == Sh
-- >>> prop $ determineShell (fromJust $ pScript "#!/usr/bin/env ksh") == Ksh
-- >>> prop $ determineShell (fromJust $ pScript "") == Bash
-- >>> prop $ determineShell (fromJust $ pScript "#!/bin/sh -e") == Sh
-- >>> prop $ determineShell (fromJust $ pScript "#!/bin/ksh\n#shellcheck shell=sh\nfoo") == Sh
-- >>> prop $ determineShell (fromJust $ pScript "#shellcheck shell=sh\nfoo") == Sh
-- >>> prop $ determineShell (fromJust $ pScript "#! /bin/sh") == Sh
-- >>> prop $ determineShell (fromJust $ pScript "#! /bin/ash") == Dash
determineShell t = fromMaybe Bash $ do
shellString <- foldl mplus Nothing $ getCandidates t
shellForExecutable shellString
@ -623,10 +627,10 @@ getIndexReferences s = fromMaybe [] $ do
re = mkRegex "(\\[.*\\])"
-- |
-- prop> getOffsetReferences ":bar" == ["bar"]
-- prop> getOffsetReferences ":bar:baz" == ["bar", "baz"]
-- prop> getOffsetReferences "[foo]:bar" == ["bar"]
-- prop> getOffsetReferences "[foo]:bar:baz" == ["bar", "baz"]
-- >>> prop $ getOffsetReferences ":bar" == ["bar"]
-- >>> prop $ getOffsetReferences ":bar:baz" == ["bar", "baz"]
-- >>> prop $ getOffsetReferences "[foo]:bar" == ["bar"]
-- >>> prop $ getOffsetReferences "[foo]:bar:baz" == ["bar", "baz"]
getOffsetReferences mods = fromMaybe [] $ do
-- if mods start with [, then drop until ]
match <- matchRegex re mods
@ -720,9 +724,9 @@ isVariableChar x = isVariableStartChar x || isDigit x
variableNameRegex = mkRegex "[_a-zA-Z][_a-zA-Z0-9]*"
-- |
-- prop> isVariableName "_fo123"
-- prop> not $ isVariableName "4"
-- prop> not $ isVariableName "test: "
-- >>> prop $ isVariableName "_fo123"
-- >>> prop $ not $ isVariableName "4"
-- >>> prop $ not $ isVariableName "test: "
isVariableName (x:r) = isVariableStartChar x && all isVariableChar r
isVariableName _ = False
@ -731,7 +735,7 @@ getVariablesFromLiteralToken token =
-- Try to get referenced variables from a literal string like "$foo"
-- Ignores tons of cases like arithmetic evaluation and array indices.
-- prop> getVariablesFromLiteral "$foo${bar//a/b}$BAZ" == ["foo", "bar", "BAZ"]
-- >>> prop $ getVariablesFromLiteral "$foo${bar//a/b}$BAZ" == ["foo", "bar", "BAZ"]
getVariablesFromLiteral string =
map (!! 0) $ matchAllSubgroups variableRegex string
where
@ -740,19 +744,19 @@ getVariablesFromLiteral string =
-- |
-- Get the variable name from an expansion like ${var:-foo}
--
-- prop> getBracedReference "foo" == "foo"
-- prop> getBracedReference "#foo" == "foo"
-- prop> getBracedReference "#" == "#"
-- prop> getBracedReference "##" == "#"
-- prop> getBracedReference "#!" == "!"
-- prop> getBracedReference "!#" == "#"
-- prop> getBracedReference "!foo#?" == "foo"
-- prop> getBracedReference "foo-bar" == "foo"
-- prop> getBracedReference "foo:-bar" == "foo"
-- prop> getBracedReference "foo: -1" == "foo"
-- prop> getBracedReference "!os*" == ""
-- prop> getBracedReference "!os?bar**" == ""
-- prop> getBracedReference "foo[bar]" == "foo"
-- >>> prop $ getBracedReference "foo" == "foo"
-- >>> prop $ getBracedReference "#foo" == "foo"
-- >>> prop $ getBracedReference "#" == "#"
-- >>> prop $ getBracedReference "##" == "#"
-- >>> prop $ getBracedReference "#!" == "!"
-- >>> prop $ getBracedReference "!#" == "#"
-- >>> prop $ getBracedReference "!foo#?" == "foo"
-- >>> prop $ getBracedReference "foo-bar" == "foo"
-- >>> prop $ getBracedReference "foo:-bar" == "foo"
-- >>> prop $ getBracedReference "foo: -1" == "foo"
-- >>> prop $ getBracedReference "!os*" == ""
-- >>> prop $ getBracedReference "!os?bar**" == ""
-- >>> prop $ getBracedReference "foo[bar]" == "foo"
getBracedReference s = fromMaybe s $
nameExpansion s `mplus` takeName noPrefix `mplus` getSpecial noPrefix `mplus` getSpecial s
where
@ -776,9 +780,9 @@ getBracedReference s = fromMaybe s $
nameExpansion _ = Nothing
-- |
-- prop> getBracedModifier "foo:bar:baz" == ":bar:baz"
-- prop> getBracedModifier "!var:-foo" == ":-foo"
-- prop> getBracedModifier "foo[bar]" == "[bar]"
-- >>> prop $ getBracedModifier "foo:bar:baz" == ":bar:baz"
-- >>> prop $ getBracedModifier "!var:-foo" == ":-foo"
-- >>> prop $ getBracedModifier "foo[bar]" == "[bar]"
getBracedModifier s = fromMaybe "" . listToMaybe $ do
let var = getBracedReference s
a <- dropModifier s

View file

@ -42,7 +42,6 @@ data CommandName = Exactly String | Basename String
data CommandCheck =
CommandCheck CommandName (Token -> Analysis)
verify :: CommandCheck -> String -> Bool
verify f s = producesComments (getChecker [f]) s == Just True
verifyNot f s = producesComments (getChecker [f]) s == Just False
@ -125,20 +124,20 @@ checker :: Parameters -> Checker
checker params = getChecker commandChecks
-- |
-- prop> verify checkTr "tr [a-f] [A-F]"
-- prop> verify checkTr "tr 'a-z' 'A-Z'"
-- prop> verify checkTr "tr '[a-z]' '[A-Z]'"
-- prop> verifyNot checkTr "tr -d '[:lower:]'"
-- prop> verifyNot checkTr "tr -d '[:upper:]'"
-- prop> verifyNot checkTr "tr -d '|/_[:upper:]'"
-- prop> verifyNot checkTr "ls [a-z]"
-- prop> verify checkTr "tr foo bar"
-- prop> verify checkTr "tr 'hello' 'world'"
-- prop> verifyNot checkTr "tr aeiou _____"
-- prop> verifyNot checkTr "a-z n-za-m"
-- prop> verifyNot checkTr "tr --squeeze-repeats rl lr"
-- prop> verifyNot checkTr "tr abc '[d*]'"
-- prop> verifyNot checkTr "tr '[=e=]' 'e'"
-- >>> prop $ verify checkTr "tr [a-f] [A-F]"
-- >>> prop $ verify checkTr "tr 'a-z' 'A-Z'"
-- >>> prop $ verify checkTr "tr '[a-z]' '[A-Z]'"
-- >>> prop $ verifyNot checkTr "tr -d '[:lower:]'"
-- >>> prop $ verifyNot checkTr "tr -d '[:upper:]'"
-- >>> prop $ verifyNot checkTr "tr -d '|/_[:upper:]'"
-- >>> prop $ verifyNot checkTr "ls [a-z]"
-- >>> prop $ verify checkTr "tr foo bar"
-- >>> prop $ verify checkTr "tr 'hello' 'world'"
-- >>> prop $ verifyNot checkTr "tr aeiou _____"
-- >>> prop $ verifyNot checkTr "a-z n-za-m"
-- >>> prop $ verifyNot checkTr "tr --squeeze-repeats rl lr"
-- >>> prop $ verifyNot checkTr "tr abc '[d*]'"
-- >>> prop $ verifyNot checkTr "tr '[=e=]' 'e'"
checkTr = CommandCheck (Basename "tr") (mapM_ f . arguments)
where
f w | isGlob w = -- The user will go [ab] -> '[ab]' -> 'ab'. Fixme?
@ -160,9 +159,9 @@ checkTr = CommandCheck (Basename "tr") (mapM_ f . arguments)
in relevant /= nub relevant
-- |
-- prop> verify checkFindNameGlob "find / -name *.php"
-- prop> verify checkFindNameGlob "find / -type f -ipath *(foo)"
-- prop> verifyNot checkFindNameGlob "find * -name '*.php'"
-- >>> prop $ verify checkFindNameGlob "find / -name *.php"
-- >>> prop $ verify checkFindNameGlob "find / -type f -ipath *(foo)"
-- >>> prop $ verifyNot checkFindNameGlob "find * -name '*.php'"
checkFindNameGlob = CommandCheck (Basename "find") (f . arguments) where
acceptsGlob (Just s) = s `elem` [ "-ilname", "-iname", "-ipath", "-iregex", "-iwholename", "-lname", "-name", "-path", "-regex", "-wholename" ]
acceptsGlob _ = False
@ -176,10 +175,10 @@ checkFindNameGlob = CommandCheck (Basename "find") (f . arguments) where
-- |
-- prop> verify checkNeedlessExpr "foo=$(expr 3 + 2)"
-- prop> verify checkNeedlessExpr "foo=`echo \\`expr 3 + 2\\``"
-- prop> verifyNot checkNeedlessExpr "foo=$(expr foo : regex)"
-- prop> verifyNot checkNeedlessExpr "foo=$(expr foo \\< regex)"
-- >>> prop $ verify checkNeedlessExpr "foo=$(expr 3 + 2)"
-- >>> prop $ verify checkNeedlessExpr "foo=`echo \\`expr 3 + 2\\``"
-- >>> prop $ verifyNot checkNeedlessExpr "foo=$(expr foo : regex)"
-- >>> prop $ verifyNot checkNeedlessExpr "foo=$(expr foo \\< regex)"
checkNeedlessExpr = CommandCheck (Basename "expr") f where
f t =
when (all (`notElem` exceptions) (words $ arguments t)) $
@ -191,21 +190,21 @@ checkNeedlessExpr = CommandCheck (Basename "expr") f where
-- |
-- prop> verify checkGrepRe "cat foo | grep *.mp3"
-- prop> verify checkGrepRe "grep -Ev cow*test *.mp3"
-- prop> verify checkGrepRe "grep --regex=*.mp3 file"
-- prop> verifyNot checkGrepRe "grep foo *.mp3"
-- prop> verifyNot checkGrepRe "grep-v --regex=moo *"
-- prop> verifyNot checkGrepRe "grep foo \\*.mp3"
-- prop> verify checkGrepRe "grep *foo* file"
-- prop> verify checkGrepRe "ls | grep foo*.jpg"
-- prop> verifyNot checkGrepRe "grep '[0-9]*' file"
-- prop> verifyNot checkGrepRe "grep '^aa*' file"
-- prop> verifyNot checkGrepRe "grep --include=*.png foo"
-- prop> verifyNot checkGrepRe "grep -F 'Foo*' file"
-- prop> verifyNot checkGrepRe "grep -- -foo bar*"
-- prop> verifyNot checkGrepRe "grep -e -foo bar*"
-- prop> verifyNot checkGrepRe "grep --regex -foo bar*"
-- >>> prop $ verify checkGrepRe "cat foo | grep *.mp3"
-- >>> prop $ verify checkGrepRe "grep -Ev cow*test *.mp3"
-- >>> prop $ verify checkGrepRe "grep --regex=*.mp3 file"
-- >>> prop $ verifyNot checkGrepRe "grep foo *.mp3"
-- >>> prop $ verifyNot checkGrepRe "grep-v --regex=moo *"
-- >>> prop $ verifyNot checkGrepRe "grep foo \\*.mp3"
-- >>> prop $ verify checkGrepRe "grep *foo* file"
-- >>> prop $ verify checkGrepRe "ls | grep foo*.jpg"
-- >>> prop $ verifyNot checkGrepRe "grep '[0-9]*' file"
-- >>> prop $ verifyNot checkGrepRe "grep '^aa*' file"
-- >>> prop $ verifyNot checkGrepRe "grep --include=*.png foo"
-- >>> prop $ verifyNot checkGrepRe "grep -F 'Foo*' file"
-- >>> prop $ verifyNot checkGrepRe "grep -- -foo bar*"
-- >>> prop $ verifyNot checkGrepRe "grep -e -foo bar*"
-- >>> prop $ verifyNot checkGrepRe "grep --regex -foo bar*"
checkGrepRe = CommandCheck (Basename "grep") check where
check cmd = f cmd (arguments cmd)
@ -257,10 +256,10 @@ checkGrepRe = CommandCheck (Basename "grep") check where
-- |
-- prop> verify checkTrapQuotes "trap \"echo $num\" INT"
-- prop> verify checkTrapQuotes "trap \"echo `ls`\" INT"
-- prop> verifyNot checkTrapQuotes "trap 'echo $num' INT"
-- prop> verify checkTrapQuotes "trap \"echo $((1+num))\" EXIT DEBUG"
-- >>> prop $ verify checkTrapQuotes "trap \"echo $num\" INT"
-- >>> prop $ verify checkTrapQuotes "trap \"echo `ls`\" INT"
-- >>> prop $ verifyNot checkTrapQuotes "trap 'echo $num' INT"
-- >>> prop $ verify checkTrapQuotes "trap \"echo $((1+num))\" EXIT DEBUG"
checkTrapQuotes = CommandCheck (Exactly "trap") (f . arguments) where
f (x:_) = checkTrap x
f _ = return ()
@ -275,13 +274,13 @@ checkTrapQuotes = CommandCheck (Exactly "trap") (f . arguments) where
-- |
-- prop> verifyNot checkReturn "return"
-- prop> verifyNot checkReturn "return 1"
-- prop> verifyNot checkReturn "return $var"
-- prop> verifyNot checkReturn "return $((a|b))"
-- prop> verify checkReturn "return -1"
-- prop> verify checkReturn "return 1000"
-- prop> verify checkReturn "return 'hello world'"
-- >>> prop $ verifyNot checkReturn "return"
-- >>> prop $ verifyNot checkReturn "return 1"
-- >>> prop $ verifyNot checkReturn "return $var"
-- >>> prop $ verifyNot checkReturn "return $((a|b))"
-- >>> prop $ verify checkReturn "return -1"
-- >>> prop $ verify checkReturn "return 1000"
-- >>> prop $ verify checkReturn "return 'hello world'"
checkReturn = CommandCheck (Exactly "return") (f . arguments)
where
f (first:second:_) =
@ -305,9 +304,9 @@ checkReturn = CommandCheck (Exactly "return") (f . arguments)
-- |
-- prop> verify checkFindExecWithSingleArgument "find . -exec 'cat {} | wc -l' \\;"
-- prop> verify checkFindExecWithSingleArgument "find . -execdir 'cat {} | wc -l' +"
-- prop> verifyNot checkFindExecWithSingleArgument "find . -exec wc -l {} \\;"
-- >>> prop $ verify checkFindExecWithSingleArgument "find . -exec 'cat {} | wc -l' \\;"
-- >>> prop $ verify checkFindExecWithSingleArgument "find . -execdir 'cat {} | wc -l' +"
-- >>> prop $ verifyNot checkFindExecWithSingleArgument "find . -exec wc -l {} \\;"
checkFindExecWithSingleArgument = CommandCheck (Basename "find") (f . arguments)
where
f = void . sequence . mapMaybe check . tails
@ -324,11 +323,11 @@ checkFindExecWithSingleArgument = CommandCheck (Basename "find") (f . arguments)
-- |
-- prop> verify checkUnusedEchoEscapes "echo 'foo\\nbar\\n'"
-- prop> verifyNot checkUnusedEchoEscapes "echo -e 'foi\\nbar'"
-- prop> verify checkUnusedEchoEscapes "echo \"n:\\t42\""
-- prop> verifyNot checkUnusedEchoEscapes "echo lol"
-- prop> verifyNot checkUnusedEchoEscapes "echo -n -e '\n'"
-- >>> prop $ verify checkUnusedEchoEscapes "echo 'foo\\nbar\\n'"
-- >>> prop $ verifyNot checkUnusedEchoEscapes "echo -e 'foi\\nbar'"
-- >>> prop $ verify checkUnusedEchoEscapes "echo \"n:\\t42\""
-- >>> prop $ verifyNot checkUnusedEchoEscapes "echo lol"
-- >>> prop $ verifyNot checkUnusedEchoEscapes "echo -n -e '\n'"
checkUnusedEchoEscapes = CommandCheck (Basename "echo") f
where
hasEscapes = mkRegex "\\\\[rnt]"
@ -344,9 +343,9 @@ checkUnusedEchoEscapes = CommandCheck (Basename "echo") f
-- |
-- prop> verify checkInjectableFindSh "find . -exec sh -c 'echo {}' \\;"
-- prop> verify checkInjectableFindSh "find . -execdir bash -c 'rm \"{}\"' ';'"
-- prop> verifyNot checkInjectableFindSh "find . -exec sh -c 'rm \"$@\"' _ {} \\;"
-- >>> prop $ verify checkInjectableFindSh "find . -exec sh -c 'echo {}' \\;"
-- >>> prop $ verify checkInjectableFindSh "find . -execdir bash -c 'rm \"{}\"' ';'"
-- >>> prop $ verifyNot checkInjectableFindSh "find . -exec sh -c 'rm \"$@\"' _ {} \\;"
checkInjectableFindSh = CommandCheck (Basename "find") (check . arguments)
where
check args = do
@ -370,9 +369,9 @@ checkInjectableFindSh = CommandCheck (Basename "find") (check . arguments)
-- |
-- prop> verify checkFindActionPrecedence "find . -name '*.wav' -o -name '*.au' -exec rm {} +"
-- prop> verifyNot checkFindActionPrecedence "find . -name '*.wav' -o \\( -name '*.au' -exec rm {} + \\)"
-- prop> verifyNot checkFindActionPrecedence "find . -name '*.wav' -o -name '*.au'"
-- >>> prop $ verify checkFindActionPrecedence "find . -name '*.wav' -o -name '*.au' -exec rm {} +"
-- >>> prop $ verifyNot checkFindActionPrecedence "find . -name '*.wav' -o \\( -name '*.au' -exec rm {} + \\)"
-- >>> prop $ verifyNot checkFindActionPrecedence "find . -name '*.wav' -o -name '*.au'"
checkFindActionPrecedence = CommandCheck (Basename "find") (f . arguments)
where
pattern = [isMatch, const True, isParam ["-o", "-or"], isMatch, const True, isAction]
@ -390,28 +389,28 @@ checkFindActionPrecedence = CommandCheck (Basename "find") (f . arguments)
-- |
-- prop> verify checkMkdirDashPM "mkdir -p -m 0755 a/b"
-- prop> verify checkMkdirDashPM "mkdir -pm 0755 $dir"
-- prop> verify checkMkdirDashPM "mkdir -vpm 0755 a/b"
-- prop> verify checkMkdirDashPM "mkdir -pm 0755 -v a/b"
-- prop> verify checkMkdirDashPM "mkdir --parents --mode=0755 a/b"
-- prop> verify checkMkdirDashPM "mkdir --parents --mode 0755 a/b"
-- prop> verify checkMkdirDashPM "mkdir -p --mode=0755 a/b"
-- prop> verify checkMkdirDashPM "mkdir --parents -m 0755 a/b"
-- prop> verifyNot checkMkdirDashPM "mkdir -p a/b"
-- prop> verifyNot checkMkdirDashPM "mkdir -m 0755 a/b"
-- prop> verifyNot checkMkdirDashPM "mkdir a/b"
-- prop> verifyNot checkMkdirDashPM "mkdir --parents a/b"
-- prop> verifyNot checkMkdirDashPM "mkdir --mode=0755 a/b"
-- prop> verifyNot checkMkdirDashPM "mkdir_func -pm 0755 a/b"
-- prop> verifyNot checkMkdirDashPM "mkdir -p -m 0755 singlelevel"
-- prop> verifyNot checkMkdirDashPM "mkdir -p -m 0755 ../bin"
-- prop> verify checkMkdirDashPM "mkdir -p -m 0755 ../bin/laden"
-- prop> verifyNot checkMkdirDashPM "mkdir -p -m 0755 ./bin"
-- prop> verify checkMkdirDashPM "mkdir -p -m 0755 ./bin/laden"
-- prop> verifyNot checkMkdirDashPM "mkdir -p -m 0755 ./../bin"
-- prop> verifyNot checkMkdirDashPM "mkdir -p -m 0755 .././bin"
-- prop> verifyNot checkMkdirDashPM "mkdir -p -m 0755 ../../bin"
-- >>> prop $ verify checkMkdirDashPM "mkdir -p -m 0755 a/b"
-- >>> prop $ verify checkMkdirDashPM "mkdir -pm 0755 $dir"
-- >>> prop $ verify checkMkdirDashPM "mkdir -vpm 0755 a/b"
-- >>> prop $ verify checkMkdirDashPM "mkdir -pm 0755 -v a/b"
-- >>> prop $ verify checkMkdirDashPM "mkdir --parents --mode=0755 a/b"
-- >>> prop $ verify checkMkdirDashPM "mkdir --parents --mode 0755 a/b"
-- >>> prop $ verify checkMkdirDashPM "mkdir -p --mode=0755 a/b"
-- >>> prop $ verify checkMkdirDashPM "mkdir --parents -m 0755 a/b"
-- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p a/b"
-- >>> prop $ verifyNot checkMkdirDashPM "mkdir -m 0755 a/b"
-- >>> prop $ verifyNot checkMkdirDashPM "mkdir a/b"
-- >>> prop $ verifyNot checkMkdirDashPM "mkdir --parents a/b"
-- >>> prop $ verifyNot checkMkdirDashPM "mkdir --mode=0755 a/b"
-- >>> prop $ verifyNot checkMkdirDashPM "mkdir_func -pm 0755 a/b"
-- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p -m 0755 singlelevel"
-- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p -m 0755 ../bin"
-- >>> prop $ verify checkMkdirDashPM "mkdir -p -m 0755 ../bin/laden"
-- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p -m 0755 ./bin"
-- >>> prop $ verify checkMkdirDashPM "mkdir -p -m 0755 ./bin/laden"
-- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p -m 0755 ./../bin"
-- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p -m 0755 .././bin"
-- >>> prop $ verifyNot checkMkdirDashPM "mkdir -p -m 0755 ../../bin"
checkMkdirDashPM = CommandCheck (Basename "mkdir") check
where
check t = potentially $ do
@ -428,13 +427,13 @@ checkMkdirDashPM = CommandCheck (Basename "mkdir") check
-- |
-- prop> verify checkNonportableSignals "trap f 8"
-- prop> verifyNot checkNonportableSignals "trap f 0"
-- prop> verifyNot checkNonportableSignals "trap f 14"
-- prop> verify checkNonportableSignals "trap f SIGKILL"
-- prop> verify checkNonportableSignals "trap f 9"
-- prop> verify checkNonportableSignals "trap f stop"
-- prop> verifyNot checkNonportableSignals "trap 'stop' int"
-- >>> prop $ verify checkNonportableSignals "trap f 8"
-- >>> prop $ verifyNot checkNonportableSignals "trap f 0"
-- >>> prop $ verifyNot checkNonportableSignals "trap f 14"
-- >>> prop $ verify checkNonportableSignals "trap f SIGKILL"
-- >>> prop $ verify checkNonportableSignals "trap f 9"
-- >>> prop $ verify checkNonportableSignals "trap f stop"
-- >>> prop $ verifyNot checkNonportableSignals "trap 'stop' int"
checkNonportableSignals = CommandCheck (Exactly "trap") (f . arguments)
where
f args = case args of
@ -464,10 +463,10 @@ checkNonportableSignals = CommandCheck (Exactly "trap") (f . arguments)
-- |
-- prop> verify checkInteractiveSu "su; rm file; su $USER"
-- prop> verify checkInteractiveSu "su foo; something; exit"
-- prop> verifyNot checkInteractiveSu "echo rm | su foo"
-- prop> verifyNot checkInteractiveSu "su root < script"
-- >>> prop $ verify checkInteractiveSu "su; rm file; su $USER"
-- >>> prop $ verify checkInteractiveSu "su foo; something; exit"
-- >>> prop $ verifyNot checkInteractiveSu "echo rm | su foo"
-- >>> prop $ verifyNot checkInteractiveSu "su root < script"
checkInteractiveSu = CommandCheck (Basename "su") f
where
f cmd = when (length (arguments cmd) <= 1) $ do
@ -485,10 +484,10 @@ checkInteractiveSu = CommandCheck (Basename "su") f
-- |
-- This is hard to get right without properly parsing ssh args
--
-- prop> verify checkSshCommandString "ssh host \"echo $PS1\""
-- prop> verifyNot checkSshCommandString "ssh host \"ls foo\""
-- prop> verifyNot checkSshCommandString "ssh \"$host\""
-- prop> verifyNot checkSshCommandString "ssh -i key \"$host\""
-- >>> prop $ verify checkSshCommandString "ssh host \"echo $PS1\""
-- >>> prop $ verifyNot checkSshCommandString "ssh host \"ls foo\""
-- >>> prop $ verifyNot checkSshCommandString "ssh \"$host\""
-- >>> prop $ verifyNot checkSshCommandString "ssh -i key \"$host\""
checkSshCommandString = CommandCheck (Basename "ssh") (f . arguments)
where
isOption x = "-" `isPrefixOf` (concat $ oversimplify x)
@ -505,24 +504,24 @@ checkSshCommandString = CommandCheck (Basename "ssh") (f . arguments)
-- |
-- prop> verify checkPrintfVar "printf \"Lol: $s\""
-- prop> verifyNot checkPrintfVar "printf 'Lol: $s'"
-- prop> verify checkPrintfVar "printf -v cow $(cmd)"
-- prop> verifyNot checkPrintfVar "printf \"%${count}s\" var"
-- prop> verify checkPrintfVar "printf '%s %s %s' foo bar"
-- prop> verify checkPrintfVar "printf foo bar baz"
-- prop> verify checkPrintfVar "printf -- foo bar baz"
-- prop> verifyNot checkPrintfVar "printf '%s %s %s' \"${var[@]}\""
-- prop> verifyNot checkPrintfVar "printf '%s %s %s\\n' *.png"
-- prop> verifyNot checkPrintfVar "printf '%s %s %s' foo bar baz"
-- prop> verifyNot checkPrintfVar "printf '%(%s%s)T' -1"
-- prop> verify checkPrintfVar "printf '%s %s\\n' 1 2 3"
-- prop> verifyNot checkPrintfVar "printf '%s %s\\n' 1 2 3 4"
-- prop> verify checkPrintfVar "printf '%*s\\n' 1"
-- prop> verifyNot checkPrintfVar "printf '%*s\\n' 1 2"
-- prop> verifyNot checkPrintfVar "printf $'string'"
-- prop> verify checkPrintfVar "printf '%-*s\\n' 1"
-- prop> verifyNot checkPrintfVar "printf '%-*s\\n' 1 2"
-- >>> prop $ verify checkPrintfVar "printf \"Lol: $s\""
-- >>> prop $ verifyNot checkPrintfVar "printf 'Lol: $s'"
-- >>> prop $ verify checkPrintfVar "printf -v cow $(cmd)"
-- >>> prop $ verifyNot checkPrintfVar "printf \"%${count}s\" var"
-- >>> prop $ verify checkPrintfVar "printf '%s %s %s' foo bar"
-- >>> prop $ verify checkPrintfVar "printf foo bar baz"
-- >>> prop $ verify checkPrintfVar "printf -- foo bar baz"
-- >>> prop $ verifyNot checkPrintfVar "printf '%s %s %s' \"${var[@]}\""
-- >>> prop $ verifyNot checkPrintfVar "printf '%s %s %s\\n' *.png"
-- >>> prop $ verifyNot checkPrintfVar "printf '%s %s %s' foo bar baz"
-- >>> prop $ verifyNot checkPrintfVar "printf '%(%s%s)T' -1"
-- >>> prop $ verify checkPrintfVar "printf '%s %s\\n' 1 2 3"
-- >>> prop $ verifyNot checkPrintfVar "printf '%s %s\\n' 1 2 3 4"
-- >>> prop $ verify checkPrintfVar "printf '%*s\\n' 1"
-- >>> prop $ verifyNot checkPrintfVar "printf '%*s\\n' 1 2"
-- >>> prop $ verifyNot checkPrintfVar "printf $'string'"
-- >>> prop $ verify checkPrintfVar "printf '%-*s\\n' 1"
-- >>> prop $ verifyNot checkPrintfVar "printf '%-*s\\n' 1 2"
checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where
f (doubledash:rest) | getLiteralString doubledash == Just "--" = f rest
f (dashv:var:rest) | getLiteralString dashv == Just "-v" = f rest
@ -572,12 +571,12 @@ checkPrintfVar = CommandCheck (Exactly "printf") (f . arguments) where
-- |
-- prop> verify checkUuoeCmd "echo $(date)"
-- prop> verify checkUuoeCmd "echo `date`"
-- prop> verify checkUuoeCmd "echo \"$(date)\""
-- prop> verify checkUuoeCmd "echo \"`date`\""
-- prop> verifyNot checkUuoeCmd "echo \"The time is $(date)\""
-- prop> verifyNot checkUuoeCmd "echo \"$(<file)\""
-- >>> prop $ verify checkUuoeCmd "echo $(date)"
-- >>> prop $ verify checkUuoeCmd "echo `date`"
-- >>> prop $ verify checkUuoeCmd "echo \"$(date)\""
-- >>> prop $ verify checkUuoeCmd "echo \"`date`\""
-- >>> prop $ verifyNot checkUuoeCmd "echo \"The time is $(date)\""
-- >>> prop $ verifyNot checkUuoeCmd "echo \"$(<file)\""
checkUuoeCmd = CommandCheck (Exactly "echo") (f . arguments) where
msg id = style id 2005 "Useless echo? Instead of 'echo $(cmd)', just use 'cmd'."
f [token] = when (tokenIsJustCommandOutput token) $ msg (getId token)
@ -585,12 +584,12 @@ checkUuoeCmd = CommandCheck (Exactly "echo") (f . arguments) where
-- |
-- prop> verify checkSetAssignment "set foo 42"
-- prop> verify checkSetAssignment "set foo = 42"
-- prop> verify checkSetAssignment "set foo=42"
-- prop> verifyNot checkSetAssignment "set -- if=/dev/null"
-- prop> verifyNot checkSetAssignment "set 'a=5'"
-- prop> verifyNot checkSetAssignment "set"
-- >>> prop $ verify checkSetAssignment "set foo 42"
-- >>> prop $ verify checkSetAssignment "set foo = 42"
-- >>> prop $ verify checkSetAssignment "set foo=42"
-- >>> prop $ verifyNot checkSetAssignment "set -- if=/dev/null"
-- >>> prop $ verifyNot checkSetAssignment "set 'a=5'"
-- >>> prop $ verifyNot checkSetAssignment "set"
checkSetAssignment = CommandCheck (Exactly "set") (f . arguments)
where
f (var:value:rest) =
@ -611,10 +610,10 @@ checkSetAssignment = CommandCheck (Exactly "set") (f . arguments)
-- |
-- prop> verify checkExportedExpansions "export $foo"
-- prop> verify checkExportedExpansions "export \"$foo\""
-- prop> verifyNot checkExportedExpansions "export foo"
-- prop> verifyNot checkExportedExpansions "export ${foo?}"
-- >>> prop $ verify checkExportedExpansions "export $foo"
-- >>> prop $ verify checkExportedExpansions "export \"$foo\""
-- >>> prop $ verifyNot checkExportedExpansions "export foo"
-- >>> prop $ verifyNot checkExportedExpansions "export ${foo?}"
checkExportedExpansions = CommandCheck (Exactly "export") (mapM_ check . arguments)
where
check t = potentially $ do
@ -624,14 +623,14 @@ checkExportedExpansions = CommandCheck (Exactly "export") (mapM_ check . argumen
"This does not export '" ++ name ++ "'. Remove $/${} for that, or use ${var?} to quiet."
-- |
-- prop> verify checkReadExpansions "read $var"
-- prop> verify checkReadExpansions "read -r $var"
-- prop> verifyNot checkReadExpansions "read -p $var"
-- prop> verifyNot checkReadExpansions "read -rd $delim name"
-- prop> verify checkReadExpansions "read \"$var\""
-- prop> verify checkReadExpansions "read -a $var"
-- prop> verifyNot checkReadExpansions "read $1"
-- prop> verifyNot checkReadExpansions "read ${var?}"
-- >>> prop $ verify checkReadExpansions "read $var"
-- >>> prop $ verify checkReadExpansions "read -r $var"
-- >>> prop $ verifyNot checkReadExpansions "read -p $var"
-- >>> prop $ verifyNot checkReadExpansions "read -rd $delim name"
-- >>> prop $ verify checkReadExpansions "read \"$var\""
-- >>> prop $ verify checkReadExpansions "read -a $var"
-- >>> prop $ verifyNot checkReadExpansions "read $1"
-- >>> prop $ verifyNot checkReadExpansions "read ${var?}"
checkReadExpansions = CommandCheck (Exactly "read") check
where
options = getGnuOpts "sreu:n:N:i:p:a:"
@ -659,9 +658,9 @@ getSingleUnmodifiedVariable word =
_ -> Nothing
-- |
-- prop> verify checkAliasesUsesArgs "alias a='cp $1 /a'"
-- prop> verifyNot checkAliasesUsesArgs "alias $1='foo'"
-- prop> verify checkAliasesUsesArgs "alias a=\"echo \\${@}\""
-- >>> prop $ verify checkAliasesUsesArgs "alias a='cp $1 /a'"
-- >>> prop $ verifyNot checkAliasesUsesArgs "alias $1='foo'"
-- >>> prop $ verify checkAliasesUsesArgs "alias a=\"echo \\${@}\""
checkAliasesUsesArgs = CommandCheck (Exactly "alias") (f . arguments)
where
re = mkRegex "\\$\\{?[0-9*@]"
@ -674,9 +673,9 @@ checkAliasesUsesArgs = CommandCheck (Exactly "alias") (f . arguments)
-- |
-- prop> verify checkAliasesExpandEarly "alias foo=\"echo $PWD\""
-- prop> verifyNot checkAliasesExpandEarly "alias -p"
-- prop> verifyNot checkAliasesExpandEarly "alias foo='echo {1..10}'"
-- >>> prop $ verify checkAliasesExpandEarly "alias foo=\"echo $PWD\""
-- >>> prop $ verifyNot checkAliasesExpandEarly "alias -p"
-- >>> prop $ verifyNot checkAliasesExpandEarly "alias foo='echo {1..10}'"
checkAliasesExpandEarly = CommandCheck (Exactly "alias") (f . arguments)
where
f = mapM_ checkArg
@ -686,8 +685,8 @@ checkAliasesExpandEarly = CommandCheck (Exactly "alias") (f . arguments)
checkArg _ = return ()
-- prop> verify checkUnsetGlobs "unset foo[1]"
-- prop> verifyNot checkUnsetGlobs "unset foo"
-- >>> prop $ verify checkUnsetGlobs "unset foo[1]"
-- >>> prop $ verifyNot checkUnsetGlobs "unset foo"
checkUnsetGlobs = CommandCheck (Exactly "unset") (mapM_ check . arguments)
where
check arg =
@ -696,14 +695,14 @@ checkUnsetGlobs = CommandCheck (Exactly "unset") (mapM_ check . arguments)
-- |
-- prop> verify checkFindWithoutPath "find -type f"
-- prop> verify checkFindWithoutPath "find"
-- prop> verifyNot checkFindWithoutPath "find . -type f"
-- prop> verifyNot checkFindWithoutPath "find -H -L \"$path\" -print"
-- prop> verifyNot checkFindWithoutPath "find -O3 ."
-- prop> verifyNot checkFindWithoutPath "find -D exec ."
-- prop> verifyNot checkFindWithoutPath "find --help"
-- prop> verifyNot checkFindWithoutPath "find -Hx . -print"
-- >>> prop $ verify checkFindWithoutPath "find -type f"
-- >>> prop $ verify checkFindWithoutPath "find"
-- >>> prop $ verifyNot checkFindWithoutPath "find . -type f"
-- >>> prop $ verifyNot checkFindWithoutPath "find -H -L \"$path\" -print"
-- >>> prop $ verifyNot checkFindWithoutPath "find -O3 ."
-- >>> prop $ verifyNot checkFindWithoutPath "find -D exec ."
-- >>> prop $ verifyNot checkFindWithoutPath "find --help"
-- >>> prop $ verifyNot checkFindWithoutPath "find -Hx . -print"
checkFindWithoutPath = CommandCheck (Basename "find") f
where
f t@(T_SimpleCommand _ _ (cmd:args)) =
@ -723,10 +722,10 @@ checkFindWithoutPath = CommandCheck (Basename "find") f
-- |
-- prop> verify checkTimeParameters "time -f lol sleep 10"
-- prop> verifyNot checkTimeParameters "time sleep 10"
-- prop> verifyNot checkTimeParameters "time -p foo"
-- prop> verifyNot checkTimeParameters "command time -f lol sleep 10"
-- >>> prop $ verify checkTimeParameters "time -f lol sleep 10"
-- >>> prop $ verifyNot checkTimeParameters "time sleep 10"
-- >>> prop $ verifyNot checkTimeParameters "time -p foo"
-- >>> prop $ verifyNot checkTimeParameters "command time -f lol sleep 10"
checkTimeParameters = CommandCheck (Exactly "time") f
where
f (T_SimpleCommand _ _ (cmd:args:_)) =
@ -738,9 +737,9 @@ checkTimeParameters = CommandCheck (Exactly "time") f
f _ = return ()
-- |
-- prop> verify checkTimedCommand "#!/bin/sh\ntime -p foo | bar"
-- prop> verify checkTimedCommand "#!/bin/dash\ntime ( foo; bar; )"
-- prop> verifyNot checkTimedCommand "#!/bin/sh\ntime sleep 1"
-- >>> prop $ verify checkTimedCommand "#!/bin/sh\ntime -p foo | bar"
-- >>> prop $ verify checkTimedCommand "#!/bin/dash\ntime ( foo; bar; )"
-- >>> prop $ verifyNot checkTimedCommand "#!/bin/sh\ntime sleep 1"
checkTimedCommand = CommandCheck (Exactly "time") f where
f (T_SimpleCommand _ _ (c:args@(_:_))) =
whenShell [Sh, Dash] $ do
@ -765,8 +764,8 @@ checkTimedCommand = CommandCheck (Exactly "time") f where
_ -> return False
-- |
-- prop> verify checkLocalScope "local foo=3"
-- prop> verifyNot checkLocalScope "f() { local foo=3; }"
-- >>> prop $ verify checkLocalScope "local foo=3"
-- >>> prop $ verifyNot checkLocalScope "f() { local foo=3; }"
checkLocalScope = CommandCheck (Exactly "local") $ \t ->
whenShell [Bash, Dash] $ do -- Ksh allows it, Sh doesn't support local
path <- getPathM t
@ -774,27 +773,27 @@ checkLocalScope = CommandCheck (Exactly "local") $ \t ->
err (getId $ getCommandTokenOrThis t) 2168 "'local' is only valid in functions."
-- |
-- prop> verify checkDeprecatedTempfile "var=$(tempfile)"
-- prop> verifyNot checkDeprecatedTempfile "tempfile=$(mktemp)"
-- >>> prop $ verify checkDeprecatedTempfile "var=$(tempfile)"
-- >>> prop $ verifyNot checkDeprecatedTempfile "tempfile=$(mktemp)"
checkDeprecatedTempfile = CommandCheck (Basename "tempfile") $
\t -> warn (getId $ getCommandTokenOrThis t) 2186 "tempfile is deprecated. Use mktemp instead."
-- |
-- prop> verify checkDeprecatedEgrep "egrep '.+'"
-- >>> prop $ verify checkDeprecatedEgrep "egrep '.+'"
checkDeprecatedEgrep = CommandCheck (Basename "egrep") $
\t -> info (getId $ getCommandTokenOrThis t) 2196 "egrep is non-standard and deprecated. Use grep -E instead."
-- |
-- prop> verify checkDeprecatedFgrep "fgrep '*' files"
-- >>> prop $ verify checkDeprecatedFgrep "fgrep '*' files"
checkDeprecatedFgrep = CommandCheck (Basename "fgrep") $
\t -> info (getId $ getCommandTokenOrThis t) 2197 "fgrep is non-standard and deprecated. Use grep -F instead."
-- |
-- prop> verify checkWhileGetoptsCase "while getopts 'a:b' x; do case $x in a) foo;; esac; done"
-- prop> verify checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; b) bar;; esac; done"
-- prop> verifyNot checkWhileGetoptsCase "while getopts 'a:b' x; do case $x in a) foo;; b) bar;; *) :;esac; done"
-- prop> verifyNot checkWhileGetoptsCase "while getopts 'a:123' x; do case $x in a) foo;; [0-9]) bar;; esac; done"
-- prop> verifyNot checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; \\?) bar;; *) baz;; esac; done"
-- >>> prop $ verify checkWhileGetoptsCase "while getopts 'a:b' x; do case $x in a) foo;; esac; done"
-- >>> prop $ verify checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; b) bar;; esac; done"
-- >>> prop $ verifyNot checkWhileGetoptsCase "while getopts 'a:b' x; do case $x in a) foo;; b) bar;; *) :;esac; done"
-- >>> prop $ verifyNot checkWhileGetoptsCase "while getopts 'a:123' x; do case $x in a) foo;; [0-9]) bar;; esac; done"
-- >>> prop $ verifyNot checkWhileGetoptsCase "while getopts 'a:' x; do case $x in a) foo;; \\?) bar;; *) baz;; esac; done"
checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f
where
f :: Token -> Analysis
@ -860,19 +859,19 @@ checkWhileGetoptsCase = CommandCheck (Exactly "getopts") f
_ -> Nothing
-- |
-- prop> verify checkCatastrophicRm "rm -r $1/$2"
-- prop> verify checkCatastrophicRm "rm -r /home/$foo"
-- prop> verifyNot checkCatastrophicRm "rm -r /home/${USER:?}/*"
-- prop> verify checkCatastrophicRm "rm -fr /home/$(whoami)/*"
-- prop> verifyNot checkCatastrophicRm "rm -r /home/${USER:-thing}/*"
-- prop> verify checkCatastrophicRm "rm --recursive /etc/*$config*"
-- prop> verify checkCatastrophicRm "rm -rf /home"
-- prop> verifyNot checkCatastrophicRm "rm -r \"${DIR}\"/{.gitignore,.gitattributes,ci}"
-- prop> verify checkCatastrophicRm "rm -r /{bin,sbin}/$exec"
-- prop> verify checkCatastrophicRm "rm -r /{{usr,},{bin,sbin}}/$exec"
-- prop> verifyNot checkCatastrophicRm "rm -r /{{a,b},{c,d}}/$exec"
-- prop> verify checkCatastrophicRm "rm -rf /usr /lib/nvidia-current/xorg/xorg"
-- prop> verify checkCatastrophicRm "rm -rf \"$STEAMROOT/\"*"
-- >>> prop $ verify checkCatastrophicRm "rm -r $1/$2"
-- >>> prop $ verify checkCatastrophicRm "rm -r /home/$foo"
-- >>> prop $ verifyNot checkCatastrophicRm "rm -r /home/${USER:?}/*"
-- >>> prop $ verify checkCatastrophicRm "rm -fr /home/$(whoami)/*"
-- >>> prop $ verifyNot checkCatastrophicRm "rm -r /home/${USER:-thing}/*"
-- >>> prop $ verify checkCatastrophicRm "rm --recursive /etc/*$config*"
-- >>> prop $ verify checkCatastrophicRm "rm -rf /home"
-- >>> prop $ verifyNot checkCatastrophicRm "rm -r \"${DIR}\"/{.gitignore,.gitattributes,ci}"
-- >>> prop $ verify checkCatastrophicRm "rm -r /{bin,sbin}/$exec"
-- >>> prop $ verify checkCatastrophicRm "rm -r /{{usr,},{bin,sbin}}/$exec"
-- >>> prop $ verifyNot checkCatastrophicRm "rm -r /{{a,b},{c,d}}/$exec"
-- >>> prop $ verify checkCatastrophicRm "rm -rf /usr /lib/nvidia-current/xorg/xorg"
-- >>> prop $ verify checkCatastrophicRm "rm -rf \"$STEAMROOT/\"*"
checkCatastrophicRm = CommandCheck (Basename "rm") $ \t ->
when (isRecursive t) $
mapM_ (mapM_ checkWord . braceExpand) $ arguments t
@ -922,8 +921,8 @@ checkCatastrophicRm = CommandCheck (Basename "rm") $ \t ->
-- |
-- prop> verify checkLetUsage "let a=1"
-- prop> verifyNot checkLetUsage "(( a=1 ))"
-- >>> prop $ verify checkLetUsage "let a=1"
-- >>> prop $ verifyNot checkLetUsage "(( a=1 ))"
checkLetUsage = CommandCheck (Exactly "let") f
where
f t = whenShell [Bash,Ksh] $ do
@ -944,15 +943,15 @@ missingDestination handler token = do
map snd args
-- |
-- prop> verify checkMvArguments "mv 'foo bar'"
-- prop> verifyNot checkMvArguments "mv foo bar"
-- prop> verifyNot checkMvArguments "mv 'foo bar'{,bak}"
-- prop> verifyNot checkMvArguments "mv \"$@\""
-- prop> verifyNot checkMvArguments "mv -t foo bar"
-- prop> verifyNot checkMvArguments "mv --target-directory=foo bar"
-- prop> verifyNot checkMvArguments "mv --target-direc=foo bar"
-- prop> verifyNot checkMvArguments "mv --version"
-- prop> verifyNot checkMvArguments "mv \"${!var}\""
-- >>> prop $ verify checkMvArguments "mv 'foo bar'"
-- >>> prop $ verifyNot checkMvArguments "mv foo bar"
-- >>> prop $ verifyNot checkMvArguments "mv 'foo bar'{,bak}"
-- >>> prop $ verifyNot checkMvArguments "mv \"$@\""
-- >>> prop $ verifyNot checkMvArguments "mv -t foo bar"
-- >>> prop $ verifyNot checkMvArguments "mv --target-directory=foo bar"
-- >>> prop $ verifyNot checkMvArguments "mv --target-direc=foo bar"
-- >>> prop $ verifyNot checkMvArguments "mv --version"
-- >>> prop $ verifyNot checkMvArguments "mv \"${!var}\""
checkMvArguments = CommandCheck (Basename "mv") $ missingDestination f
where
f t = err (getId t) 2224 "This mv has no destination. Check the arguments."
@ -967,9 +966,9 @@ checkLnArguments = CommandCheck (Basename "ln") $ missingDestination f
-- |
-- prop> verify checkFindRedirections "find . -exec echo {} > file \\;"
-- prop> verifyNot checkFindRedirections "find . -exec echo {} \\; > file"
-- prop> verifyNot checkFindRedirections "find . -execdir sh -c 'foo > file' \\;"
-- >>> prop $ verify checkFindRedirections "find . -exec echo {} > file \\;"
-- >>> prop $ verifyNot checkFindRedirections "find . -exec echo {} \\; > file"
-- >>> prop $ verifyNot checkFindRedirections "find . -execdir sh -c 'foo > file' \\;"
checkFindRedirections = CommandCheck (Basename "find") f
where
f t = do
@ -984,18 +983,18 @@ checkFindRedirections = CommandCheck (Basename "find") f
"Redirection applies to the find command itself. Rewrite to work per action (or move to end)."
_ -> return ()
-- prop> verify checkWhich "which '.+'"
-- >>> prop $ verify checkWhich "which '.+'"
checkWhich = CommandCheck (Basename "which") $
\t -> info (getId $ getCommandTokenOrThis t) 2230 "which is non-standard. Use builtin 'command -v' instead."
-- |
-- prop> verify checkSudoRedirect "sudo echo 3 > /proc/file"
-- prop> verify checkSudoRedirect "sudo cmd < input"
-- prop> verify checkSudoRedirect "sudo cmd >> file"
-- prop> verify checkSudoRedirect "sudo cmd &> file"
-- prop> verifyNot checkSudoRedirect "sudo cmd 2>&1"
-- prop> verifyNot checkSudoRedirect "sudo cmd 2> log"
-- prop> verifyNot checkSudoRedirect "sudo cmd > /dev/null 2>&1"
-- >>> prop $ verify checkSudoRedirect "sudo echo 3 > /proc/file"
-- >>> prop $ verify checkSudoRedirect "sudo cmd < input"
-- >>> prop $ verify checkSudoRedirect "sudo cmd >> file"
-- >>> prop $ verify checkSudoRedirect "sudo cmd &> file"
-- >>> prop $ verifyNot checkSudoRedirect "sudo cmd 2>&1"
-- >>> prop $ verifyNot checkSudoRedirect "sudo cmd 2> log"
-- >>> prop $ verifyNot checkSudoRedirect "sudo cmd > /dev/null 2>&1"
checkSudoRedirect = CommandCheck (Basename "sudo") f
where
f t = do
@ -1020,13 +1019,13 @@ checkSudoRedirect = CommandCheck (Basename "sudo") f
special file = concat (oversimplify file) == "/dev/null"
-- |
-- prop> verify checkSudoArgs "sudo cd /root"
-- prop> verify checkSudoArgs "sudo export x=3"
-- prop> verifyNot checkSudoArgs "sudo ls /usr/local/protected"
-- prop> verifyNot checkSudoArgs "sudo ls && export x=3"
-- prop> verifyNot checkSudoArgs "sudo echo ls"
-- prop> verifyNot checkSudoArgs "sudo -n -u export ls"
-- prop> verifyNot checkSudoArgs "sudo docker export foo"
-- >>> prop $ verify checkSudoArgs "sudo cd /root"
-- >>> prop $ verify checkSudoArgs "sudo export x=3"
-- >>> prop $ verifyNot checkSudoArgs "sudo ls /usr/local/protected"
-- >>> prop $ verifyNot checkSudoArgs "sudo ls && export x=3"
-- >>> prop $ verifyNot checkSudoArgs "sudo echo ls"
-- >>> prop $ verifyNot checkSudoArgs "sudo -n -u export ls"
-- >>> prop $ verifyNot checkSudoArgs "sudo docker export foo"
checkSudoArgs = CommandCheck (Basename "sudo") f
where
f t = potentially $ do
@ -1039,4 +1038,3 @@ checkSudoArgs = CommandCheck (Basename "sudo") f
builtins = [ "cd", "eval", "export", "history", "read", "source", "wait" ]
-- This mess is why ShellCheck prefers not to know.
parseOpts = getBsdOpts "vAknSbEHPa:g:h:p:u:c:T:r:"

View file

@ -65,9 +65,9 @@ verify c s = producesComments (testChecker c) s == Just True
verifyNot c s = producesComments (testChecker c) s == Just False
-- |
-- prop> verify checkForDecimals "((3.14*c))"
-- prop> verify checkForDecimals "foo[1.2]=bar"
-- prop> verifyNot checkForDecimals "declare -A foo; foo[1.2]=bar"
-- >>> prop $ verify checkForDecimals "((3.14*c))"
-- >>> prop $ verify checkForDecimals "foo[1.2]=bar"
-- >>> prop $ verifyNot checkForDecimals "declare -A foo; foo[1.2]=bar"
checkForDecimals = ForShell [Sh, Dash, Bash] f
where
f t@(TA_Expansion id _) = potentially $ do
@ -79,62 +79,62 @@ checkForDecimals = ForShell [Sh, Dash, Bash] f
-- |
-- prop> verify checkBashisms "while read a; do :; done < <(a)"
-- prop> verify checkBashisms "[ foo -nt bar ]"
-- prop> verify checkBashisms "echo $((i++))"
-- prop> verify checkBashisms "rm !(*.hs)"
-- prop> verify checkBashisms "source file"
-- prop> verify checkBashisms "[ \"$a\" == 42 ]"
-- prop> verify checkBashisms "echo ${var[1]}"
-- prop> verify checkBashisms "echo ${!var[@]}"
-- prop> verify checkBashisms "echo ${!var*}"
-- prop> verify checkBashisms "echo ${var:4:12}"
-- prop> verifyNot checkBashisms "echo ${var:-4}"
-- prop> verify checkBashisms "echo ${var//foo/bar}"
-- prop> verify checkBashisms "exec -c env"
-- prop> verify checkBashisms "echo -n \"Foo: \""
-- prop> verify checkBashisms "let n++"
-- prop> verify checkBashisms "echo $RANDOM"
-- prop> verify checkBashisms "echo $((RANDOM%6+1))"
-- prop> verify checkBashisms "foo &> /dev/null"
-- prop> verify checkBashisms "foo > file*.txt"
-- prop> verify checkBashisms "read -ra foo"
-- prop> verify checkBashisms "[ -a foo ]"
-- prop> verifyNot checkBashisms "[ foo -a bar ]"
-- prop> verify checkBashisms "trap mything ERR INT"
-- prop> verifyNot checkBashisms "trap mything INT TERM"
-- prop> verify checkBashisms "cat < /dev/tcp/host/123"
-- prop> verify checkBashisms "trap mything ERR SIGTERM"
-- prop> verify checkBashisms "echo *[^0-9]*"
-- prop> verify checkBashisms "exec {n}>&2"
-- prop> verify checkBashisms "echo ${!var}"
-- prop> verify checkBashisms "printf -v '%s' \"$1\""
-- prop> verify checkBashisms "printf '%q' \"$1\""
-- prop> verifyNot checkBashisms "#!/bin/dash\n[ foo -nt bar ]"
-- prop> verify checkBashisms "#!/bin/sh\necho -n foo"
-- prop> verifyNot checkBashisms "#!/bin/dash\necho -n foo"
-- prop> verifyNot checkBashisms "#!/bin/dash\nlocal foo"
-- prop> verifyNot checkBashisms "#!/bin/dash\nread -p foo -r bar"
-- prop> verifyNot checkBashisms "HOSTNAME=foo; echo $HOSTNAME"
-- prop> verify checkBashisms "RANDOM=9; echo $RANDOM"
-- prop> verify checkBashisms "foo-bar() { true; }"
-- prop> verify checkBashisms "echo $(<file)"
-- prop> verify checkBashisms "echo `<file`"
-- prop> verify checkBashisms "trap foo int"
-- prop> verify checkBashisms "trap foo sigint"
-- prop> verifyNot checkBashisms "#!/bin/dash\ntrap foo int"
-- prop> verifyNot checkBashisms "#!/bin/dash\ntrap foo INT"
-- prop> verify checkBashisms "#!/bin/dash\ntrap foo SIGINT"
-- prop> verify checkBashisms "#!/bin/dash\necho foo 42>/dev/null"
-- prop> verifyNot checkBashisms "#!/bin/sh\necho $LINENO"
-- prop> verify checkBashisms "#!/bin/dash\necho $MACHTYPE"
-- prop> verify checkBashisms "#!/bin/sh\ncmd >& file"
-- prop> verifyNot checkBashisms "#!/bin/sh\ncmd 2>&1"
-- prop> verifyNot checkBashisms "#!/bin/sh\ncmd >&2"
-- prop> verifyNot checkBashisms "#!/bin/sh\nprintf -- -f\n"
-- prop> verify checkBashisms "#!/bin/sh\nfoo+=bar"
-- prop> verify checkBashisms "#!/bin/sh\necho ${@%foo}"
-- prop> verifyNot checkBashisms "#!/bin/sh\necho ${##}"
-- >>> prop $ verify checkBashisms "while read a; do :; done < <(a)"
-- >>> prop $ verify checkBashisms "[ foo -nt bar ]"
-- >>> prop $ verify checkBashisms "echo $((i++))"
-- >>> prop $ verify checkBashisms "rm !(*.hs)"
-- >>> prop $ verify checkBashisms "source file"
-- >>> prop $ verify checkBashisms "[ \"$a\" == 42 ]"
-- >>> prop $ verify checkBashisms "echo ${var[1]}"
-- >>> prop $ verify checkBashisms "echo ${!var[@]}"
-- >>> prop $ verify checkBashisms "echo ${!var*}"
-- >>> prop $ verify checkBashisms "echo ${var:4:12}"
-- >>> prop $ verifyNot checkBashisms "echo ${var:-4}"
-- >>> prop $ verify checkBashisms "echo ${var//foo/bar}"
-- >>> prop $ verify checkBashisms "exec -c env"
-- >>> prop $ verify checkBashisms "echo -n \"Foo: \""
-- >>> prop $ verify checkBashisms "let n++"
-- >>> prop $ verify checkBashisms "echo $RANDOM"
-- >>> prop $ verify checkBashisms "echo $((RANDOM%6+1))"
-- >>> prop $ verify checkBashisms "foo &> /dev/null"
-- >>> prop $ verify checkBashisms "foo > file*.txt"
-- >>> prop $ verify checkBashisms "read -ra foo"
-- >>> prop $ verify checkBashisms "[ -a foo ]"
-- >>> prop $ verifyNot checkBashisms "[ foo -a bar ]"
-- >>> prop $ verify checkBashisms "trap mything ERR INT"
-- >>> prop $ verifyNot checkBashisms "trap mything INT TERM"
-- >>> prop $ verify checkBashisms "cat < /dev/tcp/host/123"
-- >>> prop $ verify checkBashisms "trap mything ERR SIGTERM"
-- >>> prop $ verify checkBashisms "echo *[^0-9]*"
-- >>> prop $ verify checkBashisms "exec {n}>&2"
-- >>> prop $ verify checkBashisms "echo ${!var}"
-- >>> prop $ verify checkBashisms "printf -v '%s' \"$1\""
-- >>> prop $ verify checkBashisms "printf '%q' \"$1\""
-- >>> prop $ verifyNot checkBashisms "#!/bin/dash\n[ foo -nt bar ]"
-- >>> prop $ verify checkBashisms "#!/bin/sh\necho -n foo"
-- >>> prop $ verifyNot checkBashisms "#!/bin/dash\necho -n foo"
-- >>> prop $ verifyNot checkBashisms "#!/bin/dash\nlocal foo"
-- >>> prop $ verifyNot checkBashisms "#!/bin/dash\nread -p foo -r bar"
-- >>> prop $ verifyNot checkBashisms "HOSTNAME=foo; echo $HOSTNAME"
-- >>> prop $ verify checkBashisms "RANDOM=9; echo $RANDOM"
-- >>> prop $ verify checkBashisms "foo-bar() { true; }"
-- >>> prop $ verify checkBashisms "echo $(<file)"
-- >>> prop $ verify checkBashisms "echo `<file`"
-- >>> prop $ verify checkBashisms "trap foo int"
-- >>> prop $ verify checkBashisms "trap foo sigint"
-- >>> prop $ verifyNot checkBashisms "#!/bin/dash\ntrap foo int"
-- >>> prop $ verifyNot checkBashisms "#!/bin/dash\ntrap foo INT"
-- >>> prop $ verify checkBashisms "#!/bin/dash\ntrap foo SIGINT"
-- >>> prop $ verify checkBashisms "#!/bin/dash\necho foo 42>/dev/null"
-- >>> prop $ verifyNot checkBashisms "#!/bin/sh\necho $LINENO"
-- >>> prop $ verify checkBashisms "#!/bin/dash\necho $MACHTYPE"
-- >>> prop $ verify checkBashisms "#!/bin/sh\ncmd >& file"
-- >>> prop $ verifyNot checkBashisms "#!/bin/sh\ncmd 2>&1"
-- >>> prop $ verifyNot checkBashisms "#!/bin/sh\ncmd >&2"
-- >>> prop $ verifyNot checkBashisms "#!/bin/sh\nprintf -- -f\n"
-- >>> prop $ verify checkBashisms "#!/bin/sh\nfoo+=bar"
-- >>> prop $ verify checkBashisms "#!/bin/sh\necho ${@%foo}"
-- >>> prop $ verifyNot checkBashisms "#!/bin/sh\necho ${##}"
checkBashisms = ForShell [Sh, Dash] $ \t -> do
params <- ask
kludge params t
@ -317,8 +317,8 @@ checkBashisms = ForShell [Sh, Dash] $ \t -> do
_ -> False
-- |
-- prop> verify checkEchoSed "FOO=$(echo \"$cow\" | sed 's/foo/bar/g')"
-- prop> verify checkEchoSed "rm $(echo $cow | sed -e 's,foo,bar,')"
-- >>> prop $ verify checkEchoSed "FOO=$(echo \"$cow\" | sed 's/foo/bar/g')"
-- >>> prop $ verify checkEchoSed "rm $(echo $cow | sed -e 's,foo,bar,')"
checkEchoSed = ForShell [Bash, Ksh] f
where
f (T_Pipeline id _ [a, b]) =
@ -345,10 +345,10 @@ checkEchoSed = ForShell [Bash, Ksh] f
-- |
-- prop> verify checkBraceExpansionVars "echo {1..$n}"
-- prop> verifyNot checkBraceExpansionVars "echo {1,3,$n}"
-- prop> verify checkBraceExpansionVars "eval echo DSC{0001..$n}.jpg"
-- prop> verify checkBraceExpansionVars "echo {$i..100}"
-- >>> prop $ verify checkBraceExpansionVars "echo {1..$n}"
-- >>> prop $ verifyNot checkBraceExpansionVars "echo {1,3,$n}"
-- >>> prop $ verify checkBraceExpansionVars "eval echo DSC{0001..$n}.jpg"
-- >>> prop $ verify checkBraceExpansionVars "echo {$i..100}"
checkBraceExpansionVars = ForShell [Bash] f
where
f t@(T_BraceExpansion id list) = mapM_ check list
@ -374,12 +374,12 @@ checkBraceExpansionVars = ForShell [Bash] f
-- |
-- prop> verify checkMultiDimensionalArrays "foo[a][b]=3"
-- prop> verifyNot checkMultiDimensionalArrays "foo[a]=3"
-- prop> verify checkMultiDimensionalArrays "foo=( [a][b]=c )"
-- prop> verifyNot checkMultiDimensionalArrays "foo=( [a]=c )"
-- prop> verify checkMultiDimensionalArrays "echo ${foo[bar][baz]}"
-- prop> verifyNot checkMultiDimensionalArrays "echo ${foo[bar]}"
-- >>> prop $ verify checkMultiDimensionalArrays "foo[a][b]=3"
-- >>> prop $ verifyNot checkMultiDimensionalArrays "foo[a]=3"
-- >>> prop $ verify checkMultiDimensionalArrays "foo=( [a][b]=c )"
-- >>> prop $ verifyNot checkMultiDimensionalArrays "foo=( [a]=c )"
-- >>> prop $ verify checkMultiDimensionalArrays "echo ${foo[bar][baz]}"
-- >>> prop $ verifyNot checkMultiDimensionalArrays "echo ${foo[bar]}"
checkMultiDimensionalArrays = ForShell [Bash] f
where
f token =
@ -395,16 +395,16 @@ checkMultiDimensionalArrays = ForShell [Bash] f
isMultiDim t = getBracedModifier (bracedString t) `matches` re
-- |
-- prop> verify checkPS1Assignments "PS1='\\033[1;35m\\$ '"
-- prop> verify checkPS1Assignments "export PS1='\\033[1;35m\\$ '"
-- prop> verify checkPS1Assignments "PS1='\\h \\e[0m\\$ '"
-- prop> verify checkPS1Assignments "PS1=$'\\x1b[c '"
-- prop> verify checkPS1Assignments "PS1=$'\\e[3m; '"
-- prop> verify checkPS1Assignments "export PS1=$'\\e[3m; '"
-- prop> verifyNot checkPS1Assignments "PS1='\\[\\033[1;35m\\]\\$ '"
-- prop> verifyNot checkPS1Assignments "PS1='\\[\\e1m\\e[1m\\]\\$ '"
-- prop> verifyNot checkPS1Assignments "PS1='e033x1B'"
-- prop> verifyNot checkPS1Assignments "PS1='\\[\\e\\]'"
-- >>> prop $ verify checkPS1Assignments "PS1='\\033[1;35m\\$ '"
-- >>> prop $ verify checkPS1Assignments "export PS1='\\033[1;35m\\$ '"
-- >>> prop $ verify checkPS1Assignments "PS1='\\h \\e[0m\\$ '"
-- >>> prop $ verify checkPS1Assignments "PS1=$'\\x1b[c '"
-- >>> prop $ verify checkPS1Assignments "PS1=$'\\e[3m; '"
-- >>> prop $ verify checkPS1Assignments "export PS1=$'\\e[3m; '"
-- >>> prop $ verifyNot checkPS1Assignments "PS1='\\[\\033[1;35m\\]\\$ '"
-- >>> prop $ verifyNot checkPS1Assignments "PS1='\\[\\e1m\\e[1m\\]\\$ '"
-- >>> prop $ verifyNot checkPS1Assignments "PS1='e033x1B'"
-- >>> prop $ verifyNot checkPS1Assignments "PS1='\\[\\e\\]'"
checkPS1Assignments = ForShell [Bash] f
where
f token = case token of

View file

@ -47,6 +47,10 @@ import qualified Control.Monad.Reader as Mr
import qualified Control.Monad.State as Ms
import qualified Data.Map as Map
prop :: Bool -> IO ()
prop False = putStrLn "FAIL"
prop True = return ()
type SCBase m = Mr.ReaderT (Environment m) (Ms.StateT SystemState m)
type SCParser m v = ParsecT String UserState (SCBase m) v
@ -85,7 +89,7 @@ unicodeDoubleQuotes = "\x201C\x201D\x2033\x2036"
unicodeSingleQuotes = "\x2018\x2019"
-- |
-- prop> isOk spacing " \\\n # Comment"
-- >>> prop $ isOk spacing " \\\n # Comment"
spacing = do
x <- many (many1 linewhitespace <|> try (string "\\\n" >> return ""))
optional readComment
@ -97,9 +101,9 @@ spacing1 = do
return spacing
-- |
-- prop> isOk allspacing "#foo"
-- prop> isOk allspacing " #foo\n # bar\n#baz\n"
-- prop> isOk allspacing "#foo\n#bar\n#baz\n"
-- >>> prop $ isOk allspacing "#foo"
-- >>> prop $ isOk allspacing " #foo\n # bar\n#baz\n"
-- >>> prop $ isOk allspacing "#foo\n#bar\n#baz\n"
allspacing = do
s <- spacing
more <- option False (linefeed >> return True)
@ -673,29 +677,29 @@ readConditionContents single =
-- |
-- prop> isOk readArithmeticContents " n++ + ++c"
-- prop> isOk readArithmeticContents "$N*4-(3,2)"
-- prop> isOk readArithmeticContents "n|=2<<1"
-- prop> isOk readArithmeticContents "n &= 2 **3"
-- prop> isOk readArithmeticContents "1 |= 4 && n >>= 4"
-- prop> isOk readArithmeticContents " 1 | 2 ||3|4"
-- prop> isOk readArithmeticContents "3*2**10"
-- prop> isOk readArithmeticContents "3"
-- prop> isOk readArithmeticContents "a^!-b"
-- prop> isOk readArithmeticContents "! $?"
-- prop> isOk readArithmeticContents "10#08 * 16#f"
-- prop> isOk readArithmeticContents "\"$((3+2))\" + '37'"
-- prop> isOk readArithmeticContents "foo[9*y+x]++"
-- prop> isOk readArithmeticContents "1+`echo 2`"
-- prop> isOk readArithmeticContents "foo[`echo foo | sed s/foo/4/g` * 3] + 4"
-- prop> isOk readArithmeticContents "$foo$bar"
-- prop> isOk readArithmeticContents "i<(0+(1+1))"
-- prop> isOk readArithmeticContents "a?b:c"
-- prop> isOk readArithmeticContents "\\\n3 +\\\n 2"
-- prop> isOk readArithmeticContents "a ? b ? c : d : e"
-- prop> isOk readArithmeticContents "a ? b : c ? d : e"
-- prop> isOk readArithmeticContents "!!a"
-- prop> isOk readArithmeticContents "~0"
-- >>> prop $ isOk readArithmeticContents " n++ + ++c"
-- >>> prop $ isOk readArithmeticContents "$N*4-(3,2)"
-- >>> prop $ isOk readArithmeticContents "n|=2<<1"
-- >>> prop $ isOk readArithmeticContents "n &= 2 **3"
-- >>> prop $ isOk readArithmeticContents "1 |= 4 && n >>= 4"
-- >>> prop $ isOk readArithmeticContents " 1 | 2 ||3|4"
-- >>> prop $ isOk readArithmeticContents "3*2**10"
-- >>> prop $ isOk readArithmeticContents "3"
-- >>> prop $ isOk readArithmeticContents "a^!-b"
-- >>> prop $ isOk readArithmeticContents "! $?"
-- >>> prop $ isOk readArithmeticContents "10#08 * 16#f"
-- >>> prop $ isOk readArithmeticContents "\"$((3+2))\" + '37'"
-- >>> prop $ isOk readArithmeticContents "foo[9*y+x]++"
-- >>> prop $ isOk readArithmeticContents "1+`echo 2`"
-- >>> prop $ isOk readArithmeticContents "foo[`echo foo | sed s/foo/4/g` * 3] + 4"
-- >>> prop $ isOk readArithmeticContents "$foo$bar"
-- >>> prop $ isOk readArithmeticContents "i<(0+(1+1))"
-- >>> prop $ isOk readArithmeticContents "a?b:c"
-- >>> prop $ isOk readArithmeticContents "\\\n3 +\\\n 2"
-- >>> prop $ isOk readArithmeticContents "a ? b ? c : d : e"
-- >>> prop $ isOk readArithmeticContents "a ? b : c ? d : e"
-- >>> prop $ isOk readArithmeticContents "!!a"
-- >>> prop $ isOk readArithmeticContents "~0"
readArithmeticContents :: Monad m => SCParser m Token
readArithmeticContents =
readSequence
@ -877,33 +881,33 @@ readArithmeticContents =
-- |
-- prop> isOk readCondition "[ \\( a = b \\) -a \\( c = d \\) ]"
-- prop> isOk readCondition "[[ (a = b) || (c = d) ]]"
-- prop> isOk readCondition "[[ $c = [[:alpha:].~-] ]]"
-- prop> isOk readCondition "[[ $c =~ *foo* ]]"
-- prop> isOk readCondition "[[ $c =~ f( ]] )* ]]"
-- prop> isOk readCondition "[[ $c =~ a(b) ]]"
-- prop> isOk readCondition "[[ $c =~ f( ($var ]]) )* ]]"
-- prop> isOk readCondition "[[ $c =~ ^[yY]$ ]]"
-- prop> isOk readCondition "[[ ${line} =~ ^[[:space:]]*# ]]"
-- prop> isOk readCondition "[[ $l =~ ogg|flac ]]"
-- prop> isOk readCondition "[ foo -a -f bar ]"
-- prop> isOk readCondition "[[\na == b\n||\nc == d ]]"
-- prop> isOk readCondition "[[\na == b ||\nc == d ]]"
-- prop> isOk readCondition "[[ a == b\n||\nc == d ]]"
-- prop> isOk readCondition "[[ a == b ||\n c == d ]]"
-- prop> isWarning readCondition "[ a == b \n -o c == d ]"
-- prop> isOk readCondition "[[ foo =~ ^fo{1,3}$ ]]"
-- prop> isOk readCondition "[ foo '>' bar ]"
-- prop> isOk readCondition "[ foo \">=\" bar ]"
-- prop> isOk readCondition "[ foo \\< bar ]"
-- prop> isOk readCondition "[[ ${file::1} = [-.\\|/\\\\] ]]"
-- prop> isOk readCondition "[ ]"
-- prop> isOk readCondition "[ '(' x \")\" ]"
-- prop> isOk readCondition "[[ echo_rc -eq 0 ]]"
-- prop> isOk readCondition "[[ $1 =~ ^(a\\ b)$ ]]"
-- prop> isOk readCondition "[[ $1 =~ \\.a\\.(\\.b\\.)\\.c\\. ]]"
-- prop> isOk readCondition "[[ -v arr[$var] ]]"
-- >>> prop $ isOk readCondition "[ \\( a = b \\) -a \\( c = d \\) ]"
-- >>> prop $ isOk readCondition "[[ (a = b) || (c = d) ]]"
-- >>> prop $ isOk readCondition "[[ $c = [[:alpha:].~-] ]]"
-- >>> prop $ isOk readCondition "[[ $c =~ *foo* ]]"
-- >>> prop $ isOk readCondition "[[ $c =~ f( ]] )* ]]"
-- >>> prop $ isOk readCondition "[[ $c =~ a(b) ]]"
-- >>> prop $ isOk readCondition "[[ $c =~ f( ($var ]]) )* ]]"
-- >>> prop $ isOk readCondition "[[ $c =~ ^[yY]$ ]]"
-- >>> prop $ isOk readCondition "[[ ${line} =~ ^[[:space:]]*# ]]"
-- >>> prop $ isOk readCondition "[[ $l =~ ogg|flac ]]"
-- >>> prop $ isOk readCondition "[ foo -a -f bar ]"
-- >>> prop $ isOk readCondition "[[\na == b\n||\nc == d ]]"
-- >>> prop $ isOk readCondition "[[\na == b ||\nc == d ]]"
-- >>> prop $ isOk readCondition "[[ a == b\n||\nc == d ]]"
-- >>> prop $ isOk readCondition "[[ a == b ||\n c == d ]]"
-- >>> prop $ isWarning readCondition "[ a == b \n -o c == d ]"
-- >>> prop $ isOk readCondition "[[ foo =~ ^fo{1,3}$ ]]"
-- >>> prop $ isOk readCondition "[ foo '>' bar ]"
-- >>> prop $ isOk readCondition "[ foo \">=\" bar ]"
-- >>> prop $ isOk readCondition "[ foo \\< bar ]"
-- >>> prop $ isOk readCondition "[[ ${file::1} = [-.\\|/\\\\] ]]"
-- >>> prop $ isOk readCondition "[ ]"
-- >>> prop $ isOk readCondition "[ '(' x \")\" ]"
-- >>> prop $ isOk readCondition "[[ echo_rc -eq 0 ]]"
-- >>> prop $ isOk readCondition "[[ $1 =~ ^(a\\ b)$ ]]"
-- >>> prop $ isOk readCondition "[[ $1 =~ \\.a\\.(\\.b\\.)\\.c\\. ]]"
-- >>> prop $ isOk readCondition "[[ -v arr[$var] ]]"
readCondition = called "test expression" $ do
opos <- getPosition
start <- startSpan
@ -942,12 +946,12 @@ readAnnotationPrefix = do
string "shellcheck"
-- |
-- prop> isOk readAnnotation "# shellcheck disable=1234,5678\n"
-- prop> isOk readAnnotation "# shellcheck disable=SC1234 disable=SC5678\n"
-- prop> isOk readAnnotation "# shellcheck disable=SC1234 source=/dev/null disable=SC5678\n"
-- prop> isWarning readAnnotation "# shellcheck cats=dogs disable=SC1234\n"
-- prop> isOk readAnnotation "# shellcheck disable=SC2002 # All cats are precious\n"
-- prop> isOk readAnnotation "# shellcheck disable=SC1234 # shellcheck foo=bar\n"
-- >>> prop $ isOk readAnnotation "# shellcheck disable=1234,5678\n"
-- >>> prop $ isOk readAnnotation "# shellcheck disable=SC1234 disable=SC5678\n"
-- >>> prop $ isOk readAnnotation "# shellcheck disable=SC1234 source=/dev/null disable=SC5678\n"
-- >>> prop $ isWarning readAnnotation "# shellcheck cats=dogs disable=SC1234\n"
-- >>> prop $ isOk readAnnotation "# shellcheck disable=SC2002 # All cats are precious\n"
-- >>> prop $ isOk readAnnotation "# shellcheck disable=SC1234 # shellcheck foo=bar\n"
readAnnotation = called "shellcheck directive" $ do
try readAnnotationPrefix
many1 linewhitespace
@ -1005,18 +1009,18 @@ readAnyComment = do
many $ noneOf "\r\n"
-- |
-- prop> isOk readNormalWord "'foo'\"bar\"{1..3}baz$(lol)"
-- prop> isOk readNormalWord "foo**(foo)!!!(@@(bar))"
-- prop> isOk readNormalWord "foo#"
-- prop> isOk readNormalWord "$\"foo\"$'foo\nbar'"
-- prop> isWarning readNormalWord "${foo}}"
-- prop> isOk readNormalWord "foo/{}"
-- prop> isOk readNormalWord "foo\\\nbar"
-- prop> isWarning readSubshell "(foo\\ \nbar)"
-- prop> isOk readSubshell "(foo\\ ;\nbar)"
-- prop> isWarning readNormalWord "\x201Chello\x201D"
-- prop> isWarning readNormalWord "\x2018hello\x2019"
-- prop> isWarning readNormalWord "hello\x2018"
-- >>> prop $ isOk readNormalWord "'foo'\"bar\"{1..3}baz$(lol)"
-- >>> prop $ isOk readNormalWord "foo**(foo)!!!(@@(bar))"
-- >>> prop $ isOk readNormalWord "foo#"
-- >>> prop $ isOk readNormalWord "$\"foo\"$'foo\nbar'"
-- >>> prop $ isWarning readNormalWord "${foo}}"
-- >>> prop $ isOk readNormalWord "foo/{}"
-- >>> prop $ isOk readNormalWord "foo\\\nbar"
-- >>> prop $ isWarning readSubshell "(foo\\ \nbar)"
-- >>> prop $ isOk readSubshell "(foo\\ ;\nbar)"
-- >>> prop $ isWarning readNormalWord "\x201Chello\x201D"
-- >>> prop $ isWarning readNormalWord "\x2018hello\x2019"
-- >>> prop $ isWarning readNormalWord "hello\x2018"
readNormalWord = readNormalishWord ""
readNormalishWord end = do
@ -1115,9 +1119,9 @@ readParamSubSpecialChar = do
return $ T_ParamSubSpecialChar id x
-- |
-- prop> isOk readProcSub "<(echo test | wc -l)"
-- prop> isOk readProcSub "<( if true; then true; fi )"
-- prop> isOk readProcSub "<( # nothing here \n)"
-- >>> prop $ isOk readProcSub "<(echo test | wc -l)"
-- >>> prop $ isOk readProcSub "<( if true; then true; fi )"
-- >>> prop $ isOk readProcSub "<( # nothing here \n)"
readProcSub = called "process substitution" $ do
start <- startSpan
dir <- try $ do
@ -1131,13 +1135,13 @@ readProcSub = called "process substitution" $ do
return $ T_ProcSub id dir list
-- |
-- prop> isOk readSingleQuoted "'foo bar'"
-- prop> isWarning readSingleQuoted "'foo bar\\'"
-- prop> isWarning readNormalWord "'it's"
-- prop> isWarning readSimpleCommand "foo='bar\ncow 'arg"
-- prop> isOk readSimpleCommand "foo='bar cow 'arg"
-- prop> isOk readSingleQuoted "'foo\x201C\&bar'"
-- prop> isWarning readSingleQuoted "'foo\x2018\&bar'"
-- >>> prop $ isOk readSingleQuoted "'foo bar'"
-- >>> prop $ isWarning readSingleQuoted "'foo bar\\'"
-- >>> prop $ isWarning readNormalWord "'it's"
-- >>> prop $ isWarning readSimpleCommand "foo='bar\ncow 'arg"
-- >>> prop $ isOk readSimpleCommand "foo='bar cow 'arg"
-- >>> prop $ isOk readSingleQuoted "'foo\x201C\&bar'"
-- >>> prop $ isWarning readSingleQuoted "'foo\x2018\&bar'"
readSingleQuoted = called "single quoted string" $ do
start <- startSpan
startPos <- getPosition
@ -1180,14 +1184,14 @@ readSingleQuotedPart =
-- |
-- prop> isOk (readBackTicked False) "`ls *.mp3`"
-- prop> isOk (readBackTicked False) "`grep \"\\\"\"`"
-- prop> isWarning (readBackTicked False) "´grep \"\\\"\"´"
-- prop> isOk readSimpleCommand "`echo foo\necho bar`"
-- prop> isOk readSimpleCommand "echo `foo`bar"
-- prop> isWarning readSimpleCommand "echo `foo\necho `bar"
-- prop> isOk readSimpleCommand "`#inline comment`"
-- prop> isOk readSimpleCommand "echo `#comment` \\\nbar baz"
-- >>> prop $ isOk (readBackTicked False) "`ls *.mp3`"
-- >>> prop $ isOk (readBackTicked False) "`grep \"\\\"\"`"
-- >>> prop $ isWarning (readBackTicked False) "´grep \"\\\"\"´"
-- >>> prop $ isOk readSimpleCommand "`echo foo\necho bar`"
-- >>> prop $ isOk readSimpleCommand "echo `foo`bar"
-- >>> prop $ isWarning readSimpleCommand "echo `foo\necho `bar"
-- >>> prop $ isOk readSimpleCommand "`#inline comment`"
-- >>> prop $ isOk readSimpleCommand "echo `#comment` \\\nbar baz"
readQuotedBackTicked = readBackTicked True
readUnquotedBackTicked = readBackTicked False
readBackTicked quoted = called "backtick expansion" $ do
@ -1254,15 +1258,15 @@ parseForgettingContext alsoOnSuccess parser = do
fail ""
-- |
-- prop> isOk readDoubleQuoted "\"Hello $FOO\""
-- prop> isOk readDoubleQuoted "\"$'\""
-- prop> isOk readDoubleQuoted "\"\x2018hello\x2019\""
-- prop> isWarning readSimpleCommand "\"foo\nbar\"foo"
-- prop> isOk readSimpleCommand "lol \"foo\nbar\" etc"
-- prop> isOk readSimpleCommand "echo \"${ ls; }\""
-- prop> isOk readSimpleCommand "echo \"${ ls;}bar\""
-- prop> isWarning readDoubleQuoted "\"\x201Chello\x201D\""
-- prop> isOk readDoubleQuoted "\"foo\\\\n\""
-- >>> prop $ isOk readDoubleQuoted "\"Hello $FOO\""
-- >>> prop $ isOk readDoubleQuoted "\"$'\""
-- >>> prop $ isOk readDoubleQuoted "\"\x2018hello\x2019\""
-- >>> prop $ isWarning readSimpleCommand "\"foo\nbar\"foo"
-- >>> prop $ isOk readSimpleCommand "lol \"foo\nbar\" etc"
-- >>> prop $ isOk readSimpleCommand "echo \"${ ls; }\""
-- >>> prop $ isOk readSimpleCommand "echo \"${ ls;}bar\""
-- >>> prop $ isWarning readDoubleQuoted "\"\x201Chello\x201D\""
-- >>> prop $ isOk readDoubleQuoted "\"foo\\\\n\""
readDoubleQuoted = called "double quoted string" $ do
start <- startSpan
startPos <- getPosition
@ -1316,14 +1320,14 @@ readNormalLiteral end = do
return $ T_Literal id (concat s)
-- |
-- prop> isOk readGlob "*"
-- prop> isOk readGlob "[^0-9]"
-- prop> isOk readGlob "[a[:alpha:]]"
-- prop> isOk readGlob "[[:alnum:]]"
-- prop> isOk readGlob "[^[:alpha:]1-9]"
-- prop> isOk readGlob "[\\|]"
-- prop> isOk readGlob "[^[]"
-- prop> isOk readGlob "[*?]"
-- >>> prop $ isOk readGlob "*"
-- >>> prop $ isOk readGlob "[^0-9]"
-- >>> prop $ isOk readGlob "[a[:alpha:]]"
-- >>> prop $ isOk readGlob "[[:alnum:]]"
-- >>> prop $ isOk readGlob "[^[:alpha:]1-9]"
-- >>> prop $ isOk readGlob "[\\|]"
-- >>> prop $ isOk readGlob "[^[]"
-- >>> prop $ isOk readGlob "[*?]"
readGlob = readExtglob <|> readSimple <|> readClass <|> readGlobbyLiteral
where
readSimple = do
@ -1392,13 +1396,13 @@ readNormalEscaped = called "escaped char" $ do
-- |
-- prop> isOk readExtglob "!(*.mp3)"
-- prop> isOk readExtglob "!(*.mp3|*.wmv)"
-- prop> isOk readExtglob "+(foo \\) bar)"
-- prop> isOk readExtglob "+(!(foo *(bar)))"
-- prop> isOk readExtglob "*(((||))|())"
-- prop> isOk readExtglob "*(<>)"
-- prop> isOk readExtglob "@(|*())"
-- >>> prop $ isOk readExtglob "!(*.mp3)"
-- >>> prop $ isOk readExtglob "!(*.mp3|*.wmv)"
-- >>> prop $ isOk readExtglob "+(foo \\) bar)"
-- >>> prop $ isOk readExtglob "+(!(foo *(bar)))"
-- >>> prop $ isOk readExtglob "*(((||))|())"
-- >>> prop $ isOk readExtglob "*(<>)"
-- >>> prop $ isOk readExtglob "@(|*())"
readExtglob = called "extglob" $ do
start <- startSpan
c <- try $ do
@ -1475,14 +1479,14 @@ readGenericEscaped = do
return $ if x == '\n' then [] else ['\\', x]
-- |
-- prop> isOk readBraced "{1..4}"
-- prop> isOk readBraced "{foo,bar,\"baz lol\"}"
-- prop> isOk readBraced "{1,\\},2}"
-- prop> isOk readBraced "{1,{2,3}}"
-- prop> isOk readBraced "{JP{,E}G,jp{,e}g}"
-- prop> isOk readBraced "{foo,bar,$((${var}))}"
-- prop> isNotOk readBraced "{}"
-- prop> isNotOk readBraced "{foo}"
-- >>> prop $ isOk readBraced "{1..4}"
-- >>> prop $ isOk readBraced "{foo,bar,\"baz lol\"}"
-- >>> prop $ isOk readBraced "{1,\\},2}"
-- >>> prop $ isOk readBraced "{1,{2,3}}"
-- >>> prop $ isOk readBraced "{JP{,E}G,jp{,e}g}"
-- >>> prop $ isOk readBraced "{foo,bar,$((${var}))}"
-- >>> prop $ isNotOk readBraced "{}"
-- >>> prop $ isNotOk readBraced "{foo}"
readBraced = try braceExpansion
where
braceExpansion =
@ -1523,9 +1527,9 @@ readDoubleQuotedDollar = do
-- |
-- prop> isOk readDollarExpression "$(((1) && 3))"
-- prop> isWarning readDollarExpression "$(((1)) && 3)"
-- prop> isWarning readDollarExpression "$((\"$@\" &); foo;)"
-- >>> prop $ isOk readDollarExpression "$(((1) && 3))"
-- >>> prop $ isWarning readDollarExpression "$(((1)) && 3)"
-- >>> prop $ isWarning readDollarExpression "$((\"$@\" &); foo;)"
readDollarExpression :: Monad m => SCParser m Token
readDollarExpression = do
ensureDollar
@ -1537,7 +1541,7 @@ readDollarExp = arithmetic <|> readDollarExpansion <|> readDollarBracket <|> rea
parseNoteAt pos WarningC 1102 "Shells disambiguate $(( differently or not at all. For $(command substition), add space after $( . For $((arithmetics)), fix parsing errors.")
-- |
-- prop> isOk readDollarSingleQuote "$'foo\\\'lol'"
-- >>> prop $ isOk readDollarSingleQuote "$'foo\\\'lol'"
readDollarSingleQuote = called "$'..' expression" $ do
start <- startSpan
try $ string "$'"
@ -1547,7 +1551,7 @@ readDollarSingleQuote = called "$'..' expression" $ do
return $ T_DollarSingleQuoted id str
-- |
-- prop> isOk readDollarDoubleQuote "$\"hello\""
-- >>> prop $ isOk readDollarDoubleQuote "$\"hello\""
readDollarDoubleQuote = do
lookAhead . try $ string "$\""
start <- startSpan
@ -1559,8 +1563,8 @@ readDollarDoubleQuote = do
return $ T_DollarDoubleQuoted id x
-- |
-- prop> isOk readDollarArithmetic "$(( 3 * 4 +5))"
-- prop> isOk readDollarArithmetic "$(((3*4)+(1*2+(3-1))))"
-- >>> prop $ isOk readDollarArithmetic "$(( 3 * 4 +5))"
-- >>> prop $ isOk readDollarArithmetic "$(((3*4)+(1*2+(3-1))))"
readDollarArithmetic = called "$((..)) expression" $ do
start <- startSpan
try (string "$((")
@ -1580,7 +1584,7 @@ readDollarBracket = called "$[..] expression" $ do
return (T_DollarBracket id c)
-- |
-- prop> isOk readArithmeticExpression "((a?b:c))"
-- >>> prop $ isOk readArithmeticExpression "((a?b:c))"
readArithmeticExpression = called "((..)) command" $ do
start <- startSpan
try (string "((")
@ -1604,8 +1608,8 @@ readAmbiguous prefix expected alternative warner = do
return t
-- |
-- prop> isOk readDollarBraceCommandExpansion "${ ls; }"
-- prop> isOk readDollarBraceCommandExpansion "${\nls\n}"
-- >>> prop $ isOk readDollarBraceCommandExpansion "${ ls; }"
-- >>> prop $ isOk readDollarBraceCommandExpansion "${\nls\n}"
readDollarBraceCommandExpansion = called "ksh ${ ..; } command expansion" $ do
start <- startSpan
try $ do
@ -1618,10 +1622,10 @@ readDollarBraceCommandExpansion = called "ksh ${ ..; } command expansion" $ do
return $ T_DollarBraceCommandExpansion id term
-- |
-- prop> isOk readDollarBraced "${foo//bar/baz}"
-- prop> isOk readDollarBraced "${foo/'{cow}'}"
-- prop> isOk readDollarBraced "${foo%%$(echo cow\\})}"
-- prop> isOk readDollarBraced "${foo#\\}}"
-- >>> prop $ isOk readDollarBraced "${foo//bar/baz}"
-- >>> prop $ isOk readDollarBraced "${foo/'{cow}'}"
-- >>> prop $ isOk readDollarBraced "${foo%%$(echo cow\\})}"
-- >>> prop $ isOk readDollarBraced "${foo#\\}}"
readDollarBraced = called "parameter expansion" $ do
start <- startSpan
try (string "${")
@ -1631,9 +1635,9 @@ readDollarBraced = called "parameter expansion" $ do
return $ T_DollarBraced id word
-- |
-- prop> isOk readDollarExpansion "$(echo foo; ls\n)"
-- prop> isOk readDollarExpansion "$( )"
-- prop> isOk readDollarExpansion "$( command \n#comment \n)"
-- >>> prop $ isOk readDollarExpansion "$(echo foo; ls\n)"
-- >>> prop $ isOk readDollarExpansion "$( )"
-- >>> prop $ isOk readDollarExpansion "$( command \n#comment \n)"
readDollarExpansion = called "command expansion" $ do
start <- startSpan
try (string "$(")
@ -1643,11 +1647,11 @@ readDollarExpansion = called "command expansion" $ do
return $ T_DollarExpansion id cmds
-- |
-- prop> isOk readDollarVariable "$@"
-- prop> isOk (readDollarVariable >> anyChar) "$?!"
-- prop> isWarning (readDollarVariable >> anyChar) "$10"
-- prop> isWarning (readDollarVariable >> string "[@]") "$arr[@]"
-- prop> isWarning (readDollarVariable >> string "[f") "$arr[f"
-- >>> prop $ isOk readDollarVariable "$@"
-- >>> prop $ isOk (readDollarVariable >> anyChar) "$?!"
-- >>> prop $ isWarning (readDollarVariable >> anyChar) "$10"
-- >>> prop $ isWarning (readDollarVariable >> string "[@]") "$arr[@]"
-- >>> prop $ isWarning (readDollarVariable >> string "[f") "$arr[f"
readDollarVariable :: Monad m => SCParser m Token
readDollarVariable = do
start <- startSpan
@ -1697,25 +1701,25 @@ readDollarLonely = do
return $ T_Literal id "$"
-- |
-- prop> isOk readScript "cat << foo\nlol\ncow\nfoo"
-- prop> isNotOk readScript "cat <<- EOF\n cow\n EOF"
-- prop> isOk readScript "cat << foo\n$\"\nfoo"
-- prop> isNotOk readScript "cat << foo\n`\nfoo"
-- prop> isOk readScript "cat <<- !foo\nbar\n!foo"
-- prop> isOk readScript "cat << foo\\ bar\ncow\nfoo bar"
-- prop> isOk readScript "cat << foo\n\\$(f ())\nfoo"
-- prop> isOk readScript "cat <<foo>>bar\netc\nfoo"
-- prop> isOk readScript "if true; then cat << foo; fi\nbar\nfoo\n"
-- prop> isOk readScript "if true; then cat << foo << bar; fi\nfoo\nbar\n"
-- prop> isOk readScript "cat << foo $(\nfoo\n)lol\nfoo\n"
-- prop> isOk readScript "cat << foo|cat\nbar\nfoo"
-- prop> isOk readScript "cat <<'#!'\nHello World\n#!\necho Done"
-- prop> isWarning readScript "cat << foo\nbar\nfoo \n"
-- prop> isWarning readScript "cat <<foo\nbar\nfoo bar\nfoo"
-- prop> isOk readScript "cat <<- ' foo'\nbar\n foo\n"
-- prop> isWarning readScript "cat <<- ' foo'\nbar\n foo\n foo\n"
-- prop> isWarning readScript "cat << foo\n foo\n()\nfoo\n"
-- prop> isOk readScript "# shellcheck disable=SC1039\ncat << foo\n foo\n()\nfoo\n"
-- >>> prop $ isOk readScript "cat << foo\nlol\ncow\nfoo"
-- >>> prop $ isNotOk readScript "cat <<- EOF\n cow\n EOF"
-- >>> prop $ isOk readScript "cat << foo\n$\"\nfoo"
-- >>> prop $ isNotOk readScript "cat << foo\n`\nfoo"
-- >>> prop $ isOk readScript "cat <<- !foo\nbar\n!foo"
-- >>> prop $ isOk readScript "cat << foo\\ bar\ncow\nfoo bar"
-- >>> prop $ isOk readScript "cat << foo\n\\$(f ())\nfoo"
-- >>> prop $ isOk readScript "cat <<foo>>bar\netc\nfoo"
-- >>> prop $ isOk readScript "if true; then cat << foo; fi\nbar\nfoo\n"
-- >>> prop $ isOk readScript "if true; then cat << foo << bar; fi\nfoo\nbar\n"
-- >>> prop $ isOk readScript "cat << foo $(\nfoo\n)lol\nfoo\n"
-- >>> prop $ isOk readScript "cat << foo|cat\nbar\nfoo"
-- >>> prop $ isOk readScript "cat <<'#!'\nHello World\n#!\necho Done"
-- >>> prop $ isWarning readScript "cat << foo\nbar\nfoo \n"
-- >>> prop $ isWarning readScript "cat <<foo\nbar\nfoo bar\nfoo"
-- >>> prop $ isOk readScript "cat <<- ' foo'\nbar\n foo\n"
-- >>> prop $ isWarning readScript "cat <<- ' foo'\nbar\n foo\n foo\n"
-- >>> prop $ isWarning readScript "cat << foo\n foo\n()\nfoo\n"
-- >>> prop $ isOk readScript "# shellcheck disable=SC1039\ncat << foo\n foo\n()\nfoo\n"
readHereDoc = called "here document" $ do
pos <- getPosition
try $ string "<<"
@ -1884,7 +1888,7 @@ readIoDuplicate = try $ do
-- |
-- prop> isOk readIoFile ">> \"$(date +%YYmmDD)\""
-- >>> prop $ isOk readIoFile ">> \"$(date +%YYmmDD)\""
readIoFile = called "redirection" $ do
start <- startSpan
op <- readIoFileOp
@ -1905,13 +1909,13 @@ readIoSource = try $ do
return x
-- |
-- prop> isOk readIoRedirect "3>&2"
-- prop> isOk readIoRedirect "2> lol"
-- prop> isOk readIoRedirect "4>&-"
-- prop> isOk readIoRedirect "&> lol"
-- prop> isOk readIoRedirect "{foo}>&2"
-- prop> isOk readIoRedirect "{foo}<&-"
-- prop> isOk readIoRedirect "{foo}>&1-"
-- >>> prop $ isOk readIoRedirect "3>&2"
-- >>> prop $ isOk readIoRedirect "2> lol"
-- >>> prop $ isOk readIoRedirect "4>&-"
-- >>> prop $ isOk readIoRedirect "&> lol"
-- >>> prop $ isOk readIoRedirect "{foo}>&2"
-- >>> prop $ isOk readIoRedirect "{foo}<&-"
-- >>> prop $ isOk readIoRedirect "{foo}>&1-"
readIoRedirect = do
start <- startSpan
n <- readIoSource
@ -1924,7 +1928,7 @@ readIoRedirect = do
readRedirectList = many1 readIoRedirect
-- |
-- prop> isOk readHereString "<<< \"Hello $world\""
-- >>> prop $ isOk readHereString "<<< \"Hello $world\""
readHereString = called "here string" $ do
start <- startSpan
try $ string "<<<"
@ -1937,11 +1941,11 @@ readNewlineList = many1 ((linefeed <|> carriageReturn) `thenSkip` spacing)
readLineBreak = optional readNewlineList
-- |
-- prop> isWarning readScript "a &; b"
-- prop> isOk readScript "a & b"
-- prop> isWarning readScript "a &amp; b"
-- prop> isWarning readScript "a &gt; file; b"
-- prop> isWarning readScript "curl https://example.com/?foo=moo&bar=cow"
-- >>> prop $ isWarning readScript "a &; b"
-- >>> prop $ isOk readScript "a & b"
-- >>> prop $ isWarning readScript "a &amp; b"
-- >>> prop $ isWarning readScript "a &gt; file; b"
-- >>> prop $ isWarning readScript "curl https://example.com/?foo=moo&bar=cow"
readSeparatorOp = do
notFollowedBy2 (void g_AND_IF <|> void readCaseSeparator)
notFollowedBy2 (string "&>")
@ -1986,20 +1990,20 @@ readSeparator =
return ('\n', (start, end))
-- |
-- prop> isOk readSimpleCommand "echo test > file"
-- prop> isOk readSimpleCommand "cmd &> file"
-- prop> isOk readSimpleCommand "export foo=(bar baz)"
-- prop> isOk readSimpleCommand "typeset -a foo=(lol)"
-- prop> isOk readSimpleCommand "time if true; then echo foo; fi"
-- prop> isOk readSimpleCommand "time -p ( ls -l; )"
-- prop> isOk readSimpleCommand "\\ls"
-- prop> isWarning readSimpleCommand "// Lol"
-- prop> isWarning readSimpleCommand "/* Lolbert */"
-- prop> isWarning readSimpleCommand "/**** Lolbert */"
-- prop> isOk readSimpleCommand "/\\* foo"
-- prop> isWarning readSimpleCommand "elsif foo"
-- prop> isWarning readSimpleCommand "ElseIf foo"
-- prop> isWarning readSimpleCommand "elseif[$i==2]"
-- >>> prop $ isOk readSimpleCommand "echo test > file"
-- >>> prop $ isOk readSimpleCommand "cmd &> file"
-- >>> prop $ isOk readSimpleCommand "export foo=(bar baz)"
-- >>> prop $ isOk readSimpleCommand "typeset -a foo=(lol)"
-- >>> prop $ isOk readSimpleCommand "time if true; then echo foo; fi"
-- >>> prop $ isOk readSimpleCommand "time -p ( ls -l; )"
-- >>> prop $ isOk readSimpleCommand "\\ls"
-- >>> prop $ isWarning readSimpleCommand "// Lol"
-- >>> prop $ isWarning readSimpleCommand "/* Lolbert */"
-- >>> prop $ isWarning readSimpleCommand "/**** Lolbert */"
-- >>> prop $ isOk readSimpleCommand "/\\* foo"
-- >>> prop $ isWarning readSimpleCommand "elsif foo"
-- >>> prop $ isWarning readSimpleCommand "ElseIf foo"
-- >>> prop $ isWarning readSimpleCommand "elseif[$i==2]"
readSimpleCommand = called "simple command" $ do
prefix <- option [] readCmdPrefix
skipAnnotationAndWarn
@ -2126,9 +2130,9 @@ readSource t = return t
-- |
-- prop> isOk readPipeline "! cat /etc/issue | grep -i ubuntu"
-- prop> isWarning readPipeline "!cat /etc/issue | grep -i ubuntu"
-- prop> isOk readPipeline "for f; do :; done|cat"
-- >>> prop $ isOk readPipeline "! cat /etc/issue | grep -i ubuntu"
-- >>> prop $ isWarning readPipeline "!cat /etc/issue | grep -i ubuntu"
-- >>> prop $ isOk readPipeline "for f; do :; done|cat"
readPipeline = do
unexpecting "keyword/token" readKeyword
do
@ -2139,9 +2143,9 @@ readPipeline = do
readPipeSequence
-- |
-- prop> isOk readAndOr "grep -i lol foo || exit 1"
-- prop> isOk readAndOr "# shellcheck disable=1\nfoo"
-- prop> isOk readAndOr "# shellcheck disable=1\n# lol\n# shellcheck disable=3\nfoo"
-- >>> prop $ isOk readAndOr "grep -i lol foo || exit 1"
-- >>> prop $ isOk readAndOr "# shellcheck disable=1\nfoo"
-- >>> prop $ isOk readAndOr "# shellcheck disable=1\n# lol\n# shellcheck disable=3\nfoo"
readAndOr = do
start <- startSpan
apos <- getPosition
@ -2170,7 +2174,7 @@ readTermOrNone = do
return []
-- |
-- prop> isOk readTerm "time ( foo; bar; )"
-- >>> prop $ isOk readTerm "time ( foo; bar; )"
readTerm = do
allspacing
m <- readAndOr
@ -2242,11 +2246,11 @@ skipAnnotationAndWarn = optional $ do
readAnyComment
-- |
-- prop> isOk readIfClause "if false; then foo; elif true; then stuff; more stuff; else cows; fi"
-- prop> isWarning readIfClause "if false; then; echo oo; fi"
-- prop> isWarning readIfClause "if false; then true; else; echo lol; fi"
-- prop> isWarning readIfClause "if false; then true; else if true; then echo lol; fi; fi"
-- prop> isOk readIfClause "if false; then true; else\nif true; then echo lol; fi; fi"
-- >>> prop $ isOk readIfClause "if false; then foo; elif true; then stuff; more stuff; else cows; fi"
-- >>> prop $ isWarning readIfClause "if false; then; echo oo; fi"
-- >>> prop $ isWarning readIfClause "if false; then true; else; echo lol; fi"
-- >>> prop $ isWarning readIfClause "if false; then true; else if true; then echo lol; fi; fi"
-- >>> prop $ isOk readIfClause "if false; then true; else\nif true; then echo lol; fi; fi"
readIfClause = called "if expression" $ do
start <- startSpan
pos <- getPosition
@ -2322,7 +2326,7 @@ ifNextToken parser action =
action
-- |
-- prop> isOk readSubshell "( cd /foo; tar cf stuff.tar * )"
-- >>> prop $ isOk readSubshell "( cd /foo; tar cf stuff.tar * )"
readSubshell = called "explicit subshell" $ do
start <- startSpan
char '('
@ -2334,9 +2338,9 @@ readSubshell = called "explicit subshell" $ do
return $ T_Subshell id list
-- |
-- prop> isOk readBraceGroup "{ a; b | c | d; e; }"
-- prop> isWarning readBraceGroup "{foo;}"
-- prop> isOk readBraceGroup "{(foo)}"
-- >>> prop $ isOk readBraceGroup "{ a; b | c | d; e; }"
-- >>> prop $ isWarning readBraceGroup "{foo;}"
-- >>> prop $ isOk readBraceGroup "{(foo)}"
readBraceGroup = called "brace group" $ do
start <- startSpan
char '{'
@ -2355,7 +2359,7 @@ readBraceGroup = called "brace group" $ do
return $ T_BraceGroup id list
-- |
-- prop> isOk readWhileClause "while [[ -e foo ]]; do sleep 1; done"
-- >>> prop $ isOk readWhileClause "while [[ -e foo ]]; do sleep 1; done"
readWhileClause = called "while loop" $ do
start <- startSpan
kwId <- getId <$> g_While
@ -2365,7 +2369,7 @@ readWhileClause = called "while loop" $ do
return $ T_WhileExpression id condition statements
-- |
-- prop> isOk readUntilClause "until kill -0 $PID; do sleep 1; done"
-- >>> prop $ isOk readUntilClause "until kill -0 $PID; do sleep 1; done"
readUntilClause = called "until loop" $ do
start <- startSpan
kwId <- getId <$> g_Until
@ -2399,17 +2403,17 @@ readDoGroup kwId = do
-- |
-- prop> isOk readForClause "for f in *; do rm \"$f\"; done"
-- prop> isOk readForClause "for f; do foo; done"
-- prop> isOk readForClause "for((i=0; i<10; i++)); do echo $i; done"
-- prop> isOk readForClause "for ((i=0;i<10 && n>x;i++,--n))\ndo \necho $i\ndone"
-- prop> isOk readForClause "for ((;;))\ndo echo $i\ndone"
-- prop> isOk readForClause "for ((;;)) do echo $i\ndone"
-- prop> isOk readForClause "for ((;;)) ; do echo $i\ndone"
-- prop> isOk readForClause "for i do true; done"
-- prop> isOk readForClause "for ((;;)) { true; }"
-- prop> isWarning readForClause "for $a in *; do echo \"$a\"; done"
-- prop> isOk readForClause "for foo\nin\\\n bar\\\n baz\ndo true; done"
-- >>> prop $ isOk readForClause "for f in *; do rm \"$f\"; done"
-- >>> prop $ isOk readForClause "for f; do foo; done"
-- >>> prop $ isOk readForClause "for((i=0; i<10; i++)); do echo $i; done"
-- >>> prop $ isOk readForClause "for ((i=0;i<10 && n>x;i++,--n))\ndo \necho $i\ndone"
-- >>> prop $ isOk readForClause "for ((;;))\ndo echo $i\ndone"
-- >>> prop $ isOk readForClause "for ((;;)) do echo $i\ndone"
-- >>> prop $ isOk readForClause "for ((;;)) ; do echo $i\ndone"
-- >>> prop $ isOk readForClause "for i do true; done"
-- >>> prop $ isOk readForClause "for ((;;)) { true; }"
-- >>> prop $ isWarning readForClause "for $a in *; do echo \"$a\"; done"
-- >>> prop $ isOk readForClause "for foo\nin\\\n bar\\\n baz\ndo true; done"
readForClause = called "for loop" $ do
pos <- getPosition
(T_For id) <- g_For
@ -2443,8 +2447,8 @@ readForClause = called "for loop" $ do
return $ T_ForIn id name values group
-- |
-- prop> isOk readSelectClause "select foo in *; do echo $foo; done"
-- prop> isOk readSelectClause "select foo; do echo $foo; done"
-- >>> prop $ isOk readSelectClause "select foo in *; do echo $foo; done"
-- >>> prop $ isOk readSelectClause "select foo; do echo $foo; done"
readSelectClause = called "select loop" $ do
(T_Select id) <- g_Select
spacing
@ -2474,11 +2478,11 @@ readInClause = do
return things
-- |
-- prop> isOk readCaseClause "case foo in a ) lol; cow;; b|d) fooo; esac"
-- prop> isOk readCaseClause "case foo\n in * ) echo bar;; esac"
-- prop> isOk readCaseClause "case foo\n in * ) echo bar & ;; esac"
-- prop> isOk readCaseClause "case foo\n in *) echo bar ;& bar) foo; esac"
-- prop> isOk readCaseClause "case foo\n in *) echo bar;;& foo) baz;; esac"
-- >>> prop $ isOk readCaseClause "case foo in a ) lol; cow;; b|d) fooo; esac"
-- >>> prop $ isOk readCaseClause "case foo\n in * ) echo bar;; esac"
-- >>> prop $ isOk readCaseClause "case foo\n in * ) echo bar & ;; esac"
-- >>> prop $ isOk readCaseClause "case foo\n in *) echo bar ;& bar) foo; esac"
-- >>> prop $ isOk readCaseClause "case foo\n in *) echo bar;;& foo) baz;; esac"
readCaseClause = called "case expression" $ do
start <- startSpan
g_Case
@ -2523,18 +2527,18 @@ readCaseSeparator = choice [
]
-- |
-- prop> isOk readFunctionDefinition "foo() { command foo --lol \"$@\"; }"
-- prop> isOk readFunctionDefinition "foo (){ command foo --lol \"$@\"; }"
-- prop> isWarning readFunctionDefinition "foo(a, b) { true; }"
-- prop> isOk readFunctionDefinition ":(){ :|:;}"
-- prop> isOk readFunctionDefinition "?(){ foo; }"
-- prop> isOk readFunctionDefinition "..(){ cd ..; }"
-- prop> isOk readFunctionDefinition "foo() (ls)"
-- prop> isOk readFunctionDefinition "function foo { true; }"
-- prop> isOk readFunctionDefinition "function foo () { true; }"
-- prop> isWarning readFunctionDefinition "function foo{\ntrue\n}"
-- prop> isOk readFunctionDefinition "function []!() { true; }"
-- prop> isOk readFunctionDefinition "@require(){ true; }"
-- >>> prop $ isOk readFunctionDefinition "foo() { command foo --lol \"$@\"; }"
-- >>> prop $ isOk readFunctionDefinition "foo (){ command foo --lol \"$@\"; }"
-- >>> prop $ isWarning readFunctionDefinition "foo(a, b) { true; }"
-- >>> prop $ isOk readFunctionDefinition ":(){ :|:;}"
-- >>> prop $ isOk readFunctionDefinition "?(){ foo; }"
-- >>> prop $ isOk readFunctionDefinition "..(){ cd ..; }"
-- >>> prop $ isOk readFunctionDefinition "foo() (ls)"
-- >>> prop $ isOk readFunctionDefinition "function foo { true; }"
-- >>> prop $ isOk readFunctionDefinition "function foo () { true; }"
-- >>> prop $ isWarning readFunctionDefinition "function foo{\ntrue\n}"
-- >>> prop $ isOk readFunctionDefinition "function []!() { true; }"
-- >>> prop $ isOk readFunctionDefinition "@require(){ true; }"
readFunctionDefinition = called "function" $ do
start <- startSpan
functionSignature <- try readFunctionSignature
@ -2577,9 +2581,9 @@ readFunctionDefinition = called "function" $ do
return ()
-- |
-- prop> isOk readCoProc "coproc foo { echo bar; }"
-- prop> isOk readCoProc "coproc { echo bar; }"
-- prop> isOk readCoProc "coproc echo bar"
-- >>> prop $ isOk readCoProc "coproc foo { echo bar; }"
-- >>> prop $ isOk readCoProc "coproc { echo bar; }"
-- >>> prop $ isOk readCoProc "coproc echo bar"
readCoProc = called "coproc" $ do
start <- startSpan
try $ do
@ -2607,7 +2611,7 @@ readCoProc = called "coproc" $ do
readPattern = (readNormalWord `thenSkip` spacing) `sepBy1` (char '|' `thenSkip` spacing)
-- |
-- prop> isOk readCompoundCommand "{ echo foo; }>/dev/null"
-- >>> prop $ isOk readCompoundCommand "{ echo foo; }>/dev/null"
readCompoundCommand = do
cmd <- choice [
readBraceGroup,
@ -2693,24 +2697,24 @@ readStringForParser parser = do
readUntil endPos = anyChar `reluctantlyTill` (getPosition >>= guard . (== endPos))
-- |
-- prop> isOk readAssignmentWord "a=42"
-- prop> isOk readAssignmentWord "b=(1 2 3)"
-- prop> isWarning readAssignmentWord "$b = 13"
-- prop> isWarning readAssignmentWord "b = $(lol)"
-- prop> isOk readAssignmentWord "b+=lol"
-- prop> isWarning readAssignmentWord "b += (1 2 3)"
-- prop> isOk readAssignmentWord "a[3$n'']=42"
-- prop> isOk readAssignmentWord "a[4''$(cat foo)]=42"
-- prop> isOk readAssignmentWord "IFS= "
-- prop> isOk readAssignmentWord "foo="
-- prop> isOk readAssignmentWord "foo= "
-- prop> isOk readAssignmentWord "foo= #bar"
-- prop> isWarning readAssignmentWord "foo$n=42"
-- prop> isOk readAssignmentWord "foo=([a]=b [c] [d]= [e f )"
-- prop> isOk readAssignmentWord "a[b <<= 3 + c]='thing'"
-- prop> isOk readAssignmentWord "var=( (1 2) (3 4) )"
-- prop> isOk readAssignmentWord "var=( 1 [2]=(3 4) )"
-- prop> isOk readAssignmentWord "var=(1 [2]=(3 4))"
-- >>> prop $ isOk readAssignmentWord "a=42"
-- >>> prop $ isOk readAssignmentWord "b=(1 2 3)"
-- >>> prop $ isWarning readAssignmentWord "$b = 13"
-- >>> prop $ isWarning readAssignmentWord "b = $(lol)"
-- >>> prop $ isOk readAssignmentWord "b+=lol"
-- >>> prop $ isWarning readAssignmentWord "b += (1 2 3)"
-- >>> prop $ isOk readAssignmentWord "a[3$n'']=42"
-- >>> prop $ isOk readAssignmentWord "a[4''$(cat foo)]=42"
-- >>> prop $ isOk readAssignmentWord "IFS= "
-- >>> prop $ isOk readAssignmentWord "foo="
-- >>> prop $ isOk readAssignmentWord "foo= "
-- >>> prop $ isOk readAssignmentWord "foo= #bar"
-- >>> prop $ isWarning readAssignmentWord "foo$n=42"
-- >>> prop $ isOk readAssignmentWord "foo=([a]=b [c] [d]= [e f )"
-- >>> prop $ isOk readAssignmentWord "a[b <<= 3 + c]='thing'"
-- >>> prop $ isOk readAssignmentWord "var=( (1 2) (3 4) )"
-- >>> prop $ isOk readAssignmentWord "var=( 1 [2]=(3 4) )"
-- >>> prop $ isOk readAssignmentWord "var=(1 [2]=(3 4))"
readAssignmentWord = readAssignmentWordExt True
readWellFormedAssignment = readAssignmentWordExt False
readAssignmentWordExt lenient = try $ do
@ -2904,13 +2908,13 @@ ifParse p t f =
(lookAhead (try p) >> t) <|> f
-- |
-- prop> isOk readShebang "#!/bin/sh\n"
-- prop> isWarning readShebang "!# /bin/sh\n"
-- prop> isNotOk readShebang "#shellcheck shell=/bin/sh\n"
-- prop> isWarning readShebang "! /bin/sh"
-- prop> isWarning readShebang "\n#!/bin/sh"
-- prop> isWarning readShebang " # Copyright \n!#/bin/bash"
-- prop> isNotOk readShebang "# Copyright \nfoo\n#!/bin/bash"
-- >>> prop $ isOk readShebang "#!/bin/sh\n"
-- >>> prop $ isWarning readShebang "!# /bin/sh\n"
-- >>> prop $ isNotOk readShebang "#shellcheck shell=/bin/sh\n"
-- >>> prop $ isWarning readShebang "! /bin/sh"
-- >>> prop $ isWarning readShebang "\n#!/bin/sh"
-- >>> prop $ isWarning readShebang " # Copyright \n!#/bin/bash"
-- >>> prop $ isNotOk readShebang "# Copyright \nfoo\n#!/bin/bash"
readShebang = do
anyShebang <|> try readMissingBang <|> withHeader
many linewhitespace
@ -2994,11 +2998,11 @@ verifyEof = eof <|> choice [
action
-- |
-- prop> isOk readScriptFile "#!/bin/bash\necho hello world\n"
-- prop> isWarning readScriptFile "#!/bin/bash\r\necho hello world\n"
-- prop> isWarning readScriptFile "#!/bin/bash\necho hello\xA0world"
-- prop> isWarning readScriptFile "#!/usr/bin/perl\nfoo=("
-- prop> isOk readScriptFile "#!/bin/bash\n#This is an empty script\n\n"
-- >>> prop $ isOk readScriptFile "#!/bin/bash\necho hello world\n"
-- >>> prop $ isWarning readScriptFile "#!/bin/bash\r\necho hello world\n"
-- >>> prop $ isWarning readScriptFile "#!/bin/bash\necho hello\xA0world"
-- >>> prop $ isWarning readScriptFile "#!/usr/bin/perl\nfoo=("
-- >>> prop $ isOk readScriptFile "#!/bin/bash\n#This is an empty script\n\n"
readScriptFile = do
start <- startSpan
pos <- getPosition