Add JSON1 as a separate format, wrap result in an object
This commit is contained in:
parent
f4be53eb19
commit
1297ef46d7
|
@ -80,6 +80,7 @@ library
|
||||||
ShellCheck.Formatter.CheckStyle
|
ShellCheck.Formatter.CheckStyle
|
||||||
ShellCheck.Formatter.GCC
|
ShellCheck.Formatter.GCC
|
||||||
ShellCheck.Formatter.JSON
|
ShellCheck.Formatter.JSON
|
||||||
|
ShellCheck.Formatter.JSON1
|
||||||
ShellCheck.Formatter.TTY
|
ShellCheck.Formatter.TTY
|
||||||
ShellCheck.Formatter.Quiet
|
ShellCheck.Formatter.Quiet
|
||||||
ShellCheck.Interface
|
ShellCheck.Interface
|
||||||
|
|
|
@ -27,6 +27,7 @@ import qualified ShellCheck.Formatter.CheckStyle
|
||||||
import ShellCheck.Formatter.Format
|
import ShellCheck.Formatter.Format
|
||||||
import qualified ShellCheck.Formatter.GCC
|
import qualified ShellCheck.Formatter.GCC
|
||||||
import qualified ShellCheck.Formatter.JSON
|
import qualified ShellCheck.Formatter.JSON
|
||||||
|
import qualified ShellCheck.Formatter.JSON1
|
||||||
import qualified ShellCheck.Formatter.TTY
|
import qualified ShellCheck.Formatter.TTY
|
||||||
import qualified ShellCheck.Formatter.Quiet
|
import qualified ShellCheck.Formatter.Quiet
|
||||||
|
|
||||||
|
@ -141,8 +142,8 @@ formats :: FormatterOptions -> Map.Map String (IO Formatter)
|
||||||
formats options = Map.fromList [
|
formats options = Map.fromList [
|
||||||
("checkstyle", ShellCheck.Formatter.CheckStyle.format),
|
("checkstyle", ShellCheck.Formatter.CheckStyle.format),
|
||||||
("gcc", ShellCheck.Formatter.GCC.format),
|
("gcc", ShellCheck.Formatter.GCC.format),
|
||||||
("json", ShellCheck.Formatter.JSON.format False), -- JSON with 8-char tabs
|
("json", ShellCheck.Formatter.JSON.format),
|
||||||
("json1", ShellCheck.Formatter.JSON.format True), -- JSON with 1-char tabs
|
("json1", ShellCheck.Formatter.JSON1.format),
|
||||||
("tty", ShellCheck.Formatter.TTY.format options),
|
("tty", ShellCheck.Formatter.TTY.format options),
|
||||||
("quiet", ShellCheck.Formatter.Quiet.format options)
|
("quiet", ShellCheck.Formatter.Quiet.format options)
|
||||||
]
|
]
|
||||||
|
|
|
@ -30,12 +30,12 @@ import GHC.Exts
|
||||||
import System.IO
|
import System.IO
|
||||||
import qualified Data.ByteString.Lazy.Char8 as BL
|
import qualified Data.ByteString.Lazy.Char8 as BL
|
||||||
|
|
||||||
format :: Bool -> IO Formatter
|
format :: IO Formatter
|
||||||
format removeTabs = do
|
format = do
|
||||||
ref <- newIORef []
|
ref <- newIORef []
|
||||||
return Formatter {
|
return Formatter {
|
||||||
header = return (),
|
header = return (),
|
||||||
onResult = collectResult removeTabs ref,
|
onResult = collectResult ref,
|
||||||
onFailure = outputError,
|
onFailure = outputError,
|
||||||
footer = finish ref
|
footer = finish ref
|
||||||
}
|
}
|
||||||
|
@ -98,19 +98,12 @@ instance ToJSON Fix where
|
||||||
|
|
||||||
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg
|
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg
|
||||||
|
|
||||||
collectResult removeTabs ref cr sys = mapM_ f groups
|
collectResult ref cr sys = mapM_ f groups
|
||||||
where
|
where
|
||||||
comments = crComments cr
|
comments = crComments cr
|
||||||
groups = groupWith sourceFile comments
|
groups = groupWith sourceFile comments
|
||||||
f :: [PositionedComment] -> IO ()
|
f :: [PositionedComment] -> IO ()
|
||||||
f group = do
|
f group = modifyIORef ref (\x -> comments ++ x)
|
||||||
let filename = sourceFile (head group)
|
|
||||||
result <- siReadFile sys filename
|
|
||||||
let contents = either (const "") id result
|
|
||||||
let comments' = if removeTabs
|
|
||||||
then makeNonVirtual comments contents
|
|
||||||
else comments
|
|
||||||
modifyIORef ref (\x -> comments' ++ x)
|
|
||||||
|
|
||||||
finish ref = do
|
finish ref = do
|
||||||
list <- readIORef ref
|
list <- readIORef ref
|
||||||
|
|
Loading…
Reference in New Issue