servant-docs-0.12: generate API docs for your servant webservice
Safe Haskell None
Language Haskell2010

Servant.Docs.Internal

Contents

Synopsis

Documentation

data Endpoint Source #

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

Instances details
Eq Endpoint Source #
Instance details

Defined in Servant.Docs.Internal

Ord Endpoint Source #
Instance details

Defined in Servant.Docs.Internal

Show Endpoint Source #
Instance details

Defined in Servant.Docs.Internal

Generic Endpoint Source #
Instance details

Defined in Servant.Docs.Internal

Hashable Endpoint Source #
Instance details

Defined in Servant.Docs.Internal

type Rep Endpoint Source #
Instance details

Defined in Servant.Docs.Internal

showPath :: [ String ] -> String Source #

Render a path as a / -delimited string

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

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.

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.

defaultDocOptions :: DocOptions Source #

Default documentation options.

data Response Source #

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 = []}

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 = []}

data Action Source #

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.

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.

defAction :: Action Source #

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 = []}}

single :: Endpoint -> Action -> API Source #

Create an API that's comprised of a single endpoint. API is a Monoid , so combine multiple endpoints with mappend or <> .

data ShowContentTypes Source #

How many content-types for each example should be shown?

Since: 0.11.1

Constructors

AllContentTypes

For each example, show each content type.

FirstContentType

For each example, show only one content type.

Instances

Instances details
Bounded ShowContentTypes Source #
Instance details

Defined in Servant.Docs.Internal

Enum ShowContentTypes Source #
Instance details

Defined in Servant.Docs.Internal

Eq ShowContentTypes Source #
Instance details

Defined in Servant.Docs.Internal

Ord ShowContentTypes Source #
Instance details

Defined in Servant.Docs.Internal

Read ShowContentTypes Source #
Instance details

Defined in Servant.Docs.Internal

Show ShowContentTypes Source #
Instance details

Defined in Servant.Docs.Internal

data RenderingOptions Source #

Customise how an API is converted into documentation.

Since: 0.11.1

Constructors

RenderingOptions

Fields

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 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

Instances details
HasDocs Raw Source #
Instance details

Defined in Servant.Docs.Internal

HasDocs EmptyAPI Source #

The generated docs for EmptyAPI are empty.

Instance details

Defined in Servant.Docs.Internal

ReflectMethod method => HasDocs ( NoContentVerb method :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

( HasDocs a, HasDocs b) => HasDocs (a :<|> b :: Type ) Source #

The generated docs for a :<|> b just appends the docs for a with the docs for b .

Instance details

Defined in Servant.Docs.Internal

HasDocs api => HasDocs ( WithNamedContext name context api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

HasDocs api => HasDocs ( HttpVersion :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

( HasDocs api, Accept ctype) => HasDocs ( StreamBody' mods framing ctype a :> api :: Type ) Source #

TODO: this instance is incomplete.

Instance details

Defined in Servant.Docs.Internal

( ToSample a, AllMimeRender (ct ': cts) a, HasDocs api) => HasDocs ( ReqBody' mods (ct ': cts) a :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

HasDocs api => HasDocs ( RemoteHost :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

( KnownSymbol sym, ToParam ( QueryParam' mods sym a), HasDocs api) => HasDocs ( QueryParam' mods sym a :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

( KnownSymbol sym, ToParam ( QueryParams sym a), HasDocs api) => HasDocs ( QueryParams sym a :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

( KnownSymbol sym, ToParam ( QueryFlag sym), HasDocs api) => HasDocs ( QueryFlag sym :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

( ToHttpApiData a, ToSample a, KnownSymbol sym, HasDocs api) => HasDocs ( Header' mods sym a :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

HasDocs api => HasDocs ( IsSecure :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

( ToFragment ( Fragment a), HasDocs api) => HasDocs ( Fragment a :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

( KnownSymbol desc, HasDocs api) => HasDocs ( Summary desc :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

( KnownSymbol desc, HasDocs api) => HasDocs ( Description desc :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

HasDocs ( Capture' mods sym a :> api) => HasDocs ( Capture' (mod ': mods) sym a :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

( KnownSymbol descr, KnownSymbol sym, HasDocs api) => HasDocs ( Capture' ( Description descr ': mods) sym a :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

( KnownSymbol sym, ToCapture ( Capture sym a), HasDocs api) => HasDocs ( Capture' ('[] :: [ Type ]) sym a :> api :: Type ) Source #

"books" :> Capture "isbn" Text will appear as books :isbn in the docs.

Instance details

Defined in Servant.Docs.Internal

( KnownSymbol sym, ToCapture ( CaptureAll sym a), HasDocs sublayout) => HasDocs ( CaptureAll sym a :> sublayout :: Type ) Source #

"books" :> CaptureAll "isbn" Text will appear as books :isbn in the docs.

Instance details

Defined in Servant.Docs.Internal

( ToAuthInfo ( BasicAuth realm usr), HasDocs api) => HasDocs ( BasicAuth realm usr :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

HasDocs api => HasDocs ( Vault :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

( KnownSymbol path, HasDocs api) => HasDocs (path :> api :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

( ToSample a, AllMimeRender (ct ': cts) a, KnownNat status, ReflectMethod method) => HasDocs ( Verb method status (ct ': cts) a :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

docsFor :: Proxy ( Verb method status (ct ': cts) a) -> ( Endpoint , Action ) -> DocOptions -> API Source #

( ToSample a, AllMimeRender (ct ': cts) a, KnownNat status, ReflectMethod method, AllHeaderSamples ls, GetHeaders ( HList ls)) => HasDocs ( Verb method status (ct ': cts) ( Headers ls a) :: Type ) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

docsFor :: Proxy ( Verb method status (ct ': cts) ( Headers ls a)) -> ( Endpoint , Action ) -> DocOptions -> API Source #

( Accept ct, KnownNat status, ReflectMethod method) => HasDocs ( Stream method status framing ct a :: Type ) Source #

TODO: mention the endpoint is streaming, its framing strategy

Also there are no samples.

TODO: AcceptFraming for content-type

Instance details

Defined in Servant.Docs.Internal

Methods

docsFor :: Proxy ( Stream method status framing ct a) -> ( Endpoint , Action ) -> DocOptions -> API Source #

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 Text ) that explains when you're supposed to get the corresponding response.

Minimal complete definition

Nothing

Instances

Instances details
ToSample Bool Source #
Instance details

Defined in Servant.Docs.Internal

ToSample Ordering Source #
Instance details

Defined in Servant.Docs.Internal

ToSample All Source #
Instance details

Defined in Servant.Docs.Internal

ToSample Any Source #
Instance details

Defined in Servant.Docs.Internal

ToSample NoContent Source #
Instance details

Defined in Servant.Docs.Internal

ToSample a => ToSample [a] Source #
Instance details

Defined in Servant.Docs.Internal

Methods

toSamples :: Proxy [a] -> [( Text , [a])] Source #

ToSample a => ToSample ( Maybe a) Source #
Instance details

Defined in Servant.Docs.Internal

ToSample a => ToSample ( ZipList a) Source #
Instance details

Defined in Servant.Docs.Internal

ToSample a => ToSample ( First a) Source #
Instance details

Defined in Servant.Docs.Internal

ToSample a => ToSample ( Last a) Source #
Instance details

Defined in Servant.Docs.Internal

ToSample a => ToSample ( Dual a) Source #
Instance details

Defined in Servant.Docs.Internal

ToSample a => ToSample ( Sum a) Source #
Instance details

Defined in Servant.Docs.Internal

ToSample a => ToSample ( Product a) Source #
Instance details

Defined in Servant.Docs.Internal

ToSample a => ToSample ( NonEmpty a) Source #
Instance details

Defined in Servant.Docs.Internal

( ToSample a, ToSample b) => ToSample ( Either a b) Source #
Instance details

Defined in Servant.Docs.Internal

( ToSample a, ToSample b) => ToSample (a, b) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

toSamples :: Proxy (a, b) -> [( Text , (a, b))] Source #

( ToSample a, ToSample b, ToSample c) => ToSample (a, b, c) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

toSamples :: Proxy (a, b, c) -> [( Text , (a, b, c))] Source #

ToSample a => ToSample ( Const a b) Source #
Instance details

Defined in Servant.Docs.Internal

( ToSample a, ToSample b, ToSample c, ToSample d) => ToSample (a, b, c, d) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

toSamples :: Proxy (a, b, c, d) -> [( Text , (a, b, c, d))] Source #

( ToSample a, ToSample b, ToSample c, ToSample d, ToSample e) => ToSample (a, b, c, d, e) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

toSamples :: Proxy (a, b, c, d, e) -> [( Text , (a, b, c, d, e))] Source #

( ToSample a, ToSample b, ToSample c, ToSample d, ToSample e, ToSample f) => ToSample (a, b, c, d, e, f) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

toSamples :: Proxy (a, b, c, d, e, f) -> [( Text , (a, b, c, d, e, f))] Source #

( ToSample a, ToSample b, ToSample c, ToSample d, ToSample e, ToSample f, ToSample g) => ToSample (a, b, c, d, e, f, g) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

toSamples :: Proxy (a, b, c, d, e, f, g) -> [( Text , (a, b, c, d, e, f, g))] Source #

toSample :: forall a. ToSample a => Proxy a -> Maybe a Source #

Sample input or output (if there is at least one).

noSamples :: [( Text , a)] Source #

No samples.

singleSample :: a -> [( Text , a)] Source #

Single sample without description.

samples :: [a] -> [( Text , a)] Source #

Samples without documentation.

defaultSamples :: forall a. ( Generic a, GToSample ( Rep a)) => Proxy a -> [( Text , a)] Source #

Default sample Generic-based inputs/outputs.

class GToSample t where Source #

ToSample for Generics.

Note: we use combinators from Universe.Data.Helpers for more productive sample generation.

Methods

gtoSamples :: proxy t -> [( Text , t x)] Source #

Instances

Instances details
GToSample ( V1 :: k -> Type ) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

gtoSamples :: forall proxy (x :: k0). proxy V1 -> [( Text , V1 x)] Source #

GToSample ( U1 :: k -> Type ) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

gtoSamples :: forall proxy (x :: k0). proxy U1 -> [( Text , U1 x)] Source #

( GToSample p, GToSample q) => GToSample (p :+: q :: k -> Type ) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

gtoSamples :: forall proxy (x :: k0). proxy (p :+: q) -> [( Text , (p :+: q) x)] Source #

( GToSample p, GToSample q) => GToSample (p :*: q :: k -> Type ) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

gtoSamples :: forall proxy (x :: k0). proxy (p :*: q) -> [( Text , (p :*: q) x)] Source #

ToSample a => GToSample ( K1 i a :: k -> Type ) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

gtoSamples :: forall proxy (x :: k0). proxy ( K1 i a) -> [( Text , K1 i a x)] Source #

GToSample f => GToSample ( M1 i a f :: k -> Type ) Source #
Instance details

Defined in Servant.Docs.Internal

Methods

gtoSamples :: forall proxy (x :: k0). proxy ( M1 i a f) -> [( Text , M1 i a f x)] Source #

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."

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"

class ToAuthInfo a where Source #

The class that helps us get documentation for authenticated endpoints

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"

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