Z-Data-0.1.1.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 FromValue, ToValue and EncodeJSON instance.

Synopsis

Encode & Decode

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.

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

encodeBytes :: EncodeJSON a => a -> Bytes Source #

Directly encode data to JSON bytes.

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

Text version encodeBytes.

encodeTextBuilder :: EncodeJSON a => a -> TextBuilder () Source #

JSON Docs are guaranteed to be valid UTF-8 texts, so we provide this.

Re-export Value type

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.

Constructors

Object !(Vector (Text, Value)) 
Array !(Vector Value) 
String !Text 
Number !Scientific 
Bool !Bool 
Null 

Instances

Instances details
Eq Value Source # 
Instance details

Defined in Z.Data.JSON.Value

Methods

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

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

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 #

NFData Value Source # 
Instance details

Defined in Z.Data.JSON.Value

Methods

rnf :: Value -> () #

Arbitrary Value Source # 
Instance details

Defined in Z.Data.JSON.Value

Methods

arbitrary :: Gen Value

shrink :: Value -> [Value]

ToText Value Source # 
Instance details

Defined in Z.Data.JSON.Value

FromValue Value Source # 
Instance details

Defined in Z.Data.JSON.Base

EncodeJSON Value Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Value -> Builder () Source #

ToValue Value Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Value -> Value Source #

type Rep Value Source # 
Instance details

Defined in Z.Data.JSON.Value

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.

convert' :: FromValue a => Value -> Either ConvertError a Source #

Run a Converter with input value.

newtype Converter a Source #

Converter for convert result from JSON Value.

This is intended to be named differently from Parser to clear confusions.

Constructors

Converter 

Fields

Instances

Instances details
Monad Converter Source # 
Instance details

Defined in Z.Data.JSON.Base

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

Methods

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

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

MonadFail Converter Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

fail :: String -> Converter a #

Applicative Converter Source # 
Instance details

Defined in Z.Data.JSON.Base

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

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

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

Ord PathElement Source # 
Instance details

Defined in Z.Data.JSON.Base

Show PathElement Source # 
Instance details

Defined in Z.Data.JSON.Base

Generic PathElement Source # 
Instance details

Defined in Z.Data.JSON.Base

Associated Types

type Rep PathElement :: Type -> Type #

NFData PathElement Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

rnf :: PathElement -> () #

type Rep PathElement Source # 
Instance details

Defined in Z.Data.JSON.Base

type Rep PathElement = D1 ('MetaData "PathElement" "Z.Data.JSON.Base" "Z-Data-0.1.1.0-inplace" '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 #

Instances

Instances details
Eq ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Base

Ord ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Base

Show ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Base

Generic ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Base

Associated Types

type Rep ConvertError :: Type -> Type #

NFData ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

rnf :: ConvertError -> () #

type Rep ConvertError Source # 
Instance details

Defined in Z.Data.JSON.Base

type Rep ConvertError = D1 ('MetaData "ConvertError" "Z.Data.JSON.Base" "Z-Data-0.1.1.0-inplace" '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.

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

(.:!) :: 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 empty 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.

FromValue, ToValue & EncodeJSON

data Settings Source #

Generic encode/decode Settings

There should be no control charactors 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

class ToValue a where Source #

Typeclass for converting to JSON Value.

Minimal complete definition

Nothing

Methods

toValue :: a -> Value Source #

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

Instances

Instances details
ToValue Bool Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Bool -> Value Source #

ToValue Char Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Char -> Value Source #

ToValue Double Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Double -> Value Source #

ToValue Float Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Float -> Value Source #

ToValue Int Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Int -> Value Source #

ToValue Int8 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Int8 -> Value Source #

ToValue Int16 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Int16 -> Value Source #

ToValue Int32 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Int32 -> Value Source #

ToValue Int64 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Int64 -> Value Source #

ToValue Integer Source # 
Instance details

Defined in Z.Data.JSON.Base

ToValue Natural Source # 
Instance details

Defined in Z.Data.JSON.Base

ToValue Ordering Source # 
Instance details

Defined in Z.Data.JSON.Base

ToValue Word Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Word -> Value Source #

ToValue Word8 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Word8 -> Value Source #

ToValue Word16 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Word16 -> Value Source #

ToValue Word32 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Word32 -> Value Source #

ToValue Word64 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Word64 -> Value Source #

ToValue () Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: () -> Value Source #

ToValue Version Source # 
Instance details

Defined in Z.Data.JSON.Base

ToValue Text Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Text -> Value Source #

ToValue Scientific Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Scientific -> Value Source #

ToValue Str Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Str -> Value Source #

ToValue FlatIntSet Source # 
Instance details

Defined in Z.Data.JSON.Base

ToValue Value Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Value -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: [a] -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: Maybe a -> Value Source #

(ToValue a, Integral a) => ToValue (Ratio a) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Ratio a -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: Min a -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: Max a -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: First a -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: Last a -> Value Source #

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

Methods

toValue :: Identity a -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: First a -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: Last a -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: Dual a -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: NonEmpty a -> Value Source #

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

Methods

toValue :: Vector a -> Value Source #

ToValue a => ToValue (FlatSet a) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: FlatSet a -> Value Source #

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

Defined in Z.Data.JSON.Base

ToValue a => ToValue (HashSet a) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: HashSet a -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: Either a b -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

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

HasResolution a => ToValue (Fixed a) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Fixed a -> Value Source #

ToValue (Proxy a) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: Proxy a -> Value Source #

ToValue a => ToValue (FlatMap Text a) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: FlatMap Text a -> Value Source #

ToValue a => ToValue (HashMap Text a) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

toValue :: HashMap Text a -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

toValue :: Const a b -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

toValue :: Tagged a b -> Value Source #

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

class GToValue f where Source #

Methods

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

Instances

Instances details
ToValue a => GToValue (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gToValue :: Settings -> K1 i a a0 -> Value Source #

GConstrToValue f => GToValue (D1 c f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gToValue :: Settings -> D1 c f a -> Value Source #

GToValue f => GToValue (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gToValue :: Settings -> S1 ('MetaSel 'Nothing u ss ds) f a -> Value Source #

(GToValue f, Selector ('MetaSel ('Just l) u ss ds)) => GToValue (S1 ('MetaSel ('Just l) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gToValue :: Settings -> S1 ('MetaSel ('Just l) u ss ds) f a -> Value Source #

class FromValue a where Source #

Minimal complete definition

Nothing

Methods

fromValue :: Value -> Converter a Source #

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

Instances

Instances details
FromValue Bool Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Char Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Double Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Float Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Int Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Int8 Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Int16 Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Int32 Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Int64 Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue 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 Scientific and provide your own instance using withScientific if you want to allow larger inputs.

Instance details

Defined in Z.Data.JSON.Base

FromValue Natural Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Ordering Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Word Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Word8 Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Word16 Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Word32 Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Word64 Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue () Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter () Source #

FromValue Version Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Text Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Scientific Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter Scientific Source #

FromValue Str Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue FlatIntSet Source # 
Instance details

Defined in Z.Data.JSON.Base

FromValue Value Source # 
Instance details

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

(FromValue a, Integral a) => FromValue (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

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

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Min a) Source #

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

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (Max a) Source #

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (HashSet a) Source #

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

HasResolution a => FromValue (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

FromValue (Proxy a) Source #

Use Null as Proxy a

Instance details

Defined in Z.Data.JSON.Base

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

default instance prefer later key

Instance details

Defined in Z.Data.JSON.Base

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

default instance prefer later key

Instance details

Defined in Z.Data.JSON.Base

Methods

fromValue :: Value -> Converter (HashMap Text a) Source #

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

class GFromValue f where Source #

Methods

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

Instances

Instances details
FromValue a => GFromValue (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gFromValue :: Settings -> Value -> Converter (K1 i a a0) Source #

GConstrFromValue f => GFromValue (D1 c f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gFromValue :: Settings -> Value -> Converter (D1 c f a) Source #

GFromValue f => GFromValue (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gFromValue :: Settings -> Value -> Converter (S1 ('MetaSel 'Nothing u ss ds) f a) Source #

(GFromValue f, Selector ('MetaSel ('Just l) u ss ds)) => GFromValue (S1 ('MetaSel ('Just l) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gFromValue :: Settings -> Value -> Converter (S1 ('MetaSel ('Just l) u ss ds) f a) Source #

class EncodeJSON a where Source #

Minimal complete definition

Nothing

Methods

encodeJSON :: a -> Builder () Source #

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

Instances

Instances details
EncodeJSON Bool Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Bool -> Builder () Source #

EncodeJSON Char Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Char -> Builder () Source #

EncodeJSON Double Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Double -> Builder () Source #

EncodeJSON Float Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Float -> Builder () Source #

EncodeJSON Int Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Int -> Builder () Source #

EncodeJSON Int8 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Int8 -> Builder () Source #

EncodeJSON Int16 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Int16 -> Builder () Source #

EncodeJSON Int32 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Int32 -> Builder () Source #

EncodeJSON Int64 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Int64 -> Builder () Source #

EncodeJSON Integer Source # 
Instance details

Defined in Z.Data.JSON.Base

EncodeJSON Natural Source # 
Instance details

Defined in Z.Data.JSON.Base

EncodeJSON Ordering Source # 
Instance details

Defined in Z.Data.JSON.Base

EncodeJSON Word Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Word -> Builder () Source #

EncodeJSON Word8 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Word8 -> Builder () Source #

EncodeJSON Word16 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Word16 -> Builder () Source #

EncodeJSON Word32 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Word32 -> Builder () Source #

EncodeJSON Word64 Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Word64 -> Builder () Source #

EncodeJSON () Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

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

EncodeJSON Version Source # 
Instance details

Defined in Z.Data.JSON.Base

EncodeJSON Text Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Text -> Builder () Source #

EncodeJSON Scientific Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Scientific -> Builder () Source #

EncodeJSON Str Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Str -> Builder () Source #

EncodeJSON FlatIntSet Source # 
Instance details

Defined in Z.Data.JSON.Base

EncodeJSON Value Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Value -> Builder () Source #

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Maybe a -> Builder () Source #

(EncodeJSON a, Integral a) => EncodeJSON (Ratio a) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Ratio a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Min a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Max a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: First a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Last a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Identity a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: First a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Last a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Dual a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: NonEmpty a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

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

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Vector a -> Builder () Source #

EncodeJSON a => EncodeJSON (FlatSet a) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: FlatSet a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

EncodeJSON a => EncodeJSON (HashSet a) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: HashSet a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

HasResolution a => EncodeJSON (Fixed a) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Fixed a -> Builder () Source #

EncodeJSON (Proxy a) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: Proxy a -> Builder () Source #

EncodeJSON a => EncodeJSON (FlatMap Text a) Source # 
Instance details

Defined in Z.Data.JSON.Base

EncodeJSON a => EncodeJSON (HashMap Text a) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

encodeJSON :: HashMap Text a -> Builder () Source #

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

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

Defined in Z.Data.JSON.Base

Methods

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

class GEncodeJSON f where Source #

Methods

gEncodeJSON :: Settings -> f a -> Builder () Source #

Instances

Instances details
EncodeJSON a => GEncodeJSON (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gEncodeJSON :: Settings -> K1 i a a0 -> Builder () Source #

(GEncodeJSON a, GEncodeJSON b) => GEncodeJSON (a :*: b) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gEncodeJSON :: Settings -> (a :*: b) a0 -> Builder () Source #

GConstrEncodeJSON f => GEncodeJSON (D1 c f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gEncodeJSON :: Settings -> D1 c f a -> Builder () Source #

GEncodeJSON f => GEncodeJSON (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gEncodeJSON :: Settings -> S1 ('MetaSel 'Nothing u ss ds) f a -> Builder () Source #

(GEncodeJSON f, Selector ('MetaSel ('Just l) u ss ds)) => GEncodeJSON (S1 ('MetaSel ('Just l) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gEncodeJSON :: Settings -> S1 ('MetaSel ('Just l) u ss ds) f a -> Builder () Source #

Helper classes for generics

type family Field f where ... Source #

Equations

Field (a :*: b) = Field a 
Field (S1 (MetaSel Nothing u ss ds) f) = Value 
Field (S1 (MetaSel (Just l) u ss ds) f) = (Text, Value) 

class GWriteFields f where Source #

Methods

gWriteFields :: Settings -> SmallMutableArray s (Field f) -> Int -> f a -> ST s () Source #

Instances

Instances details
(ProductSize a, GWriteFields a, GWriteFields b, Field a ~ Field b) => GWriteFields (a :*: b) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gWriteFields :: Settings -> SmallMutableArray s (Field (a :*: b)) -> Int -> (a :*: b) a0 -> ST s () Source #

GToValue f => GWriteFields (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gWriteFields :: Settings -> SmallMutableArray s (Field (S1 ('MetaSel 'Nothing u ss ds) f)) -> Int -> S1 ('MetaSel 'Nothing u ss ds) f a -> ST s () Source #

(GToValue f, Selector ('MetaSel ('Just l) u ss ds)) => GWriteFields (S1 ('MetaSel ('Just l) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gWriteFields :: Settings -> SmallMutableArray s (Field (S1 ('MetaSel ('Just l) u ss ds) f)) -> Int -> S1 ('MetaSel ('Just l) u ss ds) f a -> ST s () Source #

class GMergeFields f where Source #

Instances

Instances details
GMergeFields a => GMergeFields (a :*: b) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gMergeFields :: Proxy# (a :*: b) -> SmallMutableArray s (Field (a :*: b)) -> ST s Value Source #

GMergeFields (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gMergeFields :: Proxy# (S1 ('MetaSel 'Nothing u ss ds) f) -> SmallMutableArray s (Field (S1 ('MetaSel 'Nothing u ss ds) f)) -> ST s Value Source #

GMergeFields (S1 ('MetaSel ('Just l) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gMergeFields :: Proxy# (S1 ('MetaSel ('Just l) u ss ds) f) -> SmallMutableArray s (Field (S1 ('MetaSel ('Just l) u ss ds) f)) -> ST s Value Source #

class GConstrToValue f where Source #

Methods

gConstrToValue :: Bool -> Settings -> f a -> Value Source #

Instances

Instances details
GConstrToValue (V1 :: Type -> Type) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gConstrToValue :: Bool -> Settings -> V1 a -> Value Source #

(GConstrToValue f, GConstrToValue g) => GConstrToValue (f :+: g) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gConstrToValue :: Bool -> Settings -> (f :+: g) a -> Value Source #

(ProductSize (a :*: b), GWriteFields (a :*: b), GMergeFields (a :*: b), Constructor c) => GConstrToValue (C1 c (a :*: b)) Source #

Constructor with multiple payloads

Instance details

Defined in Z.Data.JSON.Base

Methods

gConstrToValue :: Bool -> Settings -> C1 c (a :*: b) a0 -> Value Source #

(Constructor c, GToValue (S1 sc f)) => GConstrToValue (C1 c (S1 sc f)) Source #

Constructor with a single payload

Instance details

Defined in Z.Data.JSON.Base

Methods

gConstrToValue :: Bool -> Settings -> C1 c (S1 sc f) a -> Value Source #

Constructor c => GConstrToValue (C1 c (U1 :: Type -> Type)) Source #

Constructor without payload, convert to String

Instance details

Defined in Z.Data.JSON.Base

Methods

gConstrToValue :: Bool -> Settings -> C1 c U1 a -> Value Source #

type family LookupTable f where ... Source #

Equations

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 #

Methods

gFromFields :: Settings -> LookupTable f -> Int -> Converter (f a) Source #

Instances

Instances details
(ProductSize a, GFromFields a, GFromFields b, LookupTable a ~ LookupTable b) => GFromFields (a :*: b) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gFromFields :: Settings -> LookupTable (a :*: b) -> Int -> Converter ((a :*: b) a0) Source #

GFromValue f => GFromFields (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gFromFields :: Settings -> LookupTable (S1 ('MetaSel 'Nothing u ss ds) f) -> Int -> Converter (S1 ('MetaSel 'Nothing u ss ds) f a) Source #

(GFromValue f, Selector ('MetaSel ('Just l) u ss ds)) => GFromFields (S1 ('MetaSel ('Just l) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gFromFields :: Settings -> LookupTable (S1 ('MetaSel ('Just l) u ss ds) f) -> Int -> Converter (S1 ('MetaSel ('Just l) u ss ds) f a) Source #

class GBuildLookup f where Source #

Instances

Instances details
(GBuildLookup a, GBuildLookup b) => GBuildLookup (a :*: b) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gBuildLookup :: Proxy# (a :*: b) -> Int -> Text -> Value -> Converter (LookupTable (a :*: b)) Source #

GBuildLookup (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gBuildLookup :: Proxy# (S1 ('MetaSel 'Nothing u ss ds) f) -> Int -> Text -> Value -> Converter (LookupTable (S1 ('MetaSel 'Nothing u ss ds) f)) Source #

GBuildLookup (S1 ('MetaSel ('Just l) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gBuildLookup :: Proxy# (S1 ('MetaSel ('Just l) u ss ds) f) -> Int -> Text -> Value -> Converter (LookupTable (S1 ('MetaSel ('Just l) u ss ds) f)) Source #

class GConstrFromValue f where Source #

Instances

Instances details
GConstrFromValue (V1 :: Type -> Type) Source # 
Instance details

Defined in Z.Data.JSON.Base

(GConstrFromValue f, GConstrFromValue g) => GConstrFromValue (f :+: g) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gConstrFromValue :: Bool -> Settings -> Value -> Converter ((f :+: g) a) Source #

(ProductSize (a :*: b), GFromFields (a :*: b), GBuildLookup (a :*: b), Constructor c) => GConstrFromValue (C1 c (a :*: b)) Source #

Constructor with multiple payloads

Instance details

Defined in Z.Data.JSON.Base

Methods

gConstrFromValue :: Bool -> Settings -> Value -> Converter (C1 c (a :*: b) a0) Source #

(Constructor c, GFromValue (S1 sc f)) => GConstrFromValue (C1 c (S1 sc f)) Source #

Constructor with a single payload

Instance details

Defined in Z.Data.JSON.Base

Methods

gConstrFromValue :: Bool -> Settings -> Value -> Converter (C1 c (S1 sc f) a) Source #

Constructor c => GConstrFromValue (C1 c (U1 :: Type -> Type)) Source #

Constructor without payload, convert to String

Instance details

Defined in Z.Data.JSON.Base

class GAddPunctuation (f :: * -> *) where Source #

Methods

gAddPunctuation :: Proxy# f -> Builder () -> Builder () Source #

Instances

Instances details
GAddPunctuation a => GAddPunctuation (a :*: b) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gAddPunctuation :: Proxy# (a :*: b) -> Builder () -> Builder () Source #

GAddPunctuation (S1 ('MetaSel ('Nothing :: Maybe Symbol) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gAddPunctuation :: Proxy# (S1 ('MetaSel 'Nothing u ss ds) f) -> Builder () -> Builder () Source #

GAddPunctuation (S1 ('MetaSel ('Just l) u ss ds) f) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gAddPunctuation :: Proxy# (S1 ('MetaSel ('Just l) u ss ds) f) -> Builder () -> Builder () Source #

class GConstrEncodeJSON f where Source #

Methods

gConstrEncodeJSON :: Bool -> Settings -> f a -> Builder () Source #

Instances

Instances details
GConstrEncodeJSON (V1 :: Type -> Type) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gConstrEncodeJSON :: Bool -> Settings -> V1 a -> Builder () Source #

(GConstrEncodeJSON f, GConstrEncodeJSON g) => GConstrEncodeJSON (f :+: g) Source # 
Instance details

Defined in Z.Data.JSON.Base

Methods

gConstrEncodeJSON :: Bool -> Settings -> (f :+: g) a -> Builder () Source #

(GEncodeJSON (a :*: b), GAddPunctuation (a :*: b), Constructor c) => GConstrEncodeJSON (C1 c (a :*: b)) Source #

Constructor with multiple payloads

Instance details

Defined in Z.Data.JSON.Base

Methods

gConstrEncodeJSON :: Bool -> Settings -> C1 c (a :*: b) a0 -> Builder () Source #

(Constructor c, GEncodeJSON (S1 sc f)) => GConstrEncodeJSON (C1 c (S1 sc f)) Source #

Constructor with a single payload

Instance details

Defined in Z.Data.JSON.Base

Methods

gConstrEncodeJSON :: Bool -> Settings -> C1 c (S1 sc f) a -> Builder () Source #

Constructor c => GConstrEncodeJSON (C1 c (U1 :: Type -> Type)) Source #

Constructor without payload, convert to String

Instance details

Defined in Z.Data.JSON.Base

Methods

gConstrEncodeJSON :: Bool -> Settings -> C1 c U1 a -> Builder () Source #