aeson-dependent-sum-0.1.0.1: JSON encoding/decoding for dependent-sum
Copyright(c) 2022 Jack Kelly
LicenseGPL-3.0-or-later
Maintainerjack@jackkelly.name
Stabilityexperimental
Portabilitynon-portable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Aeson.Dependent.Sum

Description

When reading/writing JSON, you sometimes want to handle structures where the value at one key determines the type of the entire record. (In OpenAPI, they are sometimes called polymorphic structures and are specified using a oneOf schema with the discriminator/propertyName keyword.)

A naive approach would use a sum-of-records, and either aeson's built-in anyclass deriving or a manual two-step parse:

data Fighter = F { ... } deriving anyclass (FromJSON, ToJSON)
data Rogue = R { ... } deriving anyclass (FromJSON, ToJSON)
data Wizard = W { ... } deriving anyclass (FromJSON, ToJSON)

data Character = Fighter Fighter | Rogue Rogue | Wizard Wizard
instance FromJSON Character where
  parseJSON = withObject "Character" $ \o ->
    charClass <- o .: "class" :: Parser Text
    case charClass of
      "fighter" -> do
        favouredWeapon <- o .: "favouredWeapon"
        attackBonus <- o .: "attackBonus"
        -- etc.

This works, but sometimes you want to manipulate the tag itself as a first-class value. In these instances, the dependent-sum library can help, and we can also use deriving via to derive JSON instances on the Character newtype:

data CharacterClass a where
  Fighter :: CharacterClass Fighter
  Rogue :: CharacterClass Rogue
  Wizard :: CharacterClass Wizard

-- From the "constraints-extras" package:
$(deriveArgDict ''CharacterClass)
-- From the "dependent-sum-template" package. Not required, but useful:
$(deriveGShow ''CharacterClass)
$(deriveGEq ''CharacterClass)
$(deriveGCompare ''CharacterClass)

newtype Character = Character (DSum CharacterClass Identity)
  deriving (FromJSON, ToJSON)
  via (TaggedObjectInline "Character" "class" CharacterClass Identity)

To derive JSON instances on Character, we need to provide FromJSON and ToJSON instances for the CharacterClass tag as well as for each record type. The Some wrapper from the some package lets us wrap CharacterClass so that its kind matches what FromJSON expects:

instance FromJSON (Some CharacterClass) where
  parseJSON = withText "CharacterClass" $ \t ->
    case t of
      "fighter" -> pure $ Some Fighter
      "rogue" -> pure $ Some Rogue
      "wizard" -> pure $ Some Wizard

The newtypes in this module implement several different encoding/decoding strategies which roughly parallel the ones in aeson.

Synopsis

Documentation

newtype TaggedObject (typeName :: Symbol) (tagKey :: Symbol) (contentsKey :: Symbol) (tag :: k -> Type) (f :: k -> Type) Source #

Newtype for DSums representing JSON objects where one field determines the "type" of the object, and all the other data fields are stored under a distinct key. Analogous to the TaggedObject constructor in SumEncoding.

To derive FromJSON and ToJSON instances for JSON like this:

{
  "class": "fighter", -- or "rogue", or "wizard"
  "data": { ... } -- the exact fields differ depending on the value at "class".
}

You would derive the instance like this:

newtype Character = Character (DSum CharacterClass Identity)
  deriving (FromJSON, ToJSON)
  via (TaggedObject "Character" "class" "data" CharacterClass Identity)

Since: 0.1.0.0

Constructors

TaggedObject (DSum tag f) 

Instances

Instances details
(KnownSymbol typeName, KnownSymbol tagKey, KnownSymbol contentsKey, FromJSON (Some tag), Has' FromJSON tag f) => FromJSON (TaggedObject typeName tagKey contentsKey tag f) Source #

Since: 0.1.0.0

Instance details

Defined in Data.Aeson.Dependent.Sum

Methods

parseJSON :: Value -> Parser (TaggedObject typeName tagKey contentsKey tag f) #

parseJSONList :: Value -> Parser [TaggedObject typeName tagKey contentsKey tag f] #

(KnownSymbol tagKey, KnownSymbol contentsKey, ToJSON (Some tag), Has' ToJSON tag f) => ToJSON (TaggedObject typeName tagKey contentsKey tag f) Source #

Since: 0.1.0.0

Instance details

Defined in Data.Aeson.Dependent.Sum

Methods

toJSON :: TaggedObject typeName tagKey contentsKey tag f -> Value #

toEncoding :: TaggedObject typeName tagKey contentsKey tag f -> Encoding #

toJSONList :: [TaggedObject typeName tagKey contentsKey tag f] -> Value #

toEncodingList :: [TaggedObject typeName tagKey contentsKey tag f] -> Encoding #

newtype TaggedObjectInline (typeName :: Symbol) (tagKey :: Symbol) (tag :: k -> Type) (f :: k -> Type) Source #

Newtype for DSums representing JSON objects where one field determines the "type" of the object, and all the other data fields are stored at the same level.

To derive FromJSON and ToJSON instances for JSON like this:

{
  "class": "wizard", -- or "fighter", or "rogue"
  -- These fields will differ depending on the value at "class".
  "frogsLegs": 42,
  "eyesOfNewt": 9001
}

You would derive the instance like this:

newtype Character = Character (DSum CharacterClass Identity)
  deriving (FromJSON, ToJSON)
  via (TaggedObjectInline "Character" "class" CharacterClass Identity)

Since: 0.1.0.0

Constructors

TaggedObjectInline (DSum tag f) 

Instances

Instances details
(KnownSymbol typeName, KnownSymbol tagKey, Has' FromJSON tag f, FromJSON (Some tag)) => FromJSON (TaggedObjectInline typeName tagKey tag f) Source #

Since: 0.1.0.0

Instance details

Defined in Data.Aeson.Dependent.Sum

Methods

parseJSON :: Value -> Parser (TaggedObjectInline typeName tagKey tag f) #

parseJSONList :: Value -> Parser [TaggedObjectInline typeName tagKey tag f] #

(KnownSymbol typeName, KnownSymbol tagKey, Has' ToJSON tag f, ToJSON (Some tag)) => ToJSON (TaggedObjectInline typeName tagKey tag f) Source #

Since: 0.1.0.0

Instance details

Defined in Data.Aeson.Dependent.Sum

Methods

toJSON :: TaggedObjectInline typeName tagKey tag f -> Value #

toEncoding :: TaggedObjectInline typeName tagKey tag f -> Encoding #

toJSONList :: [TaggedObjectInline typeName tagKey tag f] -> Value #

toEncodingList :: [TaggedObjectInline typeName tagKey tag f] -> Encoding #

newtype ObjectWithSingleField (typeName :: Symbol) (tag :: k -> Type) (f :: k -> Type) Source #

Newtype for DSums representing JSON objects where the object has exactly one key, and the name of that key one field determines the "type" of the object. All the other data fields are stored in the corresponding value. Analogous to the ObjectWithSingleField constructor in SumEncoding.

To derive FromJSON and ToJSON instances for JSON like this:

{
  "wizard": { -- or "fighter", or "rogue"
    -- The contents of this object will differ depending on the key.
    "frogsLegs": 42,
    "eyesOfNewt": 9001
  }
}

You would derive the instance like this:

newtype Character = Character (DSum CharacterClass Identity)
  deriving (FromJSON, ToJSON)
  via (ObjectWithSingleField "Character" CharacterClass Identity)

If the FromJSONKey/ToJSONKey instances for Some tag encode to something other than a JSON string, then a two-element array will be parsed/generated instead, like in TwoElemArray.

Since: 0.1.0.0

Constructors

ObjectWithSingleField (DSum tag f) 

Instances

Instances details
(KnownSymbol typeName, Has' FromJSON tag f, FromJSONKey (Some tag)) => FromJSON (ObjectWithSingleField typeName tag f) Source #

Since: 0.1.0.0

Instance details

Defined in Data.Aeson.Dependent.Sum

Methods

parseJSON :: Value -> Parser (ObjectWithSingleField typeName tag f) #

parseJSONList :: Value -> Parser [ObjectWithSingleField typeName tag f] #

(Has' ToJSON tag f, ToJSONKey (Some tag)) => ToJSON (ObjectWithSingleField typeName tag f) Source #

Since: 0.1.0.0

Instance details

Defined in Data.Aeson.Dependent.Sum

Methods

toJSON :: ObjectWithSingleField typeName tag f -> Value #

toEncoding :: ObjectWithSingleField typeName tag f -> Encoding #

toJSONList :: [ObjectWithSingleField typeName tag f] -> Value #

toEncodingList :: [ObjectWithSingleField typeName tag f] -> Encoding #

newtype TwoElemArray (typeName :: Symbol) (tag :: k -> Type) (f :: k -> Type) Source #

Newtype for DSums representing serialisation to/from a two-element array. The tag is stored in the first elemnt, and the serialised value is stored in the second. Analogous to the TwoElemArray constructor in SumEncoding.

To derive FromJSON and ToJSON instances for JSON like this:

[
  "wizard", -- or "fighter", or "rogue"
  -- The contents of this object will differ depending on the previous element.
  {
    "frogsLegs": 42,
    "eyesOfNewt": 9001
  }
]

You would derive the instance like this:

newtype Character = Character (DSum CharacterClass Identity)
  deriving (FromJSON, ToJSON)
  via (TwoElemArray "Character" CharacterClass Identity)

Since: 0.1.0.0

Constructors

TwoElemArray (DSum tag f) 

Instances

Instances details
(KnownSymbol typeName, Has' FromJSON tag f, FromJSON (Some tag)) => FromJSON (TwoElemArray typeName tag f) Source #

Since: 0.1.0.0

Instance details

Defined in Data.Aeson.Dependent.Sum

Methods

parseJSON :: Value -> Parser (TwoElemArray typeName tag f) #

parseJSONList :: Value -> Parser [TwoElemArray typeName tag f] #

(Has' ToJSON tag f, ToJSON (Some tag)) => ToJSON (TwoElemArray typeName tag f) Source #

Since: 0.1.0.0

Instance details

Defined in Data.Aeson.Dependent.Sum

Methods

toJSON :: TwoElemArray typeName tag f -> Value #

toEncoding :: TwoElemArray typeName tag f -> Encoding #

toJSONList :: [TwoElemArray typeName tag f] -> Value #

toEncodingList :: [TwoElemArray typeName tag f] -> Encoding #