core-data-0.3.4.0: Convenience wrappers around common data structures and encodings
Safe HaskellNone
LanguageHaskell2010

Core.Encoding.Json

Description

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.

Often you'll be working with literals directly in your code. While you can write:

    j = JsonObject (intoMap [(JsonKey "answer", JsonNumber 42)])

and it would be correct, enabling:

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE OverloadedLists #-}

allows you to write:

    j = JsonObject [("answer", 42)]

which you is somewhat less cumbersome in declaration-heavy code. You're certainly welcome to use the constructors if you find it makes for more readable code or if you need the type annotations.

Synopsis

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.

encodeToRope :: JsonValue -> Rope Source #

Given a JSON value, encode it to a Rope (which, by definition, is UTF-8 internally).

decodeFromUTF8 :: Bytes -> Maybe JsonValue Source #

Given an array of bytes, attempt to decode it as a JSON value.

decodeFromRope :: Rope -> Maybe JsonValue Source #

Given an string that is full of a bunch of JSON, attempt to decode it.

data JsonValue Source #

A JSON value.

Instances

Instances details
Eq JsonValue Source # 
Instance details

Defined in Core.Encoding.Json

Fractional JsonValue Source # 
Instance details

Defined in Core.Encoding.Json

Num JsonValue Source # 
Instance details

Defined in Core.Encoding.Json

Show JsonValue Source # 
Instance details

Defined in Core.Encoding.Json

IsString JsonValue Source # 
Instance details

Defined in Core.Encoding.Json

Generic JsonValue Source # 
Instance details

Defined in Core.Encoding.Json

Associated Types

type Rep JsonValue :: Type -> Type #

Render JsonValue Source # 
Instance details

Defined in Core.Encoding.Json

Associated Types

type Token JsonValue #

Pretty JsonValue Source # 
Instance details

Defined in Core.Encoding.Json

Methods

pretty :: JsonValue -> Doc ann #

prettyList :: [JsonValue] -> Doc ann #

type Rep JsonValue Source # 
Instance details

Defined in Core.Encoding.Json

type Token JsonValue Source # 
Instance details

Defined in Core.Encoding.Json

newtype JsonKey Source #

Keys in a JSON object.

Constructors

JsonKey Rope 

Instances

Instances details
Eq JsonKey Source # 
Instance details

Defined in Core.Encoding.Json

Methods

(==) :: JsonKey -> JsonKey -> Bool #

(/=) :: JsonKey -> JsonKey -> Bool #

Ord JsonKey Source # 
Instance details

Defined in Core.Encoding.Json

Show JsonKey Source # 
Instance details

Defined in Core.Encoding.Json

IsString JsonKey Source # 
Instance details

Defined in Core.Encoding.Json

Methods

fromString :: String -> JsonKey #

Generic JsonKey Source # 
Instance details

Defined in Core.Encoding.Json

Associated Types

type Rep JsonKey :: Type -> Type #

Methods

from :: JsonKey -> Rep JsonKey x #

to :: Rep JsonKey x -> JsonKey #

Hashable JsonKey Source # 
Instance details

Defined in Core.Encoding.Json

Methods

hashWithSalt :: Int -> JsonKey -> Int #

hash :: JsonKey -> Int #

Render JsonKey Source # 
Instance details

Defined in Core.Encoding.Json

Associated Types

type Token JsonKey #

Textual JsonKey Source # 
Instance details

Defined in Core.Encoding.Json

Pretty JsonKey Source # 
Instance details

Defined in Core.Encoding.Json

Methods

pretty :: JsonKey -> Doc ann #

prettyList :: [JsonKey] -> Doc ann #

Key JsonKey Source # 
Instance details

Defined in Core.Encoding.Json

type Rep JsonKey Source # 
Instance details

Defined in Core.Encoding.Json

type Rep JsonKey = D1 ('MetaData "JsonKey" "Core.Encoding.Json" "core-data-0.3.4.0-IgqpNqCYboI2URbmdeDx4t" 'True) (C1 ('MetaCons "JsonKey" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rope)))
type Token JsonKey Source # 
Instance details

Defined in Core.Encoding.Json

Syntax highlighting

data JsonToken Source #

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 (00.007) j =
{
    "answer": 42
}

colourizeJson :: JsonToken -> AnsiColour 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

Orphan instances

FromJSON Rope Source # 
Instance details