| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Json
Contents
- data JsonSpec k ts = JsonSpec {}
- data FieldSpec k ts where
- data FieldKey k t
- reqKey :: Typeable t => Text -> TypedKey t
- optKey :: Typeable t => Text -> TypedKey (Maybe t)
- data TypedKey t
- (.=) :: (ToJson t, JsonReadable t, Typeable t) => TypedKey t -> (k -> t) -> FieldKey k t
- (.=?) :: (ToJson t, JsonReadable t, Typeable t) => TypedKey (Maybe t) -> (k -> Maybe t) -> FieldKey k (Maybe t)
- data JsonSumSpec k = JsonSumSpec {
- js_parser :: !(ParseSpec k)
- js_serialiser :: !(k -> KeyedSerialiser k)
- (.->) :: ConstrTagger r => Text -> Parser (ResultType r) -> r
- (<||>) :: KeyedConstr k -> ParseSpec k -> ParseSpec k
- (.<-) :: ToJson a => Text -> a -> KeyedSerialiser k
- makeParser :: JsonSpec k ts -> Parser k
- makeSerialiser :: JsonSpec k ts -> k -> Value
- makeSumParser :: JsonSumSpec k -> Parser k
- makeSumSerialiser :: JsonSumSpec k -> k -> Value
- class ToJson a where
- class JsonReadable t where
- parseJsonBs :: JsonReadable t => ByteString -> Either String t
- parseJsonBsl :: JsonReadable t => ByteString -> Either String t
- parseJsonT :: JsonReadable t => Text -> Either String t
- serialiseJsonBs :: ToJson a => a -> ByteString
- serialiseJsonBsl :: ToJson a => a -> ByteString
- serialiseJsonT :: ToJson a => a -> Text
DSL to define JSON structure
Describes JSON parsing and serialisation of a Haskell type
reqKey :: Typeable t => Text -> TypedKey t Source
Required json object key. Use IsString instance for automatic choice
optKey :: Typeable t => Text -> TypedKey (Maybe t) Source
Optional json object key. Use IsString instance for automatic choice
Json object key to a value t
(.=) :: (ToJson t, JsonReadable t, Typeable t) => TypedKey t -> (k -> t) -> FieldKey k t Source
Construct a FieldKey mapping a json key to a getter function
(.=?) :: (ToJson t, JsonReadable t, Typeable t) => TypedKey (Maybe t) -> (k -> Maybe t) -> FieldKey k (Maybe t) Source
DSL to define JSON structure for sum types
data JsonSumSpec k Source
Describes JSON parsing and serialisation of a Haskell sum type. Currently
the library can only guarantee matching parsers/serialisers for
non-sum types using JsonSpec.
Constructors
| JsonSumSpec | |
Fields
| |
(.->) :: ConstrTagger r => Text -> Parser (ResultType r) -> r Source
Associate a json key with a parser
(<||>) :: KeyedConstr k -> ParseSpec k -> ParseSpec k infixr 3 Source
Choice between multiple constructors
(.<-) :: ToJson a => Text -> a -> KeyedSerialiser k Source
Associate a JSON key with a serialiser
Make parsers and serialisers from spec
makeParser :: JsonSpec k ts -> Parser k Source
Construct a Parser from JsonSpec to implement JsonReadable instances
makeSerialiser :: JsonSpec k ts -> k -> Value Source
makeSumParser :: JsonSumSpec k -> Parser k Source
Construct a Parser from JsonSumSpec to implement JsonReadable instances
makeSumSerialiser :: JsonSumSpec k -> k -> Value Source
Construct a function from JsonSumSpec to implement ToJson instances
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.
Instances
| ToJson Bool | |
| ToJson Double | |
| ToJson Int | |
| ToJson Int64 | |
| ToJson Text | |
| ToJson Value | |
| ToJson JsonString | |
| ToJson ObjectBuilder | |
| ToJson a => ToJson [a] | |
| ToJson a => ToJson (Maybe a) | |
| ToJson a => ToJson (Vector a) | |
| (Vector Vector a, ToJson a) => ToJson (Vector a) | |
| (Storable a, ToJson a) => ToJson (Vector a) | |
| (Prim a, ToJson a) => ToJson (Vector a) | |
| (ToJson a, ToJson b) => ToJson (Either a b) | |
| (ToJson a, ToJson b) => ToJson (a, b) | |
| (ToJsonString k, ToJson v) => ToJson (HashMap k v) |
class JsonReadable t where Source
Typeclass defining an attoparsec Parser how Haskell types should
be parsed from JSON. Use predifined instances (with readJson) and
runSpec (on ObjSpec) to define instances for custom types
Instances
| JsonReadable Bool | |
| JsonReadable Double | |
| JsonReadable Int | |
| JsonReadable Int8 | |
| JsonReadable Int16 | |
| JsonReadable Int32 | |
| JsonReadable Int64 | |
| JsonReadable Word | |
| JsonReadable Word8 | |
| JsonReadable Word16 | |
| JsonReadable Word32 | |
| JsonReadable Word64 | |
| JsonReadable Text | |
| JsonReadable Scientific | |
| JsonReadable t => JsonReadable [t] | |
| JsonReadable t => JsonReadable (Maybe t) | |
| JsonReadable t => JsonReadable (Vector t) | |
| JsonReadable a => JsonReadable (HVect ((:) * a ([] *))) | |
| (JsonReadable a, JsonReadable b) => JsonReadable (Either a b) | |
| JsonReadable t => JsonReadable (t, t) |
Run parsers / serialisers
parseJsonBs :: JsonReadable t => ByteString -> Either String t Source
Parse json from a strict ByteString
parseJsonBsl :: JsonReadable t => ByteString -> Either String t Source
Parse json from a lazy ByteString
parseJsonT :: JsonReadable t => Text -> Either String t Source
Parse json from a strict Text
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