servant-docs-simple-0.3.0.0: Generate endpoints overview for Servant API

Safe HaskellNone
LanguageHaskell2010

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 "()"
                                                                  )
                                                                ]))
                                           )
                                         ]))
                    )])
Synopsis

Documentation

class HasParsableEndpoint e where Source #

Folds an api endpoint into documentation

Methods

parseEndpoint Source #

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
(HasParsableEndpoint b, Typeable ct, Typeable typ) => HasParsableEndpoint (StreamBody' m ct typ :> b :: Type) Source #

Stream body documentation

Instance details

Defined in Servant.Docs.Simple.Parse

HasParsableEndpoint b => HasParsableEndpoint (HttpVersion :> b :: Type) Source #

Request HttpVersion documentation

Instance details

Defined in Servant.Docs.Simple.Parse

(HasParsableEndpoint b, Typeable ct, Typeable typ) => HasParsableEndpoint (ReqBody' m ct typ :> b :: Type) Source #

Request body documentation

Instance details

Defined in Servant.Docs.Simple.Parse

HasParsableEndpoint b => HasParsableEndpoint (RemoteHost :> b :: Type) Source #

Request Remote host documentation

Instance details

Defined in Servant.Docs.Simple.Parse

(HasParsableEndpoint b, KnownSymbol param, Typeable typ) => HasParsableEndpoint (QueryParam' m param typ :> b :: Type) Source #

Query param documentation

Instance details

Defined in Servant.Docs.Simple.Parse

(HasParsableEndpoint b, KnownSymbol param, Typeable typ) => HasParsableEndpoint (QueryParams param typ :> b :: Type) Source #

Query params documentation

Instance details

Defined in Servant.Docs.Simple.Parse

(HasParsableEndpoint b, KnownSymbol param) => HasParsableEndpoint (QueryFlag param :> b :: Type) Source #

Query flag documentation

Instance details

Defined in Servant.Docs.Simple.Parse

(HasParsableEndpoint b, KnownSymbol ct, Typeable typ) => HasParsableEndpoint (Header' m ct typ :> b :: Type) Source #

Request header documentation

Instance details

Defined in Servant.Docs.Simple.Parse

HasParsableEndpoint b => HasParsableEndpoint (IsSecure :> b :: Type) Source #

IsSecure documentation

Instance details

Defined in Servant.Docs.Simple.Parse

(HasParsableEndpoint b, KnownSymbol token) => HasParsableEndpoint (AuthProtect token :> b :: Type) Source #

Authentication documentation

Instance details

Defined in Servant.Docs.Simple.Parse

(HasParsableEndpoint b, KnownSymbol s) => HasParsableEndpoint (Summary s :> b :: Type) Source #

Summary documentation

Instance details

Defined in Servant.Docs.Simple.Parse

(HasParsableEndpoint b, KnownSymbol desc) => HasParsableEndpoint (Description desc :> b :: Type) Source #

Description documentation

Instance details

Defined in Servant.Docs.Simple.Parse

(HasParsableEndpoint b, KnownSymbol dRoute, Typeable t) => HasParsableEndpoint (Capture' m dRoute t :> b :: Type) Source #

Capture documentation

Instance details

Defined in Servant.Docs.Simple.Parse

(HasParsableEndpoint b, KnownSymbol dRoute, Typeable t) => HasParsableEndpoint (CaptureAll dRoute t :> b :: Type) Source #

CaptureAll documentation

Instance details

Defined in Servant.Docs.Simple.Parse

(HasParsableEndpoint b, KnownSymbol realm, Typeable a) => HasParsableEndpoint (BasicAuth realm a :> b :: Type) Source #

Basic authentication documentation

Instance details

Defined in Servant.Docs.Simple.Parse

HasParsableEndpoint b => HasParsableEndpoint (Vault :> b :: Type) Source #

Vault documentation

Instance details

Defined in Servant.Docs.Simple.Parse

(HasParsableEndpoint b, KnownSymbol route) => HasParsableEndpoint (route :> b :: Type) Source #

Static route documentation

Instance details

Defined in Servant.Docs.Simple.Parse

(Typeable m, Typeable ct, Typeable typ) => HasParsableEndpoint (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

Instance details

Defined in Servant.Docs.Simple.Parse

class HasParsableApi api where Source #

Flattens API into type level list of Endpoints

Instances
HasCollatable (Endpoints a) => HasParsableApi (a :: Type) Source #

If the flattened API can be collated into documentation, it is parsable

Instance details

Defined in Servant.Docs.Simple.Parse

HasParsableApi EmptyAPI Source #

Empty APIs should have no documentation

Instance details

Defined in Servant.Docs.Simple.Parse

symbolVal' :: forall n. KnownSymbol n => Text Source #

Convert symbol to Text

toDetails :: [(Text, Details)] -> Details Source #

Convert parameter-value pairs to Details type

typeText :: forall a. Typeable a => Text Source #

Convert types to Text