Fix servant-docs code sample in README (#1335)
This commit is contained in:
parent
1760cc8527
commit
e3a29addf4
1 changed files with 44 additions and 11 deletions
|
@ -2,24 +2,56 @@
|
||||||
|
|
||||||
![servant](https://raw.githubusercontent.com/haskell-servant/servant/master/servant.png)
|
![servant](https://raw.githubusercontent.com/haskell-servant/servant/master/servant.png)
|
||||||
|
|
||||||
Generate API docs for your *servant* webservice. Feel free to also take a look at [servant-pandoc](https://github.com/mpickering/servant-pandoc) which uses this package to target a broad range of output formats using the excellent **pandoc**.
|
Generate API docs for your _servant_ webservice. Feel free to also take a look at [servant-pandoc](https://github.com/mpickering/servant-pandoc) which uses this package to target a broad range of output formats using the excellent **pandoc**.
|
||||||
|
|
||||||
## Example
|
## Example
|
||||||
|
|
||||||
See [here](https://github.com/haskell-servant/servant/blob/master/servant-docs/example/greet.md) for the output of the following program.
|
See [here](https://github.com/haskell-servant/servant/blob/master/servant-docs/example/greet.md) for the output of the following program.
|
||||||
|
|
||||||
``` haskell
|
```haskell
|
||||||
{-# LANGUAGE DataKinds #-}
|
{-# LANGUAGE DataKinds #-}
|
||||||
|
{-# LANGUAGE DeriveGeneric #-}
|
||||||
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE PolyKinds #-}
|
{-# LANGUAGE PolyKinds #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
{-# LANGUAGE DeriveGeneric #-}
|
|
||||||
{-# LANGUAGE TypeOperators #-}
|
{-# LANGUAGE TypeOperators #-}
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
|
||||||
{-# LANGUAGE OverloadedStrings #-}
|
|
||||||
|
|
||||||
import Data.Proxy
|
import Data.Aeson (FromJSON, ToJSON)
|
||||||
import Data.Text
|
import Data.Proxy (Proxy (..))
|
||||||
|
import Data.String.Conversions (cs)
|
||||||
|
import Data.Text (Text)
|
||||||
|
import GHC.Generics (Generic)
|
||||||
|
import Servant.API
|
||||||
|
( (:<|>),
|
||||||
|
(:>),
|
||||||
|
Capture,
|
||||||
|
Delete,
|
||||||
|
Get,
|
||||||
|
JSON,
|
||||||
|
MimeRender,
|
||||||
|
PlainText,
|
||||||
|
Post,
|
||||||
|
QueryParam,
|
||||||
|
ReqBody,
|
||||||
|
mimeRender,
|
||||||
|
)
|
||||||
import Servant.Docs
|
import Servant.Docs
|
||||||
|
( API,
|
||||||
|
DocCapture (..),
|
||||||
|
DocQueryParam (..),
|
||||||
|
ParamKind (..),
|
||||||
|
ToCapture,
|
||||||
|
ToParam,
|
||||||
|
ToSample,
|
||||||
|
docs,
|
||||||
|
markdown,
|
||||||
|
singleSample,
|
||||||
|
toCapture,
|
||||||
|
toParam,
|
||||||
|
toSamples,
|
||||||
|
)
|
||||||
|
|
||||||
-- our type for a Greeting message
|
-- our type for a Greeting message
|
||||||
data Greet = Greet { _msg :: Text }
|
data Greet = Greet { _msg :: Text }
|
||||||
|
@ -29,6 +61,7 @@ data Greet = Greet { _msg :: Text }
|
||||||
-- 'MimeRender' instance for 'JSON'.
|
-- 'MimeRender' instance for 'JSON'.
|
||||||
instance FromJSON Greet
|
instance FromJSON Greet
|
||||||
instance ToJSON Greet
|
instance ToJSON Greet
|
||||||
|
instance ToSample ()
|
||||||
|
|
||||||
-- We can also implement 'MimeRender' explicitly for additional formats.
|
-- We can also implement 'MimeRender' explicitly for additional formats.
|
||||||
instance MimeRender PlainText Greet where
|
instance MimeRender PlainText Greet where
|
||||||
|
@ -36,8 +69,7 @@ instance MimeRender PlainText Greet where
|
||||||
|
|
||||||
-- we provide a sample value for the 'Greet' type
|
-- we provide a sample value for the 'Greet' type
|
||||||
instance ToSample Greet where
|
instance ToSample Greet where
|
||||||
toSample = Just g
|
toSamples _ = singleSample g
|
||||||
|
|
||||||
where g = Greet "Hello, haskeller!"
|
where g = Greet "Hello, haskeller!"
|
||||||
|
|
||||||
instance ToParam (QueryParam "capital" Bool) where
|
instance ToParam (QueryParam "capital" Bool) where
|
||||||
|
@ -45,6 +77,7 @@ instance ToParam (QueryParam "capital" Bool) where
|
||||||
DocQueryParam "capital"
|
DocQueryParam "capital"
|
||||||
["true", "false"]
|
["true", "false"]
|
||||||
"Get the greeting message in uppercase (true) or not (false). Default is false."
|
"Get the greeting message in uppercase (true) or not (false). Default is false."
|
||||||
|
Normal
|
||||||
|
|
||||||
instance ToCapture (Capture "name" Text) where
|
instance ToCapture (Capture "name" Text) where
|
||||||
toCapture _ = DocCapture "name" "name of the person to greet"
|
toCapture _ = DocCapture "name" "name of the person to greet"
|
||||||
|
@ -55,8 +88,8 @@ instance ToCapture (Capture "greetid" Text) where
|
||||||
-- API specification
|
-- API specification
|
||||||
type TestApi =
|
type TestApi =
|
||||||
"hello" :> Capture "name" Text :> QueryParam "capital" Bool :> Get '[JSON,PlainText] Greet
|
"hello" :> Capture "name" Text :> QueryParam "capital" Bool :> Get '[JSON,PlainText] Greet
|
||||||
:<|> "greet" :> RQBody '[JSON] Greet :> Post '[JSON] Greet
|
:<|> "greet" :> ReqBody '[JSON] Greet :> Post '[JSON] Greet
|
||||||
:<|> "delete" :> Capture "greetid" Text :> Delete '[] ()
|
:<|> "delete" :> Capture "greetid" Text :> Delete '[JSON] ()
|
||||||
|
|
||||||
testApi :: Proxy TestApi
|
testApi :: Proxy TestApi
|
||||||
testApi = Proxy
|
testApi = Proxy
|
||||||
|
|
Loading…
Reference in a new issue