| Copyright | (c) Dong Han 2019 | 
|---|---|
| License | BSD | 
| Maintainer | winterland1989@gmail.com | 
| Stability | experimental | 
| Portability | non-portable | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
Z.Data.JSON.Base
Description
This module provides Converter to convert Value to haskell data types, and various tools to help
user define JSON instance. It's recommended to use Z.Data.JSON instead since it contain more instances.
Synopsis
- class JSON a where
- data Value
- defaultSettings :: Settings
- data Settings = Settings {}
- 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
- kv :: Text -> Builder () -> Builder ()
- kv' :: Text -> Builder () -> Builder ()
- string :: Text -> Builder ()
- curly :: Builder () -> Builder ()
- square :: Builder () -> Builder ()
- commaSepList :: JSON a => [a] -> Builder ()
- commaSepVec :: (JSON a, Vec v a) => v a -> Builder ()
JSON Class
Type class for encode & decode JSON.
Minimal complete definition
Nothing
Methods
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 Maptype 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.
Constructors
| 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.
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.
Constructors
| Converter | |
| Fields 
 | |
(<?>) :: 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.
Constructors
| 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.
Constructors
| ConvertError | |
| Fields 
 | |
Instances
Arguments
| :: 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 #
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 #
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 ±Infinityto represent out of range numbers.
- Convert NullasNaN
withBoundedIntegral :: (Bounded a, Integral a) => Text -> (a -> Converter r) -> Value -> Converter r Source #
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.
Arguments
| :: 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.
kv :: Text -> Builder () -> Builder () Source #
Use : as separator to connect a label(no escape, only add quotes) with field builders.
Don't use chars which need escaped in label.
kv' :: Text -> Builder () -> Builder () Source #
Use : as separator to connect a label(escape the label and add quotes) with field builders.
string :: Text -> Builder () Source #
Escape text into JSON string and add double quotes, escaping rules:
'\b': "\b" '\f': "\f" '\n': "\n" '\r': "\r" '\t': "\t" '"': "\"" '\': "\\" 'DEL': "\u007f" other chars <= 0x1F: "\u00XX"
commaSepList :: JSON a => [a] -> Builder () Source #
Use , as separator to connect list of builders.