Refactor JSON utilities module

This commit is contained in:
Rnhmjoj 2014-12-27 16:34:29 +01:00
parent 7b025b2548
commit 7dabac6cbc
2 changed files with 20 additions and 30 deletions

30
Json.hs
View File

@ -1,9 +1,4 @@
module Json
( (|.)
, (|:)
, repr
, jprint
) where
module Json where
import Data.Aeson
import Data.Aeson.Types (parse)
@ -20,29 +15,24 @@ obj |. key = case parse (.: key) obj of
Error err -> toJSON err
-- Get the String value of a key
(|:) :: Object -> Text -> String
obj |: key = repr' (obj |. key) 0
obj |: key = repr (obj |. key)
-- Create a String representation of a JSON
-- Create a String representation of a JSON value
repr :: Value -> String
repr obj = drop 1 $ repr' obj 0
-- Create a String representation of a JSON Value
repr' :: Value -> Int -> String
repr obj = repr' obj 0 where
repr' val lev =
case val of
Array x -> intercalate ", " $ mapl (\i -> repr' i lev) x
Object x -> concat $ map (dump x) $ H.keys x
Object x -> drop 1 $ concat $ map (dump x lev) $ H.keys x
String x -> unpack x
Number x -> show x
Bool x -> show x
Null -> "null"
where
indent = '\n' : (concat . replicate lev) " "
dump o k = concat [indent, unpack k, ": ", repr' (o |. k) (lev+1)]
mapl f v = V.toList $ V.map f v
indent l = '\n' : (concat . replicate l) " "
dump o l k = concat [indent l, unpack k, ": ", repr' (o |. k) (l+1)]
-- Print a representation of a JSON Value
jprint :: Value -> IO ()
jprint = putStrLn . repr
-- Pretty print a JSON value
pprint :: Value -> IO ()
pprint = putStrLn . repr

View File

@ -54,8 +54,8 @@ handleLocal name block = do
out <- readProcess "namecoind" ["name_show", name] ""
case decode (C.pack out) of
Just res -> do
jprint $ reparse (res |: "value")
if block then jprint extra else return ()
pprint $ reparse (res |: "value")
if block then pprint extra else return ()
where
reparse = fromJust . decode . C.pack
extra = toJSON $ delete "value" res