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

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

Servant.RawM

Contents

Description

This module exposes a 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:

  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.

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
RunClient m => HasClient m (RawM' serverType) #

Creates a client route like the following:

>>> :set -XTypeOperators
>>> import Data.Type.Equality ((:~:)(Refl))
>>> Refl :: Client m (RawM' a) :~: ((Request -> Request) -> m Response)
Refl

This allows modification of the underlying Request to work for any sort of Application.

Check out the example in the source code repository that shows a more in-depth server, client, and documentation.

Instance details

Defined in Servant.RawM.Internal.Client

Associated Types

type Client m (RawM' serverType) :: * #

Methods

clientWithRoute :: Proxy m -> Proxy (RawM' serverType) -> Request -> Client m (RawM' serverType) #

hoistClientMonad :: Proxy m -> Proxy (RawM' serverType) -> (forall x. mon x -> mon' x) -> Client mon (RawM' serverType) -> Client mon' (RawM' serverType) #

HasDocs serverType => HasDocs (RawM' serverType :: *) #

This just defers to the HasDocs instance for the serverType phantom type.

Instance details

Defined in Servant.RawM.Internal.Docs

Methods

docsFor :: Proxy (RawM' serverType) -> (Endpoint, Action) -> DocOptions -> API #

HasServer (RawM' serverType :: *) context #

Creates a server instance like the following:

>>> :set -XTypeOperators
>>> import Data.Type.Equality ((:~:)(Refl))
>>> Refl :: ServerT (RawM' a) m :~: m Application
Refl
Instance details

Defined in Servant.RawM.Internal.Server

Associated Types

type ServerT (RawM' serverType) m :: * #

Methods

route :: Proxy (RawM' serverType) -> Context context -> Delayed env (Server (RawM' serverType)) -> Router env #

hoistServerWithContext :: Proxy (RawM' serverType) -> Proxy context -> (forall x. m x -> n x) -> ServerT (RawM' serverType) m -> ServerT (RawM' serverType) n #

type Client m (RawM' serverType) # 
Instance details

Defined in Servant.RawM.Internal.Client

type Client m (RawM' serverType) = (Request -> Request) -> m Response
type ServerT (RawM' serverType :: *) m # 
Instance details

Defined in Servant.RawM.Internal.Server

type ServerT (RawM' serverType :: *) m = m Application

data FileServer Source #

Used by RawM as a phantom type.

Instances
HasDocs FileServer #

This is a HasDocs instance compatible with the file servers defined in Servant.RawM.Internal.Server.

Instance details

Defined in Servant.RawM.Internal.Docs

Helper functions for writing simple file servers

serveDirectoryWebApp :: Applicative m => FilePath -> ServerT (RawM' serverType) m Source #

Serve anything under the specified directory as a RawM' endpoint.

type MyApi = "static" :> RawM'

server :: ServerT MyApi m
server = serveDirectoryWebApp "/var/www"

would capture any request to /static/<something> and look for <something> under /var/www.

It will do its best to guess the MIME type for that file, based on the extension, and send an appropriate Content-Type header if possible.

If your goal is to serve HTML, CSS and Javascript files that use the rest of the API as a webapp backend, you will most likely not want the static files to be hidden behind a /static/ prefix. In that case, remember to put the serveDirectoryWebApp handler in the last position, because servant will try to match the handlers in order.

Corresponds to the defaultWebAppSettings StaticSettings value.

serveDirectoryWith :: Applicative m => StaticSettings -> ServerT (RawM' serverType) m Source #

Alias for staticApp. Lets you serve a directory with arbitrary StaticSettings. Useful when you want particular settings not covered by the four other variants. This is the most flexible method.