highjson-0.2.0.1: Very fast JSON serialisation and parsing library

Safe HaskellNone
LanguageHaskell2010

Data.Json.Serialiser

Contents

Synopsis

Serialising to different types

serialiseJsonBs :: ToJson a => a -> ByteString Source

Serialise json to a strict ByteString

serialiseJsonBsl :: ToJson a => a -> ByteString Source

Serialise json to a lazy ByteString

serialiseJsonT :: ToJson a => a -> Text Source

Serialise json to a strict Text

Description how to serialise JSON from a Haskell type

class ToJson a where

The class of types that can be converted to JSON values. See ObjectBuilder for an example of writing a ToJson instance for a custom data type.

ToJson instances are provided for many common types. For example, to create a JSON array, call toJson on a list or Vector. To create a JSON object, call toJson on a HashMap.

Methods

toJson :: a -> Value

DSL to easily create serialiser for custom Haskell types

data SerSpec k where Source

Parser specification. Use OnlyConstr for normal types and 'FirstConstr'/'NextConstr' for sum types

Constructors

SingleConstr :: SerObjSpec k ts -> SerSpec k 
MultiConstr :: (k -> KeyedSerialiser k) -> SerSpec k 

(.<-) :: ToJson a => Text -> a -> KeyedSerialiser k Source

Associate a JSON key with a serialiser

data SerObjSpec k ts where Source

List of SpecKeys defining the serialisation of values to json

Constructors

SerObjSpecNil :: SerObjSpec k [] 
(:&&&:) :: (ToJson t, Typeable t) => !(SpecKey k t) -> !(SerObjSpec k ts) -> SerObjSpec k (t : ts) infixr 5 

data SpecKey k t Source

A json key and a getter

(.:) :: (ToJson t, Typeable t) => Text -> (k -> t) -> SpecKey k t Source

Construct a SpecKey mapping a json key to a getter function

(.:?) :: (ToJson t, Typeable t) => Text -> (k -> Maybe t) -> SpecKey k (Maybe t) Source

Construct a SpecKey mapping a json key to a getter function of a Maybe type. This allows to omit the key when generating json instead of setting it to null.

Low level JSON serialising helpers

data ObjectBuilder :: *

Builds a JSON object.

An ObjectBuilder builds one or more key-value pairs of a JSON object. They are constructed with the .= operator and combined with <>.

To turn an ObjectBuilder into a Value, use its ToJson class instance.

    data Friend = Friend
        { fId :: !Int
        , fName :: !Text
        } deriving (Eq, Show)

    instance ToJson Friend where
        toJson friend = toJson $
                   "id"   .= fId friend
                <> "name" .= fName friend

WARNING: ObjectBuilder does not check uniqueness of object keys. If two keys with the same value are inserted, then the resulting JSON document will be illegal.

emptyObject :: Value

A Value that produces the empty object.

data Value :: *

Represents a JSON value.

Values are built up from either ToJson instances or from primitives like emptyObject, array, and null.

In special cases, or when performance is of utmost importance, the unsafe functions unsafeAppendUtf8Builder are available.

Internally, Value encodes an action or sequence of actions that append JSON-encoded text to the underlying Utf8Builder.

Instances

(.=) :: ToJson a => Text -> a -> ObjectBuilder infixr 8

Create an ObjectBuilder from a key and a value.

(.=#) :: ToJson a => Addr# -> a -> ObjectBuilder infixr 8

Create an ObjectBuilder from a key and a value. The key is an ASCII-7, unescaped, zero-terminated Addr#.

WARNING: This function is unsafe. If the key is NOT zero-terminated, then an access violation might result. If the key is not a sequence of unescaped ASCII characters, the resulting JSON document will be illegal.

This function is provided for maximum performance in the common case that object keys are ASCII-7. It achieves performance by avoiding the CAF for a Text literal and avoiding the need to transcode UTF-16 to UTF-8 and escape.

To use this function, the calling source file must have the MagicHash extension enabled.

    data Friend = Friend
        { fId :: !Int
        , fName :: !Text
        } deriving (Eq, Show)

    instance ToJson Friend where
        toJson friend = toJson $
                   "id"#   .=# fId friend
                <> "name"# .=# fName friend

row :: (ToJsonString k, ToJson v) => k -> v -> ObjectBuilder infixr 8

Create an ObjectBuilder from an arbitrary key and value. The key can be any type with a ToJsonString instance.

array :: (Foldable t, ToJson a) => t a -> Value

Serialize any Foldable as a JSON array. This is generally slower than directly calling toJson on a list or Vector, but it will convert any Foldable type into an array.

nullValue :: Value

Represents a JSON "null".