Add Description and Summary combinators

This commit is contained in:
Catherine Galkina 2017-06-08 17:35:24 +03:00
parent bb7df7b890
commit 2e59a82d01
4 changed files with 39 additions and 0 deletions

View file

@ -38,6 +38,7 @@ library
Servant.API.BasicAuth
Servant.API.Capture
Servant.API.ContentTypes
Servant.API.Description
Servant.API.Empty
Servant.API.Experimental.Auth
Servant.API.Header

View file

@ -34,6 +34,9 @@ module Servant.API (
-- * Authentication
module Servant.API.BasicAuth,
-- * Endpoints description
module Servant.API.Description,
-- * Content Types
module Servant.API.ContentTypes,
-- | Serializing and deserializing types based on @Accept@ and
@ -68,6 +71,7 @@ import Servant.API.ContentTypes (Accept (..), FormUrlEncoded,
MimeRender (..), NoContent (NoContent),
MimeUnrender (..), OctetStream,
PlainText)
import Servant.API.Description (Description, Summary)
import Servant.API.Empty (EmptyAPI (..))
import Servant.API.Experimental.Auth (AuthProtect)
import Servant.API.Header (Header (..))

View file

@ -0,0 +1,32 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE PolyKinds #-}
{-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Description (Description, Summary) where
import Data.Typeable (Typeable)
import GHC.TypeLits (Symbol)
-- | Add a short summary for (part of) API.
--
-- Example:
--
-- >>> type MyApi = Summary "Get book by ISBN." :> "books" :> Capture "isbn" Text :> Get '[JSON] Book
data Summary (sym :: Symbol)
deriving (Typeable)
-- | Add more verbose description for (part of) API.
--
-- Example:
--
-- >>> type MyApi = Description "Some longer implementation details here." :> "books" :> Capture "isbn" Text :> Get '[JSON] Book
data Description (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

@ -38,6 +38,8 @@ type ComprehensiveAPIWithoutRaw =
Verb 'POST 204 '[JSON] Int :<|>
WithNamedContext "foo" '[] GET :<|>
CaptureAll "foo" Int :> GET :<|>
Summary "foo" :> GET :<|>
Description "foo" :> GET :<|>
EmptyAPI
comprehensiveAPIWithoutRaw :: Proxy ComprehensiveAPIWithoutRaw