| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
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
will produce the following Schema:encode (toSchema (Proxy :: Proxy User))
{
"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
- toOpenApiSchema :: forall (spec :: Specification). Schemaable spec => Proxy spec -> (Definitions Schema, Schema)
- class Schemaable (spec :: Specification)
- newtype EncodingSchema a = EncodingSchema {
- unEncodingSchema :: a
- newtype DecodingSchema a = DecodingSchema {
- unDecodingSchema :: a
- type family Rename (spec :: Specification) :: Specification where ...
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" )toOpenApiSchemareturns aSchema, not a. Therefore, if the "top level" of theReferencedSchemaSpecificationis aJsonRef, 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
Schemaactually 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
defsandschema(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
| Inlineable ('[] :: [(Symbol, Specification)]) spec => Schemaable spec Source # | |
Defined in Data.JsonSpec.OpenApi Methods schemaable :: MonadDeclare (Definitions Schema) m => 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
| (Schemaable (EncodingSpec a), Typeable a) => ToSchema (EncodingSchema a) Source # | |
Defined in Data.JsonSpec.OpenApi Methods declareNamedSchema :: Proxy (EncodingSchema a) -> Declare (Definitions Schema) NamedSchema # | |
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
| (Schemaable (DecodingSpec a), Typeable a) => ToSchema (DecodingSchema a) Source # | |
Defined in Data.JsonSpec.OpenApi Methods declareNamedSchema :: Proxy (DecodingSchema a) -> Declare (Definitions Schema) NamedSchema # | |
type family Rename (spec :: Specification) :: Specification where ... Source #
Resolve OpenApi name conflicts.
The json-spec mechanism for giving names to things is more powerful than
OpenApi mechanism for naming things. JsonLet allows for nested scopes,
where deeper names can shadow other names. OpenApi on the other hand only has
a flat space to name schemas, so every name is "globally scoped", resulting
in possible name conflicts when mapping JsonLet names to OpenApi names.
This type family resolves the conflict by renaming the JsonLet names
in your Specification so that they are all unique, so they won't
conflict when mapping them into the global OpenApi schema namespace.
We do not apply this type family by default because it has the potential to
add significant compilation time if your Specifications are large. If you
happen to know that your Specification contains no name conflicts then you
can avoid paying that cost.
It isn't perfect. I've tried to strike a balance between implementation complexity and avoiding unnecessary renames.
Essentially, if a duplicate name is detected, I append a ".n" to the
name, where n is an integer. So if you are using names that already
follow this format you might get into trouble.
For instance, this Specification will fail to rename properly:
> JsonLet
> '[ '("foo", JsonString)
> , '("foo.1", JsonString)
> ]
> ( JsonObject
> '[ "field1" ::: JsonRef "foo"
> , "field2" ::: JsonLet '[ '("foo", JsonInt)] (JsonRef "foo")
> ]
> )
because the "foo" in "field2" will be renamed to "foo.1", causing a new conflict with the existing "foo.1".
Equations
| Rename spec = Fst (FoldRename ('G ('[] :: [NameState])) ('A ('[] :: [NameState])) spec) |