servant-swagger-ui-0.1.1.2.1.4: Servant swagger ui

Copyright(C) 2016 Oleg Grenrus
LicenseBSD3
MaintainerOleg Grenrus <oleg.grenrus@iki.fi>
Safe HaskellNone
LanguageHaskell2010

Servant.Swagger.UI

Contents

Description

Provides SwaggerUI and corresponding swaggerUIServer to embed swagger ui into the application.

All of UI files are embedded into the binary.

An example:

-- | Actual API.
type BasicAPI = Get '[PlainText, JSON] Text
    :<|> "cat" :> Capture ":name" CatName :> Get '[JSON] Cat

-- | Swagger schema endpoint.
type SwaggerSchemaEndpoint = "swagger.js" :> Get '[JSON] Swagger

-- | Unhabitated new data type, to be able to refer to API type from the API type.
data API

-- | Underlying API type.
--
-- NOTE: place BasicAPI last for it not to override SwaggerSchemaEndpoing and SwaggerUI.
-- If you place BasicAPI first and it has Raw endpoint at root Swagger schema and UI won't work.
type API' = SwaggerSchemaEndpoint
    :<|> SwaggerUI "ui" SwaggerSchemaEndpoint API
    :<|> BasicAPI

-- Optionally we can do:
--
-- type API' = SwaggerSchemaEndpoint
--     :<|> BasicAPI
--
-- type API = SwaggerUI "ui" SwaggerSchemaEndpoint API'
--     :<|> API'

-- Unfortunately we have to write these trivial instances.

instance HasServer API context where
  type ServerT API m = ServerT API' m
  route _ = route (Proxy :: Proxy API')

type instance IsElem' e API = IsElem e API'

server :: Server API
server = pure swaggerDoc
    :<|> swaggerUIServer
    :<|> (pure "Hello World" :<|> catEndpoint)
  where
    catEndpoint name = pure $ Cat name False

Synopsis

Swagger UI API

type SwaggerUI dir endpoint api = dir :> (Get '[HTML] (SwaggerUiHtml endpoint api) :<|> (("index.html" :> Get '[HTML] (SwaggerUiHtml endpoint api)) :<|> Raw)) Source #

Swagger API ui.

swaggerUIServer :: Server (SwaggerUI dir endpoint api) Source #

Serve Swagger UI on /dir using endpoint as Swagger spec source for api.

Internals

data SwaggerUiHtml endpoint api Source #

Index file for swagger ui.

It's configured by the location of swagger schema.

Constructors

SwaggerUiHtml 

Instances

(IsElem endpoint api, HasLink * endpoint, (~) * (MkLink * endpoint) URI) => ToMarkup (SwaggerUiHtml endpoint api) Source # 

Methods

toMarkup :: SwaggerUiHtml endpoint api -> Markup #

preEscapedToMarkup :: SwaggerUiHtml endpoint api -> Markup #