Maintainer | Leon P Smith <leon@melding-monads.com> |
---|
Data.Json.Builder
Contents
Description
Data structure agnostic JSON serialization
- data Json
- toBuilder :: Value a => a -> Builder
- toJsonBS :: Value a => a -> ByteString
- toJsonLBS :: Value a => a -> ByteString
- class Value a where
- data Array
- element :: Value a => a -> Array
- class JsArray a where
- data Object
- row :: (JsString k, Value a) => k -> a -> Object
- class JsObject a where
- data Escaped
- class Value a => JsString a where
- class Monoid a where
Json Values
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
.
toJsonBS :: Value a => a -> ByteStringSource
toJsonLBS :: Value a => a -> ByteStringSource
The Value
typeclass represents types that can be rendered
into valid json syntax.
Instances
Value Bool | renders as |
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 |
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 |
(JsString k, Value a) => Value (Map k a) | renders as an |
(JsString k, Value a) => Value (HashMap k a) | renders as an |
Json Arrays ["foobar",true,42]
Json Objects {"x":3.14,"y":-2.7}
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.
Json Strings
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.
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 newtype
s 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 |
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) |