Safe Haskell | None |
---|---|
Language | Haskell2010 |
Encoding and decoding UTF-8 JSON content.
This module is a thin wrapper around the most excellent aeson library, which has rich and powerful facilities for encoding Haskell types into JSON.
Quite often, however, you find yourself having to create a Haskell type just to read some JSON coming from an external web service or API. This can be challenging when the source of the JSON is complex or varying its schema over time. For ease of exploration this module simply defines an easy to use intermediate type representing JSON as a format.
To use this module, you may find the following imports helpful:
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedLists #-} import Data.HashMap.Strict (HashMap
) import qualified Data.HashMap.Strict asHashMap
-- from the unordered-containers package. import Data.Scientific (Scientific
) -- from the scientific package import Core.Encoding.Json
Often you'll be working with literals directly in your code. While you can write:
j = JsonObject (HashMap.fromList [(JsonKey "answer", JsonNumber 42)])
and it would be correct, enabling OverloadedStrings
and OverloadedLists
allows you to write:
j = JsonObject [("answer", 42)]
which you is somewhat less cumbersome. You're certainly welcome to use the constructors if you find it makes for more readable code or if you need the type annotations.
Encoding and Decoding
encodeToUTF8 :: JsonValue -> Bytes Source #
Given a JSON value, encode it to UTF-8 bytes
I know we're not supposed to rely on types to document functions, but really, this one does what it says on the tin.
decodeFromUTF8 :: Bytes -> Maybe JsonValue Source #
Given an array of bytes, attempt to decode it as a JSON value.
A JSON value.
JsonObject (Map JsonKey JsonValue) | |
JsonArray [JsonValue] | |
JsonString Rope | |
JsonNumber Scientific | |
JsonBool Bool | |
JsonNull |
Instances
Keys in a JSON object.
Instances
Eq JsonKey Source # | |
Ord JsonKey Source # | |
Show JsonKey Source # | |
IsString JsonKey Source # | |
Defined in Core.Encoding.Json fromString :: String -> JsonKey # | |
Generic JsonKey Source # | |
Hashable JsonKey Source # | |
Defined in Core.Encoding.Json | |
Pretty JsonKey Source # | |
Defined in Core.Encoding.Json | |
Textual JsonKey Source # | |
Render JsonKey Source # | |
Key JsonKey Source # | |
Defined in Core.Encoding.Json | |
type Rep JsonKey Source # | |
Defined in Core.Encoding.Json | |
type Token JsonKey Source # | |
Defined in Core.Encoding.Json |
Syntax highlighting
Support for pretty-printing JSON values with syntax highlighting using the
prettyprinter library. To output a JSON structure to terminal
colourized with ANSI escape codes you can use the Render
instance:
debug "j" (render j)
will get you:
23:46:04Z (00000.007) j = { "answer": 42.0 }
colourizeJson :: JsonToken -> AnsiStyle Source #
Used by the Render
instance to turn symbolic annotations into ANSI colours annotations.
If you're curious, the render pipeline looks like:
render =intoText
.renderStrict
.reAnnotateS
colourize
.layoutPretty
defaultLayoutOptions
.prettyValue