| Copyright | (c) 2011-2016 Bryan O'Sullivan (c) 2011 MailRank Inc. | 
|---|---|
| License | BSD3 | 
| Stability | experimental | 
| Portability | portable | 
| Safe Haskell | Safe-Inferred | 
| Language | Haskell2010 | 
Data.Aeson.TH
Description
Functions to mechanically derive JSONFun and FromJSON instances. Note that
you need to enable the TemplateHaskell language extension in order to use this
module.
An example shows how instances are generated for arbitrary data types. First we define a data type:
data D a = Nullary
         | Unary Int
         | Product String Char a
         | Record { testOne   :: Double
                  , testTwo   :: Bool
                  , testThree :: D a
                  } deriving Eq
Next we derive the necessary instances. Note that we make use of the feature to change record field names. In this case we drop the first 4 characters of every field name. We also modify constructor names by lower-casing them:
$(deriveJSONdefaultOptions{fieldLabelModifier=drop4,constructorTagModifier= map toLower} ''D)
Now we can use the newly created instances.
d :: DIntd = Record { testOne = 3.14159 , testTwo =True, testThree = Product "test" 'A' 123 }
fromJSON (toJSON d) == Success d
This also works for data family instances, but instead of passing in the data family name (with double quotes), we pass in a data family instance constructor (with a single quote):
data family DF a
data instance DF Int = DF1 Int
                     | DF2 Int Int
                     deriving Eq
$(deriveJSON defaultOptions 'DF1)
-- Alternatively, one could pass 'DF2 instead
Please note that you can derive instances for tuples using the following syntax:
-- FromJSON and ToJSON instances for 4-tuples. $(deriveJSONdefaultOptions''(,,,))
Synopsis
- data Options
- data SumEncoding
- defaultOptions :: Options
- defaultTaggedObject :: SumEncoding
- deriveJSON :: Options -> Name -> Q [Dec]
- deriveJSON1 :: Options -> Name -> Q [Dec]
- deriveJSON2 :: Options -> Name -> Q [Dec]
- deriveToJSON :: Options -> Name -> Q [Dec]
- deriveToJSON1 :: Options -> Name -> Q [Dec]
- deriveToJSON2 :: Options -> Name -> Q [Dec]
- deriveFromJSON :: Options -> Name -> Q [Dec]
- deriveFromJSON1 :: Options -> Name -> Q [Dec]
- deriveFromJSON2 :: Options -> Name -> Q [Dec]
- mkToJSON :: Options -> Name -> Q Exp
- mkLiftToJSON :: Options -> Name -> Q Exp
- mkLiftToJSON2 :: Options -> Name -> Q Exp
- mkToEncoding :: Options -> Name -> Q Exp
- mkLiftToEncoding :: Options -> Name -> Q Exp
- mkLiftToEncoding2 :: Options -> Name -> Q Exp
- mkParseJSON :: Options -> Name -> Q Exp
- mkLiftParseJSON :: Options -> Name -> Q Exp
- mkLiftParseJSON2 :: Options -> Name -> Q Exp
Encoding configuration
Options that specify how to encode/decode your datatype to/from JSON.
Options can be set using record syntax on defaultOptions with the fields
 below.
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
  | 
| Fields | |
| 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
  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
  | 
| TwoElemArray | A constructor will be encoded to a 2-element array where the
 first element is the tag of the constructor (modified by the
  | 
Instances
| Show SumEncoding Source # | |
| Defined in Data.Aeson.Types.Internal Methods showsPrec :: Int -> SumEncoding -> ShowS # show :: SumEncoding -> String # showList :: [SumEncoding] -> ShowS # | |
| Eq SumEncoding Source # | |
| Defined in Data.Aeson.Types.Internal | |
defaultOptions :: Options Source #
Default encoding Options:
Options{fieldLabelModifier= id ,constructorTagModifier= id ,allNullaryToStringTag= True ,omitNothingFields= False ,sumEncoding=defaultTaggedObject,unwrapUnaryRecords= False ,tagSingleConstructors= False ,rejectUnknownFields= False }
defaultTaggedObject :: SumEncoding Source #
Default TaggedObject SumEncoding options:
defaultTaggedObject =TaggedObject{tagFieldName= "tag" ,contentsFieldName= "contents" }
FromJSON and ToJSON derivation
Arguments
| :: Options | Encoding options. | 
| -> Name | Name of the type for which to generate  | 
| -> Q [Dec] | 
Generates both JSONFun and FromJSON instance declarations for the given
 data type or data family instance constructor.
This is a convenience function which is equivalent to calling both
 deriveToJSON and deriveFromJSON.
Arguments
| :: Options | Encoding options. | 
| -> Name | Name of the type for which to generate  | 
| -> Q [Dec] | 
Generates both ToJSON1 and FromJSON1 instance declarations for the given
 data type or data family instance constructor.
This is a convenience function which is equivalent to calling both
 deriveToJSON1 and deriveFromJSON1.
Arguments
| :: Options | Encoding options. | 
| -> Name | Name of the type for which to generate  | 
| -> Q [Dec] | 
Generates both ToJSON2 and FromJSON2 instance declarations for the given
 data type or data family instance constructor.
This is a convenience function which is equivalent to calling both
 deriveToJSON2 and deriveFromJSON2.
Arguments
| :: Options | Encoding options. | 
| -> Name | Name of the type for which to generate a  | 
| -> Q [Dec] | 
Generates a JSONFun instance declaration for the given data type or
 data family instance constructor.
Arguments
| :: Options | Encoding options. | 
| -> Name | Name of the type for which to generate a  | 
| -> Q [Dec] | 
Generates a ToJSON1 instance declaration for the given data type or
 data family instance constructor.
Arguments
| :: Options | Encoding options. | 
| -> Name | Name of the type for which to generate a  | 
| -> Q [Dec] | 
Generates a ToJSON2 instance declaration for the given data type or
 data family instance constructor.
Arguments
| :: Options | Encoding options. | 
| -> Name | Name of the type for which to generate a  | 
| -> Q [Dec] | 
Generates a FromJSON instance declaration for the given data type or
 data family instance constructor.
Arguments
| :: Options | Encoding options. | 
| -> Name | Name of the type for which to generate a  | 
| -> Q [Dec] | 
Generates a FromJSON1 instance declaration for the given data type or
 data family instance constructor.
Arguments
| :: Options | Encoding options. | 
| -> Name | Name of the type for which to generate a  | 
| -> Q [Dec] | 
Generates a FromJSON2 instance declaration for the given data type or
 data family instance constructor.
Generates a lambda expression which encodes the given data type or
 data family instance constructor as a ToJSONFun.
Generates a lambda expression which encodes the given data type or
 data family instance constructor as a ToJSONFun by using the given encoding
 function on occurrences of the last type parameter.
Generates a lambda expression which encodes the given data type or
 data family instance constructor as a ToJSONFun by using the given encoding
 functions on occurrences of the last two type parameters.
Generates a lambda expression which encodes the given data type or data family instance constructor as a JSON string.
Generates a lambda expression which encodes the given data type or data family instance constructor as a JSON string by using the given encoding function on occurrences of the last type parameter.
Generates a lambda expression which encodes the given data type or data family instance constructor as a JSON string by using the given encoding functions on occurrences of the last two type parameters.
Generates a lambda expression which parses the JSON encoding of the given data type or data family instance constructor.
Generates a lambda expression which parses the JSON encoding of the given data type or data family instance constructor by using the given parsing function on occurrences of the last type parameter.
Generates a lambda expression which parses the JSON encoding of the given data type or data family instance constructor by using the given parsing functions on occurrences of the last two type parameters.