30 Commits

Author SHA1 Message Date
Vidar Holen
b9f7f82e29 Stable version 0.2.0 2013-10-27 16:04:33 -07:00
Vidar Holen
6d0bfcf37a Fixed parser accepting spaces after here doc token 2013-10-27 16:02:27 -07:00
Vidar Holen
e0bbb89d00 Fixed parser bug where }> wasn't recognized as Rbrace 2013-10-27 15:36:47 -07:00
Vidar Holen
a0a58d432a Merge branch 'master' of github.com:koalaman/shellcheck 2013-10-20 15:04:45 -07:00
Vidar Holen
206900fb64 Use exit status and stderr properly in terminal tool 2013-10-20 15:03:14 -07:00
koalaman
794a5523d1 Merge pull request #12 from mcandre/master
README: clarify build step
2013-10-20 13:47:15 -07:00
Andrew Pennebaker
389c7b670c README: clarify build step
Help those unfamiliar with cabal to install shellcheck.
2013-10-20 16:33:00 -04:00
Vidar Holen
b1af7bb8f2 Fixed parser error for 'for ((;;)) ; do' 2013-10-11 20:03:55 -07:00
Vidar Holen
157fea73da Suggest ./* instead of * for command arguments 2013-10-06 15:54:31 -07:00
Vidar Holen
b439f02b8e Improved assignment parsing: track indices and += vs = 2013-10-06 14:44:43 -07:00
Vidar Holen
710a28c572 Revert "Fixed parsing for 'eval var=(values)'", because it fails for 'eval $x=foo'
This reverts commit 34e69556b1.
2013-09-29 21:35:20 -07:00
Vidar Holen
702d57b655 Warn about unicode quotes 2013-09-29 21:22:42 -07:00
Vidar Holen
34e69556b1 Fixed parsing for 'eval var=(values)' 2013-09-29 21:00:29 -07:00
Vidar Holen
7c411b39ac Fixed warnings for read -p "Name: " 2013-09-29 20:55:26 -07:00
Vidar Holen
5a959bc340 Fix parser errors for unclosed $( in here docs 2013-09-21 16:27:17 -07:00
Vidar Holen
fb5f72951d Don't warn about unused variables for read '' 2013-09-12 19:11:42 -07:00
Vidar Holen
7630136d6c Move command and variable lists to ShellCheck.Data. 2013-09-12 18:50:33 -07:00
Vidar Holen
dacb8c597f Fixed a series of extglob parsing oddities and edge cases 2013-09-04 13:02:30 -07:00
Vidar Holen
d99aaaf8dc Merge branch 'master' of github.com:koalaman/shellcheck 2013-09-03 14:09:50 -07:00
Vidar Holen
876831b419 Fixed up readme 2013-09-03 14:08:30 -07:00
Vidar Holen
24580609b8 Merge branch 'master' of https://github.com/carenas/shellcheck into carenas-master 2013-09-03 14:06:38 -07:00
koalaman
5828abe324 Merge pull request #7 from carenas/master
Include jsoncheck in 'make clean' target and update required ubuntu package list.
2013-09-03 14:04:49 -07:00
Carlo Marcelo Arenas Belon
c229d3929a build: update recommended Ubuntu package list
last still supported version to use ghc6 was lucid, so it is
better to refer instead to ghc 7 as used since precise
2013-09-01 21:46:32 -07:00
Carlo Marcelo Arenas Belon
31907ca51d build: include all binaries for clean 2013-09-01 21:37:30 -07:00
Vidar Holen
58b8e0ab70 Suggest pgrep when grepping ps 2013-08-31 18:32:07 -07:00
Vidar Holen
9586a46c9c Warn about assigned but unreferenced variables 2013-08-31 18:26:20 -07:00
Vidar Holen
bb49cf8e65 Parse the contents of unquoted here documents 2013-08-31 17:03:15 -07:00
Vidar Holen
de1fa61560 Warn about client side expansion in ssh strings/heredocs. 2013-08-03 21:19:32 -07:00
Vidar Holen
07b1fd6f44 Allow :+- in function names. :(){ :|:;};:, anyone? 2013-08-03 20:22:32 -07:00
Vidar Holen
d0caa1e1df Don't warn for 'find .. | xargs -0' or 'ls -N | ..' 2013-07-25 19:58:53 -07:00
8 changed files with 394 additions and 102 deletions

View File

@@ -18,7 +18,6 @@ jsoncheck: regardless
./test/runQuack && touch .tests ./test/runQuack && touch .tests
clean: clean:
rm -f .tests shellcheck *.hi *.o ShellCheck/*.hi ShellCheck/*.o rm -f .tests shellcheck jsoncheck *.hi *.o ShellCheck/*.hi ShellCheck/*.o
regardless: regardless:

8
README
View File

@@ -19,8 +19,16 @@ ShellCheck is written in Haskell, and requires GHC, Parsec3 and Text.Regex.
To build the JSON interface and run the unit tests, it also requires QuickCheck2 and JSON. To build the JSON interface and run the unit tests, it also requires QuickCheck2 and JSON.
On Ubuntu and similar, these are called: On Ubuntu and similar, these are called:
ghc libghc-parsec3-dev libghc-json-dev libghc-regex-compat-dev libghc-quickcheck2-dev
For older releases, you may have to use:
ghc6 libghc6-parsec3-dev libghc6-quickcheck2-dev libghc6-json-dev libghc-regex-compat-dev ghc6 libghc6-parsec3-dev libghc6-quickcheck2-dev libghc6-json-dev libghc-regex-compat-dev
Executables can be built with cabal. Tests currently still rely on a Makefile. Executables can be built with cabal. Tests currently still rely on a Makefile.
Install:
cabal install
which shellcheck
~/.cabal/bin/shellcheck
Happy ShellChecking! Happy ShellChecking!

View File

@@ -1,5 +1,5 @@
Name: ShellCheck Name: ShellCheck
Version: 0.1.0 Version: 0.2.0
Description: Shell script analysis tool Description: Shell script analysis tool
License-file: LICENSE License-file: LICENSE
Author: Vidar Holen Author: Vidar Holen
@@ -10,7 +10,7 @@ Cabal-Version: >= 1.2
library library
build-depends: base >= 4, parsec, containers, regex-compat, mtl, directory build-depends: base >= 4, parsec, containers, regex-compat, mtl, directory
exposed-modules: ShellCheck.AST, ShellCheck.Parser, ShellCheck.Analytics, ShellCheck.Simple exposed-modules: ShellCheck.AST, ShellCheck.Data, ShellCheck.Parser, ShellCheck.Analytics, ShellCheck.Simple
executable shellcheck executable shellcheck
main-is: shellcheck.hs main-is: shellcheck.hs

View File

@@ -23,6 +23,10 @@ import qualified Text.Regex as Re
data Id = Id Int deriving (Show, Eq, Ord) data Id = Id Int deriving (Show, Eq, Ord)
data Quoted = Quoted | Unquoted deriving (Show, Eq)
data Dashed = Dashed | Undashed deriving (Show, Eq)
data AssignmentMode = Assign | Append deriving (Show, Eq)
data Token = data Token =
TA_Base Id String Token TA_Base Id String Token
| TA_Binary Id String Token Token | TA_Binary Id String Token Token
@@ -42,7 +46,7 @@ data Token =
| T_AndIf Id (Token) (Token) | T_AndIf Id (Token) (Token)
| T_Arithmetic Id Token | T_Arithmetic Id Token
| T_Array Id [Token] | T_Array Id [Token]
| T_Assignment Id String Token | T_Assignment Id AssignmentMode String (Maybe Token) Token
| T_Backgrounded Id Token | T_Backgrounded Id Token
| T_Backticked Id [Token] | T_Backticked Id [Token]
| T_Bang Id | T_Bang Id
@@ -80,7 +84,7 @@ data Token =
| T_GREATAND Id | T_GREATAND Id
| T_Glob Id String | T_Glob Id String
| T_Greater Id | T_Greater Id
| T_HereDoc Id Bool Bool String | T_HereDoc Id Dashed Quoted String [Token]
| T_HereString Id Token | T_HereString Id Token
| T_If Id | T_If Id
| T_IfExpression Id [([Token],[Token])] [Token] | T_IfExpression Id [([Token],[Token])] [Token]
@@ -134,6 +138,11 @@ analyze f g i t =
return . i $ newT return . i $ newT
roundAll = mapM round roundAll = mapM round
roundMaybe Nothing = return Nothing
roundMaybe (Just v) = do
s <- round v
return (Just s)
dl l v = do dl l v = do
x <- roundAll l x <- roundAll l
return $ v x return $ v x
@@ -159,7 +168,10 @@ analyze f g i t =
delve (T_IoFile id op file) = d2 op file $ T_IoFile id delve (T_IoFile id op file) = d2 op file $ T_IoFile id
delve (T_HereString id word) = d1 word $ T_HereString id delve (T_HereString id word) = d1 word $ T_HereString id
delve (T_FdRedirect id v t) = d1 t $ T_FdRedirect id v delve (T_FdRedirect id v t) = d1 t $ T_FdRedirect id v
delve (T_Assignment id v t) = d1 t $ T_Assignment id v delve (T_Assignment id mode var index value) = do
a <- roundMaybe index
b <- round value
return $ T_Assignment id mode var a b
delve (T_Array id t) = dl t $ T_Array id delve (T_Array id t) = dl t $ T_Array id
delve (T_Redirecting id redirs cmd) = do delve (T_Redirecting id redirs cmd) = do
a <- roundAll redirs a <- roundAll redirs
@@ -208,6 +220,7 @@ analyze f g i t =
delve (T_Condition id typ token) = d1 token $ T_Condition id typ delve (T_Condition id typ token) = d1 token $ T_Condition id typ
delve (T_Extglob id str l) = dl l $ T_Extglob id str delve (T_Extglob id str l) = dl l $ T_Extglob id str
delve (T_DollarBraced id op) = d1 op $ T_DollarBraced id delve (T_DollarBraced id op) = d1 op $ T_DollarBraced id
delve (T_HereDoc id d q str l) = dl l $ T_HereDoc id d q str
delve (TC_And id typ str t1 t2) = d2 t1 t2 $ TC_And id typ str delve (TC_And id typ str t1 t2) = d2 t1 t2 $ TC_And id typ str
delve (TC_Or id typ str t1 t2) = d2 t1 t2 $ TC_Or id typ str delve (TC_Or id typ str t1 t2) = d2 t1 t2 $ TC_Or id typ str
@@ -272,10 +285,10 @@ getId t = case t of
T_DollarArithmetic id _ -> id T_DollarArithmetic id _ -> id
T_BraceExpansion id _ -> id T_BraceExpansion id _ -> id
T_IoFile id _ _ -> id T_IoFile id _ _ -> id
T_HereDoc id _ _ _ -> id T_HereDoc id _ _ _ _ -> id
T_HereString id _ -> id T_HereString id _ -> id
T_FdRedirect id _ _ -> id T_FdRedirect id _ _ -> id
T_Assignment id _ _ -> id T_Assignment id _ _ _ _ -> id
T_Array id _ -> id T_Array id _ -> id
T_Redirecting id _ _ -> id T_Redirecting id _ _ -> id
T_SimpleCommand id _ _ -> id T_SimpleCommand id _ _ -> id

View File

@@ -18,6 +18,7 @@
module ShellCheck.Analytics where module ShellCheck.Analytics where
import ShellCheck.AST import ShellCheck.AST
import ShellCheck.Data
import ShellCheck.Parser import ShellCheck.Parser
import Control.Monad import Control.Monad
import Control.Monad.State import Control.Monad.State
@@ -39,6 +40,7 @@ genericChecks = [
,checkQuotesInLiterals ,checkQuotesInLiterals
,checkShebang ,checkShebang
,checkFunctionsUsedExternally ,checkFunctionsUsedExternally
,checkUnusedAssignments
] ]
checksFor Sh = map runBasicAnalysis [ checksFor Sh = map runBasicAnalysis [
@@ -129,12 +131,16 @@ basicChecks = [
,checkSpuriousExpansion ,checkSpuriousExpansion
,checkUnusedEchoEscapes ,checkUnusedEchoEscapes
,checkDollarBrackets ,checkDollarBrackets
,checkSshHereDoc
,checkSshCommandString
,checkGlobsAsOptions
] ]
treeChecks = [ treeChecks = [
checkUnquotedExpansions checkUnquotedExpansions
,checkSingleQuotedVariables ,checkSingleQuotedVariables
] ]
runBasicTreeAnalysis checks token = runBasicTreeAnalysis checks token =
checkList (map runTree checks) token checkList (map runTree checks) token
where where
@@ -147,7 +153,14 @@ err id note = addNoteFor id $ Note ErrorC $ note
info id note = addNoteFor id $ Note InfoC $ note info id note = addNoteFor id $ Note InfoC $ note
style id note = addNoteFor id $ Note StyleC $ note style id note = addNoteFor id $ Note StyleC $ note
isVariableChar x = x == '_' || x >= 'a' && x <= 'z' || x >= 'A' && x <= 'Z' || x >= '0' && x <= '9' isVariableStartChar x = x == '_' || x >= 'a' && x <= 'z' || x >= 'A' && x <= 'Z'
isVariableChar x = isVariableStartChar x || x >= '0' && x <= '9'
prop_isVariableName1 = isVariableName "_fo123"
prop_isVariableName2 = not $ isVariableName "4"
prop_isVariableName3 = not $ isVariableName "test: "
isVariableName (x:r) = isVariableStartChar x && all isVariableChar r
isVariableName _ = False
willSplit x = willSplit x =
case x of case x of
@@ -177,6 +190,9 @@ isPotentiallyConfusedGlobRegex =
matches string regex = isJust $ matchRegex regex string matches string regex = isJust $ matchRegex regex string
headOrDefault _ (a:_) = a
headOrDefault def _ = def
isConstant token = isConstant token =
case token of case token of
T_NormalWord _ l -> all isConstant l T_NormalWord _ l -> all isConstant l
@@ -270,7 +286,7 @@ prop_checkAssignAteCommand2 = verify checkAssignAteCommand "A=ls --sort=$foo"
prop_checkAssignAteCommand3 = verify checkAssignAteCommand "A=cat foo | grep bar" prop_checkAssignAteCommand3 = verify checkAssignAteCommand "A=cat foo | grep bar"
prop_checkAssignAteCommand4 = verifyNot checkAssignAteCommand "A=foo ls -l" prop_checkAssignAteCommand4 = verifyNot checkAssignAteCommand "A=foo ls -l"
prop_checkAssignAteCommand5 = verifyNot checkAssignAteCommand "PAGER=cat grep bar" prop_checkAssignAteCommand5 = verifyNot checkAssignAteCommand "PAGER=cat grep bar"
checkAssignAteCommand (T_SimpleCommand id ((T_Assignment _ _ assignmentTerm):[]) (firstWord:_)) = checkAssignAteCommand (T_SimpleCommand id ((T_Assignment _ _ _ _ assignmentTerm):[]) (firstWord:_)) =
when ("-" `isPrefixOf` (concat $ deadSimple firstWord) || when ("-" `isPrefixOf` (concat $ deadSimple firstWord) ||
(isCommonCommand (getLiteralString assignmentTerm) && not (isCommonCommand (getLiteralString firstWord)))) $ (isCommonCommand (getLiteralString assignmentTerm) && not (isCommonCommand (getLiteralString firstWord)))) $
warn id "To assign the output of a command, use var=$(cmd) ." warn id "To assign the output of a command, use var=$(cmd) ."
@@ -304,21 +320,43 @@ checkNeedlessCommands (T_SimpleCommand id _ (w:_)) | w `isCommand` "basename" =
style id "Use parameter expansion instead, such as ${var##*/}." style id "Use parameter expansion instead, such as ${var##*/}."
checkNeedlessCommands _ = return () checkNeedlessCommands _ = return ()
prop_checkPipePitfalls1 = verify checkPipePitfalls "foo | grep foo | awk bar"
prop_checkPipePitfalls2 = verifyNot checkPipePitfalls "foo | awk bar | grep foo"
prop_checkPipePitfalls3 = verify checkPipePitfalls "ls | grep -v mp3" prop_checkPipePitfalls3 = verify checkPipePitfalls "ls | grep -v mp3"
prop_checkPipePitfalls4 = verifyNot checkPipePitfalls "find . -print0 | xargs -0 foo"
prop_checkPipePitfalls5 = verifyNot checkPipePitfalls "ls -N | foo"
prop_checkPipePitfalls6 = verify checkPipePitfalls "find . | xargs foo"
checkPipePitfalls (T_Pipeline id commands) = do checkPipePitfalls (T_Pipeline id commands) = do
for [["grep"], ["sed"]] $ \id -> style id "You don't need grep | sed, sed can filter lines by itself." for ["find", "xargs"] $
for [["grep"], ["awk"]] $ \id -> style id "You don't need grep | awk, awk can filter lines by itself." \(find:xargs:_) -> let args = deadSimple xargs in
for [["ls"], ["?"]] $ \id -> warn id "Don't parse ls output; it mangles filenames." when (not $ hasShortParameter args '0') $
for [["ls"], ["grep"]] $ \id -> warn id "Don't use ls | grep. Use a glob or a for loop with a condition." warn (getId find) "Use either 'find .. -print0 | xargs -0 ..' or 'find .. -exec .. +' to allow for non-alphanumeric filenames."
for [["ls"], ["xargs"]] $ \id -> warn id "Don't use ls | xargs. Use find -exec .. +"
for [["find"], ["xargs"]]$ \id -> warn id "Don't use find | xargs cmd. find -exec cmd {} + handles whitespace." for ["?", "echo"] $
for [["?"], ["echo"]] $ \id -> info id "echo doesn't read from stdin, are you sure you should be piping to it?" \(_:echo:_) -> info (getId echo) "echo doesn't read from stdin, are you sure you should be piping to it?"
for' ["ps", "grep"] $
flip info "Consider using pgrep instead of grepping ps output."
didLs <- liftM or . sequence $ [
for' ["ls", "grep"] $
flip warn "Don't use ls | grep. Use a glob or a for loop with a condition to allow non-alphanumeric filenames.",
for' ["ls", "xargs"] $
flip warn "Use 'find .. -print0 | xargs -0 ..' or 'find .. -exec .. +' to allow non-alphanumeric filenames."
]
when (not didLs) $ do
for ["ls", "?"] $
\(ls:_) -> (when (not $ hasShortParameter (deadSimple ls) 'N') $
info (getId ls) "Use find instead of ls to better handle non-alphanumeric filenames.")
return ()
where where
for l f = for l f =
let indices = indexOfSublists l (map (take 1 . deadSimple) commands) let indices = indexOfSublists l (map (headOrDefault "" . deadSimple) commands)
in mapM_ f (map (\n -> getId $ commands !! n) indices) in do
mapM_ f (map (\n -> take (length l) $ drop n $ commands) indices)
return . not . null $ indices
for' l f = for l (first f)
first func (x:_) = func (getId x)
first _ _ = return ()
hasShortParameter list char = any (\x -> "-" `isPrefixOf` x && char `elem` x) list
checkPipePitfalls _ = return () checkPipePitfalls _ = return ()
indexOfSublists sub all = f 0 all indexOfSublists sub all = f 0 all
@@ -326,12 +364,12 @@ indexOfSublists sub all = f 0 all
f _ [] = [] f _ [] = []
f n a@(r:rest) = f n a@(r:rest) =
let others = f (n+1) rest in let others = f (n+1) rest in
if match sub (take (length sub) a) if match sub a
then n:others then n:others
else others else others
match [] [] = True match ("?":r1) (_:r2) = match r1 r2
match (["?"]:r1) (_:r2) = match r1 r2
match (x1:r1) (x2:r2) | x1 == x2 = match r1 r2 match (x1:r1) (x2:r2) | x1 == x2 = match r1 r2
match [] _ = True
match _ _ = False match _ _ = False
@@ -525,6 +563,7 @@ prop_checkUnquotedExpansions3a= verifyTree checkUnquotedExpansions "[ ! $(foo) ]
prop_checkUnquotedExpansions4 = verifyNotTree checkUnquotedExpansions "[[ $(foo) == cow ]]" prop_checkUnquotedExpansions4 = verifyNotTree checkUnquotedExpansions "[[ $(foo) == cow ]]"
prop_checkUnquotedExpansions5 = verifyNotTree checkUnquotedExpansions "for f in $(cmd); do echo $f; done" prop_checkUnquotedExpansions5 = verifyNotTree checkUnquotedExpansions "for f in $(cmd); do echo $f; done"
prop_checkUnquotedExpansions6 = verifyNotTree checkUnquotedExpansions "$(cmd)" prop_checkUnquotedExpansions6 = verifyNotTree checkUnquotedExpansions "$(cmd)"
prop_checkUnquotedExpansions7 = verifyNotTree checkUnquotedExpansions "cat << foo\n$(ls)\nfoo"
checkUnquotedExpansions t tree = checkUnquotedExpansions t tree =
check t check t
where where
@@ -842,10 +881,12 @@ inUnquotableContext tree t =
TA_Binary _ _ _ _ -> True TA_Binary _ _ _ _ -> True
TA_Trinary _ _ _ _ -> True TA_Trinary _ _ _ _ -> True
TA_Expansion _ _ -> True TA_Expansion _ _ -> True
T_Assignment _ _ _ -> True T_Assignment _ _ _ _ _ -> True
T_Redirecting _ _ _ -> or $ map (isCommand t) ["local", "declare"] T_Redirecting _ _ _ ->
any (isCommand t) ["local", "declare", "typeset", "export"]
T_DoubleQuoted _ _ -> True T_DoubleQuoted _ _ -> True
T_CaseExpression _ _ _ -> True T_CaseExpression _ _ _ -> True
T_HereDoc _ _ _ _ _ -> True
T_ForIn _ _ _ _ -> True -- Pragmatically assume it's desirable here T_ForIn _ _ _ _ -> True -- Pragmatically assume it's desirable here
x -> case Map.lookup (getId x) tree of x -> case Map.lookup (getId x) tree of
Nothing -> False Nothing -> False
@@ -1098,7 +1139,7 @@ prop_checkPS15 = verifyNot checkPS1Assignments "PS1='\\[\\033[1;35m\\]\\$ '"
prop_checkPS16 = verifyNot checkPS1Assignments "PS1='\\[\\e1m\\e[1m\\]\\$ '" prop_checkPS16 = verifyNot checkPS1Assignments "PS1='\\[\\e1m\\e[1m\\]\\$ '"
prop_checkPS17 = verifyNot checkPS1Assignments "PS1='e033x1B'" prop_checkPS17 = verifyNot checkPS1Assignments "PS1='e033x1B'"
prop_checkPS18 = verifyNot checkPS1Assignments "PS1='\\[\\e\\]'" prop_checkPS18 = verifyNot checkPS1Assignments "PS1='\\[\\e\\]'"
checkPS1Assignments (T_Assignment _ "PS1" word) = warnFor word checkPS1Assignments (T_Assignment _ _ "PS1" _ word) = warnFor word
where where
warnFor word = warnFor word =
let contents = concat $ deadSimple word in let contents = concat $ deadSimple word in
@@ -1265,6 +1306,38 @@ checkDollarBrackets (T_DollarBracket id _) =
style id "Use $((..)) instead of deprecated $[..]" style id "Use $((..)) instead of deprecated $[..]"
checkDollarBrackets _ = return () checkDollarBrackets _ = return ()
prop_checkSshHereDoc1 = verify checkSshHereDoc "ssh host << foo\necho $PATH\nfoo"
prop_checkSshHereDoc2 = verifyNot checkSshHereDoc "ssh host << 'foo'\necho $PATH\nfoo"
checkSshHereDoc (T_Redirecting _ redirs cmd)
| cmd `isCommand` "ssh" =
mapM_ checkHereDoc redirs
where
hasVariables = mkRegex "[`$]"
checkHereDoc (T_FdRedirect _ _ (T_HereDoc id _ Unquoted token tokens))
| not (all isConstant tokens) =
warn id $ "Quote '" ++ token ++ "' to make here document expansions happen on the server side rather than on the client."
checkHereDoc _ = return ()
checkSshHereDoc _ = return ()
-- This is hard to get right without properly parsing ssh args
prop_checkSshCmdStr1 = verify checkSshCommandString "ssh host \"echo $PS1\""
prop_checkSshCmdStr2 = verifyNot checkSshCommandString "ssh host \"ls foo\""
prop_checkSshCmdStr3 = verifyNot checkSshCommandString "ssh \"$host\""
checkSshCommandString = checkCommand "ssh" f
where
nonOptions args =
filter (\x -> not $ "-" `isPrefixOf` (concat $ deadSimple x)) args
f args =
case nonOptions args of
(hostport:r@(_:_)) -> checkArg $ last r
_ -> return ()
checkArg (T_NormalWord _ [T_DoubleQuoted id parts]) =
case filter (not . isConstant) parts of
[] -> return ()
(x:_) -> info (getId x) $
"Note that, unescaped, this expands on the client side."
checkArg _ = return ()
--- Subshell detection --- Subshell detection
prop_subshellAssignmentCheck = verifyFull subshellAssignmentCheck "cat foo | while read bar; do a=$bar; done; echo \"$a\"" prop_subshellAssignmentCheck = verifyFull subshellAssignmentCheck "cat foo | while read bar; do a=$bar; done; echo \"$a\""
@@ -1314,7 +1387,7 @@ getModifiedVariables t =
case t of case t of
T_SimpleCommand _ vars [] -> T_SimpleCommand _ vars [] ->
concatMap (\x -> case x of concatMap (\x -> case x of
T_Assignment id name w -> T_Assignment id _ name _ w ->
[(x, x, name, DataFrom [w])] [(x, x, name, DataFrom [w])]
_ -> [] _ -> []
) vars ) vars
@@ -1333,14 +1406,28 @@ getModifiedVariables t =
T_SelectIn id str words _ -> [(t, t, str, DataFrom words)] T_SelectIn id str words _ -> [(t, t, str, DataFrom words)]
_ -> [] _ -> []
getModifiedVariableCommand base@(T_SimpleCommand _ _ ((T_NormalWord _ ((T_Literal _ x):_)):rest)) = -- Consider 'export' a reference, since it makes the var available
getReferencedVariableCommand base@(T_SimpleCommand _ _ ((T_NormalWord _ ((T_Literal _ x):_)):rest)) =
case x of case x of
"read" -> concatMap getLiteral rest "export" -> concatMap getReference rest
_ -> [(base,base, x)]
where
getReference t@(T_Assignment _ _ name _ value) = [(t, t, name)]
getReference t@(T_NormalWord _ [T_Literal _ name]) | not ("-" `isPrefixOf` name) = [(t, t, name)]
getReference _ = []
getReferencedVariableCommand _ = []
getModifiedVariableCommand base@(T_SimpleCommand _ _ ((T_NormalWord _ ((T_Literal _ x):_)):rest)) =
filter (\(_,_,s,_) -> not ("-" `isPrefixOf` s)) $
case x of
"read" -> concatMap getLiteral rest
"let" -> concatMap letParamToLiteral rest "let" -> concatMap letParamToLiteral rest
"export" -> concatMap getModifierParam rest "export" -> concatMap getModifierParam rest
"declare" -> concatMap getModifierParam rest "declare" -> concatMap getModifierParam rest
"typeset" -> concatMap getModifierParam rest "typeset" -> concatMap getModifierParam rest
"local" -> concatMap getModifierParam rest
_ -> [] _ -> []
where where
@@ -1354,11 +1441,13 @@ getModifiedVariableCommand base@(T_SimpleCommand _ _ ((T_NormalWord _ ((T_Litera
getLiteral t@(T_NormalWord _ [T_Literal _ s]) = getLiteral t@(T_NormalWord _ [T_Literal _ s]) =
[(base, t, s, DataExternal)] [(base, t, s, DataExternal)]
getLiteral t@(T_NormalWord _ [T_SingleQuoted _ s]) =
[(base, t, s, DataExternal)]
getLiteral t@(T_NormalWord _ [T_DoubleQuoted _ [T_Literal id s]]) = getLiteral t@(T_NormalWord _ [T_DoubleQuoted _ [T_Literal id s]]) =
[(base, t, s, DataExternal)] [(base, t, s, DataExternal)]
getLiteral x = [] getLiteral x = []
getModifierParam t@(T_Assignment _ name value) = getModifierParam t@(T_Assignment _ _ name _ value) =
[(base, t, name, DataFrom [value])] [(base, t, name, DataFrom [value])]
getModifierParam _ = [] getModifierParam _ = []
@@ -1376,7 +1465,8 @@ getReferencedVariables t =
case t of case t of
T_DollarBraced id l -> map (\x -> (t, t, x)) $ [getBracedReference $ bracedString l] T_DollarBraced id l -> map (\x -> (t, t, x)) $ [getBracedReference $ bracedString l]
TA_Variable id str -> [(t, t, str)] TA_Variable id str -> [(t, t, str)]
x -> [] T_Assignment id Append str _ _ -> [(t, t, str)]
x -> getReferencedVariableCommand x
getVariableFlow t = getVariableFlow t =
let (_, stack) = runState (doStackAnalysis startScope endScope t) [] let (_, stack) = runState (doStackAnalysis startScope endScope t) []
@@ -1593,3 +1683,53 @@ checkFunctionsUsedExternally t =
info id $ info id $
"Use own script or sh -c '..' to run this from " ++ cmd ++ "." "Use own script or sh -c '..' to run this from " ++ cmd ++ "."
prop_checkUnused0 = verifyNotFull checkUnusedAssignments "var=foo; echo $var"
prop_checkUnused1 = verifyFull checkUnusedAssignments "var=foo; echo $bar"
prop_checkUnused2 = verifyNotFull checkUnusedAssignments "var=foo; export var;"
prop_checkUnused3 = verifyFull checkUnusedAssignments "for f in *; do echo '$f'; done"
prop_checkUnused4 = verifyFull checkUnusedAssignments "local i=0"
prop_checkUnused5 = verifyNotFull checkUnusedAssignments "read lol; echo $lol"
prop_checkUnused6 = verifyNotFull checkUnusedAssignments "var=4; (( var++ ))"
prop_checkUnused7 = verifyNotFull checkUnusedAssignments "var=2; $((var))"
prop_checkUnused8 = verifyFull checkUnusedAssignments "var=2; var=3;"
prop_checkUnused9 = verifyNotFull checkUnusedAssignments "read ''"
prop_checkUnused10= verifyNotFull checkUnusedAssignments "read -p 'test: '"
prop_checkUnused11= verifyNotFull checkUnusedAssignments "bar=5; export foo[$bar]=3"
checkUnusedAssignments t = snd $ runState (mapM_ checkAssignment flow) []
where
flow = getVariableFlow t
references = foldl (flip ($)) defaultMap (map insertRef flow)
insertRef (Reference (base, token, name)) =
Map.insert name ()
insertRef _ = id
checkAssignment (Assignment (_, token, name, _)) | isVariableName name =
case Map.lookup name references of
Just _ -> return ()
Nothing -> do
info (getId token) $
name ++ " appears unused. Verify it or export it."
checkAssignment _ = return ()
defaultMap = Map.fromList $ zip internalVariables $ repeat ()
prop_checkGlobsAsOptions1 = verify checkGlobsAsOptions "rm *.txt"
prop_checkGlobsAsOptions2 = verify checkGlobsAsOptions "ls ??.*"
prop_checkGlobsAsOptions3 = verifyNot checkGlobsAsOptions "rm -- *.txt"
checkGlobsAsOptions (T_SimpleCommand _ _ args) =
mapM_ check $ takeWhile (not . isEndOfArgs) args
where
check v@(T_NormalWord _ ((T_Glob id s):_)) | s == "*" || s == "?" =
info id $
"Use ./" ++ (concat $ deadSimple v)
++ " so names with dashes won't become options."
check _ = return ()
isEndOfArgs t =
case concat $ deadSimple t of
"--" -> True
":::" -> True
"::::" -> True
_ -> False
checkGlobsAsOptions _ = return ()

67
ShellCheck/Data.hs Normal file
View File

@@ -0,0 +1,67 @@
module ShellCheck.Data where
internalVariables = [
-- Generic
"", "_",
-- Bash
"BASH", "BASHOPTS", "BASHPID", "BASH_ALIASES", "BASH_ARGC",
"BASH_ARGV", "BASH_CMDS", "BASH_COMMAND", "BASH_EXECUTION_STRING",
"BASH_LINENO", "BASH_REMATCH", "BASH_SOURCE", "BASH_SUBSHELL",
"BASH_VERSINFO", "BASH_VERSION", "COMP_CWORD", "COMP_KEY",
"COMP_LINE", "COMP_POINT", "COMP_TYPE", "COMP_WORDBREAKS",
"COMP_WORDS", "COPROC", "DIRSTACK", "EUID", "FUNCNAME", "GROUPS",
"HISTCMD", "HOSTNAME", "HOSTTYPE", "LINENO", "MACHTYPE", "MAPFILE",
"OLDPWD", "OPTARG", "OPTIND", "OSTYPE", "PIPESTATUS", "PPID", "PWD",
"RANDOM", "READLINE_LINE", "READLINE_POINT", "REPLY", "SECONDS",
"SHELLOPTS", "SHLVL", "UID", "BASH_ENV", "BASH_XTRACEFD", "CDPATH",
"COLUMNS", "COMPREPLY", "EMACS", "ENV", "FCEDIT", "FIGNORE",
"FUNCNEST", "GLOBIGNORE", "HISTCONTROL", "HISTFILE", "HISTFILESIZE",
"HISTIGNORE", "HISTSIZE", "HISTTIMEFORMAT", "HOME", "HOSTFILE", "IFS",
"IGNOREEOF", "INPUTRC", "LANG", "LC_ALL", "LC_COLLATE", "LC_CTYPE",
"LC_MESSAGES", "LC_NUMERIC", "LINES", "MAIL", "MAILCHECK", "MAILPATH",
"OPTERR", "PATH", "POSIXLY_CORRECT", "PROMPT_COMMAND",
"PROMPT_DIRTRIM", "PS1", "PS2", "PS3", "PS4", "SHELL", "TIMEFORMAT",
"TMOUT", "TMPDIR", "auto_resume", "histchars",
-- Zsh
"ARGV0", "BAUD", "cdpath", "COLUMNS", "CORRECT_IGNORE",
"DIRSTACKSIZE", "ENV", "FCEDIT", "fignore", "fpath", "histchars",
"HISTCHARS", "HISTFILE", "HISTSIZE", "HOME", "IFS", "KEYBOARD_HACK",
"KEYTIMEOUT", "LANG", "LC_ALL", "LC_COLLATE", "LC_CTYPE",
"LC_MESSAGES", "LC_NUMERIC", "LC_TIME", "LINES", "LISTMAX",
"LOGCHECK", "MAIL", "MAILCHECK", "mailpath", "manpath", "module_path",
"NULLCMD", "path", "POSTEDIT", "PROMPT", "PROMPT2", "PROMPT3",
"PROMPT4", "prompt", "PROMPT_EOL_MARK", "PS1", "PS2", "PS3", "PS4",
"psvar", "READNULLCMD", "REPORTTIME", "REPLY", "reply", "RPROMPT",
"RPS1", "RPROMPT2", "RPS2", "SAVEHIST", "SPROMPT", "STTY", "TERM",
"TERMINFO", "TIMEFMT", "TMOUT", "TMPPREFIX", "watch", "WATCHFMT",
"WORDCHARS", "ZBEEP", "ZDOTDIR", "ZLE_LINE_ABORTED",
"ZLE_REMOVE_SUFFIX_CHARS", "ZLE_SPACE_SUFFIX_CHARS"
]
commonCommands = [
"admin", "alias", "ar", "asa", "at", "awk", "basename", "batch",
"bc", "bg", "break", "c99", "cal", "cat", "cd", "cflow", "chgrp",
"chmod", "chown", "cksum", "cmp", "colon", "comm", "command",
"compress", "continue", "cp", "crontab", "csplit", "ctags", "cut",
"cxref", "date", "dd", "delta", "df", "diff", "dirname", "dot",
"du", "echo", "ed", "env", "eval", "ex", "exec", "exit", "expand",
"export", "expr", "fc", "fg", "file", "find", "fold", "fort77",
"fuser", "gencat", "get", "getconf", "getopts", "grep", "hash",
"head", "iconv", "ipcrm", "ipcs", "jobs", "join", "kill", "lex",
"link", "ln", "locale", "localedef", "logger", "logname", "lp",
"ls", "m4", "mailx", "make", "man", "mesg", "mkdir", "mkfifo",
"more", "mv", "newgrp", "nice", "nl", "nm", "nohup", "od", "paste",
"patch", "pathchk", "pax", "pr", "printf", "prs", "ps", "pwd",
"qalter", "qdel", "qhold", "qmove", "qmsg", "qrerun", "qrls",
"qselect", "qsig", "qstat", "qsub", "read", "readonly", "renice",
"return", "rm", "rmdel", "rmdir", "sact", "sccs", "sed", "set",
"sh", "shift", "sleep", "sort", "split", "strings", "strip", "stty",
"tabs", "tail", "talk", "tee", "test", "time", "times", "touch",
"tput", "tr", "trap", "tsort", "tty", "type", "ulimit", "umask",
"unalias", "uname", "uncompress", "unexpand", "unget", "uniq",
"unlink", "unset", "uucp", "uudecode", "uuencode", "uustat", "uux",
"val", "vi", "wait", "wc", "what", "who", "write", "xargs", "yacc",
"zcat"
]

View File

@@ -17,9 +17,10 @@
-} -}
{-# LANGUAGE NoMonomorphismRestriction #-} {-# LANGUAGE NoMonomorphismRestriction #-}
module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), notesFromMap, Metadata(..), sortNotes, commonCommands) where module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), notesFromMap, Metadata(..), sortNotes) where
import ShellCheck.AST import ShellCheck.AST
import ShellCheck.Data
import Text.Parsec import Text.Parsec
import Debug.Trace import Debug.Trace
import Control.Monad import Control.Monad
@@ -37,15 +38,16 @@ import GHC.Exts (sortWith)
backslash = char '\\' backslash = char '\\'
linefeed = (optional carriageReturn) >> char '\n' linefeed = (optional carriageReturn) >> char '\n'
singleQuote = char '\'' singleQuote = char '\'' <|> unicodeSingleQuote
doubleQuote = char '"' doubleQuote = char '"' <|> unicodeDoubleQuote
variableStart = upper <|> lower <|> oneOf "_" variableStart = upper <|> lower <|> oneOf "_"
variableChars = upper <|> lower <|> digit <|> oneOf "_" variableChars = upper <|> lower <|> digit <|> oneOf "_"
functionChars = variableChars <|> oneOf ":+-"
specialVariable = oneOf "@*#?-$!" specialVariable = oneOf "@*#?-$!"
tokenDelimiter = oneOf "&|;<> \t\n\r" <|> nbsp tokenDelimiter = oneOf "&|;<> \t\n\r" <|> nbsp
quotable = oneOf "|&;<>()$`\\ \"'\t\n\r" <|> nbsp quotable = oneOf "|&;<>()$`\\ \"'\t\n\r" <|> nbsp <|> unicodeDoubleQuote
bracedQuotable = oneOf "}\"$`'" bracedQuotable = oneOf "}\"$`'"
doubleQuotable = oneOf "\"$`" doubleQuotable = oneOf "\"$`" <|> unicodeDoubleQuote
whitespace = oneOf " \t\n" <|> carriageReturn <|> nbsp whitespace = oneOf " \t\n" <|> carriageReturn <|> nbsp
linewhitespace = oneOf " \t" <|> nbsp linewhitespace = oneOf " \t" <|> nbsp
extglobStart = oneOf "?*@!+" extglobStart = oneOf "?*@!+"
@@ -72,6 +74,18 @@ allspacingOrFail = do
s <- allspacing s <- allspacing
when (null s) $ fail "Expected spaces" when (null s) $ fail "Expected spaces"
unicodeDoubleQuote = do
pos <- getPosition
char '\x201C' <|> char '\x201D'
parseProblemAt pos WarningC "This is a unicode double quote. Delete and retype it."
return '"'
unicodeSingleQuote = do
pos <- getPosition
char '\x2018' <|> char '\x2019'
parseProblemAt pos WarningC "This is a unicode single quote. Delete and retype it."
return '"'
carriageReturn = do carriageReturn = do
parseNote ErrorC "Literal carriage return. Run script through tr -d '\\r' ." parseNote ErrorC "Literal carriage return. Run script through tr -d '\\r' ."
char '\r' char '\r'
@@ -650,6 +664,7 @@ readProcSub = called "process substitution" $ do
prop_readSingleQuoted = isOk readSingleQuoted "'foo bar'" prop_readSingleQuoted = isOk readSingleQuoted "'foo bar'"
prop_readSingleQuoted2 = isWarning readSingleQuoted "'foo bar\\'" prop_readSingleQuoted2 = isWarning readSingleQuoted "'foo bar\\'"
prop_readsingleQuoted3 = isWarning readSingleQuoted "\x2018hello\x2019"
readSingleQuoted = called "single quoted string" $ do readSingleQuoted = called "single quoted string" $ do
id <- getNextId id <- getNextId
singleQuote singleQuote
@@ -680,27 +695,28 @@ readBackTicked = called "backtick expansion" $ do
subStart <- getPosition subStart <- getPosition
subString <- readGenericLiteral (char '`') subString <- readGenericLiteral (char '`')
char '`' char '`'
-- Result positions may be off due to escapes
result <- subParse subStart readCompoundList (unEscape subString) result <- subParse subStart readCompoundList (unEscape subString)
return $ T_Backticked id result return $ T_Backticked id result
where where
-- Position may be off due to escapes
subParse pos parser input = do
lastPosition <- getPosition
lastInput <- getInput
setPosition pos
setInput input
result <- parser
setInput lastInput
setPosition lastPosition
return result
unEscape [] = [] unEscape [] = []
unEscape ('\\':x:rest) | x `elem` "\"$`\\" = x : unEscape rest unEscape ('\\':x:rest) | x `elem` "\"$`\\" = x : unEscape rest
unEscape ('\\':'\n':rest) = unEscape rest unEscape ('\\':'\n':rest) = unEscape rest
unEscape (c:rest) = c : unEscape rest unEscape (c:rest) = c : unEscape rest
subParse pos parser input = do
lastPosition <- getPosition
lastInput <- getInput
setPosition pos
setInput input
result <- parser
setInput lastInput
setPosition lastPosition
return result
prop_readDoubleQuoted = isOk readDoubleQuoted "\"Hello $FOO\"" prop_readDoubleQuoted = isOk readDoubleQuoted "\"Hello $FOO\""
prop_readDoubleQuoted2 = isOk readDoubleQuoted "\"$'\"" prop_readDoubleQuoted2 = isOk readDoubleQuoted "\"$'\""
prop_readDoubleQuoted3 = isWarning readDoubleQuoted "\x201Chello\x201D"
readDoubleQuoted = called "double quoted string" $ do readDoubleQuoted = called "double quoted string" $ do
id <- getNextId id <- getNextId
doubleQuote doubleQuote
@@ -788,6 +804,9 @@ prop_readExtglob1 = isOk readExtglob "!(*.mp3)"
prop_readExtglob2 = isOk readExtglob "!(*.mp3|*.wmv)" prop_readExtglob2 = isOk readExtglob "!(*.mp3|*.wmv)"
prop_readExtglob4 = isOk readExtglob "+(foo \\) bar)" prop_readExtglob4 = isOk readExtglob "+(foo \\) bar)"
prop_readExtglob5 = isOk readExtglob "+(!(foo *(bar)))" prop_readExtglob5 = isOk readExtglob "+(!(foo *(bar)))"
prop_readExtglob6 = isOk readExtglob "*(((||))|())"
prop_readExtglob7 = isOk readExtglob "*(<>)"
prop_readExtglob8 = isOk readExtglob "@(|*())"
readExtglob = called "extglob" $ do readExtglob = called "extglob" $ do
id <- getNextId id <- getNextId
c <- try $ do c <- try $ do
@@ -800,8 +819,19 @@ readExtglob = called "extglob" $ do
readExtglobPart = do readExtglobPart = do
id <- getNextId id <- getNextId
x <- many1 (readNormalWordPart "" <|> readSpacePart) x <- many (readExtglobGroup <|> readNormalWordPart "" <|> readSpacePart <|> readExtglobLiteral)
return $ T_NormalWord id x return $ T_NormalWord id x
where
readExtglobGroup = do
id <- getNextId
char '('
contents <- readExtglobPart `sepBy` (char '|')
char ')'
return $ T_Extglob id "" contents
readExtglobLiteral = do
id <- getNextId
str <- many1 (oneOf "<>#;&")
return $ T_Literal id str
readSingleEscaped = do readSingleEscaped = do
@@ -962,13 +992,15 @@ readDollarLonely = do
prop_readHereDoc = isOk readHereDoc "<< foo\nlol\ncow\nfoo" prop_readHereDoc = isOk readHereDoc "<< foo\nlol\ncow\nfoo"
prop_readHereDoc2 = isWarning readHereDoc "<<- EOF\n cow\n EOF" prop_readHereDoc2 = isWarning readHereDoc "<<- EOF\n cow\n EOF"
prop_readHereDoc3 = isOk readHereDoc "<< foo\n$\"\nfoo"
prop_readHereDoc4 = isOk readHereDoc "<< foo\n`\nfoo"
readHereDoc = called "here document" $ do readHereDoc = called "here document" $ do
let stripLiteral (T_Literal _ x) = x let stripLiteral (T_Literal _ x) = x
stripLiteral (T_SingleQuoted _ x) = x stripLiteral (T_SingleQuoted _ x) = x
fid <- getNextId fid <- getNextId
pos <- getPosition pos <- getPosition
try $ string "<<" try $ string "<<"
dashed <- (char '-' >> return True) <|> return False dashed <- (char '-' >> return Dashed) <|> return Undashed
tokenPosition <- getPosition tokenPosition <- getPosition
sp <- spacing sp <- spacing
optional $ do optional $ do
@@ -976,37 +1008,60 @@ readHereDoc = called "here document" $ do
let message = "Shells are space sensitive. Use '< <(cmd)', not '<<" ++ sp ++ "(cmd)'." let message = "Shells are space sensitive. Use '< <(cmd)', not '<<" ++ sp ++ "(cmd)'."
parseProblemAt pos ErrorC message parseProblemAt pos ErrorC message
hid <- getNextId hid <- getNextId
(quoted, endToken) <- (readNormalLiteral "" >>= (\x -> return (False, stripLiteral x)) ) (quoted, endToken) <- (readNormalLiteral "" >>= (\x -> return (Unquoted, stripLiteral x)) )
<|> (readDoubleQuotedLiteral >>= return . (\x -> (True, stripLiteral x))) <|> (readDoubleQuotedLiteral >>= return . (\x -> (Quoted, stripLiteral x)))
<|> (readSingleQuotedLiteral >>= return . (\x -> (True, x))) <|> (readSingleQuotedLiteral >>= return . (\x -> (Quoted, x)))
spacing spacing
hereInfo <- anyChar `reluctantlyTill` (linefeed >> spacing >> (string endToken) >> (disregard whitespace <|> eof)) startPos <- getPosition
hereData <- anyChar `reluctantlyTill` do
linefeed
spacing
string endToken
disregard linefeed <|> eof
do do
linefeed linefeed
spaces <- spacing spaces <- spacing
verifyHereDoc dashed quoted spaces hereInfo verifyHereDoc dashed quoted spaces hereData
token <- string endToken string endToken
return $ T_FdRedirect fid "" $ T_HereDoc hid dashed quoted hereInfo parsedData <- parseHereData quoted startPos hereData
`attempting` (eof >> debugHereDoc tokenPosition endToken hereInfo) return $ T_FdRedirect fid "" $ T_HereDoc hid dashed quoted endToken parsedData
`attempting` (eof >> debugHereDoc tokenPosition endToken hereData)
verifyHereDoc dashed quoted spacing hereInfo = do where
when (not dashed && spacing /= "") $ parseNote ErrorC "Use <<- instead of << if you want to indent the end token." parseHereData Quoted startPos hereData = do
when (dashed && filter (/= '\t') spacing /= "" ) $ parseNote ErrorC "When using <<-, you can only indent with tabs." id <- getNextIdAt startPos
return () return $ [T_Literal id hereData]
debugHereDoc pos endToken doc = parseHereData Unquoted startPos hereData = do
if endToken `isInfixOf` doc subParse startPos readHereData hereData
then
let lookAt line = when (endToken `isInfixOf` line) $ readHereData = many $ try readNormalDollar <|> try readBackTicked <|> readHereLiteral
parseProblemAt pos ErrorC ("Close matches include '" ++ line ++ "' (!= '" ++ endToken ++ "').")
in do readHereLiteral = do
parseProblemAt pos ErrorC ("Found '" ++ endToken ++ "' further down, but not entirely by itself.") id <- getNextId
mapM_ lookAt (lines doc) chars <- anyChar `reluctantlyTill1` oneOf "`$"
else if (map toLower endToken) `isInfixOf` (map toLower doc) return $ T_Literal id chars
then parseProblemAt pos ErrorC ("Found " ++ endToken ++ " further down, but with wrong casing.")
else parseProblemAt pos ErrorC ("Couldn't find end token `" ++ endToken ++ "' in the here document.") verifyHereDoc dashed quoted spacing hereInfo = do
when (dashed == Undashed && spacing /= "") $
parseNote ErrorC "Use <<- instead of << if you want to indent the end token."
when (dashed == Dashed && filter (/= '\t') spacing /= "" ) $
parseNote ErrorC "When using <<-, you can only indent with tabs."
return ()
debugHereDoc pos endToken doc =
if endToken `isInfixOf` doc
then
let lookAt line = when (endToken `isInfixOf` line) $
parseProblemAt pos ErrorC ("Close matches include '" ++ line ++ "' (!= '" ++ endToken ++ "').")
in do
parseProblemAt pos ErrorC ("Found '" ++ endToken ++ "' further down, but not entirely by itself.")
mapM_ lookAt (lines doc)
else if (map toLower endToken) `isInfixOf` (map toLower doc)
then parseProblemAt pos ErrorC ("Found " ++ endToken ++ " further down, but with wrong casing.")
else parseProblemAt pos ErrorC ("Couldn't find end token `" ++ endToken ++ "' in the here document.")
readFilename = readNormalWord readFilename = readNormalWord
@@ -1092,7 +1147,7 @@ makeSimpleCommand id1 id2 prefix cmd suffix =
in in
T_Redirecting id1 redirs $ T_SimpleCommand id2 assigns args T_Redirecting id1 redirs $ T_SimpleCommand id2 assigns args
where where
assignment (T_Assignment _ _ _) = True assignment (T_Assignment _ _ _ _ _) = True
assignment _ = False assignment _ = False
redirection (T_FdRedirect _ _ _) = True redirection (T_FdRedirect _ _ _) = True
redirection _ = False redirection _ = False
@@ -1313,6 +1368,7 @@ prop_readForClause4 = isOk readForClause "for((i=0; i<10; i++)); do echo $i; don
prop_readForClause5 = isOk readForClause "for ((i=0;i<10 && n>x;i++,--n))\ndo \necho $i\ndone" prop_readForClause5 = isOk readForClause "for ((i=0;i<10 && n>x;i++,--n))\ndo \necho $i\ndone"
prop_readForClause6 = isOk readForClause "for ((;;))\ndo echo $i\ndone" prop_readForClause6 = isOk readForClause "for ((;;))\ndo echo $i\ndone"
prop_readForClause7 = isOk readForClause "for ((;;)) do echo $i\ndone" prop_readForClause7 = isOk readForClause "for ((;;)) do echo $i\ndone"
prop_readForClause8 = isOk readForClause "for ((;;)) ; do echo $i\ndone"
readForClause = called "for loop" $ do readForClause = called "for loop" $ do
pos <- getPosition pos <- getPosition
(T_For id) <- g_For (T_For id) <- g_For
@@ -1330,7 +1386,8 @@ readForClause = called "for loop" $ do
z <- readArithmeticContents z <- readArithmeticContents
spacing spacing
string "))" string "))"
readSequentialSep <|> disregard spacing spacing
optional $ readSequentialSep >> spacing
return $ \id group -> (return $ T_ForArithmetic id x y z group) return $ \id group -> (return $ T_ForArithmetic id x y z group)
readRegular = do readRegular = do
@@ -1402,6 +1459,7 @@ prop_readFunctionDefinition1 = isOk readFunctionDefinition "foo (){ command fo
prop_readFunctionDefinition2 = isWarning readFunctionDefinition "function foo() { command foo --lol \"$@\"; }" prop_readFunctionDefinition2 = isWarning readFunctionDefinition "function foo() { command foo --lol \"$@\"; }"
prop_readFunctionDefinition3 = isWarning readFunctionDefinition "function foo { lol; }" prop_readFunctionDefinition3 = isWarning readFunctionDefinition "function foo { lol; }"
prop_readFunctionDefinition4 = isWarning readFunctionDefinition "foo(a, b) { true; }" prop_readFunctionDefinition4 = isWarning readFunctionDefinition "foo(a, b) { true; }"
prop_readFunctionDefinition5 = isOk readFunctionDefinition ":(){ :|:;}"
readFunctionDefinition = called "function" $ do readFunctionDefinition = called "function" $ do
id <- getNextId id <- getNextId
name <- try readFunctionSignature name <- try readFunctionSignature
@@ -1421,7 +1479,7 @@ readFunctionSignature = do
whitespace whitespace
parseProblemAt pos InfoC "Drop the keyword 'function'. It's optional in Bash but invalid in other shells." parseProblemAt pos InfoC "Drop the keyword 'function'. It's optional in Bash but invalid in other shells."
spacing spacing
name <- readVariableName name <- readFunctionName
optional spacing optional spacing
pos <- getPosition pos <- getPosition
readParens <|> do readParens <|> do
@@ -1429,7 +1487,7 @@ readFunctionSignature = do
return name return name
readWithoutFunction = try $ do readWithoutFunction = try $ do
name <- readVariableName name <- readFunctionName
optional spacing optional spacing
readParens readParens
return name return name
@@ -1443,15 +1501,18 @@ readFunctionSignature = do
g_Rparen g_Rparen
return () return ()
readFunctionName = many1 functionChars
readPattern = (readNormalWord `thenSkip` spacing) `sepBy1` (char '|' `thenSkip` spacing) readPattern = (readNormalWord `thenSkip` spacing) `sepBy1` (char '|' `thenSkip` spacing)
prop_readCompoundCommand = isOk readCompoundCommand "{ echo foo; }>/dev/null"
readCompoundCommand = do readCompoundCommand = do
id <- getNextId id <- getNextId
cmd <- choice [ readBraceGroup, readArithmeticExpression, readSubshell, readCondition, readWhileClause, readUntilClause, readIfClause, readForClause, readSelectClause, readCaseClause, readFunctionDefinition] cmd <- choice [ readBraceGroup, readArithmeticExpression, readSubshell, readCondition, readWhileClause, readUntilClause, readIfClause, readForClause, readSelectClause, readCaseClause, readFunctionDefinition]
spacing optional spacing
redirs <- many readIoRedirect redirs <- many readIoRedirect
when (not . null $ redirs) $ optional $ do when (not . null $ redirs) $ optional $ do
lookAhead $ try (spacing >> needsSeparator) lookAhead $ try (spacing >> needsSeparator)
@@ -1484,35 +1545,40 @@ readAssignmentWord = try $ do
variable <- readVariableName variable <- readVariableName
optional (readNormalDollar >> parseNoteAt pos ErrorC optional (readNormalDollar >> parseNoteAt pos ErrorC
"For indirection, use (associative) arrays or 'read \"var$n\" <<< \"value\"'") "For indirection, use (associative) arrays or 'read \"var$n\" <<< \"value\"'")
optional readArrayIndex -- Throws away the index. Fixme? index <- optionMaybe readArrayIndex
space <- spacing space <- spacing
pos <- getPosition pos <- getPosition
op <- string "+=" <|> string "=" -- analysis doesn't treat += as a reference. fixme? op <- readAssignmentOp
space2 <- spacing space2 <- spacing
if space == "" && space2 /= "" if space == "" && space2 /= ""
then do then do
when (variable /= "IFS") $ when (variable /= "IFS") $
parseNoteAt pos InfoC $ "Note that 'var= value' (with space after equals sign) is similar to 'var=\"\"; value'." parseNoteAt pos InfoC $ "Note that 'var= value' (with space after equals sign) is similar to 'var=\"\"; value'."
value <- readEmptyLiteral value <- readEmptyLiteral
return $ T_Assignment id variable value return $ T_Assignment id op variable index value
else do else do
when (space /= "" || space2 /= "") $ when (space /= "" || space2 /= "") $
parseNoteAt pos ErrorC "Don't put spaces around the = in assignments." parseNoteAt pos ErrorC "Don't put spaces around the = in assignments."
value <- readArray <|> readNormalWord value <- readArray <|> readNormalWord
spacing spacing
return $ T_Assignment id variable value return $ T_Assignment id op variable index value
where where
readAssignmentOp =
(string "+=" >> return Append) <|> (string "=" >> return Assign)
readEmptyLiteral = do readEmptyLiteral = do
id <- getNextId id <- getNextId
return $ T_Literal id "" return $ T_Literal id ""
-- This is only approximate. Fixme? -- This is only approximate. Fixme?
-- * Bash allows foo[' ' "" $(true) 2 ``]=var
-- * foo[bar] dereferences bar
readArrayIndex = do readArrayIndex = do
char '[' char '['
optional space optional space
x <- readNormalishWord "]" x <- readNormalishWord "]"
optional space optional space
char ']' char ']'
return x
readArray = called "array assignment" $ do readArray = called "array assignment" $ do
id <- getNextId id <- getNextId
@@ -1581,13 +1647,13 @@ g_Bang = do
softCondSpacing softCondSpacing
return $ T_Bang id return $ T_Bang id
commonCommands = [ "admin", "alias", "ar", "asa", "at", "awk", "basename", "batch", "bc", "bg", "break", "c99", "cal", "cat", "cd", "cflow", "chgrp", "chmod", "chown", "cksum", "cmp", "colon", "comm", "command", "compress", "continue", "cp", "crontab", "csplit", "ctags", "cut", "cxref", "date", "dd", "delta", "df", "diff", "dirname", "dot", "du", "echo", "ed", "env", "eval", "ex", "exec", "exit", "expand", "export", "expr", "fc", "fg", "file", "find", "fold", "fort77", "fuser", "gencat", "get", "getconf", "getopts", "grep", "hash", "head", "iconv", "ipcrm", "ipcs", "jobs", "join", "kill", "lex", "link", "ln", "locale", "localedef", "logger", "logname", "lp", "ls", "m4", "mailx", "make", "man", "mesg", "mkdir", "mkfifo", "more", "mv", "newgrp", "nice", "nl", "nm", "nohup", "od", "paste", "patch", "pathchk", "pax", "pr", "printf", "prs", "ps", "pwd", "qalter", "qdel", "qhold", "qmove", "qmsg", "qrerun", "qrls", "qselect", "qsig", "qstat", "qsub", "read", "readonly", "renice", "return", "rm", "rmdel", "rmdir", "sact", "sccs", "sed", "set", "sh", "shift", "sleep", "sort", "split", "strings", "strip", "stty", "tabs", "tail", "talk", "tee", "test", "time", "times", "touch", "tput", "tr", "trap", "tsort", "tty", "type", "ulimit", "umask", "unalias", "uname", "uncompress", "unexpand", "unget", "uniq", "unlink", "unset", "uucp", "uudecode", "uuencode", "uustat", "uux", "val", "vi", "wait", "wc", "what", "who", "write", "xargs", "yacc", "zcat" ]
g_Semi = do g_Semi = do
notFollowedBy2 g_DSEMI notFollowedBy2 g_DSEMI
tryToken ";" T_Semi tryToken ";" T_Semi
keywordSeparator = eof <|> disregard whitespace <|> (disregard $ oneOf ";()[") keywordSeparator =
eof <|> disregard whitespace <|> (disregard $ oneOf ";()[<>&")
readKeyword = choice [ g_Then, g_Else, g_Elif, g_Fi, g_Do, g_Done, g_Esac, g_Rbrace, g_Rparen, g_DSEMI ] readKeyword = choice [ g_Then, g_Else, g_Elif, g_Fi, g_Do, g_Done, g_Esac, g_Rbrace, g_Rparen, g_DSEMI ]

View File

@@ -24,7 +24,6 @@ import System.Environment
import System.Exit import System.Exit
import System.IO import System.IO
clear = ansi 0 clear = ansi 0
ansi n = "\x1B[" ++ (show n) ++ "m" ansi n = "\x1B[" ++ (show n) ++ "m"
@@ -45,27 +44,26 @@ doFile path colorFunc = do
contents <- readFile actualPath contents <- readFile actualPath
doInput path contents colorFunc doInput path contents colorFunc
else do else do
putStrLn (colorFunc "error" $ "No such file: " ++ actualPath) hPutStrLn stderr (colorFunc "error" $ "No such file: " ++ actualPath)
return False
doInput filename contents colorFunc = do doInput filename contents colorFunc = do
let fileLines = lines contents let fileLines = lines contents
let lineCount = length fileLines let lineCount = length fileLines
let comments = shellCheck contents let comments = shellCheck contents
let groups = groupWith scLine comments let groups = groupWith scLine comments
if not $ null comments then do mapM_ (\x -> do
mapM_ (\x -> do let lineNum = scLine (head x)
let lineNum = scLine (head x) let line = if lineNum < 1 || lineNum > lineCount
let line = if lineNum < 1 || lineNum > lineCount then ""
then "" else fileLines !! (lineNum - 1)
else fileLines !! (lineNum - 1) putStrLn ""
putStrLn "" putStrLn $ colorFunc "message" ("In " ++ filename ++" line " ++ (show $ lineNum) ++ ":")
putStrLn $ colorFunc "message" ("In " ++ filename ++" line " ++ (show $ lineNum) ++ ":") putStrLn (colorFunc "source" line)
putStrLn (colorFunc "source" line) mapM (\c -> putStrLn (colorFunc (scSeverity c) $ cuteIndent c)) x
mapM (\c -> putStrLn (colorFunc (scSeverity c) $ cuteIndent c)) x putStrLn ""
putStrLn "" ) groups
) groups return $ null comments
else do
putStrLn ("No comments for " ++ filename)
cuteIndent comment = cuteIndent comment =
(replicate ((scColumn comment) - 1) ' ') ++ "^-- " ++ (scMessage comment) (replicate ((scColumn comment) - 1) ' ') ++ "^-- " ++ (scMessage comment)
@@ -81,6 +79,7 @@ main = do
hPutStrLn stderr "shellcheck -- bash/sh script static analysis tool" hPutStrLn stderr "shellcheck -- bash/sh script static analysis tool"
hPutStrLn stderr "Usage: shellcheck filenames..." hPutStrLn stderr "Usage: shellcheck filenames..."
exitFailure exitFailure
else else do
mapM (\f -> doFile f colors) args statuses <- mapM (\f -> doFile f colors) args
if and statuses then exitSuccess else exitFailure