Change to aeson (fixes #1085)

Adds bytestring as a dependency for putStrLn encoded values.
This commit is contained in:
Ng Zhi An 2018-05-06 16:07:53 -07:00
parent ef6a5b97b9
commit 08235a1cb2
2 changed files with 35 additions and 19 deletions

View File

@ -49,10 +49,11 @@ library
build-depends: build-depends:
-- GHC 7.6.3 (base 4.6.0.1) is buggy (#1131, #1119) in optimized mode. -- GHC 7.6.3 (base 4.6.0.1) is buggy (#1131, #1119) in optimized mode.
-- Just disable that version entirely to fail fast. -- Just disable that version entirely to fail fast.
aeson,
base > 4.6.0.1 && < 5, base > 4.6.0.1 && < 5,
bytestring,
containers >= 0.5, containers >= 0.5,
directory, directory,
json,
mtl >= 2.2.1, mtl >= 2.2.1,
parsec, parsec,
regex-tdfa, regex-tdfa,
@ -85,11 +86,12 @@ executable shellcheck
build-depends: build-depends:
semigroups semigroups
build-depends: build-depends:
aeson,
base >= 4 && < 5, base >= 4 && < 5,
bytestring,
ShellCheck, ShellCheck,
containers, containers,
directory, directory,
json >= 0.3.6,
mtl >= 2.2.1, mtl >= 2.2.1,
parsec >= 3.0, parsec >= 3.0,
QuickCheck >= 2.7.4, QuickCheck >= 2.7.4,
@ -99,11 +101,12 @@ executable shellcheck
test-suite test-shellcheck test-suite test-shellcheck
type: exitcode-stdio-1.0 type: exitcode-stdio-1.0
build-depends: build-depends:
aeson,
base >= 4 && < 5, base >= 4 && < 5,
bytestring,
ShellCheck, ShellCheck,
containers, containers,
directory, directory,
json,
mtl >= 2.2.1, mtl >= 2.2.1,
parsec, parsec,
QuickCheck >= 2.7.4, QuickCheck >= 2.7.4,

View File

@ -1,3 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
{- {-
Copyright 2012-2015 Vidar Holen Copyright 2012-2015 Vidar Holen
@ -22,10 +23,11 @@ module ShellCheck.Formatter.JSON (format) where
import ShellCheck.Interface import ShellCheck.Interface
import ShellCheck.Formatter.Format import ShellCheck.Formatter.Format
import Data.Aeson
import Data.IORef import Data.IORef
import GHC.Exts import GHC.Exts
import System.IO import System.IO
import Text.JSON import qualified Data.ByteString.Lazy.Char8 as BL
format = do format = do
ref <- newIORef [] ref <- newIORef []
@ -36,19 +38,30 @@ format = do
footer = finish ref footer = finish ref
} }
instance JSON (PositionedComment) where instance ToJSON (PositionedComment) where
showJSON comment@(PositionedComment start end (Comment level code string)) = makeObj [ toJSON comment@(PositionedComment start end (Comment level code string)) =
("file", showJSON $ posFile start), object [
("line", showJSON $ posLine start), "file" .= posFile start,
("endLine", showJSON $ posLine end), "line" .= posLine start,
("column", showJSON $ posColumn start), "endLine" .= posLine end,
("endColumn", showJSON $ posColumn end), "column" .= posColumn start,
("level", showJSON $ severityText comment), "endColumn" .= posColumn end,
("code", showJSON code), "level" .= severityText comment,
("message", showJSON string) "code" .= code,
] "message" .= string
]
readJSON = undefined toEncoding comment@(PositionedComment start end (Comment level code string)) =
pairs (
"file" .= posFile start
<> "line" .= posLine start
<> "endLine" .= posLine end
<> "column" .= posColumn start
<> "endColumn" .= posColumn end
<> "level" .= severityText comment
<> "code" .= code
<> "message" .= string
)
outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg outputError file msg = hPutStrLn stderr $ file ++ ": " ++ msg
collectResult ref result _ = collectResult ref result _ =
@ -56,5 +69,5 @@ collectResult ref result _ =
finish ref = do finish ref = do
list <- readIORef ref list <- readIORef ref
putStrLn $ encodeStrict list BL.putStrLn $ encode list