servant-server-0.18: A family of combinators for defining webservices APIs and serving them

Safe HaskellNone
LanguageHaskell2010

Servant.Server.Internal

Synopsis

Documentation

type HasServerArrowTypeError a b = (((Text "No instance HasServer (a -> b)." :$$: Text "Maybe you have used '->' instead of ':>' between ") :$$: ShowType a) :$$: Text "and") :$$: ShowType b Source #

type HasServerArrowKindError arr = (Text "Expected something of kind Symbol or *, got: k -> l on the LHS of ':>'." :$$: Text "Maybe you haven't applied enough arguments to") :$$: ShowType arr Source #

type Server api = ServerT api Handler Source #

class HasServer api context where Source #

Associated Types

type ServerT api (m :: * -> *) :: * Source #

Methods

route :: Proxy api -> Context context -> Delayed env (Server api) -> Router env Source #

hoistServerWithContext :: Proxy api -> Proxy context -> (forall x. m x -> n x) -> ServerT api m -> ServerT api n Source #

Instances
HasServer Raw context Source #

Just pass the request to the underlying application and serve its response.

Example:

type MyApi = "images" :> Raw server :: Server MyApi server = serveDirectory "/var/www/images"
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT Raw m :: Type Source #

Methods

route :: Proxy Raw -> Context context -> Delayed env (Server Raw) -> Router env Source #

hoistServerWithContext :: Proxy Raw -> Proxy context -> (forall x. m x -> n x) -> ServerT Raw m -> ServerT Raw n Source #

HasServer EmptyAPI context Source #

The server for an EmptyAPI is emptyAPIServer.

type MyApi = "nothing" :> EmptyApi server :: Server MyApi server = emptyAPIServer
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT EmptyAPI m :: Type Source #

Methods

route :: Proxy EmptyAPI -> Context context -> Delayed env (Server EmptyAPI) -> Router env Source #

hoistServerWithContext :: Proxy EmptyAPI -> Proxy context -> (forall x. m x -> n x) -> ServerT EmptyAPI m -> ServerT EmptyAPI n Source #

(TypeError (HasServerArrowTypeError a b) :: Constraint) => HasServer (a -> b :: Type) context Source #

This instance prevents from accidentally using '->' instead of :>

>>> serve (Proxy :: Proxy (Capture "foo" Int -> Get '[JSON] Int)) (error "...") ... ...No instance HasServer (a -> b). ...Maybe you have used '->' instead of ':>' between ...Capture' '[] "foo" Int ...and ...Verb 'GET 200 '[JSON] Int ... 
>>> undefined :: Server (Capture "foo" Int -> Get '[JSON] Int) ... ...No instance HasServer (a -> b). ...Maybe you have used '->' instead of ':>' between ...Capture' '[] "foo" Int ...and ...Verb 'GET 200 '[JSON] Int ... 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (a -> b) m :: Type Source #

Methods

route :: Proxy (a -> b) -> Context context -> Delayed env (Server (a -> b)) -> Router env Source #

hoistServerWithContext :: Proxy (a -> b) -> Proxy context -> (forall x. m x -> n x) -> ServerT (a -> b) m -> ServerT (a -> b) n Source #

ReflectMethod method => HasServer (NoContentVerb method :: Type) context Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (NoContentVerb method) m :: Type Source #

Methods

route :: Proxy (NoContentVerb method) -> Context context -> Delayed env (Server (NoContentVerb method)) -> Router env Source #

hoistServerWithContext :: Proxy (NoContentVerb method) -> Proxy context -> (forall x. m x -> n x) -> ServerT (NoContentVerb method) m -> ServerT (NoContentVerb method) n Source #

(HasServer a context, HasServer b context) => HasServer (a :<|> b :: Type) context Source #

A server for a :<|> b first tries to match the request against the route represented by a and if it fails tries b. You must provide a request handler for each route.

type MyApi = "books" :> Get '[JSON] [Book] -- GET /books :<|> "books" :> ReqBody Book :> Post '[JSON] Book -- POST /books server :: Server MyApi server = listAllBooks :<|> postBook where listAllBooks = ... postBook book = ...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (a :<|> b) m :: Type Source #

Methods

route :: Proxy (a :<|> b) -> Context context -> Delayed env (Server (a :<|> b)) -> Router env Source #

hoistServerWithContext :: Proxy (a :<|> b) -> Proxy context -> (forall x. m x -> n x) -> ServerT (a :<|> b) m -> ServerT (a :<|> b) n Source #

(HasContextEntry context (NamedContext name subContext), HasServer subApi subContext) => HasServer (WithNamedContext name subContext subApi :: Type) context Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (WithNamedContext name subContext subApi) m :: Type Source #

Methods

route :: Proxy (WithNamedContext name subContext subApi) -> Context context -> Delayed env (Server (WithNamedContext name subContext subApi)) -> Router env Source #

hoistServerWithContext :: Proxy (WithNamedContext name subContext subApi) -> Proxy context -> (forall x. m x -> n x) -> ServerT (WithNamedContext name subContext subApi) m -> ServerT (WithNamedContext name subContext subApi) n Source #

(TypeError (HasServerArrowKindError arr) :: Constraint) => HasServer (arr :> api :: Type) context Source #

This instance catches mistakes when there are non-saturated type applications on LHS of :>.

>>> serve (Proxy :: Proxy (Capture "foo" :> Get '[JSON] Int)) (error "...") ... ...Expected something of kind Symbol or *, got: k -> l on the LHS of ':>'. ...Maybe you haven't applied enough arguments to ...Capture' '[] "foo" ... 
>>> undefined :: Server (Capture "foo" :> Get '[JSON] Int) ... ...Expected something of kind Symbol or *, got: k -> l on the LHS of ':>'. ...Maybe you haven't applied enough arguments to ...Capture' '[] "foo" ... 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (arr :> api) m :: Type Source #

Methods

route :: Proxy (arr :> api) -> Context context -> Delayed env (Server (arr :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (arr :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (arr :> api) m -> ServerT (arr :> api) n Source #

HasServer api context => HasServer (HttpVersion :> api :: Type) context Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (HttpVersion :> api) m :: Type Source #

Methods

route :: Proxy (HttpVersion :> api) -> Context context -> Delayed env (Server (HttpVersion :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (HttpVersion :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (HttpVersion :> api) m -> ServerT (HttpVersion :> api) n Source #

(FramingUnrender framing, FromSourceIO chunk a, MimeUnrender ctype chunk, HasServer api context) => HasServer (StreamBody' mods framing ctype a :> api :: Type) context Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (StreamBody' mods framing ctype a :> api) m :: Type Source #

Methods

route :: Proxy (StreamBody' mods framing ctype a :> api) -> Context context -> Delayed env (Server (StreamBody' mods framing ctype a :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (StreamBody' mods framing ctype a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (StreamBody' mods framing ctype a :> api) m -> ServerT (StreamBody' mods framing ctype a :> api) n Source #

(AllCTUnrender list a, HasServer api context, SBoolI (FoldLenient mods), HasContextEntry (MkContextWithErrorFormatter context) ErrorFormatters) => HasServer (ReqBody' mods list a :> api :: Type) context Source #

If you use ReqBody in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of the type specified by ReqBody. The Content-Type header is inspected, and the list provided is used to attempt deserialization. If the request does not have a Content-Type header, it is treated as application/octet-stream (as specified in RFC 7231 section 3.1.1.5). This lets servant worry about extracting it from the request and turning it into a value of the type you specify.

All it asks is for a FromJSON instance.

Example:

type MyApi = "books" :> ReqBody '[JSON] Book :> Post '[JSON] Book server :: Server MyApi server = postBook where postBook :: Book -> Handler Book postBook book = ...insert into your db...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (ReqBody' mods list a :> api) m :: Type Source #

Methods

route :: Proxy (ReqBody' mods list a :> api) -> Context context -> Delayed env (Server (ReqBody' mods list a :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (ReqBody' mods list a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (ReqBody' mods list a :> api) m -> ServerT (ReqBody' mods list a :> api) n Source #

HasServer api context => HasServer (RemoteHost :> api :: Type) context Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (RemoteHost :> api) m :: Type Source #

Methods

route :: Proxy (RemoteHost :> api) -> Context context -> Delayed env (Server (RemoteHost :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (RemoteHost :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (RemoteHost :> api) m -> ServerT (RemoteHost :> api) n Source #

(KnownSymbol sym, FromHttpApiData a, HasServer api context, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods), HasContextEntry (MkContextWithErrorFormatter context) ErrorFormatters) => HasServer (QueryParam' mods sym a :> api :: Type) context Source #

If you use QueryParam "author" Text in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of type Maybe Text.

This lets servant worry about looking it up in the query string and turning it into a value of the type you specify, enclosed in Maybe, because it may not be there and servant would then hand you Nothing.

You can control how it'll be converted from Text to your type by simply providing an instance of FromHttpApiData for your type.

Example:

type MyApi = "books" :> QueryParam "author" Text :> Get '[JSON] [Book] server :: Server MyApi server = getBooksBy where getBooksBy :: Maybe Text -> Handler [Book] getBooksBy Nothing = ...return all books... getBooksBy (Just author) = ...return books by the given author...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (QueryParam' mods sym a :> api) m :: Type Source #

Methods

route :: Proxy (QueryParam' mods sym a :> api) -> Context context -> Delayed env (Server (QueryParam' mods sym a :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (QueryParam' mods sym a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (QueryParam' mods sym a :> api) m -> ServerT (QueryParam' mods sym a :> api) n Source #

(KnownSymbol sym, FromHttpApiData a, HasServer api context, HasContextEntry (MkContextWithErrorFormatter context) ErrorFormatters) => HasServer (QueryParams sym a :> api :: Type) context Source #

If you use QueryParams "authors" Text in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of type [Text].

This lets servant worry about looking up 0 or more values in the query string associated to authors and turning each of them into a value of the type you specify.

You can control how the individual values are converted from Text to your type by simply providing an instance of FromHttpApiData for your type.

Example:

type MyApi = "books" :> QueryParams "authors" Text :> Get '[JSON] [Book] server :: Server MyApi server = getBooksBy where getBooksBy :: [Text] -> Handler [Book] getBooksBy authors = ...return all books by these authors...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (QueryParams sym a :> api) m :: Type Source #

Methods

route :: Proxy (QueryParams sym a :> api) -> Context context -> Delayed env (Server (QueryParams sym a :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (QueryParams sym a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (QueryParams sym a :> api) m -> ServerT (QueryParams sym a :> api) n Source #

(KnownSymbol sym, HasServer api context) => HasServer (QueryFlag sym :> api :: Type) context Source #

If you use QueryFlag "published" in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of type Bool.

Example:

type MyApi = "books" :> QueryFlag "published" :> Get '[JSON] [Book] server :: Server MyApi server = getBooks where getBooks :: Bool -> Handler [Book] getBooks onlyPublished = ...return all books, or only the ones that are already published, depending on the argument...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (QueryFlag sym :> api) m :: Type Source #

Methods

route :: Proxy (QueryFlag sym :> api) -> Context context -> Delayed env (Server (QueryFlag sym :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (QueryFlag sym :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (QueryFlag sym :> api) m -> ServerT (QueryFlag sym :> api) n Source #

(KnownSymbol sym, FromHttpApiData a, HasServer api context, SBoolI (FoldRequired mods), SBoolI (FoldLenient mods), HasContextEntry (MkContextWithErrorFormatter context) ErrorFormatters) => HasServer (Header' mods sym a :> api :: Type) context Source #

If you use Header in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of the type specified by Header. This lets servant worry about extracting it from the request and turning it into a value of the type you specify.

All it asks is for a FromHttpApiData instance.

Example:

newtype Referer = Referer Text deriving (Eq, Show, FromHttpApiData) -- GET /view-my-referer type MyApi = "view-my-referer" :> Header "Referer" Referer :> Get '[JSON] Referer server :: Server MyApi server = viewReferer where viewReferer :: Referer -> Handler referer viewReferer referer = return referer
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Header' mods sym a :> api) m :: Type Source #

Methods

route :: Proxy (Header' mods sym a :> api) -> Context context -> Delayed env (Server (Header' mods sym a :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (Header' mods sym a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Header' mods sym a :> api) m -> ServerT (Header' mods sym a :> api) n Source #

HasServer api context => HasServer (IsSecure :> api :: Type) context Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (IsSecure :> api) m :: Type Source #

Methods

route :: Proxy (IsSecure :> api) -> Context context -> Delayed env (Server (IsSecure :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (IsSecure :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (IsSecure :> api) m -> ServerT (IsSecure :> api) n Source #

(HasServer api context, HasContextEntry context (AuthHandler Request (AuthServerData (AuthProtect tag)))) => HasServer (AuthProtect tag :> api :: Type) context Source #

Known orphan instance.

Instance details

Defined in Servant.Server.Experimental.Auth

Associated Types

type ServerT (AuthProtect tag :> api) m :: Type Source #

Methods

route :: Proxy (AuthProtect tag :> api) -> Context context -> Delayed env (Server (AuthProtect tag :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (AuthProtect tag :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (AuthProtect tag :> api) m -> ServerT (AuthProtect tag :> api) n Source #

HasServer api ctx => HasServer (Summary desc :> api :: Type) ctx Source #

Ignore Summary in server handlers.

Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Summary desc :> api) m :: Type Source #

Methods

route :: Proxy (Summary desc :> api) -> Context ctx -> Delayed env (Server (Summary desc :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (Summary desc :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (Summary desc :> api) m -> ServerT (Summary desc :> api) n Source #

HasServer api ctx => HasServer (Description desc :> api :: Type) ctx Source #

Ignore Description in server handlers.

Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Description desc :> api) m :: Type Source #

Methods

route :: Proxy (Description desc :> api) -> Context ctx -> Delayed env (Server (Description desc :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (Description desc :> api) -> Proxy ctx -> (forall x. m x -> n x) -> ServerT (Description desc :> api) m -> ServerT (Description desc :> api) n Source #

(KnownSymbol capture, FromHttpApiData a, HasServer api context, SBoolI (FoldLenient mods), HasContextEntry (MkContextWithErrorFormatter context) ErrorFormatters) => HasServer (Capture' mods capture a :> api :: Type) context Source #

If you use Capture in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of the type specified by the Capture. This lets servant worry about getting it from the URL and turning it into a value of the type you specify.

You can control how it'll be converted from Text to your type by simply providing an instance of FromHttpApiData for your type.

Example:

type MyApi = "books" :> Capture "isbn" Text :> Get '[JSON] Book server :: Server MyApi server = getBook where getBook :: Text -> Handler Book getBook isbn = ...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Capture' mods capture a :> api) m :: Type Source #

Methods

route :: Proxy (Capture' mods capture a :> api) -> Context context -> Delayed env (Server (Capture' mods capture a :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (Capture' mods capture a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Capture' mods capture a :> api) m -> ServerT (Capture' mods capture a :> api) n Source #

(KnownSymbol capture, FromHttpApiData a, HasServer api context, HasContextEntry (MkContextWithErrorFormatter context) ErrorFormatters) => HasServer (CaptureAll capture a :> api :: Type) context Source #

If you use CaptureAll in one of the endpoints for your API, this automatically requires your server-side handler to be a function that takes an argument of a list of the type specified by the CaptureAll. This lets servant worry about getting values from the URL and turning them into values of the type you specify.

You can control how they'll be converted from Text to your type by simply providing an instance of FromHttpApiData for your type.

Example:

type MyApi = "src" :> CaptureAll "segments" Text :> Get '[JSON] SourceFile server :: Server MyApi server = getSourceFile where getSourceFile :: [Text] -> Handler Book getSourceFile pathSegments = ...
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (CaptureAll capture a :> api) m :: Type Source #

Methods

route :: Proxy (CaptureAll capture a :> api) -> Context context -> Delayed env (Server (CaptureAll capture a :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (CaptureAll capture a :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (CaptureAll capture a :> api) m -> ServerT (CaptureAll capture a :> api) n Source #

(KnownSymbol realm, HasServer api context, HasContextEntry context (BasicAuthCheck usr)) => HasServer (BasicAuth realm usr :> api :: Type) context Source #

Basic Authentication

Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (BasicAuth realm usr :> api) m :: Type Source #

Methods

route :: Proxy (BasicAuth realm usr :> api) -> Context context -> Delayed env (Server (BasicAuth realm usr :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (BasicAuth realm usr :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (BasicAuth realm usr :> api) m -> ServerT (BasicAuth realm usr :> api) n Source #

HasServer api context => HasServer (Vault :> api :: Type) context Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Vault :> api) m :: Type Source #

Methods

route :: Proxy (Vault :> api) -> Context context -> Delayed env (Server (Vault :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (Vault :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Vault :> api) m -> ServerT (Vault :> api) n Source #

(KnownSymbol path, HasServer api context) => HasServer (path :> api :: Type) context Source #

Make sure the incoming request starts with "/path", strip it and pass the rest of the request path to api.

Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (path :> api) m :: Type Source #

Methods

route :: Proxy (path :> api) -> Context context -> Delayed env (Server (path :> api)) -> Router env Source #

hoistServerWithContext :: Proxy (path :> api) -> Proxy context -> (forall x. m x -> n x) -> ServerT (path :> api) m -> ServerT (path :> api) n Source #

(AllCTRender ctypes a, ReflectMethod method, KnownNat status, GetHeaders (Headers h a)) => HasServer (Verb method status ctypes (Headers h a) :: Type) context Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Verb method status ctypes (Headers h a)) m :: Type Source #

Methods

route :: Proxy (Verb method status ctypes (Headers h a)) -> Context context -> Delayed env (Server (Verb method status ctypes (Headers h a))) -> Router env Source #

hoistServerWithContext :: Proxy (Verb method status ctypes (Headers h a)) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Verb method status ctypes (Headers h a)) m -> ServerT (Verb method status ctypes (Headers h a)) n Source #

(AllCTRender ctypes a, ReflectMethod method, KnownNat status) => HasServer (Verb method status ctypes a :: Type) context Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Verb method status ctypes a) m :: Type Source #

Methods

route :: Proxy (Verb method status ctypes a) -> Context context -> Delayed env (Server (Verb method status ctypes a)) -> Router env Source #

hoistServerWithContext :: Proxy (Verb method status ctypes a) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Verb method status ctypes a) m -> ServerT (Verb method status ctypes a) n Source #

(MimeRender ctype chunk, ReflectMethod method, KnownNat status, FramingRender framing, ToSourceIO chunk a, GetHeaders (Headers h a)) => HasServer (Stream method status framing ctype (Headers h a) :: Type) context Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Stream method status framing ctype (Headers h a)) m :: Type Source #

Methods

route :: Proxy (Stream method status framing ctype (Headers h a)) -> Context context -> Delayed env (Server (Stream method status framing ctype (Headers h a))) -> Router env Source #

hoistServerWithContext :: Proxy (Stream method status framing ctype (Headers h a)) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Stream method status framing ctype (Headers h a)) m -> ServerT (Stream method status framing ctype (Headers h a)) n Source #

(MimeRender ctype chunk, ReflectMethod method, KnownNat status, FramingRender framing, ToSourceIO chunk a) => HasServer (Stream method status framing ctype a :: Type) context Source # 
Instance details

Defined in Servant.Server.Internal

Associated Types

type ServerT (Stream method status framing ctype a) m :: Type Source #

Methods

route :: Proxy (Stream method status framing ctype a) -> Context context -> Delayed env (Server (Stream method status framing ctype a)) -> Router env Source #

hoistServerWithContext :: Proxy (Stream method status framing ctype a) -> Proxy context -> (forall x. m x -> n x) -> ServerT (Stream method status framing ctype a) m -> ServerT (Stream method status framing ctype a) n Source #

methodRouter :: AllCTRender ctypes a => (b -> ([(HeaderName, ByteString)], a)) -> Method -> Proxy ctypes -> Status -> Delayed env (Handler b) -> Router env Source #

streamRouter :: forall ctype a c chunk env framing. (MimeRender ctype chunk, FramingRender framing, ToSourceIO chunk a) => (c -> ([(HeaderName, ByteString)], a)) -> Method -> Status -> Proxy framing -> Proxy ctype -> Delayed env (Handler c) -> Router env Source #