| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Servant.Docs.Simple.Parse
Description
Parse Servant API into documentation
Example script
Generating the intermediate documentation structure
Parsing custom API type combinators
Example of parsing an API
API type
type API = "hello" :> "world" :> Request :> Response type Request = ReqBody '[()] () type Response = Post '[()] ()
Intermediate structure
ApiDocs ( fromList [( "/hello/world",
, Details (fromList ([ ( "RequestBody"
, Details (fromList ([ ( "Format"
, Detail "': * () ('[] *)"
)
, ( "ContentType"
, Detail "()"
)
]))
)
, ( "RequestType"
, Detail "'POST"
)
, ( "Response"
, Details (fromList ([ ( "Format"
, Detail "': * () ('[] *)"
)
, ( "ContentType"
, Detail "()"
)
]))
)
]))
)])Documentation
class HasDocumentApi api where Source #
Folds an api endpoint into documentation
Methods
Arguments
| :: Route | Route documentation |
| -> [(Parameter, Details)] | Everything else documentation |
| -> (Route, OMap Parameter Details) | Generated documentation for the route |
We use this to destructure the API type and convert it into documentation
Instances
| (HasDocumentApi b, Typeable ct, Typeable typ) => HasDocumentApi (StreamBody' m ct typ :> b :: Type) Source # | Stream body documentation |
| HasDocumentApi b => HasDocumentApi (HttpVersion :> b :: Type) Source # | Request HttpVersion documentation |
| (HasDocumentApi b, Typeable ct, Typeable typ) => HasDocumentApi (ReqBody' m ct typ :> b :: Type) Source # | Request body documentation |
| HasDocumentApi b => HasDocumentApi (RemoteHost :> b :: Type) Source # | Request Remote host documentation |
| (HasDocumentApi b, KnownSymbol param, Typeable typ) => HasDocumentApi (QueryParam' m param typ :> b :: Type) Source # | Query param documentation |
| (HasDocumentApi b, KnownSymbol param, Typeable typ) => HasDocumentApi (QueryParams param typ :> b :: Type) Source # | Query params documentation |
| (HasDocumentApi b, KnownSymbol param) => HasDocumentApi (QueryFlag param :> b :: Type) Source # | Query flag documentation |
| (HasDocumentApi b, KnownSymbol ct, Typeable typ) => HasDocumentApi (Header' m ct typ :> b :: Type) Source # | Request header documentation |
| HasDocumentApi b => HasDocumentApi (IsSecure :> b :: Type) Source # | IsSecure documentation |
| (HasDocumentApi b, KnownSymbol token) => HasDocumentApi (AuthProtect token :> b :: Type) Source # | Authentication documentation |
| (HasDocumentApi b, KnownSymbol s) => HasDocumentApi (Summary s :> b :: Type) Source # | Summary documentation |
| (HasDocumentApi b, KnownSymbol desc) => HasDocumentApi (Description desc :> b :: Type) Source # | Description documentation |
| (HasDocumentApi b, KnownSymbol dRoute, Typeable t) => HasDocumentApi (Capture' m dRoute t :> b :: Type) Source # | Capture documentation |
| (HasDocumentApi b, KnownSymbol dRoute, Typeable t) => HasDocumentApi (CaptureAll dRoute t :> b :: Type) Source # | CaptureAll documentation |
| (HasDocumentApi b, KnownSymbol realm, Typeable a) => HasDocumentApi (BasicAuth realm a :> b :: Type) Source # | Basic authentication documentation |
| HasDocumentApi b => HasDocumentApi (Vault :> b :: Type) Source # | Vault documentation |
| (HasDocumentApi b, KnownSymbol route) => HasDocumentApi (route :> b :: Type) Source # | Static route documentation |
| (Typeable m, Typeable ct, Typeable typ) => HasDocumentApi (Verb m s ct typ :: Type) Source # | Response documentation Terminates here as responses are last parts of api endpoints Note that request type information (GET, POST etc...) is contained here |
class HasParsable api where Source #
Flattens API into type level list of Endpoints
Instances
| HasCollatable (Endpoints a) => HasParsable (a :: Type) Source # | If the flattened API can be collated into documentation, it is parsable |
Defined in Servant.Docs.Simple.Parse | |
| HasParsable EmptyAPI Source # | Empty APIs should have no documentation |
Defined in Servant.Docs.Simple.Parse | |
symbolVal' :: forall n. KnownSymbol n => Text Source #
Convert symbol to Text