| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Servant.Docs.Internal
Contents
- data Method
- 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 DocIntro = DocIntro {
- _introTitle :: String
- _introBody :: [String]
- data DocNote = DocNote {
- _noteTitle :: String
- _noteBody :: [String]
- newtype ExtraInfo layout = ExtraInfo (HashMap Endpoint Action)
- data ParamKind
- data Response = Response {
- _respStatus :: Int
- _respTypes :: [MediaType]
- _respBody :: [(Text, MediaType, ByteString)]
- _respHeaders :: [Header]
- defResponse :: Response
- data Action = Action {
- _captures :: [DocCapture]
- _headers :: [Text]
- _params :: [DocQueryParam]
- _notes :: [DocNote]
- _mxParams :: [(String, [DocQueryParam])]
- _rqtypes :: [MediaType]
- _rqbody :: [(MediaType, ByteString)]
- _response :: Response
- combineAction :: Action -> Action -> Action
- defAction :: Action
- single :: Endpoint -> Action -> API
- 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
- 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 [(MediaType, ByteString)]
- response :: Lens' Action Response
- params :: Lens' Action [DocQueryParam]
- notes :: Lens' Action [DocNote]
- mxParams :: Lens' Action [(String, [DocQueryParam])]
- headers :: Lens' Action [Text]
- captures :: Lens' Action [DocCapture]
- docs :: HasDocs layout => Proxy layout -> API
- type family IsIn endpoint api :: Constraint
- extraInfo :: (IsIn endpoint layout, HasLink endpoint, HasDocs endpoint) => Proxy endpoint -> Action -> ExtraInfo layout
- docsWith :: HasDocs layout => [DocIntro] -> ExtraInfo layout -> Proxy layout -> API
- docsWithIntros :: HasDocs layout => [DocIntro] -> Proxy layout -> API
- class HasDocs layout where
- class ToSample a b | a -> b where
- class AllHeaderSamples ls where
- allHeaderToSample :: Proxy ls -> [Header]
- 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 SupportedTypes list where
- supportedTypes :: Proxy list -> [MediaType]
- class ToParam t where
- toParam :: Proxy t -> DocQueryParam
- class ToCapture c where
- toCapture :: Proxy c -> DocCapture
- markdown :: API -> String
Documentation
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.
λ>defEndpointGET / λ>defEndpoint&path<>~["foo"] GET /foo λ>defEndpoint&path<>~["foo"] &method.~DocPOSTPOST /foo
defEndpoint :: Endpoint Source
An Endpoint whose path is `"/"` and whose method is DocGET
Here's how you can modify it:
λ>defEndpointGET / λ>defEndpoint&path<>~["foo"] GET /foo λ>defEndpoint&path<>~["foo"] &method.~DocPOSTPOST /foo
Our API documentation type, a product of top-level information and a good
old hashmap from Endpoint to Action
Constructors
| API | |
Fields
| |
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.
Constructors
| DocCapture | |
Fields
| |
Instances
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
Constructors
| DocQueryParam | |
Fields
| |
Instances
An introductory paragraph for your documentation. You can pass these to
docsWithIntros.
Constructors
| DocIntro | |
Fields
| |
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.
Constructors
| DocNote | |
Fields
| |
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.
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 an HTTP response. Has an Int status, a list of
possible MediaTypes, 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\" }")]}Constructors
| Response | |
Fields
| |
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.
Constructors
| Action | |
Fields
| |
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, body and content
types from the very left.
respHeaders :: Lens' Response [Header] Source
params :: Lens' Action [DocQueryParam] Source
captures :: Lens' Action [DocCapture] Source
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.
type family IsIn endpoint api :: Constraint Source
Closed type family, check if endpoint is exactly within API.
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"]
]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)
class HasDocs layout where Source
The class that abstracts away the impact of API combinators on documentation generation.
Instances
| 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) |
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.
class AllHeaderSamples ls where Source
Methods
allHeaderToSample :: Proxy ls -> [Header] Source
Instances
| AllHeaderSamples [k] ([] k) | |
| (ToByteString l, AllHeaderSamples [*] ls, ToSample * l l, KnownSymbol h) => AllHeaderSamples [*] ((:) * (Header h l) ls) |
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.
class SupportedTypes list where Source
Generate a list of MediaType values describing the content types
accepted by an API component.
Methods
supportedTypes :: Proxy list -> [MediaType] Source
Instances
| SupportedTypes ([] *) | |
| (Accept * ctype, SupportedTypes rest) => SupportedTypes ((:) * ctype rest) |
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."Methods
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"
Methods
toCapture :: Proxy c -> DocCapture Source