66 Commits

Author SHA1 Message Date
Vidar Holen
f25ae90746 Stable version 0.3.6
This release is dedicated to Maxis: shaping the 90s
for yours truly with SimCity, SimCopter and El-Fish.
2015-03-28 12:27:39 -07:00
Vidar Holen
3daa47c0f2 Remove zsh specific variables. 2015-03-28 11:55:25 -07:00
Vidar Holen
ed56a837c3 Killed Zsh support 2015-03-20 10:03:56 -07:00
Vidar Holen
80cf5d9852 Include [] as glob chars to warn about quoting for 2015-03-19 18:29:47 -07:00
Vidar Holen
8e554ae3d4 Fix SC2143 to not warn about pgrep and other quasi-greps. 2015-03-12 08:31:49 -07:00
Vidar Holen
0a80188363 Fix parsing of ((a?b:c)) 2015-03-08 18:11:23 -07:00
Vidar Holen
0e1a64b6ba Warn about export/declare/local masking return values. 2015-03-08 14:17:43 -07:00
Vidar Holen
0a2cf208c8 Fixed quoted ~ warning to only trigger for ~/ 2015-03-07 23:48:01 -08:00
Vidar Holen
dcc10bbdf6 Fixed accidentally ignored undef warning for ${#foo} 2015-03-07 23:01:34 -08:00
Vidar Holen
2c2e41952f Improved missing shebang message. 2015-03-07 22:37:49 -08:00
Vidar Holen
0d74140650 Multiple wrong assignment warning fixes 2015-03-07 20:15:04 -08:00
Vidar Holen
955ad60823 Fixed parser errors not being excluded by -e 2015-03-01 13:44:57 -08:00
Vidar Holen
2573332d77 Fixed edge cases for braced reference extractor. 2015-03-01 13:44:18 -08:00
Vidar Holen
00c470f323 Improve SC2143 error message 2015-03-01 12:20:37 -08:00
Vidar Holen
63188282e9 Add warning for vars that are referenced but not assigned. 2015-02-28 18:43:22 -08:00
Vidar Holen
61b4b65184 Warn about obviously bad return values, like -1 or "foo" 2015-02-14 12:03:38 -08:00
Vidar Holen
39b2bf4378 Don't warn about modifying $@ or $IFS in a subshell 2015-02-14 10:43:49 -08:00
Vidar Holen
2fe117728d Count [[ -v foo ]] (and -R) as a variable reference 2015-02-13 20:10:18 -08:00
Vidar Holen
cde3ba8769 Add filename to JSON output. 2015-02-13 19:32:20 -08:00
Vidar Holen
33c78b7c95 Track variables created through coproc. 2015-01-27 10:11:17 -08:00
Vidar Holen
a485482979 Add support for coproc 2015-01-26 22:21:04 -08:00
Vidar Holen
895d83afc5 s/deprecated/legacy/ for backtick warnings. 2015-01-25 12:27:49 -08:00
Vidar Holen
39bc011757 Rewrote catastrophic rm detection, now simpler and more robust. 2015-01-25 12:18:06 -08:00
koalaman
fe0a398239 Merge pull request #295 from orlitzky/sdist-manpage
Add a pre-sdist hook to compile the man page (Github issue #247).
2015-01-24 13:10:09 -08:00
Michael Orlitzky
1be0f1ea75 Add a pre-sdist hook to compile the man page (Github issue #247).
This replaces the default preSDist hook in Setup.hs with our own. The
only thing the new hook does is compile the man page using callCommand
from System.Process.

If Pandoc fails, the entire sdist process will fail, since
Extra-Source-Files in the cabal file now lists the man page.

This is preferable to a build hook, because Pandoc pulls in a huge
number of dependencies. It's better to build the man page once and
ship it than to require every user to build and install pandoc before
he can build ShellCheck.

This creates another TODO item: an install hook can now be used to
install the man page along with the rest of ShellCheck. But beware,
the "man path" can vary from system to system.
2015-01-24 12:15:36 -05:00
Vidar Holen
c9aa133282 Fix pattern matching error in z=$(echo) 2015-01-02 18:06:10 -08:00
Vidar Holen
7b70500d41 Suppress SC2140 if the user just prefers quoting single items at a time. 2014-12-23 19:47:55 -08:00
Vidar Holen
8bed447411 Warn when trying to find -exec "shell command" \; 2014-11-22 12:16:30 -08:00
Vidar Holen
22710bf4d8 Fixed $! counting as a positional parameter reference. 2014-11-22 11:21:54 -08:00
Vidar Holen
a354685ab1 Warn about redirecting to globs in sh 2014-11-22 10:50:38 -08:00
Vidar Holen
a8ff7a02fd Fix $10 warning triggering for $?!, and also warn about $arr[index]. 2014-11-22 10:09:19 -08:00
Vidar Holen
c5479b8ca3 Stable version 0.3.5
This release is dedicated to Maru, internet celebrity cat.
Where would the web be without you? (Runner-up: Tim Berners-Lee)
2014-11-09 16:30:00 -08:00
Vidar Holen
d9dd58bec8 Warn about 'for $var in values'. 2014-11-09 16:22:01 -08:00
Vidar Holen
af1bb93aba Better warnings for repeated ;;s 2014-11-09 14:33:36 -08:00
Vidar Holen
e909c8ac42 More lenient line feed handling in test expressions. 2014-11-08 15:35:06 -08:00
koalaman
93140e31a0 Merge pull request #253 from vlajos/typofixes-vlajos-20141104
typo fixes - https://github.com/vlajos/misspell_fixer
2014-11-04 15:27:56 -08:00
Veres Lajos
97f3834852 typo fixes - https://github.com/vlajos/misspell_fixer 2014-11-04 21:55:42 +00:00
Vidar Holen
0369f43bac Fixed 2148 to not trigger if a shell is specified with -s. 2014-11-01 13:51:19 -07:00
Vidar Holen
eb2eae2888 Don't warn about ${args[@]} when nested in other ${} 2014-11-01 12:44:27 -07:00
Vidar Holen
30c0c1f27d Allow export "foo"="bar" in 2140 2014-11-01 12:20:10 -07:00
Vidar Holen
bff5d11566 Warn about `` in '' 2014-11-01 12:17:12 -07:00
Vidar Holen
eccb9f3f71 Added -or and -print0 to SC2146 2014-11-01 12:07:09 -07:00
Vidar Holen
2814572116 cat "$@" is not UUOC 2014-10-18 19:59:13 -07:00
Vidar Holen
90bafb9aba Fixed bug where (($b)) counted as a positional reference 2014-10-18 19:51:13 -07:00
Vidar Holen
39b88bbaac Removed Arch from readme, added Debian. 2014-10-12 17:13:35 -07:00
Vidar Holen
39805ab200 Don't warn about unpassed parameters in functions using 'set ..'. 2014-10-12 17:10:46 -07:00
Vidar Holen
9dadce96c0 Improve messages for missing 'then' statements. 2014-10-12 16:17:03 -07:00
Vidar Holen
1a0e208cc3 Consider find -exec when warning about vars in single quotes. 2014-10-12 14:00:17 -07:00
Vidar Holen
a69e27b774 Warn about swapped !# in the shebang. 2014-10-11 12:35:45 -07:00
Vidar Holen
b05c12223f Don't trigger SC2004 for (( $$ )) 2014-09-23 10:27:26 -07:00
Vidar Holen
38ead0385b Fixed quoting warnings for variables in $".." 2014-09-23 10:18:28 -07:00
Vidar Holen
9e8a11e57c Merge branch 'master' of github.com:koalaman/shellcheck 2014-09-23 10:12:23 -07:00
Vidar Holen
6b84b35ec0 Don't crash on empty files with -f gcc. 2014-09-23 10:11:15 -07:00
koalaman
669fdf8e5e Merge pull request #226 from aycanirican/patch-1
Update License in ShellCheck.cabal
2014-09-18 07:09:46 -07:00
Aycan iRiCAN
dccfb3c4a1 Update ShellCheck.cabal
Fixed License.
2014-09-18 09:10:07 +03:00
Vidar Holen
40ce949a56 Only warn once per unused variable name. 2014-09-07 12:55:08 -07:00
Vidar Holen
9f3802138f Prevent overlap of 2116 and 2005 in foo $(echo $(bar)) 2014-09-04 08:41:09 -07:00
Vidar Holen
2f3533fff6 Improve warnings for $ in (()). Also improves array subscripts. 2014-08-16 17:08:57 -07:00
Vidar Holen
f9c346cfd7 Ignore SC2033 when passing quoted function names. 2014-08-16 10:45:46 -07:00
Vidar Holen
5f7419ca37 Require a QuickCheck that doesn't break on UTF-8. 2014-08-10 17:16:27 -07:00
Vidar Holen
8494509150 Warn about missing shebangs. 2014-08-09 17:32:42 -07:00
Vidar Holen
8ba1f2fdf2 Better handling of directories and inaccessible files. 2014-08-08 09:36:17 -07:00
Vidar Holen
dbadca9f61 Check PS1/PROMPT_COMMAND/trap for simple variable references 2014-07-27 09:51:48 -07:00
Vidar Holen
0347ce1b7a Warn about quoted ~ in PATH 2014-07-26 13:14:28 -07:00
Vidar Holen
7fbe66e1c6 Warn about ineffectual quotes in a="/foo/'bar baz'"; $a 2014-07-26 12:15:54 -07:00
Vidar Holen
b000b05507 Parse empty and comment-only backtick expansions. 2014-07-26 12:07:59 -07:00
11 changed files with 1139 additions and 538 deletions

View File

@@ -2,7 +2,7 @@
http://www.shellcheck.net
Copyright 2012-2014, Vidar 'koala_man' Holen
Copyright 2012-2015, Vidar 'koala_man' Holen
Licensed under the GNU Affero General Public License, v3
The goals of ShellCheck are:
@@ -16,7 +16,7 @@ The goals of ShellCheck are:
- To point out subtle caveats, corner cases and pitfalls, that may cause an
advanced user's otherwise working script to fail under future circumstances.
ShellCheck is written in Haskell, and requires at least 1 GB of RAM to compile.
ShellCheck is written in Haskell, and requires 2 GB of memory to compile.
## Installing
@@ -25,9 +25,9 @@ On systems with Cabal:
cabal update
cabal install shellcheck
On Arch Linux with community packages enabled:
On Debian based distros:
pacman -S shellcheck
apt-get install shellcheck
On OS X with homebrew:

View File

@@ -1,2 +1,43 @@
import Distribution.Simple
main = defaultMain
import Distribution.PackageDescription (
HookedBuildInfo,
emptyHookedBuildInfo )
import Distribution.Simple (
Args,
UserHooks ( preSDist ),
defaultMainWithHooks,
simpleUserHooks )
import Distribution.Simple.Setup ( SDistFlags )
-- | This requires the process package from,
--
-- https://hackage.haskell.org/package/process
--
import System.Process ( callCommand )
-- | This will use almost the default implementation, except we switch
-- out the default pre-sdist hook with our own, 'myPreSDist'.
--
main = defaultMainWithHooks myHooks
where
myHooks = simpleUserHooks { preSDist = myPreSDist }
-- | This hook will be executed before e.g. @cabal sdist@. It runs
-- pandoc to create the man page from shellcheck.1.md. If the pandoc
-- command is not found, this will fail with an error message:
--
-- /bin/sh: pandoc: command not found
--
-- Since the man page is listed in the Extra-Source-Files section of
-- our cabal file, a failure here should result in a failure to
-- create the distribution tarball (that's a good thing).
--
myPreSDist :: Args -> SDistFlags -> IO HookedBuildInfo
myPreSDist _ _ = do
putStrLn "Building the man page..."
putStrLn pandoc_cmd
callCommand pandoc_cmd
return emptyHookedBuildInfo
where
pandoc_cmd = "pandoc -s -t man shellcheck.1.md -o shellcheck.1"

View File

@@ -1,7 +1,7 @@
Name: ShellCheck
Version: 0.3.4
Version: 0.3.6
Synopsis: Shell script analysis tool
License: OtherLicense
License: AGPL-3
License-file: LICENSE
Category: Static Analysis
Author: Vidar Holen
@@ -26,6 +26,8 @@ Extra-Source-Files:
-- documentation
README.md
shellcheck.1.md
-- built with a cabal sdist hook
shellcheck.1
-- tests
test/shellcheck.hs
@@ -42,11 +44,12 @@ library
mtl,
parsec,
regex-compat,
QuickCheck >= 2.2
QuickCheck >= 2.7.4
exposed-modules:
ShellCheck.Analytics
ShellCheck.AST
ShellCheck.Data
ShellCheck.Options
ShellCheck.Parser
ShellCheck.Simple
other-modules:
@@ -62,7 +65,8 @@ executable shellcheck
mtl,
parsec,
regex-compat,
QuickCheck >= 2.2
transformers,
QuickCheck >= 2.7.4
main-is: shellcheck.hs
test-suite test-shellcheck
@@ -76,6 +80,7 @@ test-suite test-shellcheck
mtl,
parsec,
regex-compat,
QuickCheck >= 2.2
transformers,
QuickCheck >= 2.7.4
main-is: test/shellcheck.hs

View File

@@ -28,12 +28,12 @@ data Dashed = Dashed | Undashed deriving (Show, Eq)
data AssignmentMode = Assign | Append deriving (Show, Eq)
data FunctionKeyword = FunctionKeyword Bool deriving (Show, Eq)
data FunctionParentheses = FunctionParentheses Bool deriving (Show, Eq)
data ForInType = NormalForIn | ShortForIn deriving (Show, Eq)
data CaseType = CaseBreak | CaseFallThrough | CaseContinue deriving (Show, Eq)
data Token =
TA_Binary Id String Token Token
| TA_Expansion Id [Token]
| TA_Index Id Token
| TA_Sequence Id [Token]
| TA_Trinary Id Token Token Token
| TA_Unary Id String Token
@@ -48,7 +48,6 @@ data Token =
| T_Arithmetic Id Token
| T_Array Id [Token]
| T_IndexedElement Id Token Token
| T_ Id [Token]
| T_Assignment Id AssignmentMode String (Maybe Token) Token
| T_Backgrounded Id Token
| T_Backticked Id [Token]
@@ -82,7 +81,7 @@ data Token =
| T_Fi Id
| T_For Id
| T_ForArithmetic Id Token Token Token [Token]
| T_ForIn Id ForInType [String] [Token] [Token]
| T_ForIn Id String [Token] [Token]
| T_Function Id FunctionKeyword FunctionParentheses String Token
| T_GREATAND Id
| T_Glob Id String
@@ -122,6 +121,8 @@ data Token =
| T_WhileExpression Id [Token] [Token]
| T_Annotation Id [Annotation] Token
| T_Pipe Id String
| T_CoProc Id (Maybe String) Token
| T_CoProcBody Id Token
deriving (Show)
data Annotation = DisableComment Integer deriving (Show, Eq)
@@ -204,7 +205,7 @@ analyze f g i =
delve (T_BraceGroup id l) = dl l $ T_BraceGroup id
delve (T_WhileExpression id c l) = dll c l $ T_WhileExpression id
delve (T_UntilExpression id c l) = dll c l $ T_UntilExpression id
delve (T_ForIn id t v w l) = dll w l $ T_ForIn id t v
delve (T_ForIn id v w l) = dll w l $ T_ForIn id v
delve (T_SelectIn id v w l) = dll w l $ T_SelectIn id v
delve (T_CaseExpression id word cases) = do
newWord <- round word
@@ -245,7 +246,10 @@ analyze f g i =
c <- round t3
return $ TA_Trinary id a b c
delve (TA_Expansion id t) = dl t $ TA_Expansion id
delve (TA_Index id t) = d1 t $ TA_Index id
delve (T_Annotation id anns t) = d1 t $ T_Annotation id anns
delve (T_CoProc id var body) = d1 body $ T_CoProc id var
delve (T_CoProcBody id t) = d1 t $ T_CoProcBody id
delve t = return t
getId t = case t of
@@ -310,7 +314,7 @@ getId t = case t of
T_BraceGroup id _ -> id
T_WhileExpression id _ _ -> id
T_UntilExpression id _ _ -> id
T_ForIn id _ _ _ _ -> id
T_ForIn id _ _ _ -> id
T_SelectIn id _ _ _ -> id
T_CaseExpression id _ _ -> id
T_Function id _ _ _ _ -> id
@@ -330,6 +334,7 @@ getId t = case t of
TA_Sequence id _ -> id
TA_Trinary id _ _ _ -> id
TA_Expansion id _ -> id
TA_Index id _ -> id
T_ProcSub id _ _ -> id
T_Glob id _ -> id
T_ForArithmetic id _ _ _ _ -> id
@@ -338,6 +343,8 @@ getId t = case t of
T_DollarBracket id _ -> id
T_Annotation id _ _ -> id
T_Pipe id _ -> id
T_CoProc id _ _ -> id
T_CoProcBody id _ -> id
blank :: Monad m => Token -> m ()
blank = const $ return ()

File diff suppressed because it is too large Load Diff

View File

@@ -27,22 +27,10 @@ internalVariables = [
"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",
"TMOUT", "TMPDIR", "auto_resume", "histchars", "COPROC",
-- 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"
-- Other
"USER", "TZ", "TERM"
]
variablesWithoutSpaces = [

14
ShellCheck/Options.hs Normal file
View File

@@ -0,0 +1,14 @@
module ShellCheck.Options where
data Shell = Ksh | Sh | Bash
deriving (Show, Eq)
data AnalysisOptions = AnalysisOptions {
optionShellType :: Maybe Shell,
optionExcludes :: [Integer]
}
defaultAnalysisOptions = AnalysisOptions {
optionShellType = Nothing,
optionExcludes = []
}

View File

@@ -16,10 +16,11 @@
along with this program. If not, see <http://www.gnu.org/licenses/>.
-}
{-# LANGUAGE NoMonomorphismRestriction, TemplateHaskell #-}
module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), sortNotes, noteToParseNote, runTests) where
module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), sortNotes, noteToParseNote, runTests, readScript) where
import ShellCheck.AST
import ShellCheck.Data
import ShellCheck.Options
import Text.Parsec
import Debug.Trace
import Control.Monad
@@ -61,13 +62,13 @@ unicodeDoubleQuoteChars = "\x201C\x201D\x2033\x2036"
prop_spacing = isOk spacing " \\\n # Comment"
spacing = do
x <- many (many1 linewhitespace <|> try (string "\\\n"))
x <- many (many1 linewhitespace <|> try (string "\\\n" >> return ""))
optional readComment
return $ concat x
spacing1 = do
spacing <- spacing
when (null spacing) $ fail "no spacing"
when (null spacing) $ fail "Expected whitespace"
return spacing
prop_allspacing = isOk allspacing "#foo"
@@ -84,7 +85,7 @@ allspacing = do
allspacingOrFail = do
s <- allspacing
when (null s) $ fail "Expected spaces"
when (null s) $ fail "Expected whitespace"
unicodeDoubleQuote = do
pos <- getPosition
@@ -183,9 +184,9 @@ popContext = do
then do
let (a:r) = v
setCurrentContexts r
return [a]
return $ Just a
else
return []
return Nothing
pushContext c = do
v <- getCurrentContexts
@@ -233,8 +234,8 @@ reluctantlyTill1 p end = do
attempting rest branch =
(try branch >> rest) <|> rest
orFail parser stuff =
try (disregard parser) <|> (disregard stuff >> fail "nope")
orFail parser errorAction =
try parser <|> (errorAction >>= fail)
wasIncluded p = option False (p >> return True)
@@ -252,7 +253,7 @@ withContext entry p = do
popContext
return v
<|> do -- p failed without consuming input, abort context
popContext
v <- popContext
fail ""
called s p = do
@@ -270,12 +271,22 @@ readConditionContents single =
parseProblemAt pos WarningC 1009 "Use 'if cmd; then ..' to check exit code, or 'if [[ $(cmd) == .. ]]' to check output.")
where
spacingOrLf = condSpacing True
condSpacing required = do
pos <- getPosition
space <- allspacing
when (required && null space) $
parseProblemAt pos ErrorC 1035 "You are missing a required space here."
when (single && '\n' `elem` space) $
parseProblemAt pos ErrorC 1080 "When breaking lines in [ ], you need \\ before the linefeed."
return space
typ = if single then SingleBracket else DoubleBracket
readCondBinaryOp = try $ do
optional guardArithmetic
id <- getNextId
op <- choice (map tryOp ["==", "!=", "<=", ">=", "=~", ">", "<", "=", "\\<=", "\\>=", "\\<", "\\>"]) <|> otherOp
hardCondSpacing
spacingOrLf
return op
where
tryOp s = try $ do
@@ -285,7 +296,7 @@ readConditionContents single =
otherOp = try $ do
id <- getNextId
s <- readOp
when (s == "-a" || s == "-o") $ fail "Wrong operator"
when (s == "-a" || s == "-o") $ fail "Unexpected operator"
return $ TC_Binary id typ s
guardArithmetic = do
@@ -298,17 +309,14 @@ readConditionContents single =
readCondUnaryExp = do
op <- readCondUnaryOp
pos <- getPosition
(do
arg <- readCondWord
return $ op arg)
<|> (do
parseProblemAt pos ErrorC 1019 "Expected this to be an argument to the unary condition."
fail "oops")
(readCondWord >>= return . op) `orFail` do
parseProblemAt pos ErrorC 1019 "Expected this to be an argument to the unary condition."
return "Expected an argument for the unary operator"
readCondUnaryOp = try $ do
id <- getNextId
s <- readOp
hardCondSpacing
spacingOrLf
return $ TC_Unary id typ s
readOp = try $ do
@@ -337,19 +345,20 @@ readConditionContents single =
readCondAndOp = do
id <- getNextId
x <- try (string "&&" <|> string "-a")
softCondSpacing
skipLineFeeds
x <- try (readAndOrOp "&&" False <|> readAndOrOp "-a" True)
return $ TC_And id typ x
readCondOrOp = do
optional guardArithmetic
id <- getNextId
x <- try (string "||" <|> string "-o")
softCondSpacing
skipLineFeeds
x <- try (readAndOrOp "||" False <|> readAndOrOp "-o" True)
return $ TC_Or id typ x
readAndOrOp op requiresSpacing = do
x <- string op
condSpacing requiresSpacing
return x
readCondNoaryOrBinary = do
id <- getNextId
x <- readCondWord `attempting` (do
@@ -373,16 +382,21 @@ readConditionContents single =
id <- getNextId
pos <- getPosition
lparen <- try $ string "(" <|> string "\\("
when (single && lparen == "(") $ parseProblemAt pos ErrorC 1028 "In [..] you have to escape (). Use [[..]] instead."
when (not single && lparen == "\\(") $ parseProblemAt pos ErrorC 1029 "In [[..]] you shouldn't escape ()."
if single then hardCondSpacing else disregard spacing
when (single && lparen == "(") $
parseProblemAt pos ErrorC 1028 "In [..] you have to escape (). Use [[..]] instead."
when (not single && lparen == "\\(") $
parseProblemAt pos ErrorC 1029 "In [[..]] you shouldn't escape ()."
condSpacing single
x <- readCondContents
cpos <- getPosition
rparen <- string ")" <|> string "\\)"
if single then hardCondSpacing else disregard spacing
when (single && rparen == ")") $ parseProblemAt cpos ErrorC 1030 "In [..] you have to escape (). Use [[..]] instead."
when (not single && rparen == "\\)") $ parseProblemAt cpos ErrorC 1031 "In [[..]] you shouldn't escape ()."
when (isEscaped lparen `xor` isEscaped rparen) $ parseProblemAt pos ErrorC 1032 "Did you just escape one half of () but not the other?"
condSpacing single
when (single && rparen == ")") $
parseProblemAt cpos ErrorC 1030 "In [..] you have to escape (). Use [[..]] instead."
when (not single && rparen == "\\)") $
parseProblemAt cpos ErrorC 1031 "In [[..]] you shouldn't escape ()."
when (isEscaped lparen `xor` isEscaped rparen) $
parseProblemAt pos ErrorC 1032 "Did you just escape one half of () but not the other?"
return $ TC_Group id typ x
where
isEscaped ('\\':_) = True
@@ -426,21 +440,15 @@ readConditionContents single =
str <- string "|"
return $ T_Literal id str
skipLineFeeds = do
pos <- getPosition
spacing <- allspacing
when (single && '\n' `elem` spacing) $
parseProblemAt pos ErrorC 1080 "In [ ] you need \\ before line feeds."
readCondTerm = do
term <- readCondNot <|> readCondExpr
skipLineFeeds
condSpacing False
return term
readCondNot = do
id <- getNextId
char '!'
softCondSpacing
spacingOrLf
expr <- readCondExpr
return $ TC_Unary id typ "!" expr
@@ -452,7 +460,6 @@ readConditionContents single =
readCondContents = readCondOr
prop_a1 = isOk readArithmeticContents " n++ + ++c"
prop_a2 = isOk readArithmeticContents "$N*4-(3,2)"
prop_a3 = isOk readArithmeticContents "n|=2<<1"
@@ -462,14 +469,15 @@ prop_a6 = isOk readArithmeticContents " 1 | 2 ||3|4"
prop_a7 = isOk readArithmeticContents "3*2**10"
prop_a8 = isOk readArithmeticContents "3"
prop_a9 = isOk readArithmeticContents "a^!-b"
prop_aA = isOk readArithmeticContents "! $?"
prop_aB = isOk readArithmeticContents "10#08 * 16#f"
prop_aC = isOk readArithmeticContents "\"$((3+2))\" + '37'"
prop_aD = isOk readArithmeticContents "foo[9*y+x]++"
prop_aE = isOk readArithmeticContents "1+`echo 2`"
prop_aF = isOk readArithmeticContents "foo[`echo foo | sed s/foo/4/g` * 3] + 4"
prop_a10= isOk readArithmeticContents "$foo$bar"
prop_a11= isOk readArithmeticContents "i<(0+(1+1))"
prop_a10= isOk readArithmeticContents "! $?"
prop_a11= isOk readArithmeticContents "10#08 * 16#f"
prop_a12= isOk readArithmeticContents "\"$((3+2))\" + '37'"
prop_a13= isOk readArithmeticContents "foo[9*y+x]++"
prop_a14= isOk readArithmeticContents "1+`echo 2`"
prop_a15= isOk readArithmeticContents "foo[`echo foo | sed s/foo/4/g` * 3] + 4"
prop_a16= isOk readArithmeticContents "$foo$bar"
prop_a17= isOk readArithmeticContents "i<(0+(1+1))"
prop_a18= isOk readArithmeticContents "a?b:c"
readArithmeticContents =
readSequence
where
@@ -489,10 +497,10 @@ readArithmeticContents =
readArrayIndex = do
id <- getNextId
start <- literal "["
char '['
middle <- readArithmeticContents
end <- literal "]"
return $ T_NormalWord id [start, middle, end]
char ']'
return $ TA_Index id middle
literal s = do
id <- getNextId
@@ -511,7 +519,7 @@ readArithmeticContents =
readNormalDollar,
readBraced,
readBackTicked,
readNormalLiteral "+-*/=%^,]"
readNormalLiteral "+-*/=%^,]?:"
]
spacing
return $ TA_Expansion id pieces
@@ -596,7 +604,7 @@ readArithmeticContents =
id <- getNextId
op <- try $ string "++" <|> string "--"
spacing
return $ TA_Unary id ("|" ++ op) x
return $ TA_Unary id ('|':op) x
<|>
return x
@@ -613,8 +621,10 @@ prop_readCondition6 = isOk readCondition "[[ $c =~ ^[yY]$ ]]"
prop_readCondition7 = isOk readCondition "[[ ${line} =~ ^[[:space:]]*# ]]"
prop_readCondition8 = isOk readCondition "[[ $l =~ ogg|flac ]]"
prop_readCondition9 = isOk readCondition "[ foo -a -f bar ]"
prop_readCondition10= isOk readCondition "[[ a == b \n || c == d ]]"
prop_readCondition11= isOk readCondition "[[ a == b || \n c == d ]]"
prop_readCondition10= isOk readCondition "[[\na == b\n||\nc == d ]]"
prop_readCondition10a= isOk readCondition "[[\na == b ||\nc == d ]]"
prop_readCondition10b= isOk readCondition "[[ a == b\n||\nc == d ]]"
prop_readCondition11= isOk readCondition "[[ a == b ||\n c == d ]]"
prop_readCondition12= isWarning readCondition "[ a == b \n -o c == d ]"
prop_readCondition13= isOk readCondition "[[ foo =~ ^fo{1,3}$ ]]"
readCondition = called "test expression" $ do
@@ -622,9 +632,17 @@ readCondition = called "test expression" $ do
id <- getNextId
open <- try (string "[[") <|> string "["
let single = open == "["
condSpacingMsg False $ if single
then "You need spaces after the opening [ and before the closing ]."
else "You need spaces after the opening [[ and before the closing ]]."
pos <- getPosition
space <- allspacing
when (null space) $
parseProblemAt pos ErrorC 1035 $ "You need a space after the " ++
if single
then "[ and before the ]."
else "[[ and before the ]]."
when (single && '\n' `elem` space) $
parseProblemAt pos ErrorC 1080 "You need \\ before line feeds to break lines in [ ]."
condition <- readConditionContents single
cpos <- getPosition
@@ -635,14 +653,6 @@ readCondition = called "test expression" $ do
many readCmdWord -- Read and throw away remainders to get then/do warnings. Fixme?
return $ T_Condition id (if single then SingleBracket else DoubleBracket) condition
hardCondSpacing = condSpacingMsg False "You need a space here."
softCondSpacing = condSpacingMsg True "You need a space here."
condSpacingMsg soft msg = do
pos <- getPosition
space <- spacing
when (null space) $ (if soft then parseNoteAt else parseProblemAt) pos ErrorC 1035 msg
readAnnotationPrefix = do
char '#'
many linewhitespace
@@ -755,11 +765,10 @@ readDollarBracedLiteral = do
prop_readProcSub1 = isOk readProcSub "<(echo test | wc -l)"
prop_readProcSub2 = isOk readProcSub "<( if true; then true; fi )"
prop_readProcSub3 = isOk readProcSub "=(ls)"
readProcSub = called "process substitution" $ do
id <- getNextId
dir <- try $ do
x <- oneOf "<>="
x <- oneOf "<>"
char '('
return [x]
allspacing
@@ -811,6 +820,8 @@ prop_readBackTicked3 = isWarning readBackTicked "´grep \"\\\"\"´"
prop_readBackTicked4 = isOk readBackTicked "`echo foo\necho bar`"
prop_readBackTicked5 = isOk readSimpleCommand "echo `foo`bar"
prop_readBackTicked6 = isWarning readSimpleCommand "echo `foo\necho `bar"
prop_readBackTicked7 = isOk readSimpleCommand "`#inline comment`"
prop_readBackTicked8 = isOk readSimpleCommand "echo `#comment` \\\nbar baz"
readBackTicked = called "backtick expansion" $ do
id <- getNextId
startPos <- getPosition
@@ -826,7 +837,7 @@ readBackTicked = called "backtick expansion" $ do
suggestForgotClosingQuote startPos endPos "backtick expansion"
-- Result positions may be off due to escapes
result <- subParse subStart readCompoundList (unEscape subString)
result <- subParse subStart readTermOrNone (unEscape subString)
return $ T_Backticked id result
where
unEscape [] = []
@@ -939,7 +950,7 @@ readNormalEscaped = called "escaped char" $ do
pos <- getPosition
backslash
do
next <- quotable <|> oneOf "?*@!+[]{}.,"
next <- quotable <|> oneOf "?*@!+[]{}.,~#"
return $ if next == '\n' then "" else [next]
<|>
do
@@ -1084,6 +1095,7 @@ readDollarBracket = called "$[..] expression" $ do
string "]"
return (T_DollarBracket id c)
prop_readArithmeticExpression = isOk readArithmeticExpression "((a?b:c))"
readArithmeticExpression = called "((..)) command" $ do
id <- getNextId
try (string "((")
@@ -1111,23 +1123,33 @@ readDollarExpansion = called "command expansion" $ do
return $ T_DollarExpansion id cmds
prop_readDollarVariable = isOk readDollarVariable "$@"
prop_readDollarVariable2 = isOk (readDollarVariable >> anyChar) "$?!"
prop_readDollarVariable3 = isWarning (readDollarVariable >> anyChar) "$10"
prop_readDollarVariable4 = isWarning (readDollarVariable >> string "[@]") "$arr[@]"
readDollarVariable = do
id <- getNextId
pos <- getPosition
let singleCharred p = do
n <- p
value <- wrap [n]
return (T_DollarBraced id value) `attempting` do
pos <- getPosition
num <- lookAhead $ many1 p
parseNoteAt pos ErrorC 1037 $ "$" ++ (n:num) ++ " is equivalent to ${" ++ [n] ++ "}"++ num ++"."
return (T_DollarBraced id value)
let positional = do
value <- singleCharred digit
return value `attempting` do
lookAhead digit
parseNoteAt pos ErrorC 1037 "Braces are required for positionals over 9, e.g. ${10}."
let positional = singleCharred digit
let special = singleCharred specialVariable
let regular = do
name <- readVariableName
value <- wrap name
return $ T_DollarBraced id value
return (T_DollarBraced id value) `attempting` do
lookAhead $ void (string "[@]") <|> void (string "[*]") <|> void readArrayIndex
parseNoteAt pos ErrorC 1087 "Braces are required when expanding arrays, as in ${array[idx]}."
try $ char '$' >> (positional <|> special <|> regular)
@@ -1335,7 +1357,6 @@ prop_readSimpleCommand3 = isOk readSimpleCommand "export foo=(bar baz)"
prop_readSimpleCommand4 = isOk readSimpleCommand "typeset -a foo=(lol)"
prop_readSimpleCommand5 = isOk readSimpleCommand "time if true; then echo foo; fi"
prop_readSimpleCommand6 = isOk readSimpleCommand "time -p ( ls -l; )"
prop_readSimpleCommand7 = isOk readSimpleCommand "cat =(ls)"
readSimpleCommand = called "simple command" $ do
id1 <- getNextId
id2 <- getNextId
@@ -1390,6 +1411,12 @@ readAndOr = do
then andOr
else T_Annotation aid annotations andOr
readTermOrNone = do
allspacing
readTerm <|> do
eof
return []
readTerm = do
allspacing
m <- readAndOr
@@ -1433,7 +1460,11 @@ readPipe = do
spacing
return $ T_Pipe id ('|':qualifier)
readCommand = readCompoundCommand <|> readSimpleCommand
readCommand = choice [
readCompoundCommand,
readCoProc,
readSimpleCommand
]
readCmdName = do
f <- readNormalWord
@@ -1460,6 +1491,7 @@ readIfClause = called "if expression" $ do
g_Fi `orFail` do
parseProblemAt pos ErrorC 1046 "Couldn't find 'fi' for this 'if'."
parseProblem ErrorC 1047 "Expected 'fi' matching previously mentioned 'if'."
return "Expected 'fi'."
return $ T_IfExpression id ((condition, action):elifs) elses
@@ -1475,12 +1507,13 @@ readIfPart = do
allspacing
condition <- readTerm
optional (do
try . lookAhead $ g_Fi
parseProblemAt pos ErrorC 1049 "Did you forget the 'then' for this 'if'?")
ifNextToken (g_Fi <|> g_Elif) $
parseProblemAt pos ErrorC 1049 "Did you forget the 'then' for this 'if'?"
called "then clause" $ do
g_Then `orFail` parseProblem ErrorC 1050 "Expected 'then'."
g_Then `orFail` do
parseProblem ErrorC 1050 "Expected 'then'."
return "Expected 'then'."
acceptButWarn g_Semi ErrorC 1051 "No semicolons directly after 'then'."
allspacing
@@ -1496,6 +1529,10 @@ readElifPart = called "elif clause" $ do
parseProblemAt pos ErrorC 1075 "Use 'elif' instead of 'else if'."
allspacing
condition <- readTerm
ifNextToken (g_Fi <|> g_Elif) $
parseProblemAt pos ErrorC 1049 "Did you forget the 'then' for this 'elif'?"
g_Then
acceptButWarn g_Semi ErrorC 1052 "No semicolons directly after 'then'."
allspacing
@@ -1514,6 +1551,11 @@ readElsePart = called "else clause" $ do
verifyNotEmptyIf "else"
readTerm
ifNextToken parser action =
optional $ do
try . lookAhead $ parser
action
prop_readSubshell = isOk readSubshell "( cd /foo; tar cf stuff.tar * )"
readSubshell = called "explicit subshell" $ do
id <- getNextId
@@ -1537,7 +1579,7 @@ readBraceGroup = called "brace group" $ do
list <- readTerm
char '}' <|> do
parseProblem ErrorC 1056 "Expected a '}'. If you have one, try a ; or \\n in front of it."
fail "Unable to parse"
fail "Missing '}'"
return $ T_BraceGroup id list
prop_readWhileClause = isOk readWhileClause "while [[ -e foo ]]; do sleep 1; done"
@@ -1562,7 +1604,9 @@ readDoGroup loopPos = do
try . lookAhead $ g_Done
parseProblemAt loopPos ErrorC 1057 "Did you forget the 'do' for this loop?")
g_Do `orFail` parseProblem ErrorC 1058 "Expected 'do'."
g_Do `orFail` do
parseProblem ErrorC 1058 "Expected 'do'."
return "Expected 'do'."
acceptButWarn g_Semi ErrorC 1059 "No semicolons directly after 'do'."
allspacing
@@ -1575,6 +1619,7 @@ readDoGroup loopPos = do
g_Done `orFail` do
parseProblemAt pos ErrorC 1061 "Couldn't find 'done' for this 'do'."
parseProblem ErrorC 1062 "Expected 'done' matching previously mentioned 'do'."
return "Expected 'done'."
return commands
@@ -1587,12 +1632,12 @@ prop_readForClause7 = isOk readForClause "for ((;;)) do echo $i\ndone"
prop_readForClause8 = isOk readForClause "for ((;;)) ; do echo $i\ndone"
prop_readForClause9 = isOk readForClause "for i do true; done"
prop_readForClause10= isOk readForClause "for ((;;)) { true; }"
prop_readForClause11= isOk readForClause "for a b in *; do echo $a $b; done"
prop_readForClause12= isWarning readForClause "for $a in *; do echo \"$a\"; done"
readForClause = called "for loop" $ do
pos <- getPosition
(T_For id) <- g_For
spacing
readRegular id pos <|> readArithmetic id pos
readArithmetic id pos <|> readRegular id pos
where
readArithmetic id pos = called "arithmetic for condition" $ do
try $ string "(("
@@ -1613,25 +1658,12 @@ readForClause = called "for loop" $ do
return list
readRegular id pos = do
names <- readNames
readShort names <|> readLong names
where
readLong names = do
values <- readInClause <|> (optional readSequentialSep >> return [])
group <- readDoGroup pos
return $ T_ForIn id NormalForIn names values group
readShort names = do
char '('
allspacing
words <- many (readNormalWord `thenSkip` allspacing)
char ')'
allspacing
command <- readAndOr
return $ T_ForIn id ShortForIn names words [command]
readNames =
reluctantlyTill1 (readVariableName `thenSkip` spacing) $
disregard g_Do <|> disregard readInClause <|> disregard readSequentialSep
acceptButWarn (char '$') ErrorC 1086
"Don't use $ on the iterator name in for loops."
name <- readVariableName `thenSkip` spacing
values <- readInClause <|> (optional readSequentialSep >> return [])
group <- readDoGroup pos
return $ T_ForIn id name values group
prop_readSelectClause1 = isOk readSelectClause "select foo in *; do echo $foo; done"
prop_readSelectClause2 = isOk readSelectClause "select foo; do echo $foo; done"
@@ -1687,7 +1719,10 @@ readCaseItem = called "case item" $ do
optional g_Lparen
spacing
pattern <- readPattern
g_Rparen
void g_Rparen <|> do
parseProblem ErrorC 1085
"Did you forget to move the ;; after extending this case item?"
fail "Expected ) to open a new case item"
readLineBreak
list <- (lookAhead readCaseSeparator >> return []) <|> readCompoundList
separator <- readCaseSeparator `attempting` do
@@ -1749,7 +1784,31 @@ readFunctionDefinition = called "function" $ do
g_Rparen
return ()
readFunctionName = many functionChars
readFunctionName = many1 functionChars
prop_readCoProc1 = isOk readCoProc "coproc foo { echo bar; }"
prop_readCoProc2 = isOk readCoProc "coproc { echo bar; }"
prop_readCoProc3 = isOk readCoProc "coproc echo bar"
readCoProc = called "coproc" $ do
id <- getNextId
try $ do
string "coproc"
whitespace
choice [ try $ readCompoundCoProc id, readSimpleCoProc id ]
where
readCompoundCoProc id = do
var <- optionMaybe $
readVariableName `thenSkip` whitespace
body <- readBody readCompoundCommand
return $ T_CoProc id var body
readSimpleCoProc id = do
body <- readBody readSimpleCommand
return $ T_CoProc id Nothing body
readBody parser = do
id <- getNextId
body <- parser
return $ T_CoProcBody id body
readPattern = (readNormalWord `thenSkip` spacing) `sepBy1` (char '|' `thenSkip` spacing)
@@ -1793,8 +1852,7 @@ readLetSuffix = many1 (readIoRedirect <|> try readLetExpression <|> readCmdWord)
-- Get whatever a parser would parse as a string
readStringForParser parser = do
pos <- lookAhead (parser >> getPosition)
s <- readUntil pos
return s
readUntil pos
where
readUntil endPos = anyChar `reluctantlyTill` (getPosition >>= guard . (== endPos))
@@ -1807,32 +1865,32 @@ prop_readAssignmentWord6 = isWarning readAssignmentWord "b += (1 2 3)"
prop_readAssignmentWord7 = isOk readAssignmentWord "a[3$n'']=42"
prop_readAssignmentWord8 = isOk readAssignmentWord "a[4''$(cat foo)]=42"
prop_readAssignmentWord9 = isOk readAssignmentWord "IFS= "
prop_readAssignmentWord9a= isOk readAssignmentWord "foo="
prop_readAssignmentWord10= isWarning readAssignmentWord "foo$n=42"
prop_readAssignmentWord11= isOk readAssignmentWord "foo=([a]=b [c] [d]= [e f )"
prop_readAssignmentWord12= isOk readAssignmentWord "a[b <<= 3 + c]='thing'"
readAssignmentWord = try $ do
id <- getNextId
pos <- getPosition
optional (char '$' >> parseNote ErrorC 1066 "Don't use $ on the left side of assignments.")
variable <- readVariableName
notFollowedBy2 $ do -- Special case for zsh =(..) syntax
spacing1
string "=("
optional (readNormalDollar >> parseNoteAt pos ErrorC
1067 "For indirection, use (associative) arrays or 'read \"var$n\" <<< \"value\"'")
index <- optionMaybe readArrayIndex
space <- spacing
hasLeftSpace <- liftM (not . null) spacing
pos <- getPosition
op <- readAssignmentOp
space2 <- spacing
if space == "" && space2 /= ""
hasRightSpace <- liftM (not . null) spacing
isEndOfCommand <- liftM isJust $ optionMaybe (try . lookAhead $ (disregard (oneOf "\r\n;&|)") <|> eof))
if not hasLeftSpace && (hasRightSpace || isEndOfCommand)
then do
when (variable /= "IFS") $
when (variable /= "IFS" && hasRightSpace) $
parseNoteAt pos WarningC 1007
"Remove space after = if trying to assign a value (for empty string, use var='' ... )."
value <- readEmptyLiteral
return $ T_Assignment id op variable index value
else do
when (space /= "" || space2 /= "") $
when (hasLeftSpace || hasRightSpace) $
parseNoteAt pos ErrorC 1068 "Don't put spaces around the = in assignments."
value <- readArray <|> readNormalWord
spacing
@@ -1844,14 +1902,10 @@ readAssignmentWord = try $ do
id <- getNextId
return $ T_Literal id ""
-- This is only approximate. Fixme?
-- * Bash allows foo[' ' "" $(true) 2 ``]=var
-- * foo[bar] dereferences bar
readArrayIndex = do
char '['
optional space
x <- readNormalishWord "]"
optional space
x <- readArithmeticContents
char ']'
return x
@@ -1903,8 +1957,8 @@ tryParseWordToken keyword t = try $ do
"Scripts are case sensitive. Use '" ++ keyword ++ "', not '" ++ str ++ "'."
return $ t id
anycaseString =
mapM anycaseChar
anycaseString str =
mapM anycaseChar str <?> str
where
anycaseChar c = char (toLower c) <|> char (toUpper c)
@@ -1942,10 +1996,12 @@ g_Rparen = tryToken ")" T_Rparen
g_Bang = do
id <- getNextId
char '!'
softCondSpacing
void spacing1 <|> do
pos <- getPosition
parseProblemAt pos ErrorC 1035
"You are missing a required space after the !."
return $ T_Bang id
g_Semi = do
notFollowedBy2 g_DSEMI
tryToken ";" T_Semi
@@ -1958,12 +2014,21 @@ readKeyword = choice [ g_Then, g_Else, g_Elif, g_Fi, g_Do, g_Done, g_Esac, g_Rbr
ifParse p t f =
(lookAhead (try p) >> t) <|> f
prop_readShebang1 = isOk readShebang "#!/bin/sh\n"
prop_readShebang2 = isWarning readShebang "!# /bin/sh\n"
readShebang = do
try $ string "#!"
try readCorrect <|> try readSwapped
str <- many $ noneOf "\r\n"
optional carriageReturn
optional linefeed
return str
where
readCorrect = void $ string "#!"
readSwapped = do
pos <- getPosition
string "!#"
parseProblemAt pos ErrorC 1084
"Use #!, not !#, for the shebang."
prop_readScript1 = isOk readScript "#!/bin/bash\necho hello world\n"
prop_readScript2 = isWarning readScript "#!/bin/bash\r\necho hello world\n"
@@ -1987,11 +2052,11 @@ readScript = do
return $ T_Script id sb commands;
} <|> do {
parseProblem WarningC 1014 "Couldn't read any commands.";
return $ T_Script id sb [T_EOF id];
return $ T_Script id sb []
}
else do
many anyChar
return $ T_Script id sb [T_EOF id];
return $ T_Script id sb [];
where
basename s = reverse . takeWhile (/= '/') . reverse $ s
@@ -2007,8 +2072,8 @@ readScript = do
verifyShell pos s =
case isValidShell s of
Just True -> return ()
Just False -> parseProblemAt pos ErrorC 1071 "ShellCheck only supports Bourne based shell scripts, sorry!"
Nothing -> parseProblemAt pos InfoC 1008 "This shebang was unrecognized. Note that ShellCheck only handles Bourne based shells."
Just False -> parseProblemAt pos ErrorC 1071 "ShellCheck only supports sh/bash/ksh scripts. Sorry!"
Nothing -> parseProblemAt pos InfoC 1008 "This shebang was unrecognized. Note that ShellCheck only handles sh/bash/ksh."
isValidShell s =
let good = s == "" || any (`isPrefixOf` s) goodShells
@@ -2022,9 +2087,10 @@ readScript = do
goodShells = [
"sh",
"ash",
"dash",
"bash",
"ksh",
"zsh"
"ksh"
]
badShells = [
"awk",
@@ -2032,7 +2098,8 @@ readScript = do
"perl",
"python",
"ruby",
"tcsh"
"tcsh",
"zsh"
]
readUtf8Bom = called "Byte Order Mark" $ string "\xFEFF"
@@ -2060,28 +2127,29 @@ sortNotes = sortBy compareNotes
data ParseResult = ParseResult { parseResult :: Maybe (Token, Map.Map Id SourcePos), parseNotes :: [ParseNote] } deriving (Show)
makeErrorFor parsecError =
ParseNote (errorPos parsecError) ErrorC 1072 $ getStringFromParsec $ errorMessages parsecError
ParseNote (errorPos parsecError) ErrorC 1072 $
getStringFromParsec $ errorMessages parsecError
getStringFromParsec errors =
case map snd $ sortWith fst $ map f errors of
r -> unwords (take 1 $ nub r) ++ " Fix any mentioned problems and try again."
where f err =
case map f errors of
r -> unwords (take 1 $ catMaybes $ reverse r) ++
" Fix any mentioned problems and try again."
where
f err =
case err of
UnExpect s -> (1, unexpected s)
SysUnExpect s -> (2, unexpected s)
Expect s -> (3, "Expected " ++ s ++ ".")
Message s -> (4, s ++ ".")
wut "" = "eof"
wut x = x
unexpected s = "Unexpected " ++ wut s ++ "."
UnExpect s -> return $ unexpected s
SysUnExpect s -> return $ unexpected s
Expect s -> return $ "Expected " ++ s ++ "."
Message s -> if null s then Nothing else return $ s ++ "."
unexpected s = "Unexpected " ++ (if null s then "eof" else s) ++ "."
parseShell filename contents =
parseShell options filename contents =
case rp (parseWithNotes readScript) filename contents of
(Right (script, map, notes), (parsenotes, _)) ->
ParseResult (Just (script, map)) (nub $ sortNotes $ notes ++ parsenotes)
ParseResult (Just (script, map)) (nub . sortNotes . excludeNotes $ notes ++ parsenotes)
(Left err, (p, context)) ->
ParseResult Nothing
(nub $ sortNotes $ p ++ notesForContext context ++ [makeErrorFor err])
(nub . sortNotes . excludeNotes $ p ++ notesForContext context ++ [makeErrorFor err])
where
isName (ContextName _ _) = True
isName _ = False
@@ -2090,6 +2158,7 @@ parseShell filename contents =
"Couldn't parse this " ++ str ++ "."
second (ContextName pos str) = ParseNote pos InfoC 1009 $
"The mentioned parser error was in this " ++ str ++ "."
excludeNotes = filter (\c -> codeForParseNote c `notElem` optionExcludes options)
lt x = trace (show x) x
ltt t = trace (show t)

View File

@@ -18,16 +18,17 @@
{-# LANGUAGE TemplateHaskell #-}
module ShellCheck.Simple (shellCheck, ShellCheckComment, scLine, scColumn, scSeverity, scCode, scMessage, runTests) where
import ShellCheck.Parser hiding (runTests)
import ShellCheck.Analytics hiding (runTests)
import Data.Maybe
import Text.Parsec.Pos
import Data.List
import Data.Maybe
import ShellCheck.Analytics hiding (runTests)
import ShellCheck.Options
import ShellCheck.Parser hiding (runTests)
import Test.QuickCheck.All (quickCheckAll)
import Text.Parsec.Pos
shellCheck :: String -> [AnalysisOption] -> [ShellCheckComment]
shellCheck script options =
let (ParseResult result notes) = parseShell "-" script in
shellCheck :: AnalysisOptions -> String -> [ShellCheckComment]
shellCheck options script =
let (ParseResult result notes) = parseShell options "-" script in
let allNotes = notes ++ concat (maybeToList $ do
(tree, posMap) <- result
let list = runAnalytics options tree
@@ -51,21 +52,28 @@ severityToString s =
formatNote (ParseNote pos severity code text) =
ShellCheckComment (sourceLine pos) (sourceColumn pos) (severityToString severity) (fromIntegral code) text
testCheck = shellCheck defaultAnalysisOptions { optionExcludes = [2148] } -- Ignore #! warnings
prop_findsParseIssue =
let comments = shellCheck "echo \"$12\"" [] in
let comments = testCheck "echo \"$12\"" in
length comments == 1 && scCode (head comments) == 1037
prop_commentDisablesParseIssue1 =
null $ shellCheck "#shellcheck disable=SC1037\necho \"$12\"" []
null $ testCheck "#shellcheck disable=SC1037\necho \"$12\""
prop_commentDisablesParseIssue2 =
null $ shellCheck "#shellcheck disable=SC1037\n#lol\necho \"$12\"" []
null $ testCheck "#shellcheck disable=SC1037\n#lol\necho \"$12\""
prop_findsAnalysisIssue =
let comments = shellCheck "echo $1" [] in
let comments = testCheck "echo $1" in
length comments == 1 && scCode (head comments) == 2086
prop_commentDisablesAnalysisIssue1 =
null $ shellCheck "#shellcheck disable=SC2086\necho $1" []
null $ testCheck "#shellcheck disable=SC2086\necho $1"
prop_commentDisablesAnalysisIssue2 =
null $ shellCheck "#shellcheck disable=SC2086\n#lol\necho $1" []
null $ testCheck "#shellcheck disable=SC2086\n#lol\necho $1"
prop_optionDisablesIssue1 =
null $ shellCheck (defaultAnalysisOptions { optionExcludes = [2086, 2148] }) "echo $1"
prop_optionDisablesIssue2 =
null $ shellCheck (defaultAnalysisOptions { optionExcludes = [2148, 1037] }) "echo \"$10\""
return []
runTests = $quickCheckAll

View File

@@ -16,25 +16,43 @@ errors and pitfalls where the shell just gives a cryptic error message or
strange behavior, but it also reports on a few more advanced issues where
corner cases can cause delayed failures.
ShellCheck gives shell specific advice. Consider the line:
(( area = 3.14*r*r ))
+ For scripts starting with `#!/bin/sh` (or when using `-s sh`), ShellCheck
will warn that `(( .. ))` is not POSIX compliant (similar to checkbashisms).
+ For scripts starting with `#!/bin/bash` (or using `-s bash`), ShellCheck
will warn that decimals are not supported.
+ For scripts starting with `#!/bin/ksh` (or using `-s ksh`), ShellCheck will
not warn at all, as `ksh` supports decimals in arithmetic contexts.
# OPTIONS
**-f** *FORMAT*, **--format=***FORMAT*
: Specify the output format of shellcheck, which prints its results in the
standard output. Subsequent **-f** options are ignored, see **FORMATS**
below for more information.
**-e**\ *CODE1*[,*CODE2*...],\ **--exclude=***CODE1*[,*CODE2*...]
: Explicitly exclude the specified codes from the report. Subsequent **-e**
options are cumulative, but all the codes can be specified at once,
comma-separated as a single argument.
**-f** *FORMAT*, **--format=***FORMAT*
: Specify the output format of shellcheck, which prints its results in the
standard output. Subsequent **-f** options are ignored, see **FORMATS**
below for more information.
**-s**\ *shell*,\ **--shell=***shell*
: Specify Bourne shell dialect. Valid values are *sh*, *bash*, *ksh* and
*zsh*. The default is to use the file's shebang, or *bash* if the target
shell can't be determined.
: Specify Bourne shell dialect. Valid values are *sh*, *bash* and *ksh*.
The default is to use the file's shebang, or *bash* if the target shell
can't be determined.
**-V**\ *version*,\ **--version**
: Print version and exit.
# FORMATS
@@ -79,11 +97,12 @@ corner cases can cause delayed failures.
[
{
"line": line,
"column": column,
"level": level,
"code": ####,
"message": message
"file": "filename",
"line": lineNumber,
"column": columnNumber,
"level": "severitylevel",
"code": errorCode,
"message": "warning message"
},
...
]
@@ -100,6 +119,14 @@ For example, to suppress SC2035 about using `./*.jpg`:
# shellcheck disable=SC2035
echo "Files: " *.jpg
Here a shell brace group is used to suppress on multiple lines:
# shellcheck disable=SC2016
{
echo 'Modifying $PATH'
echo 'PATH=foo:$PATH' >> ~/.bashrc
}
Valid keys are:
**disable**

View File

@@ -17,12 +17,17 @@
-}
import Control.Exception
import Control.Monad
import Control.Monad.Trans
import Control.Monad.Trans.Error
import Control.Monad.Trans.List
import Data.Char
import Data.Maybe
import Data.Monoid
import GHC.Exts
import GHC.IO.Device
import Prelude hiding (catch)
import ShellCheck.Data
import ShellCheck.Options
import ShellCheck.Simple
import ShellCheck.Analytics
import System.Console.GetOpt
@@ -34,26 +39,35 @@ import Text.JSON
import qualified Data.Map as Map
data Flag = Flag String String
data Status = NoProblems | SomeProblems | BadInput | SupportFailure | SyntaxFailure | RuntimeException deriving (Ord, Eq)
data JsonComment = JsonComment FilePath ShellCheckComment
instance Error Status where
noMsg = RuntimeException
instance Monoid Status where
mempty = NoProblems
mappend = max
header = "Usage: shellcheck [OPTIONS...] FILES..."
options = [
Option ['f'] ["format"]
(ReqArg (Flag "format") "FORMAT") "output format",
Option ['e'] ["exclude"]
Option "e" ["exclude"]
(ReqArg (Flag "exclude") "CODE1,CODE2..") "exclude types of warnings",
Option ['s'] ["shell"]
(ReqArg (Flag "shell") "SHELLNAME") "Specify dialect (bash,sh,ksh,zsh)",
Option ['V'] ["version"]
Option "f" ["format"]
(ReqArg (Flag "format") "FORMAT") "output format",
Option "s" ["shell"]
(ReqArg (Flag "shell") "SHELLNAME") "Specify dialect (bash,sh,ksh)",
Option "V" ["version"]
(NoArg $ Flag "version" "true") "Print version information"
]
printErr = hPutStrLn stderr
syntaxFailure = ExitFailure 3
supportFailure = ExitFailure 4
instance JSON ShellCheckComment where
showJSON c = makeObj [
instance JSON (JsonComment) where
showJSON (JsonComment filename c) = makeObj [
("file", showJSON $ filename),
("line", showJSON $ scLine c),
("column", showJSON $ scColumn c),
("level", showJSON $ scSeverity c),
@@ -62,16 +76,15 @@ instance JSON ShellCheckComment where
]
readJSON = undefined
parseArguments :: [String] -> ErrorT Status IO ([Flag], [FilePath])
parseArguments argv =
case getOpt Permute options argv of
(opts, files, []) -> do
verifyOptions opts files
return $ Just (opts, files)
(opts, files, []) -> return (opts, files)
(_, _, errors) -> do
printErr $ concat errors ++ "\n" ++ usageInfo header options
exitWith syntaxFailure
liftIO . printErr $ concat errors ++ "\n" ++ usageInfo header options
throwError SyntaxFailure
formats :: Map.Map String (AnalysisOptions -> [FilePath] -> IO Status)
formats = Map.fromList [
("json", forJson),
("gcc", forGcc),
@@ -79,9 +92,21 @@ formats = Map.fromList [
("tty", forTty)
]
toStatus = liftM (either id (const NoProblems)) . runErrorT
catchExceptions :: IO Status -> IO Status
catchExceptions action = action -- action `catch` handler
where
handler err = do
printErr $ show (err :: SomeException)
return RuntimeException
checkComments comments = if null comments then NoProblems else SomeProblems
forTty :: AnalysisOptions -> [FilePath] -> IO Status
forTty options files = do
output <- mapM doFile files
return $ and output
return $ mconcat output
where
clear = ansi 0
ansi n = "\x1B[" ++ show n ++ "m"
@@ -97,7 +122,7 @@ forTty options files = do
colorComment level comment =
ansi (colorForLevel level) ++ comment ++ clear
doFile path = do
doFile path = catchExceptions $ do
contents <- readContents path
doInput path contents
@@ -119,34 +144,38 @@ forTty options files = do
mapM_ (\c -> putStrLn (colorFunc (scSeverity c) $ cuteIndent c)) x
putStrLn ""
) groups
return $ null comments
return . checkComments $ comments
cuteIndent comment =
replicate (scColumn comment - 1) ' ' ++
"^-- " ++ code (scCode comment) ++ ": " ++ scMessage comment
code code = "SC" ++ (show code)
code code = "SC" ++ show code
getColorFunc = do
term <- hIsTerminalDevice stdout
return $ if term then colorComment else const id
-- This totally ignores the filenames. Fixme?
forJson options files = do
comments <- liftM concat $ mapM (commentsFor options) files
forJson :: AnalysisOptions -> [FilePath] -> IO Status
forJson options files = catchExceptions $ do
comments <- runListT $ do
file <- ListT $ return files
comment <- ListT $ commentsFor options file
return $ JsonComment file comment
putStrLn $ encodeStrict comments
return . null $ comments
return $ checkComments comments
-- Mimic GCC "file:line:col: (error|warning|note): message" format
forGcc :: AnalysisOptions -> [FilePath] -> IO Status
forGcc options files = do
files <- mapM process files
return $ and files
return $ mconcat files
where
process file = do
process file = catchExceptions $ do
contents <- readContents file
let comments = makeNonVirtual (getComments options contents) contents
mapM_ (putStrLn . format file) comments
return $ null comments
return $ checkComments comments
format filename c = concat [
filename, ":",
@@ -162,20 +191,18 @@ forGcc options files = do
]
-- Checkstyle compatible output. A bit of a hack to avoid XML dependencies
forCheckstyle :: AnalysisOptions -> [FilePath] -> IO Status
forCheckstyle options files = do
putStrLn "<?xml version='1.0' encoding='UTF-8'?>"
putStrLn "<checkstyle version='4.3'>"
statuses <- mapM (\x -> process x `catch` report) files
statuses <- mapM process files
putStrLn "</checkstyle>"
return $ and statuses
return $ mconcat statuses
where
process file = do
process file = catchExceptions $ do
comments <- commentsFor options file
putStrLn (formatFile file comments)
return $ null comments
report error = do
printErr $ show (error :: SomeException)
return False
return $ checkComments comments
severity "error" = "error"
severity "warning" = "warning"
@@ -197,31 +224,31 @@ forCheckstyle options files = do
attr "column" $ show . scColumn $ c,
attr "severity" $ severity . scSeverity $ c,
attr "message" $ scMessage c,
attr "source" $ "ShellCheck.SC" ++ (show $ scCode c),
attr "source" $ "ShellCheck.SC" ++ show (scCode c),
"/>\n"
]
commentsFor options file =
liftM (getComments options) $ readContents file
commentsFor options file = liftM (getComments options) $ readContents file
getComments options contents =
excludeCodes (getExclusions options) $ shellCheck contents analysisOptions
where
analysisOptions = catMaybes [ shellOption ]
shellOption = do
option <- getOption options "shell"
sh <- shellForExecutable option
return $ ForceShell sh
getComments = shellCheck
readContents file = if file == "-" then getContents else readFile file
readContents :: FilePath -> IO String
readContents file =
if file == "-"
then getContents
else readFile file
-- Realign comments from a tabstop of 8 to 1
makeNonVirtual comments contents =
map fix comments
where
ls = lines contents
fix c = c { scColumn = real (ls !! (scLine c - 1)) 0 0 (scColumn c) }
fix c = c {
scColumn =
if scLine c > 0 && scLine c <= length ls
then real (ls !! (scLine c - 1)) 0 0 (scColumn c)
else scColumn c
}
real _ r v target | target <= v = r
real [] r v _ = r -- should never happen
real ('\t':rest) r v target =
@@ -240,7 +267,7 @@ split char str =
where
split' (a:rest) element =
if a == char
then (reverse element) : split' rest []
then reverse element : split' rest []
else split' rest (a:element)
split' [] element = [reverse element]
@@ -257,45 +284,71 @@ excludeCodes codes =
main = do
args <- getArgs
parsedArgs <- parseArguments args
code <- do
status <- process parsedArgs
return $ if status then ExitSuccess else ExitFailure 1
`catch` return
`catch` \err -> do
printErr $ show (err :: SomeException)
return $ ExitFailure 2
exitWith code
status <- toStatus $ do
(flags, files) <- parseArguments args
process flags files
exitWith $ statusToCode status
process Nothing = return False
process (Just (options, files)) =
let format = fromMaybe "tty" $ getOption options "format" in
statusToCode status =
case status of
NoProblems -> ExitSuccess
SomeProblems -> ExitFailure 1
BadInput -> ExitFailure 5
SyntaxFailure -> ExitFailure 3
SupportFailure -> ExitFailure 4
RuntimeException -> ExitFailure 2
process :: [Flag] -> [FilePath] -> ErrorT Status IO ()
process flags files = do
options <- foldM (flip parseOption) defaultAnalysisOptions flags
verifyFiles files
let format = fromMaybe "tty" $ getOption flags "format"
case Map.lookup format formats of
Nothing -> do
printErr $ "Unknown format " ++ format
printErr $ "Supported formats:"
mapM_ (printErr . write) $ Map.keys formats
exitWith supportFailure
liftIO $ do
printErr $ "Unknown format " ++ format
printErr "Supported formats:"
mapM_ (printErr . write) $ Map.keys formats
throwError SupportFailure
where write s = " " ++ s
Just f -> do
f options files
Just f -> ErrorT $ liftM Left $ f options files
verifyOptions opts files = do
when (isJust $ getOption opts "version") printVersionAndExit
parseOption flag options =
case flag of
Flag "shell" str ->
fromMaybe (die $ "Unknown shell: " ++ str) $ do
shell <- shellForExecutable str
return $ return options { optionShellType = Just shell }
let shell = getOption opts "shell" in
when (isJust shell && isNothing (shell >>= shellForExecutable)) $ do
printErr $ "Unknown shell: " ++ (fromJust shell)
exitWith supportFailure
Flag "exclude" str -> do
new <- mapM parseNum $ split ',' str
let old = optionExcludes options
return options { optionExcludes = new ++ old }
Flag "version" _ -> do
liftIO printVersion
throwError NoProblems
_ -> return options
where
die s = do
liftIO $ printErr s
throwError SupportFailure
parseNum ('S':'C':str) = parseNum str
parseNum num = do
unless (all isDigit num) $ do
liftIO . printErr $ "Bad exclusion: " ++ num
throwError SyntaxFailure
return (Prelude.read num :: Integer)
verifyFiles files =
when (null files) $ do
printErr "No files specified.\n"
printErr $ usageInfo header options
exitWith syntaxFailure
liftIO $ printErr "No files specified.\n"
liftIO $ printErr $ usageInfo header options
throwError SyntaxFailure
printVersionAndExit = do
putStrLn $ "ShellCheck - shell script analysis tool"
printVersion = do
putStrLn "ShellCheck - shell script analysis tool"
putStrLn $ "version: " ++ shellcheckVersion
putStrLn $ "license: GNU Affero General Public License, version 3"
putStrLn $ "website: http://www.shellcheck.net"
exitWith ExitSuccess
putStrLn "license: GNU Affero General Public License, version 3"
putStrLn "website: http://www.shellcheck.net"