aeson-0.6.1.0: Fast JSON parsing and encoding

Portabilityportable
Stabilityexperimental
Safe HaskellNone

Data.Aeson.TH

Description

Functions to mechanically derive ToJSON 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.

$(deriveJSON (drop 4) ''D)

This will result in the following (simplified) code to be spliced in your program:

import Control.Applicative
import Control.Monad
import Data.Aeson
import Data.Aeson.TH
import qualified Data.HashMap.Strict as H
import qualified Data.Text as T
import qualified Data.Vector as V

instance ToJSON a => ToJSON (D a) where
    toJSON =
      \value ->
        case value of
          Nullary ->
              object [T.pack "Nullary" .= toJSON ([] :: [()])]
          Unary arg1 ->
              object [T.pack "Unary" .= toJSON arg1]
          Product arg1 arg2 arg3 ->
              object [ T.pack "Product"
                       .= (Array $ create $ do
                             mv <- unsafeNew 3
                             unsafeWrite mv 0 (toJSON arg1)
                             unsafeWrite mv 1 (toJSON arg2)
                             unsafeWrite mv 2 (toJSON arg3)
                             return mv)
                     ]
          Record arg1 arg2 arg3 ->
              object [ T.pack "Record"
                       .= object [ T.pack "One"   .= arg1
                                 , T.pack "Two"   .= arg2
                                 , T.pack "Three" .= arg3
                                 ]
                     ]
instance FromJSON a => FromJSON (D a) where
    parseJSON =
      \value ->
        case value of
          Object obj ->
            case H.toList obj of
              [(conKey, conVal)] ->
                case conKey of
                  _ | conKey == T.pack "Nullary" ->
                        case conVal of
                          Array arr ->
                            if V.null arr
                            then pure Nullary
                            else fail "<error message>"
                          _ -> fail "<error message>"
                    | conKey == T.pack "Unary" ->
                        case conVal of
                          arg -> Unary <$> parseJSON arg
                    | conKey == T.pack "Product" ->
                        case conVal of
                          Array arr ->
                            if V.length arr == 3
                            then Product <$> parseJSON (arr unsafeIndex 0)
                                         <*> parseJSON (arr unsafeIndex 1)
                                         <*> parseJSON (arr unsafeIndex 2)
                            else fail "<error message>"
                          _ -> fail "<error message>"
                    | conKey == T.pack "Record" ->
                        case conVal of
                          Object recObj ->
                            if H.size recObj == 3
                            then Record <$> recObj .: T.pack "One"
                                        <*> recObj .: T.pack "Two"
                                        <*> recObj .: T.pack "Three"
                            else fail "<error message>"
                          _ -> fail "<error message>"
                    | otherwise -> fail "<error message>"
              _ -> fail "<error message>"
          _ -> fail "<error message>"

Note that every "<error message>" is in fact a descriptive message which provides as much information as is reasonable about the failed parse.

Now we can use the newly created instances.

d :: D Int
d = Record { testOne = 3.14159
           , testTwo = True
           , testThree = Product "test" 'A' 123
           }
>>> fromJSON (toJSON d) == Success d
> True

Please note that you can derive instances for tuples using the following syntax:

-- FromJSON and ToJSON instances for 4-tuples.
$(deriveJSON id ''(,,,))

Synopsis

Documentation

deriveJSONSource

Arguments

:: (String -> String)

Function to change field names.

-> Name

Name of the type for which to generate ToJSON and FromJSON instances.

-> Q [Dec] 

Generates both ToJSON and FromJSON instance declarations for the given data type.

This is a convienience function which is equivalent to calling both deriveToJSON and deriveFromJSON.

deriveToJSONSource

Arguments

:: (String -> String)

Function to change field names.

-> Name

Name of the type for which to generate a ToJSON instance declaration.

-> Q [Dec] 

Generates a ToJSON instance declaration for the given data type.

Example:

 data Foo = Foo Char Int
 $(deriveToJSON id ''Foo)

This will splice in the following code:

 instance ToJSON Foo where
      toJSON =
          \value -> case value of
                      Foo arg1 arg2 -> Array $ create $ do
                        mv <- unsafeNew 2
                        unsafeWrite mv 0 (toJSON arg1)
                        unsafeWrite mv 1 (toJSON arg2)
                        return mv

deriveFromJSONSource

Arguments

:: (String -> String)

Function to change field names.

-> Name

Name of the type for which to generate a FromJSON instance declaration.

-> Q [Dec] 

Generates a FromJSON instance declaration for the given data type.

Example:

 data Foo = Foo Char Int
 $(deriveFromJSON id ''Foo)

This will splice in the following code:

 instance FromJSON Foo where
     parseJSON =
         \value -> case value of
                     Array arr ->
                       if (V.length arr == 2)
                       then Foo <$> parseJSON (arr unsafeIndex 0)
                                <*> parseJSON (arr unsafeIndex 1)
                       else fail "<error message>"
                     other -> fail "<error message>"

mkToJSONSource

Arguments

:: (String -> String)

Function to change field names.

-> Name

Name of the type to encode.

-> Q Exp 

Generates a lambda expression which encodes the given data type as JSON.

Example:

 data Foo = Foo Int
 encodeFoo :: Foo -> Value
 encodeFoo = $(mkToJSON id ''Foo)

This will splice in the following code:

 \value -> case value of Foo arg1 -> toJSON arg1

mkParseJSONSource

Arguments

:: (String -> String)

Function to change field names.

-> Name

Name of the encoded type.

-> Q Exp 

Generates a lambda expression which parses the JSON encoding of the given data type.

Example:

 data Foo = Foo Int
 parseFoo :: Value -> Parser Foo
 parseFoo = $(mkParseJSON id ''Foo)

This will splice in the following code:

 \value -> case value of arg -> Foo <$> parseJSON arg