Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data Endpoint = Endpoint {}
- showPath :: [String] -> String
- defEndpoint :: Endpoint
- data API = API {}
- emptyAPI :: API
- data DocCapture = DocCapture {
- _capSymbol :: String
- _capDesc :: String
- data DocQueryParam = DocQueryParam {
- _paramName :: String
- _paramValues :: [String]
- _paramDesc :: String
- _paramKind :: ParamKind
- data DocFragment = DocFragment {
- _fragSymbol :: String
- _fragDesc :: String
- combineFragment :: Maybe DocFragment -> Maybe DocFragment -> Maybe DocFragment
- data DocIntro = DocIntro {
- _introTitle :: String
- _introBody :: [String]
- data DocAuthentication = DocAuthentication {}
- data DocNote = DocNote {
- _noteTitle :: String
- _noteBody :: [String]
- newtype ExtraInfo api = ExtraInfo (HashMap Endpoint Action)
- data DocOptions = DocOptions {
- _maxSamples :: Int
- defaultDocOptions :: DocOptions
- data ParamKind
- data Response = Response {
- _respStatus :: Int
- _respTypes :: [MediaType]
- _respBody :: [(Text, MediaType, ByteString)]
- _respHeaders :: [Header]
- combineResponse :: Response -> Response -> Response
- defResponse :: Response
- data Action = Action {
- _authInfo :: [DocAuthentication]
- _captures :: [DocCapture]
- _headers :: [Header]
- _params :: [DocQueryParam]
- _fragment :: Maybe DocFragment
- _notes :: [DocNote]
- _mxParams :: [(String, [DocQueryParam])]
- _rqtypes :: [MediaType]
- _rqbody :: [(Text, MediaType, ByteString)]
- _response :: Response
- combineAction :: Action -> Action -> Action
- defAction :: Action
- single :: Endpoint -> Action -> API
- data ShowContentTypes
- data RenderingOptions = RenderingOptions {}
- defRenderingOptions :: RenderingOptions
- authIntro :: Lens' DocAuthentication String
- authDataRequired :: Lens' DocAuthentication String
- maxSamples :: Iso' DocOptions Int
- apiIntros :: Lens' API [DocIntro]
- apiEndpoints :: Lens' API (HashMap Endpoint Action)
- path :: Lens' Endpoint [String]
- method :: Lens' Endpoint Method
- capSymbol :: Lens' DocCapture String
- capDesc :: Lens' DocCapture String
- paramValues :: Lens' DocQueryParam [String]
- paramName :: Lens' DocQueryParam String
- paramKind :: Lens' DocQueryParam ParamKind
- paramDesc :: Lens' DocQueryParam String
- fragSymbol :: Lens' DocFragment String
- fragDesc :: Lens' DocFragment String
- introTitle :: Lens' DocIntro String
- introBody :: Lens' DocIntro [String]
- noteTitle :: Lens' DocNote String
- noteBody :: Lens' DocNote [String]
- respTypes :: Lens' Response [MediaType]
- respStatus :: Lens' Response Int
- respHeaders :: Lens' Response [Header]
- respBody :: Lens' Response [(Text, MediaType, ByteString)]
- rqtypes :: Lens' Action [MediaType]
- rqbody :: Lens' Action [(Text, MediaType, ByteString)]
- response :: Lens' Action Response
- params :: Lens' Action [DocQueryParam]
- notes :: Lens' Action [DocNote]
- mxParams :: Lens' Action [(String, [DocQueryParam])]
- headers :: Lens' Action [Header]
- fragment :: Lens' Action (Maybe DocFragment)
- captures :: Lens' Action [DocCapture]
- authInfo :: Lens' Action [DocAuthentication]
- responseExamples :: Lens' RenderingOptions ShowContentTypes
- requestExamples :: Lens' RenderingOptions ShowContentTypes
- renderCurlBasePath :: Lens' RenderingOptions (Maybe String)
- notesHeading :: Lens' RenderingOptions (Maybe String)
- docs :: HasDocs api => Proxy api -> API
- docsWithOptions :: HasDocs api => Proxy api -> DocOptions -> API
- extraInfo :: (IsIn endpoint api, HasLink endpoint, HasDocs endpoint) => Proxy endpoint -> Action -> ExtraInfo api
- docsWith :: HasDocs api => DocOptions -> [DocIntro] -> ExtraInfo api -> Proxy api -> API
- docsWithIntros :: HasDocs api => [DocIntro] -> Proxy api -> API
- class HasDocs api where
- class ToSample a where
- toSample :: forall a. ToSample a => Proxy a -> Maybe a
- noSamples :: [(Text, a)]
- singleSample :: a -> [(Text, a)]
- samples :: [a] -> [(Text, a)]
- defaultSamples :: forall a. (Generic a, GToSample (Rep a)) => Proxy a -> [(Text, a)]
- class GToSample t where
- gtoSamples :: proxy t -> [(Text, t x)]
- class AllHeaderSamples ls where
- allHeaderToSample :: Proxy ls -> [Header]
- sampleByteString :: forall ct cts a. (ToSample a, AllMimeRender (ct ': cts) a) => Proxy (ct ': cts) -> Proxy a -> [(MediaType, ByteString)]
- sampleByteStrings :: forall ct cts a. (ToSample a, AllMimeRender (ct ': cts) a) => Proxy (ct ': cts) -> Proxy a -> [(Text, MediaType, ByteString)]
- class ToParam t where
- toParam :: Proxy t -> DocQueryParam
- class ToCapture c where
- toCapture :: Proxy c -> DocCapture
- class ToAuthInfo a where
- toAuthInfo :: Proxy a -> DocAuthentication
- class ToFragment t where
- toFragment :: Proxy t -> DocFragment
- markdown :: API -> String
- markdownWith :: RenderingOptions -> API -> String
Documentation
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 .~ HTTP.methodPost
"POST" /foo
Instances
Generic Endpoint Source # | |
Show Endpoint Source # | |
Eq Endpoint Source # | |
Ord Endpoint Source # | |
Defined in Servant.Docs.Internal | |
Hashable Endpoint Source # | |
type Rep Endpoint Source # | |
Defined in Servant.Docs.Internal type Rep Endpoint = D1 ('MetaData "Endpoint" "Servant.Docs.Internal" "servant-docs-0.13-7iUN6xvRo5667FDUPGay7C" 'False) (C1 ('MetaCons "Endpoint" 'PrefixI 'True) (S1 ('MetaSel ('Just "_path") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [String]) :*: S1 ('MetaSel ('Just "_method") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Method))) |
defEndpoint :: Endpoint Source #
An Endpoint
whose path is `"/"` and whose method is GET
Here's how you can modify it:
>>>
defEndpoint
"GET" /
>>>
defEndpoint & path <>~ ["foo"]
"GET" /foo
>>>
defEndpoint & path <>~ ["foo"] & method .~ HTTP.methodPost
"POST" /foo
Our API documentation type, a product of top-level information and a good
old hashmap from Endpoint
to Action
API | |
|
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 | |
|
Instances
Show DocCapture Source # | |
Defined in Servant.Docs.Internal showsPrec :: Int -> DocCapture -> ShowS # show :: DocCapture -> String # showList :: [DocCapture] -> ShowS # | |
Eq DocCapture Source # | |
Defined in Servant.Docs.Internal (==) :: DocCapture -> DocCapture -> Bool # (/=) :: DocCapture -> DocCapture -> Bool # | |
Ord DocCapture Source # | |
Defined in Servant.Docs.Internal compare :: DocCapture -> DocCapture -> Ordering # (<) :: DocCapture -> DocCapture -> Bool # (<=) :: DocCapture -> DocCapture -> Bool # (>) :: DocCapture -> DocCapture -> Bool # (>=) :: DocCapture -> DocCapture -> Bool # max :: DocCapture -> DocCapture -> DocCapture # min :: DocCapture -> DocCapture -> DocCapture # |
data DocQueryParam Source #
A type to represent a GET (or other possible Method
)
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 | |
|
Instances
Show DocQueryParam Source # | |
Defined in Servant.Docs.Internal showsPrec :: Int -> DocQueryParam -> ShowS # show :: DocQueryParam -> String # showList :: [DocQueryParam] -> ShowS # | |
Eq DocQueryParam Source # | |
Defined in Servant.Docs.Internal (==) :: DocQueryParam -> DocQueryParam -> Bool # (/=) :: DocQueryParam -> DocQueryParam -> Bool # | |
Ord DocQueryParam Source # | |
Defined in Servant.Docs.Internal compare :: DocQueryParam -> DocQueryParam -> Ordering # (<) :: DocQueryParam -> DocQueryParam -> Bool # (<=) :: DocQueryParam -> DocQueryParam -> Bool # (>) :: DocQueryParam -> DocQueryParam -> Bool # (>=) :: DocQueryParam -> DocQueryParam -> Bool # max :: DocQueryParam -> DocQueryParam -> DocQueryParam # min :: DocQueryParam -> DocQueryParam -> DocQueryParam # |
data DocFragment Source #
A type to represent fragment. Holds the name of the fragment and its description.
Write a ToFragment
instance for your fragment types.
Instances
Show DocFragment Source # | |
Defined in Servant.Docs.Internal showsPrec :: Int -> DocFragment -> ShowS # show :: DocFragment -> String # showList :: [DocFragment] -> ShowS # | |
Eq DocFragment Source # | |
Defined in Servant.Docs.Internal (==) :: DocFragment -> DocFragment -> Bool # (/=) :: DocFragment -> DocFragment -> Bool # | |
Ord DocFragment Source # | |
Defined in Servant.Docs.Internal compare :: DocFragment -> DocFragment -> Ordering # (<) :: DocFragment -> DocFragment -> Bool # (<=) :: DocFragment -> DocFragment -> Bool # (>) :: DocFragment -> DocFragment -> Bool # (>=) :: DocFragment -> DocFragment -> Bool # max :: DocFragment -> DocFragment -> DocFragment # min :: DocFragment -> DocFragment -> DocFragment # |
combineFragment :: Maybe DocFragment -> Maybe DocFragment -> Maybe DocFragment Source #
There should be at most one Fragment
per API endpoint.
So here we are keeping the first occurrence.
An introductory paragraph for your documentation. You can pass these to
docsWithIntros
.
DocIntro | |
|
data DocAuthentication Source #
A type to represent Authentication information about an endpoint.
Instances
Show DocAuthentication Source # | |
Defined in Servant.Docs.Internal showsPrec :: Int -> DocAuthentication -> ShowS # show :: DocAuthentication -> String # showList :: [DocAuthentication] -> ShowS # | |
Eq DocAuthentication Source # | |
Defined in Servant.Docs.Internal (==) :: DocAuthentication -> DocAuthentication -> Bool # (/=) :: DocAuthentication -> DocAuthentication -> Bool # | |
Ord DocAuthentication Source # | |
Defined in Servant.Docs.Internal compare :: DocAuthentication -> DocAuthentication -> Ordering # (<) :: DocAuthentication -> DocAuthentication -> Bool # (<=) :: DocAuthentication -> DocAuthentication -> Bool # (>) :: DocAuthentication -> DocAuthentication -> Bool # (>=) :: DocAuthentication -> DocAuthentication -> Bool # max :: DocAuthentication -> DocAuthentication -> DocAuthentication # min :: DocAuthentication -> DocAuthentication -> DocAuthentication # |
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 | |
|
newtype ExtraInfo api 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.
data DocOptions Source #
Documentation options.
DocOptions | |
|
Instances
Show DocOptions Source # | |
Defined in Servant.Docs.Internal showsPrec :: Int -> DocOptions -> ShowS # show :: DocOptions -> String # showList :: [DocOptions] -> ShowS # |
defaultDocOptions :: DocOptions Source #
Default documentation options.
Type of GET (or other Method
) 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 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 four lenses.
>>>
defResponse
Response {_respStatus = 200, _respTypes = [], _respBody = [], _respHeaders = []}
>>>
defResponse & respStatus .~ 204 & respBody .~ [("If everything goes well", "application/json", "{ \"status\": \"ok\" }")]
Response {_respStatus = 204, _respTypes = [], _respBody = [("If everything goes well",application/json,"{ \"status\": \"ok\" }")], _respHeaders = []}
Response | |
|
combineResponse :: Response -> Response -> Response Source #
Combine two Responses, we can't make a monoid because merging Status breaks the laws.
As such, we invent a non-commutative, left associative operation
combineResponse
to mush two together taking the status from the very left.
defResponse :: Response Source #
Default response: status code 200, no response body.
Can be tweaked with four lenses.
>>>
defResponse
Response {_respStatus = 200, _respTypes = [], _respBody = [], _respHeaders = []}
>>>
defResponse & respStatus .~ 204
Response {_respStatus = 204, _respTypes = [], _respBody = [], _respHeaders = []}
A datatype that represents everything that can happen at an endpoint, with its lenses:
- List of captures (
captures
) - List of GET (or other
Method
) 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.
Action | |
|
combineAction :: Action -> Action -> Action Source #
Combine two Actions, we can't make a monoid as merging Response breaks the laws.
As such, we invent a non-commutative, left associative operation
combineAction
to mush two together taking the response from the very left.
Default Action
. Has no captures
, no query params
, expects
no request body (rqbody
) and the typical response is defResponse
.
Tweakable with lenses.
>>>
defAction
Action {_authInfo = [], _captures = [], _headers = [], _params = [], _fragment = Nothing, _notes = [], _mxParams = [], _rqtypes = [], _rqbody = [], _response = Response {_respStatus = 200, _respTypes = [], _respBody = [], _respHeaders = []}}
>>>
defAction & response.respStatus .~ 201
Action {_authInfo = [], _captures = [], _headers = [], _params = [], _fragment = Nothing, _notes = [], _mxParams = [], _rqtypes = [], _rqbody = [], _response = Response {_respStatus = 201, _respTypes = [], _respBody = [], _respHeaders = []}}
data ShowContentTypes Source #
How many content-types for each example should be shown?
Since: 0.11.1
AllContentTypes | For each example, show each content type. |
FirstContentType | For each example, show only one content type. |
Instances
data RenderingOptions Source #
Customise how an API
is converted into documentation.
Since: 0.11.1
RenderingOptions | |
|
Instances
Show RenderingOptions Source # | |
Defined in Servant.Docs.Internal showsPrec :: Int -> RenderingOptions -> ShowS # show :: RenderingOptions -> String # showList :: [RenderingOptions] -> ShowS # |
defRenderingOptions :: RenderingOptions Source #
Default API generation options.
All content types are shown for both requestExamples
and
responseExamples
; notesHeading
is set to Nothing
(i.e. un-grouped).
Since: 0.11.1
docs :: HasDocs api => Proxy api -> API Source #
Generate the docs for a given API that implements HasDocs
. This is the
default way to create documentation.
docs == docsWithOptions defaultDocOptions
docsWithOptions :: HasDocs api => Proxy api -> DocOptions -> API Source #
Generate the docs for a given API that implements HasDocs
.
extraInfo :: (IsIn endpoint api, HasLink endpoint, HasDocs endpoint) => Proxy endpoint -> Action -> ExtraInfo api Source #
Create an ExtraInfo
that is guaranteed 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 <>~ [("X-Num-Unicorns", 1)] & notes <>~ [ DocNote "Title" ["This is some text"] , DocNote "Second section" ["And some more"] ]
docsWith :: HasDocs api => DocOptions -> [DocIntro] -> ExtraInfo api -> Proxy api -> 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 api => [DocIntro] -> Proxy api -> API Source #
Generate the docs for a given API that implements HasDocs
with any
number of introduction(s)
class HasDocs api where Source #
The class that abstracts away the impact of API combinators on documentation generation.
Instances
class ToSample a 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 where toSamples _ = singleSample 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 ErrorMessage
) that explains when you're supposed to
get the corresponding response.
Nothing
Instances
toSample :: forall a. ToSample a => Proxy a -> Maybe a Source #
Sample input or output (if there is at least one).
singleSample :: a -> [(Text, a)] Source #
Single sample without description.
defaultSamples :: forall a. (Generic a, GToSample (Rep a)) => Proxy a -> [(Text, a)] Source #
Default sample Generic-based inputs/outputs.
class GToSample t where Source #
for Generics.ToSample
Note: we use combinators from Universe.Data.Helpers for more productive sample generation.
gtoSamples :: proxy t -> [(Text, t x)] Source #
Instances
GToSample (U1 :: k -> Type) Source # | |
Defined in Servant.Docs.Internal | |
GToSample (V1 :: k -> Type) Source # | |
Defined in Servant.Docs.Internal | |
(GToSample p, GToSample q) => GToSample (p :*: q :: k -> Type) Source # | |
Defined in Servant.Docs.Internal | |
(GToSample p, GToSample q) => GToSample (p :+: q :: k -> Type) Source # | |
Defined in Servant.Docs.Internal | |
ToSample a => GToSample (K1 i a :: k -> Type) Source # | |
Defined in Servant.Docs.Internal | |
GToSample f => GToSample (M1 i a f :: k -> Type) Source # | |
Defined in Servant.Docs.Internal |
class AllHeaderSamples ls where Source #
allHeaderToSample :: Proxy ls -> [Header] Source #
Instances
AllHeaderSamples ('[] :: [k]) Source # | |
Defined in Servant.Docs.Internal allHeaderToSample :: Proxy '[] -> [Header] Source # | |
(ToHttpApiData l, AllHeaderSamples ls, ToSample l, KnownSymbol h) => AllHeaderSamples (Header h l ': ls :: [Type]) Source # | |
Defined in Servant.Docs.Internal |
sampleByteString :: forall ct cts a. (ToSample a, AllMimeRender (ct ': cts) a) => Proxy (ct ': cts) -> Proxy a -> [(MediaType, ByteString)] Source #
Synthesise a sample value of a type, encoded in the specified media types.
sampleByteStrings :: forall ct cts a. (ToSample a, AllMimeRender (ct ': cts) a) => Proxy (ct ': cts) -> Proxy a -> [(Text, MediaType, ByteString)] Source #
Synthesise a list of sample values of a particular type, encoded in the specified media types.
class ToParam t where Source #
The class that helps us automatically get documentation for GET
(or other Method
) parameters.
Example of an instance:
instance ToParam (QueryParam' mods "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 #
class ToAuthInfo a where Source #
The class that helps us get documentation for authenticated endpoints
toAuthInfo :: Proxy a -> DocAuthentication Source #
class ToFragment t where Source #
The class that helps us get documentation for URL fragments.
Example of an instance:
instance ToFragment (Fragment a) where toFragment _ = DocFragment "fragment" "fragment description"
toFragment :: Proxy t -> DocFragment Source #
markdown :: API -> String Source #
Generate documentation in Markdown format for
the given API
.
This is equivalent to
.markdownWith
defRenderingOptions
markdownWith :: RenderingOptions -> API -> String Source #
Generate documentation in Markdown format for
the given API
using the specified options.
These options allow you to customise aspects such as:
- Choose how many content-types for each request body example are
shown with
requestExamples
. - Choose how many content-types for each response body example
are shown with
responseExamples
.
For example, to only show the first content-type of each example:
markdownWith (defRenderingOptions
&requestExamples
.~
FirstContentType
&responseExamples
.~
FirstContentType
) myAPI
Since: 0.11.1
Instances
>>>
:set -XOverloadedStrings