generic-aeson-0.2.0.11: Derivation of Aeson instances using GHC generics.
Safe HaskellNone
LanguageHaskell2010

Generics.Generic.Aeson

Description

This module offers generic conversions to and from JSON Values for data types with a Generic instance.

The structure of the generated JSON is meant to be close to idiomatic JSON. This means:

  • Enumerations are converted to JSON strings.
  • Record fields become JSON keys.
  • Data types with one unlabeled field convert to just that field.
  • Data types with multiple unlabeled fields become arrays.
  • Multiple constructors are represented by keys.
  • Maybe values are either an absent key, or the value.

See 'tests/Main.hs' for more examples.

Synopsis

Documentation

gtoJson :: forall a. (Generic a, GtoJson (Rep a), ConNames (Rep a), GIsEnum (Rep a)) => a -> Value Source #

Convert any datatype with a Generic instance to a JSON Value.

gparseJson :: forall a. (Generic a, GfromJson (Rep a), ConNames (Rep a), GIsEnum (Rep a)) => Value -> Parser a Source #

Parse any datatype with a Generic instance from a JSON Value.

class GtoJson f where Source #

Class for converting the functors from GHC.Generics to JSON. You generally don't need to give any custom instances. Just add 'deriving Generic' and call gToJson.

Methods

gtoJSONf :: Settings -> Bool -> Bool -> f a -> Either [Value] [(Text, Value)] Source #

Generically show a functor as a JSON value. The first argument tells us if there are multiple constructors in the data type. The second indicates if this data type is an enumeration (only empty constructors). A functor is then converted to either a list of values (for non-labeled fields) or a list of String/value pairs (for labeled fields).

Instances

Instances details
GtoJson (U1 :: Type -> Type) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gtoJSONf :: Settings -> Bool -> Bool -> U1 a -> Either [Value] [(Text, Value)] Source #

ToJSON c => GtoJson (K1 a c :: Type -> Type) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gtoJSONf :: Settings -> Bool -> Bool -> K1 a c a0 -> Either [Value] [(Text, Value)] Source #

(GtoJson f, GtoJson g) => GtoJson (f :+: g) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gtoJSONf :: Settings -> Bool -> Bool -> (f :+: g) a -> Either [Value] [(Text, Value)] Source #

(GtoJson f, GtoJson g) => GtoJson (f :*: g) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gtoJSONf :: Settings -> Bool -> Bool -> (f :*: g) a -> Either [Value] [(Text, Value)] Source #

GtoJson f => GtoJson (M1 D c f) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gtoJSONf :: Settings -> Bool -> Bool -> M1 D c f a -> Either [Value] [(Text, Value)] Source #

(Constructor c, GtoJson f) => GtoJson (M1 C c f) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gtoJSONf :: Settings -> Bool -> Bool -> M1 C c f a -> Either [Value] [(Text, Value)] Source #

(Selector c, ToJSON a) => GtoJson (M1 S c (K1 i (Maybe a) :: Type -> Type)) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gtoJSONf :: Settings -> Bool -> Bool -> M1 S c (K1 i (Maybe a)) a0 -> Either [Value] [(Text, Value)] Source #

(Selector c, GtoJson f) => GtoJson (M1 S c f) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gtoJSONf :: Settings -> Bool -> Bool -> M1 S c f a -> Either [Value] [(Text, Value)] Source #

class GfromJson f where Source #

Class for parsing the functors from GHC.Generics from JSON. You generally don't need to give any custom instances. Just add 'deriving Generic' and call gFromJson.

Methods

gparseJSONf :: Settings -> Bool -> Bool -> Bool -> StateT [Value] Parser (f a) Source #

Generically read a functor from a JSON value. The first argument tells us if there are multiple constructors in the data type. The second indicates if we've already detected that this data type has multiple constructors. When this is False, the (:*:) puts the fields in the state. The third indicates if this data type is an enumeration (only empty constructors). The third is a function for parsing the recursive positions. A JSON value is then parsed to either a functor, or a failure.

Instances

Instances details
GfromJson (U1 :: Type -> Type) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gparseJSONf :: Settings -> Bool -> Bool -> Bool -> StateT [Value] Parser (U1 a) Source #

FromJSON c => GfromJson (K1 a c :: Type -> Type) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gparseJSONf :: Settings -> Bool -> Bool -> Bool -> StateT [Value] Parser (K1 a c a0) Source #

(GfromJson f, GfromJson g) => GfromJson (f :+: g) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gparseJSONf :: Settings -> Bool -> Bool -> Bool -> StateT [Value] Parser ((f :+: g) a) Source #

(GfromJson f, GfromJson g) => GfromJson (f :*: g) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gparseJSONf :: Settings -> Bool -> Bool -> Bool -> StateT [Value] Parser ((f :*: g) a) Source #

GfromJson f => GfromJson (M1 D c f) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gparseJSONf :: Settings -> Bool -> Bool -> Bool -> StateT [Value] Parser (M1 D c f a) Source #

(Constructor c, GfromJson f) => GfromJson (M1 C c f) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gparseJSONf :: Settings -> Bool -> Bool -> Bool -> StateT [Value] Parser (M1 C c f a) Source #

(Selector c, FromJSON a) => GfromJson (M1 S c (K1 i (Maybe a) :: Type -> Type)) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gparseJSONf :: Settings -> Bool -> Bool -> Bool -> StateT [Value] Parser (M1 S c (K1 i (Maybe a)) a0) Source #

(Selector c, GfromJson f) => GfromJson (M1 S c f) Source # 
Instance details

Defined in Generics.Generic.Aeson

Methods

gparseJSONf :: Settings -> Bool -> Bool -> Bool -> StateT [Value] Parser (M1 S c f a) Source #

formatLabel :: Settings -> Text -> Text Source #

Lowercases the first letter and strips leading and trailing underscores.

data Settings Source #

Constructors

Settings 

Instances

Instances details
Show Settings Source # 
Instance details

Defined in Generics.Generic.Aeson.Util

gtoJsonWithSettings :: forall a. (Generic a, GtoJson (Rep a), ConNames (Rep a), GIsEnum (Rep a)) => Settings -> a -> Value Source #