aeson-gadt-th: Derivation of Aeson instances for GADTs

This is a package candidate release! Here you can preview how this package release will appear once published to the main package index (which can be accomplished via the 'maintain' link below). Please note that once a package has been published to the main package index it cannot be undone! Please consult the package uploading documentation for more information.

[maintain] [Publish]

Warnings:

Template Haskell for generating ToJSON and FromJSON instances for GADTs. See README.md for examples.


[Skip to Readme]

Properties

Versions 0.1.0.0, 0.1.1.0, 0.1.2.0, 0.1.2.1, 0.2.0.0, 0.2.0.0, 0.2.1.0, 0.2.1.1, 0.2.1.2, 0.2.2, 0.2.3, 0.2.4, 0.2.5.0, 0.2.5.1
Change log ChangeLog.md
Dependencies aeson, aeson-gadt-th, base (>=4.8 && <4.13), dependent-sum, template-haskell, transformers [details]
License BSD-3-Clause
Copyright 2019 Obsidian Systems LLC
Author Obsidian Systems LLC
Maintainer maintainer@obsidian.systems
Category JSON
Source repo head: git clone git://github.com/obsidiansystems/aeson-gadt-th.git
Uploaded by abrar at 2019-03-28T21:00:55Z

Modules

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees


Readme for aeson-gadt-th-0.2.0.0

[back to package description]

aeson-gadt-th

Provides Template Haskell expressions for deriving ToJSON and FromJSON instances for GADTs.

Example Usage:

{-# LANGUAGE GADTs #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}

import Data.Aeson
import Data.Aeson.GADT.TH

data A :: * -> * where
  A_a :: A a
  A_b :: Int -> A ()

data B c :: * -> * where
  B_a :: c -> A a -> B c a
  B_x :: B c x

deriveJSONGADT ''A
deriveJSONGADT ''B

main :: IO ()
main = return ()

Encoding:

encode A_a
> "[\"A_a\",[]]"

Decoding:

When decoding a JSON-encoded GADT, the result will be wrapped using Data.Some.This.

case (decode $ encode A_a) :: Maybe (Some A) of
  Nothing -> error "Couldn't decode
  Just (This A_a) -> putStrLn "it worked"
  Just (This A_b) -> putStrLn "wat"
> it worked