summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorVidar Holen <spam@vidarholen.net>2016-05-22 18:53:35 -0700
committerVidar Holen <spam@vidarholen.net>2016-05-22 18:53:35 -0700
commitad1a0da9548da2716b119f27ec363333acd3a1b0 (patch)
treea9207fda115dd83bc2463e7f2b880e42ab398f36
parent47fd16b8e87dc8229d3dd6b6dfb80b00cf9f125a (diff)
Attempted bats @test supportbats
-rw-r--r--ShellCheck/AST.hs3
-rw-r--r--ShellCheck/Analytics.hs8
-rw-r--r--ShellCheck/AnalyzerLib.hs14
-rw-r--r--ShellCheck/Data.hs1
-rw-r--r--ShellCheck/Parser.hs12
5 files changed, 37 insertions, 1 deletions
diff --git a/ShellCheck/AST.hs b/ShellCheck/AST.hs
index 896d6d0..0bade0b 100644
--- a/ShellCheck/AST.hs
+++ b/ShellCheck/AST.hs
@@ -128,6 +128,7 @@ data Token =
| T_CoProc Id (Maybe String) Token
| T_CoProcBody Id Token
| T_Include Id Token Token -- . & source: SimpleCommand T_Script
+ | T_BatsTest Id Token Token
deriving (Show)
data Annotation =
@@ -265,6 +266,7 @@ analyze f g i =
delve (T_CoProc id var body) = d1 body $ T_CoProc id var
delve (T_CoProcBody id t) = d1 t $ T_CoProcBody id
delve (T_Include id includer script) = d2 includer script $ T_Include id
+ delve (T_BatsTest id name t) = d2 name t $ T_BatsTest id
delve t = return t
getId t = case t of
@@ -363,6 +365,7 @@ getId t = case t of
T_CoProc id _ _ -> id
T_CoProcBody id _ -> id
T_Include id _ _ -> id
+ T_BatsTest id _ _ -> id
blank :: Monad m => Token -> m ()
blank = const $ return ()
diff --git a/ShellCheck/Analytics.hs b/ShellCheck/Analytics.hs
index 634ab1c..0a21586 100644
--- a/ShellCheck/Analytics.hs
+++ b/ShellCheck/Analytics.hs
@@ -238,7 +238,9 @@ hasFloatingPoint params = shellType params == Ksh
isCondition [] = False
isCondition [_] = False
isCondition (child:parent:rest) =
- getId child `elem` map getId (getConditionChildren parent) || isCondition (parent:rest)
+ case child of
+ T_BatsTest {} -> True -- count anything in a @test as conditional
+ _ -> getId child `elem` map getId (getConditionChildren parent) || isCondition (parent:rest)
where
getConditionChildren t =
case t of
@@ -1772,6 +1774,7 @@ prop_subshellAssignmentCheck15 = verifyNotTree subshellAssignmentCheck "#!/bin/k
prop_subshellAssignmentCheck16 = verifyNotTree subshellAssignmentCheck "(set -e); echo $@"
prop_subshellAssignmentCheck17 = verifyNotTree subshellAssignmentCheck "foo=${ { bar=$(baz); } 2>&1; }; echo $foo $bar"
prop_subshellAssignmentCheck18 = verifyTree subshellAssignmentCheck "( exec {n}>&2; ); echo $n"
+prop_subshellAssignmentCheck19 = verifyTree subshellAssignmentCheck "@test 'foo' { a=1; }\n@test 'bar' { echo $a; }\n"
subshellAssignmentCheck params t =
let flow = variableFlow params
check = findSubshelled flow [("oops",[])] Map.empty
@@ -1854,6 +1857,7 @@ prop_checkSpacefulness29= verifyNotTree checkSpacefulness "n=$(stuff); exec {n}>
prop_checkSpacefulness30= verifyTree checkSpacefulness "file='foo bar'; echo foo > $file;"
prop_checkSpacefulness31= verifyNotTree checkSpacefulness "echo \"`echo \\\"$1\\\"`\""
prop_checkSpacefulness32= verifyNotTree checkSpacefulness "var=$1; [ -v var ]"
+prop_checkSpacefulness33= verifyNotTree checkSpacefulness "@test 'status' {\n [ $status -eq 0 ]\n}"
checkSpacefulness params t =
doVariableFlowAnalysis readF writeF (Map.fromList defaults) (variableFlow params)
@@ -2071,6 +2075,8 @@ prop_checkUnused30= verifyTree checkUnusedAssignments "let a=1"
prop_checkUnused31= verifyTree checkUnusedAssignments "let 'a=1'"
prop_checkUnused32= verifyTree checkUnusedAssignments "let a=b=c; echo $a"
prop_checkUnused33= verifyNotTree checkUnusedAssignments "a=foo; [[ foo =~ ^{$a}$ ]]"
+prop_checkUnused34= verifyNotTree checkUnusedAssignments "@test 'foo' {\ntrue\n}\n"
+
checkUnusedAssignments params t = execWriter (mapM_ warnFor unused)
where
flow = variableFlow params
diff --git a/ShellCheck/AnalyzerLib.hs b/ShellCheck/AnalyzerLib.hs
index 6f02040..9887fc4 100644
--- a/ShellCheck/AnalyzerLib.hs
+++ b/ShellCheck/AnalyzerLib.hs
@@ -267,6 +267,7 @@ getVariableFlow shell parents t =
assignFirst (T_ForIn {}) = True
assignFirst (T_SelectIn {}) = True
+ assignFirst (T_BatsTest {}) = True
assignFirst _ = False
setRead t =
@@ -284,6 +285,7 @@ leadType shell parents t =
T_Backticked _ _ -> SubshellScope "`..` expansion"
T_Backgrounded _ _ -> SubshellScope "backgrounding &"
T_Subshell _ _ -> SubshellScope "(..) group"
+ T_BatsTest {} -> SubshellScope "@bats test"
T_CoProcBody _ _ -> SubshellScope "coproc"
T_Redirecting {} ->
if fromMaybe False causesSubshell
@@ -334,6 +336,12 @@ getModifiedVariables t =
name <- getLiteralString lhs
return (t, t, name, DataString $ SourceFrom [rhs])
+ T_BatsTest {} -> [
+ (t, t, "lines", DataArray SourceExternal),
+ (t, t, "status", DataString SourceInteger),
+ (t, t, "output", DataString SourceExternal)
+ ]
+
t@(T_FdRedirect _ ('{':var) op) -> -- {foo}>&2 modifies foo
[(t, t, takeWhile (/= '}') var, DataString SourceInteger) | not $ isClosingFileOp op]
@@ -493,6 +501,12 @@ getReferencedVariables parents t =
then concatMap (getIfReference t) [lhs, rhs]
else []
+ T_BatsTest {} -> [ -- pretend @test references vars to avoid warnings
+ (t, t, "lines"),
+ (t, t, "status"),
+ (t, t, "output")
+ ]
+
t@(T_FdRedirect _ ('{':var) op) -> -- {foo}>&- references and closes foo
[(t, t, takeWhile (/= '}') var) | isClosingFileOp op]
x -> getReferencedVariableCommand x
diff --git a/ShellCheck/Data.hs b/ShellCheck/Data.hs
index 0ef8cfc..a1c7141 100644
--- a/ShellCheck/Data.hs
+++ b/ShellCheck/Data.hs
@@ -87,6 +87,7 @@ shellForExecutable name =
case name of
"sh" -> return Sh
"bash" -> return Bash
+ "bats" -> return Bash
"dash" -> return Dash
"ksh" -> return Ksh
"ksh88" -> return Ksh
diff --git a/ShellCheck/Parser.hs b/ShellCheck/Parser.hs
index eaf81a8..d750360 100644
--- a/ShellCheck/Parser.hs
+++ b/ShellCheck/Parser.hs
@@ -1934,6 +1934,16 @@ readBraceGroup = called "brace group" $ do
fail "Missing '}'"
return $ T_BraceGroup id list
+prop_readBatsTest = isOk readBatsTest "@test 'can parse' {\n true\n}"
+readBatsTest = called "bats @test" $ do
+ id <- getNextId
+ try $ string "@test"
+ spacing
+ name <- readNormalWord
+ spacing
+ test <- readBraceGroup
+ return $ T_BatsTest id name test
+
prop_readWhileClause = isOk readWhileClause "while [[ -e foo ]]; do sleep 1; done"
readWhileClause = called "while loop" $ do
pos <- getPosition
@@ -2186,6 +2196,7 @@ readCompoundCommand = do
readForClause,
readSelectClause,
readCaseClause,
+ readBatsTest,
readFunctionDefinition
]
spacing
@@ -2534,6 +2545,7 @@ readScript = do
"ash",
"dash",
"bash",
+ "bats",
"ksh"
]
badShells = [