summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorVidar Holen <spam@vidarholen.net>2018-10-10 21:27:52 -0700
committerVidar Holen <spam@vidarholen.net>2018-10-10 21:53:43 -0700
commite0e46e979af258aabbc11fe9888d4d97dcd557da (patch)
tree033926d173ae9d8c026584b407673e9487cb136a
parent79319558a59741e9075ad3353cca8fea194d5f83 (diff)
Add wiki links to output, and a -W controlling it. (Fixes #920)
-rw-r--r--CHANGELOG.md1
-rw-r--r--shellcheck.1.md5
-rw-r--r--shellcheck.hs13
-rw-r--r--src/ShellCheck/Formatter/TTY.hs74
-rw-r--r--src/ShellCheck/Interface.hs10
5 files changed, 89 insertions, 14 deletions
diff --git a/CHANGELOG.md b/CHANGELOG.md
index 44e38d5..6a65713 100644
--- a/CHANGELOG.md
+++ b/CHANGELOG.md
@@ -1,6 +1,7 @@
## ???
### Added
- Command line option --severity/-S for filtering by minimum severity
+- Command line option --wiki-link-count/-W for showing wiki links
- SC2236/SC2237: Suggest -n/-z instead of ! -z/-n
- SC2238: Warn when redirecting to a known command name, e.g. ls > rm
### Changed
diff --git a/shellcheck.1.md b/shellcheck.1.md
index 8671d1e..6600613 100644
--- a/shellcheck.1.md
+++ b/shellcheck.1.md
@@ -71,6 +71,11 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts.
: Print version information and exit.
+**-W** *NUM*,\ **--wiki-link-count=NUM**
+
+: For TTY output, show *NUM* wiki links to more information about mentioned
+ warnings. Set to 0 to disable them entirely.
+
**-x**,\ **--external-sources**
: Follow 'source' statements even when the file is not specified as input.
diff --git a/shellcheck.hs b/shellcheck.hs
index 399e44d..6b9047c 100644
--- a/shellcheck.hs
+++ b/shellcheck.hs
@@ -100,6 +100,9 @@ options = [
"Minimum severity of errors to consider (error, warning, info, style)",
Option "V" ["version"]
(NoArg $ Flag "version" "true") "Print version information",
+ Option "W" ["wiki-link-count"]
+ (ReqArg (Flag "wiki-link-count") "NUM")
+ "The number of wiki links to show, when applicable.",
Option "x" ["external-sources"]
(NoArg $ Flag "externals" "true") "Allow 'source' outside of FILES"
]
@@ -296,6 +299,14 @@ parseOption flag options =
}
}
+ Flag "wiki-link-count" countString -> do
+ count <- parseNum countString
+ return options {
+ formatterOptions = (formatterOptions options) {
+ foWikiLinkCount = count
+ }
+ }
+
_ -> return options
where
die s = do
@@ -304,7 +315,7 @@ parseOption flag options =
parseNum ('S':'C':str) = parseNum str
parseNum num = do
unless (all isDigit num) $ do
- printErr $ "Bad exclusion: " ++ num
+ printErr $ "Invalid number: " ++ num
throwError SyntaxFailure
return (Prelude.read num :: Integer)
diff --git a/src/ShellCheck/Formatter/TTY.hs b/src/ShellCheck/Formatter/TTY.hs
index f54a0b3..64091dd 100644
--- a/src/ShellCheck/Formatter/TTY.hs
+++ b/src/ShellCheck/Formatter/TTY.hs
@@ -22,18 +22,27 @@ module ShellCheck.Formatter.TTY (format) where
import ShellCheck.Interface
import ShellCheck.Formatter.Format
+import Control.Monad
+import Data.IORef
import Data.List
import GHC.Exts
-import System.Info
import System.IO
+import System.Info
+
+wikiLink = "https://www.shellcheck.net/wiki/"
+
+-- An arbitrary Ord thing to order warnings
+type Ranking = (Char, Severity, Integer)
format :: FormatterOptions -> IO Formatter
-format options = return Formatter {
- header = return (),
- footer = return (),
- onFailure = outputError options,
- onResult = outputResult options
-}
+format options = do
+ topErrorRef <- newIORef []
+ return Formatter {
+ header = return (),
+ footer = outputWiki topErrorRef,
+ onFailure = outputError options,
+ onResult = outputResult options topErrorRef
+ }
colorForLevel level =
case level of
@@ -45,13 +54,60 @@ colorForLevel level =
"source" -> 0 -- none
_ -> 0 -- none
+rankError :: PositionedComment -> Ranking
+rankError err = (ranking, cSeverity $ pcComment err, cCode $ pcComment err)
+ where
+ ranking =
+ if cCode (pcComment err) `elem` uninteresting
+ then 'Z'
+ else 'A'
+
+ -- A list of the most generic, least directly helpful
+ -- error codes to downrank.
+ uninteresting = [
+ 1009, -- Mentioned parser error was..
+ 1019, -- Expected this to be an argument
+ 1036, -- ( is invalid here
+ 1047, -- Expected 'fi'
+ 1062, -- Expected 'done'
+ 1070, -- Parsing stopped here (generic)
+ 1072, -- Missing/unexpected ..
+ 1073, -- Couldn't parse this ..
+ 1088, -- Parsing stopped here (paren)
+ 1089 -- Parsing stopped here (keyword)
+ ]
+
+appendComments errRef comments max = do
+ previous <- readIORef errRef
+ let current = map (\x -> (rankError x, cCode $ pcComment x, cMessage $ pcComment x)) comments
+ writeIORef errRef . take max . nubBy equal . sort $ previous ++ current
+ where
+ fst3 (x,_,_) = x
+ equal x y = fst3 x == fst3 y
+
+outputWiki :: IORef [(Ranking, Integer, String)] -> IO ()
+outputWiki errRef = do
+ issues <- readIORef errRef
+ unless (null issues) $ do
+ putStrLn "For more information:"
+ mapM_ showErr issues
+ where
+ showErr (_, code, msg) =
+ putStrLn $ " " ++ wikiLink ++ "SC" ++ show code ++ " -- " ++ shorten msg
+ limit = 40
+ shorten msg =
+ if length msg < limit
+ then msg
+ else (take (limit-3) msg) ++ "..."
+
outputError options file error = do
color <- getColorFunc $ foColorOption options
hPutStrLn stderr $ color "error" $ file ++ ": " ++ error
-outputResult options result sys = do
+outputResult options ref result sys = do
color <- getColorFunc $ foColorOption options
let comments = crComments result
+ appendComments ref comments (fromIntegral $ foWikiLinkCount options)
let fileGroups = groupWith sourceFile comments
mapM_ (outputForFile color sys) fileGroups
@@ -87,7 +143,7 @@ cuteIndent comment =
in
if sameLine && delta > 2 && delta < 32 then arrow delta else "^--"
-code code = "SC" ++ show code
+code num = "SC" ++ show num
getColorFunc colorOption = do
term <- hIsTerminalDevice stdout
diff --git a/src/ShellCheck/Interface.hs b/src/ShellCheck/Interface.hs
index 8432f0e..f20874f 100644
--- a/src/ShellCheck/Interface.hs
+++ b/src/ShellCheck/Interface.hs
@@ -26,7 +26,7 @@ module ShellCheck.Interface
, ParseResult(prComments, prTokenPositions, prRoot)
, AnalysisSpec(asScript, asShellType, asExecutionMode, asCheckSourced)
, AnalysisResult(arComments)
- , FormatterOptions(foColorOption)
+ , FormatterOptions(foColorOption, foWikiLinkCount)
, Shell(Ksh, Sh, Bash, Dash)
, ExecutionMode(Executed, Sourced)
, ErrorMessage
@@ -145,12 +145,14 @@ newAnalysisResult = AnalysisResult {
}
-- Formatter options
-newtype FormatterOptions = FormatterOptions {
- foColorOption :: ColorOption
+data FormatterOptions = FormatterOptions {
+ foColorOption :: ColorOption,
+ foWikiLinkCount :: Integer
}
newFormatterOptions = FormatterOptions {
- foColorOption = ColorAuto
+ foColorOption = ColorAuto,
+ foWikiLinkCount = 3
}