mirror of
https://github.com/koalaman/shellcheck.git
synced 2025-09-30 00:39:19 +08:00
Compare commits
60 Commits
Author | SHA1 | Date | |
---|---|---|---|
|
de0145fb29 | ||
|
0d4ae95e1d | ||
|
50db49e2fb | ||
|
60aafae21d | ||
|
902cb9c303 | ||
|
4f1fd43360 | ||
|
ca5af5c55a | ||
|
503cac3bb3 | ||
|
2a9c9ae0ad | ||
|
def4551991 | ||
|
67f4a0d6eb | ||
|
f92f934688 | ||
|
d4059c30b7 | ||
|
b68de7f42b | ||
|
7dacb62d36 | ||
|
3423cde931 | ||
|
b2d1aa01f7 | ||
|
19e1bdf11f | ||
|
75d51087c8 | ||
|
ed524fb77f | ||
|
97045c4af1 | ||
|
1b806f6c9f | ||
|
632c1614a1 | ||
|
00d9ef12e7 | ||
|
d07294810b | ||
|
948b750754 | ||
|
41ae95116d | ||
|
bf3c942294 | ||
|
055b40462d | ||
|
b087b7efb1 | ||
|
5d8d57cf07 | ||
|
661091a9da | ||
|
2ec60c2627 | ||
|
8b4909b238 | ||
|
95a3be6546 | ||
|
968e34e002 | ||
|
197b3e3f20 | ||
|
0e464ea476 | ||
|
811df6f0da | ||
|
4e5d32b05a | ||
|
c5141b77bf | ||
|
9dfeb6b42a | ||
|
77916d2645 | ||
|
4968e7d9ff | ||
|
075d58ee90 | ||
|
6a4a5a815e | ||
|
76a39f254b | ||
|
8ec9fa43fd | ||
|
e8634a3c27 | ||
|
9ae776530b | ||
|
0ec62390d5 | ||
|
82328cd86e | ||
|
5b58da7249 | ||
|
8676517270 | ||
|
4262c4b1bf | ||
|
7ad0110443 | ||
|
e9bba2f75a | ||
|
74ea5eaeec | ||
|
b7ee5f4410 | ||
|
e294db171e |
38
README
38
README
@@ -1,38 +0,0 @@
|
|||||||
ShellCheck - A shell script static analysis tool
|
|
||||||
http://www.vidarholen.net/contents/shellcheck
|
|
||||||
|
|
||||||
Copyright 2012, Vidar 'koala_man' Holen
|
|
||||||
Licensed under the GNU Affero General Public License, v3
|
|
||||||
|
|
||||||
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.
|
|
||||||
|
|
||||||
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 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:
|
|
||||||
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.
|
|
||||||
|
|
||||||
Install:
|
|
||||||
cabal install
|
|
||||||
|
|
||||||
which shellcheck
|
|
||||||
~/.cabal/bin/shellcheck
|
|
||||||
|
|
||||||
Happy ShellChecking!
|
|
68
README.md
Normal file
68
README.md
Normal file
@@ -0,0 +1,68 @@
|
|||||||
|
# ShellCheck - A shell script static analysis tool
|
||||||
|
|
||||||
|
http://www.shellcheck.net
|
||||||
|
|
||||||
|
Copyright 2012-2014, Vidar 'koala_man' Holen
|
||||||
|
Licensed under the GNU Affero General Public License, v3
|
||||||
|
|
||||||
|
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.
|
||||||
|
|
||||||
|
ShellCheck requires at least 1 GB of RAM to compile. Executables can be built with cabal. Tests currently still rely on a Makefile.
|
||||||
|
|
||||||
|
|
||||||
|
## Building with Cabal
|
||||||
|
|
||||||
|
Make sure cabal is installed. On Debian based distros:
|
||||||
|
|
||||||
|
apt-get install cabal-install
|
||||||
|
|
||||||
|
On Fedora:
|
||||||
|
|
||||||
|
yum install cabal-install
|
||||||
|
|
||||||
|
On Mac OS X with homebrew (http://brew.sh/):
|
||||||
|
|
||||||
|
brew install cabal-install
|
||||||
|
|
||||||
|
On Mac OS X with MacPorts (http://www.macports.org/):
|
||||||
|
|
||||||
|
port install hs-cabal-install
|
||||||
|
|
||||||
|
With cabal installed, cd to the shellcheck source directory and:
|
||||||
|
|
||||||
|
$ cabal install
|
||||||
|
...
|
||||||
|
$ which shellcheck
|
||||||
|
~/.cabal/bin/shellcheck
|
||||||
|
|
||||||
|
|
||||||
|
## Building with Make
|
||||||
|
|
||||||
|
ShellCheck is written in Haskell, and requires GHC, Parsec3, JSON and
|
||||||
|
Text.Regex. To run the unit tests, it also requires QuickCheck2.
|
||||||
|
|
||||||
|
On Fedora, these can be installed with:
|
||||||
|
|
||||||
|
yum 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
|
||||||
|
|
||||||
|
To build and run the tests, cd to the shellcheck source directory and:
|
||||||
|
|
||||||
|
$ make
|
||||||
|
|
||||||
|
|
||||||
|
Happy ShellChecking!
|
@@ -1,5 +1,6 @@
|
|||||||
Name: ShellCheck
|
Name: ShellCheck
|
||||||
Version: 0.3.0
|
-- Must also be updated in ShellCheck/Data.hs :
|
||||||
|
Version: 0.3.2
|
||||||
Synopsis: Shell script analysis tool
|
Synopsis: Shell script analysis tool
|
||||||
License: OtherLicense
|
License: OtherLicense
|
||||||
License-file: LICENSE
|
License-file: LICENSE
|
||||||
@@ -8,7 +9,7 @@ Author: Vidar Holen
|
|||||||
Maintainer: vidar@vidarholen.net
|
Maintainer: vidar@vidarholen.net
|
||||||
Homepage: http://www.shellcheck.net/
|
Homepage: http://www.shellcheck.net/
|
||||||
Build-Type: Simple
|
Build-Type: Simple
|
||||||
Cabal-Version: >= 1.6
|
Cabal-Version: >= 1.8
|
||||||
Bug-reports: https://github.com/koalaman/shellcheck/issues
|
Bug-reports: https://github.com/koalaman/shellcheck/issues
|
||||||
Description:
|
Description:
|
||||||
The goals of ShellCheck are:
|
The goals of ShellCheck are:
|
||||||
@@ -27,8 +28,29 @@ source-repository head
|
|||||||
location: git://github.com/koalaman/shellcheck.git
|
location: git://github.com/koalaman/shellcheck.git
|
||||||
|
|
||||||
library
|
library
|
||||||
build-depends: base >= 4, base < 5, parsec, containers, regex-compat, mtl, directory, json
|
build-depends:
|
||||||
exposed-modules: ShellCheck.AST, ShellCheck.Data, ShellCheck.Parser, ShellCheck.Analytics, ShellCheck.Simple
|
base >= 4 && < 5,
|
||||||
|
containers,
|
||||||
|
directory,
|
||||||
|
json,
|
||||||
|
mtl,
|
||||||
|
parsec,
|
||||||
|
regex-compat
|
||||||
|
exposed-modules:
|
||||||
|
ShellCheck.Analytics
|
||||||
|
ShellCheck.AST
|
||||||
|
ShellCheck.Data
|
||||||
|
ShellCheck.Parser
|
||||||
|
ShellCheck.Simple
|
||||||
|
|
||||||
executable shellcheck
|
executable shellcheck
|
||||||
|
build-depends:
|
||||||
|
ShellCheck,
|
||||||
|
base >= 4 && < 5,
|
||||||
|
containers,
|
||||||
|
directory,
|
||||||
|
json,
|
||||||
|
mtl,
|
||||||
|
parsec,
|
||||||
|
regex-compat
|
||||||
main-is: shellcheck.hs
|
main-is: shellcheck.hs
|
||||||
|
@@ -26,6 +26,8 @@ data Id = Id Int deriving (Show, Eq, Ord)
|
|||||||
data Quoted = Quoted | Unquoted deriving (Show, Eq)
|
data Quoted = Quoted | Unquoted deriving (Show, Eq)
|
||||||
data Dashed = Dashed | Undashed deriving (Show, Eq)
|
data Dashed = Dashed | Undashed deriving (Show, Eq)
|
||||||
data AssignmentMode = Assign | Append 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 Token =
|
data Token =
|
||||||
TA_Base Id String Token
|
TA_Base Id String Token
|
||||||
@@ -80,7 +82,7 @@ data Token =
|
|||||||
| T_For Id
|
| T_For Id
|
||||||
| T_ForArithmetic Id Token Token Token [Token]
|
| T_ForArithmetic Id Token Token Token [Token]
|
||||||
| T_ForIn Id String [Token] [Token]
|
| T_ForIn Id String [Token] [Token]
|
||||||
| T_Function Id String Token
|
| T_Function Id FunctionKeyword FunctionParentheses String Token
|
||||||
| T_GREATAND Id
|
| T_GREATAND Id
|
||||||
| T_Glob Id String
|
| T_Glob Id String
|
||||||
| T_Greater Id
|
| T_Greater Id
|
||||||
@@ -100,7 +102,7 @@ data Token =
|
|||||||
| T_NormalWord Id [Token]
|
| T_NormalWord Id [Token]
|
||||||
| T_OR_IF Id
|
| T_OR_IF Id
|
||||||
| T_OrIf Id (Token) (Token)
|
| T_OrIf Id (Token) (Token)
|
||||||
| T_Pipeline Id [Token]
|
| T_Pipeline Id [Token] [Token] -- [Pipe separators] [Commands]
|
||||||
| T_ProcSub Id String [Token]
|
| T_ProcSub Id String [Token]
|
||||||
| T_Rbrace Id
|
| T_Rbrace Id
|
||||||
| T_Redirecting Id [Token] Token
|
| T_Redirecting Id [Token] Token
|
||||||
@@ -118,6 +120,7 @@ data Token =
|
|||||||
| T_While Id
|
| T_While Id
|
||||||
| T_WhileExpression Id [Token] [Token]
|
| T_WhileExpression Id [Token] [Token]
|
||||||
| T_Annotation Id [Annotation] Token
|
| T_Annotation Id [Annotation] Token
|
||||||
|
| T_Pipe Id String
|
||||||
deriving (Show)
|
deriving (Show)
|
||||||
|
|
||||||
data Annotation = DisableComment Integer deriving (Show, Eq)
|
data Annotation = DisableComment Integer deriving (Show, Eq)
|
||||||
@@ -126,12 +129,12 @@ data ConditionType = DoubleBracket | SingleBracket deriving (Show, Eq)
|
|||||||
-- I apologize for nothing!
|
-- I apologize for nothing!
|
||||||
lolHax s = Re.subRegex (Re.mkRegex "(Id [0-9]+)") (show s) "(Id 0)"
|
lolHax s = Re.subRegex (Re.mkRegex "(Id [0-9]+)") (show s) "(Id 0)"
|
||||||
instance Eq Token where
|
instance Eq Token where
|
||||||
(==) a b = (lolHax a) == (lolHax b)
|
(==) a b = lolHax a == lolHax b
|
||||||
|
|
||||||
|
|
||||||
analyze :: Monad m => (Token -> m ()) -> (Token -> m ()) -> (Token -> Token) -> Token -> m Token
|
analyze :: Monad m => (Token -> m ()) -> (Token -> m ()) -> (Token -> Token) -> Token -> m Token
|
||||||
analyze f g i t =
|
analyze f g i =
|
||||||
round t
|
round
|
||||||
where
|
where
|
||||||
round t = do
|
round t = do
|
||||||
f t
|
f t
|
||||||
@@ -180,7 +183,7 @@ analyze f g i t =
|
|||||||
b <- round cmd
|
b <- round cmd
|
||||||
return $ T_Redirecting id a b
|
return $ T_Redirecting id a b
|
||||||
delve (T_SimpleCommand id vars cmds) = dll vars cmds $ T_SimpleCommand id
|
delve (T_SimpleCommand id vars cmds) = dll vars cmds $ T_SimpleCommand id
|
||||||
delve (T_Pipeline id l) = dl l $ T_Pipeline id
|
delve (T_Pipeline id l1 l2) = dll l1 l2 $ T_Pipeline id
|
||||||
delve (T_Banged id l) = d1 l $ T_Banged id
|
delve (T_Banged id l) = d1 l $ T_Banged id
|
||||||
delve (T_AndIf id t u) = d2 t u $ T_AndIf id
|
delve (T_AndIf id t u) = d2 t u $ T_AndIf id
|
||||||
delve (T_OrIf id t u) = d2 t u $ T_OrIf id
|
delve (T_OrIf id t u) = d2 t u $ T_OrIf id
|
||||||
@@ -218,7 +221,7 @@ analyze f g i t =
|
|||||||
return $ T_ForArithmetic id x y z list
|
return $ T_ForArithmetic id x y z list
|
||||||
|
|
||||||
delve (T_Script id s l) = dl l $ T_Script id s
|
delve (T_Script id s l) = dl l $ T_Script id s
|
||||||
delve (T_Function id name body) = d1 body $ T_Function id name
|
delve (T_Function id a b name body) = d1 body $ T_Function id a b name
|
||||||
delve (T_Condition id typ token) = d1 token $ T_Condition id typ
|
delve (T_Condition id typ token) = d1 token $ T_Condition id typ
|
||||||
delve (T_Extglob id str l) = dl l $ T_Extglob id str
|
delve (T_Extglob id str l) = dl l $ T_Extglob id str
|
||||||
delve (T_DollarBraced id op) = d1 op $ T_DollarBraced id
|
delve (T_DollarBraced id op) = d1 op $ T_DollarBraced id
|
||||||
@@ -295,7 +298,7 @@ getId t = case t of
|
|||||||
T_Array id _ -> id
|
T_Array id _ -> id
|
||||||
T_Redirecting id _ _ -> id
|
T_Redirecting id _ _ -> id
|
||||||
T_SimpleCommand id _ _ -> id
|
T_SimpleCommand id _ _ -> id
|
||||||
T_Pipeline id _ -> id
|
T_Pipeline id _ _ -> id
|
||||||
T_Banged id _ -> id
|
T_Banged id _ -> id
|
||||||
T_AndIf id _ _ -> id
|
T_AndIf id _ _ -> id
|
||||||
T_OrIf id _ _ -> id
|
T_OrIf id _ _ -> id
|
||||||
@@ -308,7 +311,7 @@ getId t = case t of
|
|||||||
T_ForIn id _ _ _ -> id
|
T_ForIn id _ _ _ -> id
|
||||||
T_SelectIn id _ _ _ -> id
|
T_SelectIn id _ _ _ -> id
|
||||||
T_CaseExpression id _ _ -> id
|
T_CaseExpression id _ _ -> id
|
||||||
T_Function id _ _ -> id
|
T_Function id _ _ _ _ -> id
|
||||||
T_Arithmetic id _ -> id
|
T_Arithmetic id _ -> id
|
||||||
T_Script id _ _ -> id
|
T_Script id _ _ -> id
|
||||||
T_Condition id _ _ -> id
|
T_Condition id _ _ -> id
|
||||||
@@ -335,10 +338,18 @@ getId t = case t of
|
|||||||
T_DollarDoubleQuoted id _ -> id
|
T_DollarDoubleQuoted id _ -> id
|
||||||
T_DollarBracket id _ -> id
|
T_DollarBracket id _ -> id
|
||||||
T_Annotation id _ _ -> id
|
T_Annotation id _ _ -> id
|
||||||
|
T_Pipe id _ -> id
|
||||||
|
|
||||||
blank :: Monad m => Token -> m ()
|
blank :: Monad m => Token -> m ()
|
||||||
blank = const $ return ()
|
blank = const $ return ()
|
||||||
doAnalysis f t = analyze f blank id t
|
doAnalysis f = analyze f blank id
|
||||||
doStackAnalysis startToken endToken t = analyze startToken endToken id t
|
doStackAnalysis startToken endToken = analyze startToken endToken id
|
||||||
doTransform i t = runIdentity $ analyze blank blank i t
|
doTransform i = runIdentity . analyze blank blank i
|
||||||
|
|
||||||
|
isLoop t = case t of
|
||||||
|
T_WhileExpression {} -> True
|
||||||
|
T_UntilExpression {} -> True
|
||||||
|
T_ForIn {} -> True
|
||||||
|
T_ForArithmetic {} -> True
|
||||||
|
T_SelectIn {} -> True
|
||||||
|
_ -> False
|
||||||
|
File diff suppressed because it is too large
Load Diff
@@ -1,8 +1,10 @@
|
|||||||
module ShellCheck.Data where
|
module ShellCheck.Data where
|
||||||
|
|
||||||
|
shellcheckVersion = "0.3.2" -- Must also be updated in ShellCheck.cabal
|
||||||
|
|
||||||
internalVariables = [
|
internalVariables = [
|
||||||
-- Generic
|
-- Generic
|
||||||
"", "_",
|
"", "_", "rest", "REST",
|
||||||
|
|
||||||
-- Bash
|
-- Bash
|
||||||
"BASH", "BASHOPTS", "BASHPID", "BASH_ALIASES", "BASH_ARGC",
|
"BASH", "BASHOPTS", "BASHPID", "BASH_ALIASES", "BASH_ARGC",
|
||||||
@@ -41,13 +43,13 @@ internalVariables = [
|
|||||||
]
|
]
|
||||||
|
|
||||||
variablesWithoutSpaces = [
|
variablesWithoutSpaces = [
|
||||||
"$", "-", "?", "!",
|
"$", "-", "?", "!",
|
||||||
"BASHPID", "BASH_ARGC", "BASH_LINENO", "BASH_SUBSHELL", "EUID", "LINENO",
|
"BASHPID", "BASH_ARGC", "BASH_LINENO", "BASH_SUBSHELL", "EUID", "LINENO",
|
||||||
"OPTIND", "PPID", "RANDOM", "SECONDS", "SHELLOPTS", "SHLVL", "UID",
|
"OPTIND", "PPID", "RANDOM", "SECONDS", "SHELLOPTS", "SHLVL", "UID",
|
||||||
"COLUMNS", "HISTFILESIZE", "HISTSIZE", "LINES"
|
"COLUMNS", "HISTFILESIZE", "HISTSIZE", "LINES"
|
||||||
]
|
]
|
||||||
|
|
||||||
commonCommands = [
|
commonCommands = [
|
||||||
"admin", "alias", "ar", "asa", "at", "awk", "basename", "batch",
|
"admin", "alias", "ar", "asa", "at", "awk", "basename", "batch",
|
||||||
"bc", "bg", "break", "c99", "cal", "cat", "cd", "cflow", "chgrp",
|
"bc", "bg", "break", "c99", "cal", "cat", "cd", "cflow", "chgrp",
|
||||||
"chmod", "chown", "cksum", "cmp", "colon", "comm", "command",
|
"chmod", "chown", "cksum", "cmp", "colon", "comm", "command",
|
||||||
@@ -70,5 +72,5 @@ commonCommands = [
|
|||||||
"unalias", "uname", "uncompress", "unexpand", "unget", "uniq",
|
"unalias", "uname", "uncompress", "unexpand", "unget", "uniq",
|
||||||
"unlink", "unset", "uucp", "uudecode", "uuencode", "uustat", "uux",
|
"unlink", "unset", "uucp", "uudecode", "uuencode", "uustat", "uux",
|
||||||
"val", "vi", "wait", "wc", "what", "who", "write", "xargs", "yacc",
|
"val", "vi", "wait", "wc", "what", "who", "write", "xargs", "yacc",
|
||||||
"zcat"
|
"zcat"
|
||||||
]
|
]
|
||||||
|
@@ -17,7 +17,7 @@
|
|||||||
-}
|
-}
|
||||||
{-# LANGUAGE NoMonomorphismRestriction #-}
|
{-# LANGUAGE NoMonomorphismRestriction #-}
|
||||||
|
|
||||||
module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), notesFromMap, Metadata(..), sortNotes) where
|
module ShellCheck.Parser (Note(..), Severity(..), parseShell, ParseResult(..), ParseNote(..), sortNotes, noteToParseNote) where
|
||||||
|
|
||||||
import ShellCheck.AST
|
import ShellCheck.AST
|
||||||
import ShellCheck.Data
|
import ShellCheck.Data
|
||||||
@@ -34,8 +34,6 @@ import System.IO
|
|||||||
import Text.Parsec.Error
|
import Text.Parsec.Error
|
||||||
import GHC.Exts (sortWith)
|
import GHC.Exts (sortWith)
|
||||||
|
|
||||||
lastError = 1074
|
|
||||||
|
|
||||||
backslash = char '\\'
|
backslash = char '\\'
|
||||||
linefeed = (optional carriageReturn) >> char '\n'
|
linefeed = (optional carriageReturn) >> char '\n'
|
||||||
singleQuote = char '\'' <|> unicodeSingleQuote
|
singleQuote = char '\'' <|> unicodeSingleQuote
|
||||||
@@ -48,14 +46,18 @@ tokenDelimiter = oneOf "&|;<> \t\n\r" <|> nbsp
|
|||||||
quotableChars = "|&;<>()\\ '\t\n\r\xA0" ++ doubleQuotableChars
|
quotableChars = "|&;<>()\\ '\t\n\r\xA0" ++ doubleQuotableChars
|
||||||
quotable = nbsp <|> unicodeDoubleQuote <|> oneOf quotableChars
|
quotable = nbsp <|> unicodeDoubleQuote <|> oneOf quotableChars
|
||||||
bracedQuotable = oneOf "}\"$`'"
|
bracedQuotable = oneOf "}\"$`'"
|
||||||
doubleQuotableChars = "\"$`\x201C\x201D"
|
doubleQuotableChars = "\"$`" ++ unicodeDoubleQuoteChars
|
||||||
doubleQuotable = unicodeDoubleQuote <|> oneOf doubleQuotableChars
|
doubleQuotable = unicodeDoubleQuote <|> oneOf doubleQuotableChars
|
||||||
whitespace = oneOf " \t\n" <|> carriageReturn <|> nbsp
|
whitespace = oneOf " \t\n" <|> carriageReturn <|> nbsp
|
||||||
linewhitespace = oneOf " \t" <|> nbsp
|
linewhitespace = oneOf " \t" <|> nbsp
|
||||||
|
|
||||||
|
suspectCharAfterQuotes = variableChars <|> char '%'
|
||||||
|
|
||||||
extglobStartChars = "?*@!+"
|
extglobStartChars = "?*@!+"
|
||||||
extglobStart = oneOf extglobStartChars
|
extglobStart = oneOf extglobStartChars
|
||||||
|
|
||||||
|
unicodeDoubleQuoteChars = "\x201C\x201D\x2033\x2036"
|
||||||
|
|
||||||
prop_spacing = isOk spacing " \\\n # Comment"
|
prop_spacing = isOk spacing " \\\n # Comment"
|
||||||
spacing = do
|
spacing = do
|
||||||
x <- many (many1 linewhitespace <|> (try $ string "\\\n"))
|
x <- many (many1 linewhitespace <|> (try $ string "\\\n"))
|
||||||
@@ -80,7 +82,7 @@ allspacingOrFail = do
|
|||||||
|
|
||||||
unicodeDoubleQuote = do
|
unicodeDoubleQuote = do
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
char '\x201C' <|> char '\x201D'
|
oneOf unicodeDoubleQuoteChars
|
||||||
parseProblemAt pos WarningC 1015 "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 '"'
|
return '"'
|
||||||
|
|
||||||
@@ -100,20 +102,20 @@ nbsp = do
|
|||||||
return ' '
|
return ' '
|
||||||
|
|
||||||
--------- Message/position annotation on top of user state
|
--------- Message/position annotation on top of user state
|
||||||
data Note = Note Severity Code String deriving (Show, Eq)
|
data Note = Note Id Severity Code String deriving (Show, Eq)
|
||||||
data ParseNote = ParseNote SourcePos 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 Severity = ErrorC | WarningC | InfoC | StyleC deriving (Show, Eq, Ord)
|
||||||
data Context = ContextName SourcePos String | ContextAnnotation [Annotation]
|
data Context = ContextName SourcePos String | ContextAnnotation [Annotation]
|
||||||
type Code = Integer
|
type Code = Integer
|
||||||
|
|
||||||
codeForNote (Note _ code _) = code
|
|
||||||
codeForParseNote (ParseNote _ _ code _) = code
|
codeForParseNote (ParseNote _ _ code _) = code
|
||||||
|
noteToParseNote map (Note id severity code message) =
|
||||||
|
ParseNote pos severity code message
|
||||||
|
where
|
||||||
|
pos = fromJust $ Map.lookup id map
|
||||||
|
|
||||||
initialState = (Id $ -1, Map.empty, [])
|
initialState = (Id $ -1, Map.empty, [])
|
||||||
|
|
||||||
getInitialMeta pos = Metadata pos []
|
|
||||||
|
|
||||||
getLastId = do
|
getLastId = do
|
||||||
(id, _, _) <- getState
|
(id, _, _) <- getState
|
||||||
return id
|
return id
|
||||||
@@ -121,7 +123,7 @@ getLastId = do
|
|||||||
getNextIdAt sourcepos = do
|
getNextIdAt sourcepos = do
|
||||||
(id, map, notes) <- getState
|
(id, map, notes) <- getState
|
||||||
let newId = incId id
|
let newId = incId id
|
||||||
let newMap = Map.insert newId (getInitialMeta sourcepos) map
|
let newMap = Map.insert newId sourcepos map
|
||||||
putState (newId, newMap, notes)
|
putState (newId, newMap, notes)
|
||||||
return newId
|
return newId
|
||||||
where incId (Id n) = (Id $ n+1)
|
where incId (Id n) = (Id $ n+1)
|
||||||
@@ -189,11 +191,6 @@ parseProblemAt pos level code msg = do
|
|||||||
Ms.modify (\(list, current) -> ((ParseNote pos level code msg):list, current))
|
Ms.modify (\(list, current) -> ((ParseNote pos level code msg):list, current))
|
||||||
|
|
||||||
-- Store non-parse problems inside
|
-- Store non-parse problems inside
|
||||||
addNoteFor id note = modifyMap $ Map.adjust (\(Metadata pos notes) -> Metadata pos (note:notes)) id
|
|
||||||
|
|
||||||
addNote note = do
|
|
||||||
id <- getLastId
|
|
||||||
addNoteFor id note
|
|
||||||
|
|
||||||
parseNote c l a = do
|
parseNote c l a = do
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
@@ -269,6 +266,7 @@ readConditionContents single = do
|
|||||||
where
|
where
|
||||||
typ = if single then SingleBracket else DoubleBracket
|
typ = if single then SingleBracket else DoubleBracket
|
||||||
readCondBinaryOp = try $ do
|
readCondBinaryOp = try $ do
|
||||||
|
optional guardArithmetic
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
op <- (choice $ (map tryOp ["==", "!=", "<=", ">=", "=~", ">", "<", "=", "\\<=", "\\>=", "\\<", "\\>"])) <|> otherOp
|
op <- (choice $ (map tryOp ["==", "!=", "<=", ">=", "=~", ">", "<", "=", "\\<=", "\\>=", "\\<", "\\>"])) <|> otherOp
|
||||||
hardCondSpacing
|
hardCondSpacing
|
||||||
@@ -284,6 +282,13 @@ readConditionContents single = do
|
|||||||
when (s == "-a" || s == "-o") $ fail "Wrong operator"
|
when (s == "-a" || s == "-o") $ fail "Wrong operator"
|
||||||
return $ TC_Binary id typ s
|
return $ TC_Binary id typ s
|
||||||
|
|
||||||
|
guardArithmetic = do
|
||||||
|
try . lookAhead $ disregard (oneOf "+*/%") <|> disregard (string "- ")
|
||||||
|
parseProblem ErrorC 1076 $
|
||||||
|
if single
|
||||||
|
then "Trying to do math? Use e.g. [ $((i/2+7)) -ge 18 ]."
|
||||||
|
else "Trying to do math? Use e.g. [[ $((i/2+7)) -ge 18 ]]."
|
||||||
|
|
||||||
readCondUnaryExp = do
|
readCondUnaryExp = do
|
||||||
op <- readCondUnaryOp
|
op <- readCondUnaryOp
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
@@ -312,9 +317,11 @@ readConditionContents single = do
|
|||||||
when (endedWith "]" x) $ do
|
when (endedWith "]" x) $ do
|
||||||
parseProblemAt pos ErrorC 1020 $
|
parseProblemAt pos ErrorC 1020 $
|
||||||
"You need a space before the " ++ (if single then "]" else "]]") ++ "."
|
"You need a space before the " ++ (if single then "]" else "]]") ++ "."
|
||||||
|
fail "Missing space before ]"
|
||||||
when (single && endedWith ")" x) $ do
|
when (single && endedWith ")" x) $ do
|
||||||
parseProblemAt pos ErrorC 1021 $
|
parseProblemAt pos ErrorC 1021 $
|
||||||
"You need a space before the \\)"
|
"You need a space before the \\)"
|
||||||
|
fail "Missing space before )"
|
||||||
disregard spacing
|
disregard spacing
|
||||||
return x
|
return x
|
||||||
where endedWith str (T_NormalWord id s@(_:_)) =
|
where endedWith str (T_NormalWord id s@(_:_)) =
|
||||||
@@ -325,17 +332,16 @@ readConditionContents single = do
|
|||||||
readCondAndOp = do
|
readCondAndOp = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
x <- try (string "&&" <|> string "-a")
|
x <- try (string "&&" <|> string "-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
|
softCondSpacing
|
||||||
|
skipLineFeeds
|
||||||
return $ TC_And id typ x
|
return $ TC_And id typ x
|
||||||
|
|
||||||
readCondOrOp = do
|
readCondOrOp = do
|
||||||
|
optional guardArithmetic
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
x <- try (string "||" <|> string "-o")
|
x <- try (string "||" <|> string "-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
|
softCondSpacing
|
||||||
|
skipLineFeeds
|
||||||
return $ TC_Or id typ x
|
return $ TC_Or id typ x
|
||||||
|
|
||||||
readCondNoaryOrBinary = do
|
readCondNoaryOrBinary = do
|
||||||
@@ -414,7 +420,17 @@ readConditionContents single = do
|
|||||||
str <- string "|"
|
str <- string "|"
|
||||||
return $ T_Literal id str
|
return $ T_Literal id str
|
||||||
|
|
||||||
readCondTerm = readCondNot <|> readCondExpr
|
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
|
||||||
|
return term
|
||||||
|
|
||||||
readCondNot = do
|
readCondNot = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
char '!'
|
char '!'
|
||||||
@@ -444,6 +460,8 @@ prop_aA = isOk readArithmeticContents "! $?"
|
|||||||
prop_aB = isOk readArithmeticContents "10#08 * 16#f"
|
prop_aB = isOk readArithmeticContents "10#08 * 16#f"
|
||||||
prop_aC = isOk readArithmeticContents "\"$((3+2))\" + '37'"
|
prop_aC = isOk readArithmeticContents "\"$((3+2))\" + '37'"
|
||||||
prop_aD = isOk readArithmeticContents "foo[9*y+x]++"
|
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"
|
||||||
readArithmeticContents =
|
readArithmeticContents =
|
||||||
readSequence
|
readSequence
|
||||||
where
|
where
|
||||||
@@ -477,7 +495,7 @@ readArithmeticContents =
|
|||||||
|
|
||||||
readExpansion = do
|
readExpansion = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
x <- readNormalDollar
|
x <- readNormalDollar <|> readBackTicked
|
||||||
spacing
|
spacing
|
||||||
return $ TA_Expansion id x
|
return $ TA_Expansion id x
|
||||||
|
|
||||||
@@ -611,6 +629,9 @@ prop_readCondition6 = isOk readCondition "[[ $c =~ ^[yY]$ ]]"
|
|||||||
prop_readCondition7 = isOk readCondition "[[ ${line} =~ ^[[:space:]]*# ]]"
|
prop_readCondition7 = isOk readCondition "[[ ${line} =~ ^[[:space:]]*# ]]"
|
||||||
prop_readCondition8 = isOk readCondition "[[ $l =~ ogg|flac ]]"
|
prop_readCondition8 = isOk readCondition "[[ $l =~ ogg|flac ]]"
|
||||||
prop_readCondition9 = isOk readCondition "[ foo -a -f bar ]"
|
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_readCondition12= isWarning readCondition "[ a == b \n -o c == d ]"
|
||||||
readCondition = called "test expression" $ do
|
readCondition = called "test expression" $ do
|
||||||
opos <- getPosition
|
opos <- getPosition
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
@@ -739,17 +760,29 @@ readProcSub = called "process substitution" $ do
|
|||||||
prop_readSingleQuoted = isOk readSingleQuoted "'foo bar'"
|
prop_readSingleQuoted = isOk readSingleQuoted "'foo bar'"
|
||||||
prop_readSingleQuoted2 = isWarning readSingleQuoted "'foo bar\\'"
|
prop_readSingleQuoted2 = isWarning readSingleQuoted "'foo bar\\'"
|
||||||
prop_readsingleQuoted3 = isWarning readSingleQuoted "\x2018hello\x2019"
|
prop_readsingleQuoted3 = isWarning readSingleQuoted "\x2018hello\x2019"
|
||||||
|
prop_readSingleQuoted4 = isWarning readNormalWord "'it's"
|
||||||
|
prop_readSingleQuoted5 = isWarning readSimpleCommand "foo='bar\ncow 'arg"
|
||||||
|
prop_readSingleQuoted6 = isOk readSimpleCommand "foo='bar cow 'arg"
|
||||||
readSingleQuoted = called "single quoted string" $ do
|
readSingleQuoted = called "single quoted string" $ do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
|
startPos <- getPosition
|
||||||
singleQuote
|
singleQuote
|
||||||
s <- readSingleQuotedPart `reluctantlyTill` singleQuote
|
s <- readSingleQuotedPart `reluctantlyTill` singleQuote
|
||||||
pos <- getPosition
|
let string = concat s
|
||||||
|
endPos <- getPosition
|
||||||
singleQuote <?> "end of single quoted string"
|
singleQuote <?> "end of single quoted string"
|
||||||
|
|
||||||
let string = concat s
|
optional $ do
|
||||||
return (T_SingleQuoted id string) `attempting` do
|
c <- try . lookAhead $ suspectCharAfterQuotes <|> oneOf "'"
|
||||||
x <- lookAhead anyChar
|
if (not (null string) && isAlpha c && isAlpha (last string))
|
||||||
when (isAlpha x && not (null string) && isAlpha (last string)) $ parseProblemAt pos WarningC 1011 "This apostrophe terminated the single quoted string!"
|
then
|
||||||
|
parseProblemAt endPos WarningC 1011 $
|
||||||
|
"This apostrophe terminated the single quoted string!"
|
||||||
|
else
|
||||||
|
when ('\n' `elem` string && not ("\n" `isPrefixOf` string)) $
|
||||||
|
suggestForgotClosingQuote startPos endPos "single quoted string"
|
||||||
|
|
||||||
|
return (T_SingleQuoted id string)
|
||||||
|
|
||||||
readSingleQuotedLiteral = do
|
readSingleQuotedLiteral = do
|
||||||
singleQuote
|
singleQuote
|
||||||
@@ -763,13 +796,24 @@ readSingleQuotedPart =
|
|||||||
|
|
||||||
prop_readBackTicked = isOk readBackTicked "`ls *.mp3`"
|
prop_readBackTicked = isOk readBackTicked "`ls *.mp3`"
|
||||||
prop_readBackTicked2 = isOk readBackTicked "`grep \"\\\"\"`"
|
prop_readBackTicked2 = isOk readBackTicked "`grep \"\\\"\"`"
|
||||||
|
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"
|
||||||
readBackTicked = called "backtick expansion" $ do
|
readBackTicked = called "backtick expansion" $ do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
pos <- getPosition
|
startPos <- getPosition
|
||||||
char '`'
|
backtick
|
||||||
subStart <- getPosition
|
subStart <- getPosition
|
||||||
subString <- readGenericLiteral "`"
|
subString <- readGenericLiteral "`´"
|
||||||
char '`'
|
endPos <- getPosition
|
||||||
|
backtick
|
||||||
|
|
||||||
|
optional $ do
|
||||||
|
c <- try . lookAhead $ suspectCharAfterQuotes
|
||||||
|
when ('\n' `elem` subString && not ("\n" `isPrefixOf` subString)) $ do
|
||||||
|
suggestForgotClosingQuote startPos endPos "backtick expansion"
|
||||||
|
|
||||||
-- Result positions may be off due to escapes
|
-- Result positions may be off due to escapes
|
||||||
result <- subParse subStart readCompoundList (unEscape subString)
|
result <- subParse subStart readCompoundList (unEscape subString)
|
||||||
return $ T_Backticked id result
|
return $ T_Backticked id result
|
||||||
@@ -778,6 +822,12 @@ readBackTicked = called "backtick expansion" $ do
|
|||||||
unEscape ('\\':x:rest) | x `elem` "$`\\" = x : unEscape rest
|
unEscape ('\\':x:rest) | x `elem` "$`\\" = x : unEscape rest
|
||||||
unEscape ('\\':'\n':rest) = unEscape rest
|
unEscape ('\\':'\n':rest) = unEscape rest
|
||||||
unEscape (c:rest) = c : unEscape rest
|
unEscape (c:rest) = c : unEscape rest
|
||||||
|
backtick =
|
||||||
|
disregard (char '`') <|> do
|
||||||
|
pos <- getPosition
|
||||||
|
char '´'
|
||||||
|
parseProblemAt pos ErrorC 1077 $
|
||||||
|
"For command expansion, the tick should slant left (` vs ´)."
|
||||||
|
|
||||||
subParse pos parser input = do
|
subParse pos parser input = do
|
||||||
lastPosition <- getPosition
|
lastPosition <- getPosition
|
||||||
@@ -792,12 +842,31 @@ subParse pos parser input = do
|
|||||||
prop_readDoubleQuoted = isOk readDoubleQuoted "\"Hello $FOO\""
|
prop_readDoubleQuoted = isOk readDoubleQuoted "\"Hello $FOO\""
|
||||||
prop_readDoubleQuoted2 = isOk readDoubleQuoted "\"$'\""
|
prop_readDoubleQuoted2 = isOk readDoubleQuoted "\"$'\""
|
||||||
prop_readDoubleQuoted3 = isWarning readDoubleQuoted "\x201Chello\x201D"
|
prop_readDoubleQuoted3 = isWarning readDoubleQuoted "\x201Chello\x201D"
|
||||||
|
prop_readDoubleQuoted4 = isWarning readSimpleCommand "\"foo\nbar\"foo"
|
||||||
|
prop_readDoubleQuoted5 = isOk readSimpleCommand "lol \"foo\nbar\" etc"
|
||||||
readDoubleQuoted = called "double quoted string" $ do
|
readDoubleQuoted = called "double quoted string" $ do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
|
startPos <- getPosition
|
||||||
doubleQuote
|
doubleQuote
|
||||||
x <- many doubleQuotedPart
|
x <- many doubleQuotedPart
|
||||||
|
endPos <- getPosition
|
||||||
doubleQuote <?> "end of double quoted string"
|
doubleQuote <?> "end of double quoted string"
|
||||||
|
optional $ do
|
||||||
|
try . lookAhead $ suspectCharAfterQuotes <|> oneOf "$\""
|
||||||
|
when (any hasLineFeed x && not (startsWithLineFeed x)) $
|
||||||
|
suggestForgotClosingQuote startPos endPos "double quoted string"
|
||||||
return $ T_DoubleQuoted id x
|
return $ T_DoubleQuoted id x
|
||||||
|
where
|
||||||
|
startsWithLineFeed ((T_Literal _ ('\n':_)):_) = True
|
||||||
|
startsWithLineFeed _ = False
|
||||||
|
hasLineFeed (T_Literal _ str) | '\n' `elem` str = True
|
||||||
|
hasLineFeed _ = False
|
||||||
|
|
||||||
|
suggestForgotClosingQuote startPos endPos name = do
|
||||||
|
parseProblemAt startPos WarningC 1078 $
|
||||||
|
"Did you forget to close this " ++ name ++ "?"
|
||||||
|
parseProblemAt endPos InfoC 1079 $
|
||||||
|
"This is actually an end quote, but due to next char it looks suspect."
|
||||||
|
|
||||||
doubleQuotedPart = readDoubleLiteral <|> readDoubleQuotedDollar <|> readBackTicked
|
doubleQuotedPart = readDoubleLiteral <|> readDoubleQuotedDollar <|> readBackTicked
|
||||||
|
|
||||||
@@ -1325,13 +1394,25 @@ transformWithSeparator i _ = id
|
|||||||
|
|
||||||
readPipeSequence = do
|
readPipeSequence = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
list <- readCommand `sepBy1` (readPipe `thenSkip` (spacing >> readLineBreak))
|
(cmds, pipes) <- sepBy1WithSeparators readCommand
|
||||||
|
(readPipe `thenSkip` (spacing >> readLineBreak))
|
||||||
spacing
|
spacing
|
||||||
return $ T_Pipeline id list
|
return $ T_Pipeline id pipes cmds
|
||||||
|
where
|
||||||
|
sepBy1WithSeparators p s = do
|
||||||
|
let elems = p >>= \x -> return ([x], [])
|
||||||
|
let seps = do
|
||||||
|
separator <- s
|
||||||
|
return $ \(a,b) (c,d) -> (a++c, b ++ d ++ [separator])
|
||||||
|
elems `chainl1` seps
|
||||||
|
|
||||||
readPipe = do
|
readPipe = do
|
||||||
notFollowedBy2 g_OR_IF
|
notFollowedBy2 g_OR_IF
|
||||||
char '|' `thenSkip` spacing
|
id <- getNextId
|
||||||
|
char '|'
|
||||||
|
qualifier <- string "&" <|> return ""
|
||||||
|
spacing
|
||||||
|
return $ T_Pipe id ('|':qualifier)
|
||||||
|
|
||||||
readCommand = (readCompoundCommand <|> readSimpleCommand)
|
readCommand = (readCompoundCommand <|> readSimpleCommand)
|
||||||
|
|
||||||
@@ -1348,6 +1429,8 @@ readCmdWord = do
|
|||||||
prop_readIfClause = isOk readIfClause "if false; then foo; elif true; then stuff; more stuff; else cows; fi"
|
prop_readIfClause = isOk readIfClause "if false; then foo; elif true; then stuff; more stuff; else cows; fi"
|
||||||
prop_readIfClause2 = isWarning readIfClause "if false; then; echo oo; fi"
|
prop_readIfClause2 = isWarning readIfClause "if false; then; echo oo; fi"
|
||||||
prop_readIfClause3 = isWarning readIfClause "if false; then true; else; echo lol; fi"
|
prop_readIfClause3 = isWarning readIfClause "if false; then true; else; echo lol; fi"
|
||||||
|
prop_readIfClause4 = isWarning readIfClause "if false; then true; else if true; then echo lol; fi"
|
||||||
|
prop_readIfClause5 = isOk readIfClause "if false; then true; else\nif true; then echo lol; fi; fi"
|
||||||
readIfClause = called "if expression" $ do
|
readIfClause = called "if expression" $ do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
@@ -1389,7 +1472,9 @@ readIfPart = do
|
|||||||
|
|
||||||
readElifPart = called "elif clause" $ do
|
readElifPart = called "elif clause" $ do
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
g_Elif
|
correctElif <- elif
|
||||||
|
when (not correctElif) $
|
||||||
|
parseProblemAt pos ErrorC 1075 "Use 'elif' instead of 'else if'."
|
||||||
allspacing
|
allspacing
|
||||||
condition <- readTerm
|
condition <- readTerm
|
||||||
g_Then
|
g_Then
|
||||||
@@ -1398,8 +1483,12 @@ readElifPart = called "elif clause" $ do
|
|||||||
verifyNotEmptyIf "then"
|
verifyNotEmptyIf "then"
|
||||||
action <- readTerm
|
action <- readTerm
|
||||||
return (condition, action)
|
return (condition, action)
|
||||||
|
where
|
||||||
|
elif = (g_Elif >> return True) <|>
|
||||||
|
(try $ g_Else >> g_If >> return False)
|
||||||
|
|
||||||
readElsePart = called "else clause" $ do
|
readElsePart = called "else clause" $ do
|
||||||
|
pos <- getPosition
|
||||||
g_Else
|
g_Else
|
||||||
acceptButWarn g_Semi ErrorC 1053 "No semicolons directly after 'else'."
|
acceptButWarn g_Semi ErrorC 1053 "No semicolons directly after 'else'."
|
||||||
allspacing
|
allspacing
|
||||||
@@ -1478,15 +1567,14 @@ prop_readForClause6 = isOk readForClause "for ((;;))\ndo echo $i\ndone"
|
|||||||
prop_readForClause7 = isOk readForClause "for ((;;)) do echo $i\ndone"
|
prop_readForClause7 = isOk readForClause "for ((;;)) do echo $i\ndone"
|
||||||
prop_readForClause8 = isOk readForClause "for ((;;)) ; do echo $i\ndone"
|
prop_readForClause8 = isOk readForClause "for ((;;)) ; do echo $i\ndone"
|
||||||
prop_readForClause9 = isOk readForClause "for i do true; done"
|
prop_readForClause9 = isOk readForClause "for i do true; done"
|
||||||
|
prop_readForClause10= isOk readForClause "for ((;;)) { true; }"
|
||||||
readForClause = called "for loop" $ do
|
readForClause = called "for loop" $ do
|
||||||
pos <- getPosition
|
pos <- getPosition
|
||||||
(T_For id) <- g_For
|
(T_For id) <- g_For
|
||||||
spacing
|
spacing
|
||||||
typ <- (readRegular <|> readArithmetic)
|
readRegular id pos <|> readArithmetic id pos
|
||||||
group <- readDoGroup pos
|
|
||||||
typ id group
|
|
||||||
where
|
where
|
||||||
readArithmetic = called "arithmetic for condition" $ do
|
readArithmetic id pos = called "arithmetic for condition" $ do
|
||||||
try $ string "(("
|
try $ string "(("
|
||||||
x <- readArithmeticContents
|
x <- readArithmeticContents
|
||||||
char ';' >> spacing
|
char ';' >> spacing
|
||||||
@@ -1497,13 +1585,19 @@ readForClause = called "for loop" $ do
|
|||||||
string "))"
|
string "))"
|
||||||
spacing
|
spacing
|
||||||
optional $ readSequentialSep >> spacing
|
optional $ readSequentialSep >> spacing
|
||||||
return $ \id group -> (return $ T_ForArithmetic id x y z group)
|
group <- readBraced <|> readDoGroup pos
|
||||||
|
return $ T_ForArithmetic id x y z group
|
||||||
|
|
||||||
readRegular = do
|
readBraced = do
|
||||||
|
(T_BraceGroup _ list) <- readBraceGroup
|
||||||
|
return list
|
||||||
|
|
||||||
|
readRegular id pos = do
|
||||||
name <- readVariableName
|
name <- readVariableName
|
||||||
spacing
|
spacing
|
||||||
values <- readInClause <|> (optional readSequentialSep >> return [])
|
values <- readInClause <|> (optional readSequentialSep >> return [])
|
||||||
return $ \id group -> (return $ T_ForIn id name values group)
|
group <- readDoGroup pos
|
||||||
|
return $ T_ForIn id name values group
|
||||||
|
|
||||||
prop_readSelectClause1 = isOk readSelectClause "select foo in *; do echo $foo; done"
|
prop_readSelectClause1 = isOk readSelectClause "select foo in *; do echo $foo; done"
|
||||||
prop_readSelectClause2 = isOk readSelectClause "select foo; do echo $foo; done"
|
prop_readSelectClause2 = isOk readSelectClause "select foo; do echo $foo; done"
|
||||||
@@ -1569,61 +1663,52 @@ readCaseItem = called "case item" $ do
|
|||||||
|
|
||||||
prop_readFunctionDefinition = isOk readFunctionDefinition "foo() { command foo --lol \"$@\"; }"
|
prop_readFunctionDefinition = isOk readFunctionDefinition "foo() { command foo --lol \"$@\"; }"
|
||||||
prop_readFunctionDefinition1 = isOk readFunctionDefinition "foo (){ command foo --lol \"$@\"; }"
|
prop_readFunctionDefinition1 = isOk readFunctionDefinition "foo (){ command foo --lol \"$@\"; }"
|
||||||
prop_readFunctionDefinition2 = isWarning readFunctionDefinition "function foo() { command foo --lol \"$@\"; }"
|
|
||||||
prop_readFunctionDefinition3 = isWarning readFunctionDefinition "function foo { lol; }"
|
|
||||||
prop_readFunctionDefinition4 = isWarning readFunctionDefinition "foo(a, b) { true; }"
|
prop_readFunctionDefinition4 = isWarning readFunctionDefinition "foo(a, b) { true; }"
|
||||||
prop_readFunctionDefinition5 = isOk readFunctionDefinition ":(){ :|:;}"
|
prop_readFunctionDefinition5 = isOk readFunctionDefinition ":(){ :|:;}"
|
||||||
prop_readFunctionDefinition6 = isOk readFunctionDefinition "?(){ foo; }"
|
prop_readFunctionDefinition6 = isOk readFunctionDefinition "?(){ foo; }"
|
||||||
prop_readFunctionDefinition7 = isOk readFunctionDefinition "..(){ cd ..; }"
|
prop_readFunctionDefinition7 = isOk readFunctionDefinition "..(){ cd ..; }"
|
||||||
prop_readFunctionDefinition8 = isOk readFunctionDefinition "foo() (ls)"
|
prop_readFunctionDefinition8 = isOk readFunctionDefinition "foo() (ls)"
|
||||||
readFunctionDefinition = called "function" $ do
|
readFunctionDefinition = called "function" $ do
|
||||||
id <- getNextId
|
functionSignature <- try readFunctionSignature
|
||||||
name <- try readFunctionSignature
|
|
||||||
allspacing
|
allspacing
|
||||||
(disregard (lookAhead $ oneOf "{(") <|> parseProblem ErrorC 1064 "Expected a { to open the function definition.")
|
(disregard (lookAhead $ oneOf "{(") <|> parseProblem ErrorC 1064 "Expected a { to open the function definition.")
|
||||||
group <- readBraceGroup <|> readSubshell
|
group <- readBraceGroup <|> readSubshell
|
||||||
return $ T_Function id name group
|
return $ functionSignature group
|
||||||
|
|
||||||
|
|
||||||
readFunctionSignature = do
|
|
||||||
readWithFunction <|> readWithoutFunction
|
|
||||||
where
|
where
|
||||||
readWithFunction = do
|
readFunctionSignature = do
|
||||||
pos <- getPosition
|
readWithFunction <|> readWithoutFunction
|
||||||
try $ do
|
where
|
||||||
string "function"
|
readWithFunction = do
|
||||||
whitespace
|
id <- getNextId
|
||||||
parseProblemAt pos InfoC 1005 "Drop the keyword 'function'. It's optional in Bash but invalid in other shells."
|
try $ do
|
||||||
spacing
|
string "function"
|
||||||
name <- readFunctionName
|
whitespace
|
||||||
optional spacing
|
spacing
|
||||||
pos <- getPosition
|
name <- readFunctionName
|
||||||
readParens <|> do
|
optional spacing
|
||||||
parseProblemAt pos InfoC 1006 "Include '()' after the function name (in addition to dropping 'function')."
|
hasParens <- wasIncluded readParens
|
||||||
return name
|
return $ T_Function id (FunctionKeyword True) (FunctionParentheses hasParens) name
|
||||||
|
|
||||||
readWithoutFunction = try $ do
|
readWithoutFunction = try $ do
|
||||||
name <- readFunctionName
|
id <- getNextId
|
||||||
optional spacing
|
name <- readFunctionName
|
||||||
readParens
|
optional spacing
|
||||||
return name
|
readParens
|
||||||
|
return $ T_Function id (FunctionKeyword False) (FunctionParentheses True) name
|
||||||
readParens = do
|
|
||||||
g_Lparen
|
|
||||||
optional spacing
|
|
||||||
g_Rparen <|> do
|
|
||||||
parseProblem ErrorC 1065 "Trying to declare parameters? Don't. Use () and refer to params as $1, $2.."
|
|
||||||
many $ noneOf "\n){"
|
|
||||||
g_Rparen
|
|
||||||
return ()
|
|
||||||
|
|
||||||
readFunctionName = many1 functionChars
|
|
||||||
|
|
||||||
|
readParens = do
|
||||||
|
g_Lparen
|
||||||
|
optional spacing
|
||||||
|
g_Rparen <|> do
|
||||||
|
parseProblem ErrorC 1065 "Trying to declare parameters? Don't. Use () and refer to params as $1, $2.."
|
||||||
|
many $ noneOf "\n){"
|
||||||
|
g_Rparen
|
||||||
|
return ()
|
||||||
|
|
||||||
|
readFunctionName = many1 functionChars
|
||||||
|
|
||||||
readPattern = (readNormalWord `thenSkip` spacing) `sepBy1` (char '|' `thenSkip` spacing)
|
readPattern = (readNormalWord `thenSkip` spacing) `sepBy1` (char '|' `thenSkip` spacing)
|
||||||
|
|
||||||
|
|
||||||
prop_readCompoundCommand = isOk readCompoundCommand "{ echo foo; }>/dev/null"
|
prop_readCompoundCommand = isOk readCompoundCommand "{ echo foo; }>/dev/null"
|
||||||
readCompoundCommand = do
|
readCompoundCommand = do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
@@ -1678,7 +1763,8 @@ readAssignmentWord = try $ do
|
|||||||
if space == "" && space2 /= ""
|
if space == "" && space2 /= ""
|
||||||
then do
|
then do
|
||||||
when (variable /= "IFS") $
|
when (variable /= "IFS") $
|
||||||
parseNoteAt pos InfoC 1007 $ "Note that 'var= value' (with space after equals sign) is similar to 'var=\"\"; value'."
|
parseNoteAt pos WarningC 1007
|
||||||
|
"Remove space after = if trying to assign a value (for empty string, use var='' ... )."
|
||||||
value <- readEmptyLiteral
|
value <- readEmptyLiteral
|
||||||
return $ T_Assignment id op variable index value
|
return $ T_Assignment id op variable index value
|
||||||
else do
|
else do
|
||||||
@@ -1725,16 +1811,24 @@ redirToken c t = try $ do
|
|||||||
notFollowedBy2 $ char '('
|
notFollowedBy2 $ char '('
|
||||||
return $ t id
|
return $ t id
|
||||||
|
|
||||||
tryWordToken s t = tryParseWordToken (string s) t `thenSkip` spacing
|
tryWordToken s t = tryParseWordToken s t `thenSkip` spacing
|
||||||
tryParseWordToken parser t = try $ do
|
tryParseWordToken keyword t = try $ do
|
||||||
id <- getNextId
|
id <- getNextId
|
||||||
parser
|
str <- anycaseString keyword
|
||||||
optional (do
|
optional (do
|
||||||
try . lookAhead $ char '['
|
try . lookAhead $ char '['
|
||||||
parseProblem ErrorC 1069 "You need a space before the [.")
|
parseProblem ErrorC 1069 "You need a space before the [.")
|
||||||
try $ lookAhead (keywordSeparator)
|
try $ lookAhead (keywordSeparator)
|
||||||
|
when (str /= keyword) $
|
||||||
|
parseProblem ErrorC 1081 $
|
||||||
|
"Scripts are case sensitive. Use '" ++ keyword ++ "', not '" ++ str ++ "'."
|
||||||
return $ t id
|
return $ t id
|
||||||
|
|
||||||
|
anycaseString str =
|
||||||
|
mapM anycaseChar str
|
||||||
|
where
|
||||||
|
anycaseChar c = char (toLower c) <|> char (toUpper c)
|
||||||
|
|
||||||
g_AND_IF = tryToken "&&" T_AND_IF
|
g_AND_IF = tryToken "&&" T_AND_IF
|
||||||
g_OR_IF = tryToken "||" T_OR_IF
|
g_OR_IF = tryToken "||" T_OR_IF
|
||||||
g_DSEMI = tryToken ";;" T_DSEMI
|
g_DSEMI = tryToken ";;" T_DSEMI
|
||||||
@@ -1865,7 +1959,7 @@ isOk p s = (fst cs) && (null . snd $ cs) where cs = checkString p s
|
|||||||
|
|
||||||
checkString parser string =
|
checkString parser string =
|
||||||
case rp (parser >> eof >> getState) "-" string of
|
case rp (parser >> eof >> getState) "-" string of
|
||||||
(Right (tree, map, notes), (problems, _)) -> (True, (notesFromMap map) ++ notes ++ problems)
|
(Right (tree, map, notes), (problems, _)) -> (True, notes ++ problems)
|
||||||
(Left _, (n, _)) -> (False, n)
|
(Left _, (n, _)) -> (False, n)
|
||||||
|
|
||||||
parseWithNotes parser = do
|
parseWithNotes parser = do
|
||||||
@@ -1874,16 +1968,11 @@ parseWithNotes parser = do
|
|||||||
parseNotes <- getParseNotes
|
parseNotes <- getParseNotes
|
||||||
return (item, map, nub . sortNotes $ parseNotes)
|
return (item, map, nub . sortNotes $ parseNotes)
|
||||||
|
|
||||||
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
|
sortNotes = sortBy compareNotes
|
||||||
|
|
||||||
|
|
||||||
data ParseResult = ParseResult { parseResult :: Maybe (Token, Map.Map Id Metadata), parseNotes :: [ParseNote] } deriving (Show)
|
data ParseResult = ParseResult { parseResult :: Maybe (Token, Map.Map Id SourcePos), parseNotes :: [ParseNote] } deriving (Show)
|
||||||
|
|
||||||
makeErrorFor parsecError =
|
makeErrorFor parsecError =
|
||||||
ParseNote (errorPos parsecError) ErrorC 1072 $ getStringFromParsec $ errorMessages parsecError
|
ParseNote (errorPos parsecError) ErrorC 1072 $ getStringFromParsec $ errorMessages parsecError
|
||||||
@@ -1903,9 +1992,11 @@ getStringFromParsec errors =
|
|||||||
|
|
||||||
parseShell filename contents = do
|
parseShell filename contents = do
|
||||||
case rp (parseWithNotes readScript) filename contents of
|
case rp (parseWithNotes readScript) filename contents of
|
||||||
(Right (script, map, notes), (parsenotes, _)) -> ParseResult (Just (script, map)) (nub $ sortNotes $ notes ++ parsenotes)
|
(Right (script, map, notes), (parsenotes, _)) ->
|
||||||
(Left err, (p, context)) -> ParseResult Nothing (nub $ sortNotes $ p ++ (notesForContext context) ++ ([makeErrorFor err]))
|
ParseResult (Just (script, map)) (nub $ sortNotes $ notes ++ parsenotes)
|
||||||
|
(Left err, (p, context)) ->
|
||||||
|
ParseResult Nothing
|
||||||
|
(nub $ sortNotes $ p ++ (notesForContext context) ++ ([makeErrorFor err]))
|
||||||
where
|
where
|
||||||
isName (ContextName _ _) = True
|
isName (ContextName _ _) = True
|
||||||
isName _ = False
|
isName _ = False
|
||||||
|
@@ -25,28 +25,28 @@ import Data.List
|
|||||||
|
|
||||||
|
|
||||||
prop_findsParseIssue =
|
prop_findsParseIssue =
|
||||||
let comments = shellCheck "echo \"$12\"" in
|
let comments = shellCheck "echo \"$12\"" [] in
|
||||||
(length comments) == 1 && (scCode $ head comments) == 1037
|
(length comments) == 1 && (scCode $ head comments) == 1037
|
||||||
prop_commentDisablesParseIssue1 =
|
prop_commentDisablesParseIssue1 =
|
||||||
null $ shellCheck "#shellcheck disable=SC1037\necho \"$12\""
|
null $ shellCheck "#shellcheck disable=SC1037\necho \"$12\"" []
|
||||||
prop_commentDisablesParseIssue2 =
|
prop_commentDisablesParseIssue2 =
|
||||||
null $ shellCheck "#shellcheck disable=SC1037\n#lol\necho \"$12\""
|
null $ shellCheck "#shellcheck disable=SC1037\n#lol\necho \"$12\"" []
|
||||||
|
|
||||||
prop_findsAnalysisIssue =
|
prop_findsAnalysisIssue =
|
||||||
let comments = shellCheck "echo $1" in
|
let comments = shellCheck "echo $1" [] in
|
||||||
(length comments) == 1 && (scCode $ head comments) == 2086
|
(length comments) == 1 && (scCode $ head comments) == 2086
|
||||||
prop_commentDisablesAnalysisIssue1 =
|
prop_commentDisablesAnalysisIssue1 =
|
||||||
null $ shellCheck "#shellcheck disable=SC2086\necho $1"
|
null $ shellCheck "#shellcheck disable=SC2086\necho $1" []
|
||||||
prop_commentDisablesAnalysisIssue2 =
|
prop_commentDisablesAnalysisIssue2 =
|
||||||
null $ shellCheck "#shellcheck disable=SC2086\n#lol\necho $1"
|
null $ shellCheck "#shellcheck disable=SC2086\n#lol\necho $1" []
|
||||||
|
|
||||||
shellCheck :: String -> [ShellCheckComment]
|
shellCheck :: String -> [AnalysisOption] -> [ShellCheckComment]
|
||||||
shellCheck script =
|
shellCheck script options =
|
||||||
let (ParseResult result notes) = parseShell "-" script in
|
let (ParseResult result notes) = parseShell "-" script in
|
||||||
let allNotes = notes ++ (concat $ maybeToList $ do
|
let allNotes = notes ++ (concat $ maybeToList $ do
|
||||||
(tree, map) <- result
|
(tree, posMap) <- result
|
||||||
let newMap = runAllAnalytics tree map
|
let list = runAnalytics options tree
|
||||||
return $ notesFromMap $ filterByAnnotation tree newMap
|
return $ map (noteToParseNote posMap) $ filterByAnnotation tree list
|
||||||
)
|
)
|
||||||
in
|
in
|
||||||
map formatNote $ nub $ sortNotes allNotes
|
map formatNote $ nub $ sortNotes allNotes
|
||||||
|
@@ -30,8 +30,11 @@ corner cases can cause delayed failures.
|
|||||||
options are cumulative, but all the codes can be specified at once,
|
options are cumulative, but all the codes can be specified at once,
|
||||||
comma-separated as a single argument.
|
comma-separated as a single argument.
|
||||||
|
|
||||||
Also note that shellcheck supports multiple Bourne shell dialects, and
|
**-s**\ *shell*,\ **--shell=***shell*
|
||||||
examines the file's shebang to determine which one to use.
|
|
||||||
|
: 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.
|
||||||
|
|
||||||
# FORMATS
|
# FORMATS
|
||||||
|
|
||||||
|
@@ -18,10 +18,13 @@
|
|||||||
import Control.Exception
|
import Control.Exception
|
||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Data.Char
|
import Data.Char
|
||||||
|
import Data.Maybe
|
||||||
import GHC.Exts
|
import GHC.Exts
|
||||||
import GHC.IO.Device
|
import GHC.IO.Device
|
||||||
import Prelude hiding (catch)
|
import Prelude hiding (catch)
|
||||||
|
import ShellCheck.Data
|
||||||
import ShellCheck.Simple
|
import ShellCheck.Simple
|
||||||
|
import ShellCheck.Analytics
|
||||||
import System.Console.GetOpt
|
import System.Console.GetOpt
|
||||||
import System.Directory
|
import System.Directory
|
||||||
import System.Environment
|
import System.Environment
|
||||||
@@ -37,7 +40,11 @@ options = [
|
|||||||
Option ['f'] ["format"]
|
Option ['f'] ["format"]
|
||||||
(ReqArg (Flag "format") "FORMAT") "output format",
|
(ReqArg (Flag "format") "FORMAT") "output format",
|
||||||
Option ['e'] ["exclude"]
|
Option ['e'] ["exclude"]
|
||||||
(ReqArg (Flag "exclude") "CODE1,CODE2..") "exclude types of warnings"
|
(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"]
|
||||||
|
(NoArg $ Flag "version" "true") "Print version information"
|
||||||
]
|
]
|
||||||
|
|
||||||
printErr = hPutStrLn stderr
|
printErr = hPutStrLn stderr
|
||||||
@@ -57,17 +64,12 @@ instance JSON ShellCheckComment where
|
|||||||
|
|
||||||
parseArguments argv =
|
parseArguments argv =
|
||||||
case getOpt Permute options argv of
|
case getOpt Permute options argv of
|
||||||
(opts, files, []) ->
|
(opts, files, []) -> do
|
||||||
if not $ null files
|
verifyOptions opts files
|
||||||
then
|
return $ Just (opts, files)
|
||||||
return $ Just (opts, files)
|
|
||||||
else do
|
|
||||||
printErr "No files specified.\n"
|
|
||||||
printErr $ usageInfo header options
|
|
||||||
exitWith syntaxFailure
|
|
||||||
|
|
||||||
(_, _, errors) -> do
|
(_, _, errors) -> do
|
||||||
printErr $ (concat errors) ++ "\n" ++ usageInfo header options
|
printErr $ concat errors ++ "\n" ++ usageInfo header options
|
||||||
exitWith syntaxFailure
|
exitWith syntaxFailure
|
||||||
|
|
||||||
formats = Map.fromList [
|
formats = Map.fromList [
|
||||||
@@ -82,7 +84,7 @@ forTty options files = do
|
|||||||
return $ and output
|
return $ and output
|
||||||
where
|
where
|
||||||
clear = ansi 0
|
clear = ansi 0
|
||||||
ansi n = "\x1B[" ++ (show n) ++ "m"
|
ansi n = "\x1B[" ++ show n ++ "m"
|
||||||
|
|
||||||
colorForLevel "error" = 31 -- red
|
colorForLevel "error" = 31 -- red
|
||||||
colorForLevel "warning" = 33 -- yellow
|
colorForLevel "warning" = 33 -- yellow
|
||||||
@@ -92,7 +94,8 @@ forTty options files = do
|
|||||||
colorForLevel "source" = 0 -- none
|
colorForLevel "source" = 0 -- none
|
||||||
colorForLevel _ = 0 -- none
|
colorForLevel _ = 0 -- none
|
||||||
|
|
||||||
colorComment level comment = (ansi $ colorForLevel level) ++ comment ++ clear
|
colorComment level comment =
|
||||||
|
ansi (colorForLevel level) ++ comment ++ clear
|
||||||
|
|
||||||
doFile path = do
|
doFile path = do
|
||||||
contents <- readContents path
|
contents <- readContents path
|
||||||
@@ -110,15 +113,17 @@ forTty options files = do
|
|||||||
then ""
|
then ""
|
||||||
else fileLines !! (lineNum - 1)
|
else fileLines !! (lineNum - 1)
|
||||||
putStrLn ""
|
putStrLn ""
|
||||||
putStrLn $ colorFunc "message" ("In " ++ filename ++" line " ++ (show $ lineNum) ++ ":")
|
putStrLn $ colorFunc "message"
|
||||||
|
("In " ++ filename ++" line " ++ show lineNum ++ ":")
|
||||||
putStrLn (colorFunc "source" line)
|
putStrLn (colorFunc "source" line)
|
||||||
mapM (\c -> putStrLn (colorFunc (scSeverity c) $ cuteIndent c)) x
|
mapM_ (\c -> putStrLn (colorFunc (scSeverity c) $ cuteIndent c)) x
|
||||||
putStrLn ""
|
putStrLn ""
|
||||||
) groups
|
) groups
|
||||||
return $ null comments
|
return $ null comments
|
||||||
|
|
||||||
cuteIndent comment =
|
cuteIndent comment =
|
||||||
(replicate ((scColumn comment) - 1) ' ') ++ "^-- " ++ (code $ scCode comment) ++ ": " ++ (scMessage comment)
|
replicate (scColumn comment - 1) ' ' ++
|
||||||
|
"^-- " ++ code (scCode comment) ++ ": " ++ scMessage comment
|
||||||
|
|
||||||
code code = "SC" ++ (show code)
|
code code = "SC" ++ (show code)
|
||||||
|
|
||||||
@@ -129,7 +134,7 @@ forTty options files = do
|
|||||||
-- This totally ignores the filenames. Fixme?
|
-- This totally ignores the filenames. Fixme?
|
||||||
forJson options files = do
|
forJson options files = do
|
||||||
comments <- liftM concat $ mapM (commentsFor options) files
|
comments <- liftM concat $ mapM (commentsFor options) files
|
||||||
putStrLn $ encodeStrict $ comments
|
putStrLn $ encodeStrict comments
|
||||||
return . null $ comments
|
return . null $ comments
|
||||||
|
|
||||||
-- Mimic GCC "file:line:col: (error|warning|note): message" format
|
-- Mimic GCC "file:line:col: (error|warning|note): message" format
|
||||||
@@ -176,8 +181,8 @@ forCheckstyle options files = do
|
|||||||
severity "warning" = "warning"
|
severity "warning" = "warning"
|
||||||
severity _ = "info"
|
severity _ = "info"
|
||||||
attr s v = concat [ s, "='", escape v, "' " ]
|
attr s v = concat [ s, "='", escape v, "' " ]
|
||||||
escape msg = concatMap escape' msg
|
escape = concatMap escape'
|
||||||
escape' c = if isOk c then [c] else "&#" ++ (show $ ord c) ++ ";"
|
escape' c = if isOk c then [c] else "&#" ++ show (ord c) ++ ";"
|
||||||
isOk x = any ($x) [isAsciiUpper, isAsciiLower, isDigit, (`elem` " ./")]
|
isOk x = any ($x) [isAsciiUpper, isAsciiLower, isDigit, (`elem` " ./")]
|
||||||
|
|
||||||
formatFile name comments = concat [
|
formatFile name comments = concat [
|
||||||
@@ -200,7 +205,14 @@ commentsFor options file =
|
|||||||
liftM (getComments options) $ readContents file
|
liftM (getComments options) $ readContents file
|
||||||
|
|
||||||
getComments options contents =
|
getComments options contents =
|
||||||
excludeCodes (getExclusions options) $ shellCheck contents
|
excludeCodes (getExclusions options) $ shellCheck contents analysisOptions
|
||||||
|
where
|
||||||
|
analysisOptions = catMaybes [ shellOption ]
|
||||||
|
shellOption = do
|
||||||
|
option <- getOption options "shell"
|
||||||
|
sh <- shellForExecutable option
|
||||||
|
return $ ForceShell sh
|
||||||
|
|
||||||
|
|
||||||
readContents file = if file == "-" then getContents else readFile file
|
readContents file = if file == "-" then getContents else readFile file
|
||||||
|
|
||||||
@@ -216,9 +228,9 @@ makeNonVirtual comments contents =
|
|||||||
real rest (r+1) (v + 8 - (v `mod` 8)) target
|
real rest (r+1) (v + 8 - (v `mod` 8)) target
|
||||||
real (_:rest) r v target = real rest (r+1) (v+1) target
|
real (_:rest) r v target = real rest (r+1) (v+1) target
|
||||||
|
|
||||||
getOption [] _ def = def
|
getOption [] _ = Nothing
|
||||||
getOption ((Flag var val):_) name _ | name == var = val
|
getOption (Flag var val:_) name | name == var = return val
|
||||||
getOption (_:rest) flag def = getOption rest flag def
|
getOption (_:rest) flag = getOption rest flag
|
||||||
|
|
||||||
getOptions options name =
|
getOptions options name =
|
||||||
map (\(Flag _ val) -> val) . filter (\(Flag var _) -> var == name) $ options
|
map (\(Flag _ val) -> val) . filter (\(Flag var _) -> var == name) $ options
|
||||||
@@ -238,8 +250,8 @@ getExclusions options =
|
|||||||
in
|
in
|
||||||
map (Prelude.read . clean) elements :: [Int]
|
map (Prelude.read . clean) elements :: [Int]
|
||||||
|
|
||||||
excludeCodes codes comments =
|
excludeCodes codes =
|
||||||
filter (not . hasCode) comments
|
filter (not . hasCode)
|
||||||
where
|
where
|
||||||
hasCode c = scCode c `elem` codes
|
hasCode c = scCode c `elem` codes
|
||||||
|
|
||||||
@@ -257,7 +269,7 @@ main = do
|
|||||||
|
|
||||||
process Nothing = return False
|
process Nothing = return False
|
||||||
process (Just (options, files)) =
|
process (Just (options, files)) =
|
||||||
let format = getOption options "format" "tty" in
|
let format = fromMaybe "tty" $ getOption options "format" in
|
||||||
case Map.lookup format formats of
|
case Map.lookup format formats of
|
||||||
Nothing -> do
|
Nothing -> do
|
||||||
printErr $ "Unknown format " ++ format
|
printErr $ "Unknown format " ++ format
|
||||||
@@ -268,3 +280,22 @@ process (Just (options, files)) =
|
|||||||
Just f -> do
|
Just f -> do
|
||||||
f options files
|
f options files
|
||||||
|
|
||||||
|
verifyOptions opts files = do
|
||||||
|
when (isJust $ getOption opts "version") printVersionAndExit
|
||||||
|
|
||||||
|
let shell = getOption opts "shell" in
|
||||||
|
when (isJust shell && isNothing (shell >>= shellForExecutable)) $ do
|
||||||
|
printErr $ "Unknown shell: " ++ (fromJust shell)
|
||||||
|
exitWith supportFailure
|
||||||
|
|
||||||
|
when (null files) $ do
|
||||||
|
printErr "No files specified.\n"
|
||||||
|
printErr $ usageInfo header options
|
||||||
|
exitWith syntaxFailure
|
||||||
|
|
||||||
|
printVersionAndExit = 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
|
||||||
|
Reference in New Issue
Block a user