Skip to content

Commit 533992c

Browse files
committed
Swagger instances for UVerb.
1 parent 321594f commit 533992c

File tree

2 files changed

+62
-1
lines changed

2 files changed

+62
-1
lines changed

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: 61 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.Swagger.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.HashMap.Strict.InsOrd (InsOrdHashMap)
@@ -183,6 +189,61 @@ instance SwaggerMethod 'OPTIONS where swaggerMethod _ = options
183189
instance SwaggerMethod 'HEAD where swaggerMethod _ = head_
184190
instance SwaggerMethod 'PATCH where swaggerMethod _ = patch
185191

192+
-- TODO: turn on lower version bound once servant is released.
193+
-- #if MIN_VERSION_servant(0,19,0)
194+
instance HasSwagger (UVerb method cs '[]) where
195+
toSwagger _ = mempty
196+
197+
-- | @since <TODO>
198+
instance
199+
{-# OVERLAPPABLE #-}
200+
( ToSchema a,
201+
HasStatus a,
202+
AllAccept cs,
203+
SwaggerMethod method,
204+
HasSwagger (UVerb method cs as)
205+
) =>
206+
HasSwagger (UVerb method cs (a ': as))
207+
where
208+
toSwagger _ =
209+
toSwagger (Proxy :: Proxy (Verb method (StatusOf a) cs a))
210+
`combineSwagger` toSwagger (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 = PathItem
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+
, _pathItemParameters = _pathItemParameters s <> _pathItemParameters t
224+
}
225+
226+
combineSwagger :: Swagger -> Swagger -> Swagger
227+
combineSwagger s t = Swagger
228+
{ _swaggerInfo = _swaggerInfo s <> _swaggerInfo t
229+
, _swaggerHost = _swaggerHost s <|> _swaggerHost t
230+
, _swaggerBasePath = _swaggerBasePath s <|> _swaggerBasePath t
231+
, _swaggerSchemes = _swaggerSchemes s <> _swaggerSchemes t
232+
, _swaggerConsumes = _swaggerConsumes s <> _swaggerConsumes t
233+
, _swaggerProduces = _swaggerProduces s <> _swaggerProduces t
234+
, _swaggerPaths = InsOrdHashMap.unionWith combinePathItem (_swaggerPaths s) (_swaggerPaths t)
235+
, _swaggerDefinitions = _swaggerDefinitions s <> _swaggerDefinitions t
236+
, _swaggerParameters = _swaggerParameters s <> _swaggerParameters t
237+
, _swaggerResponses = _swaggerResponses s <> _swaggerResponses t
238+
, _swaggerSecurityDefinitions = _swaggerSecurityDefinitions s <> _swaggerSecurityDefinitions t
239+
, _swaggerSecurity = _swaggerSecurity s <> _swaggerSecurity t
240+
, _swaggerTags = _swaggerTags s <> _swaggerTags t
241+
, _swaggerExternalDocs = _swaggerExternalDocs s <|> _swaggerExternalDocs t
242+
}
243+
244+
deriving instance ToSchema a => ToSchema (WithStatus s a)
245+
-- #endif
246+
186247
instance {-# OVERLAPPABLE #-} (ToSchema a, AllAccept cs, KnownNat status, SwaggerMethod method) => HasSwagger (Verb method status cs a) where
187248
toSwagger _ = toSwagger (Proxy :: Proxy (Verb method status cs (Headers '[] a)))
188249

0 commit comments

Comments
 (0)