Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module lets you get API docs for free. It lets you generate
an API
from the type that represents your API using docs
:
docs ::HasDocs
api =>Proxy
api ->API
Alternatively, if you wish to add one or more introductions to your
documentation, use docsWithIntros
:
docsWithIntros
::HasDocs
api => [DocIntro] ->Proxy
api ->API
You can then call markdown
on the API
value:
markdown
::API
-> String
or define a custom pretty printer:
yourPrettyDocs :: API
-> String -- or blaze-html's HTML, or ...
The only thing you'll need to do will be to implement some classes for your captures, get parameters and request or response bodies.
Here is a complete example that you can run to see the markdown pretty printer in action:
{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE TypeOperators #-} {-# OPTIONS_GHC -fno-warn-orphans #-} import Control.Lens import Data.Aeson import Data.Proxy import Data.String.Conversions import Data.Text (Text) import GHC.Generics import Servant.API import Servant.Docs -- * Example -- | A greet message data type newtype Greet = Greet Text deriving (Generic, Show) -- | We can get JSON support automatically. This will be used to parse -- and encode a Greeting as 'JSON'. instance FromJSON Greet instance ToJSON Greet -- | We can also implement 'MimeRender' for additional formats like 'PlainText'. instance MimeRender PlainText Greet where mimeRender Proxy (Greet s) = "\"" <> cs s <> "\"" -- We add some useful annotations to our captures, -- query parameters and request body to make the docs -- really helpful. instance ToCapture (Capture "name" Text) where toCapture _ = DocCapture "name" "name of the person to greet" instance ToCapture (Capture "greetid" Text) where toCapture _ = DocCapture "greetid" "identifier of the greet msg to remove" instance ToParam (QueryParam "capital" Bool) where toParam _ = DocQueryParam "capital" ["true", "false"] "Get the greeting message in uppercase (true) or not (false).\ \Default is false." Normal instance ToParam (MatrixParam "lang" String) where toParam _ = DocQueryParam "lang" ["en", "sv", "fr"] "Get the greeting message selected language. Default is en." Normal instance ToSample Greet Greet where toSample _ = Just $ Greet "Hello, haskeller!" toSamples _ = [ ("If you use ?capital=true", Greet "HELLO, HASKELLER") , ("If you use ?capital=false", Greet "Hello, haskeller") ] -- We define some introductory sections, these will appear at the top of the -- documentation. -- -- We pass them in with 'docsWith', below. If you only want to add -- introductions, you may use 'docsWithIntros' intro1 :: DocIntro intro1 = DocIntro "On proper introductions." -- The title [ "Hello there." , "As documentation is usually written for humans, it's often useful \ \to introduce concepts with a few words." ] -- Elements are paragraphs intro2 :: DocIntro intro2 = DocIntro "This title is below the last" [ "You'll also note that multiple intros are possible." ] -- API specification type TestApi = -- GET /hello/:name?capital={true, false} returns a Greet as JSON or PlainText "hello" :> MatrixParam "lang" String :> Capture "name" Text :> QueryParam "capital" Bool :> Get '[JSON, PlainText] Greet -- POST /greet with a Greet as JSON in the request body, -- returns a Greet as JSON :<|> "greet" :> ReqBody '[JSON] Greet :> Post '[JSON] Greet -- DELETE /greet/:greetid :<|> "greet" :> Capture "greetid" Text :> Delete '[JSON] () testApi :: Proxy TestApi testApi = Proxy -- Build some extra information for the DELETE /greet/:greetid endpoint. We -- want to add documentation about a secret unicorn header and some extra -- notes. extra :: ExtraInfo TestApi extra = extraInfo (Proxy :: Proxy ("greet" :> Capture "greetid" Text :> Delete '[JSON] ())) $ defAction & headers <>~ ["unicorns"] & notes <>~ [ DocNote "Title" ["This is some text"] , DocNote "Second secton" ["And some more"] ] -- Generate the data that lets us have API docs. This -- is derived from the type as well as from -- the 'ToCapture', 'ToParam' and 'ToSample' instances from above. -- -- If you didn't want intros and extra information, you could just call: -- -- > docs testAPI :: API docsGreet :: API docsGreet = docsWith [intro1, intro2] extra testApi main :: IO () main = putStrLn $ markdown docsGreet
- class HasDocs layout where
- docs :: HasDocs layout => Proxy layout -> API
- markdown :: API -> String
- newtype ExtraInfo layout = ExtraInfo (HashMap Endpoint Action)
- docsWith :: HasDocs layout => [DocIntro] -> ExtraInfo layout -> Proxy layout -> API
- docsWithIntros :: HasDocs layout => [DocIntro] -> Proxy layout -> API
- extraInfo :: (IsIn endpoint layout, HasLink endpoint, HasDocs endpoint) => Proxy endpoint -> Action -> ExtraInfo layout
- class ToSample a b | a -> b where
- sampleByteString :: forall ctypes a b. (ToSample a b, IsNonEmpty ctypes, AllMimeRender ctypes b) => Proxy ctypes -> Proxy a -> [(MediaType, ByteString)]
- sampleByteStrings :: forall ctypes a b. (ToSample a b, IsNonEmpty ctypes, AllMimeRender ctypes b) => Proxy ctypes -> Proxy a -> [(Text, MediaType, ByteString)]
- class ToParam t where
- toParam :: Proxy t -> DocQueryParam
- class ToCapture c where
- toCapture :: Proxy c -> DocCapture
- data Method
- data Endpoint
- path :: Lens' Endpoint [String]
- method :: Lens' Endpoint Method
- defEndpoint :: Endpoint
- data API
- apiIntros :: Lens' API [DocIntro]
- apiEndpoints :: Lens' API (HashMap Endpoint Action)
- emptyAPI :: API
- data DocCapture = DocCapture {
- _capSymbol :: String
- _capDesc :: String
- capSymbol :: Lens' DocCapture String
- capDesc :: Lens' DocCapture String
- data DocQueryParam = DocQueryParam {
- _paramName :: String
- _paramValues :: [String]
- _paramDesc :: String
- _paramKind :: ParamKind
- data ParamKind
- paramName :: Lens' DocQueryParam String
- paramValues :: Lens' DocQueryParam [String]
- paramDesc :: Lens' DocQueryParam String
- paramKind :: Lens' DocQueryParam ParamKind
- data DocNote = DocNote {
- _noteTitle :: String
- _noteBody :: [String]
- noteTitle :: Lens' DocNote String
- noteBody :: Lens' DocNote [String]
- data DocIntro = DocIntro {
- _introTitle :: String
- _introBody :: [String]
- introTitle :: Lens' DocIntro String
- introBody :: Lens' DocIntro [String]
- data Response = Response {
- _respStatus :: Int
- _respTypes :: [MediaType]
- _respBody :: [(Text, MediaType, ByteString)]
- _respHeaders :: [Header]
- respStatus :: Lens' Response Int
- respTypes :: Lens' Response [MediaType]
- respBody :: Lens' Response [(Text, MediaType, ByteString)]
- defResponse :: Response
- data Action
- captures :: Lens' Action [DocCapture]
- headers :: Lens' Action [Text]
- notes :: Lens' Action [DocNote]
- params :: Lens' Action [DocQueryParam]
- rqtypes :: Lens' Action [MediaType]
- rqbody :: Lens' Action [(MediaType, ByteString)]
- response :: Lens' Action Response
- defAction :: Action
- single :: Endpoint -> Action -> API
HasDocs
class and key functions
class HasDocs layout where Source
The class that abstracts away the impact of API combinators on documentation generation.
HasDocs * Raw | |
(HasDocs * layout1, HasDocs * layout2) => HasDocs * ((:<|>) layout1 layout2) | The generated docs for |
(ToSample * a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts, AllHeaderSamples [*] ls, GetHeaders (HList ls)) => HasDocs * (Get cts (Headers ls a)) | |
(ToSample * a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts) => HasDocs * (Get cts a) | |
(ToSample * a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts, AllHeaderSamples [*] ls, GetHeaders (HList ls)) => HasDocs * (Post cts (Headers ls a)) | |
(ToSample * a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts) => HasDocs * (Post cts a) | |
(ToSample * a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts, AllHeaderSamples [*] ls, GetHeaders (HList ls)) => HasDocs * (Delete cts (Headers ls a)) | |
(ToSample * a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts) => HasDocs * (Delete cts a) | |
(ToSample * a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts, AllHeaderSamples [*] ls, GetHeaders (HList ls)) => HasDocs * (Put cts (Headers ls a)) | |
(ToSample * a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts) => HasDocs * (Put cts a) | |
(ToSample k1 a b, IsNonEmpty cts, AllMimeRender cts b, HasDocs k sublayout, SupportedTypes cts) => HasDocs * ((:>) * k (ReqBody k cts a) sublayout) | |
(KnownSymbol sym, HasDocs k sublayout) => HasDocs * ((:>) * k (MatrixFlag sym) sublayout) | |
(KnownSymbol sym, HasDocs k sublayout) => HasDocs * ((:>) * k (MatrixParams k sym a) sublayout) | |
(KnownSymbol sym, ToParam * (MatrixParam k1 sym a), HasDocs k sublayout) => HasDocs * ((:>) * k (MatrixParam k sym a) sublayout) | |
(KnownSymbol sym, ToParam * (QueryFlag sym), HasDocs k sublayout) => HasDocs * ((:>) * k (QueryFlag sym) sublayout) | |
(KnownSymbol sym, ToParam * (QueryParams k1 sym a), HasDocs k sublayout) => HasDocs * ((:>) * k (QueryParams k sym a) sublayout) | |
(KnownSymbol sym, ToParam * (QueryParam k1 sym a), HasDocs k sublayout) => HasDocs * ((:>) * k (QueryParam k sym a) sublayout) | |
(KnownSymbol sym, HasDocs k sublayout) => HasDocs * ((:>) * k (Header sym a) sublayout) | |
(KnownSymbol sym, ToCapture * (Capture k1 sym a), HasDocs k sublayout) => HasDocs * ((:>) * k (Capture k sym a) sublayout) |
|
(KnownSymbol path, HasDocs k sublayout) => HasDocs * ((:>) Symbol k path sublayout) |
docs :: HasDocs layout => Proxy layout -> API Source
Generate the docs for a given API that implements HasDocs
. This is the
default way to create documentation.
Generating docs with extra information
newtype ExtraInfo layout Source
Type of extra information that a user may wish to "union" with their documentation.
These are intended to be built using extraInfo. Multiple ExtraInfo may be combined with the monoid instance.
docsWith :: HasDocs layout => [DocIntro] -> ExtraInfo layout -> Proxy layout -> API Source
Generate documentation given some extra introductions (in the form of
DocInfo
) and some extra endpoint documentation (in the form of
ExtraInfo
.
The extra introductions will be prepended to the top of the documentation, before the specific endpoint documentation. The extra endpoint documentation will be "unioned" with the automatically generated endpoint documentation.
You are expected to build up the ExtraInfo with the Monoid instance and
extraInfo
.
If you only want to add an introduction, use docsWithIntros
.
docsWithIntros :: HasDocs layout => [DocIntro] -> Proxy layout -> API Source
Generate the docs for a given API that implements HasDocs
with with any
number of introduction(s)
extraInfo :: (IsIn endpoint layout, HasLink endpoint, HasDocs endpoint) => Proxy endpoint -> Action -> ExtraInfo layout Source
Create an ExtraInfo
that is garunteed to be within the given API layout.
The safety here is to ensure that you only add custom documentation to an endpoint that actually exists within your API.
extra :: ExtraInfo TestApi extra = extraInfo (Proxy :: Proxy ("greet" :> Capture "greetid" Text :> Delete)) $ defAction & headers <>~ ["unicorns"] & notes <>~ [ DocNote "Title" ["This is some text"] , DocNote "Second secton" ["And some more"] ]
Classes you need to implement for your types
class ToSample a b | a -> b where Source
The class that lets us display a sample input or output in the supported content-types when generating documentation for endpoints that either:
- expect a request body, or
- return a non empty response body
Example of an instance:
{-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE OverloadedStrings #-} import Data.Aeson import Data.Text import GHC.Generics data Greet = Greet { _msg :: Text } deriving (Generic, Show) instance FromJSON Greet instance ToJSON Greet instance ToSample Greet Greet where toSample _ = Just g where g = Greet "Hello, haskeller!"
You can also instantiate this class using toSamples
instead of
toSample
: it lets you specify different responses along with
some context (as Text
) that explains when you're supposed to
get the corresponding response.
sampleByteString :: forall ctypes a b. (ToSample a b, IsNonEmpty ctypes, AllMimeRender ctypes b) => Proxy ctypes -> Proxy a -> [(MediaType, ByteString)] Source
Synthesise a sample value of a type, encoded in the specified media types.
sampleByteStrings :: forall ctypes a b. (ToSample a b, IsNonEmpty ctypes, AllMimeRender ctypes b) => Proxy ctypes -> Proxy a -> [(Text, MediaType, ByteString)] Source
Synthesise a list of sample values of a particular type, encoded in the specified media types.
The class that helps us automatically get documentation for GET parameters.
Example of an instance:
instance ToParam (QueryParam "capital" Bool) where toParam _ = DocQueryParam "capital" ["true", "false"] "Get the greeting message in uppercase (true) or not (false). Default is false."
toParam :: Proxy t -> DocQueryParam Source
class ToCapture c where Source
The class that helps us automatically get documentation for URL captures.
Example of an instance:
instance ToCapture (Capture "name" Text) where toCapture _ = DocCapture "name" "name of the person to greet"
toCapture :: Proxy c -> DocCapture Source
ADTs to represent an API
Supported HTTP request methods
An Endpoint
type that holds the path
and the method
.
Gets used as the key in the API
hashmap. Modify defEndpoint
or any Endpoint
value you want using the path
and method
lenses to tweak.
λ>defEndpoint
GET / λ>defEndpoint
&path
<>~
["foo"] GET /foo λ>defEndpoint
&path
<>~
["foo"] &method
.~
DocPOST
POST /foo
defEndpoint :: Endpoint Source
An Endpoint
whose path is `"/"` and whose method is DocGET
Here's how you can modify it:
λ>defEndpoint
GET / λ>defEndpoint
&path
<>~
["foo"] GET /foo λ>defEndpoint
&path
<>~
["foo"] &method
.~
DocPOST
POST /foo
data DocCapture Source
A type to represent captures. Holds the name of the capture and a description.
Write a ToCapture
instance for your captured types.
DocCapture | |
|
data DocQueryParam Source
A type to represent a GET parameter from the Query String. Holds its name, the possible values (leave empty if there isn't a finite number of them), and a description of how it influences the output or behavior.
Write a ToParam
instance for your GET parameter types
DocQueryParam | |
|
Type of GET parameter:
- Normal corresponds to
QueryParam
, i.e your usual GET parameter - List corresponds to
QueryParams
, i.e GET parameters with multiple values - Flag corresponds to
QueryFlag
, i.e a value-less GET parameter
A type to represent extra notes that may be attached to an Action
.
This is intended to be used when writing your own HasDocs instances to add extra sections to your endpoint's documentation.
DocNote | |
|
An introductory paragraph for your documentation. You can pass these to
docsWithIntros
.
DocIntro | |
|
A type to represent an HTTP response. Has an Int
status, a list of
possible MediaType
s, and a list of example ByteString
response bodies.
Tweak defResponse
using the respStatus
, respTypes
and respBody
lenses if you want.
If you want to respond with a non-empty response body, you'll most likely
want to write a ToSample
instance for the type that'll be represented
as encoded data in the response.
Can be tweaked with three lenses.
λ> defResponse Response {_respStatus = 200, _respTypes = [], _respBody = []} λ> defResponse & respStatus .~ 204 & respBody .~ [("If everything goes well", "{ \"status\": \"ok\" }")] Response {_respStatus = 204, _respTypes = [], _respBody = [("If everything goes well", "{ \"status\": \"ok\" }")]}
Response | |
|
defResponse :: Response Source
Default response: status code 200, no response body.
Can be tweaked with two lenses.
λ> defResponse Response {_respStatus = 200, _respBody = Nothing} λ> defResponse & respStatus .~ 204 & respBody .~ Just "[]" Response {_respStatus = 204, _respBody = Just "[]"}
A datatype that represents everything that can happen at an endpoint, with its lenses:
- List of captures (
captures
) - List of GET parameters (
params
) - What the request body should look like, if any is requested (
rqbody
) - What the response should be if everything goes well (
response
)
You can tweak an Action
(like the default defAction
) with these lenses
to transform an action and add some information to it.
captures :: Lens' Action [DocCapture] Source
params :: Lens' Action [DocQueryParam] Source