Refactor JSON utilities module
This commit is contained in:
parent
7b025b2548
commit
7dabac6cbc
46
Json.hs
46
Json.hs
@ -1,9 +1,4 @@
|
|||||||
module Json
|
module Json where
|
||||||
( (|.)
|
|
||||||
, (|:)
|
|
||||||
, repr
|
|
||||||
, jprint
|
|
||||||
) where
|
|
||||||
|
|
||||||
import Data.Aeson
|
import Data.Aeson
|
||||||
import Data.Aeson.Types (parse)
|
import Data.Aeson.Types (parse)
|
||||||
@ -20,29 +15,24 @@ obj |. key = case parse (.: key) obj of
|
|||||||
Error err -> toJSON err
|
Error err -> toJSON err
|
||||||
|
|
||||||
-- Get the String value of a key
|
-- Get the String value of a key
|
||||||
|
|
||||||
(|:) :: Object -> Text -> String
|
(|:) :: 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 :: Value -> String
|
||||||
repr obj = drop 1 $ repr' obj 0
|
repr obj = repr' obj 0 where
|
||||||
|
repr' val lev =
|
||||||
|
case val of
|
||||||
|
Array x -> intercalate ", " $ mapl (\i -> repr' i lev) 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"
|
||||||
|
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)]
|
||||||
|
|
||||||
-- Create a String representation of a JSON Value
|
-- Pretty print a JSON value
|
||||||
repr' :: Value -> Int -> String
|
pprint :: Value -> IO ()
|
||||||
repr' val lev =
|
pprint = putStrLn . repr
|
||||||
case val of
|
|
||||||
Array x -> intercalate ", " $ mapl (\i -> repr' i lev) x
|
|
||||||
Object x -> concat $ map (dump x) $ 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
|
|
||||||
|
|
||||||
-- Print a representation of a JSON Value
|
|
||||||
jprint :: Value -> IO ()
|
|
||||||
jprint = putStrLn . repr
|
|
4
Main.hs
4
Main.hs
@ -54,8 +54,8 @@ handleLocal name block = do
|
|||||||
out <- readProcess "namecoind" ["name_show", name] ""
|
out <- readProcess "namecoind" ["name_show", name] ""
|
||||||
case decode (C.pack out) of
|
case decode (C.pack out) of
|
||||||
Just res -> do
|
Just res -> do
|
||||||
jprint $ reparse (res |: "value")
|
pprint $ reparse (res |: "value")
|
||||||
if block then jprint extra else return ()
|
if block then pprint extra else return ()
|
||||||
where
|
where
|
||||||
reparse = fromJust . decode . C.pack
|
reparse = fromJust . decode . C.pack
|
||||||
extra = toJSON $ delete "value" res
|
extra = toJSON $ delete "value" res
|
||||||
|
Loading…
Reference in New Issue
Block a user