Skip to content

Commit 8e962b9

Browse files
committed
Merge remote-tracking branch 'origin/fisx/uverb' into maksbotan/uverb
2 parents 022875e + b9d6ee3 commit 8e962b9

File tree

5 files changed

+172
-2
lines changed

5 files changed

+172
-2
lines changed

cabal.project

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -7,3 +7,15 @@ source-repository-package
77
type: git
88
location: https://github.com/biocad/openapi3/
99
tag: bd9df532f2381c4b22fe86ef722715088f5cfa68
10+
11+
source-repository-package
12+
type: git
13+
location: https://github.com/maksbotan/servant
14+
tag: ffab120d4234fba967b85c87352096e5264a752d
15+
subdir: servant
16+
17+
source-repository-package
18+
type: git
19+
location: https://github.com/maksbotan/servant
20+
tag: ffab120d4234fba967b85c87352096e5264a752d
21+
subdir: servant-server

servant-openapi3.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -80,7 +80,7 @@ library
8080
, http-media >=0.7.1.3 && <0.9
8181
, insert-ordered-containers >=0.2.1.0 && <0.3
8282
, lens >=4.17 && <4.20
83-
, servant >=0.17 && <0.19
83+
, servant >=0.17 && <0.20
8484
, singleton-bool >=0.1.4 && <0.2
8585
, openapi3 >=3.0.0 && <4.0
8686
, text >=1.2.3.0 && <1.3

src/Servant/OpenApi/Internal.hs

Lines changed: 56 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,12 +1,14 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE ConstraintKinds #-}
33
{-# LANGUAGE DataKinds #-}
4+
{-# LANGUAGE GeneralizedNewtypeDeriving #-} -- TODO: can we get rid of this?
45
{-# LANGUAGE FlexibleContexts #-}
56
{-# LANGUAGE FlexibleInstances #-}
67
{-# LANGUAGE OverloadedStrings #-}
78
{-# LANGUAGE PolyKinds #-}
89
{-# LANGUAGE RankNTypes #-}
910
{-# LANGUAGE ScopedTypeVariables #-}
11+
{-# LANGUAGE StandaloneDeriving #-} -- TODO: can we get away with terminating support for ghcs that don't have this?
1012
{-# LANGUAGE TypeOperators #-}
1113
#if __GLASGOW_HASKELL__ >= 806
1214
{-# LANGUAGE UndecidableInstances #-}
@@ -16,6 +18,10 @@ module Servant.OpenApi.Internal where
1618
import Prelude ()
1719
import Prelude.Compat
1820

21+
-- TODO: turn on lower version bound once servant is released.
22+
-- #if MIN_VERSION_servant(0,19,0)
23+
import Control.Applicative ((<|>))
24+
-- #endif
1925
import Control.Lens
2026
import Data.Aeson
2127
import Data.Foldable (toList)
@@ -183,6 +189,56 @@ instance OpenApiMethod 'OPTIONS where openApiMethod _ = options
183189
instance OpenApiMethod 'HEAD where openApiMethod _ = head_
184190
instance OpenApiMethod 'PATCH where openApiMethod _ = patch
185191

192+
-- TODO: turn on lower version bound once servant is released.
193+
-- #if MIN_VERSION_servant(0,19,0)
194+
instance HasOpenApi (UVerb method cs '[]) where
195+
toOpenApi _ = mempty
196+
197+
-- | @since <TODO>
198+
instance
199+
{-# OVERLAPPABLE #-}
200+
( ToSchema a,
201+
HasStatus a,
202+
AllAccept cs,
203+
OpenApiMethod method,
204+
HasOpenApi (UVerb method cs as)
205+
) =>
206+
HasOpenApi (UVerb method cs (a ': as))
207+
where
208+
toOpenApi _ =
209+
toOpenApi (Proxy :: Proxy (Verb method (StatusOf a) cs a))
210+
`combineOpenApi` toOpenApi (Proxy :: Proxy (UVerb method cs as))
211+
where
212+
-- workaround for https://github.com/GetShopTV/swagger2/issues/218
213+
-- We'd like to juse use (<>) but the instances are wrong
214+
combinePathItem :: PathItem -> PathItem -> PathItem
215+
combinePathItem s t = s
216+
{ _pathItemGet = _pathItemGet s <> _pathItemGet t
217+
, _pathItemPut = _pathItemPut s <> _pathItemPut t
218+
, _pathItemPost = _pathItemPost s <> _pathItemPost t
219+
, _pathItemDelete = _pathItemDelete s <> _pathItemDelete t
220+
, _pathItemOptions = _pathItemOptions s <> _pathItemOptions t
221+
, _pathItemHead = _pathItemHead s <> _pathItemHead t
222+
, _pathItemPatch = _pathItemPatch s <> _pathItemPatch t
223+
, _pathItemTrace = _pathItemTrace s <> _pathItemTrace t
224+
, _pathItemServers = _pathItemServers s <> _pathItemServers t
225+
, _pathItemParameters = _pathItemParameters s <> _pathItemParameters t
226+
}
227+
228+
combineOpenApi :: OpenApi -> OpenApi -> OpenApi
229+
combineOpenApi s t = OpenApi
230+
{ _openApiInfo = _openApiInfo s <> _openApiInfo t
231+
, _openApiServers = _openApiServers s <> _openApiServers t
232+
, _openApiPaths = InsOrdHashMap.unionWith combinePathItem (_openApiPaths s) (_openApiPaths t)
233+
, _openApiComponents = _openApiComponents s <> _openApiComponents t
234+
, _openApiSecurity = _openApiSecurity s <> _openApiSecurity t
235+
, _openApiTags = _openApiTags s <> _openApiTags t
236+
, _openApiExternalDocs = _openApiExternalDocs s <|> _openApiExternalDocs t
237+
}
238+
239+
deriving instance ToSchema a => ToSchema (WithStatus s a)
240+
-- #endif
241+
186242
instance {-# OVERLAPPABLE #-} (ToSchema a, AllAccept cs, KnownNat status, OpenApiMethod method) => HasOpenApi (Verb method status cs a) where
187243
toOpenApi _ = toOpenApi (Proxy :: Proxy (Verb method status cs (Headers '[] a)))
188244

stack.yaml

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,3 +2,5 @@ resolver: lts-16.8
22
packages:
33
- '.'
44
- example/
5+
- ../servant/servant
6+
- ../servant/servant-server

test/Servant/OpenApiSpec.hs

Lines changed: 101 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -2,9 +2,10 @@
22
{-# LANGUAGE DeriveDataTypeable #-}
33
{-# LANGUAGE DeriveGeneric #-}
44
{-# LANGUAGE OverloadedStrings #-}
5+
{-# LANGUAGE PackageImports #-}
56
{-# LANGUAGE QuasiQuotes #-}
7+
{-# LANGUAGE TypeFamilies #-}
68
{-# LANGUAGE TypeOperators #-}
7-
{-# LANGUAGE PackageImports #-}
89
module Servant.OpenApiSpec where
910

1011
import Control.Lens
@@ -34,6 +35,7 @@ spec = describe "HasOpenApi" $ do
3435
it "Todo API" $ checkAPI (Proxy :: Proxy TodoAPI) todoAPI
3536
it "Hackage API (with tags)" $ checkOpenApi hackageOpenApiWithTags hackageAPI
3637
it "GetPost API (test subOperations)" $ checkOpenApi getPostOpenApi getPostAPI
38+
it "UVerb API" $ checkOpenApi uverbSwagger uverbAPI
3739
it "Comprehensive API" $ do
3840
let _x = toOpenApi comprehensiveAPI
3941
True `shouldBe` True -- type-level test
@@ -418,3 +420,101 @@ getPostAPI = [aesonQQ|
418420
}
419421
|]
420422

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

0 commit comments

Comments
 (0)