57 Commits

Author SHA1 Message Date
Vidar Holen
8c3d8d7cfa Stable version 0.3.0 2014-01-19 13:04:17 -08:00
Vidar Holen
380d6c3317 Cleaned up cabal file to make 'cabal check' pass. 2014-01-19 13:03:05 -08:00
Vidar Holen
16bd52333a man page: Added Directives section 2014-01-19 12:36:48 -08:00
Vidar Holen
cfb44b3fe2 Warn about 'cd $f; foo; cd ..' loop antipattern. 2014-01-17 09:02:14 -08:00
Vidar Holen
43ed5e748d Allow '# shellcheck disable=SC1234' to ignore by code. 2014-01-16 23:08:56 -08:00
Vidar Holen
4dca88aade Don't warn about quotes in variables for eval 2014-01-16 19:41:09 -08:00
Vidar Holen
1d2c7a8551 Warn about abused char classes, such as [10-15] and [:digit:] 2014-01-14 21:20:21 -08:00
koalaman
ba080e7e34 Merge pull request #61 from cheecheeo/master
expanded cabal file
2014-01-14 10:40:27 -08:00
John Chee
fc716738eb expanded cabal file 2014-01-13 19:14:18 -08:00
Vidar Holen
659709d529 Fixed ${!var} not counting as reference of var 2013-12-30 10:00:05 -08:00
Vidar Holen
5b4729d940 Parser: allow subshell function definitions 2013-12-30 09:50:14 -08:00
Vidar Holen
b936f28763 Merge branch 'manpage' 2013-12-15 19:43:02 -08:00
Vidar Holen
78d9a7ad97 Tweaked man page format 2013-12-15 19:40:05 -08:00
Vidar Holen
d540a98d33 Merge branch 'man_page' of https://github.com/Dridi/shellcheck into manpage 2013-12-15 18:44:49 -08:00
Vidar Holen
8c00850134 Minor performance tweaks (~10% improvement) 2013-12-15 18:43:34 -08:00
Vidar Holen
d1990e3396 Warn about 'i=i+1' and 'i=i + 1' 2013-12-15 16:11:17 -08:00
Dridi Boukelmoune
91fc4a046c Added a shellcheck(1) man page
The manual is mainly a copy/paste from the current documentation. It is
builded with pandoc, and written in markdown.

closes #50
2013-12-16 00:04:31 +01:00
Vidar Holen
95ebe1cd07 Fixed parser error for '..; done| ..' 2013-12-15 14:39:47 -08:00
Vidar Holen
27822a1f56 Warn about 'foo=bar echo $foo' 2013-12-14 16:06:19 -08:00
Vidar Holen
eb06b06475 Don't warn about single quoted vars for ssh 2013-12-14 15:28:58 -08:00
Vidar Holen
5d72432046 If printf string contains %, don't warn about using vars 2013-12-14 15:27:11 -08:00
Vidar Holen
da51b14789 Parser: accept here doc token strings more liberally 2013-12-14 15:20:15 -08:00
Vidar Holen
7be8485b8b Fixed parsing of 'time' in front of compound commands 2013-12-14 14:44:47 -08:00
Vidar Holen
a4d36ba0d2 Warn about while read f; do ssh "$f"; done 2013-11-29 23:05:41 -08:00
Vidar Holen
d4bc0f6e10 Don't require separator before do in 'for i do ..' 2013-11-29 16:22:37 -08:00
Vidar Holen
1011ae7b3c Fixed incorrect parsing of [ foo -a -f bar ] 2013-11-24 18:49:49 -08:00
Vidar Holen
d603ee1e89 Don't warn for A&&B||C if C is echo/exit/assignment 2013-11-24 16:15:10 -08:00
Vidar Holen
4fc518c877 Cleaned up command matching code 2013-11-24 15:48:07 -08:00
Vidar Holen
7fda86d6e2 Fixed warning for 'exec foo; exit 3' 2013-11-24 14:48:12 -08:00
Vidar Holen
6905373b6c Fix incorrect warning for 'foo > bar 2> bar' 2013-11-24 14:20:24 -08:00
Vidar Holen
1d8401d583 Assume variables have spaces by default 2013-11-17 16:16:58 -08:00
Vidar Holen
a89aee1a34 Assume variables have spaces/globs by default 2013-11-17 16:13:45 -08:00
Vidar Holen
4853dce3fe Fixed wrong quoting warning for foo=" "; foo 2013-11-17 15:00:07 -08:00
Vidar Holen
a793e09bab Added hint to suggest missing ;; in case 2013-11-17 14:41:55 -08:00
Vidar Holen
fbd85e93ee Added --exclude to filter out warnings 2013-11-17 13:41:42 -08:00
Vidar Holen
77f754fa32 Replace Prelude.catch with Control.Exception.catch 2013-11-15 17:31:55 -08:00
Vidar Holen
01d557abe6 More discriminating error codes 2013-11-14 22:46:09 -08:00
Vidar Holen
68cc00b6e8 Exit with 1 on comments and 2 on failure 2013-11-14 22:35:38 -08:00
Vidar Holen
8b7c0be06f gcc output mode now uses a tab width of 1 2013-11-14 22:23:55 -08:00
Vidar Holen
473bb666d8 Support for checkstyle compatible xml output 2013-11-13 22:39:35 -08:00
Vidar Holen
376d407ea1 Added gcc compatible output for editor integrations 2013-11-13 17:28:08 -08:00
Vidar Holen
2e13cedc4b Removed jsoncheck. Use 'shellcheck -f json -' instead 2013-11-12 21:39:41 -08:00
Vidar Holen
17515ad706 Added proper command line parsing 2013-11-12 21:22:52 -08:00
Vidar Holen
d8b5d6393a \" should not be treated specially in backticks 2013-11-12 18:27:18 -08:00
Vidar Holen
d404bc703d Show expose error code in shellcheck frontends 2013-11-10 12:22:33 -08:00
Vidar Holen
e5e08df1d9 Numbered messages 2013-11-10 10:55:46 -08:00
koalaman
1988cba147 Merge pull request #33 from daniellawrence/master
updated debian/ubuntu required packages
2013-11-07 10:21:48 -08:00
Daniel Lawrence
4cee7fd27f updated debian/ubuntu required packages 2013-11-04 16:00:47 +11:00
Vidar Holen
b75fe02aac Merge branch 'master' of github.com:koalaman/shellcheck 2013-11-03 13:58:33 -08:00
Vidar Holen
83c3dd3418 Accept ./? in function names 2013-11-03 13:58:06 -08:00
koalaman
020850dbbb Merge pull request #16 from carenas/master
gitignore and makefile for building with cabal and make
2013-11-03 13:51:13 -08:00
Vidar Holen
8d265aa25e Don't warn about expr if using : operator 2013-11-03 13:47:04 -08:00
Vidar Holen
c343217fd2 Added Fedora prerequisites in README 2013-11-03 13:27:10 -08:00
Vidar Holen
71bc26aefa Fixed parsing of | outside of groups in =~ regex 2013-11-03 13:13:24 -08:00
Vidar Holen
8a3d259ae6 Don't warn about single quotes in args to perl 2013-11-03 12:47:44 -08:00
Vidar Holen
3a9ae0ebf1 Accept dir-/basename due to edge cases like "/" and "foo" 2013-11-03 12:42:11 -08:00
Carlo Marcelo Arenas Belon
d6b903e6cc gitignore and makefile for building with cabal and make
makefile should also delete cabal generated files on cleanup so
they could be used interchangably.

ensure that all generated files are ignored as recommended by
bese practices.
2013-10-28 02:56:29 -07:00
13 changed files with 1094 additions and 393 deletions

7
.gitignore vendored Normal file
View File

@@ -0,0 +1,7 @@
*.hi
*.o
.tests
jsoncheck
shellcheck
shellcheck.1
dist

View File

@@ -2,22 +2,23 @@
GHCFLAGS=-O9
all: shellcheck jsoncheck .tests
all: shellcheck .tests shellcheck.1
: Done
shellcheck: regardless
: Conditionally compiling shellcheck
ghc $(GHCFLAGS) --make shellcheck
jsoncheck: regardless
: Conditionally compiling shellcheck
ghc $(GHCFLAGS) --make jsoncheck
.tests: *.hs */*.hs
: Running unit tests
./test/runQuack && touch .tests
shellcheck.1: shellcheck.1.md
pandoc -s -t man $< -o $@
clean:
rm -f .tests shellcheck jsoncheck *.hi *.o ShellCheck/*.hi ShellCheck/*.o
rm -f .tests shellcheck shellcheck.1
rm -f *.hi *.o ShellCheck/*.hi ShellCheck/*.o
rm -rf dist
regardless:

10
README
View File

@@ -18,10 +18,14 @@ The goals of ShellCheck are:
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.
On Ubuntu and similar, these are called:
ghc libghc-parsec3-dev libghc-json-dev libghc-regex-compat-dev libghc-quickcheck2-dev
On Fedora, these can be installed with:
yum install cabal-install ghc ghc-parsec-devel ghc-QuickCheck-devel ghc-json-devel ghc-regex-compat-devel
On Ubuntu and similar, use:
apt-get install ghc libghc-parsec3-dev libghc-json-dev libghc-regex-compat-dev libghc-quickcheck2-dev cabal-install
For older releases, you may have to use:
ghc6 libghc6-parsec3-dev libghc6-quickcheck2-dev libghc6-json-dev libghc-regex-compat-dev
apt-get install ghc6 libghc6-parsec3-dev libghc6-quickcheck2-dev libghc6-json-dev libghc-regex-compat-dev cabal-install
Executables can be built with cabal. Tests currently still rely on a Makefile.

2
Setup.hs Normal file
View File

@@ -0,0 +1,2 @@
import Distribution.Simple
main = defaultMain

View File

@@ -1,20 +1,34 @@
Name: ShellCheck
Version: 0.2.0
Description: Shell script analysis tool
Version: 0.3.0
Synopsis: Shell script analysis tool
License: OtherLicense
License-file: LICENSE
Category: Static Analysis
Author: Vidar Holen
Maintainer: vidar@vidarholen.net
Homepage: http://www.shellcheck.net/
Build-Type: Simple
Cabal-Version: >= 1.2
Cabal-Version: >= 1.6
Bug-reports: https://github.com/koalaman/shellcheck/issues
Description:
The goals of ShellCheck are:
.
* To point out and clarify typical beginner's syntax issues,
that causes a shell to give cryptic error messages.
.
* To point out and clarify typical intermediate level semantic problems,
that causes a shell to behave strangely and counter-intuitively.
.
* To point out subtle caveats, corner cases and pitfalls, that may cause an
advanced user's otherwise working script to fail under future circumstances.
source-repository head
type: git
location: git://github.com/koalaman/shellcheck.git
library
build-depends: base >= 4, parsec, containers, regex-compat, mtl, directory
build-depends: base >= 4, base < 5, parsec, containers, regex-compat, mtl, directory, json
exposed-modules: ShellCheck.AST, ShellCheck.Data, ShellCheck.Parser, ShellCheck.Analytics, ShellCheck.Simple
executable shellcheck
main-is: shellcheck.hs
executable jsoncheck
build-depends: json
main-is: jsoncheck.hs

View File

@@ -117,8 +117,10 @@ data Token =
| T_UntilExpression Id [Token] [Token]
| T_While Id
| T_WhileExpression Id [Token] [Token]
| T_Annotation Id [Annotation] Token
deriving (Show)
data Annotation = DisableComment Integer deriving (Show, Eq)
data ConditionType = DoubleBracket | SingleBracket deriving (Show, Eq)
-- I apologize for nothing!
@@ -239,6 +241,7 @@ analyze f g i t =
return $ TA_Trinary id a b c
delve (TA_Expansion id t) = d1 t $ TA_Expansion id
delve (TA_Base id b t) = d1 t $ TA_Base id b
delve (T_Annotation id anns t) = d1 t $ T_Annotation id anns
delve t = return t
getId t = case t of
@@ -331,6 +334,7 @@ getId t = case t of
T_DollarSingleQuoted id _ -> id
T_DollarDoubleQuoted id _ -> id
T_DollarBracket id _ -> id
T_Annotation id _ _ -> id
blank :: Monad m => Token -> m ()
blank = const $ return ()

File diff suppressed because it is too large Load Diff

View File

@@ -40,6 +40,13 @@ internalVariables = [
"ZLE_REMOVE_SUFFIX_CHARS", "ZLE_SPACE_SUFFIX_CHARS"
]
variablesWithoutSpaces = [
"$", "-", "?", "!",
"BASHPID", "BASH_ARGC", "BASH_LINENO", "BASH_SUBSHELL", "EUID", "LINENO",
"OPTIND", "PPID", "RANDOM", "SECONDS", "SHELLOPTS", "SHLVL", "UID",
"COLUMNS", "HISTFILESIZE", "HISTSIZE", "LINES"
]
commonCommands = [
"admin", "alias", "ar", "asa", "at", "awk", "basename", "batch",
"bc", "bg", "break", "c99", "cal", "cat", "cd", "cflow", "chgrp",

View File

@@ -34,7 +34,7 @@ import System.IO
import Text.Parsec.Error
import GHC.Exts (sortWith)
lastError = 1074
backslash = char '\\'
linefeed = (optional carriageReturn) >> char '\n'
@@ -42,15 +42,19 @@ singleQuote = char '\'' <|> unicodeSingleQuote
doubleQuote = char '"' <|> unicodeDoubleQuote
variableStart = upper <|> lower <|> oneOf "_"
variableChars = upper <|> lower <|> digit <|> oneOf "_"
functionChars = variableChars <|> oneOf ":+-"
functionChars = variableChars <|> oneOf ":+-.?"
specialVariable = oneOf "@*#?-$!"
tokenDelimiter = oneOf "&|;<> \t\n\r" <|> nbsp
quotable = oneOf "|&;<>()$`\\ \"'\t\n\r" <|> nbsp <|> unicodeDoubleQuote
quotableChars = "|&;<>()\\ '\t\n\r\xA0" ++ doubleQuotableChars
quotable = nbsp <|> unicodeDoubleQuote <|> oneOf quotableChars
bracedQuotable = oneOf "}\"$`'"
doubleQuotable = oneOf "\"$`" <|> unicodeDoubleQuote
doubleQuotableChars = "\"$`\x201C\x201D"
doubleQuotable = unicodeDoubleQuote <|> oneOf doubleQuotableChars
whitespace = oneOf " \t\n" <|> carriageReturn <|> nbsp
linewhitespace = oneOf " \t" <|> nbsp
extglobStart = oneOf "?*@!+"
extglobStartChars = "?*@!+"
extglobStart = oneOf extglobStartChars
prop_spacing = isOk spacing " \\\n # Comment"
spacing = do
@@ -77,29 +81,34 @@ allspacingOrFail = do
unicodeDoubleQuote = do
pos <- getPosition
char '\x201C' <|> char '\x201D'
parseProblemAt pos WarningC "This is a unicode double quote. Delete and retype it."
parseProblemAt pos WarningC 1015 "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."
parseProblemAt pos WarningC 1016 "This is a unicode single quote. Delete and retype it."
return '"'
carriageReturn = do
parseNote ErrorC "Literal carriage return. Run script through tr -d '\\r' ."
parseNote ErrorC 1017 "Literal carriage return. Run script through tr -d '\\r' ."
char '\r'
nbsp = do
parseNote ErrorC "This is a &nbsp;. Delete it and retype as space."
parseNote ErrorC 1018 "This is a &nbsp;. Delete it and retype as space."
char '\xA0'
return ' '
--------- Message/position annotation on top of user state
data Note = Note Severity String deriving (Show, Eq)
data ParseNote = ParseNote SourcePos Severity String deriving (Show, Eq)
data Note = Note Severity Code String deriving (Show, Eq)
data ParseNote = ParseNote SourcePos Severity Code String deriving (Show, Eq)
data Metadata = Metadata SourcePos [Note] deriving (Show)
data Severity = ErrorC | WarningC | InfoC | StyleC deriving (Show, Eq, Ord)
data Context = ContextName SourcePos String | ContextAnnotation [Annotation]
type Code = Integer
codeForNote (Note _ code _) = code
codeForParseNote (ParseNote _ _ code _) = code
initialState = (Id $ -1, Map.empty, [])
@@ -134,14 +143,24 @@ getParseNotes = do
return notes
addParseNote n = do
irrelevant <- shouldIgnoreCode (codeForParseNote n)
when (not irrelevant) $ do
(a, b, notes) <- getState
putState (a, b, n:notes)
shouldIgnoreCode code = do
context <- getCurrentContexts
return $ any disabling context
where
disabling (ContextAnnotation list) =
any disabling' list
disabling _ = False
disabling' (DisableComment n) = code == n
-- Store potential parse problems outside of parsec
parseProblem level msg = do
parseProblem level code msg = do
pos <- getPosition
parseProblemAt pos level msg
parseProblemAt pos level code msg
setCurrentContexts c = do
Ms.modify (\(list, _) -> (list, c))
@@ -164,8 +183,10 @@ pushContext c = do
v <- getCurrentContexts
setCurrentContexts (c:v)
parseProblemAt pos level msg = do
Ms.modify (\(list, current) -> ((ParseNote pos level msg):list, current))
parseProblemAt pos level code msg = do
irrelevant <- shouldIgnoreCode code
when (not irrelevant) $
Ms.modify (\(list, current) -> ((ParseNote pos level code msg):list, current))
-- Store non-parse problems inside
addNoteFor id note = modifyMap $ Map.adjust (\(Metadata pos notes) -> Metadata pos (note:notes)) id
@@ -174,11 +195,11 @@ addNote note = do
id <- getLastId
addNoteFor id note
parseNote l a = do
parseNote c l a = do
pos <- getPosition
parseNoteAt pos l a
parseNoteAt pos c l a
parseNoteAt pos l a = addParseNote $ ParseNote pos l a
parseNoteAt pos c l a = addParseNote $ ParseNote pos c l a
--------- Convenient combinators
thenSkip main follow = do
@@ -214,16 +235,15 @@ orFail parser stuff = do
wasIncluded p = option False (p >> return True)
acceptButWarn parser level note = do
acceptButWarn parser level code note = do
optional $ try (do
pos <- getPosition
parser
parseProblemAt pos level note
parseProblemAt pos level code note
)
called s p = do
pos <- getPosition
pushContext (pos, s)
withContext entry p = do
pushContext entry
do
v <- p
popContext
@@ -232,12 +252,19 @@ called s p = do
popContext
fail $ ""
called s p = do
pos <- getPosition
withContext (ContextName pos s) p
withAnnotations anns p =
withContext (ContextAnnotation anns) p
readConditionContents single = do
readCondContents `attempting` (lookAhead $ do
pos <- getPosition
s <- many1 letter
when (s `elem` commonCommands) $
parseProblemAt pos WarningC "Use 'if cmd; then ..' to check exit code, or 'if [[ $(cmd) == .. ]]' to check output.")
parseProblemAt pos WarningC 1009 "Use 'if cmd; then ..' to check exit code, or 'if [[ $(cmd) == .. ]]' to check output.")
where
typ = if single then SingleBracket else DoubleBracket
@@ -254,6 +281,7 @@ readConditionContents single = do
otherOp = try $ do
id <- getNextId
s <- readOp
when (s == "-a" || s == "-o") $ fail "Wrong operator"
return $ TC_Binary id typ s
readCondUnaryExp = do
@@ -263,7 +291,7 @@ readConditionContents single = do
arg <- readCondWord
return $ op arg)
<|> (do
parseProblemAt pos ErrorC $ "Expected this to be an argument to the unary condition."
parseProblemAt pos ErrorC 1019 $ "Expected this to be an argument to the unary condition."
fail "oops")
readCondUnaryOp = try $ do
@@ -282,10 +310,10 @@ readConditionContents single = do
x <- readNormalWord
pos <- getPosition
when (endedWith "]" x) $ do
parseProblemAt pos ErrorC $
parseProblemAt pos ErrorC 1020 $
"You need a space before the " ++ (if single then "]" else "]]") ++ "."
when (single && endedWith ")" x) $ do
parseProblemAt pos ErrorC $
parseProblemAt pos ErrorC 1021 $
"You need a space before the \\)"
disregard spacing
return x
@@ -297,17 +325,16 @@ readConditionContents single = do
readCondAndOp = do
id <- getNextId
x <- try (string "&&" <|> string "-a")
when (single && x == "&&") $ addNoteFor id $ Note ErrorC "You can't use && inside [..]. Use [[..]] instead."
when (not single && x == "-a") $ addNoteFor id $ Note ErrorC "In [[..]], use && instead of -a."
when (single && x == "&&") $ addNoteFor id $ Note ErrorC 1022 "You can't use && inside [..]. Use [[..]] instead."
when (not single && x == "-a") $ addNoteFor id $ Note ErrorC 1023 "In [[..]], use && instead of -a."
softCondSpacing
return $ TC_And id typ x
readCondOrOp = do
id <- getNextId
x <- try (string "||" <|> string "-o")
when (single && x == "||") $ addNoteFor id $ Note ErrorC "You can't use || inside [..]. Use [[..]] instead."
when (not single && x == "-o") $ addNoteFor id $ Note ErrorC "In [[..]], use && instead of -o."
when (single && x == "||") $ addNoteFor id $ Note ErrorC 1024 "You can't use || inside [..]. Use [[..]] instead."
when (not single && x == "-o") $ addNoteFor id $ Note ErrorC 1025 "In [[..]], use || instead of -o."
softCondSpacing
return $ TC_Or id typ x
@@ -316,7 +343,7 @@ readConditionContents single = do
x <- readCondWord `attempting` (do
pos <- getPosition
lookAhead (char '[')
parseProblemAt pos ErrorC $ if single
parseProblemAt pos ErrorC 1026 $ if single
then "If grouping expressions inside [..], use \\( ..\\)."
else "If grouping expressions inside [[..]], use ( .. )."
)
@@ -326,7 +353,7 @@ readConditionContents single = do
op <- readCondBinaryOp
y <- if isRegex
then readRegex
else readCondWord <|> ( (parseProblemAt pos ErrorC $ "Expected another argument for this operator.") >> mzero)
else readCondWord <|> ( (parseProblemAt pos ErrorC 1027 $ "Expected another argument for this operator.") >> mzero)
return (x `op` y)
) <|> (return $ TC_Noary id typ x)
@@ -334,16 +361,16 @@ readConditionContents single = do
id <- getNextId
pos <- getPosition
lparen <- try $ string "(" <|> string "\\("
when (single && lparen == "(") $ parseProblemAt pos ErrorC "In [..] you have to escape (). Use [[..]] instead."
when (not single && lparen == "\\(") $ parseProblemAt pos ErrorC "In [[..]] you shouldn't escape ()."
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
x <- readCondContents
cpos <- getPosition
rparen <- string ")" <|> string "\\)"
if single then hardCondSpacing else disregard spacing
when (single && rparen == ")") $ parseProblemAt cpos ErrorC "In [..] you have to escape (). Use [[..]] instead."
when (not single && rparen == "\\)") $ parseProblemAt cpos ErrorC "In [[..]] you shouldn't escape ()."
when (isEscaped lparen `xor` isEscaped rparen) $ parseProblemAt pos ErrorC "Did you just escape one half of () but not the other?"
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
@@ -357,7 +384,14 @@ readConditionContents single = do
<|> return False
readRegex = called "regex" $ do
id <- getNextId
parts <- many1 (readGroup <|> readSingleQuoted <|> readDoubleQuoted <|> readDollarExpression <|> readNormalLiteral "( " <|> readGlobLiteral)
parts <- many1 (
readGroup <|>
readSingleQuoted <|>
readDoubleQuoted <|>
readDollarExpression <|>
readNormalLiteral "( " <|>
readPipeLiteral <|>
readGlobLiteral)
disregard spacing
return $ T_NormalWord id parts
where
@@ -375,6 +409,10 @@ readConditionContents single = do
id <- getNextId
str <- readGenericLiteral1 (singleQuote <|> doubleQuotable <|> oneOf "()")
return $ T_Literal id str
readPipeLiteral = do
id <- getNextId
str <- string "|"
return $ T_Literal id str
readCondTerm = readCondNot <|> readCondExpr
readCondNot = do
@@ -433,7 +471,7 @@ readArithmeticContents =
-- Doesn't help with foo[foo]
readArrayIndex = do
char '['
x <- anyChar `reluctantlyTill1` (char ']')
x <- many1 $ noneOf "]"
char ']'
return $ "[" ++ x ++ "]"
@@ -571,6 +609,8 @@ prop_readCondition5a= isOk readCondition "[[ $c =~ a(b) ]]"
prop_readCondition5b= isOk readCondition "[[ $c =~ f( ($var ]]) )* ]]"
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 ]"
readCondition = called "test expression" $ do
opos <- getPosition
id <- getNextId
@@ -583,8 +623,8 @@ readCondition = called "test expression" $ do
cpos <- getPosition
close <- (try $ string "]]") <|> (string "]")
when (open == "[[" && close /= "]]") $ parseProblemAt cpos ErrorC "Did you mean ]] ?"
when (open == "[" && close /= "]" ) $ parseProblemAt opos ErrorC "Did you mean [[ ?"
when (open == "[[" && close /= "]]") $ parseProblemAt cpos ErrorC 1033 "Did you mean ]] ?"
when (open == "[" && close /= "]" ) $ parseProblemAt opos ErrorC 1034 "Did you mean [[ ?"
spacing
many readCmdWord -- Read and throw away remainders to get then/do warnings. Fixme?
return $ T_Condition id (if single then SingleBracket else DoubleBracket) condition
@@ -595,11 +635,45 @@ 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 msg
when (null space) $ (if soft then parseNoteAt else parseProblemAt) pos ErrorC 1035 msg
readAnnotationPrefix = do
char '#'
many linewhitespace
string "shellcheck"
prop_readAnnotation1 = isOk readAnnotation "# shellcheck disable=1234,5678\n"
prop_readAnnotation2 = isOk readAnnotation "# shellcheck disable=SC1234 disable=SC5678\n"
readAnnotation = called "shellcheck annotation" $ do
try readAnnotationPrefix
many1 linewhitespace
values <- many1 (readDisable)
linefeed
many linewhitespace
return $ concat values
where
readDisable = forKey "disable" $ do
readCode `sepBy` char ','
where
readCode = do
optional $ string "SC"
int <- many1 digit
return $ DisableComment (read int)
forKey s p = do
try $ string s
char '='
value <- p
many linewhitespace
return value
readAnnotations = do
annotations <- many (readAnnotation `thenSkip` allspacing)
return $ concat annotations
readComment = do
unexpecting "shellcheck annotation" readAnnotationPrefix
char '#'
anyChar `reluctantlyTill` linefeed
many $ noneOf "\r\n"
prop_readNormalWord = isOk readNormalWord "'foo'\"bar\"{1..3}baz$(lol)"
prop_readNormalWord2 = isOk readNormalWord "foo**(foo)!!!(@@(bar))"
@@ -616,7 +690,7 @@ readNormalishWord end = do
checkPossibleTermination pos [T_Literal _ x] =
if x `elem` ["do", "done", "then", "fi", "esac", "}"]
then parseProblemAt pos WarningC $ "Use semicolon or linefeed before '" ++ x ++ "' (or quote to make it literal)."
then parseProblemAt pos WarningC 1010 $ "Use semicolon or linefeed before '" ++ x ++ "' (or quote to make it literal)."
else return ()
checkPossibleTermination _ _ = return ()
@@ -628,7 +702,7 @@ readNormalWordPart end = do
return () `attempting` do
pos <- getPosition
lookAhead $ char '('
parseProblemAt pos ErrorC "'(' is invalid here. Did you forget to escape it?"
parseProblemAt pos ErrorC 1036 "'(' is invalid here. Did you forget to escape it?"
readSpacePart = do
@@ -675,7 +749,7 @@ readSingleQuoted = called "single quoted string" $ do
let string = concat s
return (T_SingleQuoted id string) `attempting` do
x <- lookAhead anyChar
when (isAlpha x && not (null string) && isAlpha (last string)) $ parseProblemAt pos WarningC "This apostrophe terminated the single quoted string!"
when (isAlpha x && not (null string) && isAlpha (last string)) $ parseProblemAt pos WarningC 1011 "This apostrophe terminated the single quoted string!"
readSingleQuotedLiteral = do
singleQuote
@@ -685,22 +759,23 @@ readSingleQuotedLiteral = do
readSingleQuotedPart =
readSingleEscaped
<|> anyChar `reluctantlyTill1` (singleQuote <|> backslash)
<|> (many1 $ noneOf "'\\\x2018\x2019")
prop_readBackTicked = isOk readBackTicked "`ls *.mp3`"
prop_readBackTicked2 = isOk readBackTicked "`grep \"\\\"\"`"
readBackTicked = called "backtick expansion" $ do
id <- getNextId
pos <- getPosition
char '`'
subStart <- getPosition
subString <- readGenericLiteral (char '`')
subString <- readGenericLiteral "`"
char '`'
-- Result positions may be off due to escapes
result <- subParse subStart readCompoundList (unEscape subString)
return $ T_Backticked id result
where
unEscape [] = []
unEscape ('\\':x:rest) | x `elem` "\"$`\\" = x : unEscape rest
unEscape ('\\':x:rest) | x `elem` "$`\\" = x : unEscape rest
unEscape ('\\':'\n':rest) = unEscape rest
unEscape (c:rest) = c : unEscape rest
@@ -738,7 +813,7 @@ readDoubleLiteral = do
return $ T_Literal id (concat s)
readDoubleLiteralPart = do
x <- (readDoubleEscaped <|> (anyChar >>= \x -> return [x])) `reluctantlyTill1` doubleQuotable
x <- many1 $ (readDoubleEscaped <|> (many1 $ noneOf ('\\':doubleQuotableChars)))
return $ concat x
readNormalLiteral end = do
@@ -778,7 +853,7 @@ readGlob = readExtglob <|> readSimple <|> readClass <|> readGlobbyLiteral
return $ T_Literal id [c]
readNormalLiteralPart end = do
readNormalEscaped <|> (anyChar `reluctantlyTill1` (quotable <|> extglobStart <|> char '[' <|> oneOf end))
readNormalEscaped <|> (many1 $ noneOf (end ++ quotableChars ++ extglobStartChars ++ "["))
readNormalEscaped = called "escaped char" $ do
pos <- getPosition
@@ -790,8 +865,8 @@ readNormalEscaped = called "escaped char" $ do
do
next <- anyChar
case escapedChar next of
Just name -> parseNoteAt pos WarningC $ "\\" ++ [next] ++ " is just literal '" ++ [next] ++ "' here. For " ++ name ++ ", use \"$(printf \"\\" ++ [next] ++ "\")\"."
Nothing -> parseNoteAt pos InfoC $ "This \\" ++ [next] ++ " will be a regular '" ++ [next] ++ "' in this context."
Just name -> parseNoteAt pos WarningC 1012 $ "\\" ++ [next] ++ " is just literal '" ++ [next] ++ "' here. For " ++ name ++ ", use \"$(printf \"\\" ++ [next] ++ "\")\"."
Nothing -> parseNoteAt pos InfoC 1001 $ "This \\" ++ [next] ++ " will be a regular '" ++ [next] ++ "' in this context."
return [next]
where
escapedChar 'n' = Just "line feed"
@@ -836,14 +911,14 @@ readExtglobPart = do
readSingleEscaped = do
s <- backslash
let attempt level p msg = do { try $ parseNote level msg; x <- p; return [s,x]; }
let attempt level code p msg = do { try $ parseNote level code msg; x <- p; return [s,x]; }
do {
x <- lookAhead singleQuote;
parseProblem InfoC "Are you trying to escape that single quote? echo 'You'\\''re doing it wrong'.";
parseProblem InfoC 1003 "Are you trying to escape that single quote? echo 'You'\\''re doing it wrong'.";
return [s];
}
<|> attempt InfoC linefeed "You don't break lines with \\ in single quotes, it results in literal backslash-linefeed."
<|> attempt InfoC 1004 linefeed "You don't break lines with \\ in single quotes, it results in literal backslash-linefeed."
<|> do
x <- anyChar
return [s,x]
@@ -862,8 +937,8 @@ readBraceEscaped = do
<|> (anyChar >>= (return . \x -> [bs, x]))
readGenericLiteral endExp = do
strings <- (readGenericEscaped <|> (anyChar >>= \x -> return [x])) `reluctantlyTill` endExp
readGenericLiteral endChars = do
strings <- many (readGenericEscaped <|> (many1 $ noneOf ('\\':endChars)))
return $ concat strings
readGenericLiteral1 endExp = do
@@ -893,7 +968,7 @@ prop_readDollarSingleQuote = isOk readDollarSingleQuote "$'foo\\\'lol'"
readDollarSingleQuote = called "$'..' expression" $ do
id <- getNextId
try $ string "$'"
str <- readGenericLiteral (char '\'')
str <- readGenericLiteral "'"
char '\''
return $ T_DollarSingleQuoted id str
@@ -959,7 +1034,7 @@ readDollarVariable = do
return (T_DollarBraced id value) `attempting` do
pos <- getPosition
num <- lookAhead $ many1 p
parseNoteAt pos ErrorC $ "$" ++ (n:num) ++ " is equivalent to ${" ++ [n] ++ "}"++ num ++"."
parseNoteAt pos ErrorC 1037 $ "$" ++ (n:num) ++ " is equivalent to ${" ++ [n] ++ "}"++ num ++"."
let positional = singleCharred digit
let special = singleCharred specialVariable
@@ -987,16 +1062,16 @@ readDollarLonely = do
pos <- getPosition
char '$'
n <- lookAhead (anyChar <|> (eof >> return '_'))
when (n /= '\'') $ parseNoteAt pos StyleC "$ is not used specially and should therefore be escaped."
when (n /= '\'') $ parseNoteAt pos StyleC 1000 "$ is not used specially and should therefore be escaped."
return $ T_Literal id "$"
prop_readHereDoc = isOk readHereDoc "<< foo\nlol\ncow\nfoo"
prop_readHereDoc2 = isWarning readHereDoc "<<- EOF\n cow\n EOF"
prop_readHereDoc3 = isOk readHereDoc "<< foo\n$\"\nfoo"
prop_readHereDoc4 = isOk readHereDoc "<< foo\n`\nfoo"
prop_readHereDoc5 = isOk readHereDoc "<<- !foo\nbar\n!foo"
prop_readHereDoc6 = isOk readHereDoc "<< foo\\ bar\ncow\nfoo bar"
readHereDoc = called "here document" $ do
let stripLiteral (T_Literal _ x) = x
stripLiteral (T_SingleQuoted _ x) = x
fid <- getNextId
pos <- getPosition
try $ string "<<"
@@ -1006,11 +1081,12 @@ readHereDoc = called "here document" $ do
optional $ do
try . lookAhead $ char '('
let message = "Shells are space sensitive. Use '< <(cmd)', not '<<" ++ sp ++ "(cmd)'."
parseProblemAt pos ErrorC message
parseProblemAt pos ErrorC 1038 message
hid <- getNextId
(quoted, endToken) <- (readNormalLiteral "" >>= (\x -> return (Unquoted, stripLiteral x)) )
<|> (readDoubleQuotedLiteral >>= return . (\x -> (Quoted, stripLiteral x)))
(quoted, endToken) <-
(readDoubleQuotedLiteral >>= return . (\x -> (Quoted, stripLiteral x)))
<|> (readSingleQuotedLiteral >>= return . (\x -> (Quoted, x)))
<|> (readToken >>= (\x -> return (Unquoted, x)))
spacing
startPos <- getPosition
@@ -1030,6 +1106,19 @@ readHereDoc = called "here document" $ do
`attempting` (eof >> debugHereDoc tokenPosition endToken hereData)
where
stripLiteral (T_Literal _ x) = x
stripLiteral (T_SingleQuoted _ x) = x
readToken = do
liftM concat $ many1 (escaped <|> quoted <|> normal)
where
quoted = liftM stripLiteral readDoubleQuotedLiteral <|> readSingleQuotedLiteral
normal = anyChar `reluctantlyTill1` (whitespace <|> oneOf ";&)'\"\\")
escaped = do -- surely the user must be doing something wrong at this point
char '\\'
c <- anyChar
return [c]
parseHereData Quoted startPos hereData = do
id <- getNextIdAt startPos
return $ [T_Literal id hereData]
@@ -1041,27 +1130,27 @@ readHereDoc = called "here document" $ do
readHereLiteral = do
id <- getNextId
chars <- anyChar `reluctantlyTill1` oneOf "`$"
chars <- many1 $ noneOf "`$"
return $ T_Literal id chars
verifyHereDoc dashed quoted spacing hereInfo = do
when (dashed == Undashed && spacing /= "") $
parseNote ErrorC "Use <<- instead of << if you want to indent the end token."
parseNote ErrorC 1039 "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."
parseNote ErrorC 1040 "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 ++ "').")
parseProblemAt pos ErrorC 1041 ("Close matches include '" ++ line ++ "' (!= '" ++ endToken ++ "').")
in do
parseProblemAt pos ErrorC ("Found '" ++ endToken ++ "' further down, but not entirely by itself.")
parseProblemAt pos ErrorC 1042 ("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.")
then parseProblemAt pos ErrorC 1043 ("Found " ++ endToken ++ " further down, but with wrong casing.")
else parseProblemAt pos ErrorC 1044 ("Couldn't find end token `" ++ endToken ++ "' in the here document.")
readFilename = readNormalWord
@@ -1118,7 +1207,7 @@ readSeparatorOp = do
spacing
pos <- getPosition
char ';'
parseProblemAt pos ErrorC "It's not 'foo &; bar', just 'foo & bar'."
parseProblemAt pos ErrorC 1045 "It's not 'foo &; bar', just 'foo & bar'."
return '&'
) <|> char ';' <|> char '&'
spacing
@@ -1157,6 +1246,8 @@ prop_readSimpleCommand = isOk readSimpleCommand "echo test > file"
prop_readSimpleCommand2 = isOk readSimpleCommand "cmd &> file"
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; )"
readSimpleCommand = called "simple command" $ do
id1 <- getNextId
id2 <- getNextId
@@ -1169,15 +1260,21 @@ readSimpleCommand = called "simple command" $ do
suffix <- option [] $
if isModifierCommand cmd
then readModifierSuffix
else if isTimeCommand cmd
then readTimeSuffix
else readCmdSuffix
return $ makeSimpleCommand id1 id2 prefix [cmd] suffix
where
isModifierCommand (T_NormalWord _ [T_Literal _ s]) =
s `elem` ["declare", "export", "local", "readonly", "typeset"]
isModifierCommand _ = False
-- Might not belong in T_SimpleCommand. Fixme?
isTimeCommand (T_NormalWord _ [T_Literal _ "time"]) = True
isTimeCommand _ = False
prop_readPipeline = isOk readPipeline "! cat /etc/issue | grep -i ubuntu"
prop_readPipeline2 = isWarning readPipeline "!cat /etc/issue | grep -i ubuntu"
prop_readPipeline3 = isOk readPipeline "for f; do :; done|cat"
readPipeline = do
unexpecting "keyword/token" readKeyword
do
@@ -1188,12 +1285,23 @@ readPipeline = do
readPipeSequence
prop_readAndOr = isOk readAndOr "grep -i lol foo || exit 1"
readAndOr = chainr1 readPipeline $ do
prop_readAndOr1 = isOk readAndOr "# shellcheck disable=1\nfoo"
prop_readAndOr2 = isOk readAndOr "# shellcheck disable=1\n# lol\n# shellcheck disable=3\nfoo"
readAndOr = do
aid <- getNextId
annotations <- readAnnotations
andOr <- withAnnotations annotations $ do
chainr1 readPipeline $ do
op <- g_AND_IF <|> g_OR_IF
readLineBreak
return $ case op of T_AND_IF id -> T_AndIf id
T_OR_IF id -> T_OrIf id
return $ if null annotations
then andOr
else T_Annotation aid annotations andOr
readTerm = do
allspacing
m <- readAndOr
@@ -1248,8 +1356,8 @@ readIfClause = called "if expression" $ do
elses <- option [] readElsePart
g_Fi `orFail` do
parseProblemAt pos ErrorC "Couldn't find 'fi' for this 'if'."
parseProblem ErrorC "Expected 'fi' matching previously mentioned 'if'."
parseProblemAt pos ErrorC 1046 "Couldn't find 'fi' for this 'if'."
parseProblem ErrorC 1047 "Expected 'fi' matching previously mentioned 'if'."
return $ T_IfExpression id ((condition, action):elifs) elses
@@ -1258,7 +1366,7 @@ verifyNotEmptyIf s =
optional (do
emptyPos <- getPosition
try . lookAhead $ (g_Fi <|> g_Elif <|> g_Else)
parseProblemAt emptyPos ErrorC $ "Can't have empty " ++ s ++ " clauses (use 'true' as a no-op).")
parseProblemAt emptyPos ErrorC 1048 $ "Can't have empty " ++ s ++ " clauses (use 'true' as a no-op).")
readIfPart = do
pos <- getPosition
g_If
@@ -1267,12 +1375,12 @@ readIfPart = do
optional (do
try . lookAhead $ g_Fi
parseProblemAt pos ErrorC "Did you forget the 'then' for this 'if'?")
parseProblemAt pos ErrorC 1049 "Did you forget the 'then' for this 'if'?")
called "then clause" $ do
g_Then `orFail` parseProblem ErrorC "Expected 'then'."
g_Then `orFail` parseProblem ErrorC 1050 "Expected 'then'."
acceptButWarn g_Semi ErrorC "No semicolons directly after 'then'."
acceptButWarn g_Semi ErrorC 1051 "No semicolons directly after 'then'."
allspacing
verifyNotEmptyIf "then"
@@ -1285,7 +1393,7 @@ readElifPart = called "elif clause" $ do
allspacing
condition <- readTerm
g_Then
acceptButWarn g_Semi ErrorC "No semicolons directly after 'then'."
acceptButWarn g_Semi ErrorC 1052 "No semicolons directly after 'then'."
allspacing
verifyNotEmptyIf "then"
action <- readTerm
@@ -1293,7 +1401,7 @@ readElifPart = called "elif clause" $ do
readElsePart = called "else clause" $ do
g_Else
acceptButWarn g_Semi ErrorC "No semicolons directly after 'else'."
acceptButWarn g_Semi ErrorC 1053 "No semicolons directly after 'else'."
allspacing
verifyNotEmptyIf "else"
readTerm
@@ -1313,14 +1421,14 @@ prop_readBraceGroup2 = isWarning readBraceGroup "{foo;}"
readBraceGroup = called "brace group" $ do
id <- getNextId
char '{'
allspacingOrFail <|> parseProblem ErrorC "You need a space after the '{'."
allspacingOrFail <|> parseProblem ErrorC 1054 "You need a space after the '{'."
optional $ do
pos <- getPosition
lookAhead $ char '}'
parseProblemAt pos ErrorC "You need at least one command here. Use 'true;' as a no-op."
parseProblemAt pos ErrorC 1055 "You need at least one command here. Use 'true;' as a no-op."
list <- readTerm
char '}' <|> do
parseProblem ErrorC "Expected a '}'. If you have one, try a ; or \\n in front of it."
parseProblem ErrorC 1056 "Expected a '}'. If you have one, try a ; or \\n in front of it."
fail "Unable to parse"
return $ T_BraceGroup id list
@@ -1344,21 +1452,21 @@ readDoGroup loopPos = do
pos <- getPosition
optional (do
try . lookAhead $ g_Done
parseProblemAt loopPos ErrorC "Did you forget the 'do' for this loop?")
parseProblemAt loopPos ErrorC 1057 "Did you forget the 'do' for this loop?")
g_Do `orFail` parseProblem ErrorC "Expected 'do'."
g_Do `orFail` parseProblem ErrorC 1058 "Expected 'do'."
acceptButWarn g_Semi ErrorC "No semicolons directly after 'do'."
acceptButWarn g_Semi ErrorC 1059 "No semicolons directly after 'do'."
allspacing
optional (do
try . lookAhead $ g_Done
parseProblemAt loopPos ErrorC "Can't have empty do clauses (use 'true' as a no-op).")
parseProblemAt loopPos ErrorC 1060 "Can't have empty do clauses (use 'true' as a no-op).")
commands <- readCompoundList
g_Done `orFail` do
parseProblemAt pos ErrorC "Couldn't find 'done' for this 'do'."
parseProblem ErrorC "Expected 'done' matching previously mentioned 'do'."
parseProblemAt pos ErrorC 1061 "Couldn't find 'done' for this 'do'."
parseProblem ErrorC 1062 "Expected 'done' matching previously mentioned 'do'."
return commands
@@ -1369,6 +1477,7 @@ prop_readForClause5 = isOk readForClause "for ((i=0;i<10 && n>x;i++,--n))\ndo \n
prop_readForClause6 = isOk readForClause "for ((;;))\ndo echo $i\ndone"
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"
readForClause = called "for loop" $ do
pos <- getPosition
(T_For id) <- g_For
@@ -1393,7 +1502,7 @@ readForClause = called "for loop" $ do
readRegular = do
name <- readVariableName
spacing
values <- readInClause <|> (readSequentialSep >> return [])
values <- readInClause <|> (optional readSequentialSep >> return [])
return $ \id group -> (return $ T_ForIn id name values group)
prop_readSelectClause1 = isOk readSelectClause "select foo in *; do echo $foo; done"
@@ -1419,7 +1528,7 @@ readInClause = do
do {
lookAhead (g_Do);
parseNote ErrorC "You need a line feed or semicolon before the 'do'.";
parseNote ErrorC 1063 "You need a line feed or semicolon before the 'do'.";
} <|> do {
optional $ g_Semi;
disregard allspacing;
@@ -1450,7 +1559,11 @@ readCaseItem = called "case item" $ do
g_Rparen
readLineBreak
list <- ((lookAhead g_DSEMI >> return []) <|> readCompoundList)
(g_DSEMI <|> lookAhead (readLineBreak >> g_Esac))
(g_DSEMI <|> lookAhead (readLineBreak >> g_Esac)) `attempting` do
pos <- getPosition
lookAhead g_Rparen
parseProblemAt pos ErrorC 1074
"Did you forget the ;; after the previous case item?"
readLineBreak
return (pattern, list)
@@ -1460,12 +1573,15 @@ prop_readFunctionDefinition2 = isWarning readFunctionDefinition "function foo()
prop_readFunctionDefinition3 = isWarning readFunctionDefinition "function foo { lol; }"
prop_readFunctionDefinition4 = isWarning readFunctionDefinition "foo(a, b) { true; }"
prop_readFunctionDefinition5 = isOk readFunctionDefinition ":(){ :|:;}"
prop_readFunctionDefinition6 = isOk readFunctionDefinition "?(){ foo; }"
prop_readFunctionDefinition7 = isOk readFunctionDefinition "..(){ cd ..; }"
prop_readFunctionDefinition8 = isOk readFunctionDefinition "foo() (ls)"
readFunctionDefinition = called "function" $ do
id <- getNextId
name <- try readFunctionSignature
allspacing
(disregard (lookAhead $ char '{') <|> parseProblem ErrorC "Expected a { to open the function definition.")
group <- readBraceGroup
(disregard (lookAhead $ oneOf "{(") <|> parseProblem ErrorC 1064 "Expected a { to open the function definition.")
group <- readBraceGroup <|> readSubshell
return $ T_Function id name group
@@ -1477,13 +1593,13 @@ readFunctionSignature = do
try $ do
string "function"
whitespace
parseProblemAt pos InfoC "Drop the keyword 'function'. It's optional in Bash but invalid in other shells."
parseProblemAt pos InfoC 1005 "Drop the keyword 'function'. It's optional in Bash but invalid in other shells."
spacing
name <- readFunctionName
optional spacing
pos <- getPosition
readParens <|> do
parseProblemAt pos InfoC "Include '()' after the function name (in addition to dropping 'function')."
parseProblemAt pos InfoC 1006 "Include '()' after the function name (in addition to dropping 'function')."
return name
readWithoutFunction = try $ do
@@ -1496,8 +1612,8 @@ readFunctionSignature = do
g_Lparen
optional spacing
g_Rparen <|> do
parseProblem ErrorC "Trying to declare parameters? Don't. Use () and refer to params as $1, $2.."
anyChar `reluctantlyTill` oneOf "\n){"
parseProblem ErrorC 1065 "Trying to declare parameters? Don't. Use () and refer to params as $1, $2.."
many $ noneOf "\n){"
g_Rparen
return ()
@@ -1516,7 +1632,7 @@ readCompoundCommand = do
redirs <- many readIoRedirect
when (not . null $ redirs) $ optional $ do
lookAhead $ try (spacing >> needsSeparator)
parseProblem WarningC "Bash requires ; or \\n here, after redirecting nested compound commands."
parseProblem WarningC 1013 "Bash requires ; or \\n here, after redirecting nested compound commands."
return $ T_Redirecting id redirs $ cmd
where
needsSeparator = choice [ g_Then, g_Else, g_Elif, g_Fi, g_Do, g_Done, g_Esac, g_Rbrace ]
@@ -1527,6 +1643,15 @@ readCompoundList = readTerm
readCmdPrefix = many1 (readIoRedirect <|> readAssignmentWord)
readCmdSuffix = many1 (readIoRedirect <|> readCmdWord)
readModifierSuffix = many1 (readIoRedirect <|> readAssignmentWord <|> readCmdWord)
readTimeSuffix = do
flags <- many readFlag
pipeline <- readPipeline
return $ flags ++ [pipeline]
where
-- This fails for quoted variables and such. Fixme?
readFlag = do
lookAhead $ char '-'
readCmdWord
prop_readAssignmentWord = isOk readAssignmentWord "a=42"
prop_readAssignmentWord2 = isOk readAssignmentWord "b=(1 2 3)"
@@ -1541,10 +1666,10 @@ prop_readAssignmentWord0 = isWarning readAssignmentWord "foo$n=42"
readAssignmentWord = try $ do
id <- getNextId
pos <- getPosition
optional (char '$' >> parseNote ErrorC "Don't use $ on the left side of assignments.")
optional (char '$' >> parseNote ErrorC 1066 "Don't use $ on the left side of assignments.")
variable <- readVariableName
optional (readNormalDollar >> parseNoteAt pos ErrorC
"For indirection, use (associative) arrays or 'read \"var$n\" <<< \"value\"'")
1067 "For indirection, use (associative) arrays or 'read \"var$n\" <<< \"value\"'")
index <- optionMaybe readArrayIndex
space <- spacing
pos <- getPosition
@@ -1553,12 +1678,12 @@ readAssignmentWord = try $ do
if space == "" && space2 /= ""
then do
when (variable /= "IFS") $
parseNoteAt pos InfoC $ "Note that 'var= value' (with space after equals sign) is similar to 'var=\"\"; value'."
parseNoteAt pos InfoC 1007 $ "Note that 'var= value' (with space after equals sign) is similar to 'var=\"\"; value'."
value <- readEmptyLiteral
return $ T_Assignment id op variable index value
else do
when (space /= "" || space2 /= "") $
parseNoteAt pos ErrorC "Don't put spaces around the = in assignments."
parseNoteAt pos ErrorC 1068 "Don't put spaces around the = in assignments."
value <- readArray <|> readNormalWord
spacing
return $ T_Assignment id op variable index value
@@ -1606,7 +1731,7 @@ tryParseWordToken parser t = try $ do
parser
optional (do
try . lookAhead $ char '['
parseProblem ErrorC "You need a space before the [.")
parseProblem ErrorC 1069 "You need a space before the [.")
try $ lookAhead (keywordSeparator)
return $ t id
@@ -1653,20 +1778,16 @@ g_Semi = do
tryToken ";" T_Semi
keywordSeparator =
eof <|> disregard whitespace <|> (disregard $ oneOf ";()[<>&")
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 ]
ifParse p t f = do
(lookAhead (try p) >> t) <|> f
wtf = do
x <- many anyChar
parseProblem ErrorC x
readShebang = do
try $ string "#!"
str <- anyChar `reluctantlyTill` oneOf "\r\n"
str <- many $ noneOf "\r\n"
optional carriageReturn
optional linefeed
return str
@@ -1685,10 +1806,10 @@ readScript = do
do {
allspacing;
commands <- readTerm;
eof <|> (parseProblem ErrorC "Parsing stopped here because of parsing errors.");
eof <|> (parseProblem ErrorC 1070 "Parsing stopped here because of parsing errors.");
return $ T_Script id sb commands;
} <|> do {
parseProblem WarningC "Couldn't read any commands.";
parseProblem WarningC 1014 "Couldn't read any commands.";
return $ T_Script id sb $ [T_EOF id];
}
else do
@@ -1709,8 +1830,8 @@ readScript = do
verifyShell pos s =
case isValidShell s of
Just True -> return ()
Just False -> parseProblemAt pos ErrorC "ShellCheck only supports Bourne based shell scripts, sorry!"
Nothing -> parseProblemAt pos InfoC "This shebang was unrecognized. Note that ShellCheck only handles Bourne based shells."
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."
isValidShell s =
let good = s == "" || any (`isPrefixOf` s) goodShells
@@ -1753,19 +1874,19 @@ parseWithNotes parser = do
parseNotes <- getParseNotes
return (item, map, nub . sortNotes $ parseNotes)
toParseNotes (Metadata pos list) = map (\(Note level note) -> ParseNote pos level note) list
toParseNotes (Metadata pos list) = map (\(Note level code note) -> ParseNote pos level code note) list
notesFromMap map = Map.fold (\x -> (++) (toParseNotes x)) [] map
getAllNotes result = (concatMap (notesFromMap . snd) (maybeToList . parseResult $ result)) ++ (parseNotes result)
compareNotes (ParseNote pos1 level1 s1) (ParseNote pos2 level2 s2) = compare (pos1, level1) (pos2, level2)
compareNotes (ParseNote pos1 level1 _ s1) (ParseNote pos2 level2 _ s2) = compare (pos1, level1) (pos2, level2)
sortNotes = sortBy compareNotes
data ParseResult = ParseResult { parseResult :: Maybe (Token, Map.Map Id Metadata), parseNotes :: [ParseNote] } deriving (Show)
makeErrorFor parsecError =
ParseNote (errorPos parsecError) ErrorC $ getStringFromParsec $ errorMessages parsecError
ParseNote (errorPos parsecError) ErrorC 1072 $ getStringFromParsec $ errorMessages parsecError
getStringFromParsec errors =
case map snd $ sortWith fst $ map f errors of
@@ -1786,10 +1907,12 @@ parseShell filename contents = do
(Left err, (p, context)) -> ParseResult Nothing (nub $ sortNotes $ p ++ (notesForContext context) ++ ([makeErrorFor err]))
where
notesForContext list = zipWith ($) [first, second] list
first (pos, str) = ParseNote pos ErrorC $
isName (ContextName _ _) = True
isName _ = False
notesForContext list = zipWith ($) [first, second] $ filter isName list
first (ContextName pos str) = ParseNote pos ErrorC 1073 $
"Couldn't parse this " ++ str ++ "."
second (pos, str) = ParseNote pos InfoC $
second (ContextName pos str) = ParseNote pos InfoC 1009 $
"The mentioned parser error was in this " ++ str ++ "."
lt x = trace (show x) x

View File

@@ -15,7 +15,7 @@
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
-}
module ShellCheck.Simple (shellCheck, ShellCheckComment, scLine, scColumn, scSeverity, scMessage) where
module ShellCheck.Simple (shellCheck, ShellCheckComment, scLine, scColumn, scSeverity, scCode, scMessage) where
import ShellCheck.Parser
import ShellCheck.Analytics
@@ -23,21 +23,38 @@ import Data.Maybe
import Text.Parsec.Pos
import Data.List
prop_findsParseIssue =
let comments = shellCheck "echo \"$12\"" in
(length comments) == 1 && (scCode $ head comments) == 1037
prop_commentDisablesParseIssue1 =
null $ shellCheck "#shellcheck disable=SC1037\necho \"$12\""
prop_commentDisablesParseIssue2 =
null $ shellCheck "#shellcheck disable=SC1037\n#lol\necho \"$12\""
prop_findsAnalysisIssue =
let comments = shellCheck "echo $1" in
(length comments) == 1 && (scCode $ head comments) == 2086
prop_commentDisablesAnalysisIssue1 =
null $ shellCheck "#shellcheck disable=SC2086\necho $1"
prop_commentDisablesAnalysisIssue2 =
null $ shellCheck "#shellcheck disable=SC2086\n#lol\necho $1"
shellCheck :: String -> [ShellCheckComment]
shellCheck script =
let (ParseResult result notes) = parseShell "-" script in
let allNotes = notes ++ (concat $ maybeToList $ do
(tree, map) <- result
let newMap = runAllAnalytics tree map
return $ notesFromMap newMap
return $ notesFromMap $ filterByAnnotation tree newMap
)
in
map formatNote $ nub $ sortNotes allNotes
data ShellCheckComment = ShellCheckComment { scLine :: Int, scColumn :: Int, scSeverity :: String, scMessage :: String }
data ShellCheckComment = ShellCheckComment { scLine :: Int, scColumn :: Int, scSeverity :: String, scCode :: Int, scMessage :: String }
instance Show ShellCheckComment where
show c = concat ["(", show $ scLine c, ",", show $ scColumn c, ") ", scSeverity c, ": ", scMessage c]
show c = concat ["(", show $ scLine c, ",", show $ scColumn c, ") ", scSeverity c, ": ", show (scCode c), " ", scMessage c]
severityToString s =
case s of
@@ -46,4 +63,5 @@ severityToString s =
InfoC -> "info"
StyleC -> "style"
formatNote (ParseNote pos severity text) = ShellCheckComment (sourceLine pos) (sourceColumn pos) (severityToString severity) text
formatNote (ParseNote pos severity code text) =
ShellCheckComment (sourceLine pos) (sourceColumn pos) (severityToString severity) (fromIntegral code) text

View File

@@ -1,32 +0,0 @@
{-
This file is part of ShellCheck.
http://www.vidarholen.net/contents/shellcheck
ShellCheck is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as published by
the Free Software Foundation, either version 3 of the License, or
(at your option) any later version.
ShellCheck is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
GNU Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
-}
import ShellCheck.Simple
import Text.JSON
instance JSON ShellCheckComment where
showJSON c = makeObj [
("line", showJSON $ scLine c),
("column", showJSON $ scColumn c),
("level", showJSON $ scSeverity c),
("message", showJSON $ scMessage c)
]
readJSON = undefined
main = do
script <- getContents
putStrLn $ encodeStrict $ shellCheck script

118
shellcheck.1.md Normal file
View File

@@ -0,0 +1,118 @@
% SHELLCHECK(1) Shell script analysis tool
# NAME
shellcheck - Shell script analysis tool
# SYNOPSIS
**shellcheck** [*OPTIONS*...] *FILES*...
# DESCRIPTION
ShellCheck is a static analysis and linting tool for sh/bash scripts. It's
mainly focused on handling typical beginner and intermediate level syntax
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.
# 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.
Also note that shellcheck supports multiple Bourne shell dialects, and
examines the file's shebang to determine which one to use.
# FORMATS
**tty**
: Plain text, human readable output. This is the default.
**gcc**
: GCC compatible output. Useful for editors that support compiling and
showing syntax errors.
For example, in Vim, `:set makeprg=shellcheck\ -f\ gcc\ %` will allow
using `:make` to check the script, and `:cnext` to jump to the next error.
<file>:<line>:<column>: <type>: <message>
**checkstyle**
: Checkstyle compatible XML output. Supported directly or through plugins
by many IDEs and build monitoring systems.
<?xml version='1.0' encoding='UTF-8'?>
<checkstyle version='4.3'>
<file name='file'>
<error
line='line'
column='column'
severity='severity'
message='message'
source='ShellCheck.SC####' />
...
</file>
...
</checkstyle>
**json**
: Json is a popular serialization format that is more suitable for web
applications. ShellCheck's json is compact and contains only the bare
minimum.
[
{
"line": line,
"column": column,
"level": level,
"code": ####,
"message": message
},
...
]
# DIRECTIVES
ShellCheck directives can be specified as comments in the shell script
before a command or block:
# shellcheck key=value key=value
command-or-structure
For example, to suppress SC2035 about using `./*.jpg`:
# shellcheck disable=SC2035
echo "Files: " *.jpg
Valid keys are:
**disable**
: Disables a comma separated list of error codes for the following command.
The command can be a simple command like `echo foo`, or a compound command
like a function definition, subshell block or loop.
# AUTHOR
ShellCheck is written and maintained by Vidar Holen.
# REPORTING BUGS
Bugs and issues can be reported on GitHub:
https://github.com/koalaman/shellcheck/issues
# SEE ALSO
sh(1) bash(1)

View File

@@ -15,43 +15,95 @@
You should have received a copy of the GNU Affero General Public License
along with this program. If not, see <http://www.gnu.org/licenses/>.
-}
import Control.Exception
import Control.Monad
import Data.Char
import GHC.Exts
import GHC.IO.Device
import Prelude hiding (catch)
import ShellCheck.Simple
import System.Console.GetOpt
import System.Directory
import System.Environment
import System.Exit
import System.IO
import Text.JSON
import qualified Data.Map as Map
clear = ansi 0
ansi n = "\x1B[" ++ (show n) ++ "m"
data Flag = Flag String String
colorForLevel "error" = 31 -- red
colorForLevel "warning" = 33 -- yellow
colorForLevel "info" = 32 -- green
colorForLevel "style" = 32 -- green
colorForLevel "message" = 1 -- bold
colorForLevel "source" = 0 -- none
colorForLevel _ = 0 -- none
header = "Usage: shellcheck [OPTIONS...] FILES..."
options = [
Option ['f'] ["format"]
(ReqArg (Flag "format") "FORMAT") "output format",
Option ['e'] ["exclude"]
(ReqArg (Flag "exclude") "CODE1,CODE2..") "exclude types of warnings"
]
colorComment level comment = (ansi $ colorForLevel level) ++ comment ++ clear
printErr = hPutStrLn stderr
doFile path colorFunc = do
let actualPath = if path == "-" then "/dev/stdin" else path
exists <- doesFileExist actualPath
if exists then do
contents <- readFile actualPath
doInput path contents colorFunc
syntaxFailure = ExitFailure 3
supportFailure = ExitFailure 4
instance JSON ShellCheckComment where
showJSON c = makeObj [
("line", showJSON $ scLine c),
("column", showJSON $ scColumn c),
("level", showJSON $ scSeverity c),
("code", showJSON $ scCode c),
("message", showJSON $ scMessage c)
]
readJSON = undefined
parseArguments argv =
case getOpt Permute options argv of
(opts, files, []) ->
if not $ null files
then
return $ Just (opts, files)
else do
hPutStrLn stderr (colorFunc "error" $ "No such file: " ++ actualPath)
return False
printErr "No files specified.\n"
printErr $ usageInfo header options
exitWith syntaxFailure
doInput filename contents colorFunc = do
(_, _, errors) -> do
printErr $ (concat errors) ++ "\n" ++ usageInfo header options
exitWith syntaxFailure
formats = Map.fromList [
("json", forJson),
("gcc", forGcc),
("checkstyle", forCheckstyle),
("tty", forTty)
]
forTty options files = do
output <- mapM doFile files
return $ and output
where
clear = ansi 0
ansi n = "\x1B[" ++ (show n) ++ "m"
colorForLevel "error" = 31 -- red
colorForLevel "warning" = 33 -- yellow
colorForLevel "info" = 32 -- green
colorForLevel "style" = 32 -- green
colorForLevel "message" = 1 -- bold
colorForLevel "source" = 0 -- none
colorForLevel _ = 0 -- none
colorComment level comment = (ansi $ colorForLevel level) ++ comment ++ clear
doFile path = do
contents <- readContents path
doInput path contents
doInput filename contents = do
let fileLines = lines contents
let lineCount = length fileLines
let comments = shellCheck contents
let comments = getComments options contents
let groups = groupWith scLine comments
colorFunc <- getColorFunc
mapM_ (\x -> do
let lineNum = scLine (head x)
let line = if lineNum < 1 || lineNum > lineCount
@@ -65,21 +117,154 @@ doInput filename contents colorFunc = do
) groups
return $ null comments
cuteIndent comment =
(replicate ((scColumn comment) - 1) ' ') ++ "^-- " ++ (scMessage comment)
cuteIndent comment =
(replicate ((scColumn comment) - 1) ' ') ++ "^-- " ++ (code $ scCode comment) ++ ": " ++ (scMessage comment)
getColorFunc = do
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
putStrLn $ encodeStrict $ comments
return . null $ comments
-- Mimic GCC "file:line:col: (error|warning|note): message" format
forGcc options files = do
files <- mapM process files
return $ and files
where
process file = do
contents <- readContents file
let comments = makeNonVirtual (getComments options contents) contents
mapM_ (putStrLn . format file) comments
return $ null comments
format filename c = concat [
filename, ":",
show $ scLine c, ":",
show $ scColumn c, ": ",
case scSeverity c of
"error" -> "error"
"warning" -> "warning"
_ -> "note",
": ",
concat . lines $ scMessage c,
" [SC", show $ scCode c, "]"
]
-- Checkstyle compatible output. A bit of a hack to avoid XML dependencies
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
putStrLn "</checkstyle>"
return $ and statuses
where
process file = do
comments <- commentsFor options file
putStrLn (formatFile file comments)
return $ null comments
report error = do
printErr $ show (error :: SomeException)
return False
severity "error" = "error"
severity "warning" = "warning"
severity _ = "info"
attr s v = concat [ s, "='", escape v, "' " ]
escape msg = concatMap escape' msg
escape' c = if isOk c then [c] else "&#" ++ (show $ ord c) ++ ";"
isOk x = any ($x) [isAsciiUpper, isAsciiLower, isDigit, (`elem` " ./")]
formatFile name comments = concat [
"<file ", attr "name" name, ">\n",
concatMap format comments,
"</file>"
]
format c = concat [
"<error ",
attr "line" $ show . scLine $ c,
attr "column" $ show . scColumn $ c,
attr "severity" $ severity . scSeverity $ c,
attr "message" $ scMessage c,
attr "source" $ "ShellCheck.SC" ++ (show $ scCode c),
"/>\n"
]
commentsFor options file =
liftM (getComments options) $ readContents file
getComments options contents =
excludeCodes (getExclusions options) $ shellCheck contents
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) }
real _ r v target | target <= v = r
real [] r v _ = r -- should never happen
real ('\t':rest) r v target =
real rest (r+1) (v + 8 - (v `mod` 8)) target
real (_:rest) r v target = real rest (r+1) (v+1) target
getOption [] _ def = def
getOption ((Flag var val):_) name _ | name == var = val
getOption (_:rest) flag def = getOption rest flag def
getOptions options name =
map (\(Flag _ val) -> val) . filter (\(Flag var _) -> var == name) $ options
split char str =
split' str []
where
split' (a:rest) element =
if a == char
then (reverse element) : split' rest []
else split' rest (a:element)
split' [] element = [reverse element]
getExclusions options =
let elements = concatMap (split ',') $ getOptions options "exclude"
clean = dropWhile (not . isDigit)
in
map (Prelude.read . clean) elements :: [Int]
excludeCodes codes comments =
filter (not . hasCode) comments
where
hasCode c = scCode c `elem` codes
main = do
args <- getArgs
colors <- getColorFunc
if null args then do
hPutStrLn stderr "shellcheck -- bash/sh script static analysis tool"
hPutStrLn stderr "Usage: shellcheck filenames..."
exitFailure
else do
statuses <- mapM (\f -> doFile f colors) args
if and statuses then exitSuccess else exitFailure
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
process Nothing = return False
process (Just (options, files)) =
let format = getOption options "format" "tty" in
case Map.lookup format formats of
Nothing -> do
printErr $ "Unknown format " ++ format
printErr $ "Supported formats:"
mapM_ (printErr . write) $ Map.keys formats
exitWith supportFailure
where write s = " " ++ s
Just f -> do
f options files