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

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

Servant.RawM.Internal.API

Description

 
Synopsis

Documentation

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) Source #

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) :: Type #

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 :: Type) Source #

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 :: Type) context Source #

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 :: Type #

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) Source # 
Instance details

Defined in Servant.RawM.Internal.Client

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

Defined in Servant.RawM.Internal.Server

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

data FileServer Source #

Used by RawM as a phantom type.

Instances
HasDocs FileServer Source #

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

Instance details

Defined in Servant.RawM.Internal.Docs