Skip to content

Commit 8c9517e

Browse files
fisxmaksbotan
authored andcommitted
Swagger instances for UVerb.
1 parent e1e3e76 commit 8c9517e

File tree

2 files changed

+164
-0
lines changed

2 files changed

+164
-0
lines changed

src/Servant/OpenApi/Internal.hs

Lines changed: 55 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -11,11 +11,15 @@
1111
#if __GLASGOW_HASKELL__ >= 806
1212
{-# LANGUAGE UndecidableInstances #-}
1313
#endif
14+
{-# OPTIONS_GHC -Wno-orphans #-}
1415
module Servant.OpenApi.Internal where
1516

1617
import Prelude ()
1718
import Prelude.Compat
1819

20+
#if MIN_VERSION_servant(0,18,1)
21+
import Control.Applicative ((<|>))
22+
#endif
1923
import Control.Lens
2024
import Data.Aeson
2125
import Data.Foldable (toList)
@@ -183,6 +187,57 @@ instance OpenApiMethod 'OPTIONS where openApiMethod _ = options
183187
instance OpenApiMethod 'HEAD where openApiMethod _ = head_
184188
instance OpenApiMethod 'PATCH where openApiMethod _ = patch
185189

190+
#if MIN_VERSION_servant(0,18,1)
191+
instance HasOpenApi (UVerb method cs '[]) where
192+
toOpenApi _ = mempty
193+
194+
-- | @since <2.0.1.0>
195+
instance
196+
{-# OVERLAPPABLE #-}
197+
( ToSchema a,
198+
HasStatus a,
199+
AllAccept cs,
200+
OpenApiMethod method,
201+
HasOpenApi (UVerb method cs as)
202+
) =>
203+
HasOpenApi (UVerb method cs (a ': as))
204+
where
205+
toOpenApi _ =
206+
toOpenApi (Proxy :: Proxy (Verb method (StatusOf a) cs a))
207+
`combineSwagger` toOpenApi (Proxy :: Proxy (UVerb method cs as))
208+
where
209+
-- workaround for https://github.com/GetShopTV/swagger2/issues/218
210+
combinePathItem :: PathItem -> PathItem -> PathItem
211+
combinePathItem s t = PathItem
212+
{ _pathItemGet = _pathItemGet s <> _pathItemGet t
213+
, _pathItemPut = _pathItemPut s <> _pathItemPut t
214+
, _pathItemPost = _pathItemPost s <> _pathItemPost t
215+
, _pathItemDelete = _pathItemDelete s <> _pathItemDelete t
216+
, _pathItemOptions = _pathItemOptions s <> _pathItemOptions t
217+
, _pathItemHead = _pathItemHead s <> _pathItemHead t
218+
, _pathItemPatch = _pathItemPatch s <> _pathItemPatch t
219+
, _pathItemTrace = _pathItemTrace s <> _pathItemTrace t
220+
, _pathItemParameters = _pathItemParameters s <> _pathItemParameters t
221+
, _pathItemSummary = _pathItemSummary s <|> _pathItemSummary t
222+
, _pathItemDescription = _pathItemDescription s <|> _pathItemDescription t
223+
, _pathItemServers = _pathItemServers s <> _pathItemServers t
224+
}
225+
226+
combineSwagger :: OpenApi -> OpenApi -> OpenApi
227+
combineSwagger s t = OpenApi
228+
{ _openApiInfo = _openApiInfo s <> _openApiInfo t
229+
, _openApiServers = _openApiServers s <> _openApiServers t
230+
, _openApiPaths = InsOrdHashMap.unionWith combinePathItem (_openApiPaths s) (_openApiPaths t)
231+
, _openApiComponents = _openApiComponents s <> _openApiComponents t
232+
, _openApiSecurity = _openApiSecurity s <> _openApiSecurity t
233+
, _openApiTags = _openApiTags s <> _openApiTags t
234+
, _openApiExternalDocs = _openApiExternalDocs s <|> _openApiExternalDocs t
235+
}
236+
237+
instance ToSchema a => ToSchema (WithStatus s a) where
238+
declareNamedSchema _ = declareNamedSchema (Proxy :: Proxy a)
239+
#endif
240+
186241
instance {-# OVERLAPPABLE #-} (ToSchema a, AllAccept cs, KnownNat status, OpenApiMethod method) => HasOpenApi (Verb method status cs a) where
187242
toOpenApi _ = toOpenApi (Proxy :: Proxy (Verb method status cs (Headers '[] a)))
188243

test/Servant/OpenApiSpec.hs

Lines changed: 109 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,10 +1,14 @@
1+
{-# LANGUAGE CPP #-}
12
{-# LANGUAGE DataKinds #-}
23
{-# LANGUAGE DeriveDataTypeable #-}
34
{-# LANGUAGE DeriveGeneric #-}
45
{-# LANGUAGE OverloadedStrings #-}
56
{-# LANGUAGE QuasiQuotes #-}
67
{-# LANGUAGE TypeOperators #-}
78
{-# LANGUAGE PackageImports #-}
9+
#if MIN_VERSION_servant(0,18,1)
10+
{-# LANGUAGE TypeFamilies #-}
11+
#endif
812
module Servant.OpenApiSpec where
913

1014
import Control.Lens
@@ -37,6 +41,9 @@ spec = describe "HasOpenApi" $ do
3741
it "Comprehensive API" $ do
3842
let _x = toOpenApi comprehensiveAPI
3943
True `shouldBe` True -- type-level test
44+
#if MIN_VERSION_servant(0,18,1)
45+
it "UVerb API" $ checkOpenApi uverbOpenApi uverbAPI
46+
#endif
4047

4148
main :: IO ()
4249
main = hspec spec
@@ -418,3 +425,105 @@ getPostAPI = [aesonQQ|
418425
}
419426
|]
420427

428+
-- =======================================================================
429+
-- UVerb API
430+
-- =======================================================================
431+
432+
#if MIN_VERSION_servant(0,18,1)
433+
434+
data FisxUser = FisxUser {name :: String}
435+
deriving (Eq, Show, Generic)
436+
437+
instance ToSchema FisxUser
438+
439+
instance HasStatus FisxUser where
440+
type StatusOf FisxUser = 203
441+
442+
data ArianUser = ArianUser
443+
deriving (Eq, Show, Generic)
444+
445+
instance ToSchema ArianUser
446+
447+
type UVerbAPI = "fisx" :> UVerb 'GET '[JSON] '[FisxUser, WithStatus 303 String]
448+
:<|> "arian" :> UVerb 'POST '[JSON] '[WithStatus 201 ArianUser]
449+
450+
uverbOpenApi :: OpenApi
451+
uverbOpenApi = toOpenApi (Proxy :: Proxy UVerbAPI)
452+
453+
uverbAPI :: Value
454+
uverbAPI = [aesonQQ|
455+
{
456+
"openapi": "3.0.0",
457+
"info": {
458+
"version": "",
459+
"title": ""
460+
},
461+
"components": {
462+
"schemas": {
463+
"ArianUser": {
464+
"type": "string",
465+
"enum": [
466+
"ArianUser"
467+
]
468+
},
469+
"FisxUser": {
470+
"required": [
471+
"name"
472+
],
473+
"type": "object",
474+
"properties": {
475+
"name": {
476+
"type": "string"
477+
}
478+
}
479+
}
480+
}
481+
},
482+
"paths": {
483+
"/arian": {
484+
"post": {
485+
"responses": {
486+
"201": {
487+
"content": {
488+
"application/json;charset=utf-8": {
489+
"schema": {
490+
"$ref": "#/components/schemas/ArianUser"
491+
}
492+
}
493+
},
494+
"description": ""
495+
}
496+
}
497+
}
498+
},
499+
"/fisx": {
500+
"get": {
501+
"responses": {
502+
"303": {
503+
"content": {
504+
"application/json;charset=utf-8": {
505+
"schema": {
506+
"type": "string"
507+
}
508+
}
509+
},
510+
"description": ""
511+
},
512+
"203": {
513+
"content": {
514+
"application/json;charset=utf-8": {
515+
"schema": {
516+
"$ref": "#/components/schemas/FisxUser"
517+
}
518+
}
519+
},
520+
"description": ""
521+
}
522+
}
523+
}
524+
}
525+
}
526+
}
527+
|]
528+
529+
#endif

0 commit comments

Comments
 (0)