json-spec-0.3.0.1: Type-level JSON specification
Safe HaskellNone
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 '[
      Required "name" JsonString,
      Required "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 primary motivation is to allow you to avoid Aeson Generic instances while still getting the possibility of auto-generated (and therefore correct) documentation and code in your servant APIs.

Historically, the trade-off has been:

  1. Use Generic instances, and therefore your API is brittle. Changes to Deeply nested object might unexpectedly change (and break) your API. You must structure your Haskell types exactly as they are rendered into JSON, which may not always be "natural" and easy to work with. In exchange, you get the ability to auto-derive matching ToSchema instances along with various code generation tools that all understand Aeson Generic instances.
  2. Hand-write your ToJSON and FromJSON instances, which means you get to structure your Haskell types in the way that works best for Haskell, while structuring your JSON in the way that works best for your API. It also means you can more easily support "old" decoding versions and more easily maintain backwards compatibility, etc. In exchange, you have to to hand-write your ToSchema instances, and code generation is basically out.

The goal of this library is to provide a way to hand-write the encoding and decoding of your JSON using type-level Specifications, while still allowing the use of tools that can interpret the specification and auto-generate ToSchema instances and code.

The tooling ecosystem that knows how to interpret Specifications is still pretty new, but it at least includes OpenApi compatibility (i.e. ToSchema instances) and Elm code generation.

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 [FieldSpec]

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 '[
    Required "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 '[
          Required "tag" (JsonTag "foo"),
          Required "content" JsonString
        ]
      )
      (
        JsonEither
          (
            JsonObject '[
              Required "tag" (JsonTag "bar"),
              Required "content" JsonInt
            ]
          )
          (
            JsonObject '[
              Required "tag" (JsonTag "baz"),
              Required "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.

JsonLet [(Symbol, Specification)] Specification

A "let" expression. This is useful for giving names to types, which can then be used in the generated code.

This is also useful to shorten repetitive type definitions. For example, this repetitive definition:

type Triangle =
  JsonObject '[
    Required "vertex1" (JsonObject '[
      Required "x" JsonInt,
      Required "y" JsonInt,
      Required "z" JsonInt
    ]),
    Required "vertex2" (JsonObject '[
      Required "x" JsonInt,
      Required "y" JsonInt,
      Required "z" JsonInt
    ]),
    Required "vertex3" (JsonObject '[
      Required "x" JsonInt),
      Required "y" JsonInt),
      Required "z" JsonInt)
    ])
  ]

Can be written more concisely as:

type Triangle =
  JsonLet
    '[
      '("Vertex", JsonObject '[
         ('x', JsonInt),
         ('y', JsonInt),
         ('z', JsonInt)
       ])
     ]
     (JsonObject '[
       Required "vertex1" JsonRef "Vertex",
       Required "vertex2" JsonRef "Vertex",
       Required "vertex3" JsonRef "Vertex"
     ])

Another use is to define recursive types:

type LabelledTree =
  JsonLet
    '[
      '("LabelledTree", JsonObject '[
        Required "label", JsonString,
        Required "children" (JsonArray (JsonRef "LabelledTree"))
       ])
     ]
    (JsonRef "LabelledTree")
JsonRef Symbol

A reference to a specification which has been defined in a surrounding JsonLet.

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.

Instances

Instances details
HasJsonEncodingSpec a => HasJsonEncodingSpec (Set a) Source # 
Instance details

Defined in Data.JsonSpec.Encode

Associated Types

type EncodingSpec (Set a) 
Instance details

Defined in Data.JsonSpec.Encode

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 

Instances

Instances details
KnownSymbol const => StructureFromJSON (Tag const) Source # 
Instance details

Defined in Data.JsonSpec.Decode

Methods

reprParseJSON :: Value -> Parser (Tag const)

newtype Field (key :: Symbol) t Source #

Structural representation of an object field.

Constructors

Field 

Fields

Instances

Instances details
Show t => Show (Field key t) Source # 
Instance details

Defined in Data.JsonSpec.Spec

Methods

showsPrec :: Int -> Field key t -> ShowS #

show :: Field key t -> String #

showList :: [Field key t] -> ShowS #

Eq t => Eq (Field key t) Source # 
Instance details

Defined in Data.JsonSpec.Spec

Methods

(==) :: Field key t -> Field key t -> Bool #

(/=) :: Field key t -> Field key t -> Bool #

(KnownSymbol key, StructureFromJSON val, StructureFromJSON more) => StructureFromJSON (Field key val, more) Source # 
Instance details

Defined in Data.JsonSpec.Decode

Methods

reprParseJSON :: Value -> Parser (Field key val, more)

(KnownSymbol key, StructureFromJSON val, StructureFromJSON more) => StructureFromJSON (Maybe (Field key val), more) Source # 
Instance details

Defined in Data.JsonSpec.Decode

Methods

reprParseJSON :: Value -> Parser (Maybe (Field key val), more)

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

Equations

JSONStructure spec = JStruct ('[] :: [(Symbol, Type)]) spec 

newtype Rec (env :: [(Symbol, Type)]) (name :: Symbol) (spec :: Specification) Source #

This allows for recursive specifications.

Since the specification is at the type level, and type level haskell is strict, specifying a recursive definition the "naive" way would cause an infinitely sized type.

For example this won't work:

data Foo = Foo [Foo]
instance HasJsonEncodingSpec Foo where
  type EncodingSpec Foo = JsonArray (EncodingSpec Foo)
  toJSONStructure = ... can't be written

Using JsonLet prevents the specification type from being infinitely sized, but what about "structure" type which holds real values corresponding to the spec? The structure type has to have some way to reference itself or else it too would be infinitely sized.

In order to "reference itself" the structure type has to go through a newtype somewhere along the way, and that's what this type is for. Whenever the structure type for your spec requires a self-reference, it will require you to wrap the recursed upon values in this type.

For example:

data Foo = Foo [Foo]
instance HasJsonEncodingSpec Foo where
  type EncodingSpec Foo =
    JsonLet
      '[ '("Foo", JsonArray (JsonRef "Foo")) ]
      (JsonRef "Foo")
  toJSONStructure (Foo fs) = 
    [ Rec (toJSONStructure f)
    | f <- fs
    ]

Constructors

Rec 

Fields

  • unRec :: JStruct ('(name, Rec env name spec) ': env) spec
     

Instances

Instances details
StructureFromJSON (JStruct ('(name, Rec env name spec) ': env) spec) => StructureFromJSON (Rec env name spec) Source # 
Instance details

Defined in Data.JsonSpec.Decode

Methods

reprParseJSON :: Value -> Parser (Rec env name spec)

eitherDecode :: forall (spec :: Specification). StructureFromJSON (JSONStructure spec) => Proxy spec -> Value -> Either String (JSONStructure spec) Source #

Directly decode some JSON accoring to a spec without going through any To/FromJSON instances.

class StructureFromJSON a Source #

Analog of FromJSON, but specialized for decoding our "json representations", and closed to the user because the haskell representation scheme is fixed and not extensible by the user.

We can't just use FromJSON because the types we are using to represent "json data" (i.e. the JSONStructure type family) already have ToJSON instances. Even if we were to make a bunch of newtypes or whatever to act as the json representation (and therefor also force the user to do a lot of wrapping and unwrapping), that still wouldn't be sufficient because someone could always write an overlapping (or incoherent) ToJSON instance of our newtype! This way we don't have to worry about any of that, and the types that the user must deal with when implementing fromJSONRepr can be simple tuples and such.

Minimal complete definition

reprParseJSON

Instances

Instances details
StructureFromJSON Scientific Source # 
Instance details

Defined in Data.JsonSpec.Decode

StructureFromJSON Text Source # 
Instance details

Defined in Data.JsonSpec.Decode

StructureFromJSON UTCTime Source # 
Instance details

Defined in Data.JsonSpec.Decode

StructureFromJSON () Source # 
Instance details

Defined in Data.JsonSpec.Decode

Methods

reprParseJSON :: Value -> Parser ()

StructureFromJSON Bool Source # 
Instance details

Defined in Data.JsonSpec.Decode

StructureFromJSON Int Source # 
Instance details

Defined in Data.JsonSpec.Decode

KnownSymbol const => StructureFromJSON (Tag const) Source # 
Instance details

Defined in Data.JsonSpec.Decode

Methods

reprParseJSON :: Value -> Parser (Tag const)

StructureFromJSON a => StructureFromJSON (Maybe a) Source # 
Instance details

Defined in Data.JsonSpec.Decode

Methods

reprParseJSON :: Value -> Parser (Maybe a)

StructureFromJSON a => StructureFromJSON [a] Source # 
Instance details

Defined in Data.JsonSpec.Decode

Methods

reprParseJSON :: Value -> Parser [a]

(StructureFromJSON left, StructureFromJSON right) => StructureFromJSON (Either left right) Source # 
Instance details

Defined in Data.JsonSpec.Decode

Methods

reprParseJSON :: Value -> Parser (Either left right)

(KnownSymbol key, StructureFromJSON val, StructureFromJSON more) => StructureFromJSON (Field key val, more) Source # 
Instance details

Defined in Data.JsonSpec.Decode

Methods

reprParseJSON :: Value -> Parser (Field key val, more)

(KnownSymbol key, StructureFromJSON val, StructureFromJSON more) => StructureFromJSON (Maybe (Field key val), more) Source # 
Instance details

Defined in Data.JsonSpec.Decode

Methods

reprParseJSON :: Value -> Parser (Maybe (Field key val), more)

StructureFromJSON (JStruct ('(name, Rec env name spec) ': env) spec) => StructureFromJSON (Rec env name spec) Source # 
Instance details

Defined in Data.JsonSpec.Decode

Methods

reprParseJSON :: Value -> Parser (Rec env name spec)

data FieldSpec Source #

Specify a field in an object.

Constructors

Required Symbol Specification

The field is required

Optional Symbol Specification

The field is optionsl