| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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:
- Use Generic instances, and therefore your API is brittle. Changes to a 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.
- 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
- data Specification
- type (:::) = 'Required
- type (::?) = 'Optional
- data FieldSpec
- class HasJsonEncodingSpec a where- type EncodingSpec a :: Specification
- toJSONStructure :: a -> JSONStructure (EncodingSpec a)
 
- class HasJsonDecodingSpec a where- type DecodingSpec a :: Specification
- fromJSONStructure :: JSONStructure (DecodingSpec a) -> Parser a
 
- newtype SpecJSON a = SpecJSON {- unSpecJson :: a
 
- data Tag (a :: Symbol) = Tag
- newtype Field (key :: Symbol) t = Field t
- unField :: forall (key :: Symbol) t. Field key t -> t
- newtype Ref (env :: Env) (spec :: Specification) = Ref {- unRef :: JStruct env spec
 
- eitherDecode :: forall (spec :: Specification). StructureFromJSON (JSONStructure spec) => Proxy spec -> Value -> Either String (JSONStructure spec)
- encode :: forall (spec :: Specification). StructureToJSON (JSONStructure spec) => Proxy spec -> JSONStructure spec -> Value
- type family JSONStructure (spec :: Specification) where ...
- class StructureFromJSON a
- class StructureToJSON a
Writing specifications
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
       | 
| 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  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  | 
| 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 '[
       "vertex1" ::: JsonRef "Vertex",
       "vertex2" ::: JsonRef "Vertex",
       "vertex3" ::: JsonRef "Vertex"
     ])Another use is to define recursive types: type LabelledTree =
  JsonLet
    '[
      '("LabelledTree", JsonObject '[
        "label" ::: JsonString,
        "children" ::: JsonArray (JsonRef "LabelledTree")
       ])
     ]
    (JsonRef "LabelledTree") | 
| JsonRef Symbol | A reference to a specification which has been defined in a surrounding
       | 
| JsonRaw | Some raw, uninterpreted JSON value | 
Specify a field in an object.
Constructors
| Required Symbol Specification | The field is required | 
| Optional Symbol Specification | The field is optionsl | 
Encoding/decoding via a Specification
class HasJsonEncodingSpec a where Source #
Types of this class can be encoded to JSON according to a type-level
  Specification.
Methods
toJSONStructure :: a -> JSONStructure (EncodingSpec a) Source #
Encode the value into the structure appropriate for the specification.
Instances
| HasJsonEncodingSpec a => HasJsonEncodingSpec (Set a) Source # | |||||
| Defined in Data.JsonSpec.Encode Associated Types 
 Methods toJSONStructure :: Set a -> JSONStructure (EncodingSpec (Set a)) Source # | |||||
class HasJsonDecodingSpec a where Source #
Types of this class can be JSON decoded according to a type-level
  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 aa 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".
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
| (StructureFromJSON (JSONStructure (DecodingSpec a)), HasJsonDecodingSpec a) => FromJSON (SpecJSON a) Source # | |
| Defined in Data.JsonSpec | |
| (StructureToJSON (JSONStructure (EncodingSpec a)), HasJsonEncodingSpec a) => ToJSON (SpecJSON a) Source # | |
data Tag (a :: Symbol) Source #
Structural representation of JsonTag. (I.e. a constant string value.) 
Constructors
| Tag | 
Instances
| KnownSymbol const => StructureFromJSON (Tag const) Source # | |
| Defined in Data.JsonSpec.Decode Methods reprParseJSON :: Value -> Parser (Tag const) | |
| KnownSymbol const => StructureToJSON (Tag const) Source # | |
| Defined in Data.JsonSpec.Encode Methods reprToJSON :: Tag const -> Value | |
newtype Field (key :: Symbol) t Source #
Structural representation of an object field.
Constructors
| Field t | 
Instances
| HasField (k :: Symbol) ((Field k v, more) :: Type) (v :: Type) Source # | |
| Defined in Data.JsonSpec.Spec | |
| HasField k2 more v => HasField (k2 :: k1) ((Field notIt x, more) :: Type) (v :: Type) Source # | |
| Defined in Data.JsonSpec.Spec | |
| HasField k2 more v => HasField (k2 :: k1) ((Maybe (Field notIt x), more) :: Type) (v :: Type) Source # | |
| Defined in Data.JsonSpec.Spec | |
| HasField (k :: Symbol) ((Maybe (Field k v), more) :: Type) (Maybe v :: Type) Source # | |
| Show t => Show (Field key t) Source # | |
| Eq t => Eq (Field key t) Source # | |
| (KnownSymbol key, StructureFromJSON val, StructureFromJSON more) => StructureFromJSON (Field key val, more) Source # | |
| 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 # | |
| Defined in Data.JsonSpec.Decode Methods reprParseJSON :: Value -> Parser (Maybe (Field key val), more) | |
newtype Ref (env :: Env) (spec :: Specification) Source #
This is the "Haskell structure" type of JsonRef references.
The main reason why we need this is because of recursion, as explained below:
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
... because EncodingSpec Foo would expand strictly into an array of
  EncodingSpec Foo, which would expand strictly... to infinity.
Using JsonLet prevents the specification type from being infinitely
  sized, but what about the "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 you use a JsonRef in the spec, the corresponding
  structural type will have a Ref newtype wrapper around the
  "dereferenced" structure type.
For example:
data Foo = Foo [Foo]
instance HasJsonEncodingSpec Foo where
  type EncodingSpec Foo =
    JsonLet
      '[ '("Foo", JsonArray (JsonRef "Foo")) ]
      (JsonRef "Foo")
  toJSONStructure (Foo fs) =
    Ref [ toJSONStructure <$> fs ]Strictly speaking, we wouldn't necessarily have to translate every
  JsonRef into a Ref. In principal we could get away with inserting a
  Ref somewhere in every mutually recursive cycle. But the type level
  programming to figure that out a) probably wouldn't do any favors to
  compilation times, b) is beyond what I'm willing to attempted right
  now, and c) requires some kind of deterministic and stable choice
  about where to insert the Ref (which I'm not even certain exists)
  lest arbitrary HasJsonEncodingSpec or HasJsonDecodingSpec instances
  break when the members of the recursive cycle change, causing a new
  choice about where to place the Ref.
Instances
| StructureFromJSON (JStruct env spec) => StructureFromJSON (Ref env spec) Source # | |
| Defined in Data.JsonSpec.Decode Methods reprParseJSON :: Value -> Parser (Ref env spec) | |
| StructureToJSON (JStruct env spec) => StructureToJSON (Ref env spec) Source # | |
| Defined in Data.JsonSpec.Encode Methods reprToJSON :: Ref env spec -> Value | |
Direct encoding/decoding
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.
encode :: forall (spec :: Specification). StructureToJSON (JSONStructure spec) => Proxy spec -> JSONStructure spec -> Value Source #
Given a raw Haskell structure, directly encode it directly into an aeson Value without having to go through any To/FromJSON instances.
See also: eitherDecode.
Other stuff
The items in this section are mainly exported because once in a while you might need to include them in a type signature, but they are not intended to be used directly.
type family JSONStructure (spec :: Specification) where ... Source #
JSONStructure specspec.
Basically, we represent JSON objects as "list-like" nested tuples of the form:
(Field @key1 valueType, (Field @key2 valueType, (Field @key3 valueType, ())))
Note! "Object structures" of this type have the appropriate HasField
  instances, which allows you to use -XOverloadedRecordDot to extract
  values as an alternative to pattern matching the whole tuple structure
  when building your HasJsonDecodingSpec instances. See TestHasField
  in the tests for an example
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, Specification)]]) spec | 
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
class StructureToJSON a Source #
This is like ToJSON, but specialized for our custom "json
  representation" types (i.e. the JSONStructure type family). It is
  also closed (i.e. not exported, so the user can't add instances),
  because our json representation is closed.
see StructureFromJSON for an explaination about why we don't just use
  ToJSON.
Minimal complete definition
reprToJSON