mirror of
https://github.com/koalaman/shellcheck.git
synced 2025-09-18 17:56:55 +08:00
Add filename to JSON output.
This commit is contained in:
@@ -19,6 +19,7 @@ import Control.Exception
|
|||||||
import Control.Monad
|
import Control.Monad
|
||||||
import Control.Monad.Trans
|
import Control.Monad.Trans
|
||||||
import Control.Monad.Trans.Error
|
import Control.Monad.Trans.Error
|
||||||
|
import Control.Monad.Trans.List
|
||||||
import Data.Char
|
import Data.Char
|
||||||
import Data.Maybe
|
import Data.Maybe
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
@@ -40,6 +41,8 @@ import qualified Data.Map as Map
|
|||||||
data Flag = Flag String String
|
data Flag = Flag String String
|
||||||
data Status = NoProblems | SomeProblems | BadInput | SupportFailure | SyntaxFailure | RuntimeException deriving (Ord, Eq)
|
data Status = NoProblems | SomeProblems | BadInput | SupportFailure | SyntaxFailure | RuntimeException deriving (Ord, Eq)
|
||||||
|
|
||||||
|
data JsonComment = JsonComment FilePath ShellCheckComment
|
||||||
|
|
||||||
instance Error Status where
|
instance Error Status where
|
||||||
noMsg = RuntimeException
|
noMsg = RuntimeException
|
||||||
|
|
||||||
@@ -62,8 +65,9 @@ options = [
|
|||||||
printErr = hPutStrLn stderr
|
printErr = hPutStrLn stderr
|
||||||
|
|
||||||
|
|
||||||
instance JSON ShellCheckComment where
|
instance JSON (JsonComment) where
|
||||||
showJSON c = makeObj [
|
showJSON (JsonComment filename c) = makeObj [
|
||||||
|
("file", showJSON $ filename),
|
||||||
("line", showJSON $ scLine c),
|
("line", showJSON $ scLine c),
|
||||||
("column", showJSON $ scColumn c),
|
("column", showJSON $ scColumn c),
|
||||||
("level", showJSON $ scSeverity c),
|
("level", showJSON $ scSeverity c),
|
||||||
@@ -152,10 +156,12 @@ forTty options files = do
|
|||||||
term <- hIsTerminalDevice stdout
|
term <- hIsTerminalDevice stdout
|
||||||
return $ if term then colorComment else const id
|
return $ if term then colorComment else const id
|
||||||
|
|
||||||
-- This totally ignores the filenames. Fixme?
|
|
||||||
forJson :: AnalysisOptions -> [FilePath] -> IO Status
|
forJson :: AnalysisOptions -> [FilePath] -> IO Status
|
||||||
forJson options files = catchExceptions $ do
|
forJson options files = catchExceptions $ do
|
||||||
comments <- liftM concat $ mapM (commentsFor options) files
|
comments <- runListT $ do
|
||||||
|
file <- ListT $ return files
|
||||||
|
comment <- ListT $ commentsFor options file
|
||||||
|
return $ JsonComment file comment
|
||||||
putStrLn $ encodeStrict comments
|
putStrLn $ encodeStrict comments
|
||||||
return $ checkComments comments
|
return $ checkComments comments
|
||||||
|
|
||||||
|
Reference in New Issue
Block a user