aeson-1.1.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 HaskellNone
LanguageHaskell2010

Data.Aeson.Types

Contents

Description

Types for working with JSON data.

Synopsis

Core JSON types

data Value #

A JSON value represented as a Haskell value.

Instances

Eq Value # 

Methods

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

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

Data Value # 

Methods

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

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

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

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

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

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

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

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

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

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

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

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

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

Read Value # 
Show Value # 

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

IsString Value # 

Methods

fromString :: String -> Value #

Lift Value # 

Methods

lift :: Value -> Q Exp #

NFData Value # 

Methods

rnf :: Value -> () #

Hashable Value # 

Methods

hashWithSalt :: Int -> Value -> Int #

hash :: Value -> Int #

FromJSON Value # 
KeyValue Pair # 

Methods

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

ToJSON Value # 

type Encoding = Encoding' Value #

Often used synonnym for Encoding'.

unsafeToEncoding :: Builder -> Encoding' a #

Make Encoding from Builder.

Use with care! You have to make sure that the passed Builder is a valid JSON Encoding!

fromEncoding :: Encoding' tag -> Builder #

Acquire the underlying bytestring builder.

data Series #

A series of values that, when encoded, should be separated by commas. Since 0.11.0.0, the .= operator is overloaded to create either (Text, Value) or Series. You can use Series when encoding directly to a bytestring builder as in the following example:

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

Instances

type Array = Vector Value #

A JSON "array" (sequence).

emptyArray :: Value #

The empty array.

type Pair = (Text, Value) #

A key/value pair for an Object.

type Object = HashMap Text Value #

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

emptyObject :: Value #

The empty object.

Convenience types and functions

newtype DotNetTime #

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

typeMismatch #

Arguments

:: String

The name of the type you are trying to parse.

-> Value

The actual value encountered.

-> Parser a 

Fail parsing due to a type mismatch, with a descriptive message.

Example usage:

instance FromJSON Coord where
  parseJSON (Object v) = {- type matches, life is good -}
  parseJSON wat        = typeMismatch "Coord" wat

Type conversion

data Parser a #

A JSON parser.

Instances

Monad Parser # 

Methods

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

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

return :: a -> Parser a #

fail :: String -> Parser a #

Functor Parser # 

Methods

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

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

MonadFail Parser # 

Methods

fail :: String -> Parser a #

Applicative Parser # 

Methods

pure :: a -> Parser a #

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

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

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

Alternative Parser # 

Methods

empty :: Parser a #

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

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

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

MonadPlus Parser # 

Methods

mzero :: Parser a #

mplus :: Parser a -> Parser a -> Parser a #

Semigroup (Parser a) # 

Methods

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

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

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

Monoid (Parser a) # 

Methods

mempty :: Parser a #

mappend :: Parser a -> Parser a -> Parser a #

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

data Result a #

The result of running a Parser.

Constructors

Error String 
Success a 

Instances

Monad Result # 

Methods

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

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

return :: a -> Result a #

fail :: String -> Result a #

Functor Result # 

Methods

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

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

MonadFail Result # 

Methods

fail :: String -> Result a #

Applicative Result # 

Methods

pure :: a -> Result a #

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

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

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

Foldable Result # 

Methods

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

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

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

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

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

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

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

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

toList :: Result a -> [a] #

null :: Result a -> Bool #

length :: Result a -> Int #

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

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

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

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

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

Traversable Result # 

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 # 

Methods

empty :: Result a #

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

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

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

MonadPlus Result # 

Methods

mzero :: Result a #

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

Eq a => Eq (Result a) # 

Methods

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

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

Show a => Show (Result a) # 

Methods

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

show :: Result a -> String #

showList :: [Result a] -> ShowS #

Semigroup (Result a) # 

Methods

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

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

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

Monoid (Result a) # 

Methods

mempty :: Result a #

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

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

NFData a => NFData (Result a) # 

Methods

rnf :: Result a -> () #

class FromJSON a where #

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

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

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

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

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

An example type and instance using typeMismatch:

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

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

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

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

For this common case of only being concerned with a single type of JSON value, the functions withObject, withNumber, 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

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

Instances

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

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

FromJSON Ordering # 
FromJSON Word # 
FromJSON Word8 # 
FromJSON Word16 # 
FromJSON Word32 # 
FromJSON Word64 # 
FromJSON () # 

Methods

parseJSON :: Value -> Parser () #

parseJSONList :: Value -> Parser [()] #

FromJSON Text # 
FromJSON Text # 
FromJSON Number # 
FromJSON Natural # 
FromJSON Version # 
FromJSON IntSet # 
FromJSON Scientific # 
FromJSON LocalTime # 
FromJSON ZonedTime # 
FromJSON TimeOfDay # 
FromJSON UTCTime # 
FromJSON NominalDiffTime #

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

FromJSON Day # 
FromJSON UUID # 
FromJSON DotNetTime # 
FromJSON Value # 
FromJSON a => FromJSON [a] # 

Methods

parseJSON :: Value -> Parser [a] #

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

FromJSON a => FromJSON (Maybe a) # 
(FromJSON a, Integral a) => FromJSON (Ratio a) # 
FromJSON a => FromJSON (Identity a) # 
FromJSON a => FromJSON (Min a) # 

Methods

parseJSON :: Value -> Parser (Min a) #

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

FromJSON a => FromJSON (Max a) # 

Methods

parseJSON :: Value -> Parser (Max a) #

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

FromJSON a => FromJSON (First a) # 
FromJSON a => FromJSON (Last a) # 
FromJSON a => FromJSON (WrappedMonoid a) # 
FromJSON a => FromJSON (Option a) # 
FromJSON a => FromJSON (NonEmpty a) # 
HasResolution a => FromJSON (Fixed a) #

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

FromJSON a => FromJSON (Dual a) # 
FromJSON a => FromJSON (First a) # 
FromJSON a => FromJSON (Last a) # 
FromJSON a => FromJSON (IntMap a) # 
FromJSON v => FromJSON (Tree v) # 
FromJSON a => FromJSON (Seq a) # 

Methods

parseJSON :: Value -> Parser (Seq a) #

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

(Ord a, FromJSON a) => FromJSON (Set a) # 

Methods

parseJSON :: Value -> Parser (Set a) #

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

FromJSON a => FromJSON (DList a) # 
(Eq a, Hashable a, FromJSON a) => FromJSON (HashSet a) # 
FromJSON a => FromJSON (Vector a) # 
(Storable a, FromJSON a) => FromJSON (Vector a) # 
(Vector Vector a, FromJSON a) => FromJSON (Vector a) # 
(Prim a, FromJSON a) => FromJSON (Vector a) # 
(FromJSON a, FromJSON b) => FromJSON (Either a b) # 

Methods

parseJSON :: Value -> Parser (Either a b) #

parseJSONList :: Value -> Parser [Either a b] #

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

Methods

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

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

FromJSON (Proxy k a) # 

Methods

parseJSON :: Value -> Parser (Proxy k a) #

parseJSONList :: Value -> Parser [Proxy k a] #

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

Methods

parseJSON :: Value -> Parser (Map k v) #

parseJSONList :: Value -> Parser [Map k v] #

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

Methods

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

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

FromJSON a => FromJSON (Const k a b) # 

Methods

parseJSON :: Value -> Parser (Const k a b) #

parseJSONList :: Value -> Parser [Const k a b] #

FromJSON b => FromJSON (Tagged k a b) # 

Methods

parseJSON :: Value -> Parser (Tagged k a b) #

parseJSONList :: Value -> Parser [Tagged k a b] #

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

(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) # 

Methods

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

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

(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) # 

Methods

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

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

(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) # 

Methods

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

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

(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) # 

Methods

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

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

(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) # 

Methods

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

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

(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) # 

Methods

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

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

(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) # 

Methods

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

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

(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) # 

Methods

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

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

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

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

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

Run a Parser.

parseEither :: (a -> Parser b) -> a -> Either String b #

Run a Parser with an Either result type. If the parse fails, the Left payload will contain an error message.

parseMaybe :: (a -> Parser b) -> a -> Maybe b #

Run a Parser with a Maybe result type.

class ToJSON a where #

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

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

Methods

toJSON :: a -> Value #

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

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

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

toEncoding :: a -> Encoding #

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 #

toEncodingList :: [a] -> Encoding #

Instances

ToJSON Bool # 
ToJSON Char # 
ToJSON Double # 
ToJSON Float # 
ToJSON Int # 
ToJSON Int8 # 
ToJSON Int16 # 
ToJSON Int32 # 
ToJSON Int64 # 
ToJSON Integer # 
ToJSON Ordering # 
ToJSON Word # 
ToJSON Word8 # 
ToJSON Word16 # 
ToJSON Word32 # 
ToJSON Word64 # 
ToJSON () # 

Methods

toJSON :: () -> Value #

toEncoding :: () -> Encoding #

toJSONList :: [()] -> Value #

toEncodingList :: [()] -> Encoding #

ToJSON Text # 
ToJSON Text # 
ToJSON Number # 
ToJSON Natural # 
ToJSON Version # 
ToJSON IntSet # 
ToJSON Scientific # 
ToJSON LocalTime # 
ToJSON ZonedTime # 
ToJSON TimeOfDay # 
ToJSON UTCTime # 
ToJSON NominalDiffTime # 
ToJSON Day # 
ToJSON UUID # 
ToJSON DotNetTime # 
ToJSON Value # 
ToJSON a => ToJSON [a] # 

Methods

toJSON :: [a] -> Value #

toEncoding :: [a] -> Encoding #

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

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

ToJSON a => ToJSON (Maybe a) # 
(ToJSON a, Integral a) => ToJSON (Ratio a) # 
ToJSON a => ToJSON (Identity a) # 
ToJSON a => ToJSON (Min a) # 

Methods

toJSON :: Min a -> Value #

toEncoding :: Min a -> Encoding #

toJSONList :: [Min a] -> Value #

toEncodingList :: [Min a] -> Encoding #

ToJSON a => ToJSON (Max a) # 

Methods

toJSON :: Max a -> Value #

toEncoding :: Max a -> Encoding #

toJSONList :: [Max a] -> Value #

toEncodingList :: [Max a] -> Encoding #

ToJSON a => ToJSON (First a) # 
ToJSON a => ToJSON (Last a) # 
ToJSON a => ToJSON (WrappedMonoid a) # 
ToJSON a => ToJSON (Option a) # 
ToJSON a => ToJSON (NonEmpty a) # 
HasResolution a => ToJSON (Fixed a) # 
ToJSON a => ToJSON (Dual a) # 
ToJSON a => ToJSON (First a) # 
ToJSON a => ToJSON (Last a) # 
ToJSON a => ToJSON (IntMap a) # 
ToJSON v => ToJSON (Tree v) # 
ToJSON a => ToJSON (Seq a) # 

Methods

toJSON :: Seq a -> Value #

toEncoding :: Seq a -> Encoding #

toJSONList :: [Seq a] -> Value #

toEncodingList :: [Seq a] -> Encoding #

ToJSON a => ToJSON (Set a) # 

Methods

toJSON :: Set a -> Value #

toEncoding :: Set a -> Encoding #

toJSONList :: [Set a] -> Value #

toEncodingList :: [Set a] -> Encoding #

ToJSON a => ToJSON (DList a) # 
ToJSON a => ToJSON (HashSet a) # 
ToJSON a => ToJSON (Vector a) # 
(Storable a, ToJSON a) => ToJSON (Vector a) # 
(Vector Vector a, ToJSON a) => ToJSON (Vector a) # 
(Prim a, ToJSON a) => ToJSON (Vector a) # 
(ToJSON a, ToJSON b) => ToJSON (Either a b) # 

Methods

toJSON :: Either a b -> Value #

toEncoding :: Either a b -> Encoding #

toJSONList :: [Either a b] -> Value #

toEncodingList :: [Either a b] -> Encoding #

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

Methods

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

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

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

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

ToJSON (Proxy k a) # 

Methods

toJSON :: Proxy k a -> Value #

toEncoding :: Proxy k a -> Encoding #

toJSONList :: [Proxy k a] -> Value #

toEncodingList :: [Proxy k a] -> Encoding #

(ToJSON v, ToJSONKey k) => ToJSON (Map k v) # 

Methods

toJSON :: Map k v -> Value #

toEncoding :: Map k v -> Encoding #

toJSONList :: [Map k v] -> Value #

toEncodingList :: [Map k v] -> Encoding #

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

Methods

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

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

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

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

ToJSON a => ToJSON (Const k a b) # 

Methods

toJSON :: Const k a b -> Value #

toEncoding :: Const k a b -> Encoding #

toJSONList :: [Const k a b] -> Value #

toEncodingList :: [Const k a b] -> Encoding #

ToJSON b => ToJSON (Tagged k a b) # 

Methods

toJSON :: Tagged k a b -> Value #

toEncoding :: Tagged k a b -> Encoding #

toJSONList :: [Tagged k a b] -> Value #

toEncodingList :: [Tagged k a b] -> Encoding #

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

toJSON :: Product * f g a -> Value #

toEncoding :: Product * f g a -> Encoding #

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

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

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

Methods

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

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

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

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

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

Methods

toJSON :: Compose * * f g a -> Value #

toEncoding :: Compose * * f g a -> Encoding #

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

(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) # 

Methods

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

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

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

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

(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) # 

Methods

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

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

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

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

(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) # 

Methods

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

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

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

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

(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) # 

Methods

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

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

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

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

(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) # 

Methods

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

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

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

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

(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) # 

Methods

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

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

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

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

(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) # 

Methods

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

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

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

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

(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) # 

Methods

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

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

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

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

class KeyValue kv where #

A key-value pair for encoding a JSON object.

Minimal complete definition

(.=)

Methods

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

Instances

KeyValue Pair # 

Methods

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

KeyValue Series # 

Methods

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

modifyFailure :: (String -> String) -> Parser a -> Parser a #

If the inner Parser failed, modify the failure message using the provided function. This allows you to create more descriptive error messages. For example:

parseJSON (Object o) = modifyFailure
    ("Parsing of the Foo value failed: " ++)
    (Foo <$> o .: "someField")

Since 0.6.2.0

Keys for maps

class ToJSONKey a where #

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

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

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

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

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

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

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

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

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

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

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

That's it. We can now write:

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

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

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

Then we may write:

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

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

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

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

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

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

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

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

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

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

Methods

toJSONKey :: ToJSONKeyFunction a #

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

toJSONKey :: ToJSON a => ToJSONKeyFunction a #

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

toJSONKeyList :: ToJSONKeyFunction [a] #

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

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

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

Instances

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

Methods

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

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

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

Methods

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

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

data ToJSONKeyFunction a #

Constructors

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

key is encoded to string, produces object

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

key is encoded to value, produces array

toJSONKeyText :: (a -> Text) -> ToJSONKeyFunction a #

Helper for creating textual keys.

instance ToJSONKey MyKey where
    toJSONKey = toJSONKeyText myKeyToText
      where
        myKeyToText = Text.pack . show -- or showt from text-show

contramapToJSONKeyFunction :: (b -> a) -> ToJSONKeyFunction a -> ToJSONKeyFunction b #

Contravariant map, as ToJSONKeyFunction is a contravariant functor.

class FromJSONKey a where #

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

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

Methods

fromJSONKey :: FromJSONKeyFunction a #

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

fromJSONKey :: FromJSON a => FromJSONKeyFunction a #

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

fromJSONKeyList :: FromJSONKeyFunction [a] #

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

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

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

Instances

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

Methods

fromJSONKey :: FromJSONKeyFunction (a, b, c, d) #

fromJSONKeyList :: FromJSONKeyFunction [(a, b, c, d)] #

data FromJSONKeyFunction a #

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

Constructors

FromJSONKeyCoerce !(CoerceText a)

uses coerce (unsafeCoerce in older GHCs)

FromJSONKeyText !(Text -> a)

conversion from Text that always succeeds

FromJSONKeyTextParser !(Text -> Parser a)

conversion from Text that may fail

FromJSONKeyValue !(Value -> Parser a)

conversion for non-textual keys

Instances

Functor FromJSONKeyFunction #

Only law abiding up to interpretation

fromJSONKeyCoerce :: Coercible Text a => FromJSONKeyFunction a #

Construct FromJSONKeyFunction for types coercible from Text. This conversion is still unsafe, as Hashable and Eq instances of a should be compatible with Text i.e. hash values should be equal for wrapped values as well. This property will always be maintained if the Hashable and Eq instances are derived with generalized newtype deriving. compatible with Text i.e. hash values be equal for wrapped values as well.

On pre GHC 7.8 this is unconstrainted function.

coerceFromJSONKeyFunction :: Coercible a b => FromJSONKeyFunction a -> FromJSONKeyFunction b #

Semantically the same as coerceFromJSONKeyFunction = fmap coerce = coerce.

See note on fromJSONKeyCoerce.

mapFromJSONKeyFunction :: (a -> b) -> FromJSONKeyFunction a -> FromJSONKeyFunction b #

Same as fmap. Provided for the consistency with ToJSONKeyFunction.

Liftings to unary and binary type constructors

class FromJSON1 f where #

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)

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

Methods

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

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

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

Instances

FromJSON1 [] # 

Methods

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

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

FromJSON1 Maybe # 

Methods

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

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

FromJSON1 Identity # 

Methods

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

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

FromJSON1 Min # 

Methods

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

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

FromJSON1 Max # 

Methods

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

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

FromJSON1 First # 

Methods

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

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

FromJSON1 Last # 

Methods

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

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

FromJSON1 WrappedMonoid # 

Methods

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

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

FromJSON1 Option # 

Methods

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

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

FromJSON1 NonEmpty # 

Methods

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

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

FromJSON1 Dual # 

Methods

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

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

FromJSON1 First # 

Methods

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

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

FromJSON1 Last # 

Methods

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

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

FromJSON1 IntMap # 

Methods

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

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

FromJSON1 Tree # 

Methods

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

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

FromJSON1 Seq # 

Methods

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

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

FromJSON1 DList # 

Methods

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

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

FromJSON1 Vector # 

Methods

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

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

FromJSON a => FromJSON1 (Either a) # 

Methods

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

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

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

Methods

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

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

FromJSON1 (Proxy *) # 

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

FromJSON a => FromJSON1 (Const * a) # 

Methods

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

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

FromJSON1 (Tagged k a) # 

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Lift the standard parseJSON function through the type constructor.

class FromJSON2 f where #

Lifting of the FromJSON class to binary type constructors.

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

Minimal complete definition

liftParseJSON2

Methods

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

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

Instances

FromJSON2 Either # 

Methods

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

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

FromJSON2 (,) # 

Methods

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

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

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

Methods

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

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

FromJSON2 (Const *) # 

Methods

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

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

FromJSON2 (Tagged *) # 

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Methods

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

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

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

Lift the standard parseJSON function through the type constructor.

class ToJSON1 f where #

Lifting of the ToJSON class to unary type constructors.

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

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

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

For example:

{-# LANGUAGE DeriveGeneric #-}

import GHC.Generics

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

instance ToJSON a => ToJSON1 (Pair a)

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

customOptions = defaultOptions
                { fieldLabelModifier = map toUpper
                }

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

See also ToJSON.

Methods

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

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

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

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

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

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

Instances

ToJSON1 [] # 

Methods

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

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

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

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

ToJSON1 Maybe # 

Methods

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

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

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

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

ToJSON1 Identity # 

Methods

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

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

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

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

ToJSON1 Min # 

Methods

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

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

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

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

ToJSON1 Max # 

Methods

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

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

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

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

ToJSON1 First # 

Methods

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

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

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

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

ToJSON1 Last # 

Methods

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

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

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

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

ToJSON1 WrappedMonoid # 

Methods

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

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

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

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

ToJSON1 Option # 

Methods

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

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

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

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

ToJSON1 NonEmpty # 

Methods

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

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

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

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

ToJSON1 Dual # 

Methods

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

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

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

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

ToJSON1 First # 

Methods

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

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

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

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

ToJSON1 Last # 

Methods

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

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

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

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

ToJSON1 IntMap # 

Methods

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

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

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

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

ToJSON1 Tree # 

Methods

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

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

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

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

ToJSON1 Seq # 

Methods

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

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

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

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

ToJSON1 Set # 

Methods

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

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

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

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

ToJSON1 DList # 

Methods

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

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

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

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

ToJSON1 HashSet # 

Methods

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

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

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

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

ToJSON1 Vector # 

Methods

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

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

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

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

ToJSON a => ToJSON1 (Either a) # 

Methods

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

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

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

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

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

Methods

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

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

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

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

ToJSON1 (Proxy *) # 

Methods

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

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

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

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

ToJSONKey k => ToJSON1 (Map k) # 

Methods

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

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

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

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

ToJSONKey k => ToJSON1 (HashMap k) # 

Methods

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

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

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

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

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

Methods

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

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

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

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

ToJSON a => ToJSON1 (Const * a) # 

Methods

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

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

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

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

ToJSON1 (Tagged k a) # 

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Lift the standard toJSON function through the type constructor.

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

Lift the standard toEncoding function through the type constructor.

class ToJSON2 f where #

Lifting of the ToJSON class to binary type constructors.

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

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

Minimal complete definition

liftToJSON2, liftToEncoding2

Methods

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

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

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

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

Instances

ToJSON2 Either # 

Methods

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

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

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

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

ToJSON2 (,) # 

Methods

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

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

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

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

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

Methods

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

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

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

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

ToJSON2 (Const *) # 

Methods

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

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

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

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

ToJSON2 (Tagged *) # 

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Methods

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

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

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

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

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

Lift the standard toJSON function through the type constructor.

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

Lift the standard toEncoding function through the type constructor.

Generic JSON classes

class GFromJSON arity f where #

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

Minimal complete definition

gParseJSON

Methods

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

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

Instances

GFromJSON arity U1 # 

Methods

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

GFromJSON One Par1 # 

Methods

gParseJSON :: Options -> FromArgs One a -> Value -> Parser (Par1 a) #

FromJSON1 f => GFromJSON One (Rec1 f) # 

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

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

Methods

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

data FromArgs arity a where #

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

Constructors

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

class GToJSON arity f where #

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

Minimal complete definition

gToJSON

Methods

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

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

Instances

GToJSON arity U1 # 

Methods

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

GToJSON One Par1 # 

Methods

gToJSON :: Options -> ToArgs Value One a -> Par1 a -> Value #

ToJSON1 f => GToJSON One (Rec1 f) # 

Methods

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

(AllNullary ((:+:) a b) allNullary, SumToJSON * arity ((:+:) a b) allNullary) => GToJSON arity ((:+:) a b) # 

Methods

gToJSON :: Options -> ToArgs Value arity a -> (a :+: b) a -> Value #

(WriteProduct arity a, WriteProduct arity b, ProductSize a, ProductSize b) => GToJSON arity ((:*:) a b) # 

Methods

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

ConsToJSON arity a => GToJSON arity (C1 c a) # 

Methods

gToJSON :: Options -> ToArgs Value arity a -> C1 c a a -> Value #

ToJSON a => GToJSON arity (K1 i a) # 

Methods

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

(ToJSON1 f, GToJSON One g) => GToJSON One ((:.:) f g) # 

Methods

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

GToJSON arity a => GToJSON arity (M1 i c a) # 

Methods

gToJSON :: Options -> ToArgs Value arity a -> M1 i c a a -> Value #

class GToEncoding arity f where #

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

Minimal complete definition

gToEncoding

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> f a -> Encoding #

This method (applied to defaultOptions) can be used as the default generic implementation of toEncoding (if the arity is Zero) or liftToEncoding (if the arity is One).

Instances

GToEncoding arity U1 # 

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> U1 a -> Encoding #

GToEncoding One Par1 # 
ToJSON1 f => GToEncoding One (Rec1 f) # 

Methods

gToEncoding :: Options -> ToArgs Encoding One a -> Rec1 f a -> Encoding #

(AllNullary ((:+:) a b) allNullary, SumToEncoding * arity ((:+:) a b) allNullary) => GToEncoding arity ((:+:) a b) # 

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> (a :+: b) a -> Encoding #

(EncodeProduct arity a, EncodeProduct arity b) => GToEncoding arity ((:*:) a b) # 

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> (a :*: b) a -> Encoding #

ConsToEncoding arity a => GToEncoding arity (C1 c a) # 

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> C1 c a a -> Encoding #

ToJSON a => GToEncoding arity (K1 i a) # 

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> K1 i a a -> Encoding #

(ToJSON1 f, GToEncoding One g) => GToEncoding One ((:.:) f g) # 

Methods

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

GToEncoding arity a => GToEncoding arity (M1 i c a) # 

Methods

gToEncoding :: Options -> ToArgs Encoding arity a -> M1 i c a a -> Encoding #

data ToArgs res arity a where #

A ToArgs value either stores nothing (for ToJSON) or it stores the two function arguments that encode occurrences of the type parameter (for ToJSON1).

Constructors

NoToArgs :: ToArgs res Zero a 
To1Args :: (a -> res) -> ([a] -> res) -> ToArgs res One a 

data Zero #

A type-level indicator that ToJSON or FromJSON is being derived generically.

data One #

A type-level indicator that ToJSON1 or FromJSON1 is being derived generically.

Instances

GFromJSON One Par1 # 

Methods

gParseJSON :: Options -> FromArgs One a -> Value -> Parser (Par1 a) #

GToEncoding One Par1 # 
GToJSON One Par1 # 

Methods

gToJSON :: Options -> ToArgs Value One a -> Par1 a -> Value #

FromJSON1 f => GFromJSON One (Rec1 f) # 

Methods

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

ToJSON1 f => GToEncoding One (Rec1 f) # 

Methods

gToEncoding :: Options -> ToArgs Encoding One a -> Rec1 f a -> Encoding #

ToJSON1 f => GToJSON One (Rec1 f) # 

Methods

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

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

Methods

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

(ToJSON1 f, GToEncoding One g) => GToEncoding One ((:.:) f g) # 

Methods

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

(ToJSON1 f, GToJSON One g) => GToJSON One ((:.:) f g) # 

Methods

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

genericToJSON :: (Generic a, GToJSON Zero (Rep a)) => Options -> a -> Value #

A configurable generic JSON creator. This function applied to defaultOptions is used as the default for toJSON when the type is an instance of Generic.

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

A configurable generic JSON creator. This function applied to defaultOptions is used as the default for liftToJSON when the type is an instance of Generic1.

genericToEncoding :: (Generic a, GToEncoding Zero (Rep a)) => Options -> a -> Encoding #

A configurable generic JSON encoder. This function applied to defaultOptions is used as the default for toEncoding when the type is an instance of Generic.

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

A configurable generic JSON encoder. This function applied to defaultOptions is used as the default for liftToEncoding when the type is an instance of Generic1.

genericParseJSON :: (Generic a, GFromJSON Zero (Rep a)) => Options -> Value -> Parser a #

A configurable generic JSON decoder. This function applied to defaultOptions is used as the default for parseJSON when the type is an instance of Generic.

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

A configurable generic JSON decoder. This function applied to defaultOptions is used as the default for liftParseJSON when the type is an instance of Generic1.

Inspecting Values

withObject :: String -> (Object -> Parser a) -> Value -> Parser a #

withObject expected f value applies f to the Object when value is an Object and fails using typeMismatch expected otherwise.

withText :: String -> (Text -> Parser a) -> Value -> Parser a #

withText expected f value applies f to the Text when value is a String and fails using typeMismatch expected otherwise.

withArray :: String -> (Array -> Parser a) -> Value -> Parser a #

withArray expected f value applies f to the Array when value is an Array and fails using typeMismatch expected otherwise.

withNumber :: String -> (Number -> Parser a) -> Value -> Parser a #

Deprecated: Use withScientific instead

withNumber expected f value applies f to the Number when value is a Number and fails using typeMismatch expected otherwise.

withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a #

withScientific expected f value applies f to the Scientific number when value is a Number and fails using typeMismatch expected otherwise.

withBool :: String -> (Bool -> Parser a) -> Value -> Parser a #

withBool expected f value applies f to the Bool when value is a Bool and fails using typeMismatch expected otherwise.

pairs :: Series -> Encoding #

Encode a series of key/value pairs, separated by commas.

foldable :: (Foldable t, ToJSON a) => t a -> Encoding #

Encode a Foldable as a JSON array.

(.:) :: FromJSON a => Object -> Text -> Parser a #

Retrieve the value associated with the given key of an Object. The result is empty if the key is not present or the value cannot be converted to the desired type.

This accessor is appropriate if the key and value must be present in an object for it to be valid. If the key and value are optional, use .:? instead.

(.:?) :: FromJSON a => Object -> Text -> Parser (Maybe a) #

Retrieve the value associated with the given key of an Object. The result is Nothing if the key is not present or if its value is Null, or empty if the value cannot be converted to the desired type.

This accessor is most useful if the key and value can be absent from an object without affecting its validity. If the key and value are mandatory, use .: instead.

(.:!) :: FromJSON a => Object -> Text -> Parser (Maybe a) #

Retrieve the value associated with the given key of an Object. The result is Nothing if the key is not present or empty if the value cannot be converted to the desired type.

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

(.!=) :: Parser (Maybe a) -> a -> Parser a #

Helper for use in combination with .:? to provide default values for optional JSON object fields.

This combinator is most useful if the key and value can be absent from an object without affecting its validity and we know a default value to assign in that case. If the key and value are mandatory, use .: instead.

Example usage:

 v1 <- o .:? "opt_field_with_dfl" .!= "default_val"
 v2 <- o .:  "mandatory_field"
 v3 <- o .:? "opt_field2"

object :: [Pair] -> Value #

Create a Value from a list of name/value Pairs. If duplicate keys arise, earlier keys and their associated values win.

parseField :: FromJSON a => Object -> Text -> Parser a #

Function variant of .:.

parseFieldMaybe :: FromJSON a => Object -> Text -> Parser (Maybe a) #

Function variant of .:?.

parseFieldMaybe' :: FromJSON a => Object -> Text -> Parser (Maybe a) #

Function variant of .:!.

explicitParseField :: (Value -> Parser a) -> Object -> Text -> Parser a #

Variant of .: with explicit parser function.

E.g. explicitParseField parseJSON1 :: (FromJSON1 f, FromJSON a) -> Object -> Text -> Parser (f a)

explicitParseFieldMaybe :: (Value -> Parser a) -> Object -> Text -> Parser (Maybe a) #

Variant of .:? with explicit parser function.

explicitParseFieldMaybe' :: (Value -> Parser a) -> Object -> Text -> Parser (Maybe a) #

Variant of .:! with explicit parser function.

listEncoding :: (a -> Encoding) -> [a] -> Encoding #

Helper function to use with liftToEncoding. Useful when writing own ToJSON1 instances.

newtype F a = F [a]

-- This instance encodes String as an array of chars
instance ToJSON1 F where
    liftToJSON     tj _ (F xs) = liftToJSON     tj (listValue    tj) xs
    liftToEncoding te _ (F xs) = liftToEncoding te (listEncoding te) xs

instance FromJSON1 F where
    liftParseJSON p _ v = F <$> liftParseJSON p (listParser p) v

listValue :: (a -> Value) -> [a] -> Value #

Helper function to use with liftToJSON, see listEncoding.

listParser :: (Value -> Parser a) -> Value -> Parser [a] #

Helper function to use with liftParseJSON. See listEncoding.

Generic and TH encoding configuration

data Options #

Options that specify how to encode/decode your datatype to/from JSON.

Constructors

Options 

Fields

Instances

data SumEncoding #

Specifies how to encode constructors of a sum datatype.

Constructors

TaggedObject

A constructor will be encoded to an object with a field tagFieldName which specifies the constructor tag (modified by the constructorTagModifier). If the constructor is a record the encoded record fields will be unpacked into this object. So make sure that your record doesn't have a field with the same label as the tagFieldName. Otherwise the tag gets overwritten by the encoded value of that field! If the constructor is not a record the encoded constructor contents will be stored under the contentsFieldName field.

UntaggedValue

Constructor names won't be encoded. Instead only the contents of the constructor will be encoded as if the type had a single constructor. JSON encodings have to be disjoint for decoding to work properly.

When decoding, constructors are tried in the order of definition. If some encodings overlap, the first one defined will succeed.

Note: Nullary constructors are encoded as strings (using constructorTagModifier). Having a nullary constructor alongside a single field constructor that encodes to a string leads to ambiguity.

Note: Only the last error is kept when decoding, so in the case of malformed JSON, only an error for the last constructor will be reported.

ObjectWithSingleField

A constructor will be encoded to an object with a single field named after the constructor tag (modified by the constructorTagModifier) which maps to the encoded contents of the constructor.

TwoElemArray

A constructor will be encoded to a 2-element array where the first element is the tag of the constructor (modified by the constructorTagModifier) and the second element the encoded contents of the constructor.

camelTo :: Char -> String -> String #

Deprecated: Use camelTo2 for better results

Converts from CamelCase to another lower case, interspersing the character between all capital letters and their previous entries, except those capital letters that appear together, like API.

For use by Aeson template haskell calls.

camelTo '_' 'CamelCaseAPI' == "camel_case_api"

camelTo2 :: Char -> String -> String #

Better version of camelTo. Example where it works better:

camelTo '_' 'CamelAPICase' == "camel_apicase"
camelTo2 '_' 'CamelAPICase' == "camel_api_case"

defaultTaggedObject :: SumEncoding #

Default TaggedObject SumEncoding options:

defaultTaggedObject = TaggedObject
                      { tagFieldName      = "tag"
                      , contentsFieldName = "contents"
                      }