Skip to content

Commit

Permalink
Warn about ( -d foo ) and similar.
Browse files Browse the repository at this point in the history
  • Loading branch information
koalaman committed Jan 10, 2017
1 parent 85e6c35 commit edb01fa
Showing 1 changed file with 29 additions and 0 deletions.
29 changes: 29 additions & 0 deletions ShellCheck/Analytics.hs
Original file line number Diff line number Diff line change
Expand Up @@ -159,6 +159,7 @@ nodeChecks = [
,checkReturnAgainstZero
,checkRedirectedNowhere
,checkUnmatchableCases
,checkSubshellAsTest
]


Expand Down Expand Up @@ -2705,5 +2706,33 @@ checkUnmatchableCases _ t =
return $ warn (getId candidate) 2195
"This pattern will never match the case statement's word. Double check them."

prop_checkSubshellAsTest1 = verify checkSubshellAsTest "( -e file )"
prop_checkSubshellAsTest2 = verify checkSubshellAsTest "( 1 -gt 2 )"
prop_checkSubshellAsTest3 = verifyNot checkSubshellAsTest "( grep -c foo bar )"
prop_checkSubshellAsTest4 = verifyNot checkSubshellAsTest "[ 1 -gt 2 ]"
prop_checkSubshellAsTest5 = verify checkSubshellAsTest "( -e file && -x file )"
prop_checkSubshellAsTest6 = verify checkSubshellAsTest "( -e file || -x file && -t 1 )"
prop_checkSubshellAsTest7 = verify checkSubshellAsTest "( ! -d file )"
checkSubshellAsTest _ t =
case t of
T_Subshell id [w] -> check id w
_ -> return ()
where
check id t = case t of
(T_Banged _ w) -> check id w
(T_AndIf _ w _) -> check id w
(T_OrIf _ w _) -> check id w
(T_Pipeline _ _ [T_Redirecting _ _ (T_SimpleCommand _ [] (first:second:_))]) ->
checkParams id first second
_ -> return ()


checkParams id first second = do
when (fromMaybe False $ (`elem` unaryTestOps) <$> getLiteralString first) $
err id 2204 "(..) is a subshell. Did you mean [ .. ], a test expression?"
when (fromMaybe False $ (`elem` binaryTestOps) <$> getLiteralString second) $
warn id 2205 "(..) is a subshell. Did you mean [ .. ], a test expression?"


return []
runTests = $( [| $(forAllProperties) (quickCheckWithResult (stdArgs { maxSuccess = 1 }) ) |])

0 comments on commit edb01fa

Please sign in to comment.