Add ID to indentify an operation

This commit is contained in:
acentelles 2019-11-04 14:12:46 +00:00
parent 925d50d752
commit 9fa76c859f
8 changed files with 86 additions and 12 deletions

View file

@ -47,12 +47,12 @@ import Servant.API
EmptyAPI, FramingRender (..), FramingUnrender (..),
FromSourceIO (..), Header', Headers (..), HttpVersion,
IsSecure, MimeRender (mimeRender),
MimeUnrender (mimeUnrender), NoContent (NoContent), QueryFlag,
QueryParam', QueryParams, Raw, ReflectMethod (..), RemoteHost,
ReqBody', SBoolI, Stream, StreamBody', Summary, ToHttpApiData,
ToSourceIO (..), Vault, Verb, NoContentVerb, WithNamedContext,
contentType, getHeadersHList, getResponse, toQueryParam,
toUrlPiece)
MimeUnrender (mimeUnrender), NoContent (NoContent), OperationId,
QueryFlag, QueryParam', QueryParams, Raw, ReflectMethod (..),
RemoteHost, ReqBody', SBoolI, Stream, StreamBody', Summary,
ToHttpApiData, ToSourceIO (..), Vault, Verb, NoContentVerb,
WithNamedContext, contentType, getHeadersHList, getResponse,
toQueryParam, toUrlPiece)
import Servant.API.ContentTypes
(contentTypes)
import Servant.API.Modifiers
@ -404,6 +404,15 @@ instance HasClient m api => HasClient m (Description desc :> api) where
hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api) f cl
-- | Ignore @'OperationId'@ in client functions.
instance HasClient m api => HasClient m (OperationId desc :> api) where
type Client m (OperationId desc :> api) = Client m api
clientWithRoute pm _ = clientWithRoute pm (Proxy :: Proxy api)
hoistClientMonad pm _ f cl = hoistClientMonad pm (Proxy :: Proxy api) f cl
-- | If you use a 'QueryParam' in one of your endpoints in your API,
-- the corresponding querying function will automatically take
-- an additional argument of the type specified by your 'QueryParam',

View file

@ -976,6 +976,16 @@ instance (KnownSymbol desc, HasDocs api)
action' = over notes (|> note) action
note = DocNote (symbolVal (Proxy :: Proxy desc)) []
instance (KnownSymbol desc, HasDocs api)
=> HasDocs (OperationId desc :> api) where
docsFor Proxy (endpoint, action) =
docsFor subApiP (endpoint, action')
where subApiP = Proxy :: Proxy api
action' = over notes (|> note) action
note = DocNote (symbolVal (Proxy :: Proxy desc)) []
-- TODO: We use 'AllMimeRender' here because we need to be able to show the
-- example data. However, there's no reason to believe that the instances of
-- 'AllMimeUnrender' and 'AllMimeRender' actually agree (or to suppose that

View file

@ -406,6 +406,14 @@ instance HasForeign lang ftype api
foreignFor lang ftype Proxy req =
foreignFor lang ftype (Proxy :: Proxy api) req
instance HasForeign lang ftype api
=> HasForeign lang ftype (OperationId desc :> api) where
type Foreign ftype (OperationId desc :> api) = Foreign ftype api
foreignFor lang ftype Proxy req =
foreignFor lang ftype (Proxy :: Proxy api) req
-- | Utility class used by 'listFromAPI' which computes
-- the data needed to generate a function for each endpoint
-- and hands it all back in a list.

View file

@ -72,11 +72,11 @@ import Servant.API
((:<|>) (..), (:>), Accept (..), BasicAuth, Capture',
CaptureAll, Description, EmptyAPI, FramingRender (..),
FramingUnrender (..), FromSourceIO (..), Header', If,
IsSecure (..), QueryFlag, QueryParam', QueryParams, Raw,
ReflectMethod (reflectMethod), RemoteHost, ReqBody',
SBool (..), SBoolI (..), SourceIO, Stream, StreamBody',
Summary, ToSourceIO (..), Vault, Verb, NoContentVerb,
WithNamedContext)
IsSecure (..), OperationId, QueryFlag, QueryParam',
QueryParams, Raw, ReflectMethod (reflectMethod), RemoteHost,
ReqBody', SBool (..), SBoolI (..), SourceIO, Stream,
StreamBody', Summary, ToSourceIO (..), Vault, Verb,
NoContentVerb, WithNamedContext)
import Servant.API.ContentTypes
(AcceptHeader (..), AllCTRender (..), AllCTUnrender (..),
AllMime, MimeRender (..), MimeUnrender (..), canHandleAcceptH,
@ -718,6 +718,14 @@ instance HasServer api ctx => HasServer (Description desc :> api) ctx where
route _ = route (Proxy :: Proxy api)
hoistServerWithContext _ pc nt s = hoistServerWithContext (Proxy :: Proxy api) pc nt s
-- | Ignore @'OperationId'@ in server handlers.
instance HasServer api ctx => HasServer (OperationId desc :> api) ctx where
type ServerT (OperationId desc :> api) m = ServerT api m
route _ = route (Proxy :: Proxy api)
hoistServerWithContext _ pc nt s = hoistServerWithContext (Proxy :: Proxy api) pc nt s
-- | Singleton type representing a server that serves an empty API.
data EmptyServer = EmptyServer deriving (Typeable, Eq, Show, Bounded, Enum)

View file

@ -57,6 +57,7 @@ library
Servant.API.IsSecure
Servant.API.Modifiers
Servant.API.QueryParam
Servant.API.OperationId
Servant.API.Raw
Servant.API.RemoteHost
Servant.API.ReqBody

View file

@ -42,6 +42,9 @@ module Servant.API (
-- * Endpoints description
module Servant.API.Description,
-- * Endpoints operation id
module Servant.API.OperationId,
-- * Content Types
module Servant.API.ContentTypes,
-- | Serializing and deserializing types based on @Accept@ and
@ -102,6 +105,8 @@ import Servant.API.Modifiers
(Lenient, Optional, Required, Strict)
import Servant.API.QueryParam
(QueryFlag, QueryParam, QueryParam', QueryParams)
import Servant.API.OperationId
(OperationId)
import Servant.API.Raw
(Raw)
import Servant.API.RemoteHost

View file

@ -0,0 +1,33 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_HADDOCK not-home #-}
module Servant.API.OperationId (
-- * Combinators
OperationId,
) where
import Data.Typeable
(Typeable)
import GHC.TypeLits
(Symbol)
-- | Add an operationId for a specific endpoint of an API.
--
-- Example:
--
-- >>> type MyApi = OperationId "getBookById" :> "books" :> Capture "id" Int :> Get '[JSON] Book
data OperationId (sym :: Symbol)
deriving (Typeable)
-- $setup
-- >>> import Servant.API
-- >>> import Data.Aeson
-- >>> import Data.Text
-- >>> data Book
-- >>> instance ToJSON Book where { toJSON = undefined }
-- >>> data SourceFile
-- >>> instance ToJSON SourceFile where { toJSON = undefined }

View file

@ -29,4 +29,4 @@ extra-deps:
- resourcet-1.2.2
- sop-core-0.4.0.0
- wai-extra-3.0.24.3
- tasty-1.1.0.4
- tasty-1.1.0.4