Z-Data-0.9.0.0: Array, vector and text
Copyright(c) Dong Han 2019
LicenseBSD
Maintainerwinterland1989@gmail.com
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

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

JSON Class

class JSON a where Source #

Type class for encode & decode JSON.

Minimal complete definition

Nothing

Methods

fromValue :: Value -> Converter a Source #

default fromValue :: (Generic a, GFromValue (Rep a)) => Value -> Converter a Source #

toValue :: a -> Value Source #

default toValue :: (Generic a, GToValue (Rep a)) => a -> Value Source #

encodeJSON :: a -> Builder () Source #

default encodeJSON :: (Generic a, GEncodeJSON (Rep a)) => a -> Builder () Source #

Instances

Instances details
JSON Bool Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Char Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Double Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Float Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Int Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Int8 Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Int16 Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Int32 Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Int64 Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Integer Source #

This instance includes a bounds check to prevent maliciously large inputs to fill up the memory of the target system. You can newtype Integer and provide your own instance using withScientific if you want to allow larger inputs.

Instance details

Defined in Z.Data.JSON.Base

JSON Natural Source #

This instance includes a bounds check to prevent maliciously large inputs to fill up the memory of the target system. You can newtype Natural and provide your own instance using withScientific if you want to allow larger inputs.

Instance details

Defined in Z.Data.JSON.Base

JSON Ordering Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Word Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Word8 Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Word16 Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Word32 Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Word64 Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON () Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Version Source #

Only round trip versionBranch as JSON array.

Instance details

Defined in Z.Data.JSON

JSON ExitCode Source # 
Instance details

Defined in Z.Data.JSON

JSON CChar Source # 
Instance details

Defined in Z.Data.JSON

JSON CSChar Source # 
Instance details

Defined in Z.Data.JSON

JSON CUChar Source # 
Instance details

Defined in Z.Data.JSON

JSON CShort Source # 
Instance details

Defined in Z.Data.JSON

JSON CUShort Source # 
Instance details

Defined in Z.Data.JSON

JSON CInt Source # 
Instance details

Defined in Z.Data.JSON

JSON CUInt Source # 
Instance details

Defined in Z.Data.JSON

JSON CLong Source # 
Instance details

Defined in Z.Data.JSON

JSON CULong Source # 
Instance details

Defined in Z.Data.JSON

JSON CLLong Source # 
Instance details

Defined in Z.Data.JSON

JSON CULLong Source # 
Instance details

Defined in Z.Data.JSON

JSON CBool Source # 
Instance details

Defined in Z.Data.JSON

JSON CFloat Source # 
Instance details

Defined in Z.Data.JSON

JSON CDouble Source # 
Instance details

Defined in Z.Data.JSON

JSON CPtrdiff Source # 
Instance details

Defined in Z.Data.JSON

JSON CSize Source # 
Instance details

Defined in Z.Data.JSON

JSON CWchar Source # 
Instance details

Defined in Z.Data.JSON

JSON CSigAtomic Source # 
Instance details

Defined in Z.Data.JSON

JSON CClock Source # 
Instance details

Defined in Z.Data.JSON

JSON CTime Source # 
Instance details

Defined in Z.Data.JSON

JSON CUSeconds Source # 
Instance details

Defined in Z.Data.JSON

JSON CSUSeconds Source # 
Instance details

Defined in Z.Data.JSON

JSON CIntPtr Source # 
Instance details

Defined in Z.Data.JSON

JSON CUIntPtr Source # 
Instance details

Defined in Z.Data.JSON

JSON CIntMax Source # 
Instance details

Defined in Z.Data.JSON

JSON CUIntMax Source # 
Instance details

Defined in Z.Data.JSON

JSON IntSet Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON ByteArray Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Scientific Source #

Note this instance doesn't reject large input

Instance details

Defined in Z.Data.JSON.Base

JSON ZonedTime Source #
YYYY-MM-DDTHH:MM:SS.SSSZ
Instance details

Defined in Z.Data.JSON

JSON LocalTime Source #
YYYY-MM-DDTHH:MM:SS.SSSZ
Instance details

Defined in Z.Data.JSON

JSON TimeOfDay Source #
HH:MM:SS.SSS
Instance details

Defined in Z.Data.JSON

JSON CalendarDiffTime Source # 
Instance details

Defined in Z.Data.JSON

JSON UTCTime Source #
YYYY-MM-DDTHH:MM:SS.SSSZ
Instance details

Defined in Z.Data.JSON

JSON SystemTime Source #

{"seconds": SSS, "nanoseconds": NNN}.

Instance details

Defined in Z.Data.JSON

JSON NominalDiffTime Source #

This instance includes a bounds check to prevent maliciously large inputs to fill up the memory of the target system. You can newtype NominalDiffTime and provide your own instance using withScientific if you want to allow larger inputs.

Instance details

Defined in Z.Data.JSON

JSON DiffTime Source #

This instance includes a bounds check to prevent maliciously large inputs to fill up the memory of the target system. You can newtype DiffTime and provide your own instance using withScientific if you want to allow larger inputs.

Instance details

Defined in Z.Data.JSON

JSON DayOfWeek Source # 
Instance details

Defined in Z.Data.JSON

JSON Day Source #
YYYY-MM-DD
Instance details

Defined in Z.Data.JSON

JSON CalendarDiffDays Source # 
Instance details

Defined in Z.Data.JSON

JSON Bytes Source #

This is an INCOHERENT instance, encode binary data with base64 encoding.

Instance details

Defined in Z.Data.JSON.Base

JSON Text Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON FlatIntSet Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON Value Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON HexBytes Source # 
Instance details

Defined in Z.Data.Vector.Hex

JSON CBytes Source #

JSON instances check if CBytes is properly UTF8 encoded, if it is, decode/encode it as Text, otherwise as an object with a base64 field.

> encodeText ("hello" :: CBytes)
""hello""
> encodeText ("hello\NUL" :: CBytes)     -- \NUL is encoded as C0 80, which is illegal UTF8
"{"base64":"aGVsbG/AgA=="}"
Instance details

Defined in Z.Data.CBytes

JSON [Char] Source #

This is an INCOHERENT instance, to provide JSON text encoding behaviour.

Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON [a] Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter [a] Source #

toValue :: [a] -> Value Source #

encodeJSON :: [a] -> Builder () Source #

JSON a => JSON (Maybe a) Source # 
Instance details

Defined in Z.Data.JSON.Base

(JSON a, Integral a) => JSON (Ratio a) Source #

This instance includes a bounds check to prevent maliciously large inputs to fill up the memory of the target system. You can newtype Ratio and provide your own instance using withScientific if you want to allow larger inputs.

Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (Min a) Source # 
Instance details

Defined in Z.Data.JSON

JSON a => JSON (Max a) Source # 
Instance details

Defined in Z.Data.JSON

JSON a => JSON (First a) Source # 
Instance details

Defined in Z.Data.JSON

JSON a => JSON (Last a) Source # 
Instance details

Defined in Z.Data.JSON

JSON a => JSON (WrappedMonoid a) Source # 
Instance details

Defined in Z.Data.JSON

JSON a => JSON (Identity a) Source # 
Instance details

Defined in Z.Data.JSON

JSON a => JSON (First a) Source # 
Instance details

Defined in Z.Data.JSON

JSON a => JSON (Last a) Source # 
Instance details

Defined in Z.Data.JSON

JSON a => JSON (Dual a) Source # 
Instance details

Defined in Z.Data.JSON

JSON a => JSON (NonEmpty a) Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (IntMap a) Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (Tree a) Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (Seq a) Source # 
Instance details

Defined in Z.Data.JSON.Base

(Ord a, JSON a) => JSON (Set a) Source # 
Instance details

Defined in Z.Data.JSON.Base

(Prim a, JSON a) => JSON (PrimArray a) Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (SmallArray a) Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (Array a) Source # 
Instance details

Defined in Z.Data.JSON.Base

(Eq a, Hashable a, JSON a) => JSON (HashSet a) Source # 
Instance details

Defined in Z.Data.JSON.Base

(Prim a, JSON a) => JSON (PrimVector a) Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (Vector a) Source # 
Instance details

Defined in Z.Data.JSON.Base

(Ord a, JSON a) => JSON (FlatSet a) Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (FlatIntMap a) Source # 
Instance details

Defined in Z.Data.JSON.Base

(JSON a, JSON b) => JSON (Either a b) Source # 
Instance details

Defined in Z.Data.JSON

(JSON a, JSON b) => JSON (a, b) Source # 
Instance details

Defined in Z.Data.JSON

Methods

fromValue :: Value -> Converter (a, b) Source #

toValue :: (a, b) -> Value Source #

encodeJSON :: (a, b) -> Builder () Source #

HasResolution a => JSON (Fixed a) Source #

This instance includes a bounds check to prevent maliciously large inputs to fill up the memory of the target system. You can newtype Fixed and provide your own instance using withScientific if you want to allow larger inputs.

Instance details

Defined in Z.Data.JSON.Base

JSON (Proxy a) Source #

Use Null as Proxy a

Instance details

Defined in Z.Data.JSON

JSON a => JSON (Map Text a) Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (HashMap Text a) Source #

default instance prefer later key

Instance details

Defined in Z.Data.JSON.Base

(PrimUnlifted a, JSON a) => JSON (UnliftedArray a) Source # 
Instance details

Defined in Z.Data.JSON.Base

JSON a => JSON (FlatMap Text a) Source #

default instance prefer later key

Instance details

Defined in Z.Data.JSON.Base

(JSON a, JSON b, JSON c) => JSON (a, b, c) Source # 
Instance details

Defined in Z.Data.JSON

Methods

fromValue :: Value -> Converter (a, b, c) Source #

toValue :: (a, b, c) -> Value Source #

encodeJSON :: (a, b, c) -> Builder () Source #

JSON a => JSON (Const a b) Source # 
Instance details

Defined in Z.Data.JSON

JSON b => JSON (Tagged a b) Source # 
Instance details

Defined in Z.Data.JSON

(JSON a, JSON b, JSON c, JSON d) => JSON (a, b, c, d) Source # 
Instance details

Defined in Z.Data.JSON

Methods

fromValue :: Value -> Converter (a, b, c, d) Source #

toValue :: (a, b, c, d) -> Value Source #

encodeJSON :: (a, b, c, d) -> Builder () Source #

(JSON (f a), JSON (g a)) => JSON (Product f g a) Source # 
Instance details

Defined in Z.Data.JSON

(JSON (f a), JSON (g a), JSON a) => JSON (Sum f g a) Source # 
Instance details

Defined in Z.Data.JSON

Methods

fromValue :: Value -> Converter (Sum f g a) Source #

toValue :: Sum f g a -> Value Source #

encodeJSON :: Sum f g a -> Builder () Source #

(JSON a, JSON b, JSON c, JSON d, JSON e) => JSON (a, b, c, d, e) Source # 
Instance details

Defined in Z.Data.JSON

Methods

fromValue :: Value -> Converter (a, b, c, d, e) Source #

toValue :: (a, b, c, d, e) -> Value Source #

encodeJSON :: (a, b, c, d, e) -> Builder () Source #

JSON (f (g a)) => JSON (Compose f g a) Source # 
Instance details

Defined in Z.Data.JSON

(JSON a, JSON b, JSON c, JSON d, JSON e, JSON f) => JSON (a, b, c, d, e, f) Source # 
Instance details

Defined in Z.Data.JSON

Methods

fromValue :: Value -> Converter (a, b, c, d, e, f) Source #

toValue :: (a, b, c, d, e, f) -> Value Source #

encodeJSON :: (a, b, c, d, e, f) -> Builder () Source #

(JSON a, JSON b, JSON c, JSON d, JSON e, JSON f, JSON g) => JSON (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Z.Data.JSON

Methods

fromValue :: Value -> Converter (a, b, c, d, e, f, g) Source #

toValue :: (a, b, c, d, e, f, g) -> Value Source #

encodeJSON :: (a, b, c, d, e, f, g) -> Builder () Source #

data Value Source #

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.

Instances

Instances details
Eq Value Source # 
Instance details

Defined in Z.Data.JSON.Value

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Ord Value Source # 
Instance details

Defined in Z.Data.JSON.Value

Methods

compare :: Value -> Value -> Ordering #

(<) :: Value -> Value -> Bool #

(<=) :: Value -> Value -> Bool #

(>) :: Value -> Value -> Bool #

(>=) :: Value -> Value -> Bool #

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

Show Value Source # 
Instance details

Defined in Z.Data.JSON.Value

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Generic Value Source # 
Instance details

Defined in Z.Data.JSON.Value

Associated Types

type Rep Value :: Type -> Type #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

Arbitrary Value Source # 
Instance details

Defined in Z.Data.JSON.Value

Methods

arbitrary :: Gen Value #

shrink :: Value -> [Value] #

NFData Value Source # 
Instance details

Defined in Z.Data.JSON.Value

Methods

rnf :: Value -> () #

Print Value Source # 
Instance details

Defined in Z.Data.JSON.Value

Methods

toUTF8BuilderP :: Int -> Value -> Builder () Source #

JSON Value Source # 
Instance details

Defined in Z.Data.JSON.Base

type Rep Value Source # 
Instance details

Defined in Z.Data.JSON.Value

defaultSettings :: Settings Source #

Settings T.pack T.pack False

data Settings Source #

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.

Constructors

Settings 

Fields

Encode & Decode

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.

encodeText :: JSON a => a -> Text Source #

Text version encode.

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":"&lt;a href=&quot;http:/twitter.com&quot;&gt;web&lt;/a&gt;"
        }
    ],
    "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

gToValue :: GToValue f => Settings -> f a -> Value Source #

gFromValue :: GFromValue f => Settings -> Value -> Converter (f a) Source #

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.

newtype Converter a Source #

Converter provides a monadic interface to convert protocol IR (e.g.Value) to Haskell ADT.

Constructors

Converter 

Fields

Instances

Instances details
Monad Converter Source # 
Instance details

Defined in Z.Data.JSON.Converter

Methods

(>>=) :: Converter a -> (a -> Converter b) -> Converter b #

(>>) :: Converter a -> Converter b -> Converter b #

return :: a -> Converter a #

Functor Converter Source # 
Instance details

Defined in Z.Data.JSON.Converter

Methods

fmap :: (a -> b) -> Converter a -> Converter b #

(<$) :: a -> Converter b -> Converter a #

MonadFail Converter Source # 
Instance details

Defined in Z.Data.JSON.Converter

Methods

fail :: String -> Converter a #

Applicative Converter Source # 
Instance details

Defined in Z.Data.JSON.Converter

Methods

pure :: a -> Converter a #

(<*>) :: Converter (a -> b) -> Converter a -> Converter b #

liftA2 :: (a -> b -> c) -> Converter a -> Converter b -> Converter c #

(*>) :: Converter a -> Converter b -> Converter b #

(<*) :: Converter a -> Converter b -> Converter a #

Alternative Converter Source # 
Instance details

Defined in Z.Data.JSON.Converter

Methods

empty :: Converter a #

(<|>) :: Converter a -> Converter a -> Converter a #

some :: Converter a -> Converter [a] #

many :: Converter a -> Converter [a] #

MonadPlus Converter Source # 
Instance details

Defined in Z.Data.JSON.Converter

Methods

mzero :: Converter a #

mplus :: Converter a -> Converter a -> Converter a #

fail' :: Text -> Converter a Source #

Text version of fail.

(<?>) :: 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

Instances details
Eq PathElement Source # 
Instance details

Defined in Z.Data.JSON.Converter

Ord PathElement Source # 
Instance details

Defined in Z.Data.JSON.Converter

Show PathElement Source # 
Instance details

Defined in Z.Data.JSON.Converter

Generic PathElement Source # 
Instance details

Defined in Z.Data.JSON.Converter

Associated Types

type Rep PathElement :: Type -> Type #

NFData PathElement Source # 
Instance details

Defined in Z.Data.JSON.Converter

Methods

rnf :: PathElement -> () #

type Rep PathElement Source # 
Instance details

Defined in Z.Data.JSON.Converter

type Rep PathElement = D1 ('MetaData "PathElement" "Z.Data.JSON.Converter" "Z-Data-0.9.0.0-9CZLncR3XfBEnMnIuwgUs7" 'False) (C1 ('MetaCons "Key" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "Index" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'SourceUnpack 'SourceStrict 'DecidedStrict) (Rec0 Int)) :+: C1 ('MetaCons "Embedded" 'PrefixI 'False) (U1 :: Type -> Type)))

data ConvertError Source #

Error info with (JSON) Path info.

Constructors

ConvertError 

Fields

Instances

Instances details
Eq ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Converter

Ord ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Converter

Show ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Converter

Generic ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Converter

Associated Types

type Rep ConvertError :: Type -> Type #

NFData ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Converter

Methods

rnf :: ConvertError -> () #

Print ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Converter

type Rep ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Converter

type Rep ConvertError = D1 ('MetaData "ConvertError" "Z.Data.JSON.Converter" "Z-Data-0.9.0.0-9CZLncR3XfBEnMnIuwgUs7" 'False) (C1 ('MetaCons "ConvertError" 'PrefixI 'True) (S1 ('MetaSel ('Just "errPath") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [PathElement]) :*: S1 ('MetaSel ('Just "errMsg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))

typeMismatch Source #

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 value applies f 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 value applies f 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 as NaN

withBoundedIntegral :: (Bounded a, Integral a) => Text -> (a -> Converter r) -> Value -> Converter r Source #

withBoundedScientific name f value applies f 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.

withEmbeddedJSON Source #

Arguments

:: Text

data type name

-> (Value -> Converter a)

a inner converter which will get the converted Value.

-> 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.

(.:!) :: 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 fail if the value cannot be converted to the desired type.

This differs from .:? by attempting to convert Null the same as any other JSON value, instead of interpreting it as Nothing.

convertField Source #

Arguments

:: (Value -> Converter a)

the field converter (value part of a key value pair)

-> FlatMap Text Value 
-> Text 
-> Converter a 

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.

object :: [(Text, Value)] -> Value Source #

Alias for Object . pack.

(.!) :: JSON v => Text -> v -> KVItem infixr 8 Source #

Connect key and value to a KVItem using colon, key will be escaped.

object' :: KVItem -> Builder () Source #

Add curly for comma connected KVItems.

data KVItem Source #

A newtype for Builder, whose semigroup's instance is to connect two builder with comma.

Instances

Instances details
Semigroup KVItem Source # 
Instance details

Defined in Z.Data.JSON.Base

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"

curly :: Builder () -> Builder () Source #

add {...} to original builder.

square :: Builder () -> Builder () Source #

add [...] to original builder.

commaSepList :: JSON a => [a] -> Builder () Source #

Use , as separator to connect list of builders.

commaSepVec :: (JSON a, Vec v a) => v a -> Builder () Source #

Use , as separator to connect a vector of builders.