module Mellon.Web.Server.SwaggerAPI
(
SwaggerAPI
, swaggerAPI
, swaggerApp
, swaggerServer
, mellonSwagger
, writeSwaggerJSON
) where
import Control.Lens ((&), (.~), (?~))
import Data.Aeson.Encode.Pretty (encodePretty)
import qualified Data.ByteString.Lazy.Char8 as C8 (writeFile)
import Data.Swagger
(Swagger, URL(..), description, info, license, title, url, version)
import Mellon.Controller (Controller)
import Network.Wai (Application)
import Servant ((:<|>)(..), Proxy(..), Server, serve)
import Servant.Swagger (toSwagger)
import Servant.Swagger.UI (SwaggerSchemaUI, swaggerSchemaUIServer)
import Mellon.Web.Server.API (MellonAPI, mellonAPI, server)
type SwaggerAPI = MellonAPI :<|> SwaggerSchemaUI "swagger-ui" "swagger.json"
swaggerAPI :: Proxy SwaggerAPI
swaggerAPI = Proxy
swaggerServer :: Controller d -> Server SwaggerAPI
swaggerServer cc = server cc :<|> swaggerSchemaUIServer mellonSwagger
swaggerApp :: Controller d -> Application
swaggerApp = serve swaggerAPI . swaggerServer
mellonSwagger :: Swagger
mellonSwagger = toSwagger mellonAPI
& info.title .~ "Mellon API"
& info.version .~ "1.0"
& info.description ?~ "Control physical access devices"
& info.license ?~ ("BSD3" & url ?~ URL "https://opensource.org/licenses/BSD-3-Clause")
writeSwaggerJSON :: IO ()
writeSwaggerJSON = C8.writeFile "swagger.json" (encodePretty mellonSwagger)