aeson-2.2.2.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 HaskellSafe-Inferred
LanguageHaskell2010

Data.Aeson

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 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 = withObject "Person" $ \v -> Person
        <$> v .: "name"
        <*> v .: "age"

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]"

Remarks on specific encodings

Time

This module contains instances of ToJSON and FromJSON for types from the time library.

Those instances encode time as JSON strings in ISO 8601 formats, with the following general form for UTCTime and ZonedTime, while other time types use subsets of those fields:

[+,-]YYYY-MM-DDThh:mm[:ss[.sss]]Z

where

  • [+,-] is an optional sign, + or -.
  • YYYY is the year, which must have at least 4 digits to prevent Y2K problems. Years from 0000 to 0999 must thus be zero-padded.
  • MM is a two-digit month.
  • DD is a two-digit day.
  • T is a literal 'T' character separating the date and the time of day. It may be a space instead.
  • hh is a two-digit hour.
  • mm is a two-digit minute.
  • ss is a two-digit second.
  • sss is a decimal fraction of a second; it may have any nonzero number of digits.
  • Z is a time zone; it may be preceded by an optional space.

For more information, see ISO 8601 time, and attoparsec-iso8601 (where the relevant parsers are defined).

Main encoding and decoding functions

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.

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.

Since 2.2.0.0 an alias for decode.

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.

Since 2.2.0.0 an alias for eitherDecode.

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.

encodeFile :: ToJSON a => FilePath -> a -> IO () Source #

Efficiently serialize a JSON value as a lazy ByteString and write it to a file.

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.

decodeFileStrict :: FromJSON a => FilePath -> IO (Maybe a) Source #

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

The input file's content 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.

Since 2.2.0.0 an alias for decodeStrict.

decodeFileStrict' :: FromJSON a => FilePath -> IO (Maybe a) Source #

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

Since 2.2.0.0 an alias for decodeFileStrict.

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

Like decodeStrict but returns an error message when decoding fails.

eitherDecodeFileStrict :: FromJSON a => FilePath -> IO (Either String a) Source #

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

Since 2.2.0.0 an alias for eitherDecodeStrict.

eitherDecodeFileStrict' :: FromJSON a => FilePath -> IO (Either String a) Source #

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

Since 2.2.0.0 an alias for eitherDecodeFileStrict'.

Variants for strict text

decodeStrictText :: FromJSON a => Text -> Maybe a Source #

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

Since: 2.2.1.0

eitherDecodeStrictText :: FromJSON a => Text -> Either String a Source #

Like decodeStrictText but returns an error message when decoding fails.

Since: 2.2.1.0

Exception throwing variants

newtype AesonException Source #

Exception thrown by throwDecode and variants.

Since: 2.1.2.0

Constructors

AesonException String 

throwDecode :: forall a m. (FromJSON a, MonadThrow m) => ByteString -> m a Source #

Like decode but throws an AesonException when decoding fails.

throwDecode is in aeson since 2.1.2.0, but this variant is added later.

throwDecodeStrict :: forall a m. (FromJSON a, MonadThrow m) => ByteString -> m a Source #

Like decodeStrict but throws an AesonException when decoding fails.

throwDecodeStrictText :: forall a m. (FromJSON a, MonadThrow m) => Text -> m a Source #

Like decodeStrictText but throws an AesonException when decoding fails.

Since: 2.2.1.0

throwDecode' :: forall a m. (FromJSON a, MonadThrow m) => ByteString -> m a Source #

Like decode' but throws an AesonException when decoding fails.

Since 2.2.0.0 an alias for throwDecode.

Since: 2.1.2.0

throwDecodeStrict' :: forall a m. (FromJSON a, MonadThrow m) => ByteString -> m a Source #

Like decodeStrict' but throws an AesonException when decoding fails.

Since 2.2.0.0 an alias for throwDecodeStrict.

Since: 2.1.2.0

Core JSON types

data Value Source #

A JSON value represented as a Haskell value.

Instances

Instances details
Arbitrary Value Source #

Since: 2.0.3.0

Instance details

Defined in Data.Aeson.Types.Internal

Methods

arbitrary :: Gen Value #

shrink :: Value -> [Value] #

CoArbitrary Value Source #

Since: 2.0.3.0

Instance details

Defined in Data.Aeson.Types.Internal

Methods

coarbitrary :: Value -> Gen b -> Gen b #

Function Value Source #

Since: 2.0.3.0

Instance details

Defined in Data.Aeson.Types.Internal

Methods

function :: (Value -> b) -> Value :-> b #

FromJSON Value Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON Value Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Data Value Source # 
Instance details

Defined in Data.Aeson.Types.Internal

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 :: forall r r'. (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 #

IsString Value Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

fromString :: String -> Value #

Generic Value Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Associated Types

type Rep Value :: Type -> Type #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

Read Value Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Show Value Source #

Since version 1.5.6.0 version object values are printed in lexicographic key order

>>> toJSON $ H.fromList [("a", True), ("z", False)]
Object (fromList [("a",Bool True),("z",Bool False)])
>>> toJSON $ H.fromList [("z", False), ("a", True)]
Object (fromList [("a",Bool True),("z",Bool False)])
Instance details

Defined in Data.Aeson.Types.Internal

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

NFData Value Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

rnf :: Value -> () #

Eq Value Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

Ord Value Source #

The ordering is total, consistent with Eq instance. However, nothing else about the ordering is specified, and it may change from environment to environment and version to version of either this package or its dependencies (hashable and 'unordered-containers').

Since: 1.5.2.0

Instance details

Defined in Data.Aeson.Types.Internal

Methods

compare :: Value -> Value -> Ordering #

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

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

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

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

max :: Value -> Value -> Value #

min :: Value -> Value -> Value #

Hashable Value Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

hashWithSalt :: Int -> Value -> Int #

hash :: Value -> Int #

KeyValue Encoding Series Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

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

explicitToField :: (v -> Encoding) -> Key -> v -> Series Source #

KeyValueOmit Encoding Series Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

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

explicitToFieldOmit :: (v -> Bool) -> (v -> Encoding) -> Key -> v -> Series Source #

Lift Value Source #

Since: 0.11.0.0

Instance details

Defined in Data.Aeson.Types.Internal

Methods

lift :: Quote m => Value -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Value -> Code m Value #

GToJSON' Encoding arity (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding arity a -> U1 a -> Encoding

GToJSON' Encoding arity (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding arity a -> V1 a -> Encoding

GToJSON' Value arity (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a -> U1 a -> Value

GToJSON' Value arity (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a -> V1 a -> Value

ToJSON1 f => GToJSON' Encoding One (Rec1 f) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding One a -> Rec1 f a -> Encoding

ToJSON1 f => GToJSON' Value One (Rec1 f) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value One a -> Rec1 f a -> Value

(EncodeProduct arity a, EncodeProduct arity b) => GToJSON' Encoding arity (a :*: b) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding arity a0 -> (a :*: b) a0 -> Encoding

ToJSON a => GToJSON' Encoding arity (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding arity a0 -> K1 i a a0 -> Encoding

(WriteProduct arity a, WriteProduct arity b, ProductSize a, ProductSize b) => GToJSON' Value arity (a :*: b) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a0 -> (a :*: b) a0 -> Value

ToJSON a => GToJSON' Value arity (K1 i a :: Type -> Type) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value arity a0 -> K1 i a a0 -> Value

(ToJSON1 f, GToJSON' Encoding One g) => GToJSON' Encoding One (f :.: g) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Encoding One a -> (f :.: g) a -> Encoding

(ToJSON1 f, GToJSON' Value One g) => GToJSON' Value One (f :.: g) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

gToJSON :: Options -> ToArgs Value One a -> (f :.: g) a -> Value

value ~ Value => KeyValue Value (KeyMap value) Source #

Constructs a singleton KeyMap. For calling functions that demand an Object for constructing objects. To be used in conjunction with mconcat. Prefer to use object where possible.

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Key -> v -> KeyMap value Source #

explicitToField :: (v -> Value) -> Key -> v -> KeyMap value Source #

value ~ Value => KeyValueOmit Value (KeyMap value) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.?=) :: ToJSON v => Key -> v -> KeyMap value Source #

explicitToFieldOmit :: (v -> Bool) -> (v -> Value) -> Key -> v -> KeyMap value Source #

(key ~ Key, value ~ Value) => KeyValue Value (key, value) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Key -> v -> (key, value) Source #

explicitToField :: (v -> Value) -> Key -> v -> (key, value) Source #

type Rep Value Source # 
Instance details

Defined in Data.Aeson.Types.Internal

type Encoding = Encoding' Value Source #

Often used synonym for Encoding'.

fromEncoding :: Encoding' tag -> Builder Source #

Acquire the underlying bytestring builder.

type Array = Vector Value Source #

A JSON "array" (sequence).

type Object = KeyMap Value Source #

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

data Key Source #

Instances

Instances details
Arbitrary Key Source #

Since: 2.0.3.0

Instance details

Defined in Data.Aeson.Key

Methods

arbitrary :: Gen Key #

shrink :: Key -> [Key] #

CoArbitrary Key Source #

Since: 2.0.3.0

Instance details

Defined in Data.Aeson.Key

Methods

coarbitrary :: Key -> Gen b -> Gen b #

Function Key Source #

Since: 2.0.3.0

Instance details

Defined in Data.Aeson.Key

Methods

function :: (Key -> b) -> Key :-> b #

FromJSON Key Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Key Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON Key Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Key Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Data Key Source # 
Instance details

Defined in Data.Aeson.Key

Methods

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

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

toConstr :: Key -> Constr #

dataTypeOf :: Key -> DataType #

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

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

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

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

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

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

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

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

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

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

IsString Key Source # 
Instance details

Defined in Data.Aeson.Key

Methods

fromString :: String -> Key #

Monoid Key Source # 
Instance details

Defined in Data.Aeson.Key

Methods

mempty :: Key #

mappend :: Key -> Key -> Key #

mconcat :: [Key] -> Key #

Semigroup Key Source # 
Instance details

Defined in Data.Aeson.Key

Methods

(<>) :: Key -> Key -> Key #

sconcat :: NonEmpty Key -> Key #

stimes :: Integral b => b -> Key -> Key #

Read Key Source # 
Instance details

Defined in Data.Aeson.Key

Show Key Source # 
Instance details

Defined in Data.Aeson.Key

Methods

showsPrec :: Int -> Key -> ShowS #

show :: Key -> String #

showList :: [Key] -> ShowS #

NFData Key Source # 
Instance details

Defined in Data.Aeson.Key

Methods

rnf :: Key -> () #

Eq Key Source # 
Instance details

Defined in Data.Aeson.Key

Methods

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

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

Ord Key Source # 
Instance details

Defined in Data.Aeson.Key

Methods

compare :: Key -> Key -> Ordering #

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

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

(>) :: Key -> Key -> Bool #

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

max :: Key -> Key -> Key #

min :: Key -> Key -> Key #

Hashable Key Source # 
Instance details

Defined in Data.Aeson.Key

Methods

hashWithSalt :: Int -> Key -> Int #

hash :: Key -> Int #

FoldableWithIndex Key KeyMap Source # 
Instance details

Defined in Data.Aeson.KeyMap

Methods

ifoldMap :: Monoid m => (Key -> a -> m) -> KeyMap a -> m #

ifoldMap' :: Monoid m => (Key -> a -> m) -> KeyMap a -> m #

ifoldr :: (Key -> a -> b -> b) -> b -> KeyMap a -> b #

ifoldl :: (Key -> b -> a -> b) -> b -> KeyMap a -> b #

ifoldr' :: (Key -> a -> b -> b) -> b -> KeyMap a -> b #

ifoldl' :: (Key -> b -> a -> b) -> b -> KeyMap a -> b #

FunctorWithIndex Key KeyMap Source # 
Instance details

Defined in Data.Aeson.KeyMap

Methods

imap :: (Key -> a -> b) -> KeyMap a -> KeyMap b #

TraversableWithIndex Key KeyMap Source # 
Instance details

Defined in Data.Aeson.KeyMap

Methods

itraverse :: Applicative f => (Key -> a -> f b) -> KeyMap a -> f (KeyMap b) #

SemialignWithIndex Key KeyMap Source # 
Instance details

Defined in Data.Aeson.KeyMap

Methods

ialignWith :: (Key -> These a b -> c) -> KeyMap a -> KeyMap b -> KeyMap c #

ZipWithIndex Key KeyMap Source # 
Instance details

Defined in Data.Aeson.KeyMap

Methods

izipWith :: (Key -> a -> b -> c) -> KeyMap a -> KeyMap b -> KeyMap c #

Lift Key Source # 
Instance details

Defined in Data.Aeson.Key

Methods

lift :: Quote m => Key -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Key -> Code m Key #

FilterableWithIndex Key KeyMap Source # 
Instance details

Defined in Data.Aeson.KeyMap

Methods

imapMaybe :: (Key -> a -> Maybe b) -> KeyMap a -> KeyMap b #

ifilter :: (Key -> a -> Bool) -> KeyMap a -> KeyMap a #

WitherableWithIndex Key KeyMap Source # 
Instance details

Defined in Data.Aeson.KeyMap

Methods

iwither :: Applicative f => (Key -> a -> f (Maybe b)) -> KeyMap a -> f (KeyMap b) #

iwitherM :: Monad m => (Key -> a -> m (Maybe b)) -> KeyMap a -> m (KeyMap b) #

ifilterA :: Applicative f => (Key -> a -> f Bool) -> KeyMap a -> f (KeyMap a) #

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

Instances

Instances details
FromJSON DotNetTime Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

ToJSON DotNetTime Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Read DotNetTime Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Show DotNetTime Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Eq DotNetTime Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Ord DotNetTime Source # 
Instance details

Defined in Data.Aeson.Types.Internal

FormatTime DotNetTime Source # 
Instance details

Defined in Data.Aeson.Types.Internal

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:

  • fail yields a custom error message: it is the recommended way of reporting a failure;
  • empty (or mzero) is uninformative: use it when the error is meant to be caught by some (<|>);
  • typeMismatch can be used to report a failure when the encountered value is not of the expected JSON type; unexpected is an appropriate alternative when more than one type may be expected, or to keep the expected type implicit.

prependFailure (or modifyFailure) add more information to a parser's error messages.

An example type and instance using typeMismatch and prependFailure:

-- 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 empty to fail, but typeMismatch
    -- gives a much more informative error message.
    parseJSON invalid    =
        prependFailure "parsing Coord failed, "
            (typeMismatch "Object" invalid)

For this common case of only being concerned with a single type of JSON value, the functions withObject, withScientific, etc. are provided. Their use is to be preferred when possible, since they are more terse. Using withObject, we can rewrite the above instance (assuming the same language extension and data type) as:

instance FromJSON Coord where
    parseJSON = withObject "Coord" $ \v -> Coord
        <$> v .: "x"
        <*> v .: "y"

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 it will probably be more efficient than the following option.
  • 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

or using the DerivingVia extension

deriving via Generically Coord instance FromJSON Coord

The default implementation will be equivalent to parseJSON = genericParseJSON defaultOptions; if you need different options, you can customize the generic decoding by defining:

customOptions = defaultOptions
                { fieldLabelModifier = map toUpper
                }

instance FromJSON Coord where
    parseJSON = genericParseJSON customOptions

Minimal complete definition

Nothing

Methods

parseJSON :: Value -> Parser a Source #

default parseJSON :: (Generic a, GFromJSON Zero (Rep a)) => Value -> Parser a Source #

parseJSONList :: Value -> Parser [a] Source #

omittedField :: Maybe a Source #

Default value for optional fields. Used by (.:?=) operator, and Generics and TH deriving with allowOmittedFields = True (default).

Since: 2.2.0.0

Instances

Instances details
FromJSON Key Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON DotNetTime Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Value Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Version Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON CTime Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Void Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Int16 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Int32 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Int64 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Int8 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Word16 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Word32 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Word64 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Word8 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON IntSet Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Ordering Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON URI Source #

Since: 2.2.0.0

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Scientific Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Text Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Text Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON ShortText Source #

Since: 2.0.2.0

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON CalendarDiffDays Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Day Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Month Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Quarter Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON QuarterOfYear Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON DayOfWeek Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON DiffTime Source #

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

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON NominalDiffTime Source #

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

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON SystemTime Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON UTCTime Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON CalendarDiffTime Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON LocalTime Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON TimeOfDay Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON ZonedTime Source #

Supported string formats:

YYYY-MM-DD HH:MMZ YYYY-MM-DD HH:MM:SSZ YYYY-MM-DD HH:MM:SS.SSSZ

The first space may instead be a T, and the second space is optional. The Z represents UTC. The Z may be replaced with a time zone offset of the form +0000 or -08:00, where the first two digits are hours, the : is optional and the second two digits (also optional) are minutes.

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON UUID Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Integer Source #

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

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Natural Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON () Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Bool Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Char Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Double Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Float Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Int Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Word Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON v => FromJSON (KeyMap v) Source #

Since: 2.0.1.0

Instance details

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (Down a) Source #

Since: 2.2.0.0

Instance details

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

(Generic a, GFromJSON Zero (Rep a)) => FromJSON (Generically a) Source #

Since: 2.1.0.0

Instance details

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

FromJSON v => FromJSON (Tree v) Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON1 f => FromJSON (Fix f) Source #

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.FromJSON

(FromJSON1 f, Functor f) => FromJSON (Mu f) Source #

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.FromJSON

(FromJSON1 f, Functor f) => FromJSON (Nu f) Source #

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (DNonEmpty a) Source #

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (DList a) Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (Maybe a) Source #

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

(Prim a, FromJSON a) => FromJSON (Vector a) Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

(Storable a, FromJSON a) => FromJSON (Vector a) Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

(Vector Vector a, FromJSON a) => FromJSON (Vector a) Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

FromJSON a => FromJSON (a) Source #

Since: 2.0.2.0

Instance details

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

HasResolution a => FromJSON (Fixed a) Source #

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

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON (Proxy a) Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

(FromJSONKey k, Ord k, FromJSON v) => FromJSON (Map k v) Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.FromJSON

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

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.FromJSON

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

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.FromJSON

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

Since: 1.5.1.0

Instance details

Defined in Data.Aeson.Types.FromJSON

(FromJSON v, FromJSONKey k, Eq k, Hashable k) => FromJSON (HashMap k v) Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

omittedField :: Maybe (a, b) Source #

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Since: 1.5.1.0

Instance details

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

omittedField :: Maybe (a, b, c) Source #

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

omittedField :: Maybe (a, b, c, d) Source #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Compose f g a) Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

omittedField :: Maybe (a, b, c, d, e) Source #

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

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

omittedField :: Maybe (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 # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

omittedField :: Maybe (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 # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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 #

omittedField :: Maybe (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 # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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 #

omittedField :: Maybe (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 # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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 #

omittedField :: Maybe (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 # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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 #

omittedField :: Maybe (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 # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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 #

omittedField :: Maybe (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 # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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 #

omittedField :: Maybe (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 # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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 #

omittedField :: Maybe (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 # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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 #

omittedField :: Maybe (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

Instances details
MonadFail Result Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

fail :: String -> Result a #

Foldable Result Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

foldMap :: Monoid m => (a -> m) -> Result a -> 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 # 
Instance details

Defined in Data.Aeson.Types.Internal

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 # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

empty :: Result a #

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

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

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

Applicative Result Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

pure :: a -> Result a #

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

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

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

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

Functor Result Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

Monad Result Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

return :: a -> Result a #

MonadPlus Result Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

mzero :: Result a #

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

Monoid (Result a) Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

mempty :: Result a #

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

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

Semigroup (Result a) Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

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

Show a => Show (Result a) Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

show :: Result a -> String #

showList :: [Result a] -> ShowS #

NFData a => NFData (Result a) Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

rnf :: Result a -> () #

Eq a => Eq (Result a) Source # 
Instance details

Defined in Data.Aeson.Types.Internal

Methods

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

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

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.

Instances in general must specify toJSON and should (but don't need to) specify toEncoding.

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 it will probably be more efficient than the following option.
  • 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. If you require nothing other than defaultOptions, it is sufficient to write (and this is the only alternative where the default toJSON implementation is sufficient):

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

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

instance ToJSON Coord where
    toEncoding = genericToEncoding defaultOptions

or more conveniently using the DerivingVia extension

deriving via Generically Coord instance ToJSON Coord

If on the other hand you wish to customize the generic decoding, you have to implement both methods:

customOptions = defaultOptions
                { fieldLabelModifier = map toUpper
                }

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

Previous versions of this library only had the toJSON method. Adding toEncoding had two reasons:

  1. toEncoding is more efficient for the common case that the output of toJSON is directly serialized to a ByteString. Further, expressing either method in terms of the other would be non-optimal.
  2. The choice of defaults allows a smooth transition for existing users: Existing instances that do not define toEncoding still compile and have the correct semantics. This is ensured by making the default implementation of toEncoding use 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. (this also means that specifying nothing more than instance ToJSON Coord would be sufficient as a generically decoding instance, but there probably exists no good reason to not specify toEncoding in new instances.)

Minimal complete definition

Nothing

Methods

toJSON :: a -> Value Source #

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

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

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 #

omitField :: a -> Bool Source #

Defines when it is acceptable to omit a field of this type from a record. Used by (.?=) operator, and Generics and TH deriving with omitNothingFields = True.

Since: 2.2.0.0

Instances

Instances details
ToJSON Key Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON DotNetTime Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Value Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Version Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON CTime Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Void Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int16 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int32 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int64 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int8 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word16 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word32 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word64 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word8 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON IntSet Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Ordering Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON URI Source #

Since: 2.2.0.0

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Scientific Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Text Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Text Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON ShortText Source #

Since: 2.0.2.0

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON CalendarDiffDays Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Day Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Month Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Quarter Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON QuarterOfYear Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON DayOfWeek Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON DiffTime Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON NominalDiffTime Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON SystemTime Source #

Encoded as number

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON UTCTime Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON CalendarDiffTime Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON LocalTime Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON TimeOfDay Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON ZonedTime Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON UUID Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Integer Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Natural Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON () Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Bool Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Char Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Double Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Float Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Int Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Word Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON v => ToJSON (KeyMap v) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Down a) Source #

Since: 2.2.0.0

Instance details

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

(Generic a, GToJSON' Value Zero (Rep a), GToJSON' Encoding Zero (Rep a)) => ToJSON (Generically a) Source #

Since: 2.1.0.0

Instance details

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Set a) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON v => ToJSON (Tree v) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON1 f => ToJSON (Fix f) Source #

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

(ToJSON1 f, Functor f) => ToJSON (Mu f) Source #

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

(ToJSON1 f, Functor f) => ToJSON (Nu f) Source #

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (DNonEmpty a) Source #

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (DList a) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (Maybe a) Source #

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

(Prim a, ToJSON a) => ToJSON (Vector a) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Storable a, ToJSON a) => ToJSON (Vector a) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

(Vector Vector a, ToJSON a) => ToJSON (Vector a) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

ToJSON a => ToJSON (a) Source #

Since: 2.0.2.0

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a) -> Value Source #

toEncoding :: (a) -> Encoding Source #

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

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

omitField :: (a) -> Bool Source #

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

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: [a] -> Value Source #

toEncoding :: [a] -> Encoding Source #

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

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

omitField :: [a] -> Bool Source #

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

ToJSON (Proxy a) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

(ToJSON v, ToJSONKey k) => ToJSON (Map k v) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

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

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

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

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.ToJSON

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

Since: 1.5.1.0

Instance details

Defined in Data.Aeson.Types.ToJSON

(ToJSON v, ToJSONKey k) => ToJSON (HashMap k v) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

Methods

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

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

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

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

omitField :: (a, b) -> Bool Source #

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Since: 1.5.1.0

Instance details

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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 #

omitField :: (a, b, c) -> Bool Source #

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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 #

omitField :: Sum f g a -> Bool Source #

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

Defined in Data.Aeson.Types.ToJSON

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 #

omitField :: (a, b, c, d) -> Bool Source #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Compose f g a) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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 #

omitField :: (a, b, c, d, e) -> Bool Source #

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

Defined in Data.Aeson.Types.ToJSON

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 #

omitField :: (a, b, c, d, e, f) -> Bool Source #

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

Defined in Data.Aeson.Types.ToJSON

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 #

omitField :: (a, b, c, d, e, f, g) -> Bool 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 # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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 #

omitField :: (a, b, c, d, e, f, g, h) -> Bool 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 # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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 #

omitField :: (a, b, c, d, e, f, g, h, i) -> Bool 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 # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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 #

omitField :: (a, b, c, d, e, f, g, h, i, j) -> Bool 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 # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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 #

omitField :: (a, b, c, d, e, f, g, h, i, j, k) -> Bool 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 # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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 #

omitField :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool 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 # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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 #

omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool 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 # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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 #

omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool 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 # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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 #

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

class KeyValue e kv | kv -> e where Source #

A key-value pair for encoding a JSON object.

Methods

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

explicitToField :: (v -> e) -> Key -> v -> kv Source #

Since: 2.2.0.0

Instances

Instances details
KeyValue Encoding Series Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

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

explicitToField :: (v -> Encoding) -> Key -> v -> Series Source #

value ~ Value => KeyValue Value (KeyMap value) Source #

Constructs a singleton KeyMap. For calling functions that demand an Object for constructing objects. To be used in conjunction with mconcat. Prefer to use object where possible.

Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Key -> v -> KeyMap value Source #

explicitToField :: (v -> Value) -> Key -> v -> KeyMap value Source #

(key ~ Key, value ~ Value) => KeyValue Value (key, value) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.=) :: ToJSON v => Key -> v -> (key, value) Source #

explicitToField :: (v -> Value) -> Key -> v -> (key, value) Source #

class KeyValue e kv => KeyValueOmit e kv | kv -> e where Source #

An optional key-value pair for envoding to a JSON object

Since: 2.2.0.0

Methods

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

explicitToFieldOmit :: (v -> Bool) -> (v -> e) -> Key -> v -> kv Source #

Instances

Instances details
KeyValueOmit Encoding Series Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

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

explicitToFieldOmit :: (v -> Bool) -> (v -> Encoding) -> Key -> v -> Series Source #

value ~ Value => KeyValueOmit Value (KeyMap value) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

(.?=) :: ToJSON v => Key -> v -> KeyMap value Source #

explicitToFieldOmit :: (v -> Bool) -> (v -> Value) -> Key -> v -> KeyMap value Source #

(<?>) :: Parser a -> JSONPathElement -> Parser a Source #

Add JSON Path context to a parser

When parsing a complex structure, it helps to annotate (sub)parsers with context, so that if an error occurs, you can find its location.

withObject "Person" $ \o ->
  Person
    <$> o .: "name" <?> Key "name"
    <*> o .: "age"  <?> Key "age"

(Standard methods like (.:) already do this.)

With such annotations, if an error occurs, you will get a JSON Path location of that error.

Since 0.10

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 ToJSONKeyText can be used instead of ToJSONKeyValue to encode maps as objects instead of arrays of pairs. This instance may be implemented using generics as follows:

instance ToJSONKey Color where
  toJSONKey = genericToJSONKey defaultJSONKeyOptions

Low-level implementations

Expand

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

Minimal complete definition

Nothing

Methods

toJSONKey :: 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 Value keys special treatment without using OverlappingInstances. End users should always be able to use the default implementation of this method.

Instances

Instances details
ToJSONKey Key Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Version Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Void Source #

Since: 2.1.2.0

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Int16 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Int32 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Int64 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Int8 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Word16 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Word32 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Word64 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Word8 Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey URI Source #

Since: 2.2.0.0

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Scientific Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Text Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Text Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey ShortText Source #

Since: 2.0.2.0

Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Day Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Month Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Quarter Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey QuarterOfYear Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey DayOfWeek Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey UTCTime Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey LocalTime Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey TimeOfDay Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey ZonedTime Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey UUID Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Integer Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Natural Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Bool Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Char Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Double Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Float Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Int Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSONKey Word Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

ToJSONKey a => ToJSONKey (a) Source #

Since: 2.0.2.0

Instance details

Defined in Data.Aeson.Types.ToJSON

(ToJSONKey a, ToJSON a) => ToJSONKey [a] Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

(ToJSON a, ToJSON b) => ToJSONKey (a, b) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

(ToJSON a, ToJSONKey a) => ToJSONKey (Const a b) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

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

Defined in Data.Aeson.Types.ToJSON

Methods

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

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

data ToJSONKeyFunction a Source #

Constructors

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

key is encoded to string, produces object

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

key is encoded to value, produces array

Instances

Instances details
Contravariant ToJSONKeyFunction Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

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)

If you have a sum of nullary constructors, you may use the generic implementation:

data Color = Red | Green | Blue
  deriving Generic

instance FromJSONKey Color where
  fromJSONKey = genericFromJSONKey defaultJSONKeyOptions

Minimal complete definition

Nothing

Methods

fromJSONKey :: 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 Value keys special treatment without using OverlappingInstances. End users should always be able to use the default implementation of this method.

Instances

Instances details
FromJSONKey Key Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Version Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Void Source #

Since: 2.1.2.0

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Int16 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Int32 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Int64 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Int8 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Word16 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Word32 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Word64 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Word8 Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey URI Source #

Since: 2.2.0.0

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Text Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Text Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey ShortText Source #

Since: 2.0.2.0

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Day Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Month Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Quarter Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey QuarterOfYear Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey DayOfWeek Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey UTCTime Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey LocalTime Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey TimeOfDay Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey ZonedTime Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey UUID Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Integer Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Natural Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Bool Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Char Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Double Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Float Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Int Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Word Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

FromJSONKey a => FromJSONKey (a) Source #

Since: 2.0.2.0

Instance details

Defined in Data.Aeson.Types.FromJSON

(FromJSONKey a, FromJSON a) => FromJSONKey [a] Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

(FromJSON a, FromJSON b) => FromJSONKey (a, b) Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

(FromJSON a, FromJSONKey a) => FromJSONKey (Const a b) Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

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

Defined in Data.Aeson.Types.FromJSON

data FromJSONKeyFunction a where 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 

Fields

FromJSONKeyText 

Fields

FromJSONKeyTextParser 

Fields

FromJSONKeyValue 

Fields

Instances

Instances details
Functor FromJSONKeyFunction Source #

Only law abiding up to interpretation

Instance details

Defined in Data.Aeson.Types.FromJSON

Generic keys

class GetConName f => GToJSONKey f Source #

Instances

Instances details
GetConName f => GToJSONKey (f :: k -> Type) Source # 
Instance details

Defined in Data.Aeson.Types.ToJSON

class (ConstructorNames f, SumFromString f) => GFromJSONKey f Source #

Instances

Instances details
(ConstructorNames f, SumFromString f) => GFromJSONKey f Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

genericFromJSONKey :: forall a. (Generic a, GFromJSONKey (Rep a)) => JSONKeyOptions -> FromJSONKeyFunction a Source #

fromJSONKey for Generic types. These types must be sums of nullary constructors, whose names will be used as keys for JSON objects.

See also genericToJSONKey.

Example

Expand
data Color = Red | Green | Blue
  deriving Generic

instance FromJSONKey Color where
  fromJSONKey = genericFromJSONKey defaultJSONKeyOptions

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 it will probably be more efficient than the following option.
  • 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)

or

deriving via Generically1 (Pair a) instance FromJSON1 (Pair a)

If the default implementation 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:

customOptions = defaultOptions
                { fieldLabelModifier = map toUpper
                }

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

Minimal complete definition

Nothing

Methods

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

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

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

liftOmittedField :: Maybe a -> Maybe (f a) Source #

Instances

Instances details
FromJSON1 KeyMap Source #

Since: 2.0.1.0

Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (KeyMap a) Source #

FromJSON1 Identity Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (Identity a) Source #

FromJSON1 First Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (First a) Source #

FromJSON1 Last Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (Last a) Source #

FromJSON1 Down Source #

Since: 2.2.0.0

Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (Down a) Source #

FromJSON1 First Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (First a) Source #

FromJSON1 Last Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (Last a) Source #

FromJSON1 Max Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (Max a) Source #

FromJSON1 Min Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (Min a) Source #

FromJSON1 WrappedMonoid Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON1 Dual Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (Dual a) Source #

FromJSON1 NonEmpty Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (NonEmpty a) Source #

FromJSON1 IntMap Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (IntMap a) Source #

FromJSON1 Seq Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (Seq a) Source #

FromJSON1 Tree Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (Tree a) Source #

FromJSON1 DNonEmpty Source #

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON1 DList Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (DList a) Source #

FromJSON1 Maybe Source #

Since: 1.5.3.0

Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe0 a -> Maybe0 (Maybe a) Source #

FromJSON1 Vector Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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

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

liftOmittedField :: Maybe a -> Maybe (Vector a) Source #

FromJSON1 Maybe Source # 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

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