summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
authorVidar Holen <spam@vidarholen.net>2015-12-06 12:48:53 -0800
committerVidar Holen <spam@vidarholen.net>2015-12-06 12:48:53 -0800
commitb4390414ef79e64a4b7bb6841ba76892312d8935 (patch)
treec65de81aefed31062b1f337ff7fab279173b5465
parent8acd5b13cd1fb9117e4cdaaeac474479a646c71f (diff)
Fix remaining FIXME for tty error color output.
-rw-r--r--ShellCheck/Checker.hs1
-rw-r--r--ShellCheck/Formatter/TTY.hs18
-rw-r--r--ShellCheck/Interface.hs26
-rw-r--r--shellcheck.1.md2
-rw-r--r--shellcheck.hs21
5 files changed, 37 insertions, 31 deletions
diff --git a/ShellCheck/Checker.hs b/ShellCheck/Checker.hs
index f206a60..2bfdc94 100644
--- a/ShellCheck/Checker.hs
+++ b/ShellCheck/Checker.hs
@@ -48,7 +48,6 @@ checkScript sys spec = do
results <- checkScript (csScript spec)
return CheckResult {
crFilename = csFilename spec,
- crColorOption = csColorOption spec,
crComments = results
}
where
diff --git a/ShellCheck/Formatter/TTY.hs b/ShellCheck/Formatter/TTY.hs
index 56abb71..444c28b 100644
--- a/ShellCheck/Formatter/TTY.hs
+++ b/ShellCheck/Formatter/TTY.hs
@@ -27,12 +27,12 @@ import GHC.Exts
import System.Info
import System.IO
-format :: IO Formatter
-format = return Formatter {
+format :: FormatterOptions -> IO Formatter
+format options = return Formatter {
header = return (),
footer = return (),
- onFailure = outputError,
- onResult = outputResult
+ onFailure = outputError options,
+ onResult = outputResult options
}
colorForLevel level =
@@ -45,12 +45,12 @@ colorForLevel level =
"source" -> 0 -- none
otherwise -> 0 -- none
-outputError file error = do
- color <- getColorFunc $ ColorAuto -- FIXME: should respect --color
- hPutStrLn stderr $ color "error ZZZ" $ file ++ ": " ++ error
+outputError options file error = do
+ color <- getColorFunc $ foColorOption options
+ hPutStrLn stderr $ color "error" $ file ++ ": " ++ error
-outputResult result contents = do
- color <- getColorFunc $ crColorOption result
+outputResult options result contents = do
+ color <- getColorFunc $ foColorOption options
let comments = crComments result
let fileLines = lines contents
let lineCount = fromIntegral $ length fileLines
diff --git a/ShellCheck/Interface.hs b/ShellCheck/Interface.hs
index 3c52773..41517ff 100644
--- a/ShellCheck/Interface.hs
+++ b/ShellCheck/Interface.hs
@@ -34,30 +34,21 @@ data CheckSpec = CheckSpec {
csFilename :: String,
csScript :: String,
csExcludedWarnings :: [Integer],
- csColorOption :: ColorOptions,
csShellTypeOverride :: Maybe Shell
} deriving (Show, Eq)
data CheckResult = CheckResult {
crFilename :: String,
- crComments :: [PositionedComment],
- crColorOption :: ColorOptions
+ crComments :: [PositionedComment]
} deriving (Show, Eq)
emptyCheckSpec = CheckSpec {
csFilename = "",
csScript = "",
csExcludedWarnings = [],
- csShellTypeOverride = Nothing,
- csColorOption = ColorAuto
+ csShellTypeOverride = Nothing
}
-data ColorOptions =
- ColorAuto
- | ColorAlways
- | ColorNever
- deriving (Ord, Eq, Show)
-
-- Parser input and output
data ParseSpec = ParseSpec {
psFilename :: String,
@@ -81,6 +72,13 @@ data AnalysisResult = AnalysisResult {
arComments :: [TokenComment]
}
+
+-- Formatter options
+data FormatterOptions = FormatterOptions {
+ foColorOption :: ColorOption
+}
+
+
-- Supporting data types
data Shell = Ksh | Sh | Bash | Dash deriving (Show, Eq)
data ExecutionMode = Executed | Sourced deriving (Show, Eq)
@@ -99,6 +97,12 @@ data Comment = Comment Severity Code String deriving (Show, Eq)
data PositionedComment = PositionedComment Position Comment deriving (Show, Eq)
data TokenComment = TokenComment Id Comment deriving (Show, Eq)
+data ColorOption =
+ ColorAuto
+ | ColorAlways
+ | ColorNever
+ deriving (Ord, Eq, Show)
+
-- For testing
mockedSystemInterface :: [(String, String)] -> SystemInterface Identity
mockedSystemInterface files = SystemInterface {
diff --git a/shellcheck.1.md b/shellcheck.1.md
index 2755c4c..d611db0 100644
--- a/shellcheck.1.md
+++ b/shellcheck.1.md
@@ -32,7 +32,7 @@ not warn at all, as `ksh` supports decimals in arithmetic contexts.
# OPTIONS
-**-C**\ [*WHEN*],\ **--color**[=*WHEN*]
+**-C**[*WHEN*],\ **--color**[=*WHEN*]
: For TTY outut, enable colors *always*, *never* or *auto*. The default
is *auto*. **--color** without an argument is equivalent to
diff --git a/shellcheck.hs b/shellcheck.hs
index 5848542..392d271 100644
--- a/shellcheck.hs
+++ b/shellcheck.hs
@@ -60,13 +60,15 @@ instance Monoid Status where
data Options = Options {
checkSpec :: CheckSpec,
externalSources :: Bool,
- color :: ColorOptions
+ formatterOptions :: FormatterOptions
}
defaultOptions = Options {
checkSpec = emptyCheckSpec,
externalSources = False,
- color = ColorAuto
+ formatterOptions = FormatterOptions {
+ foColorOption = ColorAuto
+ }
}
usageHeader = "Usage: shellcheck [OPTIONS...] FILES..."
@@ -96,12 +98,12 @@ parseArguments argv =
printErr $ concat errors ++ "\n" ++ usageInfo usageHeader options
throwError SyntaxFailure
-formats :: Map.Map String (IO Formatter)
-formats = Map.fromList [
+formats :: FormatterOptions -> Map.Map String (IO Formatter)
+formats options = Map.fromList [
("checkstyle", ShellCheck.Formatter.CheckStyle.format),
("gcc", ShellCheck.Formatter.GCC.format),
("json", ShellCheck.Formatter.JSON.format),
- ("tty", ShellCheck.Formatter.TTY.format)
+ ("tty", ShellCheck.Formatter.TTY.format options)
]
getOption [] _ = Nothing
@@ -157,12 +159,13 @@ process flags files = do
options <- foldM (flip parseOption) defaultOptions flags
verifyFiles files
let format = fromMaybe "tty" $ getOption flags "format"
+ let formatters = formats $ formatterOptions options
formatter <-
- case Map.lookup format formats of
+ case Map.lookup format formatters of
Nothing -> do
printErr $ "Unknown format " ++ format
printErr "Supported formats:"
- mapM_ (printErr . write) $ Map.keys formats
+ mapM_ (printErr . write) $ Map.keys formatters
throwError SupportFailure
where write s = " " ++ s
Just f -> ExceptT $ fmap Right f
@@ -238,8 +241,8 @@ parseOption flag options =
Flag "color" color ->
return options {
- checkSpec = (checkSpec options) {
- csColorOption = parseColorOption color
+ formatterOptions = (formatterOptions options) {
+ foColorOption = parseColorOption color
}
}