module Json where import Data.Aeson import Data.Aeson.Types (parse) import Data.Text (Text, unpack) import Data.List (intercalate) import qualified Data.Vector as V import qualified Data.HashMap.Strict as H -- Get the JSON value of a key (|.) :: Object -> Text -> Value obj |. key = case parse (.: key) obj of Success val -> val Error err -> toJSON err -- Get the String value of a key (|:) :: Object -> Text -> String obj |: key = repr (obj |. key) -- Create a String representation of a JSON value repr :: Value -> String repr obj = repr' obj 0 where repr' val lev = case val of Array x -> intercalate ", " $ mapl (\i -> repr' i lev) x Object x -> newline lev $ 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) newline n = if n == 1 then id else drop 1 indent l = '\n' : (concat . replicate l) " " dump o l k = concat [indent l, unpack k, ": ", repr' (o |. k) (l+1)] -- Pretty print a JSON value pprint :: Value -> IO () pprint = putStrLn . repr