Copyright | (c) Dong Han 2019 |
---|---|
License | BSD |
Maintainer | winterland1989@gmail.com |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
This module provides Converter
to convert Value
to haskell data types, and various tools to help
user define FromValue
, ToValue
and EncodeJSON
instance.
Synopsis
- type DecodeError = Either ParseError ConvertError
- decode :: FromValue a => Bytes -> (Bytes, Either DecodeError a)
- decode' :: FromValue a => Bytes -> Either DecodeError a
- decodeText :: FromValue a => Text -> (Text, Either DecodeError a)
- decodeText' :: FromValue a => Text -> Either DecodeError a
- decodeChunks :: (FromValue a, Monad m) => m Bytes -> Bytes -> m (Bytes, Either DecodeError a)
- decodeChunks' :: (FromValue a, Monad m) => m Bytes -> Bytes -> m (Either DecodeError a)
- encode :: EncodeJSON a => a -> Bytes
- encodeChunks :: EncodeJSON a => a -> [Bytes]
- encodeText :: EncodeJSON a => a -> Text
- data Value
- parseValue :: Bytes -> (Bytes, Either ParseError Value)
- parseValue' :: Bytes -> Either ParseError Value
- parseValueChunks :: Monad m => m Bytes -> Bytes -> m (Bytes, Either ParseError Value)
- parseValueChunks' :: Monad m => m Bytes -> Bytes -> m (Either ParseError Value)
- convert :: (a -> Converter r) -> a -> Either ConvertError r
- convert' :: FromValue 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
- 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
- (.:) :: FromValue a => FlatMap Text Value -> Text -> Converter a
- (.:?) :: FromValue a => FlatMap Text Value -> Text -> Converter (Maybe a)
- (.:!) :: FromValue 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)
- defaultSettings :: Settings
- data Settings = Settings {}
- class ToValue a where
- class GToValue f where
- class FromValue a where
- class GFromValue f where
- gFromValue :: Settings -> Value -> Converter (f a)
- class EncodeJSON a where
- encodeJSON :: a -> Builder ()
- class GEncodeJSON f where
- gEncodeJSON :: Settings -> f a -> Builder ()
- type family Field f where ...
- class GWriteFields f where
- gWriteFields :: Settings -> SmallMutableArray s (Field f) -> Int -> f a -> ST s ()
- class GMergeFields f where
- gMergeFields :: Proxy# f -> SmallMutableArray s (Field f) -> ST s Value
- class GConstrToValue f where
- gConstrToValue :: Bool -> Settings -> f a -> Value
- type family LookupTable f where ...
- class GFromFields f where
- gFromFields :: Settings -> LookupTable f -> Int -> Converter (f a)
- class GBuildLookup f where
- gBuildLookup :: Proxy# f -> Int -> Text -> Value -> Converter (LookupTable f)
- class GConstrFromValue f where
- gConstrFromValue :: Bool -> Settings -> Value -> Converter (f a)
- class GAddPunctuation (f :: * -> *) where
- gAddPunctuation :: Proxy# f -> Builder () -> Builder ()
- class GConstrEncodeJSON f where
- gConstrEncodeJSON :: Bool -> Settings -> f a -> Builder ()
- kv :: Text -> Builder () -> Builder ()
- kv' :: Text -> Builder () -> Builder ()
- string :: Text -> Builder ()
- commaSepList :: EncodeJSON a => [a] -> Builder ()
- commaSepVec :: (EncodeJSON a, Vec v a) => v a -> Builder ()
Encode & Decode
type DecodeError = Either ParseError ConvertError Source #
decode :: FromValue a => Bytes -> (Bytes, Either DecodeError a) Source #
Decode a JSON bytes, return any trailing bytes.
decode' :: FromValue a => Bytes -> Either DecodeError a Source #
Decode a JSON doc, only trailing JSON whitespace are allowed.
decodeText :: FromValue a => Text -> (Text, Either DecodeError a) Source #
Decode a JSON text, return any trailing text.
decodeText' :: FromValue a => Text -> Either DecodeError a Source #
Decode a JSON doc, only trailing JSON whitespace are allowed.
decodeChunks :: (FromValue a, Monad m) => m Bytes -> Bytes -> m (Bytes, Either DecodeError a) Source #
Decode JSON doc chunks, return trailing bytes.
decodeChunks' :: (FromValue a, Monad m) => m Bytes -> Bytes -> m (Either DecodeError a) Source #
Decode JSON doc chunks, consuming trailing JSON whitespaces (other trailing bytes are not allowed).
encode :: EncodeJSON a => a -> Bytes Source #
Directly encode data to JSON bytes.
encodeChunks :: EncodeJSON a => a -> [Bytes] Source #
Encode data to JSON bytes chunks.
encodeText :: EncodeJSON a => a -> Text Source #
Text version encodeBytes
.
Re-export Value
type
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
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.
parseValueChunks :: Monad m => m Bytes -> Bytes -> m (Bytes, Either ParseError Value) Source #
Increamental parse Value
without consuming trailing bytes.
parseValueChunks' :: Monad m => m Bytes -> Bytes -> m (Either ParseError Value) Source #
Increamental parse Value
and consume all trailing JSON white spaces, if there're
bytes left, parsing will fail.
Convert Value
to Haskell data
convert :: (a -> Converter r) -> a -> Either ConvertError r Source #
Run a Converter
with input value.
Converter
for convert result from JSON Value
.
This is intended to be named differently from Parser
to clear confusions.
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 #
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.
(.:) :: FromValue 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.
(.:?) :: FromValue 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 empty
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.
FromValue, ToValue & EncodeJSON
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.
class ToValue a where Source #
Typeclass for converting to JSON Value
.
Nothing
Instances
class GToValue f where Source #
Instances
GToValue f => GToValue (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f :: k -> Type) Source # | |
(GToValue f, Selector ('MetaSel ('Just l) u ss ds)) => GToValue (S1 ('MetaSel ('Just l) u ss ds) f :: k -> Type) Source # | |
ToValue a => GToValue (K1 i a :: k -> Type) Source # | |
GConstrToValue f => GToValue (D1 c f :: k -> Type) Source # | |
class FromValue a where Source #
Nothing
Instances
class GFromValue f where Source #
Instances
(GFromValue f, Selector ('MetaSel ('Just l) u ss ds)) => GFromValue (S1 ('MetaSel ('Just l) u ss ds) f :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
GFromValue f => GFromValue (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
FromValue a => GFromValue (K1 i a :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
GConstrFromValue f => GFromValue (D1 c f :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base |
class EncodeJSON a where Source #
Nothing
encodeJSON :: a -> Builder () Source #
default encodeJSON :: (Generic a, GEncodeJSON (Rep a)) => a -> Builder () Source #
Instances
class GEncodeJSON f where Source #
gEncodeJSON :: Settings -> f a -> Builder () Source #
Instances
(GEncodeJSON a, GEncodeJSON b) => GEncodeJSON (a :*: b :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
GEncodeJSON f => GEncodeJSON (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
(GEncodeJSON f, Selector ('MetaSel ('Just l) u ss ds)) => GEncodeJSON (S1 ('MetaSel ('Just l) u ss ds) f :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
EncodeJSON a => GEncodeJSON (K1 i a :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
GConstrEncodeJSON f => GEncodeJSON (D1 c f :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base |
Helper classes for generics
class GWriteFields f where Source #
gWriteFields :: Settings -> SmallMutableArray s (Field f) -> Int -> f a -> ST s () Source #
Instances
(GToValue f, Selector ('MetaSel ('Just l) u ss ds)) => GWriteFields (S1 ('MetaSel ('Just l) u ss ds) f :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
GToValue f => GWriteFields (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
(ProductSize a, GWriteFields a, GWriteFields b, Field a ~ Field b) => GWriteFields (a :*: b :: Type -> Type) Source # | |
Defined in Z.Data.JSON.Base gWriteFields :: forall s (a0 :: k). Settings -> SmallMutableArray s (Field (a :*: b)) -> Int -> (a :*: b) a0 -> ST s () Source # |
class GMergeFields f where Source #
gMergeFields :: Proxy# f -> SmallMutableArray s (Field f) -> ST s Value Source #
Instances
GMergeFields (S1 ('MetaSel ('Just l) u ss ds) f :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
GMergeFields (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
GMergeFields a => GMergeFields (a :*: b :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base gMergeFields :: Proxy# (a :*: b) -> SmallMutableArray s (Field (a :*: b)) -> ST s Value Source # |
class GConstrToValue f where Source #
Instances
GConstrToValue (V1 :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
(Constructor c, GToValue (S1 sc f)) => GConstrToValue (C1 c (S1 sc f) :: k -> Type) Source # | Constructor with a single payload |
Defined in Z.Data.JSON.Base | |
Constructor c => GConstrToValue (C1 c (U1 :: k -> Type) :: k -> Type) Source # | Constructor without payload, convert to String |
Defined in Z.Data.JSON.Base | |
(GConstrToValue f, GConstrToValue g) => GConstrToValue (f :+: g :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
(ProductSize (a :*: b), GWriteFields (a :*: b), GMergeFields (a :*: b), Constructor c) => GConstrToValue (C1 c (a :*: b) :: Type -> Type) Source # | Constructor with multiple payloads |
Defined in Z.Data.JSON.Base |
type family LookupTable f where ... Source #
LookupTable (a :*: b) = LookupTable a | |
LookupTable (S1 (MetaSel Nothing u ss ds) f) = Vector Value | |
LookupTable (S1 (MetaSel (Just l) u ss ds) f) = FlatMap Text Value |
class GFromFields f where Source #
gFromFields :: Settings -> LookupTable f -> Int -> Converter (f a) Source #
Instances
(GFromValue f, Selector ('MetaSel ('Just l) u ss ds)) => GFromFields (S1 ('MetaSel ('Just l) u ss ds) f :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
GFromValue f => GFromFields (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
(ProductSize a, GFromFields a, GFromFields b, LookupTable a ~ LookupTable b) => GFromFields (a :*: b :: Type -> Type) Source # | |
Defined in Z.Data.JSON.Base gFromFields :: forall (a0 :: k). Settings -> LookupTable (a :*: b) -> Int -> Converter ((a :*: b) a0) Source # |
class GBuildLookup f where Source #
gBuildLookup :: Proxy# f -> Int -> Text -> Value -> Converter (LookupTable f) Source #
Instances
GBuildLookup (S1 ('MetaSel ('Just l) u ss ds) f :: k -> Type) Source # | |
GBuildLookup (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f :: k -> Type) Source # | |
(GBuildLookup a, GBuildLookup b) => GBuildLookup (a :*: b :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base |
class GConstrFromValue f where Source #
Instances
GConstrFromValue (V1 :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
(Constructor c, GFromValue (S1 sc f)) => GConstrFromValue (C1 c (S1 sc f) :: k -> Type) Source # | Constructor with a single payload |
Defined in Z.Data.JSON.Base | |
Constructor c => GConstrFromValue (C1 c (U1 :: k -> Type) :: k -> Type) Source # | Constructor without payload, convert to String |
Defined in Z.Data.JSON.Base | |
(GConstrFromValue f, GConstrFromValue g) => GConstrFromValue (f :+: g :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
(ProductSize (a :*: b), GFromFields (a :*: b), GBuildLookup (a :*: b), Constructor c) => GConstrFromValue (C1 c (a :*: b) :: Type -> Type) Source # | Constructor with multiple payloads |
Defined in Z.Data.JSON.Base |
class GAddPunctuation (f :: * -> *) where Source #
Instances
GAddPunctuation a => GAddPunctuation (a :*: b) Source # | |
Defined in Z.Data.JSON.Base | |
GAddPunctuation (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f) Source # | |
Defined in Z.Data.JSON.Base | |
GAddPunctuation (S1 ('MetaSel ('Just l) u ss ds) f) Source # | |
Defined in Z.Data.JSON.Base |
class GConstrEncodeJSON f where Source #
Instances
GConstrEncodeJSON (V1 :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
(Constructor c, GEncodeJSON (S1 ('MetaSel ('Just l) u ss ds) f)) => GConstrEncodeJSON (C1 c (S1 ('MetaSel ('Just l) u ss ds) f) :: k -> Type) Source # | |
(Constructor c, GEncodeJSON (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f)) => GConstrEncodeJSON (C1 c (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f) :: k -> Type) Source # | Constructor with a single payload |
Constructor c => GConstrEncodeJSON (C1 c (U1 :: k -> Type) :: k -> Type) Source # | Constructor without payload, convert to String |
Defined in Z.Data.JSON.Base | |
(GConstrEncodeJSON f, GConstrEncodeJSON g) => GConstrEncodeJSON (f :+: g :: k -> Type) Source # | |
Defined in Z.Data.JSON.Base | |
(GEncodeJSON (a :*: b), GAddPunctuation (a :*: b), Constructor c) => GConstrEncodeJSON (C1 c (a :*: b) :: Type -> Type) Source # | Constructor with multiple payloads |
Defined in Z.Data.JSON.Base |
Helper for manually writing encoders
kv :: Text -> Builder () -> Builder () Source #
Use :
as separator to connect a label(no need to escape, only add quotes) with field builders.
kv' :: Text -> Builder () -> Builder () Source #
Use :
as separator to connect a label(escaped 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" '"': "\"" '\': "\\" '/': "\/" other chars <= 0x1F: "\u00XX"
commaSepList :: EncodeJSON a => [a] -> Builder () Source #
Use ,
as separator to connect list of builders.
commaSepVec :: (EncodeJSON a, Vec v a) => v a -> Builder () Source #
Use ,
as separator to connect a vector of builders.