Skip to content

Commit

Permalink
Allow type: object to be present on unions
Browse files Browse the repository at this point in the history
  • Loading branch information
OwenGraves committed Aug 6, 2024
1 parent 88ceb73 commit 18a5356
Show file tree
Hide file tree
Showing 5 changed files with 75 additions and 25 deletions.
Original file line number Diff line number Diff line change
@@ -0,0 +1,34 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ExplicitNamespaces #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TypeApplications #-}

module TestCases.Types.OneOfWithDiscriminatorTypeObject
( OneOfWithDiscriminatorTypeObject(..)
, oneOfWithDiscriminatorTypeObjectSchema
) where

import Fleece.Core ((#@))
import qualified Fleece.Core as FC
import Prelude (($), Eq, Show)
import Shrubbery (type (@=))
import qualified Shrubbery as Shrubbery
import qualified TestCases.Types.Bar as Bar
import qualified TestCases.Types.Baz as Baz
import qualified TestCases.Types.Foo as Foo

newtype OneOfWithDiscriminatorTypeObject = OneOfWithDiscriminatorTypeObject (Shrubbery.TaggedUnion
'[ "bar" @= Bar.Bar
, "baz" @= Baz.Baz
, "foo" @= Foo.Foo
])
deriving (Show, Eq)

oneOfWithDiscriminatorTypeObjectSchema :: FC.Fleece schema => schema OneOfWithDiscriminatorTypeObject
oneOfWithDiscriminatorTypeObjectSchema =
FC.coerceSchema $
FC.taggedUnionNamed (FC.qualifiedName "TestCases.Types.OneOfWithDiscriminatorTypeObject" "OneOfWithDiscriminatorTypeObject") "type" $
FC.taggedUnionMember @"bar" Bar.barSchema
#@ FC.taggedUnionMember @"baz" Baz.bazSchema
#@ FC.taggedUnionMember @"foo" Foo.fooSchema
1 change: 1 addition & 0 deletions json-fleece-openapi3/examples/test-cases/test-cases.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -172,6 +172,7 @@ library
TestCases.Types.NullableBoolean
TestCases.Types.Num2SchemaStartingWithNumber
TestCases.Types.OneOfWithDiscriminator
TestCases.Types.OneOfWithDiscriminatorTypeObject
TestCases.Types.OneOfWithNullable
TestCases.Types.ReferenceOneOf
TestCases.Types.ReferenceOneOfInsideOneOf
Expand Down
14 changes: 14 additions & 0 deletions json-fleece-openapi3/examples/test-cases/test-cases.yaml
Original file line number Diff line number Diff line change
Expand Up @@ -607,6 +607,20 @@ components:
bar: "#/components/schemas/Bar"
baz: "#/components/schemas/Baz"

OneOfWithDiscriminatorTypeObject:
type: object
oneOf:
- $ref: "#/components/schemas/Foo"
- $ref: "#/components/schemas/Bar"
- $ref: "#/components/schemas/Baz"

discriminator:
propertyName: "type"
mapping:
foo: "#/components/schemas/Foo"
bar: "#/components/schemas/Bar"
baz: "#/components/schemas/Baz"

Foo:
type: object
properties:
Expand Down
1 change: 1 addition & 0 deletions json-fleece-openapi3/json-fleece-openapi3.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -2019,6 +2019,7 @@ extra-source-files:
examples/test-cases/TestCases/Types/NullableBoolean.hs
examples/test-cases/TestCases/Types/Num2SchemaStartingWithNumber.hs
examples/test-cases/TestCases/Types/OneOfWithDiscriminator.hs
examples/test-cases/TestCases/Types/OneOfWithDiscriminatorTypeObject.hs
examples/test-cases/TestCases/Types/OneOfWithNullable.hs
examples/test-cases/TestCases/Types/ReferenceOneOf.hs
examples/test-cases/TestCases/Types/ReferenceOneOfInsideOneOf.hs
Expand Down
50 changes: 25 additions & 25 deletions json-fleece-openapi3/src/Fleece/OpenApi3.hs
Original file line number Diff line number Diff line change
Expand Up @@ -903,32 +903,32 @@ mkOpenApiDataFormat schemaKey typeName schema =
dataFormat <- mkFormat
pure $ Just (Map.empty, dataFormat)
in
case OA._schemaType schema of
Just OA.OpenApiString -> noRefs $ mkOpenApiStringFormat typeName schema
Just OA.OpenApiNumber -> noRefs $ mkOpenApiNumberFormat typeName schema
Just OA.OpenApiInteger -> noRefs $ mkOpenApiIntegerFormat typeName schema
Just OA.OpenApiBoolean -> do
typeOptions <- CGU.lookupTypeOptions typeName
noRefs $ pure (CGU.boolFormat typeOptions)
Just OA.OpenApiArray ->
Just <$> mkOpenApiArrayFormat schemaKey typeName schema
Just OA.OpenApiObject ->
mkOpenApiObjectFormatOrAdditionalPropertiesNewtype
CGU.Type
schemaKey
typeName
schema
Just OA.OpenApiNull -> do
typeOptions <- CGU.lookupTypeOptions typeName
noRefs $ pure (CGU.nullFormat typeOptions)
case OA._schemaOneOf schema of
Just schemas ->
case OA._schemaDiscriminator schema of
Nothing ->
Just <$> mkOneOfUnion schemaKey schemas
Just discriminator ->
Just <$> mkOneOfTaggedUnion discriminator schemaKey
Nothing ->
case OA._schemaOneOf schema of
Just schemas ->
case OA._schemaDiscriminator schema of
Nothing ->
Just <$> mkOneOfUnion schemaKey schemas
Just discriminator ->
Just <$> mkOneOfTaggedUnion discriminator schemaKey
case OA._schemaType schema of
Just OA.OpenApiString -> noRefs $ mkOpenApiStringFormat typeName schema
Just OA.OpenApiNumber -> noRefs $ mkOpenApiNumberFormat typeName schema
Just OA.OpenApiInteger -> noRefs $ mkOpenApiIntegerFormat typeName schema
Just OA.OpenApiBoolean -> do
typeOptions <- CGU.lookupTypeOptions typeName
noRefs $ pure (CGU.boolFormat typeOptions)
Just OA.OpenApiArray ->
Just <$> mkOpenApiArrayFormat schemaKey typeName schema
Just OA.OpenApiObject ->
mkOpenApiObjectFormatOrAdditionalPropertiesNewtype
CGU.Type
schemaKey
typeName
schema
Just OA.OpenApiNull -> do
typeOptions <- CGU.lookupTypeOptions typeName
noRefs $ pure (CGU.nullFormat typeOptions)
Nothing ->
mkOpenApiObjectFormatOrAdditionalPropertiesNewtype
CGU.Type
Expand Down

0 comments on commit 18a5356

Please sign in to comment.