|
7 | 7 | {-# LANGUAGE PolyKinds #-}
|
8 | 8 | {-# LANGUAGE RankNTypes #-}
|
9 | 9 | {-# LANGUAGE ScopedTypeVariables #-}
|
| 10 | +{-# LANGUAGE StandaloneDeriving #-} |
10 | 11 | {-# LANGUAGE TypeOperators #-}
|
11 | 12 | #if __GLASGOW_HASKELL__ >= 806
|
12 | 13 | {-# LANGUAGE UndecidableInstances #-}
|
13 | 14 | #endif
|
14 | 15 | module Servant.Swagger.Internal where
|
15 | 16 |
|
| 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 | + |
16 | 27 | import Prelude ()
|
17 | 28 | import Prelude.Compat
|
18 | 29 |
|
@@ -183,6 +194,60 @@ instance SwaggerMethod 'OPTIONS where swaggerMethod _ = options
|
183 | 194 | instance SwaggerMethod 'HEAD where swaggerMethod _ = head_
|
184 | 195 | instance SwaggerMethod 'PATCH where swaggerMethod _ = patch
|
185 | 196 |
|
| 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 | + |
186 | 251 | instance {-# OVERLAPPABLE #-} (ToSchema a, AllAccept cs, KnownNat status, SwaggerMethod method) => HasSwagger (Verb method status cs a) where
|
187 | 252 | toSwagger _ = toSwagger (Proxy :: Proxy (Verb method status cs (Headers '[] a)))
|
188 | 253 |
|
@@ -352,7 +417,7 @@ instance (ToSchema a, AllAccept cs, HasSwagger sub, KnownSymbol (FoldDescription
|
352 | 417 | & schema .~ ParamBody ref
|
353 | 418 |
|
354 | 419 | -- | This instance is an approximation.
|
355 |
| --- |
| 420 | +-- |
356 | 421 | -- @since 1.1.7
|
357 | 422 | instance (ToSchema a, Accept ct, HasSwagger sub, KnownSymbol (FoldDescription mods)) => HasSwagger (StreamBody' mods fr ct a :> sub) where
|
358 | 423 | toSwagger _ = toSwagger (Proxy :: Proxy sub)
|
|
0 commit comments