1
1
{-# LANGUAGE CPP #-}
2
2
{-# LANGUAGE ConstraintKinds #-}
3
3
{-# LANGUAGE DataKinds #-}
4
+ {-# LANGUAGE GeneralizedNewtypeDeriving #-} -- TODO: can we get rid of this?
4
5
{-# LANGUAGE FlexibleContexts #-}
5
6
{-# LANGUAGE FlexibleInstances #-}
6
7
{-# LANGUAGE OverloadedStrings #-}
7
8
{-# LANGUAGE PolyKinds #-}
8
9
{-# LANGUAGE RankNTypes #-}
9
10
{-# LANGUAGE ScopedTypeVariables #-}
11
+ {-# LANGUAGE StandaloneDeriving #-} -- TODO: can we get away with terminating support for ghcs that don't have this?
10
12
{-# LANGUAGE TypeOperators #-}
11
13
#if __GLASGOW_HASKELL__ >= 806
12
14
{-# LANGUAGE UndecidableInstances #-}
@@ -16,6 +18,10 @@ module Servant.Swagger.Internal where
16
18
import Prelude ()
17
19
import Prelude.Compat
18
20
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
19
25
import Control.Lens
20
26
import Data.Aeson
21
27
import Data.HashMap.Strict.InsOrd (InsOrdHashMap )
@@ -183,6 +189,61 @@ instance SwaggerMethod 'OPTIONS where swaggerMethod _ = options
183
189
instance SwaggerMethod 'HEAD where swaggerMethod _ = head_
184
190
instance SwaggerMethod 'PATCH where swaggerMethod _ = patch
185
191
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
+
186
247
instance {-# OVERLAPPABLE #-} (ToSchema a , AllAccept cs , KnownNat status , SwaggerMethod method ) => HasSwagger (Verb method status cs a ) where
187
248
toSwagger _ = toSwagger (Proxy :: Proxy (Verb method status cs (Headers '[] a )))
188
249
0 commit comments