Code Monkey home page Code Monkey logo

openapi3's Introduction

OpenApi 3

Hackage Build Status Stackage LTS Stackage Nightly

OpenAPI 3.0 data model.

The original OpenAPI 3.0 specification is available at http://swagger.io/specification/.

This package is heavily based on excellent work on Swagger 2.0 at https://github.com/GetShopTV/swagger2.

Usage

This library is intended to be used for decoding and encoding OpenApi 3.0.3 specifications as well as manipulating them.

Please refer to haddock documentation.

Some examples can be found in examples/ directory.

Trying out

All generated swagger specifications can be interactively viewed on Swagger Editor.

Ready-to-use specification can be served as JSON and interactive API documentation can be displayed using Swagger UI.

Many Swagger tools, including server and client code generation for many languages, can be found on Swagger's Tools and Integrations page.

Contributing

We are happy to receive bug reports, fixes, documentation enhancements, and other improvements.

Please report bugs via the github issue tracker.

GetShopTV Team

Biocad Team

openapi3's People

Contributors

agrafix avatar albertov avatar anneloreegger avatar arybczak avatar benweitzman avatar domenkozar avatar epsilonhalbe avatar felixonmars avatar fieldstrength avatar fisx avatar fizruk avatar gkleen avatar gromakovsky avatar ilyakooo0 avatar jackkelly-bellroy avatar johanwinther avatar maksbotan avatar mithrandi avatar mossprescott avatar ncaq avatar parsonsmatt avatar phadej avatar przemyslawlib-blueveery avatar soenkehahn avatar stevladimir avatar swamp-agr avatar taojang avatar tonicebrian avatar vwwv avatar ysangkok avatar

Stargazers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

Watchers

 avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar  avatar

openapi3's Issues

SecurityDefinitions missing "Ixed" and "At" type-class instances

Hi,

The SecurityDefinitions type defined in the OpenAPI library here

Which is a newtype wrapper over Definitions, which in-turn is a type synonym for an InsOrdHashMap Text type.

SecurityDefinitions seems to be missing type-class instances for Ixed and At type-classes, which enables us to use them with Lenses and refer to their indices using at or ix and set a particular SecurityScheme at that index if needed.

The following instances are already present in the Swagger version of the same data-type here.

Opening the issue in addition to #76 here, I'll make a PR soon for this.

Validation Schema ToJSON with Discriminator and Sum datatype

First of all, thank you for this great library.
We wanted to go further and set up tests on Schema/ToJson validation (validateToJSON).

For simple types, it works without any problem.
Beside, we have sum datatypes with a field as discriminant. So, I added Discriminator on this fiedl. But the test fail with:

["Value not valid under any of 'oneOf' schemas: Object (fromList [(\"objectType\",String \"ObjectOne\"),(\"identifier\",String \"123\"),(\"name\",String \"object one\")])"

I haven't found where I am wrong. I tried the different sumEncoding without success.

Below is the code with the tests in fail.

module Commons.Model.Discriminator where

import Data.Aeson
import Data.Aeson.Types
import qualified Data.HashMap.Strict as HM
import Data.OpenApi as OpenApi
import Relude

data SuperObject
  = Object1 ObjectOne
  | Object2 ObjectTwo
  deriving (Generic, Show, Eq)

instance ToJSON SuperObject where
  toJSON = genericToJSON defaultOptions {omitNothingFields = True, sumEncoding = UntaggedValue}

instance FromJSON SuperObject where
  parseJSON anObject@(Object p) =
    case HM.lookup "objectType" p of
      Just "ObjectOne" -> Object1 <$> parseJSON anObject
      Just "ObjectTwo" -> Object2 <$> parseJSON anObject
      _ -> fail "expected ObjectOne or ObjectTwo"
  parseJSON invalid = typeMismatch "ObjectOne or ObjectTwo" invalid

instance ToSchema SuperObject where
  declareNamedSchema val = do
    mediaSchema <- genericDeclareNamedSchema defaultSchemaOptions val
    let newDiscriminator =
          Discriminator
            { _discriminatorPropertyName = "objectType",
              _discriminatorMapping = [("ObjectOne", "#/components/schemas/ObjectOne"), ("ObjectTwo", "#/components/schemas/ObjectTwo")]
            }
    pure $ addOneDiscriminator newDiscriminator mediaSchema

addOneDiscriminator :: Discriminator -> NamedSchema -> NamedSchema
addOneDiscriminator newDiscriminator namedSchema@NamedSchema {_namedSchemaSchema = initialSchema} =
  namedSchema {_namedSchemaSchema = initialSchema {_schemaDiscriminator = Just newDiscriminator}}

data ObjectOne = ObjectOne
  { identifier :: Text,
    name :: Text,
    objectType :: Text
  }
  deriving (Generic, Show, Eq)

instance ToJSON ObjectOne where
  toJSON = genericToJSON defaultOptions

instance FromJSON ObjectOne where
  parseJSON = genericParseJSON defaultOptions

instance ToSchema ObjectOne where
  declareNamedSchema = genericDeclareNamedSchema defaultSchemaOptions

data ObjectTwo = ObjectTwo
  { identifier :: Text,
    name :: Text,
    objectType :: Text
  }
  deriving (Generic, Show, Eq)

instance ToJSON ObjectTwo where
  toJSON = genericToJSON defaultOptions

instance FromJSON ObjectTwo where
  parseJSON = genericParseJSON defaultOptions

instance ToSchema ObjectTwo where
  declareNamedSchema = genericDeclareNamedSchema defaultSchemaOptions

Test module:

module Commons.Model.DiscriminatorSpec where

import Commons.Model.Discriminator
import Relude
import Data.Aeson as Aeson
import Data.Aeson.QQ
import Data.OpenApi.Schema.Validation (validateToJSON)
import Test.Tasty.HUnit

test_validateSchemaToJSON_superObject1 =
  testCase "When validating a SuperObject Object1 against the schema, then everything is valid" $
    let superObject =
          Object1
            ObjectOne
              { identifier = "123",
                name = "object one",
                objectType = "ObjectOne"
              }
     in validateToJSON superObject @?= []

test_validateSchemaToJSON_superObject2 =
  testCase "When validating a SuperObject Object2 against the schema, then everything is valid" $
    let superObject =
          Object2
            ObjectTwo
              { identifier = "123",
                name = "object two",
                objectType = "ObjectTwo"
              }
     in validateToJSON superObject @?= []

Wrong format when generating empty scopes map

Having an empty _oAuth2Scopes map generates the following object which is invalid:

{
  "securitySchemes": {
    "OAuth2": {
      "description": "Description",
      "flows": {
        "clientCredentials": {
          "tokenUrl": "https://example.com"
        }
      },
      "type": "oauth2"
    }
  }
}

To make it valid the scopes property needs to be added, but with an empty object:

{
  "securitySchemes": {
    "OAuth2": {
      "description": "Description",
      "flows": {
        "clientCredentials": {
          "tokenUrl": "https://example.com",
          "scopes": {} // Added
        }
      },
      "type": "oauth2"
    }
  }
}

Monoid Instance for Example

There is no monoid instance for Example, though it seems one could be defined. Is that by design or oversight? Glad to submit a PR if you would accept it!

Why are the schemas different for `ToParamSchema UUID` and `ToSchema UUID`

Hello,

While writing manual OpenApi instances for a phantom type wrapping UUID today, I noticed that (undeclare (declareNamedSchema (Proxy @UUID)))._namedSchemaSchema /= toParamSchema (Proxy @UUID), which I find surprising (not just for UUID but for any type).

instance ToParamSchema UUID where
  toParamSchema _ = mempty
    & type_ ?~ OpenApiString
    & format ?~ "uuid"

instance ToSchema UUID.UUID where
  declareNamedSchema p = pure $ named "UUID" $ paramSchemaToSchema p
    & example ?~ toJSON (UUID.toText UUID.nil)

Is there a reason why the example is only for ToSchema and not for ToParamSchema?
That looks like a bug to me.

I would expect the implementation to be

instance ToParamSchema UUID where
  toParamSchema _ = mempty
    & type_ ?~ OpenApiString
    & format ?~ "uuid"
    & example ?~ toJSON (UUID.toText UUID.nil)

instance ToSchema UUID.UUID where
  declareNamedSchema p = pure $ named "UUID" $ paramSchemaToSchema p

More generally, is there a scenario where (undeclare (declareNamedSchema (Proxy @a)))._namedSchemaSchema /= toParamSchema (Proxy @a) makes sense for any type a?

Generic polymorphic schema handle lists differently to aeson

Consider a polymorphic type data T a = T [a], where the parameter is used in a list. The generically-derived instance ToSchema (T Char) agrees with ToJSON (encodes as a string), but the polymorphic version instance ToSchema (T a) does not (when used at a ~ Char -- it encodes as an array of "characters" i.e. length-1 strings.).

A complete example

{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}

module Main where

import Data.Aeson
import Data.OpenApi
import GHC.Generics

data Poly a = Poly [a]
 deriving (Generic,Show)

data Mono a = Mono [a]
 deriving (Generic,Show)

instance ToJSON a => ToJSON (Poly a)
instance ToSchema a => ToSchema (Poly a)

instance ToJSON (Mono Char)
instance ToSchema (Mono Char)

main :: IO ()
main = do
  putStrLn "Testing monomorphic instance"
  go $ Mono "foo"
  putStrLn ""
  putStrLn "Testing polymorphic instance"
  go $ Poly "foo"
 where
  go x = do
    case validatePrettyToJSON x of
      Nothing -> putStrLn "validation passed"
      Just err -> putStrLn "validation FAILED" >> putStrLn err

which results in

Testing monomorphic instance
validation passed

Testing polymorphic instance
validation FAILED
Validation against the schema fails:
  * expected JSON value of type OpenApiArray

JSON value:
"foo"

Swagger Schema:
{
    "items": {
        "example": "?",
        "maxLength": 1,
        "minLength": 1,
        "type": "string"
    },
    "type": "array"
}

Swagger Description Context:
{}

This is presumably because openapi3 and aeson handle the special case of [Char] differently.
(There may be some other such cases that differ -- I have not looked further. #50 is perhaps related.)

Global type name uniqueness constraint too onerous

Due to how Monoid instances for hashmaps work, the final API description contains exact same schemas for different types with the same name.

This is a bug unless it is required that type names are globally unique. However, it should be possible to lift this requirement by disambiguating hashmap keys, i. e. by adding route name as a prefix to each key.

Alternatively, I'd like there to be a warning or even an error, because otherwise I simply end up with wrong documentation.

Example:

-- in Module1.hs
data ResponseBody = ResponseBody { rbField1 :: () } deriving Generic

-- in Module2.hs
data ResponseBody = ResponseBody { rbField2 :: () } deriving Generic

-- in Main.hs
type MyApi
  = "Route1" :> Get '[JSON] Module1.ResponseBody
    :<|>
    "Route2" :> Get '[JSON] Module2.ResponseBody

main = let swagger = toOpenApi (Proxy :: Proxy MyApi) in
  B.putStrLn $ encodePretty swagger
{
    "components": {
        "schemas": {
            "ResponseBody": {
                "type": "object",
                "properties": {
                    "rbField2": {
                        "items": {},
                        "maxItems": 0,
                        "type": "array",
                        "example": []
                    }
                },
                "required": [
                    "rbField2"
                ]
            }
        }
    },
    "openapi": "3.0.0",
    "paths": {
        "/Route1": {
            "get": {
                "responses": {
                    "200": {
                        "content": {
                            "application/json;charset=utf-8": {
                                "schema": {
                                    "$ref": "#/components/schemas/ResponseBody"
                                }
                            }
                        },
                        "description": ""
                    }
                }
            }
        },
        "/Route2": {
            "get": {
                "responses": {
                    "200": {
                        "content": {
                            "application/json;charset=utf-8": {
                                "schema": {
                                    "$ref": "#/components/schemas/ResponseBody"
                                }
                            }
                        },
                        "description": ""
                    }
                }
            }
        }
    },
    "info": {
        "version": "",
        "title": ""
    }
}

invalid schema

I tried to leverage some automation on my openapi spec but they all failed because of errors in the schema:

Semantic error at components.schemas.BaselineCheck_'HasCase_PhysicalUnit
Component names can only contain the characters A-Z a-z 0-9 - . _
Semantic error at components.schemas.BaselineDescriptor_'CategoricalDescriptor
Component names can only contain the characters A-Z a-z 0-9 - . _

also I have names like "PlayerPoly_(PointG_Int)" .

I've tried to add some tests and a fix doing:

...
  , datatypeNameModifier = conformDatatypeNameModifier
...

-- | Adhere to spec https://www.rfc-editor.org/rfc/rfc3986#section-3.1 
-- https://github.com/OAI/OpenAPI-Specification/blob/main/versions/3.0.3.md
conformDatatypeNameModifier :: String -> String
conformDatatypeNameModifier = 
  foldl (\acc x -> acc ++ convertChar x) ""  
  where 
    convertChar = \case 
      '(' -> "_parensL_"
      ')' -> "_parensR_"
--      '\'' -> "_squote_"
      other -> [other]

but seems like a better fix would be to do "percent-encoding" . I wonder if that would be allright and in which case how to do that. Looks like we could import a library like https://hackage.haskell.org/package/network-uri-2.6.4.2/docs/Network-URI.html#v:escapeURIString . Before putting up a PR, I wanted to ask if it's fine ?

How to avoid logic duplication with manual `ToJSON` instance?

If i derive my instances of ToJSON and ToSchema, then they play nice.
However the JSON is not fit for its intended purpose.

If I manually make an instance of ToJSON, is there anyway I can avoid having to write analogous logic for ToSchema.

The only solution I see is to write an intermediary data type with which deriving gives a desired result,
and write the to and from functions between the original and intermediary type.
Have I missed something? Is there a more idiomatic way?

Invalid schema with types with primes (`'`)

When generically deriving a schema for a type whose name contains a ' we (might) generate a malformed spec.
(Such a type may come from being defined to have such a name, or mentioning a promoted constructor (with DataKinds).)
If the openapi3 generates a named schema object, it will be named the same as the type (applied to parameters, with spaces replaced by underscores).
Unfortunately, the spec https://swagger.io/specification/#components-object says this is invalid:

All the fixed fields declared above are objects that MUST use keys that match the regular expression: ^[a-zA-Z0-9\.\-_]+$

Both the online swagger editor and openapi-generator-cli validate reject the schema as invalid.

For example, consider the program

{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}

module Main where

import qualified Data.ByteString.Lazy.Char8 as B
import Data.OpenApi
import Data.OpenApi.Declare
import Data.OpenApi.Internal.Utils
import Data.Proxy
import GHC.Generics

data A = A {x :: T'}
 deriving Generic

data T' = T'
  deriving Generic

instance ToSchema A
instance ToSchema T'

main :: IO ()
main = B.putStrLn $ encodePretty $  execDeclare (declareSchemaRef $ Proxy @A) mempty

This prints

{
    "A": {
        "properties": {
            "x": {
                "$ref": "#/components/schemas/T'"
            }
        },
        "required": [
            "x"
        ],
        "type": "object"
    },
    "T'": {
        "enum": [
            "T'"
        ],
        "type": "string"
    }
}

Notice that the map keys include the character '.

The solutions I can see are:

  • Just document this behaviour.
    It is unusual to manually name an API-visible type with a ', so it is not worth fixing -- a user can always change their data declaration.
    However, if a poorly-named type comes from an external library or a user is using DataKinds, they cannot simply rename.
    Thus we should also document a workaround (one can generically derive, and use rename)
  • Document this behaviour and also use a custom type error to statically forbid such instances.
    I don't know how possible this is for the "polymorphic type with a promoted argument" case.
  • Do some encoding of every named declaration.
    It would be nice if names without ' are not mangled, and we should ensure that the encoding is injective (to avoid name clashes). On this second point, see also #56.

Expanding the possible values of a Schema example beyond `Value`

Hi @maksbotan!

At our workplace we use OpenAPI3 and are very grateful for the work that was put in it.
Recently we have taken to move away from using Aeson's Value, as it does not preserve key ordering. While JSON applications should not rely on it, it's actually quite useful for examples as similar fields are declared next to another, and we usually want some "Id" field to be the first one displayed. For example, last_name and first_name should be together.

Now, I'm not suggesting to break the compatibility by changing the type of _schemaExample :: Maybe Value to something incompatible, but rather open more possibilities by having something like an existentially-quantified type:

data Jsonable = forall a. ToJSON a => Jsonable a

_schemaExample :: Maybe JSONable

and use directly encode in the library to render the ByteString.

How does this sound? I can submit a PR if you agree on the design. :)

Add `nullable` attribute

Hi,
in OpenAPI standard a field needs to be marked as nullable: true if it can contain null value. When not using omitNothingFields in Aeson (default setting), openapi3 lib doesn't mark these fields as nullable, but it should.

The function fromAesonOptions ignores omitNothingFields, probably it would be better to not ignore it but use to determine whether to add the nullable attribute or not.

What do you think?

asyncapi & openapi

We recently discovered an initiative similar to openapi for async message (ex: kafka) asyncapi.com.

It seems very close, nearly compatible. Is there any chance you had a look at this (I'm not saying it should be in this lib but sharing code could an option between two module openapi3 & asynapi)?

Use Yaml in examples and tests

Currently this package uses JSON representation of schema for examples in docs and for tests. It would make sense to use Yaml, since this way the examples will be more readable.

Exception when parsing newer OpenApi3 schemas

When parsing OpenApi 3.0.2 schemas like the Pet Store api with:

eitherDecodeFileStrict openApiFile :: IO (Either String OpenApi)

I get an exception:

"Error in $: Additonal field don't match for key openapi: String "3.0.0" /= String "3.0.2""

This is so because in https://github.com/biocad/openapi3/blob/master/src/Data/OpenApi/Internal/AesonUtils.hs#L199-L205 the check is testing for equality on the version defined in https://github.com/biocad/openapi3/blob/master/src/Data/OpenApi/Internal.hs#L1595, so newer versions like latest 3.0.3 will fail when reading.

I thought on submitting a PR where we check for a regular expression instead of hard equality but I don't know about implications. Is this the way to go or would you approach the resolution differently?

validateJSON semantics with `allOf` seem incorrect

I have a Haskell type that is, roughly:

data WithMetadata a m = WithMetadata a m

instance (ToJSON a, ToJSON m) => ToJSON (WithMetadata a m) where
  toJSON (WithMeta a m) = unionObjects (toJSON a) (toJSON m)

unionObjects :: Value -> Value -> Value
unionObjects = undefined

Basically it just says that { foo: bar } `WithMetadata` { baz: bat } encodes like { foo: bar, baz: bat }

Writing the ToSchema for this was surprisingly pleasant,

instance (ToSchema a, ToSchema m) => ToSchema (a `WithMetadata` m) where
  declareNamedSchema _ = do
    aSchema <- declareSchemaRef (Proxy @a)
    mSchema <- declareSchemaRef (Proxy @m)

    pure $
      NamedSchema Nothing $
        mempty
          & type_ ?~ OpenApiObject
          & allOf ?~ [aSchema, mSchema]
Schema and expanded references
    {
        "items": {
            "allOf": [
                {
                    "$ref": "#/components/schemas/StandardSet" // this is the a
                },
                {
                    "properties": { // and this is the m
                        "administrativeAreas": {
                            "items": {
                                "$ref": "#/components/schemas/CountryAdministrativeArea"
                            },
                            "type": "array"
                        }
                    },
                    "required": [
                        "administrativeAreas"
                    ],
                    "type": "object"
                }
            ],
            "type": "object"
        },
        "type": "array"
    }
   {
        "CountryAdministrativeArea": {
            "properties": {
                "administrativeArea": {
                    "type": "string"
                },
                "countryCode": {
                    "$ref": "#/components/schemas/CountryCode"
                }
            },
            "required": [
                "countryCode"
            ],
            "type": "object"
        },
        "CountryCode": {
            "type": "string"
        },
        "StandardSet": {
            "properties": {
                "description": {
                    "type": "string"
                },
                "domainLabel": {
                    "type": "string"
                },
                "id": {
                    "type": "string"
                },
                "isLive": {
                    "type": "boolean"
                },
                "name": {
                    "type": "string"
                },
                "standardLabel": {
                    "type": "string"
                }
            },
            "required": [
                "id",
                "name",
                "description",
                "domainLabel",
                "standardLabel",
                "isLive"
            ],
            "type": "object"
        }
    }

I don't claim to know the semantics of allOf, but the documentation came out exactly as I wanted: it shows me an object with all of the properties of a and m:

[
  {
    "description": "string", // these fields are the ToJSON of a
    "domainLabel": "string",
    "id": "string",
    "isLive": true,
    "name": "string",
    "standardLabel": "string",
    "administrativeAreas": [ // and this field is the ToJSON of m
      {
        "administrativeArea": "string",
        "countryCode": "string"
      }
    ]
  }
]

As well as a combined schema, as if I had written it by hand:

But then I tried to use Data.OpenApi.validateJSON with this schema and a valid example, and I get a failure on every single field being unexpected:

  Errors:
    - property "administrativeAreas" is found in JSON value, but it is not mentioned in Swagger schema
    - property "description" is found in JSON value, but it is not mentioned in Swagger schema
    - property "domainLabel" is found in JSON value, but it is not mentioned in Swagger schema
    - property "id" is found in JSON value, but it is not mentioned in Swagger schema
    - property "isLive" is found in JSON value, but it is not mentioned in Swagger schema
    - property "name" is found in JSON value, but it is not mentioned in Swagger schema
    - property "standardLabel" is found in JSON value, but it is not mentioned in Swagger schema

I think this comes from the implementation for allOf:

    (view allOf -> Just variants) -> do
      -- Default semantics for Validation Monad will abort when at least one
      -- variant does not match.
      forM_ variants $ \var ->
        validateWithSchemaRef var val

What is probably happening is it is validating each of the allOf schemas individually, so any properties appear as extra when validating any one of the other schemas that don't specify them.

I think (again, just based on what the Example and Schema docs show), the intent of allOf (at least with type: object) would be to union them all into one schema, then validate with that.

The comment says "'Default' semantics" -- is there some way I can get the semantics I expected instead?

Mismatch between ToJSON and ToSchema with nullary single-record constructor

ghci> data Foo = Foo deriving stock (Generic)
ghci> genericToJSON defaultOptions Foo
Array []
 ghci> encodePretty $ runDeclare (genericDeclareSchema (fromAesonOptions (defaultOptions)) (Proxy :: Proxy Foo)) mempty
"[\n    {},\n    {\n        \"enum\": [\n            \"Foo\"\n        ],\n        \"type\": \"string\"\n    }\n]"

Now, you can get Aeson to behave in the way openapi3 does by using tagSingleConstructors 👍

ghci> genericToJSON (defaultOptions { tagSingleConstructors = True}) Foo
String "Foo"

But with tagSingleConstructors you get a mismatch when the record is not nullary:

ghci> data Bar = Bar Int deriving stock (Generic)
ghci> genericToJSON (defaultOptions { tagSingleConstructors = True}) (Bar 5)
Object (fromList [("contents",Number 5.0),("tag",String "Bar")])
ghci> encodePretty $ runDeclare (genericDeclareSchema (fromAesonOptions (defaultOptions { tagSingleConstructors = True})) (Proxy :: Proxy Bar)) mempty
"[\n    {},\n    {\n        \"maximum\": 9223372036854775807,\n        \"minimum\": -9223372036854775808,\n        \"type\": \"integer\"\n    }\n]"

Which is already known, but means that even if you can modify your encoding to navigate openapi/aeson support, there isn't a single Options that works in all cases.

Am happy to help - though if you have any insights on where to start, let me know!

(See also #55)

Generates broken schema when I use custom sum type with Maybe in parameter

Minimal example:

{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
module Main where

import Data.Proxy ( Proxy(Proxy) )
import Data.OpenApi ( ToSchema )
import Test.Hspec ( hspec )
import Test.QuickCheck.Arbitrary.Generic
    ( Arbitrary, GenericArbitrary(GenericArbitrary) )
import GHC.Generics (Generic)
import Data.Aeson ( FromJSON, ToJSON )
import Servant.OpenApi.Test ( validateEveryToJSON )
import Servant.API

data M a = J a | N
  deriving stock (Show, Generic)
  deriving anyclass (ToJSON,  FromJSON)
  deriving Arbitrary via GenericArbitrary (M a)

instance ToSchema a => ToSchema (M a)

data Foo = Foo (M (Maybe Int))
  deriving stock (Show, Generic)
  deriving anyclass (ToJSON,  FromJSON, ToSchema)
  deriving Arbitrary via GenericArbitrary Foo

type API = "foo" :> Get '[JSON] Foo

main :: IO ()
main = do
  let spec = validateEveryToJSON (Proxy @API)
  hspec spec

deps:

    , openapi3
    , hspec
    , generic-arbitrary >= 0.2 --used only to generate Arbitrary instances
    , aeson
    , servant
    , servant-openapi3 -- used only for hspec checking

Output:

Foo [✘]

Failures:

  src/Servant/OpenApi/Internal/Test.hs:137:15: 
  1) Foo
       Falsified (after 5 tests):
         Foo (J Nothing)
         Validation against the schema fails:
           * Value not valid under any of 'oneOf' schemas: Object (fromList [("contents",Null),("tag",String "J")])
         
         JSON value:
         {
             "contents": null,
             "tag": "J"
         }
         
         OpenApi Schema:
         {
             "oneOf": [
                 {
                     "properties": {
                         "contents": {
                             "maximum": 9223372036854775807,
                             "minimum": -9223372036854775808,
                             "type": "integer"
                         },
                         "tag": {
                             "enum": [
                                 "J"
                             ],
                             "type": "string"
                         }
                     },
                     "required": [
                         "tag",
                         "contents"
                     ],
                     "type": "object"
                 },
                 {
                     "properties": {
                         "tag": {
                             "enum": [
                                 "N"
                             ],
                             "type": "string"
                         }
                     },
                     "required": [
                         "tag"
                     ],
                     "type": "object"
                 }
             ],
             "type": "object"
         }

Explanation:

It happens because we have

                     "required": [
                         "tag",
                         "contents"
                     ]

in J brach, so when generated J Nothing, it turns into

         {
             "contents": null,
             "tag": "J"
         }

JSON, but contents field is required.

How to fix:

You can write an instance manually, without contents in required

{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}

...

import Control.Lens
import qualified Data.HashMap.Strict.InsOrd as InsMap

...

instance {-# OVERLAPPING #-} ToSchema a => ToSchema (M (Maybe a)) where
  declareNamedSchema _ = do
    nestedType <- declareSchemaRef (Proxy @a)
    let
      updateToTag = Inline $ mempty
        & type_ ?~ OpenApiString
        & enum_ ?~ [ "J" ]
      doNotUpdateTag = Inline $ mempty
        & type_ ?~ OpenApiString
        & enum_ ?~ [ "N" ]
      updateTo = Inline $ mempty
        & type_ ?~ OpenApiObject
        & properties .~ InsMap.fromList
          [ ("tag", updateToTag)
          , ("contents", nestedType)
          ]
        & required .~ ["tag"]
      doNotUpdate = Inline $ mempty
        & type_ ?~ OpenApiObject
        & properties .~ InsMap.fromList
          [ ("tag", doNotUpdateTag)
          ]
        & required .~ ["tag"]
    pure $ NamedSchema (Just "M") $ mempty
      & oneOf ?~ [updateTo, doNotUpdate]

...
deps:

    , lens
    , insert-ordered-containers

Prefix stripping when a `$ref` is parsed as a `Referenced` is confusing

>>> jsonref = object ["$ref" .= String "#/components/schemas/Foo"]
>>> fromJSON @Reference jsonref
Success (Reference {getReference = "#/components/schemas/Foo"})
>>> fromJSON @(Referenced Schema) jsonref
Success (Ref (Reference {getReference = "Foo"}))

This is not only confusing, but also makes it impossible to get the prefix back if I take the Reference out of a Referenced and try to render it back to JSON. Or dually, if I construct a Referenced with a Reference in it that has the prefix, it'll result in a malformed fragment specifier:

>>> jsonref = object ["$ref" .= String "#/components/schemas/Foo"]
>>> Success ref = fromJSON @Reference jsonref
>>> toJSON (Ref @Schema ref)
Object (fromList [("$ref",String "#/components/schemas/#/components/schemas/Foo")])

For the ToJSON instances, the special casing is implemented here:

referencedToJSON :: ToJSON a => Text -> Referenced a -> Value
referencedToJSON prefix (Ref (Reference ref)) = object [ "$ref" .= (prefix <> ref) ]
referencedToJSON _ (Inline x) = toJSON x
instance ToJSON (Referenced Schema) where toJSON = referencedToJSON "#/components/schemas/"
instance ToJSON (Referenced Param) where toJSON = referencedToJSON "#/components/parameters/"
instance ToJSON (Referenced Response) where toJSON = referencedToJSON "#/components/responses/"
instance ToJSON (Referenced RequestBody) where toJSON = referencedToJSON "#/components/requestBodies/"
instance ToJSON (Referenced Example) where toJSON = referencedToJSON "#/components/examples/"
instance ToJSON (Referenced Header) where toJSON = referencedToJSON "#/components/headers/"
instance ToJSON (Referenced Link) where toJSON = referencedToJSON "#/components/links/"
instance ToJSON (Referenced Callback) where toJSON = referencedToJSON "#/components/callbacks/"

And there's an analogous section for FromJSON elsewhere in the same file. IMO these instances should just do the obvious thing and forward to the appropriate instances on Reference; things like prefix stripping can be done elsewhere.

Declare loses input state

I would expect this:

> execDeclare (declare "World") "Hello"
"World"

to produce "HelloWorld". To make this more interesting, the initial state is visible during execution, but is lost afterwards:

> runDeclareT (declare "World" >> look) "Hello"
("World","HelloWorld")

Is this intentional? If not, I think the fix is just to have the bind operators include d (mappend (mappend d d') d'' combining the input and output of the second one), and I can make a PR.

How to read in an OpenApi spec with external references?

How can I parse an OpenApi document with external references?

My basic attempt doesn't work.

> Yaml.decodeFileThrow @IO @OpenApi "./openapi.yaml"
*** Exception: AesonException "Error in $.paths['/my/endpoint'].post.requestBody.content['application/json'].schema.items: expected $ref of the form \"#/components/schemas/*\", but got \"base.yaml#/components/schemas/MyForm\""

code generator incorrectly assumes that optional parameters are nullable

It seems that the code generator creates toJSON instances like this,

    where toJSON obj = Data.Aeson.Types.Internal.object ("_links" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200Links obj : "consents_to_one_to_one_messaging" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200ConsentsToOneToOneMessaging obj : "contact_id" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200ContactId obj : "email_address" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200EmailAddress obj : "email_client" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200EmailClient obj : "email_type" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200EmailType obj : "full_name" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200FullName obj : "id" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200Id obj : "interests" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200Interests obj : "ip_opt" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200IpOpt obj : "ip_signup" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200IpSignup obj : "language" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200Language obj : "last_changed" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200LastChanged obj : "last_note" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200LastNote obj : "list_id" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200ListId obj : "location" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200Location obj : "marketing_permissions" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200MarketingPermissions obj : "member_rating" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200MemberRating obj : "merge_fields" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200MergeFields obj : "source" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200Source obj : "stats" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200Stats obj : "status" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200Status obj : "tags" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200Tags obj : "tags_count" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200TagsCount obj : "timestamp_opt" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200TimestampOpt obj : "timestamp_signup" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200TimestampSignup obj : "unique_email_id" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200UniqueEmailId obj : "unsubscribe_reason" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200UnsubscribeReason obj : "vip" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200Vip obj : "web_id" Data.Aeson.Types.ToJSON..= postListsIdMembersResponseBody200WebId obj : GHC.Base.mempty)

Many of those fields are optional and have types like:

(GHC.Maybe.Maybe ([PostListsIdMembersRequestBodyMarketingPermissions']))

The problem is that if the value is Nothing then the optional field gets rendered as:

, "marketing_permissions":null

However, optional and nullable are not the same thing, and so mailchimp rejects the request with a 400 Bad Request because it fails validation.

See 'Null' here,

https://swagger.io/docs/specification/data-models/data-types/

Also also this comment,

OAI/OpenAPI-Specification#1775 (comment)

My simple proposal is that fields which are optional but not nullable should not be rendered at all if the value is Nothing.

There is a deeper problem here however. The openapi3 spec has two distinct concepts -- optional and nullable. But by using the Maybe datatype we have no way to distinguish between optional and nullable.

This is important because when POSTing data to a remote API, if an optional field is not included, then the remote API may leave the existing value alone. But if the optional field is included and set to null , then the remote server may choose to interpret that is a request to clear any existing value for that field. So we should not squash optional and nullable into a single value.

By default, fields are optional and non-nullable. So most of the time, the Maybe type is sufficient. However if a field is both optional and nullable then there needs to be a way to distinguish between skipping the field (optional) or setting the field to null (nullable).

Hardcoded references

Hello! Currently we have a bunch of hardcoded paths to some objects:

instance FromJSON (Referenced Schema)   where parseJSON = referencedParseJSON "#/components/schemas/"
instance FromJSON (Referenced Param)    where parseJSON = referencedParseJSON "#/components/parameters/"
instance FromJSON (Referenced Response) where parseJSON = referencedParseJSON "#/components/responses/"
instance FromJSON (Referenced RequestBody) where parseJSON = referencedParseJSON "#/components/requestBodies/"
instance FromJSON (Referenced Example)  where parseJSON = referencedParseJSON "#/components/examples/"
instance FromJSON (Referenced Header)   where parseJSON = referencedParseJSON "#/components/headers/"
instance FromJSON (Referenced Link)     where parseJSON = referencedParseJSON "#/components/links/"
instance FromJSON (Referenced Callback) where parseJSON = referencedParseJSON "#/components/callbacks/"

I couldn't find any rule in the specification according to this decision. The only information I found is the notation for $ref objects: https://swagger.io/docs/specification/using-ref/
Currently I work with API that has its own custom paths. Can anyone confirm or refute that paths to these objects may be custom?

Structural error at components.schemas.AggregateMRQuery.properties.select.items.items should be object

I have openapi generate

components:
  schemas:
    AggregateMRQuery:
      example:
        equateBaselines: true
        filter:
          contents:
            - patientHash1
            - patientHash2
          tag: PatientList
        group: null
        resourceId: 123e4567-e89b-12d3-a456-426614174000
        select:
          - - DefaultComp.Fumarate
            - - control
      properties:
        equateBaselines:
          type: boolean
        filter:
          $ref: '#/components/schemas/Filter'
        group:
          $ref: '#/components/schemas/SummaryOpts'
        resourceId:
          $ref: '#/components/schemas/UUID'
        select:
          items:   
            items:
              - $ref: '#/components/schemas/Id' <--- THIS IS WHERE SWAGGER EDITOR CHOKES
              - items:
                  type: string
                type: array
            maxItems: 2
            minItems: 2
            type: array
          type: array
      required:
        - resourceId
        - equateBaselines
      type: object

for the types

type Select = Maybe [(ScalarId, Maybe [T.Text])]

data Query r g = Query
  { resourceId :: r
  , select     :: Select
  , filter     :: Maybe Filter
  , group      :: Maybe g
  , equateBaselines :: Bool
  } deriving (Generic, Serialize)

swagger editor doesn't like to have an array in "items" as according to the spec, items must contain objects only. This is the message I got:
Structural error at components.schemas.AggregateMRQuery.properties.select.items.items should be object

I am ready to prepare a PR to fix that but would like some guidance. Seems like tuples in general are not a good fit for openapi specs so what should the API do ? should it error out when dealing with tuples ? or throw a warning ? I wish the API would tell me when it generates possibly invalid spec instead of discovering it via a spec validator.

Schema diffing

I think it's a pretty common use case to need a diff of two schemas: additions, removals, breaking changes etc. There are several non-haskell tools that already try to achieve that. All of them had problems with installation, parsing or validation, especially when << syntax is involved.

So I'm wondering if this would be in scope for openapi3 or rather a thing to do in a library. Has anyone already worked on that? Or are there simpler solutions?

Support for Specification Extensions in OpenApi Objects

Following Objects supports Specification Extensions which are used by some tools.

  • OpenAPI
  • Info
  • Contact
  • License
  • Server
  • ServerVariable
  • Paths
  • PathItem
  • OperationObject
  • ExternalDocumentation
  • StyleExamples
  • RequestBody
  • MediaType
  • Encoding
  • Responses
  • Response
  • Callback
  • Example
  • Link
  • Tag
  • Schema
  • XML
  • Security Scheme
  • OAUTH Flows
  • OAUTH Flow
  • SecurityRequirement

I will be able to add this support and send in a pull request if you are interested

_OpenApiItemsArray and _OpenApiItemsObject should be Prisms, not Reviews

The OpenApiItems prisms section defines Reviews, not Prisms. I assume that's a mistake? A Prism is a Review but not the other way around, so this is needlessly limiting.

In the history of the file, I see that Prisms used to be generated using makePrisms, but in cd3dc81 the makePrisms was replaced with a manual prism definition... with a Review type signature. The commit message says "fix build by manually writing out SwaggerItems prisms", so it does not seem like the restriction to Review was intentional.

Later on, in 68e95a6, the prism implementation was changed to an unto, which does produce a Review, but the second direction of the prism implementation was kept in a comment. The commit message says "Make compile cleanly with stack --pedantic", so it again does not seem like the restriction to Review was intentional.

What's the point of `SecurityDefinitions`?

This type is defined in Data.OpenApi.Internal and is not part of any other types. There are some instance defined for it and it's re-exported from Data.OpenApi. Also it's used in tests.

Is this type useful on its own (since it's not part of any other type)? How is it supposed to be used?

I see that in swagger2 there is Swagger data type with _swaggerSecurityDefinitions :: SecurityDefinitions, but apparently it was thrown away in openapi3. Is it intentional (maybe there actually was a change in the specification, i. e. maybe that's the difference between version 2 and version 3)?

Generically derived schema reference names can clash

With schemas for polymorphic types, we can have names of schemas clashing, leading to incorrect generation (i.e. inconsistent with aeson's generic ToJSON). This can happen if one has a type data T_A and also data T a & data A: the generated schema names for T_A and T A are identical!

As a complete example, consider the program

{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeApplications #-}

module Main where

import qualified Data.ByteString.Lazy.Char8 as B
import Data.OpenApi
import Data.OpenApi.Declare
import Data.OpenApi.Internal.Utils
import Data.Proxy
import Data.Typeable
import GHC.Generics

data A = A {x :: T_B, y :: T B}
 deriving Generic

data B = B

data T a = T {foo :: ()}
  deriving Generic

data T_B = T_B {bar :: Bool, quux :: Int}
  deriving Generic

instance ToSchema A
instance Typeable a => ToSchema (T a)
instance ToSchema T_B

main :: IO ()
main = B.putStrLn $ encodePretty $  execDeclare (declareSchemaRef $ Proxy @A) mempty

which has the output

{
    "A": {
        "properties": {
            "x": {
                "$ref": "#/components/schemas/T_B"
            },
            "y": {
                "$ref": "#/components/schemas/T_B"
            }
        },
        "required": [
            "x",
            "y"
        ],
        "type": "object"
    },
    "T_B": {
        "properties": {
            "bar": {
                "type": "boolean"
            },
            "quux": {
                "maximum": 9223372036854775807,
                "minimum": -9223372036854775808,
                "type": "integer"
            }
        },
        "required": [
            "bar",
            "quux"
        ],
        "type": "object"
    }
}

Notice that the two T_B schemas have overwritten each other -- a serialised value of type A will not match this schema.

Since types cannot contain the character -, one possible solution would be to change the serialisation introduced in #19 to use unspace ' ' = '-', rather than unspace ' ' = '_'.

_operationSecurity should be Maybe

According to the documentation (and the intended usage, as far as I understand), the type of _operationSecurity on the Operation data-type should be Maybe [SecurityRequirement], rather than [SecurityRequirement]. Setting this attribute to Just [] should remove all globally declared security requirements from a particular operation, which currently does not seem possible.

How to implement allOperations for optics?

I am trying to reimplement this HasOpenApi instance with Optics instead Lens. Most of the transition is pretty smooth, the usual "replacing (.) with (%)", and using the correct overloaded labels.

So far this looks like:

-- OpenApi instance
instance (HasOpenApi api, KnownPaginationPageSize settings) =>
         HasOpenApi (PaginationParameters settings :> api) where
    toOpenApi _ = toOpenApi (Proxy @api)
        & #allOperations % #parameters <>~ [O.Inline offsetParam, O.Inline limitParam]
      where
        offsetParam :: O.Param
        limitParam :: O.Param
        offsetParam = mempty
            & #name .~ "offset"
            & #description ?~
                "Pagination parameter. How many items to skip from the beginning."
            & #required ?~ False
            & #in .~ O.ParamQuery
            & #schema ?~ O.Inline offsetParamSchema
        offsetParamSchema = mempty
            & #type ?~ O.OpenApiInteger
            & #format ?~ "int32"

        limitParam = mempty
            & #name .~ "limit"
            & #description ?~ mconcat
                [ "Pagination parameter. Maximum number of items to return.\n"
                , defaultPageSizeDesc
                ]
            & #required ?~ False
            & #in .~ O.ParamQuery
            & #schema ?~ O.Inline limitParamSchema
        limitParamSchema = mempty
            & #type ?~ O.OpenApiInteger
            & #format ?~ "int32"
            & #pattern ?~ "^\\d*[1-9]\\d*$"
        defaultPageSizeDesc :: Text
        defaultPageSizeDesc = case settingDefPageSize @settings of
          Nothing -> "By default, no limit will be applied."
          Just s  -> "Defaults to " <> Text.pack (show s) <> "."

(<>~) :: (Is k A_Setter, Semigroup b) => Optic k is s t b b -> b -> s -> t
l <>~ n = over l (<> n)
infixr 4 <>~

My last problem is the #allOperations label. It is:

allOperations :: Traversal' OpenApi Operation
allOperations = paths.traverse.template

And this Traversal is obviously a lens thing and this is where my knowledge of lens & optics falls short. How could I re-implement it with optics?

Allow GHC-9.6

Bounds exclude GHC-9.6.1, which has base-4.18. I believe a Hackage revision would be sufficient to allow this.

SecurityDefinitions missing "Index" and "IxValue" type family instances

Hi,

The SecurityDefinitions type defined in the OpenAPI library here

Which is a newtype wrapper over Definitions, which in-turn is a type synonym for an InsOrdHashMap Text type.

SecurityDefinitions seems to be missing type-family instances for Index and IxValue type-families, which enables us to use them with Lenses and refer to their indices using at or ix and set a particular SecurityScheme at that index if needed.

The following instances are already present in the Swagger version of the same data-type here.

Maybe we missed them here. I'll make a PR soon for this.

(Note: They would also need type-class instances for At and Ixed, i'll open a separate issue for that.)

_operationServers should be Maybe

servers field description from the specification:

An alternative server array to service this operation. If an alternative server object is specified at the Path Item Object or Root level, it will be overridden by this value.

This seems to indicate that the field should accept null values and be optional. This does not seem to be the case at the moment.

I don't see how it would be possible to not override server objects.

DateTime string formats / ISO 8601

I'm using Servant & OpenAPI to generate a schema for code generation via openapi-generator, targeting Dart as a client language.

The current implmentations of declareNamedSchema for UTCTime, and toParamSchema for UCTime and ZonedTime generate a schema of type: string with a custom format as a specific representation of each type. This breaks codegen in the Dart client, as it defines the required type as a String where a DateTime would be more appropriate. This seems to be down to the format being a custom representation, rather than one of openapi3's built-in format values.

Given the custom formats as currently returned (yyyy-mm-ddThh:MM:ssZ and yyyy-mm-ddThh:MM:ss+hhMM) are (as far as I can see) ISO8601 - and therefore openapi3 date-time compliant, I would like to open a PR that changes the implementation declareNamedSchema for UTCTime, and toParamSchema for UTCTime and ZonedTime to return format: "date-time".

Is this a reasonable thing to do?

As ever with matters involving dates and times the devil is hiding in every detail and I expect there's a subtle detail I've missed here. Hopefully not however, as these changes help avoid wrapping a whole load of types to generate the right schema!

[BUG] OpenAPI UI doesn't apply Authorization header present in the spec

Hi,

This is a cross-post of #29 as I'm not sure which package causes the issue.

below is a sample UI interface that seems to ignore the defined "Authroization" request header and requests fail with expected 401 errors (also see the incomplete curl snippet)
Screen Shot 2021-09-28 at 17 00 59

A frozen packages snapshot contains:

openapi3 ==3.1.0
servant-openapi3 ==2.0.1.2
servant-server ==0.18.2
servant-swagger-ui ==0.3.5.3.47.1
servant-swagger-ui-core ==0.3.5

add `ToSchema Schema` instance

I am trying to return a Json schema in my servant endpoint.
I tried to derive generically ToSchema Schema but it failed because of orderedmaps
I tried a manual instance but it doesn't pass the openapi validators ofc.

instance ToSchema Schema where
  declareNamedSchema _ =
      pure $ NamedSchema Nothing $ mempty
        & properties .~ [
          ("required", Inline $ toSchema (Proxy @Int))
          , ("properties", Inline $ toSchema (Proxy @Int))
          , ("example", Inline $ mempty & type_ ?~ OpenApiObject)
          ]

I wish the instance would live in openapi3.

Outdated documentation re sum encoding differs ToSchema/ToJSON?

There is (in the haddock documentation) a statement that the default ToSchema and ToJSON instances differ in encoding sum types:

-- @'ToSchema'@ default implementation is also aligned with @'ToJSON'@ default implementation with
-- the only difference being for sum encoding. @'ToJSON'@ defaults sum encoding to @'defaultTaggedObject'@,
-- while @'ToSchema'@ defaults to something which corresponds to @'ObjectWithSingleField'@. This is due to
-- @'defaultTaggedObject'@ behavior being hard to specify in Swagger.

However, I think this is outdated and that you create a consistent schema using oneOf, as mentioned further down the documentation

-- This package implements OpenAPI 3.0 spec, which supports @oneOf@ in schemas, allowing any sum types
-- to be faithfully represented. All sum encodings supported by @aeson@ are supported here as well, with
-- an exception of 'Data.Aeson.TwoElemArray', since OpenAPI spec does not support heterogeneous arrays.

Do (default) schemas for sum types agree with aeson, or am I missing something here (I cannot come up with a case where they disagree)?

Invalid schemas generated for tuples and (some) `Map`s

Description

It seems we generate invalid schemas for all tuples and Maps with "complex" keys (those that aeson's toJSONKey is ToJSONKeyValue and thus the map is encoded as an array of key-value pairs, rather than as a json object).
This is because Map k v is encoded the same as [(k,v)] for these keys, and (k,v) generates a schema similar to

{
  "minItems": 2,
  "items": [
      {
          "type": "string"
      },
      {
          "type": "boolean"
      }
  ],
  "maxItems": 2,
  "type": "array"
}

According to the OpenAPI3 spec, the items field must not be an array.

items - Value MUST be an object and not an array

More details

Note that even homogenous tuples (e.g. (String,String)) have the same problem, since there is no special handling.
In fact, due to this restriction I don't see how to give a schema for any non-record product type, unless all its fields have the same type.

A full example, generating an invalid spec is

{-# LANGUAGE OverloadedLists #-}
{-# LANGUAGE OverloadedStrings #-}

import Control.Lens
import Data.Aeson.Encode.Pretty (encodePretty)
import Data.ByteString.Lazy.Char8 as BSL
import Data.Map (Map)
import Data.Proxy
import Data.OpenApi

main :: IO ()
main = BSL.putStrLn $ encodePretty $ (mempty :: OpenApi) &
  components . schemas .~ [ ("Buggy", toSchema (Proxy :: Proxy (Map [Int] Bool)))]

(See also this gist for the generated schema, and a few other examples)
The output of this is rejected as invalid by https://validator.swagger.io/validator
and https://editor.swagger.io/ and https://openapi-generator.tech/ (both of which give more useful error messages)

The code that constructs these specs

I expect this code was ported from / inspired by swagger2. The swagger (i.e. openapi2) spec is difficult to read, but I think it does support items being an array. However, openapi3 explicitly does not.

(re swagger/openapi2:

)

The future

I wonder if it is worth adding a custom type error to explain why hetrogenous tuples / "complex" maps cannot be given a spec?
Longer term, it seems that openapi-3.1.0 is out which (if I read (the linked JSON Schema docs) correctly) brings back the ability for items to be an array, under the name prefixItems.
However, this does not seem well supported yet, for instance none of the validators above support it.

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.