Skip to content

Commit a4e552e

Browse files
committed
[WIP] Swagger instance for UVerb.
1 parent 0b828aa commit a4e552e

File tree

4 files changed

+75
-4
lines changed

4 files changed

+75
-4
lines changed

cabal.project

Lines changed: 5 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,2 +1,6 @@
1-
packages: .
1+
packages:
2+
./
3+
../servant/servant/
4+
../servant/servant-server/
5+
26
allow-newer: aeson-pretty-0.8.7:base-compat

servant-swagger.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -82,7 +82,7 @@ library
8282
, http-media >=0.7.1.3 && <0.9
8383
, insert-ordered-containers >=0.2.1.0 && <0.3
8484
, lens >=4.17 && <4.20
85-
, servant >=0.17 && <0.18
85+
, servant >=0.17 && <0.20
8686
, singleton-bool >=0.1.4 && <0.2
8787
, swagger2 >=2.3.0.1 && <2.7
8888
, text >=1.2.3.0 && <1.3

src/Servant/Swagger/Internal.hs

Lines changed: 66 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -7,12 +7,23 @@
77
{-# LANGUAGE PolyKinds #-}
88
{-# LANGUAGE RankNTypes #-}
99
{-# LANGUAGE ScopedTypeVariables #-}
10+
{-# LANGUAGE StandaloneDeriving #-}
1011
{-# LANGUAGE TypeOperators #-}
1112
#if __GLASGOW_HASKELL__ >= 806
1213
{-# LANGUAGE UndecidableInstances #-}
1314
#endif
1415
module Servant.Swagger.Internal where
1516

17+
-- TODO: shuffle this into the other imports.
18+
#if MIN_VERSION_servant(0,18,0)
19+
import Control.Applicative ((<|>))
20+
import qualified Data.HashMap.Strict.InsOrd as I
21+
import Data.Proxy (Proxy (Proxy))
22+
import Data.Swagger (ToSchema, Swagger(..), PathItem(..))
23+
import Servant.API.Verbs (Verb)
24+
import Servant.API.UVerb (HasStatus, StatusOf, UVerb, WithStatus(WithStatus))
25+
#endif
26+
1627
import Prelude ()
1728
import Prelude.Compat
1829

@@ -183,6 +194,60 @@ instance SwaggerMethod 'OPTIONS where swaggerMethod _ = options
183194
instance SwaggerMethod 'HEAD where swaggerMethod _ = head_
184195
instance SwaggerMethod 'PATCH where swaggerMethod _ = patch
185196

197+
-- TODO: lower version bound must be 0.19
198+
#if MIN_VERSION_servant(0,18,0)
199+
instance HasSwagger (UVerb method cs '[]) where
200+
toSwagger _ = mempty
201+
202+
-- | @since <TODO>
203+
instance
204+
( ToSchema a,
205+
HasStatus a,
206+
AllAccept cs,
207+
SwaggerMethod method,
208+
HasSwagger (UVerb method cs as)
209+
) =>
210+
HasSwagger (UVerb method cs (a ': as))
211+
where
212+
toSwagger _ =
213+
toSwagger (Proxy :: Proxy (Verb method (StatusOf a) cs a))
214+
`combineSwagger` toSwagger (Proxy :: Proxy (UVerb method cs as))
215+
where
216+
-- workaround for https://github.com/GetShopTV/swagger2/issues/218
217+
-- We'd like to juse use (<>) but the instances are wrong
218+
combinePathItem :: PathItem -> PathItem -> PathItem
219+
combinePathItem s t = PathItem
220+
{ _pathItemGet = _pathItemGet s <> _pathItemGet t
221+
, _pathItemPut = _pathItemPut s <> _pathItemPut t
222+
, _pathItemPost = _pathItemPost s <> _pathItemPost t
223+
, _pathItemDelete = _pathItemDelete s <> _pathItemDelete t
224+
, _pathItemOptions = _pathItemOptions s <> _pathItemOptions t
225+
, _pathItemHead = _pathItemHead s <> _pathItemHead t
226+
, _pathItemPatch = _pathItemPatch s <> _pathItemPatch t
227+
, _pathItemParameters = _pathItemParameters s <> _pathItemParameters t
228+
}
229+
230+
combineSwagger :: Swagger -> Swagger -> Swagger
231+
combineSwagger s t = Swagger
232+
{ _swaggerInfo = _swaggerInfo s <> _swaggerInfo t
233+
, _swaggerHost = _swaggerHost s <|> _swaggerHost t
234+
, _swaggerBasePath = _swaggerBasePath s <|> _swaggerBasePath t
235+
, _swaggerSchemes = _swaggerSchemes s <> _swaggerSchemes t
236+
, _swaggerConsumes = _swaggerConsumes s <> _swaggerConsumes t
237+
, _swaggerProduces = _swaggerProduces s <> _swaggerProduces t
238+
, _swaggerPaths = I.unionWith combinePathItem (_swaggerPaths s) (_swaggerPaths t)
239+
, _swaggerDefinitions = _swaggerDefinitions s <> _swaggerDefinitions t
240+
, _swaggerParameters = _swaggerParameters s <> _swaggerParameters t
241+
, _swaggerResponses = _swaggerResponses s <> _swaggerResponses t
242+
, _swaggerSecurityDefinitions = _swaggerSecurityDefinitions s <> _swaggerSecurityDefinitions t
243+
, _swaggerSecurity = _swaggerSecurity s <> _swaggerSecurity t
244+
, _swaggerTags = _swaggerTags s <> _swaggerTags t
245+
, _swaggerExternalDocs = _swaggerExternalDocs s <|> _swaggerExternalDocs t
246+
}
247+
248+
deriving instance ToSchema a => ToSchema (WithStatus s a)
249+
#endif
250+
186251
instance {-# OVERLAPPABLE #-} (ToSchema a, AllAccept cs, KnownNat status, SwaggerMethod method) => HasSwagger (Verb method status cs a) where
187252
toSwagger _ = toSwagger (Proxy :: Proxy (Verb method status cs (Headers '[] a)))
188253

@@ -352,7 +417,7 @@ instance (ToSchema a, AllAccept cs, HasSwagger sub, KnownSymbol (FoldDescription
352417
& schema .~ ParamBody ref
353418

354419
-- | This instance is an approximation.
355-
--
420+
--
356421
-- @since 1.1.7
357422
instance (ToSchema a, Accept ct, HasSwagger sub, KnownSymbol (FoldDescription mods)) => HasSwagger (StreamBody' mods fr ct a :> sub) where
358423
toSwagger _ = toSwagger (Proxy :: Proxy sub)

stack.yaml

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,6 @@
1-
resolver: lts-13.25
1+
resolver: lts-16.7
22
packages:
33
- '.'
44
- example/
5+
- ../servant/servant
6+
- ../servant/servant-server

0 commit comments

Comments
 (0)