servant-rawm-1.0.0.0: Embed a raw 'Application' in a Servant API

CopyrightDennis Gosnell 2017
LicenseBSD3
MaintainerDennis Gosnell (cdep.illabout@gmail.com) Krasjet (nil.krjst@gmail.com)
Safe HaskellNone
LanguageHaskell2010

Servant.RawM

Contents

Description

This module defines the RawM type that allows you to embed a WAI Application in your Servant API.

It is similar to Raw provided by Servant, but there is one big difference. RawM allows you to use monadic effects to create the Application.

What does this look like in practice? The following is an example of using RawM:

  import Servant.RawM.Server

  type Api = "serve-directory-example" :> RawM

  serverRoot :: ServerT Api (ReaderT FilePath IO)
  serverRoot = rawEndpoint

  rawEndpoint :: ReaderT FilePath IO Application
  rawEndpoint = do
    filePath <- ask
    serveDirectoryWebApp filePath

  apiProxy :: Proxy Api
  apiProxy = Proxy

  app :: FilePath -> Application
  app filePath =
    serve apiProxy apiServer
    where
      apiServer :: Server Api
      apiServer = hoistServer apiProxy transformation serverRoot

      transformation :: ReaderT FilePath IO a -> Handler a
      transformation readerT = liftIO $ runReaderT readerT filePath

Notice how the above rawEndpoint handler is able to get the filePath from the ReaderT. Using Servant's default Raw type, rawEndpoint would have to be written like the following:

  type Api' = "serve-directory-example" :> Raw

  serverRoot' :: ServerT Api' (ReaderT FilePath IO)
  serverRoot' = rawEndpoint'

  rawEndpoint' :: Tagged (ReaderT FilePath IO) Application
  rawEndpoint' = ...

rawEndpoint' does not have access to the ReaderT monad, so there is no way to get the directory path.

RawM solves this problem by allowing the Application to be produced monadically.

There is an example in the source code repository that shows a more in-depth server, client, and documentation.

After servant-rawm 1.0.0.0, the implementations for RawM server, client, and documentation generator are divided into three packages: servant-rawm-server, servant-rawm-client, and servant-rawm-docs to avoid pulling in unnecessary dependencies. This module is re-exported in Servant.RawM.Server, Servant.RawM.Client, and Servant.RawM.Docs, so you don't need to import this module explicitly. Import the corresponding implementation instead.

Synopsis

RawM API parameter

type RawM = RawM' FileServer Source #

Specialization of RawM' to FileServer. This can be used if you are using serveDirectoryWebApp, serveDirectoryFileServer, etc.

data RawM' serverType Source #

This is a type to use to define a Servant API. It signifies a route that allows embedding of a WAI Application. It is similar to Raw, but it has a HasServer instance that allows embedding of monadic effects. This should be more convenient than Raw.

The phantom type serverType is used for defining the HasDocs instance. There are instances for HasClient and HasServer for RawM' with a polymorphic phantom type, but there is only a HasDocs instance specified for RawM' FileServer. This allows the end-user to easily create a HasDocs instance for a custom Application.

Instances
HasLink (RawM' st :: Type) Source # 
Instance details

Defined in Servant.RawM

Associated Types

type MkLink (RawM' st) a :: Type #

Methods

toLink :: (Link -> a) -> Proxy (RawM' st) -> Link -> MkLink (RawM' st) a #

type MkLink (RawM' st :: Type) a Source # 
Instance details

Defined in Servant.RawM

type MkLink (RawM' st :: Type) a = a

data FileServer Source #

Used by RawM as a phantom type.