json-spec-0.1.0.0: Type-level JSON specification
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.JsonSpec

Description

This module provides a way to specify the shape of your JSON data at the type level.

Example

data User = User
  { name :: Text
  , lastLogin :: UTCTime
  }
  deriving stock (Show, Eq)
  deriving (ToJSON, FromJSON) via (SpecJSON User)
instance HasJsonEncodingSpec User where
  type EncodingSpec User =
    JsonObject
      '[ '("name", JsonString)
       , '("last-login", JsonDateTime)
       ]
  toJSONStructure user =
    (Field @"name" (name user),
    (Field @"last-login" (lastLogin user),
    ()))
instance HasJsonDecodingSpec User where
  type DecodingSpec User = EncodingSpec User
  fromJSONStructure
      (Field @"name" name,
      (Field @"last-login" lastLogin,
      ()))
    =
      pure User { name , lastLogin }

Motivation

The particular use cases we focus on are enabling (but not providing in this package):

  1. Auto-generating documentation to ensure it is correct.
  2. Auto-generating client code in front-end languages to ensure it is correct.

There are already tools available to achieve this, but they all have one major drawback: they rely on generically derived Aeson instances. Some people strongly object to using generically derived Aeson instances for encoding/decoding http api data because of how brittle it is. It can be surprisingly easy accidentally break your API without noticing because you don't realize that a small change to some type somewhere affects the API representation. Avoiding this requires very strict discipline about how you organize and maintain your code. E.g. you will see a lot of comments like

--| BEWARE, Changing any of the types in this file will change the API
-- representation!!
module My.API (...) where

But then the types in this api might reference types in in other modules where it isn't as obvious that you might be changing the api when you make an update.

I have even seen people go so far as to mandate that every type appearing on the API must be in some similar "API" module. This usually ends badly because you end up with a bunch of seemingly spurious (and quite tedious) translations between between "business" types and almost identical "API" types.

The other option is to simply not use generically derived instances and code all or some of your ToJSON/FromJSON instances by hand. That (sometimes) helps solve the problem of making it a little more obvious when you are making a breaking api change. And it definitely helps with the ability to update the haskell type for some business purpose while keeping the encoding backwards compatible.

The problem now though is that you can't take advantage of any of the above tooling without writing every instance by hand. Writing all the individual instances by hand defeat's the purpose because you are back to being unsure whether they are all in sync!

The approach this library takes is to take a cue from servant and provide a way to specify the JSON encoding at the type level. You must manually specify the encoding, but you only have to do so once (at the type level). Other tools can then inspect the type using either type families or type classes to generate the appropriate artifacts or behavior. Aeson integration (provided by this package) works by using a type family to transform the spec into a new Haskell type whose structure is analogous to the specification. You are then required to transform your regular business value into a value of this "structural type" (I strongly recommend using type holes to make this easier). Values of the structural type will always encode into specification-complient JSON.

Synopsis

Documentation

data Specification Source #

Simple DSL for defining type level "specifications" for JSON data. Similar in spirit to (but not isomorphic with) JSON Schema.

Intended to be used at the type level using -XDataKinds

See JSONStructure for how these map into Haskell representations.

Constructors

JsonObject [(Symbol, Specification)]

An object with the specified properties, each having its own specification. This does not yet support optional properties, although a property can be specified as "nullable" using JsonNullable

JsonString

An arbitrary JSON string.

JsonNum

An arbitrary (floating point) JSON number.

JsonInt

A JSON integer.

JsonArray Specification

A JSON array of values which conform to the given spec.

JsonBool

A JSON boolean value.

JsonNullable Specification

A value that can either be null, or else a value conforming to the specification.

E.g.:

type SpecWithNullableField =
  JsonObject
    '[ '("nullableProperty", JsonNullable JsonString)
     ]
JsonEither Specification Specification

One of two different specifications. Corresponds to json-schema "oneOf". Useful for encoding sum types. E.g:

data MyType
  = Foo Text
  | Bar Int
  | Baz UTCTime
instance HasJsonEncodingSpec MyType where
  type EncodingSpec MyType =
    JsonEither
      (
        JsonObject
          '[ '("tag", JsonTag "foo")
           , '("content", JsonString)
           ]
      )
      (
        JsonEither
          (
            JsonObject
              '[ '("tag", JsonTag "bar")
               , '("content", JsonInt)
               ]
          )
          (
            JsonObject
              '[ '("tag", JsonTag "baz")
               , '("content", JsonDateTime)
               ]
          )
      )
JsonTag Symbol

A constant string value

JsonDateTime

A JSON string formatted as an ISO-8601 string. In Haskell this corresponds to UTCTime, and in json-schema it corresponds to the "date-time" format.

class HasJsonEncodingSpec a where Source #

Types of this class can be encoded to JSON according to a type-level Specification.

Associated Types

type EncodingSpec a :: Specification Source #

The encoding specification.

Methods

toJSONStructure :: a -> JSONStructure (EncodingSpec a) Source #

Encode the value into the structure appropriate for the specification.

class HasJsonDecodingSpec a where Source #

Types of this class can be JSON decoded according to a type-level Specification.

Associated Types

type DecodingSpec a :: Specification Source #

The decoding Specification.

Methods

fromJSONStructure :: JSONStructure (DecodingSpec a) -> Parser a Source #

Given the structural encoding of the JSON data, parse the structure into the final type. The reason this returns a Parser a instead of just a plain a is because there may still be some invariants of the JSON data that the Specification language is not able to express, and so you may need to fail parsing in those cases. For instance, Specification is not powerful enough to express "this field must contain only prime numbers".

newtype SpecJSON a Source #

Helper for defining ToJSON and FromJSON instances based on HasEncodingJsonSpec.

Use with -XDerivingVia like:

data MyObj = MyObj
  { foo :: Int
  , bar :: Text
  }
  deriving (ToJSON, FromJSON) via (SpecJSON MyObj)
instance HasEncodingSpec MyObj where ...
instance HasDecodingSpec MyObj where ...

Constructors

SpecJSON 

Fields

Instances

Instances details
(StructureFromJSON (JSONStructure (DecodingSpec a)), HasJsonDecodingSpec a) => FromJSON (SpecJSON a) Source # 
Instance details

Defined in Data.JsonSpec

(StructureToJSON (JSONStructure (EncodingSpec a)), HasJsonEncodingSpec a) => ToJSON (SpecJSON a) Source # 
Instance details

Defined in Data.JsonSpec

data Tag (a :: Symbol) Source #

Structural representation of JsonTag. (I.e. a constant string value.)

Constructors

Tag 

newtype Field (key :: Symbol) t Source #

Structural representation of an object field.

Constructors

Field t 

type family JSONStructure (spec :: Specification) where ... Source #

JSONStructure spec is the Haskell type used to contain the JSON data that will be encoded or decoded according to the provided spec.

Basically, we represent JSON objects as "list-like" nested tuples of the form:

(Field @key1 valueType,
(Field @key2 valueType,
(Field @key3 valueType,
())))

Arrays, booleans, numbers, and strings are just Lists, Bools, Scientifics, and Texts respectively.

If the user can convert their normal business logic type to/from this tuple type, then they get a JSON encoding to/from their type that is guaranteed to be compliant with the Specification