Copyright | (c) Dong Han 2020 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Types and functions for working efficiently with JSON data, the design is quite similar to aeson
or json
:
- Encode to bytes can be done directly via
encodeJSON
. - Decode are split in two step, first we parse JSON doc into
Value
, then convert to haskell data viafromValue
. ToValue
are provided so that other doc formats can be easily supported, such asYAML
.
Note this module also provides many (orphan)instances to reduce the compilation stress of a gaint Base
module.
Synopsis
- class JSON a where
- data Value
- defaultSettings :: Settings
- data Settings = Settings {}
- snakeCase :: String -> Text
- trainCase :: String -> Text
- type DecodeError = Either ParseError ConvertError
- decode :: JSON a => Bytes -> (Bytes, Either DecodeError a)
- decode' :: JSON a => Bytes -> Either DecodeError a
- decodeText :: JSON a => Text -> (Text, Either DecodeError a)
- decodeText' :: JSON a => Text -> Either DecodeError a
- type ParseChunks m err x = m Bytes -> Bytes -> m (Bytes, Either err x)
- decodeChunk :: JSON a => Bytes -> Result DecodeError a
- decodeChunks :: (JSON a, Monad m) => ParseChunks m DecodeError a
- encode :: JSON a => a -> Bytes
- encodeChunks :: JSON a => a -> [Bytes]
- encodeText :: JSON a => a -> Text
- prettyJSON :: JSON a => a -> Builder ()
- prettyValue :: Value -> Builder ()
- parseValue :: Bytes -> (Bytes, Either ParseError Value)
- parseValue' :: Bytes -> Either ParseError Value
- gToValue :: GToValue f => Settings -> f a -> Value
- gFromValue :: GFromValue f => Settings -> Value -> Converter (f a)
- gEncodeJSON :: GEncodeJSON f => Settings -> f a -> Builder ()
- convertValue :: JSON a => Value -> Either ConvertError a
- newtype Converter a = Converter {
- runConverter :: forall r. ([PathElement] -> Text -> r) -> (a -> r) -> r
- fail' :: Text -> Converter a
- (<?>) :: Converter a -> PathElement -> Converter a
- prependContext :: Text -> Converter a -> Converter a
- data PathElement
- data ConvertError = ConvertError {
- errPath :: [PathElement]
- errMsg :: Text
- typeMismatch :: Text -> Text -> Value -> Converter a
- fromNull :: Text -> a -> Value -> Converter a
- withBool :: Text -> (Bool -> Converter a) -> Value -> Converter a
- withScientific :: Text -> (Scientific -> Converter a) -> Value -> Converter a
- withBoundedScientific :: Text -> (Scientific -> Converter a) -> Value -> Converter a
- withRealFloat :: RealFloat a => Text -> (a -> Converter r) -> Value -> Converter r
- withBoundedIntegral :: (Bounded a, Integral a) => Text -> (a -> Converter r) -> Value -> Converter r
- withText :: Text -> (Text -> Converter a) -> Value -> Converter a
- withArray :: Text -> (Vector Value -> Converter a) -> Value -> Converter a
- withKeyValues :: Text -> (Vector (Text, Value) -> Converter a) -> Value -> Converter a
- withFlatMap :: Text -> (FlatMap Text Value -> Converter a) -> Value -> Converter a
- withFlatMapR :: Text -> (FlatMap Text Value -> Converter a) -> Value -> Converter a
- withHashMap :: Text -> (HashMap Text Value -> Converter a) -> Value -> Converter a
- withHashMapR :: Text -> (HashMap Text Value -> Converter a) -> Value -> Converter a
- withEmbeddedJSON :: Text -> (Value -> Converter a) -> Value -> Converter a
- (.:) :: JSON a => FlatMap Text Value -> Text -> Converter a
- (.:?) :: JSON a => FlatMap Text Value -> Text -> Converter (Maybe a)
- (.:!) :: JSON a => FlatMap Text Value -> Text -> Converter (Maybe a)
- convertField :: (Value -> Converter a) -> FlatMap Text Value -> Text -> Converter a
- convertFieldMaybe :: (Value -> Converter a) -> FlatMap Text Value -> Text -> Converter (Maybe a)
- convertFieldMaybe' :: (Value -> Converter a) -> FlatMap Text Value -> Text -> Converter (Maybe a)
- (.=) :: JSON v => Text -> v -> (Text, Value)
- object :: [(Text, Value)] -> Value
- (.!) :: JSON v => Text -> v -> KVItem
- object' :: KVItem -> Builder ()
- data KVItem
How to use this module
This module is intended to be used qualified, e.g.
import qualified Z.Data.JSON as JSON import Z.Data.JSON ((.:), JSON(..))
The easiest way to use the library is to define target data type, deriving
Generic
and JSON
instances, which provides:
fromValue
to convertValue
to Haskell values.toValue
to convert Haskell values toValue
.encodeJSON
to directly write Haskell value into JSON bytes.
For example,
{-# LANGUAGE DeriveGeneric, DeriveAnyClass, DerivingStrategies #-} import GHC.Generics (Generic) import qualified Z.Data.Builder as Builder import qualified Z.Data.JSON as JSON import qualified Z.Data.Text as T data Person = Person {name :: T.Text, age :: Int} deriving (Show, Generic) deriving anyclass (JSON.JSON)
We can now encode & decode JSON like this:
>>>
JSON.toValue (Person{ name="Alice", age=16 })
Object [("name",String "Alice"),("age",Number 16.0)]>>>
JSON.encode (Person{ name="Alice", age=16 })
[123,34,110,97,109,101,34,58,34,65,108,105,99,101,34,44,34,97,103,101,34,58,49,54,125]>>>
JSON.encodeText (Person{ name="Alice", age=16 })
"{\"age\":16,\"name\":\"Alice\"}">>>
JSON.decodeText' "{\"age\":16,\"name\":\"Alice\"}" :: Either JSON.DecodeError Person
Right (Person {age = 16, name = "Alice"})
The Generic
based instances convert Haskell data with following rules:
- Constructors without payloads are encoded as JSON String,
data T = A | B
are encoded as"A"
or"B"
. - Single constructor are ingored if there're payloads,
data T = T ...
,T
is ingored: - Records are encoded as JSON object.
data T = T{k1 :: .., k2 :: ..}
are encoded as{"k1":...,"k2":...}
. - Plain product are encoded as JSON array.
data T = T t1 t2
are encoded as "[x1,x2]". - Single field plain product are encoded as it is, i.e.
data T = T t
are encoded as "x" just like its payload. - Multiple constructors are convert to single key JSON object if there're payloads:
- Records are encoded as JSON object like above.
data T = A | B {k1 :: .., k2 :: ..}
are encoded as{"B":{"k1":...,"k2":...}}
inB .. ..
case, or"A"
inA
case. - Products inside a sum type are similar to above, wrapped by an outer single-key object layer marking which constructor used during data construction.
These rules apply to user defined ADTs, but some built-in instances have different behaviours, namely:
Maybe a
are encoded as JSONnull
inNothing
case, or directly encoded to its payload inJust
case.[a]
are encoded to JSON array,[Char]
are encoded into JSON string.NonEmpty
,Vector
,PrimVector
,HashSet
,FlatSet
,FlatIntSet
are also encoded to JSON array.Bytes
are encoded into JSON text using base64 encoding.HashMap
,FlatMap
,FlatIntMap
are encoded to JSON object.
There're some modifying options if you providing a custom Settings
, which
allow you to modify field name or constructor name, but please DO NOT
produce control characters during your modification, since we assume field
labels and constructor name won't contain them, thus we can save an extra
escaping pass. To use custom Settings
just write:
data T = T {fooT :: Int, barT :: [Int]} deriving Generic instance JSON.JSON T where -- You can omit following definition if you don't need to change settings toValue = JSON.gToValue JSON.defaultSettings{ JSON.fieldFmt = JSON.snakeCase } . from encodeJSON = JSON.gEncodeJSON JSON.defaultSettings{ JSON.fieldFmt = JSON.snakeCase } . from
>>>
JSON.toValue (T 0 [1,2,3])
Object [("foo_t",Number 0.0),("bar_t",Array [Number 1.0,Number 2.0,Number 3.0])]
You can write JSON
instances by hand if the Generic
based one doesn't suit you.
Here is an example similar to aeson's.
import qualified Z.Data.Text as T import qualified Z.Data.Vector as V import qualified Z.Data.Builder as B import qualified Z.Data.JSON as JSON import Z.Data.JSON ((.:), (.=), (.!), JSON(..)) data Person = Person { name :: T.Text , age :: Int } deriving Show instance JSON Person where fromValue = JSON.withFlatMapR "Person" $ \ v -> Person <$> v .: "name" <*> v .: "age" toValue (Person n a) = JSON.object ["name" .= n, "age" .= a] encodeJSON (Person n a) = JSON.object' $ ("name" .! n <> "age" .! a)
>>>
toValue (Person "Joe" 12)
Object [("name",String "Joe"),("age",Number 12.0)]>>>
JSON.convert' @Person . JSON.Object $ V.pack [("name",JSON.String "Joe"),("age",JSON.Number 12.0)]
Right (Person {name = "Joe", age = 12})>>>
JSON.encodeText (Person "Joe" 12)
"{"name":"Joe","age":12}"
The Value
type is different from aeson's one in that we use Vector (Text, Value)
to represent JSON objects, thus
we can choose different strategies on key duplication, the lookup map type, etc. so instead of a single withObject
,
we provide withHashMap
, withHashMapR
, withFlatMap
and withFlatMapR
which use different lookup map type, and different key order priority. Most of the time FlatMap
is faster than HashMap
since we only use the lookup map once, the cost of constructing a HashMap
is higher. If you want to directly work on key-values, withKeyValues
provide key-values vector access.
There're some useful tools to help write encoding code in Z.Data.JSON.Builder module, such as a JSON string escaping tool, etc.
If you don't particularly care for fast encoding, you can also use toValue
together with value builder, the overhead is usually very small.
JSON Class
Type class for encode & decode JSON.
Nothing
fromValue :: Value -> Converter a Source #
toValue :: a -> Value Source #
encodeJSON :: a -> Builder () Source #
Instances
A JSON value represented as a Haskell value.
The Object'
s payload is a key-value vector instead of a map, which parsed
directly from JSON document. This design choice has following advantages:
- Allow different strategies handling duplicated keys.
- Allow different
Map
type to do further parsing, e.g.FlatMap
- Roundtrip without touching the original key-value order.
- Save time if constructing map is not neccessary, e.g. using a linear scan to find a key if only that key is needed.
Object !(Vector (Text, Value)) | |
Array !(Vector Value) | |
String !Text | |
Number !Scientific | |
Bool !Bool | |
Null |
Instances
defaultSettings :: Settings Source #
Settings T.pack T.pack False
Generic encode/decode Settings
There should be no control characters in formatted texts since we don't escaping those
field names or constructor names (defaultSettings
relys on Haskell's lexical property).
Otherwise encodeJSON
will output illegal JSON string.
snakeCase :: String -> Text Source #
Snake casing a pascal cased constructor name or camel cased field name, words are always lower cased and separated by an underscore.
trainCase :: String -> Text Source #
Train casing a pascal cased constructor name or camel cased field name, words are always lower cased and separated by a hyphen.
Encode & Decode
type DecodeError = Either ParseError ConvertError Source #
decode :: JSON a => Bytes -> (Bytes, Either DecodeError a) Source #
Decode a JSON bytes, return any trailing bytes.
decode' :: JSON a => Bytes -> Either DecodeError a Source #
Decode a JSON doc, only trailing JSON whitespace are allowed.
decodeText :: JSON a => Text -> (Text, Either DecodeError a) Source #
Decode a JSON text, return any trailing text.
decodeText' :: JSON a => Text -> Either DecodeError a Source #
Decode a JSON doc, only trailing JSON whitespace are allowed.
type ParseChunks m err x = m Bytes -> Bytes -> m (Bytes, Either err x) Source #
Type alias for a streaming parser, draw chunk from Monad m with a initial chunk,
return result in Either err x
.
decodeChunk :: JSON a => Bytes -> Result DecodeError a Source #
Decode a JSON doc chunk.
decodeChunks :: (JSON a, Monad m) => ParseChunks m DecodeError a Source #
Decode JSON doc chunks, return trailing bytes.
encode :: JSON a => a -> Bytes Source #
Directly encode data to JSON bytes.
This function use buildWith
smallChunkSize
to balance common use case, if you need fine tuning on memory usage,
please use buildWith
and a custom initial chunk size with encodeJSON
.
encodeChunks :: JSON a => a -> [Bytes] Source #
Encode data to JSON bytes chunks.
prettyJSON :: JSON a => a -> Builder () Source #
Directly encode data to JSON bytes.
prettyValue :: Value -> Builder () Source #
'ValuePretty'' with 4 spaces indentation per level, e.g.
{ "results": [ { "from_user_id_str":"80430860", "profile_image_url":"http://a2.twimg.com/profile_images/536455139/icon32_normal.png", "created_at":"Wed, 26 Jan 2011 07:07:02 +0000", "from_user":"kazu_yamamoto", "id_str":"30159761706061824", "metadata": { "result_type":"recent" }, "to_user_id":null, "text":"Haskell Server Pages って、まだ続いていたのか!", "id":30159761706061824, "from_user_id":80430860, "geo":null, "iso_language_code":"no", "to_user_id_str":null, "source":"<a href="http:/twitter.com">web</a>" } ], "max_id":30159761706061824, "since_id":0, "refresh_url":"?since_id=30159761706061824&q=haskell", "next_page":"?page=2&max_id=30159761706061824&rpp=1&q=haskell", "results_per_page":1, "page":1, "completed_in":1.2606e-2, "since_id_str":"0", "max_id_str":"30159761706061824", "query":"haskell" }
parse into JSON Value
parseValue :: Bytes -> (Bytes, Either ParseError Value) Source #
Parse Value
without consuming trailing bytes.
parseValue' :: Bytes -> Either ParseError Value Source #
Parse Value
, and consume all trailing JSON white spaces, if there're
bytes left, parsing will fail.
Generic functions
gEncodeJSON :: GEncodeJSON f => Settings -> f a -> Builder () Source #
Convert Value
to Haskell data
convertValue :: JSON a => Value -> Either ConvertError a Source #
Run a Converter
with input value.
Converter
provides a monadic interface to convert protocol IR (e.g.Value
) to Haskell ADT.
Converter | |
|
(<?>) :: Converter a -> PathElement -> Converter a infixl 9 Source #
Add (JSON) Path context to a converter
When converting a complex structure, it helps to annotate (sub)converters with context, so that if an error occurs, you can find its location.
withFlatMapR "Person" $ \o -> Person <$> o .: "name" <?> Key "name" <*> o .: "age" <?> Key "age"
(Standard methods like (.:)
already do this.)
With such annotations, if an error occurs, you will get a (JSON) Path location of that error.
prependContext :: Text -> Converter a -> Converter a Source #
Add context to a failure message, indicating the name of the structure being converted.
prependContext "MyType" (fail "[error message]") -- Error: "converting MyType failed, [error message]"
data PathElement Source #
Elements of a (JSON) Value path used to describe the location of an error.
Key !Text | Path element of a key into an object, "object.key". |
Index !Int | Path element of an index into an array, "array[index]". |
Embedded | path of a embedded (JSON) String |
Instances
data ConvertError Source #
Error info with (JSON) Path info.
ConvertError | |
|
Instances
:: Text | The name of the type you are trying to convert. |
-> Text | The JSON value type you expecting to meet. |
-> Value | The actual value encountered. |
-> Converter a |
Produce an error message like converting XXX failed, expected XXX, encountered XXX
.
withScientific :: Text -> (Scientific -> Converter a) -> Value -> Converter a Source #
applies withScientific
name f valuef
to the Scientific
number
when value
is a Number
and fails using typeMismatch
otherwise.
Warning: If you are converting from a scientific to an unbounded
type such as Integer
you may want to add a restriction on the
size of the exponent (see withBoundedScientific
) to prevent
malicious input from filling up the memory of the target system.
Error message example
withScientific "MyType" f (String "oops") -- Error: "converting MyType failed, expected Number, but encountered String"
withBoundedScientific :: Text -> (Scientific -> Converter a) -> Value -> Converter a Source #
applies withBoundedScientific
name f valuef
to the Scientific
number
when value
is a Number
with exponent less than or equal to 1024.
withRealFloat :: RealFloat a => Text -> (a -> Converter r) -> Value -> Converter r Source #
@withRealFloat
try to convert floating number with following rules:
- Use
±Infinity
to represent out of range numbers. - Convert
Null
asNaN
withBoundedIntegral :: (Bounded a, Integral a) => Text -> (a -> Converter r) -> Value -> Converter r Source #
applies withBoundedScientific
name f valuef
to the Scientific
number
when value
is a Number
and value is within minBound ~ maxBound
.
withKeyValues :: Text -> (Vector (Text, Value) -> Converter a) -> Value -> Converter a Source #
Directly use Object
as key-values for further converting.
withFlatMap :: Text -> (FlatMap Text Value -> Converter a) -> Value -> Converter a Source #
Take a Object
as an 'FM.FlatMap T.Text Value', on key duplication prefer first one.
withFlatMapR :: Text -> (FlatMap Text Value -> Converter a) -> Value -> Converter a Source #
Take a Object
as an 'FM.FlatMap T.Text Value', on key duplication prefer last one.
withHashMap :: Text -> (HashMap Text Value -> Converter a) -> Value -> Converter a Source #
Take a Object
as an 'HM.HashMap T.Text Value', on key duplication prefer first one.
withHashMapR :: Text -> (HashMap Text Value -> Converter a) -> Value -> Converter a Source #
Take a Object
as an 'HM.HashMap T.Text Value', on key duplication prefer last one.
:: Text | data type name |
-> (Value -> Converter a) | a inner converter which will get the converted |
-> Value | |
-> Converter a |
Decode a nested JSON-encoded string.
(.:) :: JSON a => FlatMap Text Value -> Text -> Converter a Source #
Retrieve the value associated with the given key of an Object
.
The result is empty
if the key is not present or the value cannot
be converted to the desired type.
This accessor is appropriate if the key and value must be present
in an object for it to be valid. If the key and value are
optional, use .:?
instead.
(.:?) :: JSON a => FlatMap Text Value -> Text -> Converter (Maybe a) Source #
Retrieve the value associated with the given key of an Object
. The
result is Nothing
if the key is not present or if its value is Null
,
or fail if the value cannot be converted to the desired type.
This accessor is most useful if the key and value can be absent
from an object without affecting its validity. If the key and
value are mandatory, use .:
instead.
convertFieldMaybe :: (Value -> Converter a) -> FlatMap Text Value -> Text -> Converter (Maybe a) Source #
Variant of .:?
with explicit converter function.
convertFieldMaybe' :: (Value -> Converter a) -> FlatMap Text Value -> Text -> Converter (Maybe a) Source #
Variant of .:!
with explicit converter function.
Helper for manually writing instance.
(.=) :: JSON v => Text -> v -> (Text, Value) infixr 8 Source #
Connect key and value to a tuple to be used with object
.