json-builder-0.2.4: Data structure agnostic JSON serialization

MaintainerLeon P Smith <leon@melding-monads.com>
Safe HaskellSafe-Infered

Data.Json.Builder

Contents

Description

Data structure agnostic JSON serialization

Synopsis

Json Values

data Json Source

The Json type represents valid json syntax. It cannot be directly analyzed, however it can be turned into a Builder via toBuilder, a (lazy) ByteString via toJsonBS or toJsonLBS, or used as a component of a json Array or json Object using element or row.

Instances

class Value a whereSource

The Value typeclass represents types that can be rendered into valid json syntax.

Methods

toJson :: a -> JsonSource

Instances

Value Bool

renders as true or false

Value Double 
Value Float 
Value Int 
Value Int8 
Value Int16 
Value Int32 
Value Int64 
Value Integer 
Value Word 
Value Word8 
Value Word16 
Value Word32 
Value Word64 
Value ()

renders as null

Value Text 
Value Text 
Value ByteString 
Value ByteString 
Value Array 
Value Object 
Value Escaped 
Value Json 
Value [Char] 
Value a => Value [a]

renders as an Array

Value a => Value (Vector a)

renders as an Array

(JsString k, Value a) => Value (Map k a)

renders as an Object

(JsString k, Value a) => Value (HashMap k a)

renders as an Object

Json Arrays ["foobar",true,42]

data Array Source

The Array type represents syntax for a json array. It has been given a singleton constructor element and an instance of Monoid, so that mempty represents the empty array and mappend concatinates two arrays. Arbitrary arrays can be constructed using these operators.

element :: Value a => a -> ArraySource

The element function constructs a json array consisting of exactly one value. These arrays can be concatinated using mappend.

class JsArray a whereSource

Methods

toArray :: a -> ArraySource

Instances

JsArray Array 
Value a => JsArray [a] 
Value a => JsArray (Vector a) 

Json Objects {"x":3.14,"y":-2.7}

data Object Source

The Object type represents syntax for a json object. It has a singleton constructor row, and an instance of Monoid, so that mempty represents the empty object and mappend concatinates two objects. Arbitrary objects can be constructed using these operators.

Note that duplicate field names will appear in the output, so it is up to the user of this interface to avoid duplicate field names.

row :: (JsString k, Value a) => k -> a -> ObjectSource

The row function constructs a json object consisting of exactly one field. These objects can be concatinated using mappend.

class JsObject a whereSource

Methods

toObject :: a -> ObjectSource

Instances

JsObject Object 
(JsString k, Value a) => JsObject (Map k a) 
(JsString k, Value a) => JsObject (HashMap k a) 

Json Strings

data Escaped Source

The Escaped type represents json string syntax. The purpose of this type is so that json strings can be efficiently constructed from multiple Haskell strings without superfluous conversions or concatinations.

Internally, it is just a Builder value which must produce a UTF-8 encoded bytestring with backslashes, quotes, and control characters appropriately escaped. It also must not render the opening or closing quote, which are instead rendered by toJson.

class Value a => JsString a whereSource

The JsString typeclass represents types that can be render into json string syntax. They are special because only strings can appear as field names of json objects.

Methods

escape :: a -> EscapedSource

Instances

JsString Text 
JsString Text 
JsString ByteString

must be UTF-8 encoded

JsString ByteString

must be UTF-8 encoded

JsString Escaped 
JsString [Char] 

Monoid (from Data.Monoid)

class Monoid a where

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following laws:

  • mappend mempty x = x
  • mappend x mempty = x
  • mappend x (mappend y z) = mappend (mappend x y) z
  • mconcat = foldr mappend mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Minimal complete definition: mempty and mappend.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

Methods

mempty :: a

Identity of mappend

mappend :: a -> a -> a

An associative operation

mconcat :: [a] -> a

Fold a list using the monoid. For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

Instances

Monoid Ordering 
Monoid () 
Monoid All 
Monoid Any 
Monoid Text 
Monoid Text 
Monoid ByteString 
Monoid ByteString 
Monoid Poke 
Monoid Write 
Monoid Builder 
Monoid CommaMonoid 
Monoid Array 
Monoid Object 
Monoid Escaped 
Monoid [a] 
Monoid a => Monoid (Dual a) 
Monoid (Endo a) 
Num a => Monoid (Sum a) 
Num a => Monoid (Product a) 
Monoid (First a) 
Monoid (Last a) 
Monoid a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S." Since there is no "Semigroup" typeclass providing just mappend, we use Monoid instead.

Monoid (Vector a) 
Monoid b => Monoid (a -> b) 
(Monoid a, Monoid b) => Monoid (a, b) 
Ord k => Monoid (Map k v) 
Eq k => Monoid (HashMap k v) 
(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c) 
(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d) 
(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)