aeson-0.9.0.1: Fast JSON parsing and encoding

Copyright(c) 2011, 2012 Bryan O'Sullivan (c) 2011 MailRank, Inc.
LicenseApache
MaintainerBryan O'Sullivan <bos@serpentine.com>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell98

Data.Aeson.Types

Contents

Description

Types for working with JSON data.

Synopsis

Core JSON types

data Value Source

A JSON value represented as a Haskell value.

type Array = Vector Value Source

A JSON "array" (sequence).

emptyArray :: Value Source

The empty array.

type Pair = (Text, Value) Source

A key/value pair for an Object.

type Object = HashMap Text Value Source

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

emptyObject :: Value Source

The empty object.

Convenience types and functions

newtype DotNetTime Source

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

/Date(1302547608878)/

The number represents milliseconds since the Unix epoch.

Constructors

DotNetTime 

typeMismatch Source

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.

Type conversion

data Parser a Source

A continuation-based parser type.

data Result a Source

The result of running a Parser.

Constructors

Error String 
Success a 

class FromJSON a where Source

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

When writing an instance, use empty, mzero, or fail to make a conversion fail, e.g. if an Object is missing a required key, or the value is of the wrong type.

An example type and instance:

{-# LANGUAGE OverloadedStrings #-}

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

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

  -- A non-Object value is of the wrong type, so use mzero to fail.
  parseJSON _          = mzero

Note the use of the OverloadedStrings language extension which enables Text values to be written as string literals.

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

  • Data.Aeson.TH provides template-haskell functions which will derive an instance at compile-time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
  • Data.Aeson.Generic provides a generic fromJSON function that parses to any type which is an instance of Data.
  • If your compiler has support for the DeriveGeneric and DefaultSignatures language extensions, parseJSON will have a default generic implementation.

To use this, 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

Note that, instead of using DefaultSignatures, it's also possible to parameterize the generic decoding using genericParseJSON applied to your encoding/decoding Options:

instance FromJSON Coord where
    parseJSON = genericParseJSON defaultOptions

Minimal complete definition

Nothing

Methods

parseJSON :: Value -> Parser a Source

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 Word 
FromJSON Word8 
FromJSON Word16 
FromJSON Word32 
FromJSON Word64 
FromJSON () 
FromJSON Text 
FromJSON Text 
FromJSON Number 
FromJSON IntSet 
FromJSON Scientific 
FromJSON ZonedTime 
FromJSON UTCTime 
FromJSON DotNetTime 
FromJSON Value 
FromJSON [Char] 
FromJSON a => FromJSON [a] 
FromJSON (Ratio Integer) 
FromJSON a => FromJSON (Maybe 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) 
(Ord a, FromJSON a) => FromJSON (Set a) 
FromJSON v => FromJSON (Tree v) 
FromJSON a => FromJSON (Seq a) 
FromJSON a => FromJSON (Identity a) 
(Eq a, Hashable a, FromJSON a) => FromJSON (HashSet a) 
FromJSON a => FromJSON (Vector a) 
(Vector Vector a, FromJSON a) => FromJSON (Vector a) 
(Storable a, FromJSON a) => FromJSON (Vector a) 
(Prim a, FromJSON a) => FromJSON (Vector a) 
(FromJSON a, FromJSON b) => FromJSON (Either a b) 
(FromJSON a, FromJSON b) => FromJSON (a, b) 
FromJSON v => FromJSON (Map String v) 
FromJSON v => FromJSON (Map Text v) 
FromJSON v => FromJSON (Map Text v) 
FromJSON v => FromJSON (HashMap String v) 
FromJSON v => FromJSON (HashMap Text v) 
FromJSON v => FromJSON (HashMap Text v) 
(FromJSON a, FromJSON b, FromJSON c) => FromJSON (a, b, c) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d) => FromJSON (a, b, c, d) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e) => FromJSON (a, b, c, d, e) 
(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f) => FromJSON (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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 

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

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

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

Run a Parser.

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

Run a Parser with an Either result type.

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

Run a Parser with a Maybe result type.

class ToJSON a where Source

A type that can be converted to JSON.

An example type and instance:

@{-# LANGUAGE OverloadedStrings #-}

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

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

Note the use of the OverloadedStrings language extension which enables Text values to be written as string literals.

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

  • Data.Aeson.TH provides template-haskell functions which will derive an instance at compile-time. The generated instance is optimized for your type so will probably be more efficient than the following two options:
  • Data.Aeson.Generic provides a generic toJSON function that accepts any type which is an instance of Data.
  • If your compiler has support for the DeriveGeneric and DefaultSignatures language extensions (GHC 7.2 and newer), toJSON will have a default generic implementation.

To use the latter option, simply add a deriving Generic clause to your datatype and declare a ToJSON instance for your datatype without giving a definition for toJSON.

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 ToJSON Coord @

Note that, instead of using DefaultSignatures, it's also possible to parameterize the generic encoding using genericToJSON applied to your encoding/decoding Options:

instance ToJSON Coord where
    toJSON = genericToJSON defaultOptions

Minimal complete definition

Nothing

Methods

toJSON :: a -> Value Source

Instances

ToJSON Bool 
ToJSON Char 
ToJSON Double 
ToJSON Float 
ToJSON Int 
ToJSON Int8 
ToJSON Int16 
ToJSON Int32 
ToJSON Int64 
ToJSON Integer 
ToJSON Word 
ToJSON Word8 
ToJSON Word16 
ToJSON Word32 
ToJSON Word64 
ToJSON () 
ToJSON Text 
ToJSON Text 
ToJSON Number 
ToJSON IntSet 
ToJSON Scientific 
ToJSON ZonedTime 
ToJSON UTCTime 
ToJSON DotNetTime 
ToJSON Value 
ToJSON [Char] 
ToJSON a => ToJSON [a] 
ToJSON (Ratio Integer) 
ToJSON a => ToJSON (Maybe 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 a => ToJSON (Set a) 
ToJSON v => ToJSON (Tree v) 
ToJSON a => ToJSON (Seq a) 
ToJSON a => ToJSON (Identity a) 
ToJSON a => ToJSON (HashSet a) 
ToJSON a => ToJSON (Vector a) 
(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
(Storable a, ToJSON a) => ToJSON (Vector a) 
(Prim a, ToJSON a) => ToJSON (Vector a) 
(ToJSON a, ToJSON b) => ToJSON (Either a b) 
(ToJSON a, ToJSON b) => ToJSON (a, b) 
ToJSON v => ToJSON (Map String v) 
ToJSON v => ToJSON (Map Text v) 
ToJSON v => ToJSON (Map Text v) 
ToJSON v => ToJSON (HashMap String v) 
ToJSON v => ToJSON (HashMap Text v) 
ToJSON v => ToJSON (HashMap Text v) 
(ToJSON a, ToJSON b, ToJSON c) => ToJSON (a, b, c) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d) => ToJSON (a, b, c, d) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e) => ToJSON (a, b, c, d, e) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f) => ToJSON (a, b, c, d, e, f) 
(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g) => ToJSON (a, b, c, d, e, f, g) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 
(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) 

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

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

Generic JSON classes

class GFromJSON f where Source

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

Methods

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

This method (applied to defaultOptions) is used as the default generic implementation of parseJSON.

Instances

GFromJSON U1 
FromJSON a => GFromJSON (K1 i a) 
(AllNullary ((:+:) a b) allNullary, ParseSum ((:+:) a b) allNullary) => GFromJSON ((:+:) a b) 
(FromProduct a, FromProduct b, ProductSize a, ProductSize b) => GFromJSON ((:*:) a b) 
ConsFromJSON a => GFromJSON (C1 c a) 
GFromJSON a => GFromJSON (M1 i c a) 

class GToJSON f where Source

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

Methods

gToJSON :: Options -> f a -> Value Source

This method (applied to defaultOptions) is used as the default generic implementation of toJSON.

Instances

GToJSON U1 
ToJSON a => GToJSON (K1 i a) 
(AllNullary ((:+:) a b) allNullary, SumToJSON ((:+:) a b) allNullary) => GToJSON ((:+:) a b) 
(WriteProduct a, WriteProduct b, ProductSize a, ProductSize b) => GToJSON ((:*:) a b) 
ConsToJSON a => GToJSON (C1 c a) 
GToJSON a => GToJSON (M1 i c a) 

genericToJSON :: (Generic a, GToJSON (Rep a)) => Options -> a -> Value Source

A configurable generic JSON encoder. This function applied to defaultOptions is used as the default for toJSON when the type is an instance of Generic.

genericParseJSON :: (Generic a, GFromJSON (Rep a)) => Options -> Value -> Parser a Source

A configurable generic JSON decoder. This function applied to defaultOptions is used as the default for parseJSON when the type is an instance of Generic.

Inspecting Values

withObject :: String -> (Object -> Parser a) -> Value -> Parser a Source

withObject expected f value applies f to the Object when value is an Object and fails using typeMismatch expected otherwise.

withText :: String -> (Text -> Parser a) -> Value -> Parser a Source

withText expected f value applies f to the Text when value is a String and fails using typeMismatch expected otherwise.

withArray :: String -> (Array -> Parser a) -> Value -> Parser a Source

withArray expected f value applies f to the Array when value is an Array and fails using typeMismatch expected otherwise.

withNumber :: String -> (Number -> Parser a) -> Value -> Parser a Source

Deprecated: Use withScientific instead

withNumber expected f value applies f to the Number when value is a Number. and fails using typeMismatch expected otherwise.

withScientific :: String -> (Scientific -> Parser a) -> Value -> Parser a Source

withScientific expected f value applies f to the Scientific number when value is a Number. and fails using typeMismatch expected otherwise.

withBool :: String -> (Bool -> Parser a) -> Value -> Parser a Source

withBool expected f value applies f to the Bool when value is a Bool and fails using typeMismatch expected otherwise.

Constructors and accessors

(.=) :: ToJSON a => Text -> a -> Pair Source

Construct a Pair from a key and a value.

(.:) :: FromJSON a => Object -> Text -> Parser a Source

Retrieve the value associated with the given key of an Object. The result is empty if the key is not present or the value cannot be converted to the desired type.

This accessor is appropriate if the key and value must be present in an object for it to be valid. If the key and value are optional, use '(.:?)' instead.

(.:?) :: FromJSON a => Object -> Text -> Parser (Maybe a) Source

Retrieve the value associated with the given key of an Object. The result is Nothing if the key is not present, or 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.

(.!=) :: Parser (Maybe a) -> a -> Parser a Source

Helper for use in combination with .:? to provide default values for optional JSON object fields.

This combinator is most useful if the key and value can be absent from an object without affecting its validity and we know a default value to assign in that case. If the key and value are mandatory, use '(.:)' instead.

Example usage:

 v1 <- o .:? "opt_field_with_dfl" .!= "default_val"
 v2 <- o .:  "mandatory_field"
 v3 <- o .:? "opt_field2"

object :: [Pair] -> Value Source

Create a Value from a list of name/value Pairs. If duplicate keys arise, earlier keys and their associated values win.

Generic and TH encoding configuration

data Options Source

Options that specify how to encode/decode your datatype to/from JSON.

Constructors

Options 

Fields

fieldLabelModifier :: String -> String

Function applied to field labels. Handy for removing common record prefixes for example.

constructorTagModifier :: String -> String

Function applied to constructor tags which could be handy for lower-casing them for example.

allNullaryToStringTag :: Bool

If True the constructors of a datatype, with all nullary constructors, will be encoded to just a string with the constructor tag. If False the encoding will always follow the sumEncoding.

omitNothingFields :: Bool

If True record fields with a Nothing value will be omitted from the resulting object. If False the resulting object will include those fields mapping to null.

sumEncoding :: SumEncoding

Specifies how to encode constructors of a sum datatype.

data SumEncoding Source

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.

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 Source

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"

defaultTaggedObject :: SumEncoding Source

Default TaggedObject SumEncoding options:

defaultTaggedObject = TaggedObject
                      { tagFieldName      = "tag"
                      , contentsFieldName = "contents"
                      }