aeson-1.0.1.0: Fast JSON parsing and encoding

Copyright(c) 2011-2016 Bryan O'Sullivan (c) 2011 MailRank, Inc.
LicenseBSD3
MaintainerBryan O'Sullivan <bos@serpentine.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Data.Aeson

Contents

Description

Types and functions for working efficiently with JSON data.

(A note on naming: in Greek mythology, Aeson was the father of Jason.)

Synopsis

How to use this library

This section contains basic information on the different ways to work with data using this library. These range from simple but inflexible, to complex but flexible.

The most common way to use the library is to define a data type, corresponding to some JSON data you want to work with, and then write either a FromJSON instance, a to ToJSON instance, or both for that type.

For example, given this JSON data:

{ "name": "Joe", "age": 12 }

we create a matching data type:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

data Person = Person {
      name :: Text
    , age  :: Int
    } deriving (Generic, Show)

The LANGUAGE pragma and Generic instance let us write empty FromJSON and ToJSON instances for which the compiler will generate sensible default implementations.

instance ToJSON Person where
    -- No need to provide a toJSON implementation.

    -- For efficiency, we write a simple toEncoding implementation, as
    -- the default version uses toJSON.
    toEncoding = genericToEncoding defaultOptions

instance FromJSON Person
    -- No need to provide a parseJSON implementation.

We can now encode a value like so:

>>> encode (Person {name = "Joe", age = 12})
"{\"name\":\"Joe\",\"age\":12}"

Writing instances by hand

When necessary, we can write ToJSON and FromJSON instances by hand. This is valuable when the JSON-on-the-wire and Haskell data are different or otherwise need some more carefully managed translation. Let's revisit our JSON data:

{ "name": "Joe", "age": 12 }

We once again create a matching data type, without bothering to add a Generic instance this time:

data Person = Person {
      name :: Text
    , age  :: Int
    } deriving Show

To decode data, we need to define a FromJSON instance:

{-# LANGUAGE OverloadedStrings #-}

instance FromJSON Person where
    parseJSON (Object v) = Person <$>
                           v .: "name" <*>
                           v .: "age"
    -- A non-Object value is of the wrong type, so fail.
    parseJSON _          = empty

We can now parse the JSON data like so:

>>> decode "{\"name\":\"Joe\",\"age\":12}" :: Maybe Person
Just (Person {name = "Joe", age = 12})

To encode data, we need to define a ToJSON instance. Let's begin with an instance written entirely by hand.

instance ToJSON Person where
    -- this generates a Value
    toJSON (Person name age) =
        object ["name" .= name, "age" .= age]

    -- this encodes directly to a bytestring Builder
    toEncoding (Person name age) =
        pairs ("name" .= name <> "age" .= age)

We can now encode a value like so:

>>> encode (Person {name = "Joe", age = 12})
"{\"name\":\"Joe\",\"age\":12}"

There are predefined FromJSON and ToJSON instances for many types. Here's an example using lists and Ints:

>>> decode "[1,2,3]" :: Maybe [Int]
Just [1,2,3]

And here's an example using the Map type to get a map of Ints.

>>> decode "{\"foo\":1,\"bar\":2}" :: Maybe (Map String Int)
Just (fromList [("bar",2),("foo",1)])

Working with the AST

Sometimes you want to work with JSON data directly, without first converting it to a custom data type. This can be useful if you want to e.g. convert JSON data to YAML data, without knowing what the contents of the original JSON data was. The Value type, which is an instance of FromJSON, is used to represent an arbitrary JSON AST (abstract syntax tree). Example usage:

>>> decode "{\"foo\": 123}" :: Maybe Value
Just (Object (fromList [("foo",Number 123)]))
>>> decode "{\"foo\": [\"abc\",\"def\"]}" :: Maybe Value
Just (Object (fromList [("foo",Array (fromList [String "abc",String "def"]))]))

Once you have a Value you can write functions to traverse it and make arbitrary transformations.

Decoding to a Haskell value

We can decode to any instance of FromJSON:

λ> decode "[1,2,3]" :: Maybe [Int]
Just [1,2,3]

Alternatively, there are instances for standard data types, so you can use them directly. For example, use the Map type to get a map of Ints.

λ> import Data.Map
λ> decode "{\"foo\":1,\"bar\":2}" :: Maybe (Map String Int)
Just (fromList [("bar",2),("foo",1)])

Decoding a mixed-type object

The above approach with maps of course will not work for mixed-type objects that don't follow a strict schema, but there are a couple of approaches available for these.

The Object type contains JSON objects:

λ> decode "{\"name\":\"Dave\",\"age\":2}" :: Maybe Object
Just (fromList) [("name",String "Dave"),("age",Number 2)]

You can extract values from it with a parser using parse, parseEither or, in this example, parseMaybe:

λ> do result <- decode "{\"name\":\"Dave\",\"age\":2}"
      flip parseMaybe result $ \obj -> do
        age <- obj .: "age"
        name <- obj .: "name"
        return (name ++ ": " ++ show (age*2))

Just "Dave: 4"

Considering that any type that implements FromJSON can be used here, this is quite a powerful way to parse JSON. See the documentation in FromJSON for how to implement this class for your own data types.

The downside is that you have to write the parser yourself; the upside is that you have complete control over the way the JSON is parsed.

Encoding and decoding

Decoding is a two-step process.

  • When decoding a value, the process is reversed: the bytes are converted to a Value, then the FromJSON class is used to convert to the desired type.

There are two ways to encode a value.

  • Convert to a Value using toJSON, then possibly further encode. This was the only method available in aeson 0.9 and earlier.
  • Directly encode (to what will become a ByteString) using toEncoding. This is much more efficient (about 3x faster, and less memory intensive besides), but is only available in aeson 0.10 and newer.

For convenience, the encode and decode functions combine both steps.

Direct encoding

In older versions of this library, encoding a Haskell value involved converting to an intermediate Value, then encoding that.

A "direct" encoder converts straight from a source Haskell value to a ByteString without constructing an intermediate Value. This approach is faster than toJSON, and allocates less memory. The toEncoding method makes it possible to implement direct encoding with low memory overhead.

To complicate matters, the default implementation of toEncoding uses toJSON. Why? The toEncoding method was added to this library much more recently than toJSON. Using toJSON ensures that packages written against older versions of this library will compile and produce correct output, but they will not see any speedup from direct encoding.

To write a minimal implementation of direct encoding, your type must implement GHC's Generic class, and your code should look like this:

    toEncoding = genericToEncoding defaultOptions

What if you have more elaborate encoding needs? For example, perhaps you need to change the names of object keys, omit parts of a value.

To encode to a JSON "object", use the pairs function.

    toEncoding (Person name age) =
        pairs ("name" .= name <> "age" .= age)

Any container type that implements Foldable can be encoded to a JSON "array" using foldable.

> import Data.Sequence as Seq
> encode (Seq.fromList [1,2,3])
"[1,2,3]"

decode :: FromJSON a => ByteString -> Maybe a Source #

Efficiently deserialize a JSON value from a lazy ByteString. If this fails due to incomplete or invalid input, Nothing is returned.

The input must consist solely of a JSON document, with no trailing data except for whitespace.

This function parses immediately, but defers conversion. See json for details.

decode' :: FromJSON a => ByteString -> Maybe a Source #

Efficiently deserialize a JSON value from a lazy ByteString. If this fails due to incomplete or invalid input, Nothing is returned.

The input must consist solely of a JSON document, with no trailing data except for whitespace.

This function parses and performs conversion immediately. See json' for details.

eitherDecode :: FromJSON a => ByteString -> Either String a Source #

Like decode but returns an error message when decoding fails.

eitherDecode' :: FromJSON a => ByteString -> Either String a Source #

Like decode' but returns an error message when decoding fails.

encode :: ToJSON a => a -> ByteString Source #

Efficiently serialize a JSON value as a lazy ByteString.

This is implemented in terms of the ToJSON class's toEncoding method.

Variants for strict bytestrings

decodeStrict :: FromJSON a => ByteString -> Maybe a Source #

Efficiently deserialize a JSON value from a strict ByteString. If this fails due to incomplete or invalid input, Nothing is returned.

The input must consist solely of a JSON document, with no trailing data except for whitespace.

This function parses immediately, but defers conversion. See json for details.

decodeStrict' :: FromJSON a => ByteString -> Maybe a Source #

Efficiently deserialize a JSON value from a strict ByteString. If this fails due to incomplete or invalid input, Nothing is returned.

The input must consist solely of a JSON document, with no trailing data except for whitespace.

This function parses and performs conversion immediately. See json' for details.

eitherDecodeStrict :: FromJSON a => ByteString -> Either String a Source #

Like decodeStrict but returns an error message when decoding fails.

eitherDecodeStrict' :: FromJSON a => ByteString -> Either String a Source #

Like decodeStrict' but returns an error message when decoding fails.

Core JSON types

data Value Source #

A JSON value represented as a Haskell value.

Instances

Eq Value Source # 

Methods

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

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

Data Value Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value #

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Value) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) #

gmapT :: (forall b. Data b => b -> b) -> Value -> Value #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

Read Value Source # 
Show Value Source # 

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

IsString Value Source # 

Methods

fromString :: String -> Value #

Lift Value Source # 

Methods

lift :: Value -> Q Exp #

NFData Value Source # 

Methods

rnf :: Value -> () #

Hashable Value Source # 

Methods

hashWithSalt :: Int -> Value -> Int #

hash :: Value -> Int #

KeyValue Pair Source # 

Methods

(.=) :: ToJSON v => Text -> v -> Pair Source #

ToJSON Value Source # 
FromJSON Value Source # 

type Encoding = Encoding' Value Source #

Often used synonnym for Encoding'.

fromEncoding :: Encoding' tag -> Builder Source #

Acquire the underlying bytestring builder.

type Array = Vector Value Source #

A JSON "array" (sequence).

type Object = HashMap Text Value Source #

A JSON "object" (key/value map).

Convenience types

newtype DotNetTime Source #

A newtype wrapper for UTCTime that uses the same non-standard serialization format as Microsoft .NET, whose System.DateTime type is by default serialized to JSON as in the following example:

/Date(1302547608878)/

The number represents milliseconds since the Unix epoch.

Constructors

DotNetTime 

Fields

Type conversion

class FromJSON a where Source #

A type that can be converted from JSON, with the possibility of failure.

In many cases, you can get the compiler to generate parsing code for you (see below). To begin, let's cover writing an instance by hand.

There are various reasons a conversion could fail. For example, an Object could be missing a required key, an Array could be of the wrong size, or a value could be of an incompatible type.

The basic ways to signal a failed conversion are as follows:

  • empty and mzero work, but are terse and uninformative
  • fail yields a custom error message
  • typeMismatch produces an informative message for cases when the value encountered is not of the expected type

An example type and instance:

-- Allow ourselves to write Text literals.
{-# LANGUAGE OverloadedStrings #-}

data Coord = Coord { x :: Double, y :: Double }

instance FromJSON Coord where
  parseJSON (Object v) = Coord    <$>
                         v .: "x" <*>
                         v .: "y"

  -- We do not expect a non-Object value here.
  -- We could use mzero to fail, but typeMismatch
  -- gives a much more informative error message.
  parseJSON invalid    = typeMismatch "Coord" invalid

Instead of manually writing your FromJSON instance, there are two options to do it automatically:

  • Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
  • The compiler can provide a default generic implementation for parseJSON.

To use the second, simply add a deriving Generic clause to your datatype and declare a FromJSON instance for your datatype without giving a definition for parseJSON.

For example, the previous example can be simplified to just:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

data Coord = Coord { x :: Double, y :: Double } deriving Generic

instance FromJSON Coord

If DefaultSignatures doesn't give exactly the results you want, you can customize the generic decoding with only a tiny amount of effort, using genericParseJSON with your preferred Options:

instance FromJSON Coord where
    parseJSON = genericParseJSON defaultOptions

Instances

FromJSON Bool Source # 
FromJSON Char Source # 
FromJSON Double Source # 
FromJSON Float Source # 
FromJSON Int Source # 
FromJSON Int8 Source # 
FromJSON Int16 Source # 
FromJSON Int32 Source # 
FromJSON Int64 Source # 
FromJSON Integer Source #

WARNING: Only parse Integers from trusted input since an attacker could easily fill up the memory of the target system by specifying a scientific number with a big exponent like 1e1000000000.

FromJSON Ordering Source # 
FromJSON Word Source # 
FromJSON Word8 Source # 
FromJSON Word16 Source # 
FromJSON Word32 Source # 
FromJSON Word64 Source # 
FromJSON () Source # 
FromJSON Text Source # 
FromJSON Text Source # 
FromJSON Number Source # 
FromJSON Natural Source # 
FromJSON Version Source # 
FromJSON IntSet Source # 
FromJSON Scientific Source # 
FromJSON LocalTime Source # 
FromJSON ZonedTime Source # 
FromJSON TimeOfDay Source # 
FromJSON UTCTime Source # 
FromJSON NominalDiffTime Source #

WARNING: Only parse lengths of time from trusted input since an attacker could easily fill up the memory of the target system by specifying a scientific number with a big exponent like 1e1000000000.

FromJSON Day Source # 
FromJSON DotNetTime Source # 
FromJSON Value Source # 
FromJSON a => FromJSON [a] Source # 
FromJSON a => FromJSON (Maybe a) Source # 
(FromJSON a, Integral a) => FromJSON (Ratio a) Source # 
FromJSON a => FromJSON (Identity a) Source # 
FromJSON a => FromJSON (Min a) Source # 
FromJSON a => FromJSON (Max a) Source # 
FromJSON a => FromJSON (First a) Source # 
FromJSON a => FromJSON (Last a) Source # 
FromJSON a => FromJSON (WrappedMonoid a) Source # 
FromJSON a => FromJSON (Option a) Source # 
FromJSON a => FromJSON (NonEmpty a) Source # 
HasResolution a => FromJSON (Fixed a) Source #

WARNING: Only parse fixed-precision numbers from trusted input since an attacker could easily fill up the memory of the target system by specifying a scientific number with a big exponent like 1e1000000000.

FromJSON a => FromJSON (Dual a) Source # 
FromJSON a => FromJSON (First a) Source # 
FromJSON a => FromJSON (Last a) Source # 
FromJSON v => FromJSON (Tree v) Source # 
FromJSON a => FromJSON (Seq a) Source # 
FromJSON a => FromJSON (IntMap a) Source # 
(Ord a, FromJSON a) => FromJSON (Set a) Source # 
FromJSON a => FromJSON (DList a) Source # 
(Eq a, Hashable a, FromJSON a) => FromJSON (HashSet a) Source # 
FromJSON a => FromJSON (Vector a) Source # 
(Vector Vector a, FromJSON a) => FromJSON (Vector a) Source # 
(Storable a, FromJSON a) => FromJSON (Vector a) Source # 
(Prim a, FromJSON a) => FromJSON (Vector a) Source # 
(FromJSON a, FromJSON b) => FromJSON (Either a b) Source # 
(FromJSON a, FromJSON b) => FromJSON (a, b) Source # 

Methods

parseJSON :: Value -> Parser (a, b) Source #

parseJSONList :: Value -> Parser [(a, b)] Source #

FromJSON (Proxy k a) Source # 
(FromJSONKey k, Ord k, FromJSON v) => FromJSON (Map k v) Source # 
(FromJSON v, FromJSONKey k, Eq k, Hashable k) => FromJSON (HashMap k v) Source # 
(FromJSON a, FromJSON b, FromJSON c) => FromJSON (a, b, c) Source # 

Methods

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

parseJSONList :: Value -> Parser [(a, b, c)] Source #

FromJSON a => FromJSON (Const k a b) Source # 
FromJSON b => FromJSON (Tagged k a b) Source # 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a, b, c, d) Source # 

Methods

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

parseJSONList :: Value -> Parser [(a, b, c, d)] Source #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Sum * f g a) Source # 

Methods

parseJSON :: Value -> Parser (Sum * f g a) Source #

parseJSONList :: Value -> Parser [Sum * f g a] Source #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Product * f g a) Source # 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON (a, b, c, d, e) Source # 

Methods

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

parseJSONList :: Value -> Parser [(a, b, c, d, e)] Source #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Compose * * f g a) Source # 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON (a, b, c, d, e, f) Source # 

Methods

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

parseJSONList :: Value -> Parser [(a, b, c, d, e, f)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON (a, b, c, d, e, f, g) Source # 

Methods

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

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON (a, b, c, d, e, f, g, h) Source # 

Methods

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

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON (a, b, c, d, e, f, g, h, i) Source # 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i) Source #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON (a, b, c, d, e, f, g, h, i, j) Source # 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j) Source #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON (a, b, c, d, e, f, g, h, i, j, k) Source # 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k) Source #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l) Source # 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l) Source #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m) Source #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n, FromJSON o) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] Source #

data Result a Source #

The result of running a Parser.

Constructors

Error String 
Success a 

Instances

Monad Result Source # 

Methods

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

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

return :: a -> Result a #

fail :: String -> Result a #

Functor Result Source # 

Methods

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

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

MonadFail Result Source # 

Methods

fail :: String -> Result a #

Applicative Result Source # 

Methods

pure :: a -> Result a #

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

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

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

Foldable Result Source # 

Methods

fold :: Monoid m => Result m -> m #

foldMap :: Monoid m => (a -> m) -> Result a -> m #

foldr :: (a -> b -> b) -> b -> Result a -> b #

foldr' :: (a -> b -> b) -> b -> Result a -> b #

foldl :: (b -> a -> b) -> b -> Result a -> b #

foldl' :: (b -> a -> b) -> b -> Result a -> b #

foldr1 :: (a -> a -> a) -> Result a -> a #

foldl1 :: (a -> a -> a) -> Result a -> a #

toList :: Result a -> [a] #

null :: Result a -> Bool #

length :: Result a -> Int #

elem :: Eq a => a -> Result a -> Bool #

maximum :: Ord a => Result a -> a #

minimum :: Ord a => Result a -> a #

sum :: Num a => Result a -> a #

product :: Num a => Result a -> a #

Traversable Result Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Result a -> f (Result b) #

sequenceA :: Applicative f => Result (f a) -> f (Result a) #

mapM :: Monad m => (a -> m b) -> Result a -> m (Result b) #

sequence :: Monad m => Result (m a) -> m (Result a) #

Alternative Result Source # 

Methods

empty :: Result a #

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

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

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

MonadPlus Result Source # 

Methods

mzero :: Result a #

mplus :: Result a -> Result a -> Result a #

Eq a => Eq (Result a) Source # 

Methods

(==) :: Result a -> Result a -> Bool #

(/=) :: Result a -> Result a -> Bool #

Show a => Show (Result a) Source # 

Methods

showsPrec :: Int -> Result a -> ShowS #

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Semigroup (Result a) Source # 

Methods

(<>) :: Result a -> Result a -> Result a #

sconcat :: NonEmpty (Result a) -> Result a #

stimes :: Integral b => b -> Result a -> Result a #

Monoid (Result a) Source # 

Methods

mempty :: Result a #

mappend :: Result a -> Result a -> Result a #

mconcat :: [Result a] -> Result a #

NFData a => NFData (Result a) Source # 

Methods

rnf :: Result a -> () #

fromJSON :: FromJSON a => Value -> Result a Source #

Convert a value from JSON, failing if the types do not match.

class ToJSON a where Source #

A type that can be converted to JSON.

An example type and instance:

-- Allow ourselves to write Text literals.
{-# LANGUAGE OverloadedStrings #-}

data Coord = Coord { x :: Double, y :: Double }

instance ToJSON Coord where
  toJSON (Coord x y) = object ["x" .= x, "y" .= y]

  toEncoding (Coord x y) = pairs ("x" .= x <> "y" .= y)

Instead of manually writing your ToJSON instance, there are two options to do it automatically:

  • Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
  • The compiler can provide a default generic implementation for toJSON.

To use the second, simply add a deriving Generic clause to your datatype and declare a ToJSON instance for your datatype without giving definitions for toJSON or toEncoding.

For example, the previous example can be simplified to a more minimal instance:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

data Coord = Coord { x :: Double, y :: Double } deriving Generic

instance ToJSON Coord where
    toEncoding = genericToEncoding defaultOptions

Why do we provide an implementation for toEncoding here? The toEncoding function is a relatively new addition to this class. To allow users of older versions of this library to upgrade without having to edit all of their instances or encounter surprising incompatibilities, the default implementation of toEncoding uses toJSON. This produces correct results, but since it performs an intermediate conversion to a Value, it will be less efficient than directly emitting an Encoding. Our one-liner definition of toEncoding above bypasses the intermediate Value.

If DefaultSignatures doesn't give exactly the results you want, you can customize the generic encoding with only a tiny amount of effort, using genericToJSON and genericToEncoding with your preferred Options:

instance ToJSON Coord where
    toJSON     = genericToJSON defaultOptions
    toEncoding = genericToEncoding defaultOptions

Methods

toJSON :: a -> Value Source #

Convert a Haskell value to a JSON-friendly intermediate type.

toJSON :: (Generic a, GToJSON Zero (Rep a)) => a -> Value Source #

Convert a Haskell value to a JSON-friendly intermediate type.

toEncoding :: a -> Encoding Source #

Encode a Haskell value as JSON.

The default implementation of this method creates an intermediate Value using toJSON. This provides source-level compatibility for people upgrading from older versions of this library, but obviously offers no performance advantage.

To benefit from direct encoding, you must provide an implementation for this method. The easiest way to do so is by having your types implement Generic using the DeriveGeneric extension, and then have GHC generate a method body as follows.

instance ToJSON Coord where
    toEncoding = genericToEncoding defaultOptions

toJSONList :: [a] -> Value Source #

toEncodingList :: [a] -> Encoding Source #

Instances

ToJSON Bool Source # 
ToJSON Char Source # 
ToJSON Double Source # 
ToJSON Float Source # 
ToJSON Int Source # 
ToJSON Int8 Source # 
ToJSON Int16 Source # 
ToJSON Int32 Source # 
ToJSON Int64 Source # 
ToJSON Integer Source # 
ToJSON Ordering Source # 
ToJSON Word Source # 
ToJSON Word8 Source # 
ToJSON Word16 Source # 
ToJSON Word32 Source # 
ToJSON Word64 Source # 
ToJSON () Source # 
ToJSON Text Source # 
ToJSON Text Source # 
ToJSON Number Source # 
ToJSON Natural Source # 
ToJSON Version Source # 
ToJSON IntSet Source # 
ToJSON Scientific Source # 
ToJSON LocalTime Source # 
ToJSON ZonedTime Source # 
ToJSON TimeOfDay Source # 
ToJSON UTCTime Source # 
ToJSON NominalDiffTime Source # 
ToJSON Day Source # 
ToJSON DotNetTime Source # 
ToJSON Value Source # 
ToJSON a => ToJSON [a] Source # 

Methods

toJSON :: [a] -> Value Source #

toEncoding :: [a] -> Encoding Source #

toJSONList :: [[a]] -> Value Source #

toEncodingList :: [[a]] -> Encoding Source #

ToJSON a => ToJSON (Maybe a) Source # 
(ToJSON a, Integral a) => ToJSON (Ratio a) Source # 
ToJSON a => ToJSON (Identity a) Source # 
ToJSON a => ToJSON (Min a) Source # 
ToJSON a => ToJSON (Max a) Source # 
ToJSON a => ToJSON (First a) Source # 
ToJSON a => ToJSON (Last a) Source # 
ToJSON a => ToJSON (WrappedMonoid a) Source # 
ToJSON a => ToJSON (Option a) Source # 
ToJSON a => ToJSON (NonEmpty a) Source # 
HasResolution a => ToJSON (Fixed a) Source # 
ToJSON a => ToJSON (Dual a) Source # 
ToJSON a => ToJSON (First a) Source # 
ToJSON a => ToJSON (Last a) Source # 
ToJSON v => ToJSON (Tree v) Source # 
ToJSON a => ToJSON (Seq a) Source # 
ToJSON a => ToJSON (IntMap a) Source # 
ToJSON a => ToJSON (Set a) Source # 
ToJSON a => ToJSON (DList a) Source # 
ToJSON a => ToJSON (HashSet a) Source # 
ToJSON a => ToJSON (Vector a) Source # 
(Vector Vector a, ToJSON a) => ToJSON (Vector a) Source # 
(Storable a, ToJSON a) => ToJSON (Vector a) Source # 
(Prim a, ToJSON a) => ToJSON (Vector a) Source # 
(ToJSON a, ToJSON b) => ToJSON (Either a b) Source # 
(ToJSON a, ToJSON b) => ToJSON (a, b) Source # 

Methods

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

toEncoding :: (a, b) -> Encoding Source #

toJSONList :: [(a, b)] -> Value Source #

toEncodingList :: [(a, b)] -> Encoding Source #

ToJSON (Proxy k a) Source # 
(ToJSON v, ToJSONKey k) => ToJSON (Map k v) Source # 
(ToJSON v, ToJSONKey k) => ToJSON (HashMap k v) Source # 
(ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) Source # 

Methods

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

toEncoding :: (a, b, c) -> Encoding Source #

toJSONList :: [(a, b, c)] -> Value Source #

toEncodingList :: [(a, b, c)] -> Encoding Source #

ToJSON a => ToJSON (Const k a b) Source # 
ToJSON b => ToJSON (Tagged k a b) Source # 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) Source # 

Methods

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

toEncoding :: (a, b, c, d) -> Encoding Source #

toJSONList :: [(a, b, c, d)] -> Value Source #

toEncodingList :: [(a, b, c, d)] -> Encoding Source #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Sum * f g a) Source # 

Methods

toJSON :: Sum * f g a -> Value Source #

toEncoding :: Sum * f g a -> Encoding Source #

toJSONList :: [Sum * f g a] -> Value Source #

toEncodingList :: [Sum * f g a] -> Encoding Source #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Product * f g a) Source # 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a, b, c, d, e) Source # 

Methods

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

toEncoding :: (a, b, c, d, e) -> Encoding Source #

toJSONList :: [(a, b, c, d, e)] -> Value Source #

toEncodingList :: [(a, b, c, d, e)] -> Encoding Source #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Compose * * f g a) Source # 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a, b, c, d, e, f) Source # 

Methods

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

toEncoding :: (a, b, c, d, e, f) -> Encoding Source #

toJSONList :: [(a, b, c, d, e, f)] -> Value Source #

toEncodingList :: [(a, b, c, d, e, f)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a, b, c, d, e, f, g) Source # 

Methods

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

toEncoding :: (a, b, c, d, e, f, g) -> Encoding Source #

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

toEncodingList :: [(a, b, c, d, e, f, g)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON (a, b, c, d, e, f, g, h) Source # 

Methods

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

toEncoding :: (a, b, c, d, e, f, g, h) -> Encoding Source #

toJSONList :: [(a, b, c, d, e, f, g, h)] -> Value Source #

toEncodingList :: [(a, b, c, d, e, f, g, h)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON (a, b, c, d, e, f, g, h, i) Source # 

Methods

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

toEncoding :: (a, b, c, d, e, f, g, h, i) -> Encoding Source #

toJSONList :: [(a, b, c, d, e, f, g, h, i)] -> Value Source #

toEncodingList :: [(a, b, c, d, e, f, g, h, i)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON (a, b, c, d, e, f, g, h, i, j) Source # 

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j) -> Value Source #

toEncoding :: (a, b, c, d, e, f, g, h, i, j) -> Encoding Source #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j)] -> Value Source #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON (a, b, c, d, e, f, g, h, i, j, k) Source # 

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k) -> Value Source #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k) -> Encoding Source #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Value Source #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l) Source # 

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Value Source #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Encoding Source #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Value Source #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) Source # 

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Value Source #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Encoding Source #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Value Source #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) Source # 

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Value Source #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Encoding Source #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Value Source #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n, ToJSON o) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) Source # 

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Value Source #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Encoding Source #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Value Source #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Encoding Source #

class KeyValue kv where Source #

A key-value pair for encoding a JSON object.

Minimal complete definition

(.=)

Methods

(.=) :: ToJSON v => Text -> v -> kv infixr 8 Source #

Instances

KeyValue Pair Source # 

Methods

(.=) :: ToJSON v => Text -> v -> Pair Source #

KeyValue Series Source # 

Methods

(.=) :: ToJSON v => Text -> v -> Series Source #

Keys for maps

class ToJSONKey a where Source #

Typeclass for types that can be used as the key of a map-like container (like Map or HashMap). For example, since Text has a ToJSONKey instance and Char has a ToJSON instance, we can encode a value of type Map Text Char:

>>> LBC8.putStrLn $ encode $ Map.fromList [("foo" :: Text, 'a')]
{"foo":"a"}

Since Int also has a ToJSONKey instance, we can similarly write:

>>> LBC8.putStrLn $ encode $ Map.fromList [(5 :: Int, 'a')]
{"5":"a"}

JSON documents only accept strings as object keys. For any type from base that has a natural textual representation, it can be expected that its ToJSONKey instance will choose that representation.

For data types that lack a natural textual representation, an alternative is provided. The map-like container is represented as a JSON array instead of a JSON object. Each value in the array is an array with exactly two values. The first is the key and the second is the value.

For example, values of type '[Text]' cannot be encoded to a string, so a Map with keys of type '[Text]' is encoded as follows:

>>> LBC8.putStrLn $ encode $ Map.fromList [(["foo","bar","baz" :: Text], 'a')]
[[["foo","bar","baz"],"a"]]

The default implementation of ToJSONKey chooses this method of encoding a key, using the ToJSON instance of the type.

To use your own data type as the key in a map, all that is needed is to write a ToJSONKey (and possibly a FromJSONKey) instance for it. If the type cannot be trivially converted to and from Text, it is recommended that ToJSONKeyValue is used. Since the default implementations of the typeclass methods can build this from a ToJSON instance, there is nothing that needs to be written:

data Foo = Foo { fooAge :: Int, fooName :: Text }
  deriving (Eq,Ord,Generic)
instance ToJSON Foo
instance ToJSONKey Foo

That's it. We can now write:

>>> let m = Map.fromList [(Foo 4 "bar",'a'),(Foo 6 "arg",'b')]
>>> LBC8.putStrLn $ encode m
[[{"fooName":"bar","fooAge":4},"a"],[{"fooName":"arg","fooAge":6},"b"]]

The next case to consider is if we have a type that is a newtype wrapper around Text. The recommended approach is to use generalized newtype deriving:

newtype RecordId = RecordId { getRecordId :: Text}
  deriving (Eq,Ord,ToJSONKey)

Then we may write:

>>> LBC8.putStrLn $ encode $ Map.fromList [(RecordId "abc",'a')]
{"abc":"a"}

Simple sum types are a final case worth considering. Suppose we have:

data Color = Red | Green | Blue
  deriving (Show,Read,Eq,Ord)

It is possible to get the ToJSONKey instance for free as we did with Foo. However, in this case, we have a natural way to go to and from Text that does not require any escape sequences. So, in this example, ToJSONKeyText will be used instead of ToJSONKeyValue. The Show instance can be used to help write ToJSONKey:

instance ToJSONKey Color where
  toJSONKey = ToJSONKeyText f g
    where f = Text.pack . show
          g = text . Text.pack . show
          -- text function is from Data.Aeson.Encoding

The situation of needing to turning function a -> Text into a ToJSONKeyFunction is common enough that a special combinator is provided for it. The above instance can be rewritten as:

instance ToJSONKey Color where
  toJSONKey = toJSONKeyText (Text.pack . show)

The performance of the above instance can be improved by not using String as an intermediate step when converting to Text. One option for improving performance would be to use template haskell machinery from the text-show package. However, even with the approach, the Encoding (a wrapper around a bytestring builder) is generated by encoding the Text to a ByteString, an intermediate step that could be avoided. The fastest possible implementation would be:

-- Assuming that OverloadedStrings is enabled
instance ToJSONKey Color where
  toJSONKey = ToJSONKeyText f g
    where f x = case x of {Red -> "Red";Green ->"Green";Blue -> "Blue"}
          g x = case x of {Red -> text "Red";Green -> text "Green";Blue -> text "Blue"}
          -- text function is from Data.Aeson.Encoding

This works because GHC can lift the encoded values out of the case statements, which means that they are only evaluated once. This approach should only be used when there is a serious need to maximize performance.

Methods

toJSONKey :: ToJSONKeyFunction a Source #

Strategy for rendering the key for a map-like container.

toJSONKey :: ToJSON a => ToJSONKeyFunction a Source #

Strategy for rendering the key for a map-like container.

toJSONKeyList :: ToJSONKeyFunction [a] Source #

This is similar in spirit to the showsList method of Show. It makes it possible to give String keys special treatment without using OverlappingInstances. End users should always be able to use the default implementation of this method.

toJSONKeyList :: ToJSON a => ToJSONKeyFunction [a] Source #

This is similar in spirit to the showsList method of Show. It makes it possible to give String keys special treatment without using OverlappingInstances. End users should always be able to use the default implementation of this method.

Instances

ToJSONKey Bool Source # 
ToJSONKey Char Source # 
ToJSONKey Double Source # 
ToJSONKey Float Source # 
ToJSONKey Int Source # 
ToJSONKey Int8 Source # 
ToJSONKey Int16 Source # 
ToJSONKey Int32 Source # 
ToJSONKey Int64 Source # 
ToJSONKey Integer Source # 
ToJSONKey Word Source # 
ToJSONKey Word8 Source # 
ToJSONKey Word16 Source # 
ToJSONKey Word32 Source # 
ToJSONKey Word64 Source # 
ToJSONKey Text Source # 
ToJSONKey Text Source # 
ToJSONKey Natural Source # 
ToJSONKey Version Source # 
ToJSONKey Scientific Source # 
ToJSONKey LocalTime Source # 
ToJSONKey ZonedTime Source # 
ToJSONKey TimeOfDay Source # 
ToJSONKey UTCTime Source # 
ToJSONKey Day Source # 
(ToJSONKey a, ToJSON a) => ToJSONKey [a] Source # 
(ToJSONKey a, ToJSON a) => ToJSONKey (Identity a) Source # 
HasResolution a => ToJSONKey (Fixed a) Source # 
(ToJSON a, ToJSON b) => ToJSONKey (a, b) Source # 
(ToJSON a, ToJSON b, ToJSON c) => ToJSONKey (a, b, c) Source # 
ToJSONKey b => ToJSONKey (Tagged k a b) Source # 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSONKey (a, b, c, d) Source # 

Methods

toJSONKey :: ToJSONKeyFunction (a, b, c, d) Source #

toJSONKeyList :: ToJSONKeyFunction [(a, b, c, d)] Source #

data ToJSONKeyFunction a Source #

Constructors

ToJSONKeyText !(a -> Text) !(a -> Encoding' Text)

key is encoded to string, produces object

ToJSONKeyValue !(a -> Value) !(a -> Encoding)

key is encoded to value, produces array

class FromJSONKey a where Source #

Read the docs for ToJSONKey first. This class is a conversion in the opposite direction. If you have a newtype wrapper around Text, the recommended way to define instances is with generalized newtype deriving:

newtype SomeId = SomeId { getSomeId :: Text }
  deriving (Eq,Ord,Hashable,FromJSONKey)

Methods

fromJSONKey :: FromJSONKeyFunction a Source #

Strategy for parsing the key of a map-like container.

fromJSONKey :: FromJSON a => FromJSONKeyFunction a Source #

Strategy for parsing the key of a map-like container.

fromJSONKeyList :: FromJSONKeyFunction [a] Source #

This is similar in spirit to the readList method of Read. It makes it possible to give String keys special treatment without using OverlappingInstances. End users should always be able to use the default implementation of this method.

fromJSONKeyList :: FromJSON a => FromJSONKeyFunction [a] Source #

This is similar in spirit to the readList method of Read. It makes it possible to give String keys special treatment without using OverlappingInstances. End users should always be able to use the default implementation of this method.

Instances

FromJSONKey Bool Source # 
FromJSONKey Char Source # 
FromJSONKey Double Source # 
FromJSONKey Float Source # 
FromJSONKey Int Source # 
FromJSONKey Int8 Source # 
FromJSONKey Int16 Source # 
FromJSONKey Int32 Source # 
FromJSONKey Int64 Source # 
FromJSONKey Integer Source # 
FromJSONKey Word Source # 
FromJSONKey Word8 Source # 
FromJSONKey Word16 Source # 
FromJSONKey Word32 Source # 
FromJSONKey Word64 Source # 
FromJSONKey Text Source # 
FromJSONKey Text Source # 
FromJSONKey Natural Source # 
FromJSONKey Version Source # 
FromJSONKey LocalTime Source # 
FromJSONKey ZonedTime Source # 
FromJSONKey TimeOfDay Source # 
FromJSONKey UTCTime Source # 
FromJSONKey Day Source # 
(FromJSONKey a, FromJSON a) => FromJSONKey [a] Source # 
(FromJSONKey a, FromJSON a) => FromJSONKey (Identity a) Source # 
(FromJSON a, FromJSON b) => FromJSONKey (a, b) Source # 
(FromJSON a, FromJSON b, FromJSON c) => FromJSONKey (a, b, c) Source # 
FromJSONKey b => FromJSONKey (Tagged k a b) Source # 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSONKey (a, b, c, d) Source # 

data FromJSONKeyFunction a Source #

This type is related to ToJSONKeyFunction. If FromJSONKeyValue is used in the FromJSONKey instance, then ToJSONKeyValue should be used in the ToJSONKey instance. The other three data constructors for this type all correspond to ToJSONKeyText. Strictly speaking, FromJSONKeyTextParser is more powerful than FromJSONKeyText, which is in turn more powerful than FromJSONKeyCoerce. For performance reasons, these exist as three options instead of one.

Constructors

FromJSONKeyCoerce !(CoerceText a)

uses coerce (unsafeCoerce in older GHCs)

FromJSONKeyText !(Text -> a)

conversion from Text that always succeeds

FromJSONKeyTextParser !(Text -> Parser a)

conversion from Text that may fail

FromJSONKeyValue !(Value -> Parser a)

conversion for non-textual keys

Instances

Functor FromJSONKeyFunction Source #

Only law abiding up to interpretation

Liftings to unary and binary type constructors

class FromJSON1 f where Source #

Lifting of the FromJSON class to unary type constructors.

Instead of manually writing your FromJSON1 instance, there are two options to do it automatically:

  • Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
  • The compiler can provide a default generic implementation for liftParseJSON.

To use the second, simply add a deriving Generic1 clause to your datatype and declare a FromJSON1 instance for your datatype without giving a definition for liftParseJSON.

For example:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

data Pair a b = Pair { pairFst :: a, pairSnd :: b } deriving Generic1

instance FromJSON a => FromJSON1 (Pair a)

If DefaultSignatures doesn't give exactly the results you want, you can customize the generic decoding with only a tiny amount of effort, using genericLiftParseJSON with your preferred Options:

instance FromJSON a => FromJSON1 (Pair a) where
    liftParseJSON = genericLiftParseJSON defaultOptions

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a) Source #

liftParseJSON :: (Generic1 f, GFromJSON One (Rep1 f)) => (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [f a] Source #

Instances

FromJSON1 [] Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [a] Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [[a]] Source #

FromJSON1 Maybe Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Maybe a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Maybe a] Source #

FromJSON1 Identity Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Identity a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Identity a] Source #

FromJSON1 Min Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Min a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Min a] Source #

FromJSON1 Max Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Max a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Max a] Source #

FromJSON1 First Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (First a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [First a] Source #

FromJSON1 Last Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Last a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Last a] Source #

FromJSON1 WrappedMonoid Source # 
FromJSON1 Option Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Option a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Option a] Source #

FromJSON1 NonEmpty Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (NonEmpty a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [NonEmpty a] Source #

FromJSON1 Dual Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Dual a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Dual a] Source #

FromJSON1 First Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (First a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [First a] Source #

FromJSON1 Last Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Last a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Last a] Source #

FromJSON1 Tree Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Tree a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Tree a] Source #

FromJSON1 Seq Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Seq a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Seq a] Source #

FromJSON1 IntMap Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (IntMap a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [IntMap a] Source #

FromJSON1 DList Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (DList a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [DList a] Source #

FromJSON1 Vector Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Vector a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Vector a] Source #

FromJSON a => FromJSON1 (Either a) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Either a a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Either a a] Source #

FromJSON a => FromJSON1 ((,) a) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, a)] Source #

(FromJSONKey k, Ord k) => FromJSON1 (Map k) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Map k a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Map k a] Source #

(FromJSONKey k, Eq k, Hashable k) => FromJSON1 (HashMap k) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (HashMap k a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [HashMap k a] Source #

(FromJSON a, FromJSON b) => FromJSON1 ((,,) a b) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, b, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, b, a)] Source #

FromJSON a => FromJSON1 (Const * a) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Const * a a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Const * a a] Source #

FromJSON1 (Tagged k a) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Tagged k a a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Tagged k a a] Source #

(FromJSON a, FromJSON b, FromJSON c) => FromJSON1 ((,,,) a b c) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, b, c, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, b, c, a)] Source #

(FromJSON1 f, FromJSON1 g) => FromJSON1 (Sum * f g) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Sum * f g a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Sum * f g a] Source #

(FromJSON1 f, FromJSON1 g) => FromJSON1 (Product * f g) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Product * f g a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Product * f g a] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON1 ((,,,,) a b c d) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, b, c, d, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, b, c, d, a)] Source #

(FromJSON1 f, FromJSON1 g) => FromJSON1 (Compose * * f g) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Compose * * f g a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Compose * * f g a] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON1 ((,,,,,) a b c d e) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, b, c, d, e, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, b, c, d, e, a)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON1 ((,,,,,,) a b c d e f) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, b, c, d, e, f, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, b, c, d, e, f, a)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON1 ((,,,,,,,) a b c d e f g) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, b, c, d, e, f, g, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, b, c, d, e, f, g, a)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON1 ((,,,,,,,,) a b c d e f g h) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, b, c, d, e, f, g, h, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, b, c, d, e, f, g, h, a)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON1 ((,,,,,,,,,) a b c d e f g h i) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, b, c, d, e, f, g, h, i, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, b, c, d, e, f, g, h, i, a)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON1 ((,,,,,,,,,,) a b c d e f g h i j) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, b, c, d, e, f, g, h, i, j, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, b, c, d, e, f, g, h, i, j, a)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON1 ((,,,,,,,,,,,) a b c d e f g h i j k) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, a)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, a)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, a)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n) => FromJSON1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) Source # 

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a) Source #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, a)] Source #

parseJSON1 :: (FromJSON1 f, FromJSON a) => Value -> Parser (f a) Source #

Lift the standard parseJSON function through the type constructor.

class FromJSON2 f where Source #

Lifting of the FromJSON class to binary type constructors.

Instead of manually writing your FromJSON2 instance, Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time.

Minimal complete definition

liftParseJSON2

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (f a b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [f a b] Source #

Instances

FromJSON2 Either Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (Either a b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [Either a b] Source #

FromJSON2 (,) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, b)] Source #

FromJSON a => FromJSON2 ((,,) a) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, a, b)] Source #

FromJSON2 (Const *) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (Const * a b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [Const * a b] Source #

(FromJSON a, FromJSON b) => FromJSON2 ((,,,) a b) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, b, a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, b, a, b)] Source #

(FromJSON a, FromJSON b, FromJSON c) => FromJSON2 ((,,,,) a b c) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, b, c, a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, b, c, a, b)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON2 ((,,,,,) a b c d) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, b, c, d, a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, b, c, d, a, b)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON2 ((,,,,,,) a b c d e) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, b, c, d, e, a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, b, c, d, e, a, b)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON2 ((,,,,,,,) a b c d e f) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, b, c, d, e, f, a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, b, c, d, e, f, a, b)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g) => FromJSON2 ((,,,,,,,,) a b c d e f g) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, b, c, d, e, f, g, a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, b, c, d, e, f, g, a, b)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h) => FromJSON2 ((,,,,,,,,,) a b c d e f g h) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, b, c, d, e, f, g, h, a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, b, c, d, e, f, g, h, a, b)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON2 ((,,,,,,,,,,) a b c d e f g h i) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, b, c, d, e, f, g, h, i, a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, b, c, d, e, f, g, h, i, a, b)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON2 ((,,,,,,,,,,,) a b c d e f g h i j) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, b, c, d, e, f, g, h, i, j, a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, b, c, d, e, f, g, h, i, j, a, b)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON2 ((,,,,,,,,,,,,) a b c d e f g h i j k) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, a, b)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON2 ((,,,,,,,,,,,,,) a b c d e f g h i j k l) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, a, b)] Source #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON2 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m) Source # 

Methods

liftParseJSON2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, a, b) Source #

liftParseJSONList2 :: (Value -> Parser a) -> (Value -> Parser [a]) -> (Value -> Parser b) -> (Value -> Parser [b]) -> Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, a, b)] Source #

parseJSON2 :: (FromJSON2 f, FromJSON a, FromJSON b) => Value -> Parser (f a b) Source #

Lift the standard parseJSON function through the type constructor.

class ToJSON1 f where Source #

Lifting of the ToJSON class to unary type constructors.

Instead of manually writing your ToJSON1 instance, there are two options to do it automatically:

  • Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
  • The compiler can provide a default generic implementation for toJSON1.

To use the second, simply add a deriving Generic1 clause to your datatype and declare a ToJSON1 instance for your datatype without giving definitions for liftToJSON or liftToEncoding.

For example:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

data Pair = Pair { pairFst :: a, pairSnd :: b } deriving Generic1

instance ToJSON a => ToJSON1 (Pair a)

If DefaultSignatures doesn't give exactly the results you want, you can customize the generic encoding with only a tiny amount of effort, using genericLiftToJSON and genericLiftToEncoding with your preferred Options:

instance ToJSON a => ToJSON1 (Pair a) where
    liftToJSON     = genericLiftToJSON defaultOptions
    liftToEncoding = genericLiftToEncoding defaultOptions

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> f a -> Value Source #

liftToJSON :: (Generic1 f, GToJSON One (Rep1 f)) => (a -> Value) -> ([a] -> Value) -> f a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [f a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding Source #

liftToEncoding :: (Generic1 f, GToEncoding One (Rep1 f)) => (a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [f a] -> Encoding Source #

Instances

ToJSON1 [] Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> [a] -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [[a]] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> [a] -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [[a]] -> Encoding Source #

ToJSON1 Maybe Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Maybe a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Maybe a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Maybe a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Maybe a] -> Encoding Source #

ToJSON1 Identity Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Identity a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Identity a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Identity a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Identity a] -> Encoding Source #

ToJSON1 Min Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Min a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Min a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Min a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Min a] -> Encoding Source #

ToJSON1 Max Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Max a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Max a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Max a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Max a] -> Encoding Source #

ToJSON1 First Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> First a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [First a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> First a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [First a] -> Encoding Source #

ToJSON1 Last Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Last a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Last a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Last a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Last a] -> Encoding Source #

ToJSON1 WrappedMonoid Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> WrappedMonoid a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [WrappedMonoid a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> WrappedMonoid a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [WrappedMonoid a] -> Encoding Source #

ToJSON1 Option Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Option a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Option a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Option a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Option a] -> Encoding Source #

ToJSON1 NonEmpty Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> NonEmpty a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [NonEmpty a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> NonEmpty a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [NonEmpty a] -> Encoding Source #

ToJSON1 Dual Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Dual a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Dual a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Dual a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Dual a] -> Encoding Source #

ToJSON1 First Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> First a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [First a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> First a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [First a] -> Encoding Source #

ToJSON1 Last Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Last a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Last a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Last a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Last a] -> Encoding Source #

ToJSON1 Tree Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Tree a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Tree a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Tree a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Tree a] -> Encoding Source #

ToJSON1 Seq Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Seq a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Seq a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Seq a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Seq a] -> Encoding Source #

ToJSON1 IntMap Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> IntMap a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [IntMap a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> IntMap a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [IntMap a] -> Encoding Source #

ToJSON1 Set Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Set a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Set a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Set a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Set a] -> Encoding Source #

ToJSON1 DList Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> DList a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [DList a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> DList a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [DList a] -> Encoding Source #

ToJSON1 HashSet Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> HashSet a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [HashSet a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> HashSet a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [HashSet a] -> Encoding Source #

ToJSON1 Vector Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Vector a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Vector a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Vector a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Vector a] -> Encoding Source #

ToJSON a => ToJSON1 (Either a) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Either a a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Either a a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Either a a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Either a a] -> Encoding Source #

ToJSON a => ToJSON1 ((,) a) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> (a, a) -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [(a, a)] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, a)] -> Encoding Source #

ToJSONKey k => ToJSON1 (Map k) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Map k a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Map k a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Map k a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Map k a] -> Encoding Source #

ToJSONKey k => ToJSON1 (HashMap k) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> HashMap k a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [HashMap k a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> HashMap k a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [HashMap k a] -> Encoding Source #

(ToJSON a, ToJSON b) => ToJSON1 ((,,) a b) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> (a, b, a) -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [(a, b, a)] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, b, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, b, a)] -> Encoding Source #

ToJSON a => ToJSON1 (Const * a) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Const * a a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Const * a a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Const * a a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Const * a a] -> Encoding Source #

ToJSON1 (Tagged k a) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Tagged k a a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Tagged k a a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Tagged k a a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Tagged k a a] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c) => ToJSON1 ((,,,) a b c) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> (a, b, c, a) -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [(a, b, c, a)] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, b, c, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, b, c, a)] -> Encoding Source #

(ToJSON1 f, ToJSON1 g) => ToJSON1 (Sum * f g) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Sum * f g a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Sum * f g a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Sum * f g a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Sum * f g a] -> Encoding Source #

(ToJSON1 f, ToJSON1 g) => ToJSON1 (Product * f g) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Product * f g a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Product * f g a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Product * f g a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Product * f g a] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON1 ((,,,,) a b c d) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> (a, b, c, d, a) -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [(a, b, c, d, a)] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, b, c, d, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, b, c, d, a)] -> Encoding Source #

(ToJSON1 f, ToJSON1 g) => ToJSON1 (Compose * * f g) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> Compose * * f g a -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [Compose * * f g a] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> Compose * * f g a -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [Compose * * f g a] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON1 ((,,,,,) a b c d e) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> (a, b, c, d, e, a) -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [(a, b, c, d, e, a)] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, b, c, d, e, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, b, c, d, e, a)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON1 ((,,,,,,) a b c d e f) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> (a, b, c, d, e, f, a) -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [(a, b, c, d, e, f, a)] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, b, c, d, e, f, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, b, c, d, e, f, a)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON1 ((,,,,,,,) a b c d e f g) Source # 

Methods

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

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

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, b, c, d, e, f, g, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, b, c, d, e, f, g, a)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON1 ((,,,,,,,,) a b c d e f g h) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> (a, b, c, d, e, f, g, h, a) -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [(a, b, c, d, e, f, g, h, a)] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, b, c, d, e, f, g, h, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, b, c, d, e, f, g, h, a)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON1 ((,,,,,,,,,) a b c d e f g h i) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> (a, b, c, d, e, f, g, h, i, a) -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [(a, b, c, d, e, f, g, h, i, a)] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, b, c, d, e, f, g, h, i, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, b, c, d, e, f, g, h, i, a)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON1 ((,,,,,,,,,,) a b c d e f g h i j) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> (a, b, c, d, e, f, g, h, i, j, a) -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [(a, b, c, d, e, f, g, h, i, j, a)] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, b, c, d, e, f, g, h, i, j, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, b, c, d, e, f, g, h, i, j, a)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON1 ((,,,,,,,,,,,) a b c d e f g h i j k) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> (a, b, c, d, e, f, g, h, i, j, k, a) -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [(a, b, c, d, e, f, g, h, i, j, k, a)] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, b, c, d, e, f, g, h, i, j, k, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, b, c, d, e, f, g, h, i, j, k, a)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON1 ((,,,,,,,,,,,,) a b c d e f g h i j k l) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> (a, b, c, d, e, f, g, h, i, j, k, l, a) -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [(a, b, c, d, e, f, g, h, i, j, k, l, a)] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, b, c, d, e, f, g, h, i, j, k, l, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, b, c, d, e, f, g, h, i, j, k, l, a)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON1 ((,,,,,,,,,,,,,) a b c d e f g h i j k l m) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, a) -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, a)] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, a)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n) => ToJSON1 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m n) Source # 

Methods

liftToJSON :: (a -> Value) -> ([a] -> Value) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a) -> Value Source #

liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, a)] -> Value Source #

liftToEncoding :: (a -> Encoding) -> ([a] -> Encoding) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, n, a) -> Encoding Source #

liftToEncodingList :: (a -> Encoding) -> ([a] -> Encoding) -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, a)] -> Encoding Source #

toJSON1 :: (ToJSON1 f, ToJSON a) => f a -> Value Source #

Lift the standard toJSON function through the type constructor.

toEncoding1 :: (ToJSON1 f, ToJSON a) => f a -> Encoding Source #

Lift the standard toEncoding function through the type constructor.

class ToJSON2 f where Source #

Lifting of the ToJSON class to binary type constructors.

Instead of manually writing your ToJSON2 instance, Data.Aeson.TH provides Template Haskell functions which will derive an instance at compile time.

The compiler cannot provide a default generic implementation for liftToJSON2, unlike toJSON and liftToJSON.

Minimal complete definition

liftToJSON2, liftToEncoding2

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> f a b -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [f a b] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> f a b -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [f a b] -> Encoding Source #

Instances

ToJSON2 Either Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> Either a b -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [Either a b] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> Either a b -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [Either a b] -> Encoding Source #

ToJSON2 (,) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> (a, b) -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [(a, b)] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, b)] -> Encoding Source #

ToJSON a => ToJSON2 ((,,) a) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> (a, a, b) -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [(a, a, b)] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, a, b)] -> Encoding Source #

ToJSON2 (Const *) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> Const * a b -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [Const * a b] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> Const * a b -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [Const * a b] -> Encoding Source #

(ToJSON a, ToJSON b) => ToJSON2 ((,,,) a b) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> (a, b, a, b) -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [(a, b, a, b)] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, b, a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, b, a, b)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c) => ToJSON2 ((,,,,) a b c) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> (a, b, c, a, b) -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [(a, b, c, a, b)] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, b, c, a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, b, c, a, b)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON2 ((,,,,,) a b c d) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> (a, b, c, d, a, b) -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [(a, b, c, d, a, b)] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, b, c, d, a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, b, c, d, a, b)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON2 ((,,,,,,) a b c d e) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> (a, b, c, d, e, a, b) -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [(a, b, c, d, e, a, b)] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, b, c, d, e, a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, b, c, d, e, a, b)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON2 ((,,,,,,,) a b c d e f) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> (a, b, c, d, e, f, a, b) -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [(a, b, c, d, e, f, a, b)] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, b, c, d, e, f, a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, b, c, d, e, f, a, b)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON2 ((,,,,,,,,) a b c d e f g) Source # 

Methods

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

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

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, b, c, d, e, f, g, a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, b, c, d, e, f, g, a, b)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h) => ToJSON2 ((,,,,,,,,,) a b c d e f g h) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> (a, b, c, d, e, f, g, h, a, b) -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [(a, b, c, d, e, f, g, h, a, b)] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, b, c, d, e, f, g, h, a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, b, c, d, e, f, g, h, a, b)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON2 ((,,,,,,,,,,) a b c d e f g h i) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> (a, b, c, d, e, f, g, h, i, a, b) -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [(a, b, c, d, e, f, g, h, i, a, b)] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, b, c, d, e, f, g, h, i, a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, b, c, d, e, f, g, h, i, a, b)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON2 ((,,,,,,,,,,,) a b c d e f g h i j) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> (a, b, c, d, e, f, g, h, i, j, a, b) -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [(a, b, c, d, e, f, g, h, i, j, a, b)] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, b, c, d, e, f, g, h, i, j, a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, b, c, d, e, f, g, h, i, j, a, b)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON2 ((,,,,,,,,,,,,) a b c d e f g h i j k) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> (a, b, c, d, e, f, g, h, i, j, k, a, b) -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [(a, b, c, d, e, f, g, h, i, j, k, a, b)] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, b, c, d, e, f, g, h, i, j, k, a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, b, c, d, e, f, g, h, i, j, k, a, b)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON2 ((,,,,,,,,,,,,,) a b c d e f g h i j k l) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> (a, b, c, d, e, f, g, h, i, j, k, l, a, b) -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [(a, b, c, d, e, f, g, h, i, j, k, l, a, b)] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, b, c, d, e, f, g, h, i, j, k, l, a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, b, c, d, e, f, g, h, i, j, k, l, a, b)] -> Encoding Source #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON2 ((,,,,,,,,,,,,,,) a b c d e f g h i j k l m) Source # 

Methods

liftToJSON2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, a, b) -> Value Source #

liftToJSONList2 :: (a -> Value) -> ([a] -> Value) -> (b -> Value) -> ([b] -> Value) -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, a, b)] -> Value Source #

liftToEncoding2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> (a, b, c, d, e, f, g, h, i, j, k, l, m, a, b) -> Encoding Source #

liftToEncodingList2 :: (a -> Encoding) -> ([a] -> Encoding) -> (b -> Encoding) -> ([b] -> Encoding) -> [(a, b, c, d, e, f, g, h, i, j, k, l, m, a, b)] -> Encoding Source #

toJSON2 :: (ToJSON2 f, ToJSON a, ToJSON b) => f a b -> Value Source #

Lift the standard toJSON function through the type constructor.

toEncoding2 :: (ToJSON2 f, ToJSON a, ToJSON b) => f a b -> Encoding Source #

Lift the standard toEncoding function through the type constructor.

Generic JSON classes and options

class GFromJSON arity f where Source #

Class of generic representation types that can be converted from JSON.

Minimal complete definition

gParseJSON

Methods

gParseJSON :: Options -> FromArgs arity a -> Value -> Parser (f a) Source #

This method (applied to defaultOptions) is used as the default generic implementation of parseJSON (if the arity is Zero) or liftParseJSON (if the arity is One).

Instances

GFromJSON arity U1 Source # 

Methods

gParseJSON :: Options -> FromArgs arity a -> Value -> Parser (U1 a) Source #

GFromJSON One Par1 Source # 
FromJSON1 f => GFromJSON One (Rec1 f) Source # 

Methods

gParseJSON :: Options -> FromArgs One a -> Value -> Parser (Rec1 f a) Source #

(AllNullary ((:+:) a b) allNullary, ParseSum * arity ((:+:) a b) allNullary) => GFromJSON arity ((:+:) a b) Source # 

Methods

gParseJSON :: Options -> FromArgs arity a -> Value -> Parser ((a :+: b) a) Source #

(FromProduct arity a, FromProduct arity b, ProductSize a, ProductSize b) => GFromJSON arity ((:*:) a b) Source # 

Methods

gParseJSON :: Options -> FromArgs arity a -> Value -> Parser ((a :*: b) a) Source #

ConsFromJSON arity a => GFromJSON arity (C1 c a) Source # 

Methods

gParseJSON :: Options -> FromArgs arity a -> Value -> Parser (C1 c a a) Source #

FromJSON a => GFromJSON arity (K1 i a) Source # 

Methods

gParseJSON :: Options -> FromArgs arity a -> Value -> Parser (K1 i a a) Source #

(FromJSON1 f, GFromJSON One g) => GFromJSON One ((:.:) f g) Source # 

Methods

gParseJSON :: Options -> FromArgs One a -> Value -> Parser ((f :.: g) a) Source #

GFromJSON arity a => GFromJSON arity (M1 i c a) Source # 

Methods

gParseJSON :: Options -> FromArgs arity a -> Value -> Parser (M1 i c a a) Source #

data FromArgs arity a where Source #

A FromArgs value either stores nothing (for FromJSON) or it stores the two function arguments that decode occurrences of the type parameter (for FromJSON1).

Constructors

NoFromArgs :: FromArgs Zero a 
From1Args :: (Value -> Parser a) -> (Value -> Parser [a]) -> FromArgs One a 

class GToJSON arity f where Source #

Class of generic representation types that can be converted to JSON.

Minimal complete definition

gToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a -> f a -> Value Source #

This method (applied to defaultOptions) is used as the default generic implementation of toJSON (if the arity is Zero) or liftToJSON (if the arity is One).

Instances

GToJSON arity U1 Source # 

Methods

gToJSON :: Options -> ToArgs Value arity a -> U1 a -> Value Source #

GToJSON One Par1 Source # 

Methods

gToJSON :: Options -> ToArgs Value One a -> Par1 a -> Value Source #

ToJSON1 f => GToJSON One (Rec1 f) Source # 

Methods

gToJSON :: Options -> ToArgs Value One a -> Rec1 f a -> Value Source #

(AllNullary ((:+:) a b) allNullary, SumToJSON * arity ((:+:) a b) allNullary) => GToJSON arity ((:+:) a b) Source # 

Methods

gToJSON :: Options -> ToArgs Value arity a -> (a :+: b) a -> Value Source #

(WriteProduct arity a, WriteProduct arity b, ProductSize a, ProductSize b) => GToJSON arity ((:*:) a b) Source # 

Methods

gToJSON :: Options -> ToArgs Value arity a -> (a :*: b) a -> Value Source #

ConsToJSON arity a => GToJSON arity (C1 c a) Source # 

Methods

gToJSON :: Options -> ToArgs Value arity a -> C1 c a a -> Value Source #

ToJSON a => GToJSON arity (K1 i a) Source # 

Methods

gToJSON :: Options -> ToArgs Value arity a -> K1 i a a -> Value Source #

(ToJSON1 f, GToJSON One g) => GToJSON One ((:.:) f g) Source # 

Methods

gToJSON :: Options -> ToArgs Value One a -> (f :.: g) a -> Value Source #

GToJSON arity a => GToJSON arity (M1 i c a) Source # 

Methods

gToJSON :: Options -> ToArgs Value arity a -> M1 i c a a -> Value Source #

class GToEncoding arity f where Source #

Class of generic representation types that can be converted to a JSON Encoding.

Minimal complete definition

gToEncoding

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> f a -> Encoding Source #

This method (applied to defaultOptions) can be used as the default generic implementation of toEncoding (if the arity is Zero) or liftToEncoding (if the arity is One).

Instances

GToEncoding arity U1 Source # 

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> U1 a -> Encoding Source #

GToEncoding One Par1 Source # 
ToJSON1 f => GToEncoding One (Rec1 f) Source # 
(AllNullary ((:+:) a b) allNullary, SumToEncoding * arity ((:+:) a b) allNullary) => GToEncoding arity ((:+:) a b) Source # 

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> (a :+: b) a -> Encoding Source #

(EncodeProduct arity a, EncodeProduct arity b) => GToEncoding arity ((:*:) a b) Source # 

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> (a :*: b) a -> Encoding Source #

ConsToEncoding arity a => GToEncoding arity (C1 c a) Source # 

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> C1 c a a -> Encoding Source #

ToJSON a => GToEncoding arity (K1 i a) Source # 

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> K1 i a a -> Encoding Source #

(ToJSON1 f, GToEncoding One g) => GToEncoding One ((:.:) f g) Source # 

Methods

gToEncoding :: Options -> ToArgs Encoding One a -> (f :.: g) a -> Encoding Source #

GToEncoding arity a => GToEncoding arity (M1 i c a) Source # 

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> M1 i c a a -> Encoding Source #

data ToArgs res arity a where Source #

A ToArgs value either stores nothing (for ToJSON) or it stores the two function arguments that encode occurrences of the type parameter (for ToJSON1).

Constructors

NoToArgs :: ToArgs res Zero a 
To1Args :: (a -> res) -> ([a] -> res) -> ToArgs res One a 

data Zero Source #

A type-level indicator that ToJSON or FromJSON is being derived generically.

data One Source #

A type-level indicator that ToJSON1 or FromJSON1 is being derived generically.

genericToJSON :: (Generic a, GToJSON Zero (Rep a)) => Options -> a -> Value Source #

A configurable generic JSON creator. This function applied to defaultOptions is used as the default for toJSON when the type is an instance of Generic.

genericLiftToJSON :: (Generic1 f, GToJSON One (Rep1 f)) => Options -> (a -> Value) -> ([a] -> Value) -> f a -> Value Source #

A configurable generic JSON creator. This function applied to defaultOptions is used as the default for liftToJSON when the type is an instance of Generic1.

genericToEncoding :: (Generic a, GToEncoding Zero (Rep a)) => Options -> a -> Encoding Source #

A configurable generic JSON encoder. This function applied to defaultOptions is used as the default for toEncoding when the type is an instance of Generic.

genericLiftToEncoding :: (Generic1 f, GToEncoding One (Rep1 f)) => Options -> (a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding Source #

A configurable generic JSON encoder. This function applied to defaultOptions is used as the default for liftToEncoding when the type is an instance of Generic1.

genericParseJSON :: (Generic a, GFromJSON Zero (Rep a)) => Options -> Value -> Parser a Source #

A configurable generic JSON decoder. This function applied to defaultOptions is used as the default for parseJSON when the type is an instance of Generic.

genericLiftParseJSON :: (Generic1 f, GFromJSON One (Rep1 f)) => Options -> (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (f a) Source #

A configurable generic JSON decoder. This function applied to defaultOptions is used as the default for liftParseJSON when the type is an instance of Generic1.

Inspecting Values

withObject :: String -> (Object -> Parser a) -> Value -> Parser a Source #

withObject expected f value applies f to the Object when value is an Object and fails using typeMismatch expected otherwise.

withText :: String -> (Text -> Parser a) -> Value -> Parser a Source #

withText expected f value applies f to the Text when value is a String and fails using typeMismatch expected otherwise.

withArray :: String -> (Array -> Parser a) -> Value -> Parser a Source #

withArray expected f value applies f to the Array when value is an Array and fails using typeMismatch expected otherwise.

withNumber :: String -> (Number -> Parser a) -> Value -> Parser a Source #

Deprecated: Use withScientific instead

withNumber expected f value applies f to the Number when value is a Number. and fails using typeMismatch expected otherwise.

withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a Source #

withScientific expected f value applies f to the Scientific number when value is a Number. and fails using typeMismatch expected otherwise.

withBool :: String -> (Bool -> Parser a) -> Value -> Parser a Source #

withBool expected f value applies f to the Bool when value is a Bool and fails using typeMismatch expected otherwise.

Constructors and accessors

data Series Source #

A series of values that, when encoded, should be separated by commas. Since 0.11.0.0, the .= operator is overloaded to create either (Text, Value) or Series. You can use Series when encoding directly to a bytestring builder as in the following example:

toEncoding (Person name age) = pairs ("name" .= name <> "age" .= age)

pairs :: Series -> Encoding Source #

Encode a series of key/value pairs, separated by commas.

foldable :: (Foldable t, ToJSON a) => t a -> Encoding Source #

Encode a Foldable as a JSON array.

(.:) :: FromJSON a => Object -> Text -> Parser 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.

(.:?) :: FromJSON a => Object -> Text -> Parser (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.

(.:!) :: FromJSON a => Object -> Text -> Parser (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 parse Null the same as any other JSON value, instead of interpreting it as Nothing.

(.!=) :: Parser (Maybe a) -> a -> Parser a Source #

Helper for use in combination with .:? to provide default values for optional JSON object fields.

This combinator is most useful if the key and value can be absent from an object without affecting its validity and we know a default value to assign in that case. If the key and value are mandatory, use .: instead.

Example usage:

 v1 <- o .:? "opt_field_with_dfl" .!= "default_val"
 v2 <- o .:  "mandatory_field"
 v3 <- o .:? "opt_field2"

object :: [Pair] -> Value Source #

Create a Value from a list of name/value Pairs. If duplicate keys arise, earlier keys and their associated values win.

Parsing

json :: Parser Value Source #

Parse a top-level JSON value.

The conversion of a parsed value to a Haskell value is deferred until the Haskell value is needed. This may improve performance if only a subset of the results of conversions are needed, but at a cost in thunk allocation.

This function is an alias for value. In aeson 0.8 and earlier, it parsed only object or array types, in conformance with the now-obsolete RFC 4627.

json' :: Parser Value Source #

Parse a top-level JSON value.

This is a strict version of json which avoids building up thunks during parsing; it performs all conversions immediately. Prefer this version if most of the JSON data needs to be accessed.

This function is an alias for value'. In aeson 0.8 and earlier, it parsed only object or array types, in conformance with the now-obsolete RFC 4627.