json-spec-openapi-0.3.0.0: json-spec-openapi
Safe HaskellNone
LanguageHaskell2010

Data.JsonSpec.OpenApi

Description

This module provides tools for integrating the type-level JSON Specification with the "openapi" package.

You can use toOpenApiSchema as a low-level tool to transform json-spec Specifications into openapi3 Schemas directly, irrespective of any particular business data type.

More likely you will want to use -XDerivingVia along with EncodingSchema or DecodingSchema to derive ToSchema instances for your data types.

Example, given this data type:

data User = User
  {      name :: Text
  , lastLogin :: Maybe UTCTime
  }
  deriving ToSchema via (EncodingSchema User) -- <-- ToSchema instance defined here
instance HasJsonEncodingSpec User where
  type EncodingSpec User =
    JsonObject
      '[ Required "name" JsonString
       , Optional "last-login" JsonDateTime
       ]
  toJSONStructure user =
    (Field @"name" (name user),
    (fmap (Field @"last-login") (lastLogin user),
    ()))

Calling encode (toSchema (Proxy :: Proxy User)) will produce the following Schema:

{
  "additionalProperties": false,
  "properties": {
    "last-login": {
      "format": "date-time",
      "type": "string"
    },
    "name": {
      "type": "string"
    }
  },
  "required": [
    "name"
  ],
  "type": "object"
}

If you needed more control over the content of the schema you might also consider doing something like this, e.g. in the case where you would like to allow additional properties:

data User = User
  {      name :: Text
  , lastLogin :: Maybe UTCTime
  }
instance HasJsonEncodingSpec User where
  type EncodingSpec User =
    JsonObject
      '[ Required "name" JsonString
       , Optional "last-login" JsonDateTime
       ]
  toJSONStructure user =
    (Field @"name" (name user),
    (fmap (Field @"last-login") (lastLogin user),
    ()))
instance ToSchema User where
  declareNamedSchema _proxy =
      pure $
        NamedSchema
          Nothing
          (
            toOpenApiSchema (EncodingSpec User)
              & set
                  additionalProperties
                  (Just (AdditionalPropertiesAllowed True))
          )
Synopsis

Documentation

toOpenApiSchema :: forall (spec :: Specification). Schemaable spec => Proxy spec -> (Definitions Schema, Schema) Source #

Convert a Specification into an OpenApi Schema. The type class Schemaable is an internal and opaque implementation detail and not something you should have to worry about.

It should already have an instance for every Specification that can be turned into a Schema. If it does not, then that is a bug. Please report it! :-)

The limitations of this function are:

  • It behaves in a possibly unexpected way when given a top level schema of the form:

    JsonLet '[
      '("foo", ...)
    ] (
      JsonRef "foo"
    )

    toOpenApiSchema returns a Schema, not a Referenced Schema. Therefore, if the "top level" of the Specification is a JsonRef, then we will try to dereference and inline the referenced schema. In other words,

    toOpenApiSchema (Proxy @(
        JsonLet
          '[ '("foo", JsonString) ]
          (JsonRef "foo")
      ))

    will behave as if you had called

    toOpenApiSchema (Proxy @(
        JsonLet
          '[ '("foo", JsonString) ]
          JsonString
      ))

    However, if the reference is undefined, then you will get a custom type error explaining what the problem is.

  • With the exception of the above point, we do not check to make sure that every referenced used in the returned Schema actually contains a definition. So for instance this will "work":

    let
      (defs, schema) =
        toOpenApiSchema
          (Proxy @(
            JsonObject '[
              ("bar", JsonRef "not-defined")
            ]
          ))
    in
      ...

    This will compile, and will not throw any runtime errors directly, but depending on how you use defs and schema (like, for instance, generating an OpenApi specification) you will probably encounter a runtime error complaining that "not-defined" hasn't been defined.

class Schemaable (spec :: Specification) Source #

Specifications that can be turned into OpenApi Schemas.

This is intended to be an opaque implementation detail. The only reason it is exported is because there are some cases where you might need to be able to spell this constraint in code that builds off of this package.

Minimal complete definition

schemaable

Instances

Instances details
Schemaable 'JsonBool Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

Schemaable 'JsonDateTime Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

Schemaable 'JsonInt Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

Schemaable 'JsonNum Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

Schemaable 'JsonString Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

Schemaable spec => Schemaable ('JsonArray spec) Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

Schemaable spec => Schemaable ('JsonNullable spec) Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

(Schemaable ('JsonObject more), Refable spec, KnownSymbol key) => Schemaable ('JsonObject ('Optional key spec ': more)) Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

Methods

schemaable :: MonadDeclare (Definitions Schema) m => Proxy ('JsonObject ('Optional key spec ': more)) -> m Schema

(Schemaable ('JsonObject more), Refable spec, KnownSymbol key) => Schemaable ('JsonObject ('Required key spec ': more)) Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

Methods

schemaable :: MonadDeclare (Definitions Schema) m => Proxy ('JsonObject ('Required key spec ': more)) -> m Schema

Schemaable ('JsonObject ('[] :: [FieldSpec])) Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

KnownSymbol tag => Schemaable ('JsonTag tag) Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

(Schemaable left, Schemaable right) => Schemaable ('JsonEither left right) Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

Methods

schemaable :: MonadDeclare (Definitions Schema) m => Proxy ('JsonEither left right) -> m Schema

(KnownSymbol name, Schemaable def, Schemaable ('JsonLet more ('JsonRef target))) => Schemaable ('JsonLet ('(name, def) ': more) ('JsonRef target)) Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

Methods

schemaable :: MonadDeclare (Definitions Schema) m => Proxy ('JsonLet ('(name, def) ': more) ('JsonRef target)) -> m Schema

(KnownSymbol target, Schemaable def, Schemaable ('JsonLet more def)) => Schemaable ('JsonLet ('(target, def) ': more) ('JsonRef target)) Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

Methods

schemaable :: MonadDeclare (Definitions Schema) m => Proxy ('JsonLet ('(target, def) ': more) ('JsonRef target)) -> m Schema

Unsatisfiable (((((((T "`JsonRef \"" ':<>: T target) ':<>: T "\"` is not defined.\n") ':$$: T "You are trying to use a JsonRef as the \"top level\" ") ':$$: T "schema. We try to satisfy this request by looking up ") ':$$: T "the reference and inlining it. However in this case you ") ':$$: T "are trying to reference a schema which is not defined, ") ':$$: T "so this won't work.\n") => Schemaable ('JsonLet ('[] :: [(Symbol, Specification)]) ('JsonRef target)) Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

Methods

schemaable :: MonadDeclare (Definitions Schema) m => Proxy ('JsonLet ('[] :: [(Symbol, Specification)]) ('JsonRef target)) -> m Schema

(Defs defs, Schemaable spec) => Schemaable ('JsonLet defs spec) Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

Methods

schemaable :: MonadDeclare (Definitions Schema) m => Proxy ('JsonLet defs spec) -> m Schema

newtype EncodingSchema a Source #

Helper for defining ToSchema instances based on HasJsonEncodingSpec using deriving via.

Example:

data MyType = ...
  deriving ToSchema via (EncodingSchema MyType)
instance HasJsonEncodingSchema MyType where
  ...

Constructors

EncodingSchema 

Fields

Instances

Instances details
(Schemaable (EncodingSpec a), Typeable a) => ToSchema (EncodingSchema a) Source # 
Instance details

Defined in Data.JsonSpec.OpenApi

newtype DecodingSchema a Source #

Helper for defining ToSchema instances based on HasJsonDecodingSpec using deriving via.

Example:

data MyType = ...
  deriving ToSchema via (DecodingSchema MyType)
instance HasJsonDecodingSchema MyType where
  ...

Constructors

DecodingSchema 

Fields

Instances

Instances details
(Schemaable (DecodingSpec a), Typeable a) => ToSchema (DecodingSchema a) Source # 
Instance details

Defined in Data.JsonSpec.OpenApi